1 !WRF:DRIVER_LAYER:DOMAIN_OBJECT
2 MODULE module_domain_type
4 USE module_driver_constants
10 INTEGER, PARAMETER :: MAX_TILING_ZONES = 20
12 ! needed to provide static definition of IO_MASK_SIZE
13 #include "../inc/streams.h"
15 CHARACTER (LEN=80) program_name
17 ! An entire domain. This contains multiple meteorological fields by having
18 ! arrays (such as "data_3d") of pointers for each field. Also inside each
19 ! domain is a link to a couple of other domains, one is just the
20 ! "next" domain that is to be stored, the other is the next domain which
21 ! happens to also be on the "same_level".
24 INTEGER :: stream(IO_MASK_SIZE)
28 TYPE(domain), POINTER :: ptr
32 INTEGER, POINTER :: i_start(:)
33 INTEGER, POINTER :: i_end(:)
34 INTEGER, POINTER :: j_start(:)
35 INTEGER, POINTER :: j_end(:)
42 CHARACTER*80 :: VarName
44 CHARACTER*1 :: ProcOrient ! 'X' 'Y' or ' ' (X, Y, or non-transposed)
45 CHARACTER*80 :: DataName
46 CHARACTER*80 :: Description
48 CHARACTER*10 :: MemoryOrder
49 CHARACTER*10 :: Stagger
50 CHARACTER*80 :: dimname1
51 CHARACTER*80 :: dimname2
52 CHARACTER*80 :: dimname3
53 LOGICAL :: scalar_array
54 LOGICAL :: boundary_array
56 ! definition of IO_MASK_SIZE comes from build and must be the same as
57 ! in both definitions of GET_MASK (frame/pack_utils.c and tools/misc.c)
58 INTEGER, DIMENSION(IO_MASK_SIZE) :: streams
59 INTEGER :: sd1,ed1,sd2,ed2,sd3,ed3
60 INTEGER :: sm1,em1,sm2,em2,sm3,em3
61 INTEGER :: sp1,ep1,sp2,ep2,sp3,ep3
62 CHARACTER*80 :: MemberOf ! only for 4+D tracer arrays
64 INTEGER :: Ntl ! 0 single; 1, 2, ... if multi
65 LOGICAL :: subgrid_x, subgrid_y ! true if has a subgrid dimension
67 INTEGER, POINTER :: num_table(:)
68 INTEGER, POINTER :: index_table(:,:)
69 LOGICAL, POINTER :: boundary_table(:,:)
70 CHARACTER*256, POINTER :: dname_table(:,:)
71 CHARACTER*256, POINTER :: desc_table(:,:)
72 CHARACTER*256, POINTER :: units_table(:,:)
73 TYPE(streamrec), POINTER :: streams_table(:,:)
75 TYPE ( fieldlist ) , POINTER :: next
77 REAL, POINTER :: rfield_0d
78 REAL, POINTER, DIMENSION(:) :: rfield_1d
79 REAL, POINTER, DIMENSION(:,:) :: rfield_2d
80 REAL, POINTER, DIMENSION(:,:,:) :: rfield_3d
81 REAL, POINTER, DIMENSION(:,:,:,:) :: rfield_4d
82 REAL, POINTER, DIMENSION(:,:,:,:,:) :: rfield_5d
83 REAL, POINTER, DIMENSION(:,:,:,:,:,:) :: rfield_6d
84 REAL, POINTER, DIMENSION(:,:,:,:,:,:,:) :: rfield_7d
86 DOUBLE PRECISION, POINTER :: dfield_0d
87 DOUBLE PRECISION, POINTER, DIMENSION(:) :: dfield_1d
88 DOUBLE PRECISION, POINTER, DIMENSION(:,:) :: dfield_2d
89 DOUBLE PRECISION, POINTER, DIMENSION(:,:,:) :: dfield_3d
90 DOUBLE PRECISION, POINTER, DIMENSION(:,:,:,:) :: dfield_4d
91 DOUBLE PRECISION, POINTER, DIMENSION(:,:,:,:,:) :: dfield_5d
92 DOUBLE PRECISION, POINTER, DIMENSION(:,:,:,:,:,:) :: dfield_6d
93 DOUBLE PRECISION, POINTER, DIMENSION(:,:,:,:,:,:,:) :: dfield_7d
95 INTEGER, POINTER :: ifield_0d
96 INTEGER, POINTER, DIMENSION(:) :: ifield_1d
97 INTEGER, POINTER, DIMENSION(:,:) :: ifield_2d
98 INTEGER, POINTER, DIMENSION(:,:,:) :: ifield_3d
99 INTEGER, POINTER, DIMENSION(:,:,:,:) :: ifield_4d
100 INTEGER, POINTER, DIMENSION(:,:,:,:,:) :: ifield_5d
101 INTEGER, POINTER, DIMENSION(:,:,:,:,:,:) :: ifield_6d
102 INTEGER, POINTER, DIMENSION(:,:,:,:,:,:,:) :: ifield_7d
104 LOGICAL, POINTER :: lfield_0d
105 LOGICAL, POINTER, DIMENSION(:) :: lfield_1d
106 LOGICAL, POINTER, DIMENSION(:,:) :: lfield_2d
107 ! save some space; you can still have these but will not be part of list
108 ! so cannot do i/o, etc on 3d or greater logical arrays
109 ! LOGICAL, POINTER, DIMENSION(:,:,:) :: lfield_3d
110 ! LOGICAL, POINTER, DIMENSION(:,:,:,:) :: lfield_4d
111 ! LOGICAL, POINTER, DIMENSION(:,:,:,:,:) :: lfield_5d
112 ! LOGICAL, POINTER, DIMENSION(:,:,:,:,:,:) :: lfield_6d
113 ! LOGICAL, POINTER, DIMENSION(:,:,:,:,:,:,:) :: lfield_7d
117 #include "state_subtypes.inc"
121 TYPE ( fieldlist ), POINTER :: head_statevars
122 TYPE ( fieldlist ), POINTER :: tail_statevars
124 ! SEE THE INCLUDE FILE FOR DEFINITIONS OF STATE FIELDS WITHIN THE DOMAIN DATA STRUCTURE
125 #include "state_struct.inc"
127 INTEGER :: comms( max_comms ), shift_x, shift_y
131 INTEGER :: communicator
132 INTEGER :: iocommunicator
133 INTEGER,POINTER :: mapping(:,:)
134 INTEGER,POINTER :: i_start(:),i_end(:)
135 INTEGER,POINTER :: j_start(:),j_end(:)
137 INTEGER :: num_tiles ! taken out of namelist 20000908
138 INTEGER :: num_tiles_x ! taken out of namelist 20000908
139 INTEGER :: num_tiles_y ! taken out of namelist 20000908
140 INTEGER :: num_tiles_spec ! place to store number of tiles computed from
141 ! externally specified params
143 TYPE(domain_ptr) , DIMENSION( : ) , POINTER :: parents
144 TYPE(domain_ptr) , DIMENSION( : ) , POINTER :: nests
145 TYPE(domain) , POINTER :: sibling ! overlapped domains at same lev
146 LOGICAL :: allocated ! has alloc_space_field been called on this domain?
147 TYPE(domain) , POINTER :: intermediate_grid
148 LOGICAL :: is_intermediate
149 INTEGER :: nids, nide, njds, njde ! for intermediate domains, carry around the nest dimensions
150 INTEGER :: num_parents, num_nests, num_siblings
151 INTEGER , DIMENSION( max_parents ) :: child_of_parent
152 INTEGER , DIMENSION( max_nests ) :: active
153 LOGICAL :: active_this_task
155 INTEGER , DIMENSION(MAX_STREAMS) :: nframes ! frames per outfile for history
158 TYPE(domain) , POINTER :: next
159 TYPE(domain) , POINTER :: same_level
161 LOGICAL , DIMENSION ( 4 ) :: bdy_mask ! which boundaries are on processor
162 LOGICAL :: interp_mp ! .true. = MOIST, SCALAR u,d,f,s will be called
163 LOGICAL :: first_force
167 INTEGER :: sd31, ed31, sd32, ed32, sd33, ed33, &
168 sd21, ed21, sd22, ed22, &
171 INTEGER :: sp31, ep31, sp32, ep32, sp33, ep33, &
172 sp21, ep21, sp22, ep22, &
174 sm31, em31, sm32, em32, sm33, em33, &
175 sm21, em21, sm22, em22, &
177 sp31x, ep31x, sp32x, ep32x, sp33x, ep33x, &
178 sp21x, ep21x, sp22x, ep22x, &
179 sm31x, em31x, sm32x, em32x, sm33x, em33x, &
180 sm21x, em21x, sm22x, em22x, &
181 sp31y, ep31y, sp32y, ep32y, sp33y, ep33y, &
182 sp21y, ep21y, sp22y, ep22y, &
183 sm31y, em31y, sm32y, em32y, sm33y, em33y, &
184 sm21y, em21y, sm22y, em22y
186 ! currently allocated domain dimesions
187 INTEGER :: alloced_sd31, alloced_ed31, &
188 alloced_sd32, alloced_ed32, &
189 alloced_sd33, alloced_ed33, &
190 alloced_sm31, alloced_em31, &
191 alloced_sm32, alloced_em32, &
192 alloced_sm33, alloced_em33, &
193 alloced_sm31x, alloced_em31x, &
194 alloced_sm32x, alloced_em32x, &
195 alloced_sm33x, alloced_em33x, &
196 alloced_sm31y, alloced_em31y, &
197 alloced_sm32y, alloced_em32y, &
198 alloced_sm33y, alloced_em33y
200 Type(WRFU_Clock), POINTER :: domain_clock
201 Type(WRFU_Time) :: start_subtime, stop_subtime
202 Type(WRFU_Time) :: this_bdy_time, next_bdy_time
203 Type(WRFU_Time) :: this_emi_time, next_emi_time
204 Type(WRFU_TimeInterval), DIMENSION(MAX_WRF_ALARMS) :: io_intervals
205 Type(WRFU_Alarm), POINTER :: alarms(:)
206 ! This awful hackery accounts for the fact that ESMF2.2.0 objects cannot tell
207 ! us if they have ever been created or not. So, we have to keep track of this
208 ! ourselves to avoid destroying an object that has never been created! Rip
209 ! this out once ESMF has useful introspection for creation...
210 LOGICAL :: domain_clock_created
211 LOGICAL, POINTER :: alarms_created(:)
213 ! Have clocks and times been initialized yet?
216 ! The following are used by the adaptive time step
217 ! T. Hutchinson, WSI 1/11/07
220 REAL :: last_max_vert_cfl
221 REAL :: last_max_horiz_cfl
223 REAL :: max_horiz_cfl
224 Type(WRFU_TimeInterval) :: last_dtInterval
226 ! Time series location information
227 INTEGER :: ntsloc, ntsloc_domain
228 INTEGER :: next_ts_time
229 INTEGER, POINTER, DIMENSION(:) :: itsloc, jtsloc, id_tsloc
230 REAL, POINTER, DIMENSION(:) :: lattsloc, lontsloc
231 CHARACTER (LEN=5), POINTER, DIMENSION(:) :: nametsloc
232 CHARACTER (LEN=25), POINTER, DIMENSION(:) :: desctsloc
233 CHARACTER (LEN=256), POINTER, DIMENSION(:) :: ts_filename
234 LOGICAL :: have_calculated_tslocs
235 LOGICAL :: have_displayed_alloc_stats ! used in module_alloc_space to display alloc stats; only do it once.
237 ! Track location information
238 CHARACTER (LEN=19), POINTER, DIMENSION(:) :: track_time_in
239 REAL, POINTER, DIMENSION(:) :: track_lat_in, track_lon_in
241 INTEGER :: track_loc, track_loc_domain
242 INTEGER :: track_next_time
243 INTEGER, POINTER, DIMENSION(:) :: track_i, track_j
245 CHARACTER (LEN=19), POINTER, DIMENSION(:) :: track_time_domain
246 REAL, POINTER, DIMENSION(:) :: track_lat_domain, track_lon_domain
248 LOGICAL :: track_have_calculated
249 LOGICAL :: track_have_input
251 ! 20121003 jm : for caching tiling
252 TYPE( tile_zone ) :: tile_zones(MAX_TILING_ZONES)
253 LOGICAL :: tiling_latch(MAX_TILING_ZONES)
256 END MODULE module_domain_type