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 branches/UKMO/r5518_INGV1_WAVE-coupling/NEMOGCM/TOOLS/SIREN/src – NEMO

source: branches/UKMO/r5518_INGV1_WAVE-coupling/NEMOGCM/TOOLS/SIREN/src/global.f90 @ 7152

Last change on this file since 7152 was 7152, checked in by jcastill, 7 years ago

Initial implementation of wave coupling branch - INGV wave branch + UKMO wave coupling branch

File size: 5.5 KB
Line 
1!----------------------------------------------------------------------
2! NEMO system team, System and Interface for oceanic RElocable Nesting
3!----------------------------------------------------------------------
4!
5! MODULE: global
6!
7! DESCRIPTION:
8!> @brief This module defines global variables and parameters.
9!
10!> @author
11!> J.paul
12! REVISION HISTORY:
13!> @date November, 2013 - Initial Version
14!
15!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
16!----------------------------------------------------------------------
17MODULE global
18   USE kind                         ! F90 kind parameter
19   USE netcdf
20
21   IMPLICIT NONE
22
23   PUBLIC :: dp_fill         !< default fill value
24   PUBLIC :: ip_nsep         !< number of separator listed
25   PUBLIC :: ip_ncom         !< number of comment character listed
26   PUBLIC :: cp_sep          !< list of separator
27   PUBLIC :: cp_com          !< list of comment character
28
29   PUBLIC :: ip_npoint       !< number of point on ARAKAWA C-grid
30   PUBLIC :: jp_T            !< indice for T-point on ARAKAWA C-grid
31   PUBLIC :: jp_U            !< indice for U-point on ARAKAWA C-grid
32   PUBLIC :: jp_V            !< indice for V-point on ARAKAWA C-grid
33   PUBLIC :: jp_F            !< indice for F-point on ARAKAWA C-grid
34   PUBLIC :: cp_grid_point   !< list of grid_point character
35
36   PUBLIC :: ip_maxdim       !< maximum number of dimension to be used
37   PUBLIC :: jp_I            !< indice for I-direction
38   PUBLIC :: jp_J            !< indice for J-direction
39   PUBLIC :: jp_K            !< indice for K-direction
40   PUBLIC :: jp_L            !< indice for L-direction
41   PUBLIC :: cp_dimorder     !< dimension order
42
43   PUBLIC :: ip_maxvar       !< maximum number of variable
44   PUBLIC :: ip_maxmtx       !< matrix variable maximum dimension
45   PUBLIC :: ip_maxseg       !< maximum number of segment
46   PUBLIC :: ip_ghost        !< number of ghost cell
47
48   PUBLIC :: ip_ninterp      !< number of available interpolation method
49   PUBLIC :: cp_interp_list  !< list of interpolation name
50   
51   PUBLIC :: ip_nextrap      !< number of available extrapolation method
52   PUBLIC :: cp_extrap_list  !< list of extrapolation name
53   
54   PUBLIC :: ip_nfilter      !< number of available filter
55   PUBLIC :: cp_filter_list  !< list of filter name
56
57   PUBLIC :: ip_ncard        !< number of cardinal point
58   PUBLIC :: cp_card         !< array of cardinal point
59   PUBLIC :: jp_north        !< indice for north boundary
60   PUBLIC :: jp_south        !< indice for south boundary
61   PUBLIC :: jp_east         !< indice for east  boundary
62   PUBLIC :: jp_west         !< indice for west  boundary
63
64   ! NOTE_avoid_public_variables_if_possible
65
66   INTEGER(i4)                             , PARAMETER :: ip_maxvar =200   !< maximum number of variable
67   INTEGER(i4)                             , PARAMETER :: ip_maxmtx =100   !< matrix variable maximum dimension (cf create_bathy)
68   INTEGER(i4)                             , PARAMETER :: ip_maxseg =50    !< maximum number of segment for each boundary
69
70   INTEGER(i4)                             , PARAMETER :: ip_nsep=2        !< number of separator listed
71   CHARACTER(1)     , DIMENSION(ip_nsep)   , PARAMETER :: cp_sep = (/'.','_'/) !< list of separator
72
73   INTEGER(i4)                             , PARAMETER :: ip_ncom=2        !< number of comment character listed
74   CHARACTER(1)     , DIMENSION(ip_ncom)   , PARAMETER :: cp_com = (/'#','!'/) !< list of comment character
75   
76   INTEGER(i4)                             , PARAMETER :: ip_ghost=1       !< number of ghost cell
77
78   INTEGER(i4)                             , PARAMETER :: ip_ninterp=3
79   CHARACTER(LEN=lc), DIMENSION(ip_ninterp), PARAMETER :: cp_interp_list = &
80   &  (/ 'nearest', &
81   &     'cubic  ', &
82   &     'linear '  /)
83
84   INTEGER(i4)                             , PARAMETER :: ip_nextrap=2
85   CHARACTER(LEN=lc), DIMENSION(ip_nextrap), PARAMETER :: cp_extrap_list = &
86   &  (/ 'dist_weight', &
87   &     'min_error  ' /)
88
89   INTEGER(i4)                             , PARAMETER :: ip_nfilter=5
90   CHARACTER(LEN=lc), DIMENSION(ip_nfilter), PARAMETER :: cp_filter_list = &
91   &  (/ 'butterworth', &
92   &     'blackman   ', &
93   &     'hamming    ', &
94   &     'hann       ', &
95   &     'gauss      '/)
96
97   REAL(dp)                                , PARAMETER :: dp_fill=NF90_FILL_DOUBLE !< default fill value
98
99   INTEGER(i4)                             , PARAMETER :: ip_npoint=4
100   INTEGER(i4)                             , PARAMETER :: jp_T=1
101   INTEGER(i4)                             , PARAMETER :: jp_U=2
102   INTEGER(i4)                             , PARAMETER :: jp_V=3
103   INTEGER(i4)                             , PARAMETER :: jp_F=4
104   CHARACTER(LEN=1), DIMENSION(ip_npoint)  , PARAMETER :: cp_grid_point = &
105   &  (/ 'T', 'U', 'V', 'F' /)
106
107
108   INTEGER(i4)                             , PARAMETER :: ip_maxdim=4
109   INTEGER(i4)                             , PARAMETER :: jp_I=1
110   INTEGER(i4)                             , PARAMETER :: jp_J=2
111   INTEGER(i4)                             , PARAMETER :: jp_K=3
112   INTEGER(i4)                             , PARAMETER :: jp_L=4
113   CHARACTER(LEN=ip_maxdim)                , PARAMETER :: cp_dimorder = 'xyzt' !< dimension order to output
114
115   INTEGER(i4), PARAMETER :: ip_ncard=4
116   CHARACTER(LEN=lc), DIMENSION(ip_ncard), PARAMETER :: cp_card = &
117   &  (/ 'north', &
118   &     'south', &
119   &     'east ', &
120   &     'west ' /)
121
122   INTEGER(i4), PARAMETER :: jp_north=1
123   INTEGER(i4), PARAMETER :: jp_south=2
124   INTEGER(i4), PARAMETER :: jp_east =3
125   INTEGER(i4), PARAMETER :: jp_west =4
126
127
128
129END MODULE global
130
Note: See TracBrowser for help on using the repository browser.