FV3 Bundle
Type_Kinds.f90
Go to the documentation of this file.
1 !
2 ! Type_Kinds
3 !
4 ! Module to hold specification kinds for variable declaration, as well as
5 ! associated descriptors.
6 !
7 ! CREATION HISTORY:
8 ! Written by: Paul van Delst, 12-Jun-2000
9 ! paul.vandelst@noaa.gov
10 !
11 
12 MODULE type_kinds
13 
14  ! ---------------------------
15  ! Disable all implicit typing
16  ! ---------------------------
17  IMPLICIT NONE
18 
19 
20  ! ------------
21  ! Visibilities
22  ! ------------
23  ! Everything is private by default
24  PRIVATE
25  ! The integer types
26  PUBLIC :: byte , n_bytes_byte
27  PUBLIC :: short , n_bytes_short
28  PUBLIC :: long , n_bytes_long
29  PUBLIC :: llong , n_bytes_llong
30  PUBLIC :: ip_kind, n_bytes_ip_kind ! Default integer set by IIP
31  PUBLIC :: ip , n_bytes_ip ! Aliases for IP_Kind
32  ! The floating point types
33  PUBLIC :: single , n_bytes_single
34  PUBLIC :: double , n_bytes_double
35  PUBLIC :: quad , n_bytes_quad
36  PUBLIC :: fp_kind, n_bytes_fp_kind ! Default integer set by IFP
37  PUBLIC :: fp , n_bytes_fp ! Aliases for FP_Kind
38 
39 
40  ! -------------------------------------------------------------------
41  ! THE DEFAULT INTEGER INDEX. Change the value of IIP for the required
42  ! integer kind. The following chart details the correspondence:
43  !
44  ! IIP INTEGER(IP)
45  ! ==============================
46  ! 1 Byte
47  ! 2 Short (2 bytes)
48  ! 3 Long (4 bytes)
49  ! 4 LLong (8 bytes) **IF AVAILABLE, Long OTHERWISE**
50  !
51  ! -------------------------------------------------------------------
52  INTEGER, PARAMETER :: iip = 3 ! 1=Byte, 2=Short, 3=Long, 4=LLong
53 
54 
55  ! -------------------------------------------------------------------
56  ! THE DEFAULT FLOATING POINT INDEX. Change the value of IFP for the
57  ! required floating point kind. The following chart details the
58  ! correspondence:
59  !
60  ! IFP REAL(FP)
61  ! ==============================
62  ! 1 Single (4 bytes)
63  ! 2 Double (8 bytes)
64  ! 3 Quad (16 bytes) **IF AVAILABLE, Double OTHERWISE**
65  !
66  ! -------------------------------------------------------------------
67  INTEGER, PARAMETER :: ifp = 2 ! 1=Single, 2=Double, 3=Quad
68 
69 
70  ! -------------------
71  ! Integer definitions
72  ! -------------------
73  ! Integer types
74  INTEGER, PARAMETER :: byte = selected_int_kind(1) ! Byte integer
75  INTEGER, PARAMETER :: short = selected_int_kind(4) ! Short integer
76  INTEGER, PARAMETER :: long = selected_int_kind(8) ! Long integer
77  INTEGER, PARAMETER :: llong = selected_int_kind(16) ! LLong integer
78 
79  ! Expected 8-bit byte sizes of the integer kinds
80  INTEGER, PARAMETER :: n_bytes_byte = 1
81  INTEGER, PARAMETER :: n_bytes_short = 2
82  INTEGER, PARAMETER :: n_bytes_long = 4
83  INTEGER, PARAMETER :: n_bytes_llong = 8
84  ! Define arrays for default definition
85  INTEGER, PARAMETER :: n_ip = 4
86  INTEGER, PARAMETER, DIMENSION(N_IP) :: ip_kind_types = (/ byte, &
87  short, &
88  long, &
89  llong /)
90  INTEGER, PARAMETER, DIMENSION(N_IP) :: ip_byte_sizes = (/ n_bytes_byte, &
91  n_bytes_short, &
92  n_bytes_long, &
93  n_bytes_llong /)
94  ! Default values
95  INTEGER, PARAMETER :: ip_kind =ip_kind_types(iip)
96  INTEGER, PARAMETER :: n_bytes_ip_kind=ip_byte_sizes(iip)
97  INTEGER, PARAMETER :: ip =ip_kind
98  INTEGER, PARAMETER :: n_bytes_ip=n_bytes_ip_kind
99 
100 
101  ! --------------------------
102  ! Floating point definitions
103  ! --------------------------
104  ! Floating point types
105  INTEGER, PARAMETER :: single = selected_real_kind(6) ! Single precision
106  INTEGER, PARAMETER :: double = selected_real_kind(15) ! Double precision
107  INTEGER, PARAMETER :: quad = selected_real_kind(20) ! Quad precision
108 
109  ! Expected 8-bit byte sizes of the floating point kinds
110  INTEGER, PARAMETER :: n_bytes_single = 4
111  INTEGER, PARAMETER :: n_bytes_double = 8
112  INTEGER, PARAMETER :: n_bytes_quad = 16
113  ! Define arrays for default definition
114  INTEGER, PARAMETER :: n_fp = 3
115  INTEGER, PARAMETER, DIMENSION(N_FP) :: fp_kind_types = (/ single, &
116  double, &
117  quad /)
118  INTEGER, PARAMETER, DIMENSION(N_FP) :: fp_byte_sizes = (/ n_bytes_single, &
119  n_bytes_double, &
120  n_bytes_quad /)
121  ! Default values
122  INTEGER, PARAMETER :: fp_kind = fp_kind_types(ifp)
123  INTEGER, PARAMETER :: n_bytes_fp_kind = fp_byte_sizes(ifp)
124  INTEGER, PARAMETER :: fp =fp_kind
125  INTEGER, PARAMETER :: n_bytes_fp=n_bytes_fp_kind
126 
127 END MODULE type_kinds
integer, parameter, public ip_kind
Definition: Type_Kinds.f90:95
integer, parameter, public llong
Definition: Type_Kinds.f90:77
integer, parameter, public n_bytes_single
Definition: Type_Kinds.f90:110
integer, parameter, public long
Definition: Type_Kinds.f90:76
integer, parameter, public fp
Definition: Type_Kinds.f90:124
integer, parameter, public ip
Definition: Type_Kinds.f90:97
integer, parameter, public n_bytes_ip_kind
Definition: Type_Kinds.f90:96
integer, parameter, public byte
Definition: Type_Kinds.f90:74
integer, parameter, public n_bytes_long
Definition: Type_Kinds.f90:82
integer, parameter, public double
Definition: Type_Kinds.f90:106
integer, parameter, public single
Definition: Type_Kinds.f90:105
integer, parameter, public short
Definition: Type_Kinds.f90:75
integer, dimension(n_ip), parameter ip_byte_sizes
Definition: Type_Kinds.f90:90
integer, parameter, public quad
Definition: Type_Kinds.f90:107
integer, parameter, public n_bytes_quad
Definition: Type_Kinds.f90:112
integer, dimension(n_fp), parameter fp_kind_types
Definition: Type_Kinds.f90:115
integer, parameter, public n_bytes_fp_kind
Definition: Type_Kinds.f90:123
integer, parameter, public n_bytes_double
Definition: Type_Kinds.f90:111
integer, parameter ifp
Definition: Type_Kinds.f90:67
integer, parameter, public n_bytes_llong
Definition: Type_Kinds.f90:83
integer, parameter, public n_bytes_byte
Definition: Type_Kinds.f90:80
integer, parameter iip
Definition: Type_Kinds.f90:52
integer, parameter n_ip
Definition: Type_Kinds.f90:85
integer, parameter, public n_bytes_short
Definition: Type_Kinds.f90:81
integer, dimension(n_ip), parameter ip_kind_types
Definition: Type_Kinds.f90:86
integer, parameter n_fp
Definition: Type_Kinds.f90:114
integer, parameter, public n_bytes_ip
Definition: Type_Kinds.f90:98
integer, parameter, public n_bytes_fp
Definition: Type_Kinds.f90:125
integer, parameter, public fp_kind
Definition: Type_Kinds.f90:122
integer, dimension(n_fp), parameter fp_byte_sizes
Definition: Type_Kinds.f90:118