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.
global.f90 in utils/tools/SIREN/src – NEMO

source: utils/tools/SIREN/src/global.f90 @ 13369

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

update: cf changelog inside documentation

  • Property dummy set to 1
  • Property svn:keywords set to URL Date Author Revision
File size: 7.2 KB
Line 
1!----------------------------------------------------------------------
2! NEMO system team, System and Interface for oceanic RElocable Nesting
3!----------------------------------------------------------------------
4!
5! DESCRIPTION:
6!> @brief This module defines global variables and parameters.
7!>
8!> @author
9!> J.paul
10!>
11!> @date November, 2013 - Initial Version
12!> @date September, 2015
13!> - define fill value for each variable type
14!> @date January, 2019
15!> - define svn URL variable
16!> @date October, 2019
17!> - define svn Revision, Date, and Author variable
18!>
19!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
20!----------------------------------------------------------------------
21MODULE global
22
23   USE kind                         ! F90 kind parameter
24   USE netcdf
25
26   IMPLICIT NONE
27
28   PUBLIC :: dp_fill         !< default fill value
29   PUBLIC :: ip_nsep         !< number of separator listed
30   PUBLIC :: ip_ncom         !< number of comment character listed
31   PUBLIC :: cp_sep          !< list of separator
32   PUBLIC :: cp_com          !< list of comment character
33
34   PUBLIC :: ip_npoint       !< number of point on ARAKAWA C-grid
35   PUBLIC :: jp_T            !< indice for T-point on ARAKAWA C-grid
36   PUBLIC :: jp_U            !< indice for U-point on ARAKAWA C-grid
37   PUBLIC :: jp_V            !< indice for V-point on ARAKAWA C-grid
38   PUBLIC :: jp_F            !< indice for F-point on ARAKAWA C-grid
39   PUBLIC :: cp_grid_point   !< list of grid_point character
40
41   PUBLIC :: ip_maxdim       !< maximum number of dimension to be used
42   PUBLIC :: jp_I            !< indice for I-direction
43   PUBLIC :: jp_J            !< indice for J-direction
44   PUBLIC :: jp_K            !< indice for K-direction
45   PUBLIC :: jp_L            !< indice for L-direction
46   PUBLIC :: cp_dimorder     !< dimension order
47
48   PUBLIC :: ip_maxvar       !< maximum number of variable
49   PUBLIC :: ip_maxmtx       !< matrix variable maximum dimension
50   PUBLIC :: ip_maxseg       !< maximum number of segment
51   PUBLIC :: ip_ghost        !< number of ghost cell
52
53   PUBLIC :: ip_ninterp      !< number of available interpolation method
54   PUBLIC :: cp_interp_list  !< list of interpolation name
55
56   PUBLIC :: ip_nextrap      !< number of available extrapolation method
57   PUBLIC :: cp_extrap_list  !< list of extrapolation name
58
59   PUBLIC :: ip_nfilter      !< number of available filter
60   PUBLIC :: cp_filter_list  !< list of filter name
61
62   PUBLIC :: ip_ncard        !< number of cardinal point
63   PUBLIC :: cp_card         !< array of cardinal point
64   PUBLIC :: jp_north        !< indice for north boundary
65   PUBLIC :: jp_south        !< indice for south boundary
66   PUBLIC :: jp_east         !< indice for east  boundary
67   PUBLIC :: jp_west         !< indice for west  boundary
68
69   PUBLIC :: ip_maxdimcfg    !< maximum dimension in configuration file
70   PUBLIC :: ip_maxdumcfg    !< maximum dummy variable in configuration file
71   PUBLIC :: cp_url          !< svn url
72
73   PUBLIC :: ip_kddim        !< kd-tree dimension number
74
75   ! NOTE_avoid_public_variables_if_possible
76
77   INTEGER(i4)                             , PARAMETER :: ip_maxvar =200   !< maximum number of variable
78   INTEGER(i4)                             , PARAMETER :: ip_maxmtx =50    !< matrix variable maximum dimension (cf create_bathy)
79   INTEGER(i4)                             , PARAMETER :: ip_maxseg =10    !< maximum number of segment for each boundary
80
81   INTEGER(i4)                             , PARAMETER :: ip_nsep=2        !< number of separator listed
82   CHARACTER(1)     , DIMENSION(ip_nsep)   , PARAMETER :: cp_sep = (/'.','_'/) !< list of separator
83
84   INTEGER(i4)                             , PARAMETER :: ip_ncom=2        !< number of comment character listed
85   CHARACTER(1)     , DIMENSION(ip_ncom)   , PARAMETER :: cp_com = (/'#','!'/) !< list of comment character
86
87   INTEGER(i4)                             , PARAMETER :: ip_ghost=1       !< number of ghost cell
88
89   INTEGER(i4)                             , PARAMETER :: ip_ninterp=3
90   CHARACTER(LEN=lc), DIMENSION(ip_ninterp), PARAMETER :: cp_interp_list = &
91   &  (/ 'nearest', &
92   &     'cubic  ', &
93   &     'linear '  /)
94
95   INTEGER(i4)                             , PARAMETER :: ip_nextrap=2
96   CHARACTER(LEN=lc), DIMENSION(ip_nextrap), PARAMETER :: cp_extrap_list = &
97   &  (/ 'dist_weight', &
98   &     'min_error  ' /)
99
100   INTEGER(i4)                             , PARAMETER :: ip_nfilter=5
101   CHARACTER(LEN=lc), DIMENSION(ip_nfilter), PARAMETER :: cp_filter_list = &
102   &  (/ 'butterworth', &
103   &     'blackman   ', &
104   &     'hamming    ', &
105   &     'hann       ', &
106   &     'gauss      '/)
107
108   REAL(dp)                                , PARAMETER :: dp_fill_i1=NF90_FILL_BYTE   !< byte fill value
109   REAL(dp)                                , PARAMETER :: dp_fill_i2=NF90_FILL_SHORT  !< short fill value
110   REAL(dp)                                , PARAMETER :: dp_fill_i4=NF90_FILL_INT    !< INT fill value
111   REAL(dp)                                , PARAMETER :: dp_fill_sp=NF90_FILL_FLOAT  !< real fill value
112   REAL(dp)                                , PARAMETER :: dp_fill=NF90_FILL_DOUBLE    !< double fill value
113
114   INTEGER(i4)                             , PARAMETER :: ip_npoint=4
115   INTEGER(i4)                             , PARAMETER :: jp_T=1
116   INTEGER(i4)                             , PARAMETER :: jp_U=2
117   INTEGER(i4)                             , PARAMETER :: jp_V=3
118   INTEGER(i4)                             , PARAMETER :: jp_F=4
119   CHARACTER(LEN=1), DIMENSION(ip_npoint)  , PARAMETER :: cp_grid_point = &
120   &  (/ 'T', 'U', 'V', 'F' /)
121
122
123   INTEGER(i4)                             , PARAMETER :: ip_maxdimcfg=10 !< maximum dimension in configuration file
124   INTEGER(i4)                             , PARAMETER :: ip_maxdim=4
125   INTEGER(i4)                             , PARAMETER :: jp_I=1
126   INTEGER(i4)                             , PARAMETER :: jp_J=2
127   INTEGER(i4)                             , PARAMETER :: jp_K=3
128   INTEGER(i4)                             , PARAMETER :: jp_L=4
129   CHARACTER(LEN=ip_maxdim)                , PARAMETER :: cp_dimorder = 'xyzt' !< dimension order to output
130
131   INTEGER(i4)                             , PARAMETER :: ip_ncard=4
132   CHARACTER(LEN=lc), DIMENSION(ip_ncard)  , PARAMETER :: cp_card = &
133   &  (/ 'north', &
134   &     'south', &
135   &     'east ', &
136   &     'west ' /)
137
138   INTEGER(i4)                             , PARAMETER :: jp_north=1
139   INTEGER(i4)                             , PARAMETER :: jp_south=2
140   INTEGER(i4)                             , PARAMETER :: jp_east =3
141   INTEGER(i4)                             , PARAMETER :: jp_west =4
142
143   INTEGER(i4)                             , PARAMETER :: ip_maxdumcfg = 10 !< maximum dummy variable, dimension, or attribute
144                                                                            !< in configuration file
145
146   INTEGER(i4)                             , PARAMETER :: ip_kddim = 3 !<  kd-tree dimensions (x/y/z)
147
148   CHARACTER(LEN=lc)                       , PARAMETER :: cp_url="$URL$"    !< svn url
149   CHARACTER(LEN=lc)                       , PARAMETER :: cp_version = "$Revision$"
150   CHARACTER(LEN=lc)                       , PARAMETER :: cp_author = "$Author$"
151   CHARACTER(LEN=lc)                       , PARAMETER :: cp_date = "$Date$"
152
153END MODULE global
154
Note: See TracBrowser for help on using the repository browser.