21 integer :: i_thomp_mp_climo
23 integer :: j_thomp_mp_climo
25 integer,
public :: lev_thomp_mp_climo
28 type(esmf_grid
) :: thomp_mp_climo_grid
31 type(esmf_field
),
public :: qnifa_climo_input_grid
34 type(esmf_field
),
public :: qnwfa_climo_input_grid
37 type(esmf_field
),
public :: thomp_pres_climo_input_grid
54 integer :: error, ncid, rc, clb(2), cub(2)
55 integer :: i, j, localpet, npets, id_var
56 integer :: jda(8), jdow, jdoy, jday, id_dim
57 integer :: mm, mmm, mmp, mon1, mon2
59 real(esmf_kind_r8),
allocatable :: dummy3d(:,:,:)
60 real(esmf_kind_r8),
allocatable :: dummy3d_mon1(:,:,:)
61 real(esmf_kind_r8),
allocatable :: dummy3d_mon2(:,:,:)
62 real(esmf_kind_r8),
pointer :: lat_ptr(:,:), lon_ptr(:,:)
63 real(esmf_kind_r8),
allocatable :: lons(:), lats(:)
64 real :: rjday, dayhf(13), wei1m, wei2m
68 type(esmf_polekind_flag
) :: polekindflag(2)
70 data dayhf/ 15.5, 45.0, 74.5,105.0,135.5,166.0, &
71 196.5,227.5,258.0,288.5,319.0,349.5,380.5/
77 print*,
"- READ THOMP_MP_CLIMO_FILE: ", trim(thomp_mp_climo_file)
78 error=nf90_open(trim(thomp_mp_climo_file),nf90_nowrite,ncid)
79 call
netcdf_err(error,
'opening: '//trim(thomp_mp_climo_file) )
81 error=nf90_inq_dimid(ncid,
'lat', id_dim)
83 error=nf90_inquire_dimension(ncid,id_dim,len=j_thomp_mp_climo)
86 error=nf90_inq_dimid(ncid,
'lon', id_dim)
88 error=nf90_inquire_dimension(ncid,id_dim,len=i_thomp_mp_climo)
91 error=nf90_inq_dimid(ncid,
'plev', id_dim)
93 error=nf90_inquire_dimension(ncid,id_dim,len=lev_thomp_mp_climo)
96 allocate(lons(i_thomp_mp_climo))
97 allocate(lats(j_thomp_mp_climo))
98 error=nf90_inq_varid(ncid,
'lon', id_var)
99 call
netcdf_err(error,
'reading lon field id' )
100 error=nf90_get_var(ncid, id_var, lons)
101 call
netcdf_err(error,
'reading grid longitude' )
102 error=nf90_inq_varid(ncid,
'lat', id_var)
103 call
netcdf_err(error,
'reading lat field id' )
104 error=nf90_get_var(ncid, id_var, lats)
105 call
netcdf_err(error,
'reading grid latitude' )
111 print*,
"- CALL VMGetGlobal"
112 call esmf_vmgetglobal(vm, rc=rc)
113 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
116 print*,
"- CALL VMGet"
117 call esmf_vmget(vm, localpet=localpet, petcount=npets, rc=rc)
118 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
121 polekindflag(1:2) = esmf_polekind_monopole
123 print*,
"- CALL GridCreate1PeriDim FOR THOMP MP CLIMO GRID."
124 thomp_mp_climo_grid = esmf_gridcreate1peridim(minindex=(/1,1/), &
125 maxindex=(/i_thomp_mp_climo,j_thomp_mp_climo/), &
126 polekindflag=polekindflag, &
129 coordsys=esmf_coordsys_sph_deg, &
130 regdecomp=(/1,npets/), &
131 indexflag=esmf_index_global, rc=rc)
132 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
135 print*,
"- CALL GridAddCoord FOR THOMP MP CLIMO GRID."
136 call esmf_gridaddcoord(thomp_mp_climo_grid, &
137 staggerloc=esmf_staggerloc_center, rc=rc)
138 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
145 print*,
"- CALL GridGetCoord FOR INPUT GRID X-COORD."
147 call esmf_gridgetcoord(thomp_mp_climo_grid, &
148 staggerloc=esmf_staggerloc_center, &
150 farrayptr=lon_ptr, rc=rc)
151 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
154 print*,
"- CALL GridGetCoord FOR INPUT GRID Y-COORD."
156 call esmf_gridgetcoord(thomp_mp_climo_grid, &
157 staggerloc=esmf_staggerloc_center, &
159 computationallbound=clb, &
160 computationalubound=cub, &
161 farrayptr=lat_ptr, rc=rc)
162 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
165 do i = clb(1), cub(1)
166 lon_ptr(i,:) = lons(i)
169 do j = clb(2), cub(2)
170 lat_ptr(:,j) = lats(j)
177 print*,
"- CALL FieldCreate FOR QNIFA INPUT CLIMO."
178 qnifa_climo_input_grid = esmf_fieldcreate(thomp_mp_climo_grid, &
179 typekind=esmf_typekind_r8, &
180 staggerloc=esmf_staggerloc_center, &
181 ungriddedlbound=(/1/), &
182 ungriddedubound=(/lev_thomp_mp_climo/), rc=rc)
183 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
186 print*,
"- CALL FieldCreate FOR QNWFA INPUT CLIMO."
187 qnwfa_climo_input_grid = esmf_fieldcreate(thomp_mp_climo_grid, &
188 typekind=esmf_typekind_r8, &
189 staggerloc=esmf_staggerloc_center, &
190 ungriddedlbound=(/1/), &
191 ungriddedubound=(/lev_thomp_mp_climo/), rc=rc)
192 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
195 print*,
"- CALL FieldCreate FOR THOMP PRESS CLIMO."
196 thomp_pres_climo_input_grid = esmf_fieldcreate(thomp_mp_climo_grid, &
197 typekind=esmf_typekind_r8, &
198 staggerloc=esmf_staggerloc_center, &
199 ungriddedlbound=(/1/), &
200 ungriddedubound=(/lev_thomp_mp_climo/), rc=rc)
201 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
211 if (cycle_mon == 2 .and. cycle_day == 29)
then
223 call w3doxdat(jda,jdow,jdoy,jday)
224 rjday = float(jdoy) + float(jda(5)) / 24.
225 if(rjday < dayhf(1)) rjday = rjday + 365.
230 if(rjday >= dayhf(mmm) .and. rjday < dayhf(mmp))
then
237 wei1m = (dayhf(mon2)-rjday)/(dayhf(mon2)-dayhf(mon1))
242 print*,
"- BOUNDING MONTHS AND INTERPOLATION WEIGHTS: ", mon1, wei1m, mon2, wei2m
249 if (localpet == 0)
then
250 allocate(dummy3d(i_thomp_mp_climo, j_thomp_mp_climo, lev_thomp_mp_climo))
252 allocate(dummy3d_mon1(i_thomp_mp_climo, j_thomp_mp_climo, lev_thomp_mp_climo))
254 allocate(dummy3d_mon2(i_thomp_mp_climo, j_thomp_mp_climo, lev_thomp_mp_climo))
257 allocate(dummy3d(0,0,0))
258 allocate(dummy3d_mon1(0,0,0))
259 allocate(dummy3d_mon2(0,0,0))
262 if (localpet == 0)
then
263 print*,
"- READ QNIFA FOR BOUNDING MONTH 1"
264 error=nf90_inq_varid(ncid,
'nifa', id_var)
265 call
netcdf_err(error,
'reading nifa field id' )
266 error=nf90_get_var(ncid, id_var, dummy3d_mon1, start=(/1,1,1,mon1/), &
267 count=(/i_thomp_mp_climo,j_thomp_mp_climo,lev_thomp_mp_climo,1/) )
268 call
netcdf_err(error,
'reading nifa month1 field' )
269 print*,
"- READ QNIFA FOR BOUNDING MONTH 2"
270 error=nf90_get_var(ncid, id_var, dummy3d_mon2, start=(/1,1,1,mon2/), &
271 count=(/i_thomp_mp_climo,j_thomp_mp_climo,lev_thomp_mp_climo,1/) )
272 call
netcdf_err(error,
'reading nifa month2 field' )
273 dummy3d(:,:,:) = wei1m * dummy3d_mon1 + wei2m * dummy3d_mon2
276 print*,
"- CALL FieldScatter FOR qnifa input climo."
277 call esmf_fieldscatter(qnifa_climo_input_grid, dummy3d, rootpet=0, rc=rc)
278 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
281 if (localpet == 0)
then
282 print*,
"- READ QNWFA FOR BOUNDING MONTH 1"
283 error=nf90_inq_varid(ncid,
'nwfa', id_var)
284 call
netcdf_err(error,
'reading nwfa field id' )
285 error=nf90_get_var(ncid, id_var, dummy3d_mon1, start=(/1,1,1,mon1/), &
286 count=(/i_thomp_mp_climo,j_thomp_mp_climo,lev_thomp_mp_climo,1/) )
287 call
netcdf_err(error,
'reading nwfa month1 field' )
288 print*,
"- READ QNWFA FOR BOUNDING MONTH 2"
289 error=nf90_get_var(ncid, id_var, dummy3d_mon2, start=(/1,1,1,mon2/), &
290 count=(/i_thomp_mp_climo,j_thomp_mp_climo,lev_thomp_mp_climo,1/) )
291 call
netcdf_err(error,
'reading nwfa month2 field' )
292 dummy3d(:,:,:) = wei1m * dummy3d_mon1 + wei2m * dummy3d_mon2
295 print*,
"- CALL FieldScatter FOR qnwfa input climo."
296 call esmf_fieldscatter(qnwfa_climo_input_grid, dummy3d, rootpet=0, rc=rc)
297 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
300 if (localpet == 0)
then
301 print*,
"- READ PRESSURE FOR BOUNDING MONTH 1"
302 error=nf90_inq_varid(ncid,
'prs', id_var)
303 call
netcdf_err(error,
'reading prs field id' )
304 error=nf90_get_var(ncid, id_var, dummy3d_mon1, start=(/1,1,1,mon1/), &
305 count=(/i_thomp_mp_climo,j_thomp_mp_climo,lev_thomp_mp_climo,1/) )
306 call
netcdf_err(error,
'reading prs month1 field' )
307 print*,
"- READ PRESSURE FOR BOUNDING MONTH 2"
308 error=nf90_get_var(ncid, id_var, dummy3d_mon2, start=(/1,1,1,mon2/), &
309 count=(/i_thomp_mp_climo,j_thomp_mp_climo,lev_thomp_mp_climo,1/) )
310 call
netcdf_err(error,
'reading prs month2 field' )
311 dummy3d(:,:,:) = wei1m * dummy3d_mon1 + wei2m * dummy3d_mon2
314 print*,
"- CALL FieldScatter FOR thomp press."
315 call esmf_fieldscatter(thomp_pres_climo_input_grid, dummy3d, rootpet=0, rc=rc)
316 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
319 error=nf90_close(ncid)
321 deallocate(lons, lats, dummy3d, dummy3d_mon1, dummy3d_mon2)
334 call esmf_griddestroy(thomp_mp_climo_grid, rc=rc)
335 call esmf_fielddestroy(thomp_pres_climo_input_grid, rc=rc)
336 call esmf_fielddestroy(qnifa_climo_input_grid, rc=rc)
337 call esmf_fielddestroy(qnwfa_climo_input_grid, rc=rc)
subroutine netcdf_err(err, string)
Error handler for netcdf.
subroutine, public cleanup_thomp_mp_climo_input_data
Free up memory associated with this module.
Module to read the Thompson climatological MP data file and set up the associated esmf field and grid...
subroutine error_handler(string, rc)
General error handler.
subroutine, public read_thomp_mp_climo_data
Read Thompson climatological MP data file and time interpolate data to current cycle time...
This module contains code to read the setup namelist file, handle the varmap file for GRIB2 data...