New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
kind.f90 in utils/tools/SIREN/src – NEMO

source: utils/tools/SIREN/src/kind.f90 @ 12080

Last change on this file since 12080 was 12080, checked in by jpaul, 4 years ago

update nemo trunk

File size: 2.1 KB
RevLine 
[4213]1!----------------------------------------------------------------------
2! NEMO system team, System and Interface for oceanic RElocable Nesting
3!----------------------------------------------------------------------
4!
5! DESCRIPTION:
6!> This module defines the F90 kind parameter for common data types.
7!>
[12080]8!>
[4213]9!> @author
10!> G. Madec
11! REVISION HISTORY:
12!> @date June, 2006 - Initial Version
13!> @date December, 2012 - G. Madec
14!>  - add a standard length of character strings
[12080]15!>
[4213]16!> @todo
17!> - check i8 max value
[12080]18!>
19!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[4213]20!----------------------------------------------------------------------
21MODULE kind
[12080]22
[4213]23   IMPLICIT NONE
24   ! NOTE_avoid_public_variables_if_possible
25
26   !                                                                !!** Floating point **
27   ! SELECTED_REAL_KIND(P,R) returns the kind value of a real data type
28   ! with decimal precision of at least P digits, exponent range of at least R
29   INTEGER, PUBLIC, PARAMETER ::   sp = SELECTED_REAL_KIND( 6, 37)   !< single precision (real 4)
30   INTEGER, PUBLIC, PARAMETER ::   dp = SELECTED_REAL_KIND(12,307)   !< double precision (real 8)
31   INTEGER, PUBLIC, PARAMETER ::   wp = dp                           !< working precision
32
33   !                                                                !!** Integer **
34   ! SELECTED_INT_KIND(R) return the kind value of the smallest integer type
35   ! that can represent all values ranging ] -10^R , 10^R [
36   INTEGER, PUBLIC, PARAMETER ::   i1 = SELECTED_INT_KIND( 1)        !< single precision (integer 1)
37   INTEGER, PUBLIC, PARAMETER ::   i2 = SELECTED_INT_KIND( 4)        !< single precision (integer 2)
38   INTEGER, PUBLIC, PARAMETER ::   i4 = SELECTED_INT_KIND( 9)        !< single precision (integer 4)
39   INTEGER, PUBLIC, PARAMETER ::   i8 = SELECTED_INT_KIND(14)        !< double precision (integer 8)
40   
41   !                                                                !!** Integer **
42   INTEGER, PUBLIC, PARAMETER ::   lc = 256                          !< Length of Character strings
43
44END MODULE kind
45
Note: See TracBrowser for help on using the repository browser.