1 | MODULE iom_def |
---|
2 | !!===================================================================== |
---|
3 | !! *** MODULE iom_def *** |
---|
4 | !! IOM variables definitions |
---|
5 | !!==================================================================== |
---|
6 | !! History : 9.0 ! 06 09 (S. Masson) Original code |
---|
7 | !! " ! 07 07 (D. Storkey) Add uldname |
---|
8 | !!-------------------------------------------------------------------- |
---|
9 | !!--------------------------------------------------------------------------------- |
---|
10 | !! NEMO/OPA 3.3 , NEMO Consortium (2010) |
---|
11 | !! $Id$ |
---|
12 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
13 | !!--------------------------------------------------------------------------------- |
---|
14 | |
---|
15 | USE par_kind |
---|
16 | |
---|
17 | IMPLICIT NONE |
---|
18 | PRIVATE |
---|
19 | |
---|
20 | INTEGER, PARAMETER, PUBLIC :: jpdom_data = 1 !: ( 1 :jpidta, 1 :jpjdta) |
---|
21 | INTEGER, PARAMETER, PUBLIC :: jpdom_global = 2 !: ( 1 :jpiglo, 1 :jpjglo) |
---|
22 | INTEGER, PARAMETER, PUBLIC :: jpdom_local = 3 !: One of the 3 following cases |
---|
23 | INTEGER, PARAMETER, PUBLIC :: jpdom_local_full = 4 !: ( 1 :jpi , 1 :jpi ) |
---|
24 | INTEGER, PARAMETER, PUBLIC :: jpdom_local_noextra = 5 !: ( 1 :nlci , 1 :nlcj ) |
---|
25 | INTEGER, PARAMETER, PUBLIC :: jpdom_local_noovlap = 6 !: (nldi:nlei ,nldj:nlej ) |
---|
26 | INTEGER, PARAMETER, PUBLIC :: jpdom_unknown = 7 !: No dimension checking |
---|
27 | INTEGER, PARAMETER, PUBLIC :: jpdom_autoglo = 8 !: |
---|
28 | INTEGER, PARAMETER, PUBLIC :: jpdom_autoglo_xy = 9 !: Automatically set horizontal dimensions only |
---|
29 | INTEGER, PARAMETER, PUBLIC :: jpdom_autodta = 10 !: |
---|
30 | |
---|
31 | INTEGER, PARAMETER, PUBLIC :: jpioipsl = 100 !: Use ioipsl (fliocom only) library |
---|
32 | INTEGER, PARAMETER, PUBLIC :: jpnf90 = 101 !: Use nf90 library |
---|
33 | INTEGER, PARAMETER, PUBLIC :: jprstdimg = 102 !: Use restart dimgs (fortran direct acces) library |
---|
34 | #if defined key_dimgout |
---|
35 | INTEGER, PARAMETER, PUBLIC :: jprstlib = jprstdimg !: restarts io library |
---|
36 | #else |
---|
37 | INTEGER, PARAMETER, PUBLIC :: jprstlib = jpnf90 !: restarts io library |
---|
38 | #endif |
---|
39 | |
---|
40 | INTEGER, PARAMETER, PUBLIC :: jp_r8 = 200 !: write REAL(8) |
---|
41 | INTEGER, PARAMETER, PUBLIC :: jp_r4 = 201 !: write REAL(4) |
---|
42 | INTEGER, PARAMETER, PUBLIC :: jp_i4 = 202 !: write INTEGER(4) |
---|
43 | INTEGER, PARAMETER, PUBLIC :: jp_i2 = 203 !: write INTEGER(2) |
---|
44 | INTEGER, PARAMETER, PUBLIC :: jp_i1 = 204 !: write INTEGER(1) |
---|
45 | |
---|
46 | INTEGER, PARAMETER, PUBLIC :: jpmax_files = 100 !: maximum number of simultaneously opened file |
---|
47 | INTEGER, PARAMETER, PUBLIC :: jpmax_vars = 600 !: maximum number of variables in one file |
---|
48 | INTEGER, PARAMETER, PUBLIC :: jpmax_dims = 4 !: maximum number of dimensions for one variable |
---|
49 | INTEGER, PARAMETER, PUBLIC :: jpmax_digits = 5 !: maximum number of digits for the cpu number in the file name |
---|
50 | |
---|
51 | !$AGRIF_DO_NOT_TREAT |
---|
52 | INTEGER, PUBLIC :: iom_open_init = 0 !: used to initialize iom_file(:)%nfid to 0 |
---|
53 | !XIOS read restart |
---|
54 | LOGICAL, PUBLIC :: lxios_read !: read single file restart using XIOS |
---|
55 | LOGICAL, PUBLIC :: lxios_sini = .FALSE. ! is restart in a single file |
---|
56 | LOGICAL, PUBLIC :: lxios_set = .FALSE. |
---|
57 | !XIOS read restart |
---|
58 | LOGICAL, PUBLIC :: lwxios !: read single file restart using XIOS |
---|
59 | INTEGER, PUBLIC :: wxioso !: type of restart file when writing using XIOS 1 - single, 2 - multiple |
---|
60 | LOGICAL, PUBLIC :: lspr !: single processor read data flag |
---|
61 | |
---|
62 | |
---|
63 | TYPE, PUBLIC :: file_descriptor |
---|
64 | CHARACTER(LEN=240) :: name !: name of the file |
---|
65 | INTEGER :: nfid !: identifier of the file (0 if closed) |
---|
66 | INTEGER :: iolib !: library used to read the file (jpioipsl, jpnf90 or jprstdimg) |
---|
67 | INTEGER :: nvars !: number of identified varibles in the file |
---|
68 | INTEGER :: iduld !: id of the unlimited dimension |
---|
69 | INTEGER :: lenuld !: length of the unlimited dimension (number of records in file) |
---|
70 | INTEGER :: irec !: writing record position |
---|
71 | CHARACTER(LEN=32) :: uldname !: name of the unlimited dimension |
---|
72 | CHARACTER(LEN=32), DIMENSION(jpmax_vars) :: cn_var !: names of the variables |
---|
73 | INTEGER, DIMENSION(jpmax_vars) :: nvid !: id of the variables |
---|
74 | INTEGER, DIMENSION(jpmax_vars) :: ndims !: number of dimensions of the variables |
---|
75 | LOGICAL, DIMENSION(jpmax_vars) :: luld !: variable using the unlimited dimension |
---|
76 | INTEGER, DIMENSION(jpmax_dims,jpmax_vars) :: dimsz !: size of variables dimensions |
---|
77 | REAL(kind=wp), DIMENSION(jpmax_vars) :: scf !: scale_factor of the variables |
---|
78 | REAL(kind=wp), DIMENSION(jpmax_vars) :: ofs !: add_offset of the variables |
---|
79 | LOGICAL :: lsngl = .FALSE. !: one file flag |
---|
80 | END TYPE file_descriptor |
---|
81 | TYPE(file_descriptor), DIMENSION(jpmax_files), PUBLIC :: iom_file !: array containing the info for all opened files |
---|
82 | |
---|
83 | INTEGER, PARAMETER, PUBLIC :: max_rst_fields = 85 |
---|
84 | |
---|
85 | TYPE, PUBLIC :: RST_FIELD |
---|
86 | CHARACTER(len=30) :: vname ! names of variables in restart file |
---|
87 | CHARACTER(len=30) :: grid |
---|
88 | END TYPE RST_FIELD |
---|
89 | TYPE(RST_FIELD), PUBLIC :: rst_fields(max_rst_fields) |
---|
90 | |
---|
91 | !$AGRIF_END_DO_NOT_TREAT |
---|
92 | |
---|
93 | !!===================================================================== |
---|
94 | END MODULE iom_def |
---|