OPEN: USEROPEN Specifier

The USEROPEN specifier lets you pass control to a routine that directly opens a file. The file can use system calls or library routines to establish a special context that changes the effect of subsequent Fortran I/O statements.

The USEROPEN specifier takes the following form:

USEROPEN = function-name

function-name

Is the name of an external function; it must be of type INTEGER(4) (INTEGER*4).
The external function can be written in Fortran, C, or other languages.

If the function is written in Fortran, do not execute a Fortran OPEN statement to open the file named in USEROPEN.

The Intel® Fortran Run-time Library (RTL) I/O support routines call the function named in USEROPEN in place of the system calls normally used when the file is first opened for I/O.

On Windows* systems, the Fortran RTL normally calls CreateFile( ) to open a file. When USEROPEN is specified, the called function opens the file (or pipe, etc.) by using CreateFile( ) and returns the handle of the file (return value from CreateFile( )) when it returns control to the calling Fortran program.

On Linux* and Mac OS* X systems, the Fortran RTL normally calls the open function to open a file. When USEROPEN is specified, the called function opens the file by calling open and returns the file descriptor of the file when it returns control to the calling Fortran program.

When opening the file, the called function usually specifies options different from those provided by a normal Fortran OPEN statement.

Examples

The following shows an example on Linux and Mac OS X systems and an example on Windows systems.

Example on Linux and Mac OS X systems:

      PROGRAM UserOpenMain
      IMPLICIT NONE

      EXTERNAL      UOPEN
      INTEGER(4)    UOPEN

      CHARACTER(10) :: FileName="UOPEN.DAT"
      INTEGER       :: IOS
      CHARACTER(255):: InqFullName
      CHARACTER(100):: InqFileName
      INTEGER       :: InqLun
      CHARACTER(30) :: WriteOutBuffer="Write_One_Record_to_the_File. "
      CHARACTER(30) :: ReadInBuffer  ="??????????????????????????????"

110   FORMAT( X,"FortranMain: ",A," Created (iostat=",I0,")")
115   FORMAT( X,"FortranMain: ",A,": Creation Failed (iostat=",I0,")")
120   FORMAT( X,"FortranMain: ",A,": ERROR: INQUIRE Returned Wrong FileName")
130   FORMAT( X,"FortranMain: ",A,": ERROR: ReadIn and WriteOut Buffers Do Not Match")

      WRITE(*,'(X,"FortranMain: Test the USEROPEN Facility of Open")')

      OPEN(UNIT=10,FILE='UOPEN.DAT',STATUS='REPLACE',USEROPEN=UOPEN, &
           IOSTAT=ios, ACTION='READWRITE')     

!     When the OPEN statement is executed, the uopen_ function receives control.
!     The uopen_ function opens the file by calling open(), and subsequently
!     returns control with the handle returned by open().

      IF (IOS .EQ. 0)  THEN
         WRITE(*,110) TRIM(FileName), IOS
         INQUIRE(10, NAME=InqFullName)
         CALL ParseForFileName(InqFullName,InqFileName)
         IF (InqFileName .NE. FileName) THEN 
            WRITE(*,120) TRIM(FileName)
         END IF
      ELSE
         WRITE(*,115) TRIM(FileName), IOS
         GOTO 9999
      END IF

      WRITE(10,*) WriteOutBuffer
      REWIND(10)
      READ(10,*) ReadInBuffer
      IF (ReadinBuffer .NE. WriteOutbuffer) THEN
         WRITE(*,130) TRIM(FileName)
      END IF

      CLOSE(10)
      WRITE(*,'(X,"FortranMain: Test of USEROPEN Completed")')

9999  CONTINUE
      END

!---------------------------------------------------------------
! SUBROUTINE: ParseForFileName
!             Takes a full pathname and returns the filename
!             with its extension. 
!---------------------------------------------------------------
      SUBROUTINE ParseForFileName(FullName,FileName)

      CHARACTER(255):: FullName
      CHARACTER(255):: FileName
      INTEGER       :: P

      P = INDEX(FullName,'/',.TRUE.)
      FileName = FullName(P+1:)

      END

//
// File: UserOpen_Sub.c
//
// This routine opens a file using data passed from the Intel(c) Fortran OPEN statement.
//

#include <stdio.h>
#include <stdlib.h>
#include <fcntl.h>
#include <sys/types.h>
#include <sys/stat.h>
#include <sys/file.h>
#include <errno.h>
int uopen_ ( char *file_name,   /* access read: name of the file to open (null terminated) */
             int  *open_flags,  /* access read: READ/WRITE, see file.h or open(2) */
             int  *create_mode, /* access read: set if the file is to be created */
             int  *unit_num,    /* access read: logical unit number to be opened */
             int  filenam_len ) /* access read: number of characters in file_name */
{
    /*
    ** The returned value is the following:
    **    value >= 0 is a valid file descriptor
    **    value < 0 is an error
    */
    int return_value;

    printf(" %s: Opening FILENAME = %s\n", __FILE__, file_name);
    printf(" %s: open_flags = 0x%8.8x\n", __FILE__, *open_flags);
    if ( *open_flags & O_CREAT ) {
        printf(" %s: the file is being created, create_mode = 0x%8.8x\n", __FILE__, *create_mode);
    }

    printf(" %s: open() ", __FILE__);
    return_value = open(file_name, *open_flags, *create_mode);
    if (return_value < 0) {
        printf("FAILED.\n");
    } else {
        printf("SUCCEEDED.\n");
    }

    return (return_value);
} /* end of uopen_() */


 Example on Windows systems: 

