1 | MODULE in_out_manager |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE in_out_manager *** |
---|
4 | !! I/O manager utilities : Defines run parameters together with logical units |
---|
5 | !!===================================================================== |
---|
6 | !! History : 1.0 ! 2002-06 (G. Madec) original code |
---|
7 | !! 2.0 ! 2006-07 (S. Masson) iom, add ctl_stop, ctl_warn |
---|
8 | !! 3.0 ! 2008-06 (G. Madec) add ctmp4 to ctmp10 |
---|
9 | !! 3.2 ! 2009-08 (S. MAsson) add new ctl_opn |
---|
10 | !! 3.3 ! 2010-10 (A. Coward) add NetCDF4 usage |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | |
---|
13 | !!---------------------------------------------------------------------- |
---|
14 | USE par_oce ! ocean parameter |
---|
15 | USE nc4interface ! NetCDF4 interface |
---|
16 | |
---|
17 | IMPLICIT NONE |
---|
18 | PUBLIC |
---|
19 | |
---|
20 | !!---------------------------------------------------------------------- |
---|
21 | !! namrun namelist parameters |
---|
22 | !!---------------------------------------------------------------------- |
---|
23 | CHARACTER(lc) :: cn_exp !: experiment name used for output filename |
---|
24 | CHARACTER(lc) :: cn_ocerst_in !: suffix of ocean restart name (input) |
---|
25 | CHARACTER(lc) :: cn_ocerst_indir !: restart input directory |
---|
26 | CHARACTER(lc) :: cn_ocerst_out !: suffix of ocean restart name (output) |
---|
27 | CHARACTER(lc) :: cn_ocerst_outdir !: restart output directory |
---|
28 | LOGICAL :: ln_rstart !: start from (F) rest or (T) a restart file |
---|
29 | LOGICAL :: ln_rst_list !: output restarts at list of times (T) or by frequency (F) |
---|
30 | INTEGER :: nn_rstctl !: control of the time step (0, 1 or 2) |
---|
31 | INTEGER :: nn_rstssh = 0 !: hand made initilization of ssh or not (1/0) |
---|
32 | INTEGER :: nn_it000 !: index of the first time step |
---|
33 | INTEGER :: nn_itend !: index of the last time step |
---|
34 | INTEGER :: nn_date0 !: initial calendar date aammjj |
---|
35 | INTEGER :: nn_time0 !: initial time of day in hhmm |
---|
36 | INTEGER :: nn_leapy !: Leap year calendar flag (0/1 or 30) |
---|
37 | INTEGER :: nn_istate !: initial state output flag (0/1) |
---|
38 | INTEGER :: nn_write !: model standard output frequency |
---|
39 | INTEGER :: nn_stock !: restart file frequency |
---|
40 | INTEGER, DIMENSION(10) :: nn_stocklist !: restart dump times |
---|
41 | LOGICAL :: ln_mskland !: mask land points in NetCDF outputs (costly: + ~15%) |
---|
42 | LOGICAL :: ln_cfmeta !: output additional data to netCDF files required for compliance with the CF metadata standard |
---|
43 | LOGICAL :: ln_clobber !: clobber (overwrite) an existing file |
---|
44 | INTEGER :: nn_chunksz !: chunksize (bytes) for NetCDF file (works only with iom_nf90 routines) |
---|
45 | LOGICAL :: ln_xios_read !: use xios to read single file restart |
---|
46 | INTEGER :: nn_wxios !: write resart using xios 0 - no, 1 - single, 2 - multiple file output |
---|
47 | INTEGER :: nn_no !: Assimilation cycle |
---|
48 | |
---|
49 | #if defined key_netcdf4 |
---|
50 | !!---------------------------------------------------------------------- |
---|
51 | !! namnc4 namelist parameters (key_netcdf4) |
---|
52 | !!---------------------------------------------------------------------- |
---|
53 | ! The following four values determine the partitioning of the output fields |
---|
54 | ! into netcdf4 chunks. They are unrelated to the nn_chunk_sz setting which is |
---|
55 | ! for runtime optimisation. The individual netcdf4 chunks can be optionally |
---|
56 | ! gzipped (recommended) leading to significant reductions in I/O volumes |
---|
57 | ! !!!** variables only used with iom_nf90 routines and key_netcdf4 ** |
---|
58 | INTEGER :: nn_nchunks_i !: number of chunks required in the i-dimension |
---|
59 | INTEGER :: nn_nchunks_j !: number of chunks required in the j-dimension |
---|
60 | INTEGER :: nn_nchunks_k !: number of chunks required in the k-dimension |
---|
61 | INTEGER :: nn_nchunks_t !: number of chunks required in the t-dimension |
---|
62 | LOGICAL :: ln_nc4zip !: netcdf4 usage: (T) chunk and compress output using the HDF5 sublayers of netcdf4 |
---|
63 | ! ! (F) ignore chunking request and use the netcdf4 library |
---|
64 | ! ! to produce netcdf3-compatible files |
---|
65 | #endif |
---|
66 | |
---|
67 | !$AGRIF_DO_NOT_TREAT |
---|
68 | TYPE(snc4_ctl) :: snc4set !: netcdf4 chunking control structure (always needed for decision making) |
---|
69 | !$AGRIF_END_DO_NOT_TREAT |
---|
70 | |
---|
71 | |
---|
72 | !! conversion of DOCTOR norm namelist name into model name |
---|
73 | !! (this should disappear in a near futur) |
---|
74 | |
---|
75 | CHARACTER(lc) :: cexper !: experiment name used for output filename |
---|
76 | INTEGER :: nrstdt !: control of the time step (0, 1 or 2) |
---|
77 | INTEGER :: nit000 !: index of the first time step |
---|
78 | INTEGER :: nitend !: index of the last time step |
---|
79 | INTEGER :: ndate0 !: initial calendar date aammjj |
---|
80 | INTEGER :: nleapy !: Leap year calendar flag (0/1 or 30) |
---|
81 | INTEGER :: ninist !: initial state output flag (0/1) |
---|
82 | INTEGER :: nwrite !: model standard output frequency |
---|
83 | INTEGER :: nstock !: restart file frequency |
---|
84 | INTEGER, DIMENSION(10) :: nstocklist !: restart dump times |
---|
85 | |
---|
86 | !!---------------------------------------------------------------------- |
---|
87 | !! was in restart but moved here because of the OFF line... better solution should be found... |
---|
88 | !!---------------------------------------------------------------------- |
---|
89 | INTEGER :: nitrst !: time step at which restart file should be written |
---|
90 | LOGICAL :: lrst_oce !: logical to control the oce restart write |
---|
91 | LOGICAL :: lrst_ice !: logical to control the ice restart write |
---|
92 | INTEGER :: numror = 0 !: logical unit for ocean restart (read). Init to 0 is needed for SAS (in daymod.F90) |
---|
93 | INTEGER :: numrir !: logical unit for ice restart (read) |
---|
94 | INTEGER :: numrow !: logical unit for ocean restart (write) |
---|
95 | INTEGER :: numriw !: logical unit for ice restart (write) |
---|
96 | INTEGER :: nrst_lst !: number of restart to output next |
---|
97 | |
---|
98 | !!---------------------------------------------------------------------- |
---|
99 | !! output monitoring |
---|
100 | !!---------------------------------------------------------------------- |
---|
101 | LOGICAL :: ln_ctl !: run control for debugging |
---|
102 | TYPE :: sn_ctl !: optional use structure for finer control over output selection |
---|
103 | LOGICAL :: l_config = .FALSE. !: activate/deactivate finer control |
---|
104 | ! Note if l_config is True then ln_ctl is ignored. |
---|
105 | ! Otherwise setting ln_ctl True is equivalent to setting |
---|
106 | ! all the following logicals in this structure True |
---|
107 | LOGICAL :: l_runstat = .FALSE. !: Produce/do not produce run.stat file (T/F) |
---|
108 | LOGICAL :: l_trcstat = .FALSE. !: Produce/do not produce tracer.stat file (T/F) |
---|
109 | LOGICAL :: l_oceout = .FALSE. !: Produce all ocean.outputs (T) or just one (F) |
---|
110 | LOGICAL :: l_layout = .FALSE. !: Produce all layout.dat files (T) or just one (F) |
---|
111 | LOGICAL :: l_mppout = .FALSE. !: Produce/do not produce mpp.output_XXXX files (T/F) |
---|
112 | LOGICAL :: l_mpptop = .FALSE. !: Produce/do not produce mpp.top.output_XXXX files (T/F) |
---|
113 | ! Optional subsetting of processor report files |
---|
114 | ! Default settings of 0/1000000/1 should ensure all areas report. |
---|
115 | ! Set to a more restrictive range to select specific areas |
---|
116 | INTEGER :: procmin = 0 !: Minimum narea to output |
---|
117 | INTEGER :: procmax = 1000000 !: Maximum narea to output |
---|
118 | INTEGER :: procincr = 1 !: narea increment to output |
---|
119 | INTEGER :: ptimincr = 1 !: timestep increment to output (time.step and run.stat) |
---|
120 | END TYPE sn_ctl |
---|
121 | |
---|
122 | TYPE (sn_ctl) :: sn_cfctl !: run control structure for selective output |
---|
123 | LOGICAL :: ln_timing !: run control for timing |
---|
124 | LOGICAL :: ln_diacfl !: flag whether to create CFL diagnostics |
---|
125 | INTEGER :: nn_print !: level of print (0 no print) |
---|
126 | INTEGER :: nn_ictls !: Start i indice for the SUM control |
---|
127 | INTEGER :: nn_ictle !: End i indice for the SUM control |
---|
128 | INTEGER :: nn_jctls !: Start j indice for the SUM control |
---|
129 | INTEGER :: nn_jctle !: End j indice for the SUM control |
---|
130 | INTEGER :: nn_isplt !: number of processors following i |
---|
131 | INTEGER :: nn_jsplt !: number of processors following j |
---|
132 | INTEGER :: nn_bench !: benchmark parameter (0/1) |
---|
133 | INTEGER :: nn_bit_cmp = 0 !: bit reproducibility (0/1) |
---|
134 | ! |
---|
135 | INTEGER :: nprint, nictls, nictle, njctls, njctle, isplt, jsplt !: OLD namelist names |
---|
136 | |
---|
137 | INTEGER :: ijsplt = 1 !: nb of local domain = nb of processors |
---|
138 | |
---|
139 | !!---------------------------------------------------------------------- |
---|
140 | !! logical units |
---|
141 | !!---------------------------------------------------------------------- |
---|
142 | INTEGER :: numstp = -1 !: logical unit for time step |
---|
143 | INTEGER :: numtime = -1 !: logical unit for timing |
---|
144 | INTEGER :: numout = 6 !: logical unit for output print; Set to stdout to ensure any |
---|
145 | INTEGER :: numnul = -1 !: logical unit for /dev/null |
---|
146 | ! ! early output can be collected; do not change |
---|
147 | INTEGER :: numnam_ref = -1 !: logical unit for reference namelist |
---|
148 | INTEGER :: numnam_cfg = -1 !: logical unit for configuration specific namelist |
---|
149 | INTEGER :: numond = -1 !: logical unit for Output Namelist Dynamics |
---|
150 | INTEGER :: numnam_ice_ref = -1 !: logical unit for ice reference namelist |
---|
151 | INTEGER :: numnam_ice_cfg = -1 !: logical unit for ice reference namelist |
---|
152 | INTEGER :: numoni = -1 !: logical unit for Output Namelist Ice |
---|
153 | INTEGER :: numevo_ice = -1 !: logical unit for ice variables (temp. evolution) |
---|
154 | INTEGER :: numrun = -1 !: logical unit for run statistics |
---|
155 | INTEGER :: numdct_in = -1 !: logical unit for transports computing |
---|
156 | INTEGER :: numdct_vol = -1 !: logical unit for voulume transports output |
---|
157 | INTEGER :: numdct_heat = -1 !: logical unit for heat transports output |
---|
158 | INTEGER :: numdct_salt = -1 !: logical unit for salt transports output |
---|
159 | INTEGER :: numfl = -1 !: logical unit for floats ascii output |
---|
160 | INTEGER :: numflo = -1 !: logical unit for floats ascii output |
---|
161 | |
---|
162 | !!---------------------------------------------------------------------- |
---|
163 | !! Run control |
---|
164 | !!---------------------------------------------------------------------- |
---|
165 | INTEGER :: no_print = 0 !: optional argument of fld_fill (if present, suppress some control print) |
---|
166 | INTEGER :: nstop = 0 !: error flag (=number of reason for a premature stop run) |
---|
167 | INTEGER :: nwarn = 0 !: warning flag (=number of warning found during the run) |
---|
168 | CHARACTER(lc) :: ctmp1, ctmp2, ctmp3 !: temporary characters 1 to 3 |
---|
169 | CHARACTER(lc) :: ctmp4, ctmp5, ctmp6 !: temporary characters 4 to 6 |
---|
170 | CHARACTER(lc) :: ctmp7, ctmp8, ctmp9 !: temporary characters 7 to 9 |
---|
171 | CHARACTER(lc) :: ctmp10 !: temporary character 10 |
---|
172 | CHARACTER(lc) :: cform_err = "(/,' ===>>> : E R R O R', /,' ===========',/)" !: |
---|
173 | CHARACTER(lc) :: cform_war = "(/,' ===>>> : W A R N I N G', /,' ===============',/)" !: |
---|
174 | LOGICAL :: lwm = .FALSE. !: boolean : true on the 1st processor only (always) |
---|
175 | LOGICAL :: lwp = .FALSE. !: boolean : true on the 1st processor only .OR. ln_ctl |
---|
176 | LOGICAL :: lsp_area = .TRUE. !: to make a control print over a specific area |
---|
177 | CHARACTER(lc) :: cxios_context !: context name used in xios |
---|
178 | CHARACTER(lc) :: crxios_context !: context name used in xios to read restart |
---|
179 | CHARACTER(lc) :: cwxios_context !: context name used in xios to write restart file |
---|
180 | |
---|
181 | !!---------------------------------------------------------------------- |
---|
182 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
183 | !! $Id: in_out_manager.F90 10570 2019-01-24 15:14:49Z acc $ |
---|
184 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
185 | !!===================================================================== |
---|
186 | END MODULE in_out_manager |
---|