Sun Studio 12: Fortran Library Reference

Chapter 1 Fortran Library Routines

This chapter describes the Fortran library routines.

All the routines described in this chapter have corresponding man pages in section 3F of the man library. For example, man -s 3F access will display the man page entry for the library routine access.

This chapter does not describe the standard Fortran 95 intrinsic routines. See the relevant Fortran 95 standards documents for information on intrinsics.

See also the Numerical Computation Guide for additional math routines that are callable from Fortran and C. These include the standard math library routines in libm and libsunmath (see Intro(3M)), optimized versions of these libraries, the SPARC vector math library, libmvec, and others.

See 2.3.4.2 Memory Functions for details on Fortran 77 and VMS intrinsic functions implemented by the f95 compiler.

1.1 Data Type Considerations

Unless otherwise indicated, the function routines listed here are not intrinsics. That means that the type of data a function returns may conflict with the implicit typing of the function name, and require explicit type declaration by the user. For example, getpid() returns INTEGER*4 and would require an INTEGER*4 getpid declaration to ensure proper handling of the result. (Without explicit typing, a REAL result would be assumed by default because the function name starts with g.) As a reminder, explicit type statements appear in the function summaries for these routines.

Be aware that IMPLICIT statements and the -dbl and -xtypemap compiler options also alter the data typing of arguments and the treatment of return values. A mismatch between the expected and actual data types in calls to these library routines could cause unexpected behavior. Options -xtypemap and -dbl promote the data type of INTEGER functions to INTEGER*8, REAL functions to REAL*8, and DOUBLE functions to REAL*16. To protect against these problems, function names and variables appearing in library calls should be explicitly typed with their expected sizes, as in:


        integer*4 seed, getuid
        real*4 ran
        ...
        seed = 70198
        val = getuid() + ran(seed)
        ...

Explicit typing in the example protects the library calls from any data type promotion when the -xtypemap and -dbl compiler options are used. Without explicit typing, these options could produce unexpected results. See the Fortran User’s Guide and the f95(1) man page for details on these options.

The Fortran 95 compiler, f95, provides an include file, system.inc, that defines the interfaces for most non-intrinsic library routines. Include this file to insure that functions you call and their arguments are properly typed, especially when default data types are changed with -xtypemap.


        include ’system.inc’
        integer(4) mypid
        mypid = getpid()
        print *, mypid

You can catch many issues related to type mismatches over library calls by using the Fortran compilers’ global program checking option, -Xlist. Global program checking by the f95 compiler is described in the Fortran User’s Guide, the Fortran Programming Guide, and the f95(1) man page.

1.2 64-Bit Environments

Compiling a program to run in a 64-bit operating environment (that is, compiling with -m64, and running the executable on a 64–bit enabled SPARC or x86 platform) changes the return values of certain functions. These are usually functions that interface standard system-level routines, such as malloc(3F) (see 1.4.35 malloc, malloc64, realloc, free: Allocate/Reallocate/Deallocate Memory), and may take or return 32-bit or 64-bit values depending on the environment. To provide portability of code between 32-bit and 64-bit environments, 64-bit versions of these routines have been provided that always take and/or return 64-bit values. The following table identifies library routine provided for use in 64-bit environments:

Table 1–1 Library Routines for 64-bit Environments

Function  

Description  

malloc64

Allocate memory and return a pointer 

fseeko64

Reposition a large file 

ftello64

Determine position of a large file 

stat64, fstat64, lstat64

Determine status of a file 

time64,ctime64,gmtime64,ltime64

Dissect system time, convert to character 

qsort64

Sort the elements of an array 

1.3 Fortran Math Functions

The following functions and subroutines are part of the Fortran math libraries. They are available to all programs compiled with f95. These routines are non-intrinsics that take a specific data type as an argument and return the same. Non-intrinsics do have to be declared in the routine referencing them.

Many of these routines are "wrappers", Fortran interfaces to routines in the C language library, and as such are non-standard Fortran. They include IEEE recommended support functions, and specialized random number generators. See the Numerical Computation Guide and the man pages libm_single(3F), libm_double(3F), libm_quadruple(3F), for more information about these libraries.

1.3.1 Single-Precision Functions

These subprograms are single-precision math functions and subroutines.

In general, the functions below provide access to single-precision math functions that do not correspond to standard Fortran generic intrinsic functions—data types are determined by the usual data typing rules.

These functions need not be explicitly typed with a REAL statement as long as default typing holds. (Names beginning with “r” are REAL, with “i” are INTEGER.)

For details on these routines, see the C math library man pages (3M). For example, for r_acos(x) see the acos(3M) man page.

Table 1–2 Single-Precision Math Functions

Function Name  

Return Type  

Description  

r_acos( x )

r_acosd( x )

r_acosh( x )

r_acosp( x )

r_acospi( x )

REAL

REAL

REAL

REAL

REAL

arc cosine

--

arc cosh

--

--

r_atan( x )

r_atand( x )

r_atanh( x )

r_atanp( x )

r_atanpi( x )

REAL

REAL

REAL

REAL

REAL

arc tangent

--

arc tanh

--

--

r_asin( x )

r_asind( x )

r_asinh( x )

r_asinp( x )

r_asinpi( x )

REAL

REAL

REAL

REAL

REAL

arc sine

--

arc sinh

--

--

r_atan2( y, x )

r_atan2d( y, x )

r_atan2pi( y, x )

REAL

REAL

REAL

arc tangent

--

--

r_cbrt( x )

r_ceil( x )

r_copysign( x, y )

REAL

REAL

REAL

cube root

ceiling

--

r_cos( x )

r_cosd( x )

r_cosh( x )

r_cosp( x )

r_cospi( x )

REAL

REAL

REAL

REAL

REAL

cosine

--

hyperb cos

--

--

r_erf( x )

r_erfc( x )

REAL

REAL

err function

--

r_expm1( x )

r_floor( x )

r_hypot( x, y )

r_infinity( )

REAL

REAL

REAL

REAL

(e**x)-1

floor

hypotenuse

--

r_j0( x )

r_j1( x )

r_jn(n, x )

REAL

REAL

REAL

Bessel--

--

ir_finite( x )

ir_fp_class( x )

ir_ilogb( x )

ir_irint( x )

ir_isinf( x )

ir_isnan( x )

ir_isnormal( x )

ir_issubnormal( x )

ir_iszero( x )

ir_signbit( x )

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

--

--

--

--

--

--

--

--

--

--

r_addran()

r_addrans( x, p, l, u )

r_lcran()

r_lcrans( x, p, l, u )

r_shufrans(x, p, l, u)

REAL

subroutineREAL

subroutine

subroutine

randomnumbergenerators

r_lgamma( x )

r_logb( x )

r_log1p( x )

r_log2( x )

REAL

REAL

REAL

REAL

log gamma

--

--

--

r_max_normal()

r_max_subnormal()

r_min_normal()

r_min_subnormal()

r_nextafter( x, y )

r_quiet_nan( n )

r_remainder( x, y )

r_rint( x )

r_scalb( x, y )

r_scalbn( x, n )

r_signaling_nan( n )

r_significand( x )

REAL

REAL

REAL

REAL

REAL

REAL

REAL

REAL

REAL

REAL

REAL

REAL

 

r_sin( x )

r_sind( x )

r_sinh( x )

r_sinp( x )

r_sinpi( x )

REAL

REAL

REAL

REAL

REAL

sine

--

hyperb sin

--

--

r_sincos( x, s, c )

r_sincosd( x, s, c )

r_sincosp( x, s, c )

r_sincospi( x, s, c )

subroutine

subroutine

subroutine

subroutine

sine & cosine

--

--

--

r_tan( x )

r_tand( x )

r_tanh( x )

r_tanp( x )

r_tanpi( x )

REAL

REAL

REAL

REAL

REAL

tangent

--

hyperb tan

--

--

r_y0( x )

r_y1( x )

r_yn( n, x )

REAL

REAL

REAL

bessel

--

--

See also: intro(3M) and the Numerical Computation Guide.

1.3.2 Double-Precision Functions

The following subprograms are double-precision math functions and subroutines.

In general, these functions do not correspond to standard Fortran generic intrinsic functions—data types are determined by the usual data typing rules.

These DOUBLE PRECISION functions need to appear in a DOUBLE PRECISION statement.

Refer to the C library man pages for details: the man page for d_acos(x) is acos(3M)

Table 1–3 Double Precision Math Functions

Function Name  

Return Type  

Description  

d_acos( x )

d_acosd( x )

d_acosh( x )

d_acosp( x )

