Skip to content

Proposal for a common data model module to set default KINDS #13

Closed
@rweed

Description

@rweed

The following (sorry about the length) is a module that sets defaults for real and integer KIND parameters (what I call a data model) but allows users to define there own or change the defaults using preprocessor defines. I think something like this along with some module procedures for checking things like storage size and interrogating machine parameters ala R1MACH from Linpack etc. should be a basic part of the library. This would allow users to build different versions with different combinations of integer and real default types. I prefer this approach over trying to provide a different routine for each possible combination of integer and real types. Again, thats a personal preference but I prefer having 4 different versions of a library over trying to to provide four different versions of a subroutine/function and providing a generic interface. Also, I think part of the coding standard for the library should forbid real(8), real*8, implicit double precision etc.

*** dataModel.F90 ***

Module dataModel

! Define default data model precisions (kinds) for a project
! The default data model is assumed to be 32 bit integers and
! 64 bit reals

! Define intrinsic KIND parameters for Modern Fortran programs. 
! If we have a Fortran 2008 compliant version of ISO_FORTRAN_ENV, we will 
! use it; if not we will create our own versions of the equivalent Fortran 
! integer and real kinds using SELECT_INT_KIND and SELECT_REAL_KIND. We
! also define a "machine zero" function for both 32 and 64 bit Real values 

  Use ISO_FORTRAN_ENV

#ifdef HAVE_USER_DATA_MODEL
  USE USERDATAMODEL, ONLY: USER_DEFAULT_INT, USER_DEFAULT_REAL
#endif

  Implicit NONE 

#ifdef NO_F2008_ENV

! Define Integer and Real intrinsic KINDS with same names as in Fortran 2008
! ISO_FORTRAN_ENV
   
  Integer, Parameter :: INT8    = SELECTED_INT_KIND(2) 
  Integer, Parameter :: INT16   = SELECTED_INT_KIND(4) 
  Integer, Parameter :: INT32   = SELECTED_INT_KIND(9)
  Integer, Parameter :: INT64   = SELECTED_INT_KIND(18)
  Integer, Parameter :: REAL32  = SELECTED_REAL_KIND(P=6,  R=37)
  Integer, Parameter :: REAL64  = SELECTED_REAL_KIND(P=15, R=307)

#endif

#ifdef NO_REAL128
!  Integer, Parameter :: REAL128 = REAL64
#else
#ifdef NO_F2008_ENV
  Integer, Parameter :: REAL128 = SELECTED_REAL_KIND(p=33, R=4931)
#endif
#endif

#ifdef HAVE_USER_DATAMODEL

! Set DEFAULT_INT and DEFAULT_REAL to USER DATAMODEL
! values. Otherwise use native defaults

  Integer, Parameter :: DEFAULT_INT  = USER_DEFAULT_INT
  Integer, Parameter :: DEFAULT_REAL = USER_DEFAULT_REAL

#else 

! Set default values to 32 bit integers and 64 bit reals but allow
! users to change this at compile time by setting -DI8INT or -DR4REAL
! to select 64 bit integers and/or 32 bit reals

#ifdef I8INT 
  Integer, Parameter :: DEFAULT_INT  = INT64
#else
  Integer, Parameter :: DEFAULT_INT  = INT32
#endif

#ifdef R4REAL
  Integer, Parameter :: DEFAULT_REAL = REAL32
#else
#ifdef R16REAL
  Integer, Parameter :: DEFAULT_REAL = REAL128
#else
  Integer, Parameter :: DEFAULT_REAL = REAL64
#endif
#endif

#endif

! Define short(er) names and comman aliases for the default kind parameters

  Integer, Parameter :: WP   = DEFAULT_REAL 
  Integer, Parameter :: IWP  = DEFAULT_INT 
  Integer, Parameter :: QP   = REAL128

! Define a C_ENUM type for use with Fortran ENUMERATOR variables. This
! should be just C_INT but we define an explicit C_ENUM to handle
! the possiblility that its not. This should have been included in
! the Fortran 2003 C-Interop facility but for some reason known
! only to the standards folks was not. 

  Enum, BIND(C)
    ENUMERATOR :: dummy
  End Enum

  Private :: dummy

  Integer, Parameter :: C_ENUM=KIND(dummy)

  Public :: INT8, INT16, INT32, INT64, REAL32, REAL64, REAL128, C_ENUM, WP, &
            IWP, QP

End Module dataModel

Metadata

Metadata

Assignees

No one assigned

    Labels

    No labels
    No labels

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions