Interface to Windows Dialog Boxes

How can one call a Windows dialog box for setting the name and path of files to read from and write to?
Thank you for the help.

Regards,
Bob

1 Like

Hi Bob,

Is your application written in Fortran, and if yes, what library are you using to create Windows GUI elements?

I don’t think I have the knowledge to help, but as many details as you can provide will be helpful to whomever can answer this.

Dear @Robert,
in Linux you could use zenity (https://en.wikipedia.org/wiki/Zenity) from command line, and therefore call it in Fortran 2008 using CALL SYSTEM() (https://gcc.gnu.org/onlinedocs/gfortran/SYSTEM.html). I have found that version for the Windows world: https://github.com/maravento/winzenity

You could also use our https://github.com/vmagnin/gtk-fortran project, but it would be like using a sledgehammer to kill a fly (I am not sure that expression is commonly used in English, but you should understand what I mean…)

1 Like

Or the standard-conforming (>= Fortran 2008) execute_command_line() instead of system(), I guess.

1 Like

You want the Windows API routines GetOpenFileName and GetSaveFileName. You pass these a data structure with details of what you are looking for (default file types, default folder, etc.) and it does the work of creating and displaying the file selection dialog, returning to you the file specification. Intel Fortran provides a worked example in its Samples Bundle.

Intel Fortran, and I think some other Windows compilers, provides modules with declarations for these routines.

3 Likes

Ah yes, sorry, CALL SYSTEM() is a GNU extension, as specified in the GCC doc.

This is what you want, but you need VS+Intel Fortran:

subroutine OpenNewFile( hWnd )
use Constant
use Toolbar

integer , parameter :: FILE_LEN = 80 !每次读入的字符长度
type(T_OPENFILENAME) :: OpenFN !定义OPENFILENAME结构体
integer4 :: hWnd !OPEN对话框的父窗口句柄
integer
4 :: hInstance !定义当前实例句柄
character256 :: szFilter !定义文件过滤条件
character
256 :: szFile !定义文件名(不含路径)
character256 :: szFileTitle !定义文件名(含路径)
character
256 :: lpszTitle !对话框的标题
character256 :: lpszDefExt !文件的默认扩展名
integer
4 :: hFile !文件的句柄
type(T_OFSTRUCT) :: OfStruct1 !文件的相关信息的结构体
integer :: wStyle !文件的行为状态:读还是写?
character500 :: lpStrPtr !文件名(转换而来)
character
(FILE_LEN) :: FileBuf !存放读入的数据

integer iret,i
integer cBufLen
logical ret

szFile = ".txt"C
szFileTitle = " "C
lpszTitle= "Open a File"C
lpszDefExt= "
.txt"C
iret = lstrcpy(szFilter,"Text Files (.TXT)|.TXT|All Files (.)|.||"C)
call ConvertFilterString(szFilter)

OpenFN%lStructSize = 76 !sizeof(OpenFN)
OpenFN%hwndOwner = hWnd
OpenFN%hInstance = hInstance
OpenFN%lpstrFilter = LOC(szFilter)
OpenFN%lpstrCustomFilter = NULL
OpenFN%nMaxCustFilter = 0
OpenFN%nFilterIndex = 1
OpenFN%lpstrFile = LOC(szFile)
OpenFN%nMaxFile = 256
OpenFN%lpstrFileTitle = LOC(szFileTitle)
OpenFN%nMaxFileTitle = 256
OpenFN%lpstrInitialDir = NULL
OpenFN%lpstrTitle = LOC(lpszTitle)
OpenFN%nFileOffset = 0
OpenFN%nFileExtension = 0
OpenFN%lpstrDefExt = LOC(lpszDefExt)
OpenFN%lCustData = 0

ret = GetOpenFileName( OpenFN )
if ( IAND( OpenFN%Flags , OFN_READONLY ) .ne. 0 ) then
wStyle = OF_READ
else
wStyle = OF_READWRITE
end if

!打开文件
ret = convertFtoCstring(lpStrPtr,OpenFN%lpstrFile)
hFile = OpenFile(lpStrPtr,OfStruct1, wStyle )

!读文件
iret=GetDC(hWnd) !为了获得设备描述表
do i=1,3
cBufLen = lread( hFile, LOC(FileBuf), 10 ) !后面的数字10表示一次读入的字符个数
ret=TextOut(iret,100,100+100*i,FileBuf,LEN(FileBuf)) !输出新的字母
enddo
iret=ReleaseDC(hWnd,iret)

iret = lclose( hFile )
return
end

Simply Fortran for Windows provides AppGraphics module which contains
dlgopenfile (filename, maskdesc, mask, title) and dlgsavefile functions.

@lm_lxt @sblionel Thank you for the code. (I ran the in-line comments through Google translate and the translation worked well.) What in your code requires VS+Intel Fortran? Are GetOpenFileName and GetSaveFileName modules that get linked into the executable, or are these DLL files that get called at runtime? And where do I get these modules or DLLs?

@milancurcic My application is written in Fortran. I am not calling any Windows GUIs. (I don’t know how to do that.) The program reads from a text file and writes to a text file. But having a Windows GUI for getting the input and output file names would be nice.

@vmagnin, @pcosta Thank you for the suggestion to look into Zenity. I did not know of this and I will check it out.

@Dobrodzieju Your solution looks to be the the easiest, but I don’t have Simply Fortran. But your solution raises a point. It would be great if the equivalent of dlgopenfile() and dlgsavefile() be included in the Fortran standard library mentioned over at fortran-lang.org/community/.

See also https://github.com/kvaps/zenity-windows/ which seems based on a more recent version of zenity (although the github deposit has not been updated for 4 years…)

Concerning dlgopenfile() and dlgsavefile() or equivalent, I doubt they could be included in the Fortran standard library because it’s too dependent on the operating system.

Well there is a file system operation module in development (see here) which aims to work across operating systems. The related issues are:

While it might be difficult to get it to work across operating systems, a simple file dialog can be a very effective way to bring a program closer to the users. Recently, I did a project in MATLAB where I used the uigetfile function (“Open file selection dialog box”). In the first iteration of the program I had a command-line interface, but the users (fellow scientists and master students), were not that happy to work with it. As soon as I added the file selection dialog box, they found it much more convincing and easier to use. The purpose of the program was to measure the surface tension of a liquid drop from a set of images and produce a small text report. I even got asked if I could improve the code/user experience further for them.

1 Like

@Robert Intel Fortran is not required to use the Windows API routines. It does, however, include predefined declarations that make it easier. All that is necessary is a compiler that supports the STDCALL calling mechanism (on 32-bit only, not an issue on 64-bit), a declaration of the appropriate derived type, and linking against comdlg32.lib (part of the Windows SDK).

The code sample from @lm_lxt requires some modules (Constant and Toolbar) that they must have created themselves, as those are not part of Intel Fortran. (Visual Studio is also not required to use the Windows API.)

Here is the complete Intel code sample (I can’t get the whole thing to format as code):
! ==============================================================
!
! SAMPLE SOURCE CODE - SUBJECT TO THE TERMS OF SAMPLE CODE LICENSE AGREEMENT,
! http://software.intel.com/en-us/articles/intel-sample-source-code-license-agreement/
!
! Copyright 2016 Intel Corporation
!
! THIS FILE IS PROVIDED “AS IS” WITH NO WARRANTIES, EXPRESS OR IMPLIED, INCLUDING BUT
! NOT LIMITED TO ANY IMPLIED WARRANTY OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
! PURPOSE, NON-INFRINGEMENT OF INTELLECTUAL PROPERTY RIGHTS.
!
! =============================================================
!
program fileopen
use comdlg32
implicit none

! Declare structure used to pass and receive attributes
!
type(T_OPENFILENAME) ofn

! Declare filter specification.  This is a concatenation of
! pairs of null-terminated strings.  The first string in each pair
! is the file type name, the second is a semicolon-separated list
! of file types for the given name.  The list ends with a trailing
! null-terminated empty string.
!
character(*),parameter :: filter_spec = &
  "Text Files"C//"*.txt"C// &
  "Fortran Files"C//"*.f90;*.f"C//""C

! Declare string variable to return the file specification.
! Initialize with an initial filespec, if any - null string
! otherwise
!
character(512) :: file_spec = ""C
integer status,ilen
ofn%lStructSize = SIZEOF(ofn)
ofn%hwndOwner = NULL
ofn%hInstance = NULL  ! For Win32 applications, you
                      ! can set this to the appropriate
                      ! hInstance
                      !
ofn%lpstrFilter = loc(filter_spec)
ofn%lpstrCustomFilter = NULL
ofn%nMaxCustFilter = 0
ofn%nFilterIndex = 1 ! Specifies initial filter value
ofn%lpstrFile = loc(file_spec)
ofn%nMaxFile = sizeof(file_spec)
ofn%nMaxFileTitle = 0
ofn%lpstrInitialDir = NULL  ! Use Windows default directory
ofn%lpstrTitle = loc(""C)
ofn%Flags = OFN_PATHMUSTEXIST
ofn%lpstrDefExt = loc("txt"C)
ofn%lpfnHook = NULL
ofn%lpTemplateName = NULL

! Call GetOpenFileName and check status
! 
status = GetOpenFileName(ofn)
if (status .eq. 0) then
  type *,'No file name specified'
else
  ! Get length of file_spec by looking for trailing NUL
  ilen = INDEX(file_spec,CHAR(0))
  type *,'Filespec is ',file_spec(1:ilen-1)
  ! Example of how to see if user said "Read Only"
  !  
  if (IAND(ofn%flags,OFN_READONLY) /= 0) &
    type *,'Readonly was requested'
end if
end program fileopen

The Intel example uses some extensions, such as LOC(), SIZEOF() and ""C (NUL-terminated C strings), Many compilers support these, but if yours doesn’t they aren’t hard to replicate in standard Fortran. If your compiler does not provide an interface for the function, a declaration of the OPENFILENAME type and constants such as OFN_PATHMUSTEXIST, you’ll have to write these yourself. The Windows API documentation has the necessary information you’ll need to do so.

Alternatively you can use DISLIN library, which nowadays is free. It provides
some “widget” routines, also for the file system operations, as far as I remember.
And it is cross-platform.

@Sblionel Being a newbie to windows API, I have basic questions regarding the statements:
use comdlg32
status = GetOpenFileName(ofn)

I Googled comdlg32 and see that this is the Common Dialog Box Library. And I found comdlg32.dll in the c:\windows\system32 folder.

Am I correct that the statement use comdlg32 tells the fortran compiler to bring in this dll from the system32 folder? I assume the compiler knows to look there by default. I also assume GetOpenFileName() is a function contained within comdlg32.dll, and that is how the compiler/linker knows about GetOpenFileName(). Correct?

When my program runs on a second computer, does the second computer need it’s own copy of comdlg32.dll in order to run my program, or is everything packaged into my program’s exe.

Thank you.

Every Windows system has comdlg32.dll. You don’t link to DLLs, you link to LIBs (DLL export libraries). You get the .LIB only if you have the WIndows SDK installed.

The compiler knows about GetOpenFileName() only if there is a Fortran declaration of it (typically an INTERFACE block. This will declare the Fortran name (which is case-insensitive), the external name (case-sensitive), and on 32-bit, that it is STDCALL. It will also declare its arguments. In Intel Fortran, you get this if you USE COMDLG32. Other compilers may do things differently. If your compiler doesn’t have a declaration, you can write your own, but you do need to know how to translate the C description from the Windows API library into Fortran.

You don’t need anything extra to run on a different Windows system - the DLL is an integral part of Windows and has been “forever”.

The reply from @sblionel is professional.

@Robert: I just gave you one example. You can try it out with the QuickWin/Windowing project.

I think the calling to the Win APIs is a bit of a hassle because you might need 100 lines of Fortran code to create a simple GUI. The same task requires only 10 lines of code in Python or Tcl. So Python/Tcl + Fortran might be a good choice.

I do not agree that calling Python or Tcl is any less of a hassle than the 30-odd (not 100) lines it takes to use the Windows API. Calling out to Python/Tcl/etc. means needing a second install, plus creating a way to get the information to and from the external language.

Even if you wanted to create a full-blown Windowing application, there are Fortran libraries available (free and paid) to make it easier.

FWIW, I rewrote the Intel example to be self-contained and Fortran 2018-compliant (except for the one line of directive). I have tested this using Intel Fortran 2020 Update 4 for both 32 and 64 bit targets. (Earlier versions have a bug that make the filters not work on x64.) Even with my declaring the large data structure, it’s only 76 lines.

program GetFile
use, intrinsic :: iso_c_binding
implicit none

type, bind(C) :: OPENFILENAME_T
   integer(C_INT32_T) lStructSize 
   integer(C_INTPTR_T) hwndOwner 
   integer(C_INTPTR_T) hInstance  
   type(C_PTR) lpstrFilter
   type(C_PTR) lpstrCustomFilter 
   integer(C_INT32_T) nMaxCustFilter
   integer(C_INT32_T) nFilterIndex
   type(C_PTR) lpstrFile
   integer(C_INT32_T) nMaxFile
   type(C_PTR) lpstrFileTitle
   integer(C_INT32_T) nMaxFileTitle
   type(C_PTR) lpstrInitialDir 
   type(C_PTR) lpstrTitle
   integer(C_INT32_T) Flags
   integer(C_INT16_T) nFileOffset 
   integer(C_INT16_T) nFileExtension
   type(C_PTR) lpstrDefExt
   integer(C_INTPTR_T) lCustData
   type(C_FUNPTR) lpfnHook 
   type(C_PTR) lpTemplateName
   integer(C_INTPTR_T) pvReserved;
   integer(C_INT32_T)  dwReserved;
   integer(C_INT32_T)  FlagsEx;
end type OPENFILENAME_T

interface
    function GetOpenFileName (Arg1) bind(C,name="GetOpenFileNameA")
    import
    !DIR$ ATTRIBUTES STDCALL :: GetOpenFileName
    integer(C_INT32_T) :: GetOpenFileName
    type(OPENFILENAME_T), intent(INOUT) :: Arg1
    end function GetOpenFileName   
end interface

type(OPENFILENAME_T) :: ofn
character(100), target :: filter_spec = &
 "Text Files"//C_NULL_CHAR//"*.txt"//C_NULL_CHAR// &
 "Fortran Files"//C_NULL_CHAR//"*.f90;*.f"//C_NULL_CHAR//C_NULL_CHAR
character(512), target :: file_spec = C_NULL_CHAR
character(7), target :: title = "Select"//C_NULL_CHAR
character(4), target :: DefExt = "txt"//C_NULL_CHAR
integer(C_INT32_T) :: status, ilen
integer(C_INT32_T), parameter :: NULL = 0, OFN_PATHMUSTEXIST = INT(Z'0800')

ofn%lStructSize = C_SIZEOF(ofn)
ofn%hwndOwner = NULL
ofn%hInstance = NULL  !
ofn%lpstrFilter = C_LOC(filter_spec)
ofn%lpstrCustomFilter = C_NULL_PTR
ofn%nMaxCustFilter = 0
ofn%nFilterIndex = 1 ! Specifies initial filter value
ofn%lpstrFile = C_LOC(file_spec)
ofn%nMaxFile = LEN(file_spec)-1
ofn%nMaxFileTitle = 0
ofn%lpstrInitialDir = C_NULL_PTR  ! Use Windows default directory
ofn%lpstrTitle = C_LOC(title)
ofn%Flags = OFN_PATHMUSTEXIST
ofn%lpstrDefExt = C_LOC(DefExt)
ofn%lpfnHook = C_NULL_FUNPTR
ofn%lpTemplateName = C_NULL_PTR

status = GetOpenFileName(ofn)
if (status == 0) then
  print *,'No file name specified'
else
  ! Get length of file_spec by looking for trailing NUL
  ilen = INDEX(file_spec,C_NULL_CHAR)
  print *,'Filespec is ',file_spec(1:ilen-1)
end if
  
end program GetFile
3 Likes

@sblionel Thank you very much for the code post. The GetOpenFileName works very nicely. It gives my program a great looking Windows standard dialog box for selecting input files and, with not many changes, for selecting output files.

3 Likes

I looked at the simplest GUI example, QuickWin requires about 30 lines of code, Windowing requires about 100 lines of code, but Tcl only requires 2 lines. If it is a simple data exchange, the pipe mode maybe a fine choice, only need to add about 10-15 lines of Tcl code on the basis of 2 lines of code.

Of course, the second language requires more time from the user, which is a problem.

1 Like