BCS Logo
BRITISH COMPUTER SOCIETY Fortran Specialist Group

Fortran 2000
Programme
The Group
Comment
Overview
Data handling
Derived types
OO features
Report

About Us
FSG Home page
Joining the Group
Contact details

Important Disclaimer

Floating-point Exception Handling and
Interfacing with C


John Reid, JKR Associates
Convener, ISO Fortran Committee WG5

Please note: this HTML file has been constructed directly from the slides used in the presentation.


Requirements for handling exceptions
  • Access IEEE conditions on IEEE hardware
  • Support other aspects of IEEE
  • Recognize partial support and provide enquiries
  • Provide control on the degree of support
  • Allow partial support on non-IEEE hardware

We found that it was impossible to do all this with a procedure library or a non-intrinsic module.

With an intrinsic module, we can make the USE statement control the compiler's action.

Snag: Cannot develop an implementation outside the compiler.


Intrinsic modules

IEEE_EXCEPTIONS supports exceptions - at least overflow and divide-by-zero.

IEEE_ARITHMETIC supports other IEEE features. It behaves as if it has a USE statement for IEEE_EXCEPTIONS.

IEEE_FEATURES provides control over the features needed.

Example:

USE, INTRINSIC :: IEEE_EXCEPTIONS
USE, INTRINSIC :: IEEE_FEATURES, &
               ONLY:IEEE_INVALID_FLAG


Types for flags and status

IEEE_EXCEPTIONS and IEEE_ARITHMETIC
contain:

  • IEEE_FLAG_TYPE, with values:
    IEEE_OVERFLOW, IEEE_DIVIDE_BY_ZERO,
    IEEE_INVALID, IEEE_UNDERFLOW, and
    IEEE_INEXACT.
  • IEEE_STATUS_TYPE, for saving the floating point status.

The modules also contains the array constants
IEEE_USUAL = (/ IEEE_OVERFLOW, IEEE_DIVIDE_BY_ZERO, IEEE_INVALID /),
IEEE_ALL = (/ IEEE_USUAL, IEEE_UNDERFLOW, IEEE_INEXACT /).


Types for class and rounding

The module IEEE_ARITHMETIC contains:

  • IEEE_CLASS_TYPE, with values:
    IEEE_NEGATIVE_INF,
    IEEE_NEGATIVE_NORMAL
    IEEE_NEGATIVE_DENORMAL,
    IEEE_NEGATIVE_ZERO,
    IEEE_POSITIVE_ZERO,
    IEEE_POSITIVE_DENORMAL,
    IEEE_POSITIVE_NORMAL,
    IEEE_POSITIVE_INF,
    IEEE_SIGNALING_NAN, IEEE_QUIET_NAN.
  • IEEE_ROUND_TYPE, with values:
    IEEE_NEAREST, IEEE_TO_ZERO, IEEE_UP, IEEE_DOWN, IEEE_OTHER.


The module IEEE_FEATURES

IEEE_FEATURES contains the derived type:

  • IEEE_FEATURES_TYPE, with values:
    IEEE_DATATYPE,
    IEEE_DENORMAL,
    IEEE_DIVIDE,
    IEEE_HALTING,
    IEEE_INEXACT_FLAG,
    IEEE_INF,
    IEEE_INVALID_FLAG,
    IEEE_NAN,
    IEEE_ROUNDING,
    IEEE_SQRT,
    IEEE_UNDERFLOW_FLAG.


Inquiry functions

The modules IEEE_EXCEPTIONS and IEEE_ARITHMETIC contain:

  • IEEE_SUPPORT_FLAG(FLAG[,X])
  • IEEE_SUPPORT_HALTING(FLAG)

The module IEEE_ARITHMETIC contains:

  • IEEE_SUPPORT_DATATYPE([X])
  • IEEE_SUPPORT_DENORMAL([X])
  • IEEE_SUPPORT_DIVIDE([X])
  • IEEE_SUPPORT_INF([X])
  • IEEE_SUPPORT_NAN([X])
  • IEEE_SUPPORT_ROUNDING(ROUND_VALUE[,X])
  • IEEE_SUPPORT_SQRT([X])
  • IEEE_SUPPORT_STANDARD([X])


