Contents

XL Fortran for Linux

  • Language Standards
  • Fortran 2003 Draft Standard
  • Fortran 95
  • Fortran 90
  • Other Standards and Standards Documents
  • Typographical Conventions
  • How to Read Syntax Diagrams
  • Sample Syntax Diagram
  • Using Examples
  • Fundamentals of the XL Fortran Language

  • Characters
  • Names
  • Statements
  • Statement Keywords
  • Statement Labels
  • Lines and Source Formats
  • Fixed Source Form
  • Free Source Form
  • IBM Free Source Form
  • Conditional Compilation
  • Order of Statements and Execution Sequence
  • Data Types and Data Objects

  • Data Types
  • Type Parameters and Specifiers
  • Data Objects
  • Constants
  • Automatic Objects
  • Intrinsic Types
  • Integer
  • Real
  • Complex
  • Logical
  • Character
  • BYTE
  • Derived Types
  • Input/Output
  • Determining Type for Derived Types
  • Record Structures
  • Union and Map
  • Typeless Literal Constants
  • Hexadecimal Constants
  • Octal Constants
  • Binary Constants
  • Hollerith Constants
  • Using Typeless Constants
  • How Type Is Determined
  • Definition Status of Variables
  • Events Causing Definition
  • Events Causing Undefinition
  • Allocation Status
  • Storage Classes for Variables
  • Fundamental Storage Classes
  • Secondary Storage Classes
  • Storage Class Assignment
  • Array Concepts

  • Arrays
  • Bounds of a Dimension
  • Extent of a Dimension
  • Rank, Shape, and Size of an Array
  • Array Declarators
  • Explicit-Shape Arrays
  • Examples of Explicit-Shape Arrays
  • Automatic Arrays
  • Adjustable Arrays
  • Pointee Arrays
  • Assumed-Shape Arrays
  • Examples of Assumed-Shape Arrays
  • Deferred-Shape Arrays
  • Allocatable Arrays
  • Array Pointers
  • Assumed-Size Arrays
  • Examples of Assumed-Size Arrays
  • Array Elements
  • Notes
  • Array Element Order
  • Array Sections
  • Subscript Triplets
  • Vector Subscripts
  • Array Sections and Substring Ranges
  • Array Sections and Structure Components
  • Rank and Shape of Array Sections
  • Array Constructors
  • Implied-DO List for an Array Constructor
  • Expressions Involving Arrays
  • Expressions and Assignment

  • Introduction to Expressions and Assignment
  • Primary
  • Constant Expressions
  • Examples of Constant Expressions
  • Initialization Expressions
  • Examples of Initialization Expressions
  • Specification Expressions
  • Examples of Specification Expressions
  • Operators and Expressions
  • Arithmetic
  • Character
  • General
  • Logical
  • Primary
  • Relational
  • Extended Intrinsic and Defined Operations
  • How Expressions Are Evaluated
  • Precedence of Operators
  • Using BYTE Data Objects
  • Intrinsic Assignment
  • Arithmetic Conversion
  • WHERE Construct
  • Interpreting Masked Array Assignments
  • FORALL Construct
  • Interpreting the FORALL Construct
  • Pointer Assignment
  • Examples of Pointer Assignment
  • Integer Pointer Assignment
  • Execution Control

  • Statement Blocks
  • ASSOCIATE Construct
  • DO Construct
  • The Terminal Statement
  • DO WHILE Construct
  • Example
  • IF Construct
  • Example
  • SELECT CASE Construct
  • Examples
  • Branching
  • Program Units and Procedures

  • Scope
  • The Scope of a Name
  • Association
  • Construct Association
  • Host Association
  • Use Association
  • Pointer Association
  • Integer Pointer Association
  • Program Units, Procedures, and Subprograms
  • Internal Procedures
  • Interface Concepts
  • Interface Blocks
  • Example of an Interface
  • Generic Interface Blocks
  • Unambiguous Generic Procedure References
  • Extending Intrinsic Procedures with Generic Interface Blocks
  • Defined Operators
  • Defined Assignment
  • Main Program
  • Modules
  • Example of a Module
  • Block Data Program Unit
  • Example of a Block Data Program Unit
  • Function and Subroutine Subprograms
  • Procedure References
  • Intrinsic Procedures
  • Conflicts Between Intrinsic Procedure Names and Other Names
  • Arguments
  • Actual Argument Specification
  • Argument Association
  • %VAL and %REF
  • Intent of Dummy Arguments
  • Optional Dummy Arguments
  • Restrictions on Optional Dummy Arguments Not Present
  • Length of Character Arguments
  • Variables as Dummy Arguments
  • Allocatable Objects as Dummy Arguments
  • Pointers as Dummy Arguments
  • Procedures as Dummy Arguments
  • Asterisks as Dummy Arguments
  • Resolution of Procedure References
  • Rules for Resolving Procedure References to Names
  • Resolving Procedure References to Generic Names
  • Recursion
  • Pure Procedures
  • Examples
  • Elemental Procedures
  • Examples
  • XL Fortran Input/Output

  • Records
  • Formatted Records
  • Unformatted Records
  • Endfile Records
  • Files
  • Definition of an External File
  • File Access Methods
  • Units
  • Connection of a Unit
  • Data Transfer Statements
  • Asynchronous Input/Output
  • Advancing and Nonadvancing Input/Output
  • File Position Before and After Data Transfer
  • Conditions and IOSTAT Values
  • End-Of-Record Conditions
  • End-Of-File Conditions
  • Error Conditions
  • Input/Output Formatting

  • Format-Directed Formatting
  • Complex Editing
  • Data Edit Descriptors
  • Control Edit Descriptors
  • Interaction of Input/Output Lists and Format Specifications
  • Comma-Separated Input/Output
  • Data Edit Descriptors
  • A (Character) Editing
  • B (Binary) Editing
  • E, D, and Q (Extended Precision) Editing
  • EN Editing
  • ES Editing
  • F (Real without Exponent) Editing
  • G (General) Editing
  • I (Integer) Editing
  • L (Logical) Editing
  • O (Octal) Editing
  • Q (Character Count) Editing
  • Z (Hexadecimal) Editing
  • Control Edit Descriptors
  • / (Slash) Editing
  • : (Colon) Editing
  • $ (Dollar) Editing
  • Apostrophe/Double Quotation Mark Editing (Character-String Edit Descriptor)
  • BN (Blank Null) and BZ (Blank Zero) Editing
  • H Editing
  • P (Scale Factor) Editing
  • S, SP, and SS (Sign Control) Editing
  • T, TL, TR, and X (Positional) Editing
  • List-Directed Formatting
  • Value Separators
  • List-Directed Input
  • List-Directed Output
  • Namelist Formatting
  • Namelist Input
  • Namelist Output
  • Statements and Attributes

  • Attributes
  • ALLOCATABLE
  • ALLOCATE
  • ASSIGN
  • ASSOCIATE
  • AUTOMATIC
  • BACKSPACE
  • BIND
  • BLOCK DATA
  • BYTE
  • CALL
  • CASE
  • CHARACTER
  • CLOSE
  • COMMON
  • COMPLEX
  • CONTAINS
  • CONTINUE
  • CYCLE
  • DATA
  • DEALLOCATE
  • Derived Type
  • DIMENSION
  • DO
  • DO WHILE
  • DOUBLE COMPLEX
  • DOUBLE PRECISION
  • ELSE
  • ELSE IF
  • ELSEWHERE
  • END
  • END (Construct)
  • END INTERFACE
  • END TYPE
  • ENDFILE
  • ENTRY
  • EQUIVALENCE
  • EXIT
  • EXTERNAL
  • FLUSH
  • FORALL
  • FORALL (Construct)
  • FORMAT
  • FUNCTION
  • GO TO (Assigned)
  • GO TO (Computed)
  • GO TO (Unconditional)
  • IF (Arithmetic)
  • IF (Block)
  • IF (Logical)
  • IMPLICIT
  • IMPORT
  • INQUIRE
  • INTEGER
  • INTENT
  • INTERFACE
  • INTRINSIC
  • LOGICAL
  • MODULE
  • MODULE PROCEDURE
  • NAMELIST
  • NULLIFY
  • OPEN
  • OPTIONAL
  • PARAMETER
  • PAUSE
  • POINTER (Fortran 90)
  • POINTER (integer)
  • PRINT
  • PRIVATE
  • PROCEDURE
  • PROGRAM
  • PROTECTED
  • PUBLIC
  • READ
  • REAL
  • RECORD
  • RETURN
  • REWIND
  • SAVE
  • SELECT CASE
  • SEQUENCE
  • Statement Function
  • STATIC
  • STOP
  • SUBROUTINE
  • TARGET
  • TYPE
  • Type Declaration
  • USE
  • VALUE
  • VIRTUAL
  • VOLATILE
  • WAIT
  • WHERE
  • WRITE
  • Directives

  • Comment and Noncomment Form Directives
  • Comment Form Directives
  • Noncomment Form Directives
  • Directives and Optimization
  • Assertive Directives
  • Directives for Loop Optimization
  • Detailed Directive Descriptions
  • ASSERT
  • BLOCK_LOOP
  • CNCALL
  • COLLAPSE
  • EJECT
  • INCLUDE
  • INDEPENDENT
  • #LINE
  • LOOPID
  • NOSIMD
  • NOVECTOR
  • PERMUTATION
  • @PROCESS
  • SNAPSHOT
  • SOURCEFORM
  • STREAM_UNROLL
  • SUBSCRIPTORDER
  • UNROLL
  • UNROLL_AND_FUSE
  • Hardware-Specific Directives

  • CACHE_ZERO
  • EIEIO
  • ISYNC
  • LIGHT_SYNC
  • PREFETCH
  • PROTECTED STREAM
  • SMP Directives

  • An Introduction to SMP Directives
  • Parallel Region Construct
  • Work-sharing Constructs
  • Combined Parallel Work-sharing Constructs
  • Synchronization Constructs
  • Other OpenMP Directives
  • Non-OpenMP SMP Directives
  • Detailed Descriptions of SMP Directives
  • ATOMIC
  • BARRIER
  • CRITICAL / END CRITICAL
  • DO / END DO
  • DO SERIAL
  • FLUSH
  • MASTER / END MASTER
  • ORDERED / END ORDERED
  • PARALLEL / END PARALLEL
  • PARALLEL DO / END PARALLEL DO
  • PARALLEL SECTIONS / END PARALLEL SECTIONS
  • PARALLEL WORKSHARE / END PARALLEL WORKSHARE
  • SCHEDULE
  • SECTIONS / END SECTIONS
  • SINGLE / END SINGLE
  • THREADLOCAL
  • THREADPRIVATE
  • WORKSHARE
  • OpenMP Directive Clauses
  • Global Rules for Directive Clauses
  • COPYIN
  • COPYPRIVATE
  • DEFAULT
  • IF
  • FIRSTPRIVATE
  • LASTPRIVATE
  • NUM_THREADS
  • ORDERED
  • PRIVATE
  • REDUCTION
  • SCHEDULE
  • SHARED
  • Intrinsic Procedures

  • Classes of Intrinsic Procedures
  • Inquiry Intrinsic Functions
  • Elemental Intrinsic Procedures
  • System Inquiry Intrinsic Functions
  • Transformational Intrinsic Functions
  • Intrinsic Subroutines
  • Data Representation Models
  • Integer Bit Model
  • Integer Data Model
  • Real Data Model
  • Detailed Descriptions of Intrinsic Procedures
  • ABORT()
  • ABS(A)
  • ACHAR(I)
  • ACOS(X)
  • ACOSD(X)
  • ADJUSTL(STRING)
  • ADJUSTR(STRING)
  • AIMAG(Z), IMAG(Z)
  • AINT(A, KIND)
  • ALL(MASK, DIM)
  • ALLOCATED(ARRAY) or ALLOCATED(SCALAR)
  • ANINT(A, KIND)
  • ANY(MASK, DIM)
  • ASIN(X)
  • ASIND(X)
  • ASSOCIATED(POINTER, TARGET)
  • ATAN(X)
  • ATAND(X)
  • ATAN2(Y, X)
  • ATAN2D(Y, X)
  • BIT_SIZE(I)
  • BTEST(I, POS)
  • CEILING(A, KIND)
  • CHAR(I, KIND)
  • CMPLX(X, Y, KIND)
  • COMMAND_ARGUMENT_COUNT()
  • CONJG(Z)
  • COS(X)
  • COSD(X)
  • COSH(X)
  • COUNT(MASK, DIM)
  • CPU_TIME(TIME)
  • CSHIFT(ARRAY, SHIFT, DIM)
  • CVMGx(TSOURCE, FSOURCE, MASK)
  • DATE_AND_TIME(DATE, TIME, ZONE, VALUES)
  • DBLE(A)
  • DCMPLX(X, Y)
  • DIGITS(X)
  • DIM(X, Y)
  • DOT_PRODUCT(VECTOR_A, VECTOR_B)
  • DPROD(X, Y)
  • EOSHIFT(ARRAY, SHIFT, BOUNDARY, DIM)
  • EPSILON(X)
  • ERF(X)
  • ERFC(X)
  • EXP(X)
  • EXPONENT(X)
  • FLOOR(A, KIND)
  • FRACTION(X)
  • GAMMA(X)
  • GETENV(NAME, VALUE)
  • GET_COMMAND(COMMAND, LENGTH, STATUS)
  • GET_COMMAND_ARGUMENT(NUMBER, VALUE, LENGTH, STATUS)
  • GET_ENVIRONMENT_VARIABLE(NAME, VALUE, LENGTH, STATUS, TRIM_NAME)
  • HFIX(A)
  • HUGE(X)
  • IACHAR(C)
  • IAND(I, J)
  • IBCLR(I, POS)
  • IBITS(I, POS, LEN)
  • IBSET(I, POS)
  • ICHAR(C)
  • IEOR(I, J)
  • ILEN(I)
  • IMAG(Z)
  • INDEX(STRING, SUBSTRING, BACK)
  • INT(A, KIND)
  • INT2(A)
  • IOR(I, J)
  • ISHFT(I, SHIFT)
  • ISHFTC(I, SHIFT, SIZE)
  • KIND(X)
  • LBOUND(ARRAY, DIM)
  • LEADZ(I)
  • LEN(STRING)
  • LEN_TRIM(STRING)
  • LGAMMA(X)
  • LGE(STRING_A, STRING_B)
  • LGT(STRING_A, STRING_B)
  • LLE(STRING_A, STRING_B)
  • LLT(STRING_A, STRING_B)
  • LOC(X)
  • LOG(X)
  • LOG10(X)
  • LOGICAL(L, KIND)
  • LSHIFT(I, SHIFT)
  • MATMUL(MATRIX_A, MATRIX_B, MINDIM)
  • MAX(A1, A2, A3, ...)
  • MAXEXPONENT(X)
  • MAXLOC(ARRAY, DIM, MASK) or MAXLOC(ARRAY, MASK)
  • MAXVAL(ARRAY, DIM, MASK) or MAXVAL(ARRAY, MASK)
  • MERGE(TSOURCE, FSOURCE, MASK)
  • MIN(A1, A2, A3, ...)
  • MINEXPONENT(X)
  • MINLOC(ARRAY, DIM, MASK) or MINLOC(ARRAY, MASK)
  • MINVAL(ARRAY, DIM, MASK) or MINVAL(ARRAY, MASK)
  • MOD(A, P)
  • MODULO(A, P)
  • MVBITS(FROM, FROMPOS, LEN, TO, TOPOS)
  • NEAREST(X,S)
  • NEW_LINE(A)
  • NINT(A, KIND)
  • NOT(I)
  • NULL(MOLD)
  • NUM_PARTHDS()
  • NUMBER_OF_PROCESSORS(DIM)
  • NUM_USRTHDS()
  • PACK(ARRAY, MASK, VECTOR)
  • POPCNT(I)
  • POPPAR(I)
  • PRECISION(X)
  • PRESENT(A)
  • PROCESSORS_SHAPE()
  • PRODUCT(ARRAY, DIM, MASK) or PRODUCT(ARRAY, MASK)
  • QCMPLX(X, Y)
  • QEXT(A)
  • RADIX(X)
  • RAND()
  • RANDOM_NUMBER(HARVEST)
  • RANDOM_SEED(SIZE, PUT, GET, GENERATOR)
  • RANGE(X)
  • REAL(A, KIND)
  • REPEAT(STRING, NCOPIES)
  • RESHAPE(SOURCE, SHAPE, PAD, ORDER)
  • RRSPACING(X)
  • RSHIFT(I, SHIFT)
  • SCALE(X,I)
  • SCAN(STRING, SET, BACK)
  • SELECTED_INT_KIND(R)
  • SELECTED_REAL_KIND(P, R)
  • SET_EXPONENT(X,I)
  • SHAPE(SOURCE)
  • SIGN(A, B)
  • SIGNAL(I, PROC)
  • SIN(X)
  • SIND(X)
  • SINH(X)
  • SIZE(ARRAY, DIM)
  • SIZEOF(A)
  • SPACING(X)
  • SPREAD(SOURCE, DIM, NCOPIES)
  • SQRT(X)
  • SRAND(SEED)
  • SUM(ARRAY, DIM, MASK) or SUM(ARRAY, MASK)
  • SYSTEM(CMD, RESULT)
  • SYSTEM_CLOCK(COUNT, COUNT_RATE, COUNT_MAX)
  • TAN(X)
  • TAND(X)
  • TANH(X)
  • TINY(X)
  • TRANSFER(SOURCE, MOLD, SIZE)
  • TRANSPOSE(MATRIX)
  • TRIM(STRING)
  • UBOUND(ARRAY, DIM)
  • UNPACK(VECTOR, MASK, FIELD)
  • VERIFY(STRING, SET, BACK)
  • Hardware-Specific Intrinsic Procedures

  • ALIGNX(K,M)
  • FCFI(I)
  • FCTID(X)
  • FCTIDZ(X)
  • FCTIW(X)
  • FCTIWZ(X)
  • FMADD(A, X, Y)
  • FMSUB(A, X, Y)
  • FNABS(X)
  • FNMADD(A, X, Y)
  • FNMSUB(A, X, Y)
  • FRE(X)
  • FRES(X)
  • FRSQRTE(X)
  • FRSQRTES(X)
  • FSEL(X,Y,Z)
  • MTFSF(MASK, R)
  • MTFSFI(BF, I)
  • MULHY(RA, RB)
  • POPCNTB(I)
  • ROTATELI(RS, IS, SHIFT, MASK)
  • ROTATELM(RS, SHIFT, MASK)
  • SETFSB0(BT)
  • SETFSB1(BT)
  • SFTI(M, Y)
  • SWDIV(X,Y)
  • SWDIV_NOCHK(X,Y)
  • TRAP(A, B, TO)
  • Language Interoperability Features

  • Interoperability of Types
  • Intrinsic Types
  • Derived Types
  • Interoperability of Variables
  • Interoperability of Common Blocks
  • Interoperability of Procedures
  • The ISO_C_BINDING Module
  • Constants for use as Kind Type Parameters
  • Character Constants
  • Other Constants
  • Types
  • Procedures
  • Binding Labels
  • The ISO_FORTRAN_ENV Intrinsic Module

  • CHARACTER_STORAGE_SIZE
  • ERROR_UNIT
  • FILE_STORAGE_SIZE
  • INPUT_UNIT
  • IOSTAT_END
  • IOSTAT_EOR
  • NUMERIC_STORAGE_SIZE
  • OUTPUT_UNIT
  • OpenMP Execution Environment and Lock Routines

  • omp_destroy_lock(svar)
  • omp_destroy_nest_lock(nvar)
  • omp_get_dynamic()
  • omp_get_max_threads()
  • omp_get_nested()
  • omp_get_num_procs()
  • omp_get_num_threads()
  • omp_get_thread_num()
  • omp_get_wtick()
  • omp_get_wtime()
  • omp_in_parallel()
  • omp_init_lock(svar)
  • omp_init_nest_lock(nvar)
  • omp_set_dynamic(enable_expr)
  • omp_set_lock(svar)
  • omp_set_nested(enable_expr)
  • omp_set_nest_lock(nvar)
  • omp_set_num_threads(number_of_threads_expr)
  • omp_test_lock(svar)
  • omp_test_nest_lock(nvar)
  • omp_unset_lock(svar)
  • omp_unset_nest_lock(nvar)
  • Pthreads Library Module

  • Pthreads Data Structures, Functions, and Subroutines
  • Pthreads Data Types
  • Functions That Perform Operations on Thread Attribute Objects
  • Functions and Subroutines That Perform Operations on Threads
  • Functions That Perform Operations on Mutex Attribute Objects
  • Functions That Perform Operations on Mutex Objects
  • Functions That Perform Operations on Attribute Objects of Condition Variables
  • Functions That Perform Operations on Condition Variable Objects
  • Functions That Perform Operations on Thread-Specific Data
  • Functions and Subroutines That Perform Operations to Control Thread Cancelability
  • Functions That Perform Operations on Read-Write Lock Attribute Objects
  • Functions That Perform Operations on Read-Write Lock Objects
  • Functions That Perform Operations for One-Time Initialization
  • f_maketime(delay)
  • f_pthread_attr_destroy(attr)
  • f_pthread_attr_getdetachstate(attr, detach)
  • f_pthread_attr_getguardsize(attr, guardsize)
  • f_pthread_attr_getinheritsched(attr, inherit)
  • f_pthread_attr_getschedparam(attr, param)
  • f_pthread_attr_getschedpolicy(attr, policy)
  • f_pthread_attr_getscope(attr, scope)
  • f_pthread_attr_getstack(attr, stackaddr, ssize)
  • f_pthread_attr_init(attr)
  • f_pthread_attr_setdetachstate(attr, detach)
  • f_pthread_attr_setguardsize(attr, guardsize)
  • f_pthread_attr_setinheritsched(attr, inherit)
  • f_pthread_attr_setschedparam(attr, param)
  • f_pthread_attr_setschedpolicy(attr, policy)
  • f_pthread_attr_setscope(attr, scope)
  • f_pthread_attr_setstack(attr, stackaddr, ssize)
  • f_pthread_attr_t
  • f_pthread_cancel(thread)
  • f_pthread_cleanup_pop(exec)
  • f_pthread_cleanup_push(cleanup, flag, arg)
  • f_pthread_cond_broadcast(cond)
  • f_pthread_cond_destroy(cond)
  • f_pthread_cond_init(cond, cattr)
  • f_pthread_cond_signal(cond)
  • f_pthread_cond_t
  • f_pthread_cond_timedwait(cond, mutex, timeout)
  • f_pthread_cond_wait(cond, mutex)
  • f_pthread_condattr_destroy(cattr)
  • f_pthread_condattr_getpshared(cattr, pshared)
  • f_pthread_condattr_init(cattr)
  • f_pthread_condattr_setpshared(cattr, pshared)
  • f_pthread_condattr_t
  • f_pthread_create(thread, attr, flag, ent, arg)
  • f_pthread_detach(thread)
  • f_pthread_equal(thread1, thread2)
  • f_pthread_exit(ret)
  • f_pthread_getconcurrency()
  • f_pthread_getschedparam(thread, policy, param)
  • f_pthread_getspecific(key, arg)
  • f_pthread_join(thread, ret)
  • f_pthread_key_create(key, dtr)
  • f_pthread_key_delete(key)
  • f_pthread_key_t
  • f_pthread_kill(thread, sig)
  • f_pthread_mutex_destroy(mutex)
  • f_pthread_mutex_init(mutex, mattr)
  • f_pthread_mutex_lock(mutex)
  • f_pthread_mutex_t
  • f_pthread_mutex_trylock(mutex)
  • f_pthread_mutex_unlock(mutex)
  • f_pthread_mutexattr_destroy(mattr)
  • f_pthread_mutexattr_getpshared(mattr, pshared)
  • f_pthread_mutexattr_gettype(mattr, type)
  • f_pthread_mutexattr_init(mattr)
  • f_pthread_mutexattr_setpshared(mattr, pshared)
  • f_pthread_mutexattr_settype(mattr, type)
  • f_pthread_mutexattr_t
  • f_pthread_once(once, initr)
  • f_pthread_once_t
  • f_pthread_rwlock_destroy(rwlock)
  • f_pthread_rwlock_init(rwlock, rwattr)
  • f_pthread_rwlock_rdlock(rwlock)
  • f_pthread_rwlock_t
  • f_pthread_rwlock_tryrdlock(rwlock)
  • f_pthread_rwlock_trywrlock(rwlock)
  • f_pthread_rwlock_unlock(rwlock)
  • f_pthread_rwlock_wrlock(rwlock)
  • f_pthread_rwlockattr_destroy(rwattr)
  • f_pthread_rwlockattr_getpshared(rwattr, pshared)
  • f_pthread_rwlockattr_init(rwattr)
  • f_pthread_rwlockattr_setpshared(rwattr, pshared)
  • f_pthread_rwlockattr_t
  • f_pthread_self()
  • f_pthread_setcancelstate(state, oldstate)
  • f_pthread_setcanceltype(type, oldtype)
  • f_pthread_setconcurrency(new_level)
  • f_pthread_setschedparam(thread, policy, param)
  • f_pthread_setspecific(key, arg)
  • f_pthread_t
  • f_pthread_testcancel()
  • f_sched_param
  • f_sched_yield()
  • f_timespec
  • Floating-Point Control and Inquiry Procedures

  • fpgets fpsets
  • Efficient Floating-Point Control and Inquiry Procedures
  • xlf_fp_util Floating-Point Procedures
  • IEEE Modules and Support
  • Compiling and Exception Handling
  • General Rules for Implementing IEEE Modules
  • IEEE Derived Data Types and Constants
  • IEEE Operators
  • IEEE PROCEDURES
  • Rules for Floating-Point Status
  • Examples
  • Service and Utility Procedures

  • General Service and Utility Procedures
  • List of Service and Utility Procedures
  • alarm_(time, func)
  • bic_(X1, X2)
  • bis_(X1, X2)
  • bit_(X1, X2)
  • clock_()
  • ctime_(STR, TIME)
  • date()
  • dtime_(dtime_struct)
  • etime_(etime_struct)
  • exit_(exit_status)
  • fdate_(str)
  • fiosetup_(unit, command, argument)
  • flush_(lunit)
  • ftell_(lunit)
  • ftell64_(lunit)
  • getarg(i1,c1)
  • getcwd_(name)
  • getfd(lunit)
  • getgid_()
  • getlog_(name)
  • getpid_()
  • getuid_()
  • global_timef()
  • gmtime_(stime, tarray)
  • hostnm_(name)
  • iargc()
  • idate_(idate_struct)
  • ierrno_()
  • irand()
  • irtc()
  • itime_(itime_struct)
  • jdate()
  • lenchr_(str)
  • lnblnk_(str)
  • ltime_(stime, tarray)
  • mclock()
  • qsort_(array, len, isize, compar)
  • qsort_down(array, len, isize)
  • qsort_up(array, len, isize)
  • rtc()
  • setrteopts(c1)
  • sleep_(sec)
  • time_()
  • timef()
  • timef_delta(t)
  • umask_(cmask)
  • usleep_(msec)
  • xl__trbk()
  • Appendix A. Compatibility Across Standards

  • Fortran 90 compatibility
  • Obsolescent Features
  • Deleted Features
  • Appendix B. ASCII and EBCDIC Character Sets

    Glossary

    IBM Copyright 2003