constants.fpp Source File


Contents

Source Code


Source Code

# include "define.inc"

!> A module which defines a variety of constants, for example, 
!! mathematical constants like pi, dimensions of arrays whose sizes are
!! set at compile time, and kind parameters. 
!!
!! This module must not be compiled with a padding option
!! such as -qautodbl=dbl of xlf which makes type conversion
!! of variables even with explicit kind statements.
module constants
  use, intrinsic :: iso_fortran_env, only: int8, int16, int32, int64, real32, real64, real128
  use, intrinsic :: iso_c_binding, only: c_sizeof
  implicit none

  private

  public :: size_of

  public :: kind_is, kind_id, kind_rs, kind_rd, kind_rq
  
  public :: dp, sp, spc, dpc, ii

  public :: zi, pi, twopi, sqrt_pi, sqrt_twopi
  public :: dzi, dpi, dtwopi, dsqrt_pi, dsqrt_twopi

# ifdef NAG_PREC
  public :: nag_kind
# endif

  public :: run_name_size


  !> Defines the length of character string used to store all
  !! file names that are based on the run_name prefix. 
#ifdef RUN_NAME_SIZE
  integer, parameter :: run_name_size = RUN_NAME_SIZE
#else
  integer, parameter :: run_name_size = 2000
#endif

  !> Symbolic names for kind type of single and double-precision reals:
  !! (with at least 6 and 12 digits of accuracy)
  integer, parameter :: kind_i1 = int8
  integer, parameter :: kind_ih = int16
  integer, parameter :: kind_is = int32
  integer, parameter :: kind_id = int64
  integer, parameter :: kind_rs = real32
  integer, parameter :: kind_rd = real64
  integer, parameter :: kind_rq = real128

  ! <EGH

  !> Single precision real kind. Needed for gryffin99, a fork of the Hammett, Beer & Dorland code
  !! from 1999
  integer, parameter :: sp = real32
  !> Double precision real kind. Needed for gryffin99, a fork of the Hammett, Beer & Dorland code
  !! from 1999
  integer, parameter :: dp = real64
  !> Single precision complex kind. Needed for gryffin99, a fork of the Hammett, Beer & Dorland code
  !! from 1999
  integer, parameter :: spc = kind((1.0_sp,1.0_sp))
  !> Double precision complex kind. Needed for gryffin99, a fork of the Hammett, Beer & Dorland code
  !! from 1999
  integer, parameter :: dpc = kind((1.0_dp,1.0_dp))
  !> Square root of -1. Needed for gryffin99, a fork of the Hammett, Beer & Dorland code
  !! from 1999
  complex(dp), parameter :: ii = (0._dp, 1._dp)
  ! EGH>

# if NAG_PREC == _NAGDBLE_
  integer, parameter :: nag_kind=kind_rd
# elif NAG_PREC == _NAGSNGL_
  integer, parameter :: nag_kind=kind_rs
# endif


  !> Square root of -1.
  complex, parameter :: zi = ( 0.0 , 1.0 )
  complex (kind=kind(1.d0)), parameter :: dzi = ( 0.d0 , 1.d0 )

  !> Pi to quad precision, (double if DBLE is unset)
  double precision, parameter :: dpi = &
       3.14159265358979323846264338327950288419716939938
  !> 2*Pi to quad precision, (double if DBLE is unset)
  double precision, parameter :: dtwopi=2.*dpi
  !> Sqrt(pi) in double or quad precision depending on DBLE
  double precision, parameter :: dsqrt_pi = sqrt(dpi)
  !> Sqrt(2 * pi) in double or quad precision depending on DBLE
  double precision, parameter :: dsqrt_twopi = sqrt(dtwopi)
  !> Pi to double precision, (single if DBLE is unset)
  real, parameter :: pi = dpi
  !> 2*Pi to double precision, (single if DBLE is unset)
  real, parameter :: twopi= dtwopi
  !> Sqrt(pi) in single or double precision depending on DBLE
  real, parameter :: sqrt_pi = dsqrt_pi
  !> Sqrt(2 * pi) in single or double precision depending on DBLE
  real, parameter :: sqrt_twopi = dsqrt_twopi

! Note: we will use dp="double precision" for almost everything.
!
! The fortran-90 "kind" types is kind of awkward.  But the old trick of
! using a "-r8" compiler switch to promote all real variables to 64 bits 
! doesn't work on some fortran 90 compilers, and so the above use of 
! the standard fortran-90 routine selected_real_kind is more portable.
!
! It may not be a good idea to mimic "-r8" by making sp to be identical
! to dp, or to write single and double-precision versions of 
! generic subroutines, since on the Cray computers both single and
! "double" precision are 64 bits, and the compiler will complain that
! it can't distinguish the two specific subroutines.  In some cases,
! the cray compiler may be able to distinguish between two real "kinds"
! for the purposes of distinguishing overloaded procedure names,
! even though the two real kinds map to the same precision (64 bits).
!
! If this ever does become a problem, then you may be able to get around it by
! commenting out the double precision function names from the list of 
! overloaded procedures (i.e., the "module procedure" statements).
!

  !> Returns the number of bytes of storage required by its
  !> argument. Equivalent to `c_sizeof` from `iso_c_binding`
  interface size_of
     module procedure size_of_i1, size_of_ih, size_of_is, size_of_id
     module procedure size_of_rs, size_of_rd
     module procedure size_of_cs, size_of_cd
     module procedure size_of_rq, size_of_cq
  end interface

contains
  elemental integer function size_of_i1 (arg)
    integer (kind_i1), intent(in) :: arg
    size_of_i1 = c_sizeof(arg)
  end function size_of_i1

  elemental integer function size_of_ih (arg)
    integer (kind_ih), intent(in) :: arg
    size_of_ih = c_sizeof(arg)
  end function size_of_ih

  elemental integer function size_of_is (arg)
    integer (kind_is), intent(in) :: arg
    size_of_is = c_sizeof(arg)
  end function size_of_is

  elemental integer function size_of_id (arg)
    integer (kind_id), intent(in) :: arg
    size_of_id = c_sizeof(arg)
  end function size_of_id

  elemental integer function size_of_rs (arg)
    real (kind_rs), intent(in) :: arg
    size_of_rs = c_sizeof(arg)
  end function size_of_rs

  elemental integer function size_of_rd (arg)
    real (kind_rd), intent(in) :: arg
    size_of_rd = c_sizeof(arg)
  end function size_of_rd

  elemental integer function size_of_rq (arg)
    real (kind_rq), intent(in) :: arg
    size_of_rq = c_sizeof(arg)
  end function size_of_rq

  elemental integer function size_of_cs (arg)
    complex (kind_rs), intent(in) :: arg
    size_of_cs = c_sizeof(arg)
  end function size_of_cs

  elemental integer function size_of_cd (arg)
    complex (kind_rd), intent(in) :: arg
    size_of_cd = c_sizeof(arg)
  end function size_of_cd

  elemental integer function size_of_cq (arg)
    complex (kind_rq), intent(in) :: arg
    size_of_cq = c_sizeof(arg)
  end function size_of_cq

end module constants