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.
in_out_manager.F90 in NEMO/trunk/src/OCE/IOM – NEMO

source: NEMO/trunk/src/OCE/IOM/in_out_manager.F90 @ 14553

Last change on this file since 14553 was 14553, checked in by gsamson, 3 years ago

merge ticket2628_r14502_abl_restart_xios branch into trunk; sette identical between r14502 and r14544; ticket #2628

  • Property svn:keywords set to Id
File size: 13.2 KB
Line 
1MODULE 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
83   !!----------------------------------------------------------------------
84   !! was in restart but moved here because of the OFF line... better solution should be found...
85   !!----------------------------------------------------------------------
86   INTEGER ::   nitrst                !: time step at which restart file should be written
87   LOGICAL ::   lrst_oce              !: logical to control the oce restart write
88   LOGICAL ::   lrst_ice              !: logical to control the ice restart write
89   LOGICAL ::   lrst_abl              !: logical to control the abl restart write
90   INTEGER ::   numror = 0            !: logical unit for ocean restart (read). Init to 0 is needed for SAS (in daymod.F90)
91   INTEGER ::   numrir = 0            !: logical unit for ice   restart (read)
92   INTEGER ::   numrar = 0            !: logical unit for abl   restart (read)
93   INTEGER ::   numrow = 0            !: logical unit for ocean restart (write)
94   INTEGER ::   numriw = 0            !: logical unit for ice   restart (write)
95   INTEGER ::   numraw = 0            !: logical unit for abl   restart (write)
96   INTEGER ::   numrtr = 0            !: trc restart (read )
97   INTEGER ::   numrtw = 0            !: trc restart (write )
98   INTEGER ::   numrsr = 0            !: logical unit for sed restart (read)
99   INTEGER ::   numrsw = 0            !: logical unit for sed restart (write)
100
101   INTEGER ::   nrst_lst              !: number of restart to output next
102
103   !!----------------------------------------------------------------------
104   !!                    output monitoring
105   !!----------------------------------------------------------------------
106   TYPE :: sn_ctl                !: structure for control over output selection
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_prtctl  = .FALSE.  !: Produce/do not produce mpp.output_XXXX files (T/F)
112      LOGICAL :: l_prttrc  = .FALSE.  !: Produce/do not produce mpp.top.output_XXXX files (T/F)
113      LOGICAL :: l_oasout  = .FALSE.  !: Produce/do not write oasis setup info to ocean.output (T/F)
114                                      !  Optional subsetting of processor report files
115                                      !  Default settings of 0/1000000/1 should ensure all areas report.
116                                      !  Set to a more restrictive range to select specific areas
117      INTEGER :: procmin   = 0        !: Minimum narea to output
118      INTEGER :: procmax   = 1000000  !: Maximum narea to output
119      INTEGER :: procincr  = 1        !: narea increment to output
120      INTEGER :: ptimincr  = 1        !: timestep increment to output (time.step and run.stat)
121   END TYPE
122   TYPE(sn_ctl), SAVE :: sn_cfctl     !: run control structure for selective output, must have SAVE for default init. of sn_ctl
123   LOGICAL ::   ln_timing        !: run control for timing
124   LOGICAL ::   ln_diacfl        !: flag whether to create CFL diagnostics
125   INTEGER ::   nn_ictls         !: Start i indice for the SUM control
126   INTEGER ::   nn_ictle         !: End   i indice for the SUM control
127   INTEGER ::   nn_jctls         !: Start j indice for the SUM control
128   INTEGER ::   nn_jctle         !: End   j indice for the SUM control
129   INTEGER ::   nn_isplt         !: number of processors following i
130   INTEGER ::   nn_jsplt         !: number of processors following j
131
132   !!----------------------------------------------------------------------
133   !!                        logical units
134   !!----------------------------------------------------------------------
135   INTEGER ::   numstp          =   -1      !: logical unit for time step
136   INTEGER ::   numtime         =   -1      !: logical unit for timing
137   INTEGER ::   numout          =    6      !: logical unit for output print; Set to stdout to ensure any
138   INTEGER ::   numnul          =   -1      !: logical unit for /dev/null
139      !                                     !  early output can be collected; do not change
140   INTEGER ::   numond          =   -1      !: logical unit for Output Namelist Dynamics
141   INTEGER ::   numoni          =   -1      !: logical unit for Output Namelist Ice
142   INTEGER ::   numevo_ice      =   -1      !: logical unit for ice variables (temp. evolution)
143   INTEGER ::   numrun          =   -1      !: logical unit for run statistics
144   INTEGER ::   numdct_in       =   -1      !: logical unit for transports computing
145   INTEGER ::   numdct_vol      =   -1      !: logical unit for volume transports output
146   INTEGER ::   numdct_heat     =   -1      !: logical unit for heat   transports output
147   INTEGER ::   numdct_salt     =   -1      !: logical unit for salt   transports output
148   INTEGER ::   numfl           =   -1      !: logical unit for floats ascii output
149   INTEGER ::   numflo          =   -1      !: logical unit for floats ascii output
150      !
151   CHARACTER(LEN=:), ALLOCATABLE :: numnam_ref      !: character buffer for reference namelist
152   CHARACTER(LEN=:), ALLOCATABLE :: numnam_cfg      !: character buffer for configuration specific namelist
153   CHARACTER(LEN=:), ALLOCATABLE :: numnam_ice_ref  !: character buffer for ice reference namelist
154   CHARACTER(LEN=:), ALLOCATABLE :: numnam_ice_cfg  !: character buffer for ice configuration specific namelist
155
156   !!----------------------------------------------------------------------
157   !!                          Run control
158   !!----------------------------------------------------------------------
159   INTEGER       ::   no_print = 0          !: optional argument of fld_fill (if present, suppress some control print)
160   INTEGER       ::   nstop = 0             !: error flag (=number of reason for a premature stop run)
161!$AGRIF_DO_NOT_TREAT
162   INTEGER       ::   ngrdstop = -1         !: grid number having nstop > 1
163!$AGRIF_END_DO_NOT_TREAT
164   INTEGER       ::   nwarn = 0             !: warning flag (=number of warning found during the run)
165   CHARACTER(lc) ::   ctmp1, ctmp2, ctmp3   !: temporary characters 1 to 3
166   CHARACTER(lc) ::   ctmp4, ctmp5, ctmp6   !: temporary characters 4 to 6
167   CHARACTER(lc) ::   ctmp7, ctmp8, ctmp9   !: temporary characters 7 to 9
168   CHARACTER(lc) ::   ctmp10                !: temporary character 10
169   LOGICAL       ::   lwm      = .FALSE.    !: boolean : true on the 1st processor only (always)
170   LOGICAL       ::   lwp      = .FALSE.    !: boolean : true on the 1st processor only .OR. sn_cfctl%l_oceout=T
171   LOGICAL       ::   lsp_area = .TRUE.     !: to make a control print over a specific area
172   CHARACTER(LEN=lc) ::   cxios_context     !: context name used in xios
173   CHARACTER(LEN=lc) ::   cr_ocerst_cxt     !: context name used in xios to read OCE restart
174   CHARACTER(LEN=lc) ::   cw_ocerst_cxt     !: context name used in xios to write OCE restart file
175   CHARACTER(LEN=lc) ::   cr_icerst_cxt     !: context name used in xios to read SI3 restart
176   CHARACTER(LEN=lc) ::   cw_icerst_cxt     !: context name used in xios to write SI3 restart file
177   CHARACTER(LEN=lc) ::   cr_ablrst_cxt     !: context name used in xios to read ABL restart
178   CHARACTER(LEN=lc) ::   cw_ablrst_cxt     !: context name used in xios to write ABL restart file
179   CHARACTER(LEN=lc) ::   cr_toprst_cxt     !: context name used in xios to read TOP restart
180   CHARACTER(LEN=lc) ::   cw_toprst_cxt     !: context name used in xios to write TOP restart file
181   CHARACTER(LEN=lc) ::   cr_sedrst_cxt     !: context name used in xios to read SEDIMENT restart
182   CHARACTER(LEN=lc) ::   cw_sedrst_cxt     !: context name used in xios to write SEDIMENT restart file
183
184
185
186
187   !! * Substitutions
188#  include "do_loop_substitute.h90"
189   !!----------------------------------------------------------------------
190   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
191   !! $Id$
192   !! Software governed by the CeCILL license (see ./LICENSE)
193   !!=====================================================================
194END MODULE in_out_manager
Note: See TracBrowser for help on using the repository browser.