source: TOOLS/MOZAIC/src/MOZAIC/dimension.f90 @ 3918

Last change on this file since 3918 was 3918, checked in by omamce, 6 years ago

O.M. : change espfrac from fortran parameter to parameter read in run.def

File size: 7.1 KB
Line 
1! -*- Mode: f90 -*-
2!> Module dimensions
3!!   
4MODULE dimensions
5   !!
6   USE declare
7   IMPLICIT NONE
8   SAVE
9   PUBLIC
10   !!
11   CHARACTER (len=10) :: c_period = 'none' ! or lgm, mpwp, etc ...
12   !!
13   INTEGER (kind=il)   :: jpoi  !< Dimensions ocean X
14   INTEGER (kind=il)   :: jpoj  !< Dimensions ocean Y
15   CHARACTER (len = 3) :: comod  !< Ocean model name
16   CHARACTER (len = 10) :: cotyp  !< Ocean model type
17   INTEGER (kind=il)   :: jpon   !< Global (1D) dimensions
18   !!
19   REAL (kind=rl) :: epsfrac = 1.0E-10_rl  !< Min fraction of sea acceptable. To check : should be compatible with EPSFRA in LMDZ ?
20   !
21   INTEGER (kind=il) :: jpoe !< Number (maxi) of edges to describe ocean box
22   !!
23   INTEGER (kind=il) :: noperio !< Periodicity of ocean grid
24   LOGICAL :: lmasko=.FALSE.  !< If TRUE, masked points of oceanic     grid (land) are considered for computing.
25   LOGICAL :: l_recalc_o = .TRUE. !< Recalcule des surfaces ocean
26   CHARACTER (len=280) :: c_oce_msk_file = 'NONE'
27   !!
28   INTEGER (kind=il) :: jpai, jpait, jpaiu, jpaiv !< Dimensions atmosphere X
29   INTEGER (kind=il) :: jpaj, jpajt, jpaju, jpajv !< Dimensions atmosphere Y
30
31   CHARACTER (LEN=80)  :: c_suffix  = 'none' ! Add a suffix to all file names
32   CHARACTER (LEN=240) :: c_comment = 'none' ! Add a comment in all NetCDF Files
33   
34   CHARACTER (len = 3) :: camod    !< Atm model name
35   CHARACTER (len = 10) :: catyp   !< Atm model type
36   !!
37   INTEGER (kind=il) :: naperio !< Periodicite de la grille atmosphere
38   LOGICAL :: lmaska=.TRUE.     !< If TRUE, masked points of atmospheric grid (land) are considered for computing.
39   LOGICAL :: la_nortop         !< If TRUE, latitude indreases with index in output files
40   LOGICAL :: l_recalc_a = .TRUE. !< Recalcule des surfaces atmospheres
41   LOGICAL :: la_pole !< IF TRUE, special handing of atmospheric pole points
42   !!
43   INTEGER (kind=il) :: jpae !< Number (maxi) of edges to describe atm box
44   !!
45   INTEGER (kind=il) :: jpan  !< Dimension of 1D atm array, T grid
46   INTEGER (kind=il) :: jpanu !< Dimension of 1D atm array, U grid
47   INTEGER (kind=il) :: jpanv !< Dimension of 1D atm array, V grid
48   !!
49   LOGICAL :: lwra2o=.TRUE. !< TRUE if atm -> oce weights/adresses are computed
50   LOGICAL :: lwro2a=.TRUE. !< TRUE if oce -> atm weights/adresses are computed
51   INTEGER (kind=il) :: norma2o=1 !< Type of normalization atm-> oce: 0: none, 1: intensive, 2: extensive
52   INTEGER (kind=il) :: normo2a=1 !< Type of normalization oce -> atm: 0: none, 1: intensive, 2: extensive
53   !!
54   INTEGER (kind=il) :: jpa2o !< Dimensions for computing weights, atm -> oce
55   INTEGER (kind=il) :: jpo2a !< Dimensions for computing weights, oce -> atm
56   !!
57   LOGICAL :: limit_stack !< If true, limit stack size in NetCDF calls, by slicing output operation
58   LOGICAL :: l_grid_cdf  !< If TRUE, read grid specification in NetCDF format
59   !! LOGICAL :: l_wei_cdf   !< if TRUE, read weights and adresses in NetCDF (Oasis 3 format)
60   LOGICAL :: l_wei_i4    !< if TRUE, write adresses in INTEGER*4
61   LOGICAL :: l_wei_i8    !< if TRUE, write adresses in INTEGER*8
62   LOGICAL :: l_wei_oasis_3   !< if TRUE, write Oasis 3 weight file
63   LOGICAL :: l_wei_oasis_mct !< if TRUE, write Oasis MCT weight file
64   LOGICAL :: l_limit_iosize !< If TRUE, don't do full diagnostics in cotes.f90
65   CHARACTER (LEN=10) :: c_read_wei = 'oasis_3'
66   CHARACTER (len=64) :: c_FlioMode   !< Flio file format
67   CHARACTER (len=3) :: c_oasis !< Oasis version
68   integer (kind=il) :: slice_size !< Slice size for writing NetCDF files
69   !!
70   LOGICAL :: locerev !< Strategie de nommage des champs ocean
71   LOGICAL :: latmrev !< Strategie de nommage des champs atmosphere
72   !!
73   INTEGER (kind=il)            :: jmo2a    !< Maximum number of found neighbors, ocean -> atmosphere
74   INTEGER (kind=il)            :: jma2o    !< Maximum number of found neighbors, atmosphere -> ocean
75   INTEGER (kind=il)            :: jma2or   !< Maximum number of found neighbors : run-off
76   INTEGER (kind=il)            :: jma2oi   !< Maximum number of found neighbors : icestream
77   !!
78   REAL (kind=rl) :: xa_inf !< Minimum value of atm longitudes
79   REAL (kind=rl) :: xa_sup !< Maximum value of atm longitudes
80   REAL (kind=rl) :: ya_inf !< Minimum value of atm latitudes
81   REAL (kind=rl) :: ya_sup !< Maximum value of atm latitudes
82   REAL (kind=rl) :: xo_inf !< Minimum value of oce longitudes
83   REAL (kind=rl) :: xo_sup !< Maximum value of oce longitudes
84   REAL (kind=rl) :: yo_inf !< Minimum value of oce latitudes
85   REAL (kind=rl) :: yo_sup !< Maximum value of oce latitudes
86   !!
87   !
88   LOGICAL :: l_fast !< Quick and dirty version, for test only
89   !!
90   LOGICAL :: l_dryrun              !< Flag for fast and dirty search
91   LOGICAL :: l_ipsldbg             !< Flag for debugging IOIPSL operations
92   INTEGER (kind=il) :: lev_dry     !< For dry run : use to test I/O
93   INTEGER (kind=il) :: ndebug=2    !< Levels of printing
94   CHARACTER (len=20) :: o2a_orien="nord_en_haut"  !< Orientation for o2a diag file
95   !!
96   !! Basins
97   CHARACTER (len=40) :: cl_atl, cl_pac, cl_noclo, cl_nomed, c_basins
98   !!
99   !! Poids run-off
100   !!
101   LOGICAL :: lriv     !< Traitement du runoff des rivières
102   LOGICAL :: lcoast   !< Traitement specifique des points cotiers
103   LOGICAL :: lint_atm !< Calcul pour run-off intégré sur la maille atm
104   LOGICAL :: lint_oce !< Calcul pour run-off intégré sur la maille oce
105   LOGICAL :: lnear    !< Route le run-off des pts atm 'proches' de la cote vers le point oce le plus proche
106   LOGICAL :: lnei     !< Si vrai, route le run-off des points atm 'proches' de la cote vers les point atmosphères mouilles les plus proches.
107   LOGICAL :: ltotal          !< Route tout les points atm vers l'oce le plus proche.
108   LOGICAL :: ltotal_dist     !< Route tout les points atm vers l'oce le plus proche, avec distance maxi
109   LOGICAL :: ltotal_dist_2   !< Route tout les point atm vers les oce cotiers le plus proche, avec distance maxi
110   LOGICAL :: ltotal_dist_3   !< Route tout les point atm vers les oce le plus proche, cotiers ou pas, avec distance maxi
111   LOGICAL :: l_etal_oce   !
112   REAL (kind=rl) :: dist_etal_oce
113   LOGICAL :: lessai          !< Cas en test
114   CHARACTER (len=20) :: cotes_omsk, cotes_amsk
115   REAL    (kind=rl), DIMENSION (:), ALLOCATABLE :: dist_coast_o, dist_coast_a
116   !
117   LOGICAL, DIMENSION (:), ALLOCATABLE :: lacot, laland, laoce, lanoroute, la_nearcoast
118   LOGICAL, DIMENSION (:), ALLOCATABLE :: locot, looce, lo_nearcoast
119   !
120   REAL (kind=rl) :: dist_max        = r_earth !< Earth radius
121   REAL (kind=rl) :: dist_max_atm    = 400.0E3_rl !< Max distance for searching next atm neighbours
122   REAL (kind=rl) :: dist_max_oce    = 400.0E3_rl !< Max distance for searching the ocean points
123   REAL (kind=rl) :: dist_max_large  = 400.0E3_rl !< Another max distance ...
124   LOGICAL :: l_large = .TRUE. !< @todo a commenter ...
125   !!
126   !! Poids icestream
127   !!
128   INTEGER (kind=il) :: jp_calv ! Nombre de zone de collectes
129   REAL (kind=rl), DIMENSION (:), ALLOCATABLE :: ylimits
130   LOGICAL :: l_calving_nomed !< Calving does not go to mediterranean sea (include Red Sea, Persian Gul)
131   LOGICAL :: l_calving_noatl !< Calving does not go to Atlantic
132   LOGICAL :: l_calving_nopac !< Calving does not go to Pacific
133   
134   !!
135END MODULE dimensions
Note: See TracBrowser for help on using the repository browser.