ICON Community Interface 0.4.0
Loading...
Searching...
No Matches
comin_descrdata_types.F90
Go to the documentation of this file.
1
3!
4! @authors 10/2021 :: ICON Community Interface <comin@icon-model.org>
5!
6! SPDX-License-Identifier: BSD-3-Clause
7!
8! See LICENSES for license information.
9! Where software is supplied by third parties, it is indicated in the
10! headers of the routines.
11!
13 USE iso_c_binding, ONLY : c_signed_char, c_int, c_bool
14 USE comin_setup_constants, ONLY : wp
15 IMPLICIT NONE
16
17 PRIVATE
18
26
27#include "comin_global.inc"
28
29 ! ------------------------------------
30 ! data types for descriptive data structures
31 ! ------------------------------------
32
33 ! Descriptive data from p_patch apart from few exceptions (e.g. lon and lat)
34 ! handed to ComIn as pointer, all other descriptive data are copies from
35 ! host model, which need to be updated during the model simulation if changed
36
41 ! number of logical domains
42 INTEGER(C_INT) :: n_dom
43 ! maximum number of model domains
44 INTEGER(C_INT) :: max_dom
45 ! block size
46 INTEGER(C_INT) :: nproma
47 ! KIND value (REAL)
48 INTEGER(C_INT) :: wp
49 ! block index
50 INTEGER(C_INT) :: min_rlcell_int
51 INTEGER(C_INT) :: min_rlcell
52 INTEGER(C_INT) :: max_rlcell
53 INTEGER(C_INT) :: min_rlvert_int
54 INTEGER(C_INT) :: min_rlvert
55 INTEGER(C_INT) :: max_rlvert
56 INTEGER(C_INT) :: min_rledge_int
57 INTEGER(C_INT) :: min_rledge
58 INTEGER(C_INT) :: max_rledge
59 ! block index
60 INTEGER(C_INT) :: grf_bdywidth_c
61 INTEGER(C_INT) :: grf_bdywidth_e
62 ! whether this is a restarted run
63 LOGICAL(C_BOOL) :: lrestartrun
64 ! parameter A of the vertical coordinate (without influence of topography)
65 ! index=1,nlev+1
66 REAL(wp), ALLOCATABLE :: vct_a(:)
67 ! The yac instance id used by the host model
68 INTEGER(C_INT) :: yac_instance_id
69 ! Host model version information
70 CHARACTER(LEN=:), ALLOCATABLE :: host_git_remote_url
71 CHARACTER(LEN=:), ALLOCATABLE :: host_git_branch
72 CHARACTER(LEN=:), ALLOCATABLE :: host_git_tag
73 CHARACTER(LEN=:), ALLOCATABLE :: host_revision
74 ! Information about the computation device (accelerator)
75 LOGICAL(C_BOOL) :: has_device
76 CHARACTER(LEN=:), ALLOCATABLE :: device_name
77 CHARACTER(LEN=:), ALLOCATABLE :: device_vendor
78 CHARACTER(LEN=:), ALLOCATABLE :: device_driver
80
83 ! number of local cells
84 INTEGER(C_INT), POINTER :: ncells => null()
85 ! number of global cells
86 INTEGER(C_INT), POINTER :: ncells_global => null()
87 ! number of blocks for cells
88 INTEGER(C_INT), POINTER :: nblks => null()
89
90 INTEGER(C_INT), POINTER :: max_connectivity => null()
91 ! number of edges connected to cell
92 ! index1=1,nproma, index2=1,nblks_c
93 INTEGER(C_INT), POINTER, CONTIGUOUS :: num_edges(:,:) => null()
94 ! lateral boundary distance indices
95 ! index1=1,nproma, index2=1,nblks_c
96 INTEGER(C_INT), POINTER :: refin_ctrl(:,:) => null()
97 ! list of start indices for each refin_ctrl level
98 ! index1=min_rlcell,max_rlcell (defined in mo_impl_constants)
99 INTEGER(C_INT), POINTER, CONTIGUOUS :: start_index(:) => null()
100 ! list of end indices for each refin_ctrl level
101 ! index1=min_rlcell,max_rlcell
102 INTEGER(C_INT), POINTER, CONTIGUOUS :: end_index(:) => null()
103 ! list of start block for each refin_ctrl level
104 ! index1=min_rlcell,max_rlcell
105 INTEGER(C_INT), POINTER, CONTIGUOUS :: start_block(:) => null()
106 ! list of end block for each refin_ctrl level
107 ! index1=min_rlcell,max_rlcell
108 INTEGER(C_INT), POINTER, CONTIGUOUS :: end_block(:) => null()
109 ! domain ID of child triangles:
110 ! index1=1,nproma, index2=1,nblks_c
111 INTEGER(C_INT), POINTER, CONTIGUOUS :: child_id(:,:) => null()
112 ! line index of parent triangle:
113 ! index1=1,nproma, index2=1,nblks_c
114 INTEGER(C_INT), POINTER, CONTIGUOUS :: parent_glb_idx(:,:) => null()
115 ! block index of parent triangle:
116 ! index1=1,nproma, index2=1,nblks_c
117 INTEGER(C_INT), POINTER, CONTIGUOUS :: parent_glb_blk(:,:) => null()
118 ! line indices and blocks of verts of triangle:
119 ! index1=1,nproma, index2=1,nblks_c, index3=1,3
120 INTEGER(C_INT), POINTER, CONTIGUOUS :: vertex_idx(:,:,:) => null()
121 INTEGER(C_INT), POINTER, CONTIGUOUS :: vertex_blk(:,:,:) => null()
122 ! line indices and blocks of neighbors of triangle:
123 ! index1=1,nproma, index2=1,nblks_c, index3=1,3
124 INTEGER(C_INT), POINTER, CONTIGUOUS :: neighbor_blk(:,:,:) => null()
125 INTEGER(C_INT), POINTER, CONTIGUOUS :: neighbor_idx(:,:,:) => null()
126 ! line indices and blocks of edges of triangle:
127 ! index1=1,nproma, index2=1,nblks_c, index3=1,3
128 INTEGER(C_INT), POINTER, CONTIGUOUS :: edge_idx(:,:,:) => null()
129 INTEGER(C_INT), POINTER, CONTIGUOUS :: edge_blk(:,:,:) => null()
130 ! longitude & latitude of centers of triangular cells
131 ! index1=nproma, index2=1,nblks_c
132 REAL(wp), ALLOCATABLE :: clon(:,:)
133 REAL(wp), ALLOCATABLE :: clat(:,:)
134 ! area of triangle
135 ! index1=nproma, index2=1,nblks_c
136 REAL(wp), POINTER, CONTIGUOUS :: area(:,:) => null()
137 ! geometrical height of half levels at cell centre
138 ! index1=1,nproma, index2=1,nlev+1, index3=1,nblks_c
139 REAL(wp), ALLOCATABLE :: hhl(:,:,:)
140
141 ! global cell indices
142 INTEGER(C_INT), POINTER, CONTIGUOUS :: glb_index(:) => null()
143 ! Domain decomposition flag:
144 ! decomp_domain==0: inner domain, decomp_domain>0: boundary, decomp_domain<0: undefined
145 ! For cells:
146 ! 0=owned, 1=shared edge with owned, 2=shared vertex with owned
147 ! index1=nproma, index2=1,nblks_c
148 INTEGER(C_INT), POINTER, CONTIGUOUS :: decomp_domain(:,:) => null()
150
153 ! number of local verts
154 INTEGER(C_INT), POINTER :: nverts => null()
155 ! number of global verts
156 INTEGER(C_INT), POINTER :: nverts_global => null()
157 ! number of blocks for verts
158 INTEGER(C_INT), POINTER :: nblks => null()
159 ! number of edges connected to vertex
160 ! index1=1,nproma, index2=1,nblks_v
161 INTEGER(C_INT), POINTER, CONTIGUOUS :: num_edges(:,:) => null()
162
163 ! lateral boundary distance indices
164 ! index1=1,nproma, index2=1,nblks_v
165 INTEGER(C_INT), POINTER :: refin_ctrl(:,:) => null()
166 ! list of start indices for each refin_ctrl level
167 ! index1=min_rlvert,max_rlvert (defined in mo_impl_constants), index2=n_childdom
168 INTEGER(C_INT), POINTER, CONTIGUOUS :: start_index(:) => null()
169 ! list of end indices for each refin_ctrl level
170 ! index1=min_rlvert,max_rlvert, index2=n_childdom
171 INTEGER(C_INT), POINTER, CONTIGUOUS :: end_index(:) => null()
172 ! list of start block for each refin_ctrl level
173 ! index1=min_rlvert,max_rlvert, index2=n_childdom
174 INTEGER(C_INT), POINTER, CONTIGUOUS :: start_block(:) => null()
175 ! list of end block for each refin_ctrl level
176 ! index1=min_rlvert,max_rlvert, index2=n_childdom
177 INTEGER(C_INT), POINTER, CONTIGUOUS :: end_block(:) => null()
178 ! block indices of neighbor vertices:
179 ! index1=1,nproma, index2=1,nblks_v, index3=1,6
180 INTEGER(C_INT), POINTER, CONTIGUOUS :: neighbor_blk(:,:,:) => null()
181 ! line indices of neighbor vertices:
182 ! index1=1,nproma, index2=1,nblks_v, index3=1,6
183 INTEGER(C_INT), POINTER, CONTIGUOUS :: neighbor_idx(:,:,:) => null()
184 ! line indices of cells around each vertex:
185 ! index1=1,nproma, index2=1,nblks_v, index3=1,6
186 INTEGER(C_INT), POINTER, CONTIGUOUS :: cell_idx(:,:,:) => null()
187 ! block indices of cells around each vertex:
188 ! index1=1,nproma, index2=1,nblks_v, index3=1,6
189 INTEGER(C_INT), POINTER, CONTIGUOUS :: cell_blk(:,:,:) => null()
190 ! line indices of edges around a vertex:
191 ! index1=1,nproma, index2=1,nblks_v, index3=1,6
192 INTEGER(C_INT), POINTER, CONTIGUOUS :: edge_idx(:,:,:) => null()
193 ! block indices of edges around a vertex:
194 ! index1=1,nproma, index2=1,nblks_v, index3=1,6
195 INTEGER(C_INT), POINTER, CONTIGUOUS :: edge_blk(:,:,:) => null()
196 ! longitude & latitude of vertex:
197 ! index1=1,nproma, index2=1,nblks_v
198 REAL(wp), ALLOCATABLE :: vlon(:,:)
199 REAL(wp), ALLOCATABLE :: vlat(:,:)
201
204 ! number of local edges
205 INTEGER(C_INT), POINTER :: nedges => null()
206 ! number of global edges
207 INTEGER(C_INT), POINTER :: nedges_global => null()
208 ! number of blocks for edges
209 INTEGER(C_INT), POINTER :: nblks => null()
210
211 ! lateral boundary distance indices
212 ! index1=1,nproma, index2=1,nblks_e
213 INTEGER(C_INT), POINTER :: refin_ctrl(:,:) => null()
214 ! list of start indices for each refin_ctrl level
215 ! index1=min_rledge,max_rledge (defined in mo_impl_constants), index2=n_childdom
216 INTEGER(C_INT), POINTER, CONTIGUOUS :: start_index(:) => null()
217 ! list of end indices for each refin_ctrl level
218 ! index1=min_rledge,max_rledge, index2=n_childdom
219 INTEGER(C_INT), POINTER, CONTIGUOUS :: end_index(:) => null()
220 ! list of start block for each refin_ctrl level
221 ! index1=min_rledge,max_rledge, index2=n_childdom
222 INTEGER(C_INT), POINTER, CONTIGUOUS :: start_block(:) => null()
223 ! list of end block for each refin_ctrl level
224 ! index1=min_rledge,max_rledge, index2=n_childdom
225 INTEGER(C_INT), POINTER, CONTIGUOUS :: end_block(:) => null()
226 ! domain ID of child edges:
227 ! index1=1,nproma, index2=1,nblks_e
228 INTEGER(C_INT), POINTER, CONTIGUOUS :: child_id(:,:) => null()
229 ! line index of parent edges:
230 ! index1=1,nproma, index2=1,nblks_e
231 INTEGER(C_INT), POINTER, CONTIGUOUS :: parent_glb_idx(:,:) => null()
232 ! block index of parent edges:
233 ! index1=1,nproma, index2=1,nblks_e
234 INTEGER(C_INT), POINTER, CONTIGUOUS :: parent_glb_blk(:,:) => null()
235 ! line indices of adjacent cells:
236 ! index1=1,nproma, index2=1,nblks_e, index3=1,2
237 INTEGER(C_INT), POINTER, CONTIGUOUS :: cell_idx(:,:,:) => null()
238 ! block indices of adjacent cells:
239 ! index1=1,nproma, index2=1,nblks_e, index3=1,2
240 INTEGER(C_INT), POINTER, CONTIGUOUS :: cell_blk(:,:,:) => null()
241 ! line indices of edge vertices:
242 ! vertex indices 3 and 4 are the non-edge-aligned vertices of cells 1 and 2
243 ! index1=1,nproma, index2=1,nblks_e, index3=1,4
244 INTEGER(C_INT), POINTER, CONTIGUOUS :: vertex_idx(:,:,:) => null()
245 ! block indices of edge vertices:
246 ! index1=1,nproma, index2=1,nblks_e, index3=1,4
247 INTEGER(C_INT), POINTER, CONTIGUOUS :: vertex_blk(:,:,:) => null()
248 ! longitude & latitude of edge midpoint
249 ! index=1,nproma, index2=1,nblks_e
250 REAL(wp), ALLOCATABLE :: elon(:,:)
251 REAL(wp), ALLOCATABLE :: elat(:,:)
253
257 ! horizontal grid filename
258 CHARACTER(LEN=:), POINTER :: grid_filename => null()
259 ! alphanumerical hash of grid
260 INTEGER(c_signed_char), POINTER :: grid_uuid(:) => null()
261 ! number of grid used (GRIB2 key)
262 ! index=1,max_dom
263 INTEGER(C_INT) :: number_of_grid_used
264 ! domain ID of current domain
265 INTEGER(C_INT), POINTER :: id => null()
266 ! domain id of parent
267 INTEGER(C_INT), POINTER :: parent_id => null()
268 ! ids for all child domains
269 INTEGER(C_INT), POINTER :: child_id(:) => null()
270 ! actual number of child domains
271 INTEGER(C_INT), POINTER :: n_childdom => null()
272 ! time at which execution of a (nested) model domain starts
273 REAL(wp) :: dom_start
274 ! time at which execution of a (nested) model domain terminates
275 REAL(wp) :: dom_end
276 ! no. of vertical model levels
277 INTEGER(C_INT), POINTER :: nlev => null()
278 ! half level of parent domain that coincides with upper margin of current
279 ! domain
280 INTEGER(C_INT), POINTER :: nshift => null()
281 ! total shift of model top w.r.t. global domain
282 INTEGER(C_INT), POINTER :: nshift_total => null()
283
288
292 CHARACTER(LEN=COMIN_MAX_DATETIME_STR_LEN) :: exp_start
293 CHARACTER(LEN=COMIN_MAX_DATETIME_STR_LEN) :: exp_stop
294 CHARACTER(LEN=COMIN_MAX_DATETIME_STR_LEN) :: run_start
295 CHARACTER(LEN=COMIN_MAX_DATETIME_STR_LEN) :: run_stop
297
298 INTERFACE
299 FUNCTION comin_glb2loc_index_lookup_fct(jg, glb) RESULT(loc)
300 INTEGER, INTENT(IN) :: jg
301 INTEGER, INTENT(IN) :: glb
302 INTEGER :: loc
304 END INTERFACE
305
306END MODULE comin_descrdata_types
integer, parameter, public wp
working precision
Vertex information for grid data structures.
Patch grid data structure, gathering information on grids.
Global data is invariant wrt the computational grid and never changed or updated.
Simulation status information, sim_current contains current time step.