Newer
Older
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
MODULE iom_def
!!======================================================================
!! *** MODULE iom_def ***
!! IOM variables definitions
!!======================================================================
!! History : 9.0 ! 2006 09 (S. Masson) Original code
!! - ! 2007 07 (D. Storkey) Add uldname
!! 4.0 ! 2017-11 (M. Andrejczuk) Extend IOM interface to write any 3D fields
!!----------------------------------------------------------------------
USE par_kind
USE netcdf
IMPLICIT NONE
PRIVATE
INTEGER, PARAMETER, PUBLIC :: jpdom_global = 1 !: ( 1 :Ni0glo, 1 :Nj0glo)
INTEGER, PARAMETER, PUBLIC :: jpdom_local = 2 !: (Nis0: Nie0 ,Njs0: Nje0 )
INTEGER, PARAMETER, PUBLIC :: jpdom_unknown = 3 !: No dimension checking
INTEGER, PARAMETER, PUBLIC :: jpdom_auto = 4 !:
INTEGER, PARAMETER, PUBLIC :: jpdom_auto_xy = 5 !: Automatically set horizontal dimensions only
INTEGER, PARAMETER, PUBLIC :: jp_r8 = 200 !: write REAL(8)
INTEGER, PARAMETER, PUBLIC :: jp_r4 = 201 !: write REAL(4)
INTEGER, PARAMETER, PUBLIC :: jp_i4 = 202 !: write INTEGER(4)
INTEGER, PARAMETER, PUBLIC :: jp_i2 = 203 !: write INTEGER(2)
INTEGER, PARAMETER, PUBLIC :: jp_i1 = 204 !: write INTEGER(1)
INTEGER, PARAMETER, PUBLIC :: jpmax_files = 100 !: maximum number of simultaneously opened file
INTEGER, PARAMETER, PUBLIC :: jpmax_vars = 1200 !: maximum number of variables in one file
INTEGER, PARAMETER, PUBLIC :: jpmax_dims = 4 !: maximum number of dimensions for one variable
INTEGER, PARAMETER, PUBLIC :: jpmax_digits = 9 !: maximum number of digits for the cpu number in the file name
!$AGRIF_DO_NOT_TREAT
INTEGER, PUBLIC :: iom_open_init = 0 !: used to initialize iom_file(:)%nfid to 0
!XIOS write restart
LOGICAL, PUBLIC :: lwxios = .FALSE. !: write single file restart using XIOS
INTEGER, PUBLIC :: nxioso = 0 !: type of restart file when writing using XIOS 1 - single, 2 - multiple
!XIOS read restart
LOGICAL, PUBLIC :: lrxios = .FALSE. !: read single file restart using XIOS main switch
LOGICAL, PUBLIC :: lxios_sini = .FALSE. ! is restart in a single file
TYPE, PUBLIC :: file_descriptor
CHARACTER(LEN=240) :: name !: name of the file
CHARACTER(LEN=3 ) :: comp !: name of component opening the file ('OCE', 'ICE'...)
INTEGER :: nfid !: identifier of the file (0 if closed)
!: jpioipsl option has been removed)
INTEGER :: nvars !: number of identified varibles in the file
INTEGER :: iduld !: id of the unlimited dimension
INTEGER :: lenuld !: length of the unlimited dimension (number of records in file)
INTEGER :: irec !: writing record position
CHARACTER(LEN=32) :: uldname !: name of the unlimited dimension
CHARACTER(LEN=32), DIMENSION(jpmax_vars) :: cn_var !: names of the variables
INTEGER, DIMENSION(jpmax_vars) :: nvid !: id of the variables
INTEGER, DIMENSION(jpmax_vars) :: ndims !: number of dimensions of the variables
LOGICAL, DIMENSION(jpmax_vars) :: luld !: variable using the unlimited dimension
INTEGER, DIMENSION(jpmax_dims,jpmax_vars) :: dimsz !: size of variables dimensions
REAL(kind=wp), DIMENSION(jpmax_vars) :: scf !: scale_factor of the variables
REAL(kind=wp), DIMENSION(jpmax_vars) :: ofs !: add_offset of the variables
END TYPE file_descriptor
TYPE(file_descriptor), DIMENSION(jpmax_files), PUBLIC :: iom_file !: array containing the info for all opened files
!$AGRIF_END_DO_NOT_TREAT
!
!! * Substitutions
# include "do_loop_substitute.h90"
!!----------------------------------------------------------------------
!! NEMO/OCE 4.0 , NEMO Consortium (2018)
!! $Id: iom_def.F90 14072 2020-12-04 07:48:38Z laurent $
!! Software governed by the CeCILL license (see ./LICENSE)
!!======================================================================
END MODULE iom_def