Elemental functions

The module IEEE_ARITHMETIC contains:

  • IEEE_CLASS(X)
  • IEEE_COPY_SIGN(X,Y)
  • IEEE_IS_FINITE(X)
  • IEEE_IS_NAN(X)
  • IEEE_IS_NEGATIVE(X)
  • IEEE_IS_NORMAL(X)
  • IEEE_LOGB(X)
  • IEEE_NEXT_AFTER(X,Y)
  • IEEE_REM(X,Y)
  • IEEE_RINT(X)
  • IEEE_SCALB(X,I)
  • IEEE_UNORDERED(X,Y)
  • IEEE_VALUE(X,CLASS)


Elemental subroutines

The modules IEEE_EXCEPTIONS and IEEE_ARITHMETIC contain:

  • IEEE_GET_FLAG(FLAG,FLAG_VALUE)
  • IEEE_GET_HALTING_MODE(FLAG,HALTING)
  • IEEE_SET_FLAG(FLAG,FLAG_VALUE)
  • IEEE_SET_HALTING_MODE(FLAG,HALTING)


Non-elemental subroutines

The modules IEEE_EXCEPTIONS and IEEE_ARITHMETIC contain:

  • IEEE_GET_STATUS(STATUS_VALUE)
  • IEEE_SET_STATUS(STATUS_VALUE)

The module IEEE_ARITHMETIC contains:

  • IEEE_GET_ROUNDING_MODE(ROUND_VALUE)
  • IEEE_SET_ROUNDING_MODE(ROUND_VALUE)
Transformational function

The module IEEE_ARITHMETIC contains:

  • IEEE_SELECTED_REAL_KIND([P,][R])

Back to the top


Interoperability with C

Any entity involved in interoperating with C must be such that equivalent declarations of it may be made in the two languages.

Enforced within the Fortran program by requiring all such entities to be interoperable.

We will explain in turn what this requires for types, variables, and procedures.

They are all requirements on the syntax so that the compiler knows at compile time whether an entity is interoperable.

We finish with two examples.


Interoperability of intrinsic types

Intrinsic module "ISO_C_BINDING" contains named constants holding kind type parameter values.

For integer type:

C_INT               int
C_SHORT             short int
C_LONG              long int
C_LONG_LONG         long long int
C_SIGNED_CHAR       signed char, unsigned char
C_SIZE_T            size_t
C_INT_LEAST8_T      int_least8_t
C_INT_LEAST16_T     int_least16_t
C_INT_LEAST32_T     int_least32_t
C_INT_LEAST64_T     int_least64_t
C_INT_FAST8_T       int_fast8_t
C_INT_FAST16_T      int_fast16_t
C_INT_FAST32_T      int_fast32_t
C_INT_FAST64_T      int_fast64_t
C_INTMAX_T          c intmax_t


For other types:

C_FLOAT                float
C_DOUBLE               double
C_LONG_DOUBLE          long double
                       
C_FLOAT_COMPLEX        float _Complex
C_DOUBLE_COMPLEX       double _Complex
C_LONG_DOUBLE_COMPLEX  long double _Complex

C_BOOL                 _Bool
                      
C_CHAR                 char

Lack of support is indicated with a negative value.

For character type, interoperability requires that LEN be one and these named constants are provided: C_NULL_CHAR, C_ALERT, C_BACKSPACE, C_FORM_FEED, C_NEW_LINE, C_CARRIAGE_RETURN, C_HORIZONTAL_TAB, C_VERTICAL_TAB.


Interoperability of derived types

For a derived type to be interoperable, it must be given the BIND attribute explicitly:

      TYPE, BIND(C) :: MYTYPE
       :
      END TYPE MYTYPE

