13 subroutine interp(localpet, method, input_file)
24 character(len=*),
intent(in) :: input_file
26 integer :: rc, localpet
27 integer :: i, j, ij, tile, n, ncid, status
28 integer :: l(1), u(1), t
29 integer :: clb_mdl(2), cub_mdl(2)
30 integer :: varid, record
31 integer :: tile_num, pt_loc_this_tile
32 integer :: isrctermprocessing
34 integer(esmf_kind_i4),
allocatable :: mask_mdl_one_tile(:,:)
35 integer(esmf_kind_i4),
pointer :: unmapped_ptr(:)
37 real(esmf_kind_r4),
pointer :: data_mdl_ptr(:,:)
38 real(esmf_kind_r4),
pointer :: data_src_ptr(:,:)
39 real(esmf_kind_r4),
allocatable :: data_src_global(:,:)
40 real(esmf_kind_r4),
allocatable :: data_mdl_one_tile(:,:)
41 real(esmf_kind_r4),
allocatable :: vegt_mdl_one_tile(:,:)
42 real(esmf_kind_r4),
allocatable :: lat_mdl_one_tile(:,:)
43 real(esmf_kind_r4),
allocatable :: lon_mdl_one_tile(:,:)
45 type(esmf_regridmethod_flag),
intent(in) :: method
46 type(esmf_field) :: data_field_src
47 type(esmf_routehandle) :: regrid_data
48 type(esmf_polemethod_flag) :: pole
50 print*,
"- CALL FieldCreate FOR SOURCE GRID DATA." 51 data_field_src = esmf_fieldcreate(
grid_src, &
52 typekind=esmf_typekind_r4, &
53 indexflag=esmf_index_global, &
54 staggerloc=esmf_staggerloc_center, &
57 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
60 print*,
"- CALL FieldGet FOR SOURCE GRID DATA." 62 call esmf_fieldget(data_field_src, &
63 farrayptr=data_src_ptr, &
65 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
68 print*,
"- CALL FieldGet FOR MODEL GRID DATA." 71 farrayptr=data_mdl_ptr, &
72 computationallbound=clb_mdl, &
73 computationalubound=cub_mdl, &
75 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
78 if (localpet == 0)
then 81 allocate(data_src_global(0,0))
84 print*,
'- OPEN SOURCE FILE ', trim(input_file)
85 status = nf90_open(input_file, nf90_nowrite, ncid)
86 call netcdf_err(status,
"IN ROUTINE INTERP OPENING SOURCE FILE")
88 if (localpet == 0)
then 94 allocate(data_mdl_one_tile(0,0))
95 allocate(mask_mdl_one_tile(0,0))
96 allocate(lat_mdl_one_tile(0,0))
97 allocate(lon_mdl_one_tile(0,0))
108 if (localpet == 0)
then 109 status = nf90_inq_varid(ncid,
field_names(n), varid)
110 call netcdf_err(status,
"IN ROUTINE INTERP READING FIELD ID")
111 status = nf90_get_var(ncid, varid, data_src_global, start=(/1,1,t/), count=(/
i_src,
j_src,1/))
112 call netcdf_err(status,
"IN ROUTINE INTERP READING FIELD")
115 print*,
"- CALL FieldScatter FOR SOURCE GRID DATA." 116 call esmf_fieldscatter(data_field_src, data_src_global, rootpet=0, rc=rc)
117 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
120 isrctermprocessing = 1
122 if (record == 1)
then 124 if (method == esmf_regridmethod_bilinear)
then 125 pole = esmf_polemethod_allavg
127 pole = esmf_polemethod_none
130 print*,
"- CALL FieldRegridStore." 131 nullify(unmapped_ptr)
132 call esmf_fieldregridstore(data_field_src, &
134 srcmaskvalues=(/0/), &
135 dstmaskvalues=(/0/), &
137 unmappedaction=esmf_unmappedaction_ignore, &
138 normtype=esmf_normtype_fracarea, &
139 srctermprocessing=isrctermprocessing, &
140 routehandle=regrid_data, &
141 regridmethod=method, &
142 unmappeddstlist=unmapped_ptr, &
144 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
149 print*,
"- CALL Field_Regrid." 150 call esmf_fieldregrid(data_field_src, &
152 routehandle=regrid_data, &
153 termorderflag=esmf_termorder_srcseq, &
155 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
173 l = lbound(unmapped_ptr)
174 u = ubound(unmapped_ptr)
177 tile_num = ((unmapped_ptr(ij)-1) / (
i_mdl*
j_mdl))
178 pt_loc_this_tile = unmapped_ptr(ij) - (tile_num *
i_mdl *
j_mdl)
181 j = (pt_loc_this_tile - 1) /
i_mdl + 1
182 i = mod(pt_loc_this_tile,
i_mdl)
184 data_mdl_ptr(i,j) = -9999.9
191 case (
'substrate_temperature',
'vegetation_greenness',
'leaf_area_index',
'slope_type',
'soil_type',
'soil_color')
192 if (localpet == 0)
then 195 allocate(vegt_mdl_one_tile(0,0))
201 print*,
"- CALL FieldGather FOR MODEL LATITUDE." 202 call esmf_fieldgather(
latitude_field_mdl, lat_mdl_one_tile, rootpet=0, tile=tile, rc=rc)
203 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
206 print*,
"- CALL FieldGather FOR MODEL LONGITUDE." 208 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
211 print*,
"- CALL FieldGather FOR MODEL GRID DATA." 212 call esmf_fieldgather(
data_field_mdl, data_mdl_one_tile, rootpet=0, tile=tile, rc=rc)
213 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
216 print*,
"- CALL FieldGather FOR MODEL GRID LAND MASK." 217 call esmf_fieldgather(
mask_field_mdl, mask_mdl_one_tile, rootpet=0, tile=tile, rc=rc)
218 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
222 case (
'substrate_temperature',
'vegetation_greenness',
'leaf_area_index',
'slope_type',
'soil_type',
'soil_color')
223 print*,
"- CALL FieldGather FOR MODEL GRID VEG TYPE." 224 call esmf_fieldgather(
vegt_field_mdl, vegt_mdl_one_tile, rootpet=0, tile=tile, rc=rc)
225 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
229 if (localpet == 0)
then 230 print*,
'- CALL SEARCH FOR TILE ',tile
233 case (
'substrate_temperature',
'vegetation_greenness',
'leaf_area_index',
'slope_type',
'soil_type',
'soil_color')
236 where(mask_mdl_one_tile == 0) data_mdl_one_tile =
missing 237 call output (data_mdl_one_tile, lat_mdl_one_tile, lon_mdl_one_tile,
i_mdl,
j_mdl, tile, record, t, n)
241 print*,
"- CALL FieldScatter FOR MODEL GRID VEGETATION TYPE." 242 call esmf_fieldscatter(
vegt_field_mdl, data_mdl_one_tile, rootpet=0, tile=tile, rc=rc)
243 if(esmf_logfounderror(rctocheck=rc,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
249 if (
allocated(vegt_mdl_one_tile))
deallocate(vegt_mdl_one_tile)
254 status=nf90_close(ncid)
256 deallocate(data_mdl_one_tile, mask_mdl_one_tile)
257 deallocate(data_src_global, lat_mdl_one_tile, lon_mdl_one_tile)
259 print*,
"- CALL FieldRegridRelease." 260 call esmf_fieldregridrelease(routehandle=regrid_data, rc=rc)
262 print*,
"- CALL FieldDestroy." 263 call esmf_fielddestroy(data_field_src, rc=rc)
284 character(len=*),
intent(in) :: field_ch
286 integer,
intent(in) :: idim, jdim
288 real(esmf_kind_i4),
intent(in) :: vegt(idim,jdim)
289 real(esmf_kind_r4),
intent(inout) :: field(idim,jdim)
291 integer,
parameter :: landice=15
293 integer :: i, j, ierr
295 real :: landice_value
297 select case (field_ch)
298 case (
'substrate_temperature')
299 landice_value = 273.15
302 if (nint(vegt(i,j)) == landice)
then 303 field(i,j) = min(field(i,j), landice_value)
307 case (
'vegetation_greenness')
311 if (nint(vegt(i,j)) == landice)
then 312 field(i,j) = landice_value
316 case (
'leaf_area_index')
320 if (nint(vegt(i,j)) == landice)
then 321 field(i,j) = landice_value
329 if (nint(vegt(i,j)) == landice)
then 330 field(i,j) = landice_value
332 if (nint(field(i,j)) == nint(landice_value)) field(i,j) = 2.0
340 if (nint(vegt(i,j)) == landice)
then 341 field(i,j) = landice_value
343 if (nint(field(i,j)) == nint(landice_value)) field(i,j) = 6.0
351 if (nint(vegt(i,j)) == landice)
then 352 field(i,j) = landice_value
357 print*,
'- FATAL ERROR IN ROUTINE ADJUST_FOR_LANDICE. UNIDENTIFIED FIELD : ', field_ch
358 call mpi_abort(mpi_comm_world, 57, ierr)
integer, public j_src
j dimension of the source grid.
type(esmf_field), public vegt_field_mdl
ESMF field object that holds the vegetation type on the model grid.
subroutine search(field, mask, idim, jdim, tile, field_name)
Replace undefined values on the model grid with a valid value at a nearby neighbor.
subroutine output(data_one_tile, lat_one_tile, lon_one_tile, i_mdl, j_mdl, tile, record, time, field_idx)
Output model data for a single tile and a single record in netcdf format.
character(len=50), dimension(:), allocatable, public field_names
Names of fields to be processed.
real(kind=4), public missing
Value assigned to undefined points (i.e., ocean points for a land field).
type(esmf_field), public longitude_field_mdl
ESMF field object that holds the model grid longitude.
This module defines the model grid.
integer, public j_mdl
j dimension of model tile.
Read grid specs, date information and land/sea mask for the source data that will be interpolated to ...
integer, public num_time_recs
Number of time records.
subroutine adjust_for_landice(field, vegt, idim, jdim, field_ch)
Ensure consistent fields at land ice points.
type(esmf_field), public latitude_field_mdl
ESMF field object that holds the model grid latitude.
integer, public i_mdl
i dimension of model tile.
type(esmf_field), public mask_field_mdl
ESMF field object that holds the model land mask.
type(esmf_field), public data_field_mdl
ESMF field object that holds the data interpolated to model grid.
integer, public num_tiles
Total number of model grid tiles.
integer, public i_src
i dimension of the source grid.
subroutine, public error_handler(string, rc)
Handle errors.
subroutine interp(localpet, method, input_file)
Read the input source data and interpolate it to the model grid.
integer, public num_fields
Number of fields in the file.
subroutine, public netcdf_err(err, string)
Handle netCDF error codes.
type(esmf_grid), public grid_src
ESMF grid object for the source grid.