! ! Subroutine: LoadGrid ! callback: SelectPoint_Zoom ! SUBROUTINE LoadGrid !*************************************************************************** !* * !* THIS SUBROUTINE CREATES A DIALOG BOX THAT ALLOWS THE USER TO INPUT THE * !* .feg GRID FILE. THIS ROUTINE USES THE SYSTEM COMMON DIALOG ACCESS * !* THROUGH THE WINDOWS API. * !* * !*************************************************************************** use dflib use dfwin use Global implicit none type (t_openfilename) iofn logical(4) iRet integer(4) ierror integer(4) iUnit character(26*7) allfilters character(60) dlgtitle logical(4) checked ! added on March 10, 2005, needs to set to ZoomInOut mode external SelectPoint_Zoom ! update statusbar infor. call setstatusbar(0,'LoadGrid'C) call setstatusbar(1,' 'C) ! ALLFILTERS = 'Finite Element Grid files (*.feg)' // char(0) // '*.FEG' // char(0) // char(0) DLGTITLE = 'Input Grid File'C iofn%HWNDOWNER = GETHWNDQQ(QWIN$FRAMEWINDOW) iofn%HINSTANCE = NULL iofn%LPSTRFILTER = LOC(ALLFILTERS) iofn%LPSTRCUSTOMFILTER = NULL iofn%NMAXCUSTFILTER = NULL iofn%NFILTERINDEX = 1 iofn%LPSTRFILE = LOC(FEG_INP) iofn%NMAXFILE = LEN(FEG_INP) iofn%LPSTRFILETITLE = NULL iofn%NMAXFILETITLE = NULL iofn%LPSTRINITIALDIR = NULL iofn%LPSTRTITLE = LOC(DLGTITLE) iofn%FLAGS = NULL iofn%NFILEOFFSET = NULL iofn%NFILEEXTENSION = NULL iofn%LPSTRDEFEXT = NULL iofn%LCUSTDATA = NULL iofn%LPFNHOOK = NULL iofn%LPTEMPLATENAME = NULL !iofn%LSTRUCTSIZE = (BIT_SIZE(iofn%LSTRUCTSIZE) + & ! BIT_SIZE(iofn%HWNDOWNER) + & ! BIT_SIZE(iofn%HINSTANCE) + & ! BIT_SIZE(iofn%LPSTRFILTER) + & ! BIT_SIZE(iofn%LPSTRCUSTOMFILTER) + & ! BIT_SIZE(iofn%NMAXCUSTFILTER) + & ! BIT_SIZE(iofn%NFILTERINDEX) + & ! BIT_SIZE(iofn%LPSTRFILE) + & ! BIT_SIZE(iofn%NMAXFILE) + & ! BIT_SIZE(iofn%LPSTRFILETITLE) + & ! BIT_SIZE(iofn%NMAXFILETITLE) + & ! BIT_SIZE(iofn%LPSTRINITIALDIR) + & ! BIT_SIZE(iofn%LPSTRTITLE) + & ! BIT_SIZE(iofn%FLAGS) + & ! BIT_SIZE(iofn%NFILEOFFSET) + & ! BIT_SIZE(iofn%NFILEEXTENSION) + & ! BIT_SIZE(iofn%LPSTRDEFEXT) + & ! BIT_SIZE(iofn%LCUSTDATA) + & ! BIT_SIZE(iofn%LPFNHOOK) + & ! BIT_SIZE(iofn%LPTEMPLATENAME))/8 ! 8 bit = 1 Byte !N.B. When converting this program to the x64 platform, the above code stopped working; ! I found a hint on the web, and replaced it with: iofn%LSTRUCTSIZE = SizeOf(iofn) if (.not.(GridLoaded)) then iRet = GETOPENFILENAME(iofn) CALL COMDLGER(ierror) ! CHECK TO SEE IF THE OK BUTTON HAS BEEN PRESSED if(iRet .and. (ierror == 0)) then call Read_Grid ! After successful Read_Grid, LOGICAL :: gridLoaded in MODULE Global is set .TRUE. if (gridLoaded) then ! adjust window title ! enter new frame window title iUnit = getactiveqq() iRet = SetWindowText(GetHwndQQ(iUnit), TRIM(feg_inp) // CHAR(0)) call DrawGrid if(BaseLoaded) call DrawBase ! Added on March 10, 2005 ! set to default zoom in/out with 2.02 scale factor when new grid is loaded iUnit = getactiveqq() iRet = REGISTERMOUSEEVENT (iUnit, MOUSE$LBUTTONDOWN, SelectPoint_Zoom) ZoomInOut_checked = .true. end if endif else call error3 end if ! update statusbar infor. call setstatusbar(0, 'Ready'C) call setstatusbar(1, ' 'C) return end subroutine LoadGrid