In the calling Fortran program, the function named in USEROPEN must first be declared in an EXTERNAL statement. For example, the following Fortran code might be used to call the USEROPEN procedure UOPEN:

  IMPLICIT INTEGER (A-Z)
  EXTERNAL UOPEN
  ...
  OPEN(UNIT=10,FILE='UOPEN.DAT',STATUS='NEW',USEROPEN=UOPEN)

When the OPEN statement is executed, the UOPEN function receives control. The function opens the file by calling CreateFile( ), performs whatever operations were specified, and subsequently returns control (with the handle returned by CreateFile( )) to the calling Fortran program.

Here is what the UOPEN function might look like:

        INTEGER FUNCTION UOPEN( FILENAME,      &
                                DESIRED_ACCESS, &
                                SHARE_MODE,     &
                                A_NULL,         &
                                CREATE_DISP,    &
                                FLAGS_ATTR,     &
                                B_NULL,         &
                                UNIT,           &
                                FLEN )
        !DEC$ ATTRIBUTES C, ALIAS:'_UOPEN' :: UOPEN
        !DEC$ ATTRIBUTES REFERENCE :: FILENAME
        !DEC$ ATTRIBUTES REFERENCE :: DESIRED_ACCESS
        !DEC$ ATTRIBUTES REFERENCE :: SHARE_MODE
        !DEC$ ATTRIBUTES REFERENCE :: CREATE_DISP
        !DEC$ ATTRIBUTES REFERENCE :: FLAGS_ATTR
        !DEC$ ATTRIBUTES REFERENCE :: UNIT
        USE IFWIN
        IMPLICIT INTEGER (A-Z)
        CHARACTER*(FLEN) FILENAME
        TYPE(T_SECURITY_ATTRIBUTES), POINTER :: NULL_SEC_ATTR

! Set the FILE_FLAG_WRITE_THROUGH bit in the flag attributes to CreateFile( )
! (for whatever reason)
        FLAGS_ATTR = FLAGS_ATTR + FILE_FLAG_WRITE_THROUGH

! Do the CreateFile( ) call and return the status to the Fortran rtl
        STS = CreateFile( FILENAME,             &
                          DESIRED_ACCESS,       &
                          SHARE_MODE,           &
                          NULL_SEC_ATTR,        &
                          CREATE_DISP,          &
                          FLAGS_ATTR,           &
                          0 )

        UOPEN = STS
        RETURN
        END

The UOPEN function is declared to use the cdecl calling convention, so it matches the Fortran rtl declaration of a useropen routine.

The following function definition and arguments are passed from the Intel Fortran Run-time Library to the function named in USEROPEN:

       INTEGER FUNCTION UOPEN( FILENAME,       &
                               DESIRED_ACCESS, &
                               SHARE_MODE,     &
                               A_NULL,         &
                               CREATE_DISP,    &
                               FLAGS_ATTR,     &
                               B_NULL,         &
                               UNIT,           &
                               FLEN )
        !DEC$ ATTRIBUTES C, ALIAS:'_UOPEN' :: UOPEN
        !DEC$ ATTRIBUTES REFERENCE :: DESIRED_ACCESS
        !DEC$ ATTRIBUTES REFERENCE :: SHARE_MODE
        !DEC$ ATTRIBUTES REFERENCE :: CREATE_DISP
        !DEC$ ATTRIBUTES REFERENCE :: FLAGS_ATTR
        !DEC$ ATTRIBUTES REFERENCE :: UNIT

The first 7 arguments correspond to the CreateFile( ) api arguments. The value of these arguments is set according the caller's OPEN( ) arguments:

FILENAME

Is the address of a null terminated character string that is the name of the file.

DESIRED_ACCESS

Is the desired access (read-write) mode passed by reference.

SHARE_MODE

Is the file sharing mode passed by reference.

A_NULL

Is always null. The Fortran runtime library always passes a NULL for the pointer to a SECURITY_ATTRIBUTES structure in its CreateFile( ) call.

CREATE_DISP

Is the creation disposition specifying what action to take on files that exist, and what action to take on files that do not exist. It is passed by reference.

FLAGS_ATTR

Specifies the file attributes and flags for the file. It is passed by reference.

B_NULL

Is always null. The Fortran runtime library always passes a NULL for the handle to a template file in it's CreateFile( ) call.

The last 2 arguments are the Fortran unit number and length of the file name:

UNIT

Is the Fortran unit number on which this OPEN is being done. It is passed by reference.

FLEN

Is the length of the file name, not counting the terminating null, and passed by value.


Submit feedback on this help topic

Copyright © 1996-2010, Intel Corporation. All rights reserved.