Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Modeless dialog box

yuric
Beginner
384 Views
One thing i don't have clear is the use of modeless dialogs without resorting to the fortran windows app. environment.

Assume i have a quickwin project which contains various dialogs activated by a frame-window callback routine such as:


!-------------Frame window----

LOGICAL(KIND=4) FUNCTION INITIALSETTINGS
USE DFLIB
IMPLICIT NONE
CHARACTER(LEN=50)mname
integer(2) iret
INTEGER(4) mnum
RECORD /qwinfo/qw

EXTERNAL call_dialog

qw%type = QWIN$MAX
iret = SETWSIZEQQ(QWIN$FRAMEWINDOW,qw)

...

mnum = 1
mname = '&My Dialog'C
IF (.NOT.APPENDMENUQQ &(mnum,$menuenabled,mname,call_dialog)) THEN
INITIALSETTINGS = .FALSE.
RETURN
END IF

INITIALSETTINGS = .TRUE.
RETURN
END

!------------Call-back routine

Subroutine call_dialog(checked)
use dflib
use DFLOGM

logical checked
external My_Dlg

Call My_dlg()

end subroutine call_dialog

!---- display dialog-------------

subroutine My_dlg()

use DFLOGM

type(dialog) dlg
include 'resource.fd'
...

if (.not. DlgInit(IDD_copump_panel, dlg)) then
write (*,*) "Error: dialog not found"
else

...

retint = DlgModal(dlg)
Call DlgUninit(dlg)

end if
end subroutine

!-------------------------------


Some routines in the projects also open windows with

OPEN (number, file='user',title='my title')
...
CLOSE(number)

and put in there some graphical output (for example, the output from SCIGRAPH)

My first question is: what defines a project like this as a "QuickWin" project? I just see it's a project that uses DFLOGM. However, when i started using the fortran app wizard, i started it as a multiple-window "QuickWin project". What are the ripercussions of that initial choice?

The reason i ask is that QuickWin apps. are said to be unable to handle modeless dialogs. But i have seen examples of modeless dialogs handled through DFLOGM.
What exactly does make a project unable to have modeless dialogs?

How can i incorporate a modeless dialog in my project (shortly described above) without rebuilding everything into a Fortran Windows application?

Thanks so much for the much needed inputs!

yuric



0 Kudos
1 Reply
Jugoslav_Dujic
Valued Contributor II
384 Views
The statement that QuickWin cannot handle modeless dialogs is only half true. What determines ability to handle modeless dialogs is presence of a message loop. Since any Win32 GUI application has to have a message loop*, QuickWin has it too, but it's hidden in qwin.lib. QuickWin apps have two threads -- primary (where the callbacks are executed, and which is driven by that message loop) and secondary (where PROGRAM is executed, which doesn't have a message loop unless you write one). That's the reason why you can end the PROGRAM with an endless loop -- the primary thread actually does the job.

Thus, modeless dialogs work in QuickWin if called from a callback function. The only flaw is that keyboard navigation does not work, since it requires presence of IsDialogMessage() function in message loop.

IIRC, QuickWin project is actually determined only by /libs:qwin switch, which instructs the compiler to link in QuickWin's startup code, which is different from other types of projects.

Just FYI, here's the message loop which is supposed to be general-purpose (i.e. to handle an arbitrary number of modeless dialogs with keybord navigation) -- but there's no place where you can put it in a QuickWin project:

DO WHILE(GetMessage(Mesg,NULL,0,0).NEQV..FALSE.)
      hActive=GetActiveWindow()
      iStyle=GetWindowLong(hActive,GWL_EXSTYLE)
      IF (IAND(iStyle,WS_EX_CONTROLPARENT).NE.0) THEN
            IF (.NOT.IsDialogMessage(hActive,Mesg)) THEN
                  iSt=TranslateMessage(Mesg)
                  iSt=DispatchMessage(Mesg)
            END IF
      ELSE
            iSt=TranslateMessage(Mesg)
            iSt=DispatchMessage(Mesg)
      END IF
END DO


Jugoslav


* If you wonder about dialog-based applications, DialogBox(Param) function has a built-in message loop.
0 Kudos
Reply