Each component must have interoperable type and type parameters, must not be a pointer, and must not be allocatable. This allows Fortran and C types to correspond, for example

         typedef struct {
           int m, n;
           float r;
         } myctype

is interoperable with

         USE ISO_C_BINDING
         TYPE, BIND(C) :: MYFTYPE
           INTEGER(C_INT) :: I, J
           REAL(C_FLOAT) :: S
         END TYPE MYFTYPE


The name of the type and the names of the components are not significant for interoperability.

No Fortran type is interoperable with a C union type, struct type that contains a bit field, or struct type that contains a flexible array member.


Interoperability of variables

A scalar Fortran variable is interoperable if it is of interoperable type and type parameters, and is neither a pointer nor allocatable.

An array Fortran variable is interoperable if it is of interoperable type and type parameters, and is of explicit shape or assumed size. It interoperates with a C array of the same type, type parameters and shape, but with reversal of subscripts.

For example, a Fortran array declared as

       INTEGER :: A(18, 3:7, *)

is interoperable with a C array declared as

       int b[][5][18]


Interoperability with C pointers

For interoperating with C pointers (addresses), the module contains a derived type C_PTR that is interoperable with any C pointer type and a named constant C_NULL_PTR.

The module also contains the procedures:

C_LOC(X) returns the C address of X.
X is permitted to be
  1. a procedure that is interoperable;
  2. a variable with interoperable type and type parameters that has the TARGET attribute and is either interoperable, an allocated allocatable variable, or a scalar pointer with a target; or
  3. a nonpolymorpic scalar without nonkind parameters that has the TARGET attribute and is either an allocated allocatable variable, or a scalar pointer with a target.


C_ASSOCIATED (C_PTR1[, C_PTR2]) is an inquiry function with value false if C_PTR1 is a C null pointer or if C_PTR2 is present with a different value; otherwise, the value true.

C_F_POINTER (CPTR, FPTR [, SHAPE])) is a subroutine with arguments

CPTR is a scalar of type C_PTR with intent IN. Its value is the C address of an entity that is interoperable with variables of the type and type parameters of FPTR or was returned by a call of C_LOC for a variable of the type and type parameters of FPTR. It must not be the C address of a Fortran variable that does not have the TARGET attribute.
FPTR is a pointer that becomes pointer associated with the target of CPTR. If it is an array, its shape is specified by SHAPE.
SHAPE (optional) is a rank-one array of type integer with intent IN. If present, its size is equal to the rank of FPTR. If FPTR is an array, it must be present.


This is the mechanism for passing dynamic arrays between the languages.

A Fortran pointer target or assumed-shape array cannot be passed to C since its elements need not be contiguous in memory.

However, an allocated allocatable array may be passed to C and an array allocated in C may be associated with a Fortran pointer.

Case (c) of C_LOC allows the C program to receive a pointer to a Fortran scalar that is not interoperable. It is not intended that any use of it be made within C except to pass it back to Fortran where it will be dereferenced through C_F_POINTER and accessed.


Interoperability of procedures

For the sake of interoperability, a new attribute, VALUE, has been introduced for scalar dummy arguments. When the procedure is called, a copy of the actual argument is made. The dummy argument is a variable that may be altered during execution of the procedure, but on return no copy back takes place.

A Fortran procedure is interoperable if it has an explicit interface and is declared with the BIND attribute:

 FUNCTION FUNC(I, J, K, L, M), BIND(C)

All the dummy arguments must be interoperable.

For a function, the result must be scalar and interoperable.


The procedure has a 'binding label', which has global scope and is the name by which it is known to the C processor.

By default, it is the lower-case version of the Fortran name.

An alternative binding label may be specified:

  FUNCTION FUNC(I, J, K, L, M), &
           BIND(C, NAME='C_Func')

Such a procedure corresponds to a C function prototype with the same binding label. For a function, the result must be interoperable with the prototype result. For a subroutine, the prototype must have a void result.

A dummy argument with the VALUE attribute must correspond to a formal parameter of the prototype that is not of a pointer type. A dummy argument without the VALUE attribute must correspond to a formal parameter of the prototype that is of a pointer type.


