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

source: NEMO/trunk/src/OCE/IOM/iom_def.F90 @ 11048

Last change on this file since 11048 was 10425, checked in by smasson, 5 years ago

trunk: merge back dev_r10164_HPC09_ESIWACE_PREP_MERGE@10424 into the trunk

  • Property svn:keywords set to Id
File size: 5.3 KB
RevLine 
[544]1MODULE iom_def
[9019]2   !!======================================================================
[544]3   !!                    ***  MODULE  iom_def ***
4   !! IOM variables definitions
[9019]5   !!======================================================================
6   !! History :  9.0  ! 2006 09  (S. Masson) Original code
7   !!             -   ! 2007 07  (D. Storkey) Add uldname
8   !!            4.0  ! 2017-11 (M. Andrejczuk) Extend IOM interface to write any 3D fields
9   !!----------------------------------------------------------------------
[544]10   USE par_kind
11
12   IMPLICIT NONE
13   PRIVATE
14
[7646]15   INTEGER, PARAMETER, PUBLIC ::   jpdom_data          = 1   !: ( 1  :jpiglo, 1  :jpjglo)    !!gm to be suppressed
[544]16   INTEGER, PARAMETER, PUBLIC ::   jpdom_global        = 2   !: ( 1  :jpiglo, 1  :jpjglo)
17   INTEGER, PARAMETER, PUBLIC ::   jpdom_local         = 3   !: One of the 3 following cases
18   INTEGER, PARAMETER, PUBLIC ::   jpdom_local_full    = 4   !: ( 1  :jpi   , 1  :jpi   )
19   INTEGER, PARAMETER, PUBLIC ::   jpdom_local_noextra = 5   !: ( 1  :nlci  , 1  :nlcj  )
20   INTEGER, PARAMETER, PUBLIC ::   jpdom_local_noovlap = 6   !: (nldi:nlei  ,nldj:nlej  )
21   INTEGER, PARAMETER, PUBLIC ::   jpdom_unknown       = 7   !: No dimension checking
[679]22   INTEGER, PARAMETER, PUBLIC ::   jpdom_autoglo       = 8   !:
[6140]23   INTEGER, PARAMETER, PUBLIC ::   jpdom_autoglo_xy    = 9   !: Automatically set horizontal dimensions only
24   INTEGER, PARAMETER, PUBLIC ::   jpdom_autodta       = 10  !:
[544]25
[556]26   INTEGER, PARAMETER, PUBLIC ::   jp_r8    = 200      !: write REAL(8)
27   INTEGER, PARAMETER, PUBLIC ::   jp_r4    = 201      !: write REAL(4)
28   INTEGER, PARAMETER, PUBLIC ::   jp_i4    = 202      !: write INTEGER(4)
29   INTEGER, PARAMETER, PUBLIC ::   jp_i2    = 203      !: write INTEGER(2)
30   INTEGER, PARAMETER, PUBLIC ::   jp_i1    = 204      !: write INTEGER(1)
[544]31
[7646]32   INTEGER, PARAMETER, PUBLIC ::   jpmax_files  = 100  !: maximum number of simultaneously opened file
33   INTEGER, PARAMETER, PUBLIC ::   jpmax_vars   = 1200 !: maximum number of variables in one file
[544]34   INTEGER, PARAMETER, PUBLIC ::   jpmax_dims   =  4   !: maximum number of dimensions for one variable
35   INTEGER, PARAMETER, PUBLIC ::   jpmax_digits =  5   !: maximum number of digits for the cpu number in the file name
36
[9367]37
[571]38!$AGRIF_DO_NOT_TREAT
[1359]39   INTEGER, PUBLIC            ::   iom_open_init = 0   !: used to initialize iom_file(:)%nfid to 0
[9367]40!XIOS write restart   
41   LOGICAL, PUBLIC            ::   lwxios          !: write single file restart using XIOS
42   INTEGER, PUBLIC            ::   nxioso          !: type of restart file when writing using XIOS 1 - single, 2 - multiple
43!XIOS read restart   
44   LOGICAL, PUBLIC            ::   lrxios          !: read single file restart using XIOS
45   LOGICAL, PUBLIC            ::   lxios_sini = .FALSE. ! is restart in a single file
46   LOGICAL, PUBLIC            ::   lxios_set  = .FALSE. 
[571]47
[9367]48
49
[556]50   TYPE, PUBLIC ::   file_descriptor
[544]51      CHARACTER(LEN=240)                        ::   name     !: name of the file
52      INTEGER                                   ::   nfid     !: identifier of the file (0 if closed)
[6140]53                                                              !: jpioipsl option has been removed)
[544]54      INTEGER                                   ::   nvars    !: number of identified varibles in the file
55      INTEGER                                   ::   iduld    !: id of the unlimited dimension
[6140]56      INTEGER                                   ::   lenuld   !: length of the unlimited dimension (number of records in file)
[544]57      INTEGER                                   ::   irec     !: writing record position 
[911]58      CHARACTER(LEN=32)                         ::   uldname  !: name of the unlimited dimension
[577]59      CHARACTER(LEN=32), DIMENSION(jpmax_vars)  ::   cn_var   !: names of the variables
[544]60      INTEGER, DIMENSION(jpmax_vars)            ::   nvid     !: id of the variables
61      INTEGER, DIMENSION(jpmax_vars)            ::   ndims    !: number of dimensions of the variables
62      LOGICAL, DIMENSION(jpmax_vars)            ::   luld     !: variable using the unlimited dimension
63      INTEGER, DIMENSION(jpmax_dims,jpmax_vars) ::   dimsz    !: size of variables dimensions
64      REAL(kind=wp), DIMENSION(jpmax_vars)      ::   scf      !: scale_factor of the variables
65      REAL(kind=wp), DIMENSION(jpmax_vars)      ::   ofs      !: add_offset of the variables
[9019]66      INTEGER                                   ::   nlev     ! number of vertical levels
[556]67   END TYPE file_descriptor
68   TYPE(file_descriptor), DIMENSION(jpmax_files), PUBLIC ::   iom_file !: array containing the info for all opened files
[9367]69   INTEGER, PARAMETER, PUBLIC                   :: max_rst_fields = 95 !: maximum number of restart variables defined in iom_set_rst_vars
70   TYPE, PUBLIC :: RST_FIELD 
71    CHARACTER(len=30) :: vname = "NO_NAME" ! names of variables in restart file
72    CHARACTER(len=30) :: grid = "NO_GRID"
73    LOGICAL           :: active =.FALSE. ! for restart write only: true - write field, false do not write field
74   END TYPE RST_FIELD
[550]75!$AGRIF_END_DO_NOT_TREAT
[9367]76   !
[9598]77   TYPE(RST_FIELD), PUBLIC, SAVE :: rst_wfields(max_rst_fields), rst_rfields(max_rst_fields)
[9367]78   !
[9019]79   !!----------------------------------------------------------------------
[9598]80   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[9019]81   !! $Id$
[10068]82   !! Software governed by the CeCILL license (see ./LICENSE)
[9019]83   !!======================================================================
[544]84END MODULE iom_def
Note: See TracBrowser for help on using the repository browser.