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

GETFILEINFOQQ

PASeeger
Beginner
731 Views
GETFILEINFOQQ
This code worked in the olden days, but since I am now compiling in x64 I have to use FILE$INFOI8 in place of FILE$INFO. (See p. 1511 of the Fortran 18 Guide and Reference document.) But I now get this message:

Compiler error #6284: There is no matching specific function for this generic function reference.   [GETFILEINFOQQ]
 
What have I done wrong? There is a little confusion in the document, which defined the derived type FILE$INFOI8 as if the name was still FILE$INFO, but I assume that is just a typo. Has that been fixed or changed in the new documentation?
 
Here is a truncated copy of the relevant portion of the code. I marked the line where the error occurs with -->.  I also uploaded the complete subroutine that fails, but I don't expect anyone to read it!
 

Thanks - Phil Seeger 

      INCLUDE  'BuildData.inc'

     COMMON /Build_Data/ NSURF, NREG, NPARAM, idum, NAME, SURF,

     &                    ICONNCT, REG, INDX, PARAM, DataPath
C  'DataPath' determined at Initialization, and saved in common
    ...
      TYPE(FILE$INFOI8) DIR_INFO
      INTEGER*8 hndl8
      INTEGER*4 NN
      DATA SourcePath, LenPath/' ', 0/
      SAVE SourcePath, LenPath
    ...
         CASE ('S')
            SourcePath = DataPath(1:LEN_TRIM(DataPath))//'Tables\'
            LenPath = LEN_TRIM(SourcePath)
            FLAG = DLGSET(DBOX, 1000+I, 100, DLG_NUMITEMS)
            N = 0
!           Loop to find all possible Source Table (*.tbl) files
            hndl8 = FILE$FIRST
            DO WHILE (hndl8.NE.FILE$LAST .AND. hndl8.NE.FILE$ERROR)
  -->         NN = GETFILEINFOQQ(SourcePath(1:LenPath)//'*.tbl',
     &                            DIR_INFO, hndl8)
               IF (NN .GT. 0) THEN
C                 Add file name to a COMBOBOX for possible selection
                  N = N + 1
                  FLAG = DLGSET(DBOX, 1000+I, DIR_INFO%NAME(1:NN), N)
               END IF
            END DO
            FLAG = DLGSET(DBOX, 1000+I, N, DLG_NUMITEMS)
            FLAG = DLGSET(DBOX, 1000+I, STR(I), DLG_STATE)
         END SELECT
 
0 Kudos
1 Solution
mecej4
Honored Contributor III
731 Views

The source file that you attached cannot be compiled unless you also provide the include files named in it. I suspect that the error lies in the type declaration of handle-type variables that are passed to Windows routines through IFPORT. If you ran the 32-bit compiler on the code that you provided (and from which you took the excerpts that you posted inline), the compiler would complain (Error #6284) that INTEGER(8) variables are not suitable for use as Windows handle variables in 32-bit mode. Conversely, INTEGER(4) variables are not proper for handles in Windows 64.

You can use the same source code for 32-bit and 64-bit Windows if you declare the type of handles as INTEGER(KIND=INT_PTR_KIND( )). The following short example code displays information regarding files with the extension '.F90' in a particular directory. It runs with IFort 18.0.3, 32 or 64 bit.

C     List all files in a specified directory that have the extension ".f90"
      program xseeger
	  use ifport
	  implicit none
      TYPE(FILE$INFO) DIR_INFO
      INTEGER(KIND=INT_PTR_KIND( )) hndl
      INTEGER NN,n,i
      CHARACTER(20) SourcePath
C
      SourcePath = 's:\lang\'
      N = 0
      hndl = FILE$FIRST
	  print *,'   FILE             LENGTH'
      DO 
         NN = GETFILEINFOQQ(trim(SourcePath)//'*.f90',DIR_INFO, hndl)
	     IF(hndl.eq.FILE$LAST.or.hndl.eq.FILE$ERROR.or.NN.eq.0)exit
         N = N + 1
		 write(*,'(I2,2x,A15,2x,I6)')N,dir_info%name,dir_info%length
      END DO
      end program

The IFort documentation page on GETFILEINFOQQ also contains a slightly longer example.

View solution in original post

0 Kudos
2 Replies
mecej4
Honored Contributor III
732 Views

The source file that you attached cannot be compiled unless you also provide the include files named in it. I suspect that the error lies in the type declaration of handle-type variables that are passed to Windows routines through IFPORT. If you ran the 32-bit compiler on the code that you provided (and from which you took the excerpts that you posted inline), the compiler would complain (Error #6284) that INTEGER(8) variables are not suitable for use as Windows handle variables in 32-bit mode. Conversely, INTEGER(4) variables are not proper for handles in Windows 64.

You can use the same source code for 32-bit and 64-bit Windows if you declare the type of handles as INTEGER(KIND=INT_PTR_KIND( )). The following short example code displays information regarding files with the extension '.F90' in a particular directory. It runs with IFort 18.0.3, 32 or 64 bit.

C     List all files in a specified directory that have the extension ".f90"
      program xseeger
	  use ifport
	  implicit none
      TYPE(FILE$INFO) DIR_INFO
      INTEGER(KIND=INT_PTR_KIND( )) hndl
      INTEGER NN,n,i
      CHARACTER(20) SourcePath
C
      SourcePath = 's:\lang\'
      N = 0
      hndl = FILE$FIRST
	  print *,'   FILE             LENGTH'
      DO 
         NN = GETFILEINFOQQ(trim(SourcePath)//'*.f90',DIR_INFO, hndl)
	     IF(hndl.eq.FILE$LAST.or.hndl.eq.FILE$ERROR.or.NN.eq.0)exit
         N = N + 1
		 write(*,'(I2,2x,A15,2x,I6)')N,dir_info%name,dir_info%length
      END DO
      end program

The IFort documentation page on GETFILEINFOQQ also contains a slightly longer example.

0 Kudos
PASeeger
Beginner
731 Views

Thank you mecej4!  Your answer was exactly what I needed to know, and your explanation was very clear.

Phil Seeger

 

0 Kudos
Reply