Interoperability of global data

An interoperable module variable or a common block with interoperable members may be given the BIND attribute:

 USE ISO_C_BINDING
 INTEGER(C_INT), BIND(C) :: C_EXTERN
 INTEGER(C_LONG) :: C2
 BIND(C, NAME='myVariable') :: C2
 COMMON /COM/ R, S
 REAL(C_FLOAT) :: R, S
 BIND(C) :: /COM/

It has a binding label defined by the same rules as for procedures and interoperates with a C variable of a corresponding type.


Example of Fortran calling C

C Function Prototype:

int C_Library_Function(void* sendbuf, 
     int sendcount, int *recvcounts)

Fortran Module:

MODULE FTN_C
 INTERFACE
  FUNCTION C_LIBRARY_FUNCTION &
   (SENDBUF, SENDCOUNT, RECVCOUNTS), &
   BIND(C, NAME='C_Library_Function')
   USE ISO_C_BINDING
   INTEGER(C_INT) :: C_LIBRARY_FUNCTION 
   TYPE (C_PTR), VALUE :: SENDBUF
   INTEGER (C_INT), VALUE :: SENDCOUNT
   TYPE (C_PTR), VALUE :: RECVCOUNTS
  END FUNCTION C_LIBRARY_FUNCTION
 END INTERFACE
END MODULE FTN_C


Fortran Calling Sequence:

USE ISO_C_BINDING, ONLY: C_INT, &
                   C_FLOAT, C_LOC
USE FTN_C

REAL (C_FLOAT), TARGET :: SEND(100)
INTEGER (C_INT)        :: SENDCOUNT
INTEGER (C_INT), ALLOCATABLE, &
               TARGET :: RECVCOUNTS(:)
  ...
ALLOCATE( RECVCOUNTS(100) 
  ...
CALL C_LIBRARY_FUNCTION(C_LOC(SEND),  &
     SENDCOUNT, C_LOC(RECVCOUNTS))
 ...


Example of C calling Fortran

Fortran Code:

SUBROUTINE SIMULATION(ALPHA, BETA, &
         GAMMA, DELTA, ARRAYS), BIND(C)
 USE ISO_C_BINDING
 INTEGER (C_LONG), VALUE :: ALPHA
 REAL (C_DOUBLE), INTENT(INOUT) :: BETA
 INTEGER (C_LONG), INTENT(OUT) :: GAMMA
 REAL (C_DOUBLE),DIMENSION(*), &
                    INTENT(IN) :: DELTA
 TYPE, BIND(C) :: PASS
  INTEGER (C_INT) :: LENC, LENF
  TYPE (C_PTR)    :: C, F
 END TYPE PASS
 TYPE (PASS), INTENT(INOUT) :: ARRAYS
 ...
END SUBROUTINE SIMULATION


C Struct Declaration:

struct pass {int lenc, lenf; 
       float* f, *c}

C Function Prototype:

void simulation(long alpha, 
   double *beta, long *gamma, 
   double delta[], struct pass *arrays)

C Calling Sequence:

simulation(alpha, &beta, 
    &gamma, delta, &arrays);


Some code within subroutine SIMULATION

REAL (C_FLOAT), ALLOCATABLE, TARGET, &
      SAVE :: ETA(:)
REAL (C_FLOAT), POINTER :: C_ARRAY(:)
 ...
! Associate C_ARRAY with an array 
! allocated in C
CALL C_F_POINTER (ARRAYS%C, C_ARRAY, &
                 (/ARRAYS%LENC/) )
 ...
! Allocate an array and make it 
! available in C
ARRAYS%LENF = 100
ALLOCATE (ETA(ARRAYS%LENF))
ARRAYS%F = C_LOC(ETA)
 ...


Valid HTML 4.01! Comments on this or any other of the Group's pages should be sent by e-mail to the BCS FSG Web Editor, Peter Crouch, at pccrouch@bcs.org.uk



© Copyright The British Computer Society