Resolve system temporary path on Windows

Hi. I would like to write to a temporary file in the system TEMP directory. The trouble is that I’m unable to resolve the system’s path.
I’ve tried

program main
implicit none
character(len=255) :: tempFile
tempFile = "%TEMP%\k3c09d.tmp"
print *, tempFile
end program main

I’ve expected “C:\Users\username\AppData\Local\Temp\k3c09d.tmp”, but the output is simply “%TEMP%\k3c09d.tmp”. :smile:. Thanks.

1 Like

What I think you’re looking for is the intrinsic subroutine GET_ENVIRONMENT_VARIABLE. Take a look at e.g https://gcc.gnu.org/onlinedocs/gfortran/GET_005fENVIRONMENT_005fVARIABLE.html to see how it works.

4 Likes

Hi @Dave. Yes, thank you. Problem solved :+1:

2 Likes

Does not STATUS="SCRATCH" do what you want?

1 Like

STATUS=“SCRATCH” results in a file that is deleted when the program terminates. If one needs a scratch file that is accessed multiple times from one or more programs before it is deleted, than the fortran model does not fit. Another quirk of the fortran scratch model is that it cannot be associated with a file name, only with a unit number, so that further makes it difficult to share a scratch file over multiple runs.

1 Like

I do not use MS Windows, so I don’t know how it works. However, I do remember that VAX/VMS had logical names that could be used in filenames. Those logical names were automatically translated during the OPEN() statement, and (if I remember correctly) a subsequent INQUIRE() statement revealed the full file name with the logical name substituted.

1 Like

Windows does not have that baked into the file system. If your path is being interpreted by the CLI, you can use environment variables as sort-of macros. CMD uses %varname%, PowerShell is a bit more complex. You can do your own expansion of the % syntax, though, using the ExpandEnvironmentStrings Windows API.

1 Like

In the case of OP, it appears a hack with Fortran intrinsic GET_ENVIRONMENT_VARIABLE was adequate.

However if one wants to pursue more detailed IO and in a safer manner, then the option will be to make use of vendor-provided APIs and to investigate calling them from Fortran.

In the case of Microsoft Windows OS, the APIs would be 'GetTempPath, GetTempFileName`, etc. as described at the Microsoft site e.g., GetTempFileName function (winbase.h) - Win32 apps | Microsoft Learn. These APIs are based on Microsoft C/C++ and are mostly compatible with Fortran facility toward interoperability with a C companion processor, in this case Microsoft C/C++ compiler.

One can then set up Fortran interfaces to these APIs and work with them in Fortran code, here’s a rather simple almost trivial but complete example of writing to a temporary file in the TEMP directory on Windows:

module clib_m
! C standard library functions

   use, intrinsic :: iso_c_binding, only : c_size_t, c_char

   interface
      function strlen(s) result(slen) bind(C, name="strlen")
      ! <string.h>: strlen

         import :: c_size_t, c_char

         character(kind=c_char, len=1), intent(in) :: s(*)
         ! Function result
         integer(c_size_t) :: slen

       end function

    end interface

end module 

module IWinAPI_m

   use, intrinsic :: iso_c_binding, only : DWORD => c_int, UINT => c_int, c_char, c_null_char

   integer(DWORD), parameter :: MAX_PATH = 260

   interface

      function GetTempPath( nBufferLength, lpBuffer ) result(iret) bind(C, name="GetTempPathA")
      !DIR$ ATTRIBUTES STDCALL :: GetTempPath
      
      ! c.f. https://docs.microsoft.com/en-us/windows/win32/api/fileapi/nf-fileapi-gettemppatha
      ! Microsoft API
      ! DWORD GetTempPathA(DWORD nBufferLength, LPSTR lpBuffer);
         import :: DWORD, c_char

         ! Argument list
         integer(DWORD), intent(in), value :: nBufferLength
         character(kind=c_char, len=1), intent(inout) :: lpBuffer(*)
         ! Function result
         integer(DWORD) :: iret

      !GCC$ ATTRIBUTES STDCALL :: GetTempPath 
      end function

      function GetTempFileName( lpPathName, lpPrefixString, uUnique, lpTempFileName )               &
         result(iret) bind(C, name="GetTempFileNameA")
      !DIR$ ATTRIBUTES STDCALL :: GetTempFileName
      
      ! c.f. https://docs.microsoft.com/en-us/windows/win32/api/winbase/nf-winbase-gettempfilename
      ! Microsoft API
      ! UINT GetTempFileName( LPCTSTR lpPathName, LPCTSTR lpPrefixString, UINT uUnique,
      !                       LPTSTR lpTempFileName);
         import :: UINT, c_char

         ! Argument list
         character(kind=c_char,len=1), intent(in)    :: lpPathName(*)
         character(kind=c_char,len=1), intent(in)    :: lpPrefixString(*)
         integer(UINT), intent(in), value            :: uUnique
         character(kind=c_char,len=1), intent(inout) :: lpTempFileName(*)
         ! Function result
         integer(UINT) :: iret

      !GCC$ ATTRIBUTES STDCALL :: GetTempFileName 
      end function

   end interface 

end module
 
   use IWinAPI_m
   use clib_m, only : strlen

   integer(DWORD) :: irc
   character(kind=c_char, len=:), allocatable :: temp_path, temp_file, prefix_string
   integer(UINT) :: lun

   allocate ( character(kind=c_char, len=MAX_PATH+1) :: temp_path )
   irc = GetTempPath( len(temp_path), temp_path )
   if ( irc > 0 ) then
      temp_path = temp_path(1:irc) 
      print *, "Temporary path name: ", temp_path
   else
      print *, "GetTempPath call failed."
   end if

   ! Proceed assuming temp path name is less than MAX_PATH-14
   prefix_string = c_char_"FOR" // c_null_char
   lun = 0
   allocate ( character(kind=c_char, len=MAX_PATH+1) :: temp_file )
   irc = GetTempFileName( temp_path, prefix_string, lun, temp_file )
   if ( irc > 0 ) then
      temp_file = temp_file(1:strlen(temp_file)) 
      print *, "Temporary file name: ", temp_file
   else
      print *, "GetTempFileName call failed."
   end if

   open( newunit=lun, file=temp_file, iostat=irc )
   if ( irc /= 0 ) then
      print *, "Error opening temporary file."
      stop
   end if

   write( lun, fmt=*, iostat=irc ) "Hello World!"
   if ( irc /= 0 ) then
      print *, "Error opening temporary file."
      stop
   end if
   
   close( lun, iostat=irc )
   if ( irc /= 0 ) then
      print *, "Error closing temporary file."
      stop
   end if

end 

Here’s the execution output using gfortran for a Guest account on Windows; note the output of the temporary file is displayed separately.

C:\temp>gfortran -Wall -Wno-maybe-uninitialized -std=f2018 p.f90 -o gcc-p.exe

C:\temp>gcc-p.exe
Temporary path name: C:\Users\Guest\AppData\Local\Temp
Temporary file name: C:\Users\Guest\AppData\Local\Temp\FORF091.tmp

C:\temp>type “C:\Users\Guest\AppData\Local\Temp\FORF091.tmp”
Hello World!

C:\temp>

Note also the above example relies on the Windows API to create as well as name the temporary file in the appropriate temporary folder which is how the vendor would suggest the applications on Windows work with such temporary files.

1 Like

Hi @FortranFan. Thanks for the detailed answer. I really appreciate it. :+1:

1 Like