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 branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/TOOLS/SIREN/src – NEMO

source: branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/TOOLS/SIREN/src/kind.f90 @ 5214

Last change on this file since 5214 was 5214, checked in by davestorkey, 9 years ago

Merge in changes from the trunk up to rev 5107.

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