regrid_sfc  1.13.0
regridStates.F90
Go to the documentation of this file.
1 
4 
8 
9  program regridstates
10 
11  use mpi_f08
12  use esmf
13 
14  use grids_io, only : setup_grid, &
15  write_from_fields, &
16  read_into_fields, &
17  n_tiles, &
18  grid_setup_type
19 
20  use utilities, only : error_handler
21 
22  implicit none
23 
24  integer, parameter :: max_vars = 10
25 
26  ! namelist inputs
27  character(len=15) :: variable_list(max_vars)
28  integer :: n_vars, n_tims, extrap_levs
29  integer :: time_list(10)
30  logical :: add_time_dim
31  real(esmf_kind_r8) :: missing_value ! value given to unmapped cells in the output grid
32 
33  type(grid_setup_type) :: grid_setup_in, grid_setup_out
34 
35  integer :: ierr, localpet, npets
36  integer :: v, t, srcterm
37 
38  character(100) :: fname_time
39 
40  type(esmf_vm) :: vm
41  type(esmf_grid), allocatable :: grid_in(:)
42  type(esmf_grid) :: grid_out
43  type(esmf_field), allocatable :: fields_in(:,:)
44  type(esmf_field), allocatable :: fields_out(:,:)
45  type(esmf_routehandle) :: regrid_route
46  real(esmf_kind_r8), pointer :: ptr_out(:,:)
47 
48  integer :: ut
49 
50  real :: t1, t2, t3, t4
51  character(len=3) :: tstr
52 
53  ! see README for details of namelist variables.
54  namelist /config/ n_vars, variable_list, missing_value, extrap_levs, time_list, add_time_dim
55 
56 ! INITIALIZE
57 !-------------------------------------------------------------------------
58 
59  call cpu_time(t1)
60 
61  call mpi_init(ierr)
62 
63  call esmf_initialize(rc=ierr)
64  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
65  call error_handler("INITIALIZING ESMF", ierr)
66 
67  call esmf_vmgetglobal(vm, rc=ierr)
68  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
69  call error_handler("IN VMGetGlobal", ierr)
70 
71  call esmf_vmget(vm, localpet=localpet, petcount=npets, rc=ierr)
72  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
73  call error_handler("IN VMGet", ierr)
74 
75 !-------------------------------------------------------------------------
76 ! RUN
77 !-------------------------------------------------------------------------
78 
79  print*,'** pets: local, total: ',localpet, npets
80 
81  ! checks
82 
83  if (mod(npets,n_tiles) /= 0) then
84  call error_handler("must run with a task count that is a multiple of 6", 1)
85  endif
86 
87 !------------------------
88 ! read in namelist
89 
90  ! defaults
91  missing_value=-999.
92  extrap_levs=2
93  time_list=-1
94 
95  open(newunit=ut, file='regrid.nml', iostat=ierr)
96  if (ierr /= 0) call error_handler("OPENING regrid NAMELIST.", ierr)
97  read(ut, nml=config, iostat=ierr)
98  if (ierr /= 0) call error_handler("OPENING config NAMELIST.", ierr)
99  call readin_setup(ut,"input",grid_setup_in)
100  call readin_setup(ut,"output",grid_setup_out)
101  close (ut)
102 
103 
104  n_tims = 0
105  do t=1,10
106  if (time_list(t) .lt. 0) exit
107  n_tims = n_tims + 1
108  enddo
109  if (n_tims < 1) then
110  call error_handler("n_tims < 1. must have at least one valid increment hour in time_list", 1)
111  endif
112 
113 !------------------------
114 ! Create esmf grid objects for input and output grids, and add land masks
115 
116 ! TO DO - can we make the number of tasks more flexible for fv3
117 
118  if (localpet==0) print*,'** Setting up grids'
119  allocate(grid_in(n_tims))
120  do t = 1, n_tims
121  if (grid_setup_in%mask_from_input) then
122  call setup_grid(localpet, npets, grid_setup_in, grid_in(t), time_list(t) )
123  else
124  call setup_grid(localpet, npets, grid_setup_in, grid_in(t))
125  endif
126  enddo
127  call setup_grid(localpet, npets, grid_setup_out, grid_out )
128 
129 !------------------------
130 ! Create input and output fields
131 
132  if (localpet==0) print*,'** Creating/Reading fields'
133 
134 ! input
135  allocate(fields_in(n_tims,n_vars))
136 
137  do t = 1, n_tims
138  do v = 1, n_vars
139 
140  fields_in(t,v) = esmf_fieldcreate(grid_in(t), &
141  typekind=esmf_typekind_r8, &
142  staggerloc=esmf_staggerloc_center, &
143  name="input for regridding", &
144  rc=ierr)
145 
146  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
147  call error_handler("in FieldCreate "//trim(variable_list(v)), ierr)
148  end do
149  end do
150 
151 ! output
152  allocate(fields_out(n_tims,n_vars))
153 
154  do t = 1, n_tims
155  do v = 1, n_vars
156 
157  fields_out(t,v) = esmf_fieldcreate(grid_out, &
158  typekind=esmf_typekind_r8, &
159  staggerloc=esmf_staggerloc_center, &
160  name="output of regridding", &
161  rc=ierr)
162  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
163  call error_handler("in FieldCreate, field_out", ierr)
164 
165 
166  ! set the default output value (for non-mapped cells)
167  call esmf_fieldget(fields_out(t,v), &
168  farrayptr=ptr_out, &
169  rc=ierr)
170  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
171  call error_handler("IN FieldGet", ierr)
172 
173  ptr_out=missing_value
174 
175  enddo
176  enddo
177 
178 !------------------------
179 ! read data into input fields
180 
181  do t = 1, n_tims
182 
183  write(tstr,"(I3.3)")time_list(t)
184  fname_time = trim(grid_setup_in%fname)//tstr//".nc"
185  write(6,*) 'reading into ', trim(fname_time)
186  call read_into_fields(localpet, grid_setup_in%ires, grid_setup_in%jres, &
187  trim(fname_time), trim(grid_setup_in%dir), &
188  grid_setup_in, n_vars, variable_list(1:n_vars), fields_in(t,:))
189  enddo
190 
191  call cpu_time(t2)
192 !------------------------
193 ! regrid the input fields to the output grid
194 
195  if (localpet==0) print*,'** Performing regridding'
196 
197  srcterm=1
198  ! get regriding route for a field (only uses the grid info in the field)
199  ! to turn off masking, remove [src/dstMaskVales] argumemnts
200  call esmf_fieldregridstore(srcfield=fields_in(1,1), srcmaskvalues=(/0/), &
201  dstfield=fields_out(1,1), dstmaskvalues=(/0/), &
202  ! allow unmapped grid cells, without returning error
203  unmappedaction=esmf_unmappedaction_ignore, &
204  polemethod=esmf_polemethod_allavg, &
205  ! fill un-mapped grid cells with a neighbour
206  extrapmethod=esmf_extrapmethod_creep, &
207  ! number of "levels" of neighbours to search for a value
208  extrapnumlevels=extrap_levs, &
209  ! needed for reproducibility
210  ! (combined with ESMF_TERMORDER_SRCSEQ below)
211  srctermprocessing=srcterm, &
212  routehandle=regrid_route, &
213  ! use bilinear interp (slightly better results than PATCH)
214  regridmethod=esmf_regridmethod_bilinear, rc=ierr)
215  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
216  call error_handler("IN FieldRegridStore", ierr)
217 
218 ! do the re-gridding
219 
220  call cpu_time(t3)
221 
222  do t=1, n_tims
223  do v=1, n_vars
224  call esmf_fieldregrid(fields_in(t,v), &
225  fields_out(t,v), &
226  routehandle=regrid_route, &
227  zeroregion=esmf_region_select, & ! initialize output with missing_value
228  termorderflag=esmf_termorder_srcseq, rc=ierr)
229  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
230  call error_handler("IN FieldRegrid", ierr)
231  enddo
232  enddo
233 
234 ! TO-DO: terrain-correct temperatures (all layers?)
235 
236 ! write out fields on destination grid. All times into same file.
237 
238  if (localpet==0) print*,'** Writing out regridded fields'
239 
240  call write_from_fields(localpet, grid_setup_out%ires, grid_setup_out%jres, &
241  trim(grid_setup_out%fname), trim(grid_setup_out%dir), &
242  n_vars, n_tims, variable_list(1:n_vars), fields_out, add_time_dim)
243 
244 
245 ! clean up
246 
247  call esmf_fieldregridrelease(routehandle=regrid_route, rc=ierr)
248  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
249  call error_handler("IN FieldRegridRelease", ierr)
250 
251  do t = 1, n_tims
252  do v = 1, n_vars
253  call esmf_fielddestroy(fields_in(t,v),rc=ierr)
254  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
255  call error_handler("DESTROYING FIELD", ierr)
256 
257  call esmf_fielddestroy(fields_out(t,v),rc=ierr)
258  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
259  call error_handler("DESTROYING FIELD", ierr)
260  enddo
261 
262  call esmf_griddestroy(grid_in(t), rc=ierr)
263  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
264  call error_handler("DESTROYING GRID", ierr)
265  enddo
266 
267  call esmf_griddestroy(grid_out,rc=ierr)
268  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
269  call error_handler("DESTROYING GRID", ierr)
270 
271 !-------------------------------------------------------------------------
272 ! FINALIZE
273 !-------------------------------------------------------------------------
274 
275  call esmf_finalize(endflag=esmf_end_keepmpi, rc=ierr)
276  call mpi_finalize(ierr)
277 
278  call cpu_time(t4)
279  if (localpet==0) print*, '** time in tile2tile', t4 - t1
280  if (localpet==0) print*, '** time in RegridStore', t3 - t2
281 
282  print*,"** DONE.", localpet
283 
284  end program regridstates
subroutine readin_setup(unt, namel, grid_setup)
Subroutine to read in namelists, and convert values into setupgrid.