d_acospi( x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

arc cosine

--

arc cosh

--

--

d_atan( x )

d_atand( x )

d_atanh( x )

d_atanp( x )

d_atanpi( x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

arc tangent

--

arc tanh

--

--

d_asin( x )

d_asind( x )

d_asinh( x )

d_asinp( x )

d_asinpi( x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

arc sine

--

arc sinh

--

--

d_atan2( y, x )

d_atan2d( y, x )

d_atan2pi( y, x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

arc tangent

--

--

d_cbrt( x )

d_ceil( x )

d_copysign( x, x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

cube root

ceiling

--

d_cos( x )

d_cosd( x )

d_cosh( x )

d_cosp( x )

d_cospi( x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

cosine

--

hyperb cos

--

--

d_erf( x )

d_erfc( x )

DOUBLE PRECISION

DOUBLE PRECISION

error func

--

d_expm1( x )

d_floor( x )

d_hypot( x, y )

d_infinity( )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

(e**x)-1

floor

hypotenuse

--

d_j0( x )

d_j1( x )

d_jn(n, x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

Bessel

--

--

id_finite( x )

id_fp_class( x )

id_ilogb( x )

id_irint( x )

id_isinf( x )

id_isnan( x )

id_isnormal( x )

id_issubnormal( x )

id_iszero( x )

id_signbit( x )

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

 

d_addran()

d_addrans(x, p, l, u)

d_lcran()

d_lcrans(x, p, l, u )

d_shufrans(x, p, l,u)

DOUBLE PRECISION

subroutine

DOUBLE PRECISION

subroutine

subroutine

random number generators

d_lgamma( x )

d_logb( x )

d_log1p( x )

d_log2( x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

log gamma

--

--

--

d_max_normal()

d_max_subnormal()

d_min_normal()

d_min_subnormal()

d_nextafter( x, y )

d_quiet_nan( n )

d_remainder( x, y )

d_rint( x )

d_scalb( x, y )

d_scalbn( x, n )

d_signaling_nan( n )

d_significand( x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

 

d_sin( x )

d_sind( x )

d_sinh( x )

d_sinp( x )

d_sinpi( x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

sine

--

hyper sine

--

--

d_sincos( x, s, c )

d_sincosd( x, s, c )

d_sincosp( x, s, c )

d_sincospi( x, s, c )

subroutine

subroutine

subroutine

subroutine

sine & cosine

--

--

d_tan( x )

d_tand( x )

d_tanh( x )

d_tanp( x )

d_tanpi( x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

tangent

--

hyperb tan

--

--

d_y0( x )

d_y1( x )

d_yn( n, x )

DOUBLE PRECISION

DOUBLE PRECISION

DOUBLE PRECISION

bessel

--

--

See also: intro(3M) and the Numerical Computation Guide.

1.3.3 Quad-Precision Functions

These subprograms are quadruple-precision (REAL*16) math functions and subroutines.

In general, these do not correspond to standard generic intrinsic functions; data types are determined by the usual data typing rules.

The quadruple precision functions must appear in a REAL*16 statement

Table 1–4 Quadruple-Precision libm Functions

Function Name  

Return Type  

q_copysign( x, y )

q_fabs( x )

q_fmod( x )

q_infinity( )

REAL*16

REAL*16

REAL*16

REAL*16

iq_finite( x )

iq_fp_class( x )

iq_ilogb( x )

iq_isinf( x )

iq_isnan( x )

iq_isnormal( x )

iq_issubnormal( x )

iq_iszero( x )

iq_signbit( x )

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

INTEGER

q_max_normal()

q_max_subnormal()

q_min_normal()

q_min_subnormal()

q_nextafter( x, y )

q_quiet_nan( n )

q_remainder( x, y )

q_scalbn( x, n )

q_signaling_nan( n )

REAL*16

REAL*16

REAL*16

REAL*16

REAL*16

REAL*16

REAL*16

REAL*16

REAL*16

If you need to use any other quadruple-precision libm function, you can call it using $PRAGMA C(fcn) before the call. For details, see the chapter on the C–Fortran interface in the Fortran Programming Guide.

1.4 Fortran Library Routines Reference

This section details the subroutines and functions in the Fortran library that are part of the Sun Studio Fortran 95 software but are not standard Fortran 95 intrinsics.

A synopsis of the calling interface is presented in a table of the form

data declarations

calling prototype synopsis with arguments

argument 1 name

data type

input/output

description

argument 2 name

data type

input/output

description

Return value

data type

Output 

description

Additional man pages are available in section 3f of the Sun Studio man pages. For example, the command man -s 3f access will display the man page for the access() function. References to man pages appear in this manual as manpagename(section). For example, a reference to the man page for the access() function appears as access(3f), and the man page for the Fortran 95 compiler as f95(1)

1.4.1 abort: Terminate and Write Core File

The subroutine is called by:


call abort

abort flushes the I/O buffers and then aborts the process, possibly producing a core file memory dump in the current directory. See limit(1) about limiting or suppressing core dumps.

1.4.2 access: Check File Permissions or Existence

The function is called by:

INTEGER*4 access

status = access ( name, mode )

name

character

Input 

File name 

mode

character

Input 

Permissions 

Return value 

INTEGER*4

Output 

status=0: OKstatus>0: Error code

access determines if you can access the file name with the permissions specified by mode. access returns zero if the access specified by mode would be successful. See also gerror(3F) to interpret error codes.

Set mode to one or more of r, w, x, in any order or combination, or blank, where r, w, x have the following meanings:

’r’

Test for read permission 

’w’

Test for write permission 

’x’

Test for execute permission 

’ ’

Test for existence of the file 

Example 1: Test for read/write permission:


      INTEGER*4  access, status
      status = access ( ’taccess.data’, ’rw’ )
      if ( status .eq. 0 ) write(*,*) "ok"
      if ( status .ne. 0 ) write(*,*) ’cannot read/write’, status

Example 2: Test for existence:


      INTEGER*4  access, status
      status = access ( ’taccess.data’, ’ ’ )    ! blank mode
      if ( status .eq. 0 ) write(*,*) "file exists"
      if ( status .ne. 0 ) write(*,*) ’no such file’, status

1.4.3 alarm: Call Subroutine After a Specified Time

The function is called by:

INTEGER*4 alarm

n = alarm ( time, sbrtn )

time

INTEGER*4

Input 

Number of seconds to wait (0=do not call) 

sbrtn

Routine name 

Input 

Subprogram to execute must be listed in an external statement. 

Return value 

INTEGER*4

Output 

Time remaining on the last alarm 

Example: alarm—wait 9 seconds then call sbrtn:


       integer*4 alarm, time / 1 /
       common / alarmcom / i
       external sbrtn
       i = 9
       write(*,*) i
       nseconds =  alarm ( time, sbrtn )
       do n = 1,100000         ! Wait until alarm activates sbrtn.
        r = n              ! (any calculations that take enough time)
        x=sqrt(r)
       end do
       write(*,*) i
       end
       subroutine sbrtn
       common / alarmcom / i
       i = 3                     ! Do no I/O in this routine.
       return
       end

See also: alarm(3C), sleep(3F), and signal(3F). Note the following restrictions:

1.4.4 bit: Bit Functions: and, or, …, bit, setbit, …

The definitions are:

and( word1, word2 )

Computes bitwise and of its arguments.

or( word1, word2 )

Computes bitwise inclusive or of its arguments.

xor( word1, word2 )

Computes bitwise exclusive or of its arguments.

not( word )

Returns bitwise complement of its argument.

lshift( word, nbits )

Logical left shift with no end around carry.

rshift( word, nbits )

Arithmetic right shift with sign extension.

call bis( bitnum, word )

Sets bit bitnum in word to 1.

call bic( bitnum, word )

Clears bit bitnum in word to 0.

bit( bitnum, word )

Tests bit bitnum in word and returns LOGICAL .true. if the bit is 1, .false. if it is 0.

call setbit(bitnum,word,state)

Sets bit bitnum in word to 1 if state is nonzero, and clears it otherwise.

The alternate external versions for MIL-STD-1753 are:

iand( m, n )

Computes the bitwise and of its arguments.

ior( m, n )

Computes the bitwise inclusive or of its arguments.

ieor( m, n )

Computes the bitwise exclusive or of its arguments.

ishft( m, k )

Is a logical shift with no end around carry (left if k>0, right if k<0).

ishftc( m, k, ic )

Circular shift: right-most ic bits of m are left-shifted circularly k places.

ibits( m, i, len )

Extracts bits: from m, starting at bit i, extracts len bits.

ibset( m, i )

Sets bit: return value is equal to word m with bit number i set to 1.

ibclr( m, i )

Clears bit: return value is equal to word m with bit number i set to 0.

btest( m, i )

Tests bit i in m; returns LOGICAL .true. if the bit is 1, and .false. if it is 0.

See also 1.4.36 mvbits: Move a Bit Field, and Chapters 2 and 3 for other functions that manipulate bit fields.

1.4.4.1 Usage: and, or, xor, not, rshift, lshift

For the intrinsic functions:

x = and( word1, word2 )

x = or( word1, word2 )

x = xor( word1, word2 )

x = not( word )

x = rshift( word, nbits )

x = lshift( word, nbits )

word, word1, word2, nbits are integer input arguments. These are intrinsic functions expanded inline by the compiler. The data type returned is that of the first argument.

No test is made for a reasonable value of nbits.

Example: and, or, xor, not:


demo% cat tandornot.f
        print 1, and(7,4), or(7,4), xor(7,4), not(4)
 1      format(4x ’and(7,4)’, 5x ’or(7,4)’, 4x ’xor(7,4)’,
     1         6x ’not(4)’/4o12.11)
        end
demo% f95 tandornot.f
demo% a.out
    and(7,4)     or(7,4)    xor(7,4)      not(4)
 00000000004 00000000007 00000000003 37777777773
demo%

Example: lshift, rshift:


demo% cat tlrshift.f
       integer*4 lshift, rshift
       print 1, lshift(7,1), rshift(4,1)
 1     format(1x ’lshift(7,1)’, 1x ’rshift(4,1)’/2o12.11)
       end
demo% f95 tlrshift.f
demo% a.out
 lshift(7,1) rshift(4,1)
 00000000016 00000000002
demo%

1.4.4.2 Usage: bic, bis, bit, setbit

For the subroutines and functions

call bic( bitnum, word )

call bis( bitnum, word )

call setbit( bitnum, word, state )

LOGICAL bit

x = bit( bitnum, word )

bitnum, state, and word are INTEGER*4 input arguments. Function bit() returns a logical value.

Bits are numbered so that bit 0 is the least significant bit, and bit 31 is the most significant.

bic, bis, and setbit are external subroutines. bit is an external function.

Example 3: bic, bis, setbit, bit:


        integer*4 bitnum/2/, state/0/, word/7/
        logical bit
        print 1, word
 1      format(13x ’word’, o12.11)
        call bic( bitnum, word )
        print 2, word
 2      format(’after bic(2,word)’, o12.11)
        call bis( bitnum, word )
        print 3, word
 3      format(’after bis(2,word)’, o12.11)
        call setbit( bitnum, word, state )
        print 4, word
 4      format(’after setbit(2,word,0)’, o12.11)
        print 5, bit(bitnum, word)
 5      format(’bit(2,word)’, L )
        end
<output>
             word 00000000007
after bic(2,word) 00000000003
after bis(2,word) 00000000007
after setbit(2,word,0) 00000000003
bit(2,word) F

1.4.5 chdir: Change Default Directory

The function is called by:

INTEGER*4 chdir

n = chdir( dirname )

dirname

character

Input 

Directory name 

Return value 

INTEGER*4

Output 

n=0: OK, n>0: Error code

Example: chdir—change cwd to MyDir:


       INTEGER*4  chdir, n
       n =  chdir ( ’MyDir’ )
       if ( n .ne. 0 ) stop ’chdir: error’
       end

See also: chdir(2), cd(1), and gerror(3F) to interpret error codes.

Path names can be no longer than MAXPATHLEN as defined in <sys/param.h>. They can be relative or absolute paths.

Use of this function can cause inquire by unit to fail.

Certain Fortran file operations reopen files by name. Using chdir while doing I/O can cause the runtime system to lose track of files created with relative path names. including the files that are created by open statements without file names.

1.4.6 chmod: Change the Mode of a File

The function is called by:

INTEGER*4 chmod

n = chmod( name, mode )

name

character

Input 

Path name 

mode

character

Input 

Anything recognized by chmod(1),

such as o-w, 444, etc.

Return value 

INTEGER*4

Output 

n = 0: OK; n>0: System error number

Example: chmod—add write permissions to MyFile:


        character*18 name, mode
        INTEGER*4 chmod, n
        name = ’MyFile’
        mode = ’+w’
        n =  chmod( name, mode )
        if ( n .ne. 0 ) stop ’chmod: error’
        end

See also: chmod(1), and gerror(3F) to interpret error codes.

Path names cannot be longer than MAXPATHLEN as defined in <sys/param.h>. They can be relative or absolute paths.

1.4.7 date: Get Current Date as a Character String


Note –

This routine is not “Year 2000 Safe” because it returns only a two-digit value for the year. Programs that compute differences between dates using the output of this routine may not work properly after 31 December, 1999. Programs using this date() routine will see a runtime warning message the first time the routine is called to alert the user. See date_and_time() as a possible alternate routine.


The subroutine is called by:

call date( c )

c

CHARACTER*9

Output 

Variable, array, array element, or character substring 

The form of the returned string c is dd-mmm-yy, where dd is the day of the month as a 2-digit number, mmm is the month as a 3-letter abbreviation, and yy is the year as a 2-digit number (and is not year 2000 safe!).

Example: date:


demo% cat dat1.f
* dat1.f -- Get the date as a character string.
        character c*9
        call date ( c )
        write(*,"(’ The date today is: ’, A9 )" ) c
        end
demo% f95 dat1.f
demo% a.out
Computing time differences using the 2 digit year from subroutine
        date is not safe after year 2000.
 The date today is: 9-Jan-02
demo%

See also idate() and date_and_time().

1.4.7.1 date_and_time: Get Date and Time

This is a Fortran 95 intrinsic routine, and is Year 2000 safe.

The date_and_time subroutine returns data from the real-time clock and the date. Local time is returned, as well as the difference between local time and Universal Coordinated Time (UTC) (also known as Greenwich Mean Time, GMT).

The date_and_time() subroutine is called by:

call date_and_time( date, time, zone, values )

date

CHARACTER*8

Output 

Date, in form CCYYMMDD, where CCYY is the four-digit year, MM the two-digit month, and DD the two-digit day of the month. For example: 19980709 

time

CHARACTER*10

Output 

The current time, in the form hhmmss.sss, where hh is the hour, mm minutes, and ss.sss seconds and milliseconds. 

zone

CHARACTER*5

Output 

The time difference with respect to UTC, expressed in hours and minutes, in the form hhmm 

values

INTEGER*4 VALUES(8)

Output 

An integer array of 8 elements described below. 

The eight values returned in the INTEGER*4 values array are

VALUES(1)

The year, as a 4-digit integer. For example, 1998. 

VALUES(2)

The month, as an integer from 1 to 12. 

VALUES(3)

The day of the month, as an integer from 1 to 31. 

VALUES(4)

The time difference, in minutes, with respect to UTC. 

VALUES(5)

The hour of the day, as an integer from 1 to 23. 

VALUES(6)

The minutes of the hour, as an integer from 1 to 59. 

VALUES(7)

The seconds of the minute, as an integer from 0 to 60. 

VALUES(8)

The milliseconds of the second, in range 0 to 999. 

An example using date_and_time:


demo% cat dtm.f
       integer date_time(8)
       character*10 b(3)
       call date_and_time(b(1), b(2), b(3), date_time)
       print *,’date_time    array values:’
       print *,’year=’,date_time(1)
       print *,’month_of_year=’,date_time(2)
       print *,’day_of_month=’,date_time(3)
       print *,’time difference in minutes=’,date_time(4)
       print *,’hour of day=’,date_time(5)
       print *,’minutes of hour=’,date_time(6)
       print *,’seconds of minute=’,date_time(7)
       print *,’milliseconds of second=’,date_time(8)
       print *, ’DATE=’,b(1)
       print *, ’TIME=’,b(2)
       print *, ’ZONE=’,b(3)
       end

When run on a computer in California, USA on February 16, 2000, it generated the following output:


 date_time    array values:
 year= 2000
 month_of_year= 2
 day_of_month= 16
 time difference in minutes= -420
 hour of day= 11
 minutes of hour= 49
 seconds of minute= 29
 milliseconds of second= 236
 DATE=20000216
 TIME=114929.236
 ZONE=-0700

1.4.8 dtime, etime: Elapsed Execution Time

Both functions have return values of elapsed time (or -1.0 as error indicator).The time returned is in seconds.

Versions of dtime and etime used by Fortran 95 use the system’s low resolution clock by default. The resolution is one hundreth of a second. However, if the program is run under the Sun OSTM operating system utility ptime(1), (/usr/proc/bin/ptime), the high resolution clock is used.

1.4.8.1 dtime: Elapsed Time Since the Last dtime Call

For dtime, the elapsed time is:

The function is called by:

e = dtime( tarray )

tarray

real(2)

Output 

e= -1.0: Error: tarray values are undefined

e≠ -1.0: User time in tarray(1) if no error. System time in tarray(2) if no error

Return value 

real

Output 

e= -1.0: Error

e≠ -1.0: The sum of tarray(1) and tarray(2)

Example: dtime(), single processor:


demo% cat tdtime.f
       real e, dtime, t(2)
       print *, ’elapsed:’, e, ’, user:’, t(1), ’, sys:’, t(2)
       do i = 1, 10000
        k=k+1
       end do
       e = dtime( t )
       print *, ’elapsed:’, e, ’, user:’, t(1), ’, sys:’, t(2)
       end
demo% f95 tdtime.f
demo% a.out
elapsed: 0.0E+0 , user: 0.0E+0 , sys: 0.0E+0
 elapsed: 0.03 , user: 0.01 , sys: 0.02
demo%

1.4.8.2 etime: Elapsed Time Since Start of Execution

For etime, the elapsed time is:

The runtime library determines that a program is executing in a multiprocessor mode if either the PARALLEL or OMP_NUM_THREADS environment variables are defined to some integer value greater than 1.

The function is called by:

e = etime( tarray )

tarray

real(2)

Output 

e= -1.0: Error: tarray values are undefined.

e≠ -1.0: Single Processor: User time in tarray(1). System time in tarray(2)

Multiple Processor: Wall clock time in tarray(1), 0.0 in tarray(2)

Return value 

real

Output 

e= -1.0: Error

e≠ -1.0: The sum of tarray(1) and tarray(2)

Take note that the initial call to etime will be inaccurate. It merely enables the system clock. Do not use the value returned by the initial call to etime.

Example: etime(), single processor:


demo% cat tetime.f
       real e, etime, t(2)
       e = etime(t)         !  Startup etime - do not use result
       do i = 1, 10000
        k=k+1
       end do
       e = etime( t )
       print *, ’elapsed:’, e, ’, user:’, t(1), ’, sys:’, t(2)
       end
demo% f95 tetime.f
demo% a.out
elapsed: 0.02 , user: 0.01 , sys: 0.01
demo%

See also times(2), and the Fortran Programming Guide.

1.4.9 exit: Terminate a Process and Set the Status

The subroutine is called by:

call exit( status )

status

INTEGER*4

Input 

Example: exit():


     ...
       if(dx .lt. 0.) call exit( 0 )
    ...
       end

exit flushes and closes all the files in the process, and notifies the parent process if it is executing a wait.

status should be in the range of 0–255. This call will never return.

The C function exit can cause cleanup actions before the final system ’exit’.

Calling exit without an argument causes a compile-time warning message, and a zero will be automatically provided as an argument. See also: exit(2), fork(2), fork(3F), wait(2), wait(3F).

1.4.10 fdate: Return Date and Time in an ASCII String

The subroutine or function is called by:

call fdate( string )

string

character*24

Output 

or:

CHARACTER fdate*24

string = fdate()

If used as a function, the calling routine must define the type and size of fdate.

Return value 

character*24

Output 

Example 1: fdate as a subroutine:


       character*24 string
       call fdate( string )
       write(*,*) string
       end

Output:


 Wed Aug  3 15:30:23 1994

Example 2: fdate as a function, same output:


       character*24 fdate
       write(*,*)  fdate()
       end

See also: ctime(3), time(3F), and idate(3F).

1.4.11 flush: Flush Output to a Logical Unit

The function is called by:

INTEGER*4 flush

n = flush( lunit )

lunit

INTEGER*4

Input 

Logical unit 

Return value 

INTEGER*4

Output 

n = 0 no errorn > 0 error number

The flush function flushes the contents of the buffer for the logical unit, lunit, to the associated file. This is most useful for logical units 0 and 6 when they are both associated with the console terminal. The function returns a positive error number if an error was encountered; zero otherwise.

See also fclose(3S).

1.4.12 fork: Create a Copy of the Current Process

The function is called by:

INTEGER*4 fork

n = fork()

Return value 

INTEGER*4

Output 

n>0: n=Process ID of copy

n<0, n=System error code

The fork function creates a copy of the calling process. The only distinction between the two processes is that the value returned to one of them, referred to as the parent process, will be the process ID of the copy. The copy is usually referred to as the child process. The value returned to the child process will be zero.

All logical units open for writing are flushed before the fork to avoid duplication of the contents of I/O buffers in the external files.

Example: fork():


       INTEGER*4 fork, pid
       pid = fork()
       if(pid.lt.0) stop ’fork error’
       if(pid.gt.0) then
              print *, ’I am the parent’
       else
              print *, ’I am the child’
       endif

A corresponding exec routine has not been provided because there is no satisfactory way to retain open logical units across the exec routine. However, the usual function of fork/exec can be performed using system(3F). See also: fork(2), wait(3F), kill(3F), system(3F), and perror(3F).

1.4.13 fseek, ftell: Determine Position and Reposition a File

fseek and ftell are routines that permit repositioning of a file. ftell returns a file’s current position as an offset of so many bytes from the beginning of the file. At some later point in the program, fseek can use this saved offset value to reposition the file to that same place for reading.

1.4.13.1 fseek: Reposition a File on a Logical Unit

The function is called by:

INTEGER*4 fseek

n = fseek( lunit, offset, from )

lunit

INTEGER*4

Input 

Open logical unit 

offset

INTEGER*4

or

INTEGER*8

Input 

Offset in bytes relative to position specified by from

 

An INTEGER*8 offset value is required when compiled for a 64-bit environment. If a literal constant is supplied, it must be a 64-bit constant, for example: 100_8

from

INTEGER*4

Input 

0=Beginning of file 

1=Current position 

2=End of file 

Return value 

INTEGER*4

Output 

n=0: OK; n>0: System error code


Note –

On sequential files, following a call to fseek by an output operation (for example, WRITE) causes all data records following the fseek position to be deleted and replaced by the new data record (and an end-of-file mark). Rewriting a record in place can only be done with direct access files.


Example: fseek()—Reposition MyFile to two bytes from the beginning


        INTEGER*4 fseek, lunit/1/, offset/2/, from/0/, n
        open( UNIT=lunit, FILE=’MyFile’ )
        n = fseek( lunit, offset, from )
        if ( n .gt. 0 ) stop ’fseek error’
        end

Example: Same example in a 64-bit environment and compiled with -m64:


        INTEGER*4 fseek, lunit/1/,  from/0/, n
        INTEGER*8 offset/2/
        open( UNIT=lunit, FILE=’MyFile’ )
        n = fseek( lunit, offset, from )
        if ( n .gt. 0 ) stop ’fseek error’
        end

1.4.13.2 ftell: Return Current Position of File

The function is called by:

INTEGER*4 ftell

n = ftell( lunit )

lunit

INTEGER*4

Input 

Open logical unit 

Return value 

INTEGER*4

Output 

n>=0: n=Offset in bytes from start of file

n<0: n=System error code

Example: ftell():


       INTEGER*4 ftell, lunit/1/, n
       open( UNIT=lunit, FILE=’MyFile’ )
       ...
       n = ftell( lunit )
       if ( n .lt. 0 ) stop ’ftell error’
       ...

Example: Same example in a 64-bit environment and compiled with -m64:


       INTEGER*4 lunit/1/
       INTEGER*8 ftell, n
       open( UNIT=lunit, FILE=’MyFile’ )
       ...
       n = ftell( lunit )
       if ( n .lt. 0 ) stop ’ftell error’
       ...

See also fseek(3S) and perror(3F); also fseeko64(3F) ftello64(3F).

1.4.14 fseeko64, ftello64: Determine Position and Reposition a Large File

fseeko64 and ftello64 are "large file" versions of fseek and ftell. They take and return INTEGER*8 file position offsets. (A "large file" is larger than 2 Gigabytes and therefore a byte-position must be represented by a 64-bit integer.) Use these versions to determine and/or reposition large files.

1.4.14.1 fseeko64: Reposition a File on a Logical Unit

The function is called by:

INTEGER fseeko64

n = fseeko64( lunit, offset64, from )

lunit

INTEGER*4

Input 

Open logical unit 

offset64

INTEGER*8

Input 

64-bit offset in bytes relative to position specified by from

from

INTEGER*4

Input 

0=Beginning of file 

1=Current position 

2=End of file 

Return value 

INTEGER*4

Output 

n=0: OK; n>0: System error code


Note –

On sequential files, following a call to fseeko64 by an output operation (for example, WRITE) causes all data records following the fseek position to be deleted and replaced by the new data record (and an end-of-file mark). Rewriting a record in place can only be done with direct access files.


Example: fseeko64()—Reposition MyFile to two bytes from the beginning:


       INTEGER fseeko64, lunit/1/, from/0/, n
       INTEGER*8 offset/200/
       open( UNIT=lunit, FILE=’MyFile’ )
       n = fseeko64( lunit, offset, from )
       if ( n .gt. 0 ) stop ’fseek error’
       end

1.4.14.2 ftello64: Return Current Position of File

The function is called by:

INTEGER*8 ftello64

n = ftello64( lunit )

lunit

INTEGER*4

Input 

Open logical unit 

Return value 

INTEGER*8

Output 

n≥0: n=Offset in bytes from start of file

n<0: n=System error code

Example: ftello64():


       INTEGER*8 ftello64, lunit/1/, n
       open( UNIT=lunit, FILE=’MyFile’ )
       ...
       n = ftello64( lunit )
       if ( n .lt. 0 ) stop ’ftell error’
       ...

1.4.15 getarg, iargc: Get Command-Line Arguments

getarg and iargc access arguments on the command line (after expansion by the command-line preprocessor.

1.4.15.1 getarg: Get a Command-Line Argument

The subroutine is called by:

call getarg( k, arg )

k

INTEGER*4

Input 

Index of argument (0=first=command name) 

arg

character*n

Output 

kth argument

n

INTEGER*4

Size of arg

Large enough to hold longest argument 

1.4.15.2 iargc: Get the Number of Command-Line Arguments

The function is called by:

m = iargc()

Return value 

INTEGER*4

Output 

Number of arguments on the command line 

Example: iargc and getarg, get argument count and each argument:


demo% cat yarg.f
       character argv*10
       INTEGER*4 i, iargc, n
       n = iargc()
       do 1 i = 1, n
         call getarg( i, argv )
 1       write( *, ’( i2, 1x, a )’ ) i, argv
       end
demo% f95 yarg.f
demo% a.out *.f
1 first.f
2 yarg.f

See also execve(2) and getenv(3F).

1.4.16 getc, fgetc: Get Next Character

getc and fgetc get the next character from the input stream. Do not mix calls to these routines with normal Fortran I/O on the same logical unit.

1.4.16.1 getc: Get Next Character From stdin

The function is called by:

INTEGER*4 getc

status = getc( char )

char

character

Output 

Next character 

Return value 

INTEGER*4

Output 

status=0: OK

status=-1: End of file

status>0: System error code or f95 I/O error code

Example: getc gets each character from the keyboard; note the Control-D (^D):


       character char
       INTEGER*4 getc, status
       status = 0
       do while ( status .eq. 0 )
         status = getc( char )
         write(*, ’(i3, o4.3)’) status, char
       end do
       end

After compiling, a sample run of the above source is:


demo% a.out
ab            Program reads letters typed in
0 141         Program outputs status and octal value of the characters entered
0 142            141 represents ’a’, 142 is ’b’
0 012            012 represents the RETURN key
^D               terminated by a CONTROL-D.
-1 377        Next attempt to read returns CONTROL-D
demo%

For any logical unit, do not mix normal Fortran input with getc().

1.4.16.2 fgetc: Get Next Character From Specified Logical Unit

The function is called by:

INTEGER*4 fgetc

status = fgetc( lunit, char )

lunit

INTEGER*4

Input 

Logical unit 

char

character

Output 

Next character 

Return value 

INTEGER*4

Output 

status=-1: End of File

status>0: System error code or f95 I/O error code

Example: fgetc gets each character from tfgetc.data; note the linefeeds (Octal 012):


       character char
       INTEGER*4 fgetc, status
       open( unit=1, file=’tfgetc.data’ )
       status = 0
       do while ( status .eq. 0 )
          status = fgetc( 1, char )
          write(*, ’(i3, o4.3)’) status, char
       end do
       end

After compiling, a sample run of the above source is:


demo% cat tfgetc.data
ab
yz
demo% a.out
0 141       ”a’ read
0 142       ”b’ read
0 012       linefeed read
0 171       ”y’ read
0 172       ”z’ read
0 012       linefeed read
-1 012      CONTROL-D read
demo%

For any logical unit, do not mix normal Fortran input with fgetc().

See also: getc(3S), intro(2), and perror(3F).

1.4.17 getcwd: Get Path of Current Working Directory

The function is called by:

INTEGER*4 getcwd

status = getcwd( dirname )

dirname

character*n

Output 

The path of the current directory is returned 

Path name of the current working directory. n must be large enough for longest path name

Return value 

INTEGER*4

Output 

status=0: OK

status>0: Error code

Example: getcwd:


       INTEGER*4 getcwd, status
       character*64 dirname
       status = getcwd( dirname )
       if ( status .ne. 0 ) stop ’getcwd: error’
       write(*,*) dirname
       end

See also: chdir(3F), perror(3F), and getwd(3).

Note: the path names cannot be longer than MAXPATHLEN as defined in <sys/param.h>.

1.4.18 getenv: Get Value of Environment Variables

The subroutine is called by:

call getenv( ename, evalue )

ename

character*n

Input 

Name of the environment variable sought 

evalue

character*n

Output 

Value of the environment variable found; blanks if not successful 

The size of ename and evalue must be large enough to hold their respective character strings.

If evalue is too short to hold the complete string value, the string is truncated to fit in evalue.

The getenv subroutine searches the environment list for a string of the form ename=evalue and returns the value in evalue if such a string is present; otherwise, it fills evalue with blanks.

Example: Use getenv() to print the value of $SHELL:


       character*18  evalue
       call getenv( ’SHELL’, evalue )
       write(*,*) "’", evalue, "’"
       end

See also: execve(2) and environ(5).

1.4.19 getfd: Get File Descriptor for External Unit Number

The function is called by:

INTEGER*4 getfd

fildes = getfd( unitn )

unitn

INTEGER*4

Input 

External unit number 

Return value 

INTEGER*4 or INTEGER*8

Output 

File descriptor if file is connected; -1 if file is not connected An INTEGER*8 result is returned when compiling for 64-bit environments

Example: getfd():


       INTEGER*4 fildes, getfd, unitn/1/
       open( unitn, file=’tgetfd.data’ )
       fildes = getfd( unitn )
       if ( fildes .eq. -1 ) stop ’getfd: file not connected’
       write(*,*) ’file descriptor = ’, fildes
       end

See also open(2).

1.4.20 getfilep: Get File Pointer for External Unit Number

The function is:

irtn = c_read( getfilep( unitn ), inbyte, 1 )

c_read

C function 

Input 

User’s own C function. See example. 

unitn

INTEGER*4

Input 

External unit number. 

getfilep

INTEGER*4 or INTEGER*8

Return value 

File pointer if the file is connected; -1 if the file is not connected.An INTEGER*8 value is returned when compiling for 64-bit environments

This function is used for mixing standard Fortran I/O with C I/O. Such a mix is nonportable, and is not guaranteed for subsequent releases of the operating system or Fortran. Use of this function is not recommended, and no direct interface is provided. You must create your own C routine to use the value returned by getfilep. A sample C routine is shown below.

Example: Fortran uses getfilep by passing it to a C function:


demo% cat tgetfilepF.f

        character*1  inbyte
        integer*4    c_read,  getfilep, unitn / 5 /
        external     getfilep
        write(*,’(a,$)’) ’What is the digit? ’

        irtn = c_read( getfilep( unitn ), inbyte, 1 )

        write(*,9)  inbyte
   9    format(’The digit read by C is ’, a )
        end

Sample C function actually using getfilep:


demo% cat tgetfilepC.c

#include <stdio.h>
int c_read_ ( fd, buf, nbytes, buf_len )
FILE **fd ;
char *buf ;
int *nbytes, buf_len ;
{
         return fread( buf, 1, *nbytes, *fd ) ;
}

A sample compile-build-run is:


demo% cc -c tgetfilepC.c
demo% f95 tgetfilepC.o tgetfilepF.f
demo% a.out
What is the digit? 3
The digit read by C is 3
demo%

For more information, read the chapter on the C-Fortran interface in the Fortran Programming Guide. See also open(2).

1.4.21 getlog: Get User’s Login Name

The subroutine is called by:

call getlog( name )

name

character*n

Output 

User’s login name, or all blanks if the process is running detached from a terminal. n should be large enough to hold the longest name.

Example: getlog:


       character*18 name
       call getlog( name )
       write(*,*) "’", name, "’"
       end

See also getlogin(3).

1.4.22 getpid: Get Process ID

The function is called by:

INTEGER*4 getpid

pid = getpid()

Return value 

INTEGER*4

Output 

Process ID of the current process

Example: getpid:


       INTEGER*4 getpid, pid
       pid = getpid()
       write(*,*) ’process id = ’, pid
       end

See also getpid(2).

1.4.23 getuid, getgid: Get User or Group ID of Process

getuid and getgid get the user or group ID of the process, respectively.

1.4.23.1 getuid: Get User ID of the Process

The function is called by:

INTEGER*4 getuid

uid = getuid()

Return value 

INTEGER*4

Output 

User ID of the process 

1.4.23.2 getgid: Get Group ID of the Process

The function is called by:

INTEGER*4 getgid

gid = getgid()

Return value 

INTEGER*4

Output 

Group ID of the process 

Example: getuid() and getpid():


       INTEGER*4 getuid, getgid, gid, uid
       uid = getuid()
       gid = getgid()
       write(*,*) uid, gid
       end

See also: getuid(2).

1.4.24 hostnm: Get Name of Current Host

The function is called by:

INTEGER*4 hostnm

status = hostnm( name )

name

character*n

Output 

Name of current host system. n must be large enough to hold the host name.

Return value 

INTEGER*4

Output 

status=0: OK

status>0: Error

Example: hostnm():


      INTEGER*4 hostnm, status
      character*8 name
      status = hostnm( name )
      write(*,*) ’host name = "’, name, ’"’
      end

See also gethostname(2).

1.4.25 idate: Return Current Date

idate puts the current system date into one integer array: day, month, and year.

The subroutine is called by:

call idate( iarray ) Standard Version

iarray

INTEGER*4

Output 

Three-element array: day, month, year. 

Example: idate (standard version):


demo% cat tidate.f
       INTEGER*4 iarray(3)
       call idate( iarray )
       write(*, "(’ The date is: ’,3i5)" )  iarray
       end
demo% f95 tidate.f
demo% a.out
 The date is: 10 8 1998
demo%

1.4.26 ieee_flags,ieee_handler,sigfpe: IEEE Arithmetic

These subprograms provide modes and status required to fully exploit ANSI/IEEE Standard 754-1985 arithmetic in a Fortran program. They correspond closely to the functions ieee_flags(3M), ieee_handler(3M), and sigfpe(3).

Here is a summary:

Table 1–5 IEEE Arithmetic Support Routines

ieeer = ieee_flags( action,mode,in,out )

ieeer = ieee_handler(action,exception,hdl )

ieeer = sigfpe( code, hdl )

action

character

Input 

code

sigfpe_code_type

Input 

mode

character

Input 

in

character

Input 

exception

character

Input 

hdl

sigfpe_handler_type

Input 

out

character

Output 

Return value 

INTEGER*4

Output 

See the Numerical Computation Guide for details on how these functions can be used strategically.

If you use sigfpe, you must do your own setting of the corresponding trap-enable-mask bits in the floating-point status register. The details are in the SPARC architecture manual. The libm function ieee_handler sets these trap-enable-mask bits for you.

The character keywords accepted for mode and exception depend on the value of action.

Table 1–6 ieee_flags( action , mode , in , out) Parameters and Actions

action = ’clearall’

mode, in, out, unused; returns 0

action = ’clear’

clear mode, in

out is unused; returns 0

mode = ’direction’

 

mode = ’exception’

in = ’inexact’ or

’division’ or

’underflow’ or

’overflow’ or

’invalid’ or

’all’ or

’common’

action = ’set’

set floating-point mode, in

out is unused; returns 0

mode = ’direction’

in = ’nearest’ or

’tozero’ or

’positive’ or

’negative’

mode = ’exception’

in = ’inexact’ or

’division’ or

’underflow’ or

’overflow’ or

’invalid’ or

’all’ or

’common’

action = ’get’

test mode settings

in, out may be blank or one of the settings to test returns the current setting depending on mode, or ’not available’ The function returns 0 or the current exception flags if mode = ’exception

mode =’direction’

out = ’nearest’ or

’tozero’ or

’positive’ or

’negative’

mode =’exception’

out = ’inexact’ or

’division’ or

’underflow’ or

’overflow’ or

’invalid’ or

’all’ or

’common’

Table 1–7 ieee_handler( action , in , out) Parameters

action = ’clear’

clear user exception handing of in; out is unused

in = ’inexact’ or

’division’ or

’underflow’ or

’overflow’ or

’invalid’ or

’all’ or

’common’

action = ’set’

set user exception handing of in; out is address of handler routine, or SIGFPE_DEFAULT, or SIGFPE_ABORT, or SIGFPE_IGNORE defined in

floating point.h

in = ’inexact’ or

’division’ or

’underflow’ or

’overflow’ or

’invalid’ or

’all’ or

’common’

Example 1: Set rounding direction to round toward zero, unless the hardware does not support directed rounding modes:


    INTEGER*4 ieeer
    character*1 mode, out, in
    ieeer = ieee_flags( ’set’, ’direction’, ’tozero’, out )

Example 2: Clear rounding direction to default (round toward nearest):


    character*1 out, in
    ieeer = ieee_flags(’clear’,’direction’, in, out )

Example 3: Clear all accrued exception-occurred bits:


    character*18 out
    ieeer = ieee_flags( ’clear’, ’exception’, ’all’, out )

Example 4: Detect overflow exception as follows:


    character*18 out
    ieeer = ieee_flags( ’get’, ’exception’, ’overflow’, out )
    if (out .eq. ’overflow’ ) stop ’overflow’

The above code sets out to overflow and ieeer to 25 (this value is platform dependent). Similar coding detects exceptions, such as invalid or inexact.

Example 5: hand1.f, write and use a signal handler:


       external hand
       real r / 14.2 /,  s / 0.0 /
       i = ieee_handler( ’set’, ’division’, hand )
       t = r/s
       end

       INTEGER*4 function hand ( sig, sip, uap )
       INTEGER*4 sig, address
       structure /fault/
           INTEGER*4 address
       end structure
       structure /siginfo/
           INTEGER*4 si_signo
           INTEGER*4 si_code
           INTEGER*4 si_errno
           record /fault/ fault
       end structure
       record /siginfo/ sip
       address = sip.fault.address
       write (*,10) address
 10    format(’Exception at hex address ’, z8 )
       end

Change the declarations for address and function hand to INTEGER*8 to enable Example 5 in a 64-bit, SPARC environment (-m64)

See the Numerical Computation Guide. See also: floatingpoint(3), signal(3), sigfpe(3), floatingpoint(3F), ieee_flags(3M), and ieee_handler(3M).

1.4.26.1 floatingpoint.h: Fortran IEEE Definitions

The header file floatingpoint.h defines constants and types used to implement standard floating-point according to ANSI/IEEE Std 754-1985.

Include the file in a Fortran 95 source program as follows:


#include "floatingpoint.h"

Use of this include file requires preprocessing prior to Fortran compilation. The source file referencing this include file will automatically be preprocessed if the name has a .F, .F90 or .F95 extension.

IEEE Rounding Mode:

fp_direction_type

The type of the IEEE rounding direction mode. The order of enumeration varies according to hardware. 

SIGFPE Handling:

sigfpe_code_type

The type of a SIGFPE code.

sigfpe_handler_type

The type of a user-definable SIGFPE exception handler called to handle a particular SIGFPE code.

SIGFPE_DEFAULT

A macro indicating default SIGFPE exception handling: IEEE exceptions to continue with a default result and to abort for other SIGFPE codes.

SIGFPE_IGNORE

A macro indicating an alternate SIGFPE exception handling, namely to ignore and continue execution.

SIGFPE_ABORT

A macro indicating an alternate SIGFPE exception handling, namely to abort with a core dump.

IEEE Exception Handling:

N_IEEE_EXCEPTION

The number of distinct IEEE floating-point exceptions. 

fp_exception_type

The type of the N_IEEE_EXCEPTION exceptions. Each exception is given a bit number.

fp_exception_field_type

The type intended to hold at least N_IEEE_EXCEPTION bits corresponding to the IEEE exceptions numbered by fp_exception_type. Thus, fp_inexact corresponds to the least significant bit and fp_invalid to the fifth least significant bit. Some operations can set more than one exception.

IEEE Classification:

fp_class_type

A list of the classes of IEEE floating-point values and symbols. 

Refer to the Numerical Computation Guide. See also ieee_environment(3F).

1.4.27 index,rindex,lnblnk: Index or Length of Substring

These functions search through a character string:

index(a1,a2)

Index of first occurrence of string a2 in string a1

rindex(a1,a2)

Index of last occurrence of string a2 in string a1

lnblnk(a1)

Index of last nonblank in string a1

index has the following forms:

1.4.27.1 index: First Occurrence of a Substring in a String

The index is an intrinsic function called by:

n = index( a1, a2 )

a1

character

Input 

Main string 

a2

character

Input 

Substring

Return value 

INTEGER

Output 

n>0: Index of first occurrence of a2 in a1

n=0: a2 does not occur in a1.

If declared INTEGER*8, index() will return an INTEGER*8 value when compiled for a 64-bit environment and character variable a1 is a very large character string (greater than 2 Gigabytes).

1.4.27.2 rindex: Last Occurrence of a Substring in a String

The function is called by:

INTEGER*4 rindex

n = rindex( a1, a2 )

a1

character

Input 

Main string 

a2

character

Input 

Substring 

Return value 

INTEGER*4 orINTEGER*8

Output 

n>0: Index of last occurrence of a2 in a1

n=0: a2 does not occur in a1INTEGER*8 returned in 64-bit environments

1.4.27.3 lnblnk: Last Nonblank in a String

The function is called by:

n = lnblnk( a1 )

a1

character

Input 

String 

Return value 

INTEGER*4 orINTEGER*8

Output 

n>0: Index of last nonblank in a1

n=0: a1 is all nonblankINTEGER*8 returned in 64-bit environments

Example: index(), rindex(), lnblnk():


demo% cat tindex.f
*                        123456789012345678901
       character s*24 / ’abcPDQxyz...abcPDQxyz’ /
       INTEGER*4 declen, index, first, last, len, lnblnk, rindex
       declen = len( s )
       first = index( s, ’abc’ )
       last = rindex( s, ’abc’ )
       lastnb = lnblnk( s )
       write(*,*) declen, lastnb
       write(*,*) first, last
       end
demo% f95 tindex.f
demo% a.out
24 21     <- declen is 24  because intrinsic len() returns the declared length of  s
1 13

Note –

Programs compiled to run in a 64-bit environment must declare index, rindex and lnblnk (and their receiving variables) INTEGER*8 to handle very large character strings.


1.4.28 inmax: Return Maximum Positive Integer

The function is called by:

m = inmax()

Return value 

INTEGER*4

Output 

The maximum positive integer 

Example: inmax:


demo% cat tinmax.f
       INTEGER*4 inmax, m
       m = inmax()
       write(*,*) m
       end
demo% f95 tinmax.f
demo% a.out
   2147483647
demo%

See also libm_single(3F) and libm_double(3F). See also the non-standard FORTRAN 77 intrinsic function ephuge() described in Chapter 3.

1.4.29 itime: Current Time

itime puts the current system time into an integer array: hour, minute, and second. The subroutine is called by:

call itime( iarray )

iarray

INTEGER*4

Output 

3-element array: 

iarray(1) = hour

iarray(2) = minute

iarray(3) = second

Example: itime:


demo% cat titime.f
       INTEGER*4 iarray(3)
       call itime( iarray )
       write (*, "(’ The time is: ’,3i5)" )  iarray
       end
demo% f95 titime.f
demo% a.out
 The time is: 15 42 35

See also time(3F), ctime(3F), and fdate(3F).

1.4.30 kill: Send a Signal to a Process

The function is called by:

status = kill( pid, signum )

pid

INTEGER*4

Input 

Process ID of one of the user’s processes 

signum

INTEGER*4

Input 

Valid signal number. See signal(3).

Return value 

INTEGER*4

Output 

status=0: OK

status>0: Error code

Example (fragment): Send a message using kill():


       INTEGER*4 kill, pid, signum
*    …
       status = kill( pid, signum )
       if ( status .ne. 0 ) stop ’kill: error’
       write(*,*) ’Sent signal ’, signum, ’ to process ’, pid
       end

The function sends signal signum, and integer signal number, to the process pid. Valid signal numbers are listed in the C include file /usr/include/sys/signal.h

See also: kill(2), signal(3), signal(3F), fork(3F), and perror(3F).

1.4.31 link, symlnk: Make a Link to an Existing File

link creates a link to an existing file. symlink creates a symbolic link to an existing file.

The functions are called by:

status = link( name1, name2 )

INTEGER*4 symlnk

status = symlnk( name1, name2 )

name1

character*n

Input 

Path name of an existing file 

name2

character*n

Input 

Path name to be linked to the file, name1.

name2 must not already exist.

Return value 

INTEGER*4

Output 

status=0: OK

status>0: System error code

1.4.31.1 link: Create a Link to an Existing File

Example 1: link: Create a link named data1 to the file, tlink.db.data.1:


demo% cat tlink.f
        character*34 name1/’tlink.db.data.1’/, name2/’data1’/
        integer*4 link, status
        status = link( name1, name2 )
        if ( status .ne. 0 ) stop ’link: error’
        end
demo% f95 tlink.f
demo% ls -l data1
data1 not found
demo% a.out
demo% ls -l data1
-rw-rw-r-- 2 generic 2 Aug 11 08:50 data1
demo%

1.4.31.2 symlnk: Create a Symbolic Link to an Existing File

Example 2: symlnk: Create a symbolic link named data1 to the file, tlink.db.data.1:


demo% cat tsymlnk.f
       character*34 name1/’tlink.db.data.1’/, name2/’data1’/
       INTEGER*4 status, symlnk
       status = symlnk( name1, name2 )
       if ( status .ne. 0 ) stop ’symlnk: error’
       end
demo% f95 tsymlnk.f
demo% ls -l data1
data1 not found
demo% a.out
demo% ls -l data1
lrwxrwxrwx 1 generic 15 Aug 11 11:09 data1 -> tlink.db.data.1
demo%

See also: link(2), symlink(2), perror(3F), and unlink(3F).

Note: the path names cannot be longer than MAXPATHLEN as defined in <sys/param.h>.

1.4.32 loc: Return the Address of an Object

This intrinsic function is called by:

k = loc( arg )

arg

Any type 

Input 

Variable or array 

Return value 

INTEGER*4-or-

INTEGER*8

Output 

Address of arg

 

Returns an INTEGER*8 pointer when compiled to run in a 64-bit environment with -m64. See Note below.

Example: loc:


       INTEGER*4 k, loc
       real arg / 9.0 /
       k = loc( arg )
       write(*,*) k
       end

Note –

Programs compiled to run in a 64-bit environment should declare INTEGER*8 the variable receiving output from the loc() function.


1.4.33 long, short: Integer Object Conversion

long and short handle integer object conversions between INTEGER*4 and INTEGER*2, and is especially useful in subprogram call lists.

1.4.33.1 long: Convert a Short Integer to a Long Integer

The function is called by:

call ExpecLong( long(int2) )

int2

INTEGER*2

Input 

Return value 

INTEGER*4

Output 

1.4.33.2 short: Convert a Long Integer to a Short Integer

The function is:

INTEGER*2 short

call ExpecShort( short(int4) )

int4

INTEGER*4

Input 

Return value 

INTEGER*2

Output 

Example (fragment): long() and short():


       integer*4 int4/8/, long
       integer*2 int2/8/, short
       call ExpecLong( long(int2) )
       call ExpecShort( short(int4) )
       …
       end

ExpecLong is some subroutine called by the user program that expects a long (INTEGER*4) integer argument. Similarly, ExpecShort expects a short (INTEGER*2) integer argument.

long is useful if constants are used in calls to library routines and the code is compiled with the -i2 option.

short is useful in similar context when an otherwise long object must be passed as a short integer. Passing an integer to short that is too large in magnitude does not cause an error, but will result in unexpected behavior.

1.4.34 longjmp, isetjmp: Return to Location Set by isetjmp

isetjmp sets a location for longjmp; longjmp returns to that location.

1.4.34.1 isetjmp: Set the Location for longjmp

This intrinsic function is called by:

ival = isetjmp( env )

env

INTEGER*4

Output 

env is a 12-element integer array.In 64-bit environments it must be declared INTEGER*8

Return value 

INTEGER*4

Output 

ival = 0 if isetjmp is called explicitly

ival ≠ 0 if isetjmp is called through longjmp

1.4.34.2 longjmp: Return to the Location Set by isetjmp

The subroutine is called by:

call longjmp( env, ival )

env

INTEGER*4

Input 

env is the 12-word integer array initialized by isetjmp.In 64-bit environments it must be declared INTEGER*8

ival

INTEGER*4

Output 

ival = 0 if isetjmp is called explicitly

ival ≠ 0 if isetjmp is called through longjmp

Description

The isetjmp and longjmp routines are used to deal with errors and interrupts encountered in a low-level routine of a program. They are f95 intrinsics.

These routines should be used only as a last resort. They require discipline, and are not portable. Read the man page, setjmp(3V), for bugs and other details.

isetjmp saves the stack environment in env. It also saves the register environment.

longjmp restores the environment saved by the last call to isetjmp, and returns in such a way that execution continues as if the call to isetjmp had just returned the value ival.

The integer expression ival returned from isetjmp is zero if longjmp is not called, and nonzero if longjmp is called.

Example: Code fragment using isetjmp and longjmp:


       INTEGER*4  env(12)
       common /jmpblk/ env
       j = isetjmp( env )
       if ( j .eq. 0 ) then
               call  sbrtnA
           else
          call error_processor
       end if
       end
       subroutine sbrtnA
       INTEGER*4  env(12)
       common /jmpblk/ env
       call longjmp( env, ival )
       return
       end

Restrictions

See setjmp(3V).

1.4.35 malloc, malloc64, realloc, free: Allocate/Reallocate/Deallocate Memory

The functions malloc(), malloc64(), and realloc() allocate blocks of memory and return the starting address of the block. The return value can be used to set an INTEGER or Cray-style POINTER variable. realloc() reallocates an existing memory block with a new size. free() deallocates memory blocks allocated by malloc(), malloc64(), or realloc().


Note –

These routines are implemented as intrinsic functions in f95, but were external functions in f77. They should not appear on type declarations in Fortran 95 programs, or on EXTERNAL statements unless you wish to use your own versions. The realloc() routine is only implemented for f95.


Standard-conforming Fortran 95 programs should use ALLOCATE and DEALLOCATE statements on ALLOCATABLE arrays to perform dynamic memory management, and not make direct calls to malloc/realloc/free.

Legacy Fortran 77 programs could use malloc()/malloc64() to assign values to Cray-style POINTER variables, which have the same data representation as INTEGER variables. Cray-style POINTER variables are implemented in f95 to support portability from Fortran 77.

1.4.35.1 Allocate Memory: malloc, malloc64

The malloc() function is called by:

k = malloc( n )

n

INTEGER

Input 

Number of bytes of memory 

Return value 

INTEGER(Cray POINTER)

Output 

k>0: k = address of the start of the block of memory allocated

k=0: Error

 

An INTEGER*8 pointer value is returned when compiled for a 64-bit environment with -m64. See Note below.


Note –

This function is intrinsic in Fortran 95 and was external in Fortran 77. Fortran 77 programs compiled to run in 64-bit environments would declare the malloc() function and the variables receiving its output as INTEGER*8. The function malloc64(3F) was provided to make programs portable between 32-bit and 64-bit environments.

k = malloc64( n )

n

INTEGER*8

Input 

Number of bytes of memory 

Return value 

INTEGER*8

(Cray POINTER)

Output 

k>0: k=address of the start of the block of memory allocated

k=0: Error


These functions allocate an area of memory and return the address of the start of that area. (In a 64-bit environment, this returned byte address may be outside the INTEGER*4 numerical range—the receiving variables must be declared INTEGER*8 to avoid truncation of the memory address.) The region of memory is not initialized in any way, and it should not be assumed to be preset to anything, especially zero!

Example: Code fragment using malloc():


       parameter (NX=1000)
       integer ( p2X, X )
       real*4 X(1)
       …
       p2X = malloc( NX*4 )
       if ( p2X .eq. 0 ) stop ’malloc: cannot allocate’
       do 11 i=1,NX
 11         X(i) = 0.
       …
       end

In the above example, we acquire 4,000 bytes of memory, pointed to by p2X, and initialize it to zero.

1.4.35.2 Reallocate Memory: realloc

The realloc() f95 intrinsic function is called by:

k = realloc(ptr, n )

ptr

INTEGER

Input 

Pointer to existing memory block. (Value returned from a previous malloc() or realloc() call).

n

INTEGER

Input 

Requested new size of block, in bytes. 

Return value 

INTEGER

(Cray POINTER)

Output 

k>0: k=address of the start of the new block of memory allocated

k=0: Error

 

An INTEGER*8 pointer value is returned when compiled for a 64-bit environment with -m64. See Note below.

The realloc() function changes the size of the memory block pointed to by ptr to n bytes and returns a pointer to the (possibly moved) new block. The contents of the memory block will be unchanged up to the lesser of the new and old sizes.

If ptr is zero, realloc() behaves the same as malloc() and allocates a new memory block of size n bytes.

If n is zero and ptr is not zero, the memory block pointed to is made available for further allocation and is returned to the system only upon termination of the application.

Example: Using malloc() and realloc() and Cray-style POINTER variables:


       PARAMETER (nsize=100001)
       POINTER (p2space,space)
       REAL*4 space(1)

       p2space = malloc(4*nsize)
       if(p2space .eq. 0) STOP ’malloc: cannot allocate space’
       ...
       p2space = realloc(p2space, 9*4*nsize)
       if(p2space .eq. 0) STOP ’realloc: cannot reallocate space’
       ...
       CALL free(p2space)
       ...

Note that realloc() is only implemented for f95.

1.4.35.3 free: Deallocate Memory Allocated by Malloc

The subroutine is called by:

call free ( ptr )

ptr

Cray POINTER

Input 

free deallocates a region of memory previously allocated by malloc and realloc(). The region of memory is returned to the memory manager; it is no longer available to the user’s program.

Example: free():


       real x
       pointer ( ptr, x )
       ptr = malloc ( 10000 )
       call free ( ptr )
       end
 

1.4.36 mvbits: Move a Bit Field

The subroutine is called by:

call mvbits( src, ini1, nbits, des, ini2 )

src

INTEGER*4

Input 

Source 

ini1

INTEGER*4

Input 

Initial bit position in the source 

nbits

INTEGER*4

Input 

Number of bits to move

des

INTEGER*4

Output 

Destination 

ini2

INTEGER*4

Input 

Initial bit position in the destination 

Example: mvbits:


demo% cat mvb1.f
* mvb1.f -- From src, initial bit 0, move 3 bits to des, initial *           bit 3.
*    src    des
* 543210 543210 <- Bit numbers
* 000111 000001 <- Values before move
* 000111 111001 <- Values after move
       INTEGER*4 src, ini1, nbits, des, ini2
       data src, ini1, nbits, des, ini2
     1    / 7,    0,     3,   1,    3 /
       call mvbits ( src, ini1, nbits, des, ini2 )
       write (*,"(5o3)") src, ini1, nbits, des, ini2
       end
demo% f95 mvb1.f
demo% a.out
  7  0  3 71  3
demo%

Note the following:

1.4.37 perror, gerror, ierrno: Get System Error Messages

These routines perform the following functions:

perror

Print a message to Fortran logical unit 0, stderr.

gerror

Get a system error message (of the last detected system error) 

ierrno

Get the error number of the last detected system error. 

1.4.37.1 perror: Print Message to Logical Unit 0, stderr

The subroutine is called by:

call perror( string )

string

character*n

Input 

The message. It is written preceding the standard error message for the last detected system error. 

Example 1:


    call perror( "file is for formatted I/O" )

1.4.37.2 gerror: Get Message for Last Detected System Error

The subroutine or function is called by:

call gerror( string )

string

character*n

Output 

Message for the last detected system error 

Example 2: gerror() as a subroutine:


       character string*30
       …
       call gerror ( string )
       write(*,*) string

Example 3: gerror() as a function; string not used:


       character gerror*30, z*30
       …
       z = gerror( )
       write(*,*) z

1.4.37.3 ierrno: Get Number for Last Detected System Error

The function is called by:

n = ierrno()

Return value 

INTEGER*4

Output 

Number of last detected system error 

This number is updated only when an error actually occurs. Most routines and I/O statements that might generate such errors return an error code after the call; that value is a more reliable indicator of what caused the error condition.

Example 4: ierrno():


       INTEGER*4 ierrno, n
       …
       n = ierrno()
       write(*,*) n

See also intro(2) and perror(3).

Note:

1.4.38 putc, fputc: Write a Character to a Logical Unit

putc writes to logical unit 6, normally the control terminal output.

fputc writes to a logical unit.

These functions write a character to the file associated with a Fortran logical unit bypassing normal Fortran I/O.

Do not mix normal Fortran output with output by these functions on the same unit.

Note that to write any of the special \ escape characters, such as ’\n’ newline, requires compiling with -f77=backslash FORTRAN 77 compatibility option.

1.4.38.1 putc: Write to Logical Unit 6

The function is called by:

INTEGER*4 putc

status = putc( char )

char

character

Input 

The character to write to the unit 

Return value 

INTEGER*4

Output 

status=0: OK

status>0: System error code

Example: putc():


demo% cat tputc.f
       character char, s*10 / ’OK by putc’ /
       INTEGER*4 putc, status
       do i = 1, 10
        char = s(i:i)
        status = putc( char )
       end do
       status = putc( ’\n’ )
       end
demo% f95 -f77=backslash tputc.f
demo% a.out
OK by putc
demo%

1.4.38.2 fputc: Write to Specified Logical Unit

The function is called by:

INTEGER*4 fputc

status = fputc( lunit,char )

lunit

INTEGER*4

Input 

The unit to write to 

char

character

Input 

The character to write to the unit 

Return value 

INTEGER*4

Output 

status=0: OK

status>0: System error code

Example: fputc():


demo% cat tfputc.f
       character char, s*11 / ’OK by fputc’ /
       INTEGER*4 fputc, status
       open( 1, file=’tfputc.data’)
       do i = 1, 11
        char = s(i:i)
        status = fputc( 1, char )
       end do
       status = fputc( 1, ’\n’ )
       end
demo% f95 -f77=backslash tfputc.f
demo% a.out
demo% cat tfputc.data
OK by fputc
demo%

See also putc(3S), intro(2), and perror(3F).

1.4.39 qsort,qsort64: Sort the Elements of a One-Dimensional Array

The subroutine is called by:

call qsort( array, len, isize, compar )

call qsort64( array, len8, isize8, compar )

array

array

Input 

Contains the elements to be sorted 

len

INTEGER*4

Input 

Number of elements in the array. 

len8

INTEGER*8

Input 

Number of elements in the array 

isize

INTEGER*4

Input 

Size of an element, typically: 

4 for integer or real 

8 for double precision or complex 

16 for double complex 

Length of character object for character arrays 

isize8

INTEGER*8

Input 

Size of an element, typically: 

4_8 for integer or real 

8_8 for double precision or complex 

16_8 for double complex 

Length of character object for character arrays 

compar

function name 

Input 

Name of a user-supplied INTEGER*2 function.

Determines sorting order: compar(arg1,arg2)

Use qsort64 in 64-bit environments with arrays larger than 2 Gbytes. Be sure to specify the array length, len8, and the element size, isize8, as INTEGER*8 data. Use the Fortran 95 style constants to explicitly specify INTEGER*8 constants.

The compar(arg1, arg2) arguments are elements of array, returning:

Negative 

If arg1 is considered to precede arg2

Zero 

If arg1 is equivalent to arg2

Positive 

If arg1 is considered to follow arg2

For example:


demo% cat tqsort.f
       external compar
       integer*2 compar
       INTEGER*4 array(10)/5,1,9,0,8,7,3,4,6,2/,len/10/,
     1           isize/4/
       call qsort( array, len, isize, compar )
       write(*,’(10i3)’) array
       end
       integer*2 function compar( a, b )
       INTEGER*4 a, b
       if ( a .lt. b ) compar = -1
       if ( a .eq. b ) compar = 0
       if ( a .gt. b ) compar = 1
       return
       end
demo% f95 tqsort.f
demo% a.out
  0 1 2 3 4 5 6 7 8 9

1.4.40 ran: Generate a Random Number Between 0 and 1

Repeated calls to ran generate a sequence of random numbers with a uniform distribution. See lcrans(3m).

r = ran( i )

i

INTEGER*4

Input 

Variable or array element 

r

REAL

Output 

Variable or array element 

Example: ran:


demo% cat ran1.f
* ran1.f -- Generate random numbers.
       INTEGER*4 i, n
       real r(10)
       i = 760013
       do n = 1, 10
        r(n) = ran ( i )
       end do
       write ( *, "( 5 f11.6 )" ) r
       end
demo% f95 ran1.f
demo% a.out
   0.222058 0.299851 0.390777 0.607055 0.653188
   0.060174 0.149466 0.444353 0.002982 0.976519
demo%
 

Note the following:


    SEED = 6909 * SEED + 1 (MOD 2**32)

1.4.41 rand, drand, irand: Return Random Values

rand returns real values in the range 0.0 through 1.0.

drand returns double precision values in the range 0.0 through 1.0.

irand returns positive integers in the range 0 through 2147483647.

These functions use random(3) to generate sequences of random numbers. The three functions share the same 256 byte state array. The only advantage of these functions is that they are widely available on UNIX systems. For better random number generators, compare lcrans, addrans, and shufrans. See also random(3), and the Numerical Computation Guide

i = irand( k )

r = rand( k )

d = drand( k )

k

INTEGER*4

Input 

k=0: Get next random number in the sequence

k=1: Restart sequence, return first number

k>0: Use as a seed for new sequence, return first

number 

rand

REAL*4

Output 

 

drand

REAL*8

Output 

 

irand

INTEGER*4

Output 

 

Example: irand():


demo% cat trand.f
       integer*4 v(5), iflag/0/
       do i = 1, 5
        v(i) = irand( iflag )
       end do
       write(*,*) v
       end
demo% f95 trand.f
demo% a.out
   2078917053 143302914 1027100827 1953210302 755253631
demo%
 

1.4.42 rename: Rename a File

The function is called by:

INTEGER*4 rename

status = rename( from, to )

from

character*n

Input 

Path name of an existing file 

to

character*n

Input 

New path name for the file 

Return value 

INTEGER*4

Output 

status=0: OK

status>0: System error code

If the file specified by to exists, then both from and to must be the same type of file, and must reside on the same file system. If to exists, it is removed first.

Example: rename()—Rename file trename.old to trename.new


demo% cat trename.f
       INTEGER*4 rename, status
       character*18 from/’trename.old’/, to/’trename.new’/
       status = rename( from, to )
       if ( status .ne. 0 ) stop ’rename: error’
       end
demo% f95 trename.f
demo% ls trename*
trename.f trename.old
demo% a.out
demo% ls trename*
trename.f trename.new
demo%

See also rename(2) and perror(3F).

Note: the path names cannot be longer than MAXPATHLEN as defined in <sys/param.h>.

1.4.43 secnds: Get System Time in Seconds, Minus Argument

t = secnds( t0 )

t0

REAL

Input 

Constant, variable, or array element 

Return Value 

REAL

Output 

Number of seconds since midnight, minus t0

Example: secnds:


demo% cat sec1.f
       real elapsed, t0, t1, x, y
       t0 = 0.0
       t1 = secnds( t0 )
       y = 0.1
       do i = 1, 10000
        x = asin( y )
       end do
       elapsed = secnds( t1 )
       write ( *, 1 ) elapsed
  1    format ( ’ 10000 arcsines: ’, f12.6, ’ sec’ )
       end
demo% f95 sec1.f
demo% a.out
 10000 arcsines:     0.009064 sec
demo%

Note that:

1.4.44 set_io_err_handler, get_io_err_handler: Set and Get I/O Error Handler

set_io_err_handler() declares a user-defined routine to be called whenever errors are detected on a specified input logical unit.

get_io_err_handler() returns the address of the currently declared error handling routine.

These routines are module subroutines and can only be accessed when USE SUN_IO_HANDLERS appears in the calling routine.

USE SUN_IO_HANDLERS

call set_io_err_handler(iu, subr_name, istat)

iu

INTEGER*8

Input 

Logical unit number 

subr_name

EXTERNAL

Input 

Name of user-supplied error handler subroutine. 

istat

INTEGER*4

Output 

Return status. 

USE SUN_IO_HANDLERS

call get_io_err_handler(iu, subr_pointer, istat)

iu

INTEGER*8

Input 

Logical unit number 

subr_pointer

POINTER

Output 

Address of currenly declared handler routine. 

istat

INTEGER*4

Output 

Return status. 

SET_IO_ERR_HANDLER sets the user-supplied subroutine subr_name to be used as the I/O error handler for the logical unit iu when an input error occurs. iu has to be a connected Fortran logical unit for a formatted file. istat will be set to a non-zero value if there is an error, otherwise it is set to zero.

For example, if SET_IO_ERR_HANDLER is called before the logical unit iu has been opened, istat will be set to 1001 ("Illegal Unit"). If subr_name is NULL user error-handling is turned off and the program reverts to default Fortran error handling.

Use GET_IO_ERR_HANDLER to get the address of the function currently being used as the error handler for this logical unit. For example, call GET_IO_ERR_HANDLER to save the current I/O before switching to another handler routine. The error handler can be restored with the saved value later.

subr_name is the name of the user-supplied routine to handle the I/O error on logical unit iu. The runtime I/O library passes all relevant information to subr_name, enabling this routine to diagnose the problem and possibly fix the error before continuing.

The interface to the user-supplied error handler routine is as follows:

SUBROUTINE SUB_NAME(UNIT, SRC_FILE, SRC_LINE, DATA_FILE, FILE_POS,

CURR_BUFF, CURR_ITEM, CORR_CHAR, CORR_ACTION )

INTENT (IN) UNIT, SRC_FILE, SRC_LINE, DATA_FILE

INTENT (IN) FILE_POS, CURR_BUFF, CURR_ITEM

INTENT (OUT) CORR_CHAR, CORR_ACTION

UNIT

INTEGER*8

Input 

Logical unit number of the input file reporting an error. 

SRC_FILE

CHARACTER*(*)

Input 

Name of the Fortran source file originating the input operation. 

SRC_LINE

INTEGER*8

Input 

Line number in SRC_FILE of the input operation with an error.

DATA_FILE

CHARACTER*(*)

Input 

Name of the data file being read. Avaliable only if the file is an opened external file. If the name is not available, (logical unit 5 for example), DATA_FILE is set to a zero-length character data item.

FILE_POS

INTEGER*8

Input 

Current position in the input file, in bytes. Defined only if the name of the DATA_FILE is known.

CURR_BUFF

CHARACTER*(*)

Input 

Character string containing the remaining data from the input record. The bad input character is the first character in the string. 

CURR_ITEM

INTEGER*8

Input 

The number of input items in the record that have been read, including the current one, when the error is detected. For example:READ(12,10)L,(ARR(I),I=1,L)

IF the value of CURR_ITEM is 15 in this case, it means the error happens while reading the 14th element of ARR, with L being the first item and ARR(1) being the second, and so on.

CORR_CHAR

CHARACTER

Output 

The user-supplied corrected character to be returned by the handler. This value is used only when CORR_ACTION is non-zero. If CORR_CHAR is an invalid character, the handler will be called again until a valid character is returned. This could cause an infinite loop, a situation the user is required to protect against.

CORR_ACTION

INTEGER

Output 

Specifies the corrective action to be taken by the I/O library. With a zero value no special action is taken and the library reverts to its default error processing. A value of 1 returns CORR_CHAR to the I/O error processing routine.

1.4.44.1 Limitations

The I/O handler can only replace once character with another character. It cannot replace one character with more than one character.

The error recovery algorithm can only fix a bad character it currently reads, not a bad character which has already been interpreted as a valid character in a different context. For example,in a list-directed read, if the input is "1.234509.8765" when the correct input should be "1.2345 9.8765" then the I/O library will run into an error at the second period because it is not a valid number. But, by that time, it is not possible to go back and change the ’0’ into a blank.

Currently, this error-handling capability does not work for namelist-directed input. When doing namelist-directed input, the specified I/O error handler will not be invoked when an error occurs.

I/O error handlers can only be set for external files, not internal files, because there are no logical units associated with internal files.

The I/O error handler is called only for syntactic errors, not system errors or semantic errors(such as an overflowed input value).

It is possible to have an infinite loop if the user-supplied I/O error handler keeps providing a bad character to the I/O library, causing it to call the user-supplied I/O error handler over and over again. If an error keeps occuring at the same file position then the error handler should terminate itself. One way to do this is to take the default error path by setting CORR_ACTION to 0. Then the I/O library will continue with the normal error handling.

1.4.45 sh: Fast Execution of an sh Command

The function is called by:

INTEGER*4 sh

status = sh( string )

string

character*n

Input 

String containing command to do 

Return value 

INTEGER*4

Output 

Exit status of the shell executed. See wait(2) for an explanation of this value.

Example: sh():


       character*18 string / ’ls > MyOwnFile.names’ /
       INTEGER*4 status, sh
       status = sh( string )
       if ( status .ne. 0 ) stop ’sh: error’
       ...
       end

The function sh passes string to the sh shell as input, as if the string had been typed as a command.

The current process waits until the command terminates.

The functions sh(3f) and system(3f) pass the argument string to a shell for execution. They convert the argument string from a Fortran character value to a C string value and pass it to the C routine system(3c). The routines sh(3f) and system(3f) differ in that system flushes the Fortran I/O buffers before calling the C routine system, while sh does not. Flushing the buffers can take significant time, and so, if any Fortran output is irrelevant to the result of the call, the routine sh is preferred over the routine system.

The sh() function is not MT-safe. Do not call it from multithreaded or parallelized programs.

See also: execve(2), wait(2), and system(3c).

Note: string cannot be longer than 1,024 characters.

1.4.46 signal: Change the Action for a Signal

The function is called by:

INTEGER*4 signal or INTEGER*8 signal

n = signal( signum, proc, flag )

signum

INTEGER*4

Input 

Signal number; see signal(3)

proc

Routine name 

Input 

Name of user signal handling routine; must be in an external statement 

flag

INTEGER*4

Input 

flag < 0: Use proc as the signal handler

flag ≥ 0: Ignore proc; pass flag as the action:

flag = 0: Use the default action

flag = 1: Ignore this signal

Return value 

INTEGER*4

Output 

n=-1: System error

n>0: Definition of previous action

n>1: n=Address of routine that would have been called

n<-1: If signum is a valid signal number, then: n=address of routine that would have been called. If signum is a not a valid signal number, then: n is an error number.

 

INTEGER*8

 

On 64-bit environments, signal and the variables receiving its output must be declared INTEGER*8

If proc is called, it is passed the signal number as an integer argument.

If a process incurs a signal, the default action is usually to clean up and abort. A signal handling routine provides the capability of catching specific exceptions or interrupts for special processing.

The returned value can be used in subsequent calls to signal to restore a previous action definition.

You can get a negative return value even though there is no error. In fact, if you pass a valid signal number to signal(), and you get a return value less than -1, then it is OK.

floatingpoint.h defines proc values SIGFPE_DEFAULT, SIGFPE_IGNORE, and SIGFPE_ABORT. See 1.4.26.1 floatingpoint.h: Fortran IEEE Definitions.

In 64-bit environments, signal must be declared INTEGER*8, along with the variables receiving its output, to avoid truncation of the address that may be returned.

See also kill(1), signal(3), and kill(3F), and Numerical Computation Guide.

1.4.47 sleep: Suspend Execution for an Interval

The subroutine is called by:

call sleep( itime )

itime

INTEGER*4

Input 

Number of seconds to sleep 

The actual time can be up to 1 second less than itime due to granularity in system timekeeping.

Example: sleep():


       INTEGER*4 time / 5 /
       write(*,*) ’Start’
       call sleep( time )
       write(*,*) ’End’
       end

See also sleep(3).

1.4.48 stat, lstat, fstat: Get File Status

These functions return the following information:

Both stat and lstat query by file name. fstat queries by logical unit.

1.4.48.1 stat: Get Status for File, by File Name

The function is called by:

INTEGER*4 stat

ierr = stat ( name, statb )

name

character*n

Input 

Name of the file 

statb

INTEGER*4

Output 

Status structure for the file, 13-element array 

Return value 

INTEGER*4

Output 

ierr=0: OK

ierr>0: Error code

Example 1: stat():


       character name*18 /’MyFile’/
       INTEGER*4 ierr, stat, lunit/1/, statb(13)
       open( unit=lunit, file=name )
       ierr = stat ( name, statb )
       if ( ierr .ne. 0 ) stop ’stat: error’
       write(*,*)’UID of owner = ’,statb(5),’,
     1   blocks = ’,statb(13)
       end

1.4.48.2 fstat: Get Status for File, by Logical Unit

The function

INTEGER*4 fstat

ierr = fstat ( lunit, statb )

lunit

INTEGER*4

Input 

Logical unit number 

statb

INTEGER*4

Output 

Status for the file: 13-element array 

Return value 

INTEGER*4

Output 

ierr=0: OK

ierr>0: Error code

is called by:

Example 2: fstat():


       character name*18 /’MyFile’/
       INTEGER*4 fstat, lunit/1/, statb(13)
       open( unit=lunit, file=name )
       ierr = fstat ( lunit, statb )
       if ( ierr .ne. 0 ) stop ’fstat: error’
       write(*,*)’UID of owner = ’,statb(5),’,
     1      blocks = ’,statb(13)
       end

1.4.48.3 lstat: Get Status for File, by File Name

The function is called by:

ierr = lstat ( name, statb )

name

character*n

Input 

File name 

statb

INTEGER*4

Output 

Status array of file, 13 elements 

Return value 

INTEGER*4

Output 

ierr=0: OK

ierr>0: Error code

Example 3: lstat():


       character name*18 /’MyFile’/
       INTEGER*4 lstat, lunit/1/, statb(13)
       open( unit=lunit, file=name )
       ierr = lstat ( name, statb )
       if ( ierr .ne. 0 ) stop ’lstat: error’
       write(*,*)’UID of owner = ’,statb(5),’,
     1   blocks = ’,statb(13)
       end

1.4.48.4 Detail of Status Array for Files

The meaning of the information returned in the INTEGER*4 array statb is as described for the structure stat under stat(2).

Spare values are not included. The order is shown in the following table:

statb(1)

statb(2)

statb(3)

statb(4)

statb(5)

statb(6)

statb(7)

statb(8)

statb(9)

statb(10)

statb(11)

statb(12)

statb(13)

Device inode resides on 

This inode’s number 

Protection 

Number of hard links to the file 

User ID of owner 

Group ID of owner 

Device type, for inode that is device 

Total size of file 

File last access time 

File last modify time 

File last status change time 

Optimal blocksize for file system I/O ops 

Actual number of blocks allocated 

See also stat(2), access(3F), perror(3F), and time(3F).

Note: the path names can be no longer than MAXPATHLEN as defined in <sys/param.h>.

1.4.49 stat64, lstat64, fstat64: Get File Status

64-bit "long file" versions of stat, lstat, fstat. These routines are identical to the non-64-bit routines, except that the 13-element array statb must be declared INTEGER*8.

1.4.50 system: Execute a System Command

The function is called by:

INTEGER*4 system

status = system( string )

string

character*n

Input 

String containing command to do 

Return value 

INTEGER*4

Output 

Exit status of the shell executed. See wait(2) for an explanation of this value.

Example: system():


       character*8 string / ’ls s*’ /
       INTEGER*4 status, system
       status = system( string )
       if ( status .ne. 0 ) stop ’system: error’
       end

The function system passes string to your shell as input, as if the string had been typed as a command. Note: string cannot be longer than 1024 characters.

If system can find the environment variable SHELL, then system uses the value of SHELL as the command interpreter (shell); otherwise, it uses sh(1).

The current process waits until the command terminates.

Historically, cc developed with different assumptions:

The system function flushes all open files:

The functions sh(3f) and system(3f) pass the argument string to a shell for execution. They convert the argument string from a Fortran character value to a C string value and pass it to the C routine system(3c). The routines sh(3f) and system(3f) differ in that system flushes the Fortran I/O buffers before calling the C routine system, while sh does not. Flushing the buffers can take significant time, and so, if any Fortran output is irrelevant to the result of the call, the routine sh is preferred over the routine system.

See also: execve(2), wait(2), and system(3).

The system() function is not MT-safe. Do not call it from multithreaded or parallelized programs.

1.4.51 time, ctime, ltime, gmtime: Get System Time

These routines have the following functions:

time

Standard version: Get system time as integer (seconds since 0 GMT 1/1/70)

VMS Version: Get the system time as character (hh:mm:ss) 

ctime

Convert a system time to an ASCII string. 

ltime

Dissect a system time into month, day, and so forth, local time. 

gmtime

Dissect a system time into month, day, and so forth, GMT. 

1.4.51.1 time: Get System Time

The time() function is called by:

INTEGER*4 time or INTEGER*8

n = time() Standard Version

Return value 

INTEGER*4

Output 

Time, in seconds, since 0:0:0, GMT, 1/1/70 

 

INTEGER*8

Output 

In 64-bit environments, time returns an INTEGER*8 value

The function time() returns an integer with the time since 00:00:00 GMT, January 1, 1970, measured in seconds. This is the value of the operating system clock.

Example: time(), version standard with the operating system:


demo% cat ttime.f
        INTEGER*4  n, time
        n = time()
        write(*,*) ’Seconds since 0 1/1/70 GMT = ’, n
        end
demo% f95 ttime.f
demo% a.out
 Seconds since 0 1/1/70 GMT =   913240205
demo%

1.4.51.2 ctime: Convert System Time to Character

The function ctime converts a system time, stime, and returns it as a 24-character ASCII string.

The function is called by:

CHARACTER ctime*24

string = ctime( stime )

stime

INTEGER*4

Input 

System time from time() (standard version)

Return value 

character*24

Output 

System time as character string. Declare ctime and string as character*24.

The format of the ctime returned value is shown in the following example. It is described in the man page ctime(3C).

Example: ctime():


demo% cat tctime.f
        character*24 ctime, string
        INTEGER*4  n, time
        n = time()
        string = ctime( n )
        write(*,*) ’ctime: ’, string
        end
demo% f95 tctime.f
demo% a.out
 ctime: Wed Dec  9 13:50:05 1998
demo%

1.4.51.3 ltime: Split System Time to Month, Day,… (Local)

This routine dissects a system time into month, day, and so forth, for the local time zone.

The subroutine is called by:

call ltime( stime, tarray )

stime

INTEGER*4

Input 

System time from time() (standard version)

tarray

INTEGER*4(9)

Output 

System time, local, as day, month, year, … 

For the meaning of the elements in tarray, see the next section.

Example: ltime():


demo% cat tltime.f
        integer*4  stime, tarray(9), time
        stime = time()
        call ltime( stime, tarray )
        write(*,*) ’ltime: ’, tarray
        end
demo% f95 tltime.f
demo% a.out
 ltime: 25 49 10 12 7 91 1 223 1
demo%

1.4.51.4 gmtime: Split System Time to Month, Day, … (GMT)

This routine dissects a system time into month, day, and so on, for GMT.

The subroutine is:

call gmtime( stime, tarray )

stime

INTEGER*4

Input 

System time from time() (standard version)

tarray

INTEGER*4(9)

Output 

System time, GMT, as day, month, year, … 

Example: gmtime:


demo% cat tgmtime.f
        integer*4  stime, tarray(9), time
        stime = time()
        call gmtime( stime, tarray )
        write(*,*) ’gmtime: ’, tarray
        end
demo% f95t tgmtime.f
demo% a.out
 gmtime:   12  44  19  18  5  94  6  168  0
demo%

Here are the tarray() values for ltime and gmtime: index, units, and range:

Seconds (0 - 61) 

Minutes (0 - 59) 

Hours (0 - 23) 

Day of month (1 - 31) 

Months since January (0 - 11) 

Year - 1900 

Day of week (Sunday = 0) 

Day of year (0 - 365) 

Daylight Saving Time, 1 if DST in effect 

These values are defined by the C library routine ctime(3C), which explains why the system may return a count of seconds greater than 59. See also: idate(3F), and fdate(3F).

1.4.51.5 ctime64, gmtime64, ltime64: System Time Routines for 64-bit Environments

These are versions of the corresponding routines ctime, gmtime, and ltime, to provide portability on 64-bit environments. They are identical to these routines except that the input variable stime must be INTEGER*8.

When used in a 32-bit environment with an INTEGER*8 stime, if the value of stime is beyond the INTEGER*4 range ctime64 returns all asterisks, while gmtime and ltime fill the tarray array with -1.

1.4.52 ttynam, isatty: Get Name of a Terminal Port

ttynam and isatty handle terminal port names.

1.4.52.1 ttynam: Get Name of a Terminal Port

The function ttynam returns a blank padded path name of the terminal device associated with logical unit lunit.

The function is called by:

CHARACTER ttynam*24

name = ttynam( lunit )

lunit

INTEGER*4

Input 

Logical unit 

Return value 

character*n

Output 

If nonblank returned: name=path name of device on lunit. Size n must be large enough for the longest path name.

If empty string (all blanks) returned: lunit is not associated with a terminal device in the directory, /dev

1.4.52.2 isatty: Is this Unit a Terminal?

The function isatty returns true or false depending on whether or not logical unit lunit is a terminal device or not.

The function is called by:

terminal = isatty( lunit )

lunit

INTEGER*4

Input 

Logical unit 

Return value 

LOGICAL*4

Output 

terminal=true: It is a terminal device

terminal=false: It is not a terminal device

Example: Determine if lunit is a tty:


       character*12 name, ttynam
       INTEGER*4 lunit /5/
       logical*4 isatty, terminal
       terminal = isatty( lunit )
       name = ttynam( lunit )
       write(*,*) ’terminal = ’, terminal, ’, name = "’, name, ’"’
       end

The output is:


 terminal = T, name = "/dev/ttyp1  "

1.4.53 unlink: Remove a File

The function is called by:

INTEGER*4 unlink

n = unlink ( patnam )

patnam

character*n

Input 

File name 

Return value 

INTEGER*4

Output 

n=0: OK

n>0: Error

The function unlink removes the file specified by path name patnam. If this is the last link to the file, the contents of the file are lost.

Example: unlink()—Remove the tunlink.data file:


demo% cat tunlink.f
       call unlink( ’tunlink.data’ )
       end
demo% f95 tunlink.f
demo% ls tunl*
tunlink.f tunlink.data
demo% a.out
demo% ls tunl*
tunlink.f

See also: unlink(2), link(3F), and perror(3F). Note: the path names cannot be longer than MAXPATHLEN as defined in <sys/param.h>.

1.4.54 wait: Wait for a Process to Terminate

The function is:

INTEGER*4 wait

n = wait( status )

status

INTEGER*4

Output 

Termination status of the child process 

Return value 

INTEGER*4

Output 

n>0: Process ID of the child process

n<0: n=System error code; see wait(2).

wait suspends the caller until a signal is received, or one of its child processes terminates. If any child has terminated since the last wait, return is immediate. If there are no children, return is immediate with an error code.

Example: Code fragment using wait():


       INTEGER*4 n, status, wait
       …
       n = wait( status )
       if ( n .lt. 0 ) stop ’wait: error’
       …
       end

See also: wait(2), signal(3F), kill(3F), and perror(3F).