FV3-JEDI
fv3jedi_io_gfs_mod.f90
Go to the documentation of this file.
2 
3 ! iso
4 use iso_c_binding
5 
6 ! oops
7 use datetime_mod
8 use string_utils, only: swap_name_member
9 
10 ! fckit
11 use fckit_configuration_module, only: fckit_configuration
12 
13 ! fms
14 use fms_io_mod, only: restart_file_type, register_restart_field
15 use fms_io_mod, only: free_restart_type, restore_state, save_restart
16 use mpp_domains_mod, only: east, north, center
17 use mpp_mod, only: mpp_pe, mpp_root_pe
18 
19 ! fv3jedi
25 
26 ! --------------------------------------------------------------------------------------------------
27 
28 implicit none
29 private
30 public fv3jedi_io_gfs
31 
32 ! If adding a new file it is added here and object and config in setup
33 integer, parameter :: numfiles = 9
34 
36  character(len=128) :: datapath
37  character(len=128) :: filenames(numfiles)
38  character(len=128) :: filenames_conf(numfiles)
39  integer :: index_core = 1 ! Files like fv_core.res.tile<n>.nc
40  integer :: index_trcr = 2 ! Files like fv_tracer.res.tile<n>.nc
41  integer :: index_sfcd = 3 ! Files like sfc_data.tile<n>.nc
42  integer :: index_sfcw = 4 ! Files like fv_srf_wnd.res.tile<n>.nc
43  integer :: index_cplr = 5 ! Files like coupler.res
44  integer :: index_spec = 6 ! Files like grid_spec.res.tile<n>.nc
45  integer :: index_phys = 7 ! Files like phy_data.tile<n>.nc
46  integer :: index_orog = 8 ! Files like C<npx-1>_oro_data.tile<n>.nc
47  integer :: index_cold = 9 ! Files like gfs_data.tile<n>.nc
48  logical :: ps_in_file
49  logical :: skip_coupler
50  logical :: prepend_date
51  contains
52  procedure :: setup_conf ! Setup for when config is available, called from constructors
53  procedure :: setup_date ! Setup when datetime is available
54  procedure :: read_meta
55  procedure :: read_fields
56  procedure :: write
57  final :: dummy_final
58 end type fv3jedi_io_gfs
59 
60 ! --------------------------------------------------------------------------------------------------
61 
62 contains
63 
64 ! --------------------------------------------------------------------------------------------------
65 
66 subroutine setup_conf(self, f_conf)
67 
68 class(fv3jedi_io_gfs), intent(inout) :: self
69 type(fckit_configuration), intent(in) :: f_conf
70 
71 integer :: n
72 character(len=:), allocatable :: str
73 character(len=13) :: fileconf(numfiles)
74 
75 ! Get path to files
76 ! -----------------
77 call f_conf%get_or_die("datapath",str)
78 if (len(str) > 128) &
79  call abor1_ftn('fv3jedi_io_gfs_mod.setup: datapath too long, max FMS char length= 128')
80 
81 ! For ensemble methods switch out member template
82 ! -----------------------------------------------
83 call swap_name_member(f_conf, str)
84 
85 self%datapath = str
86 deallocate(str)
87 
88 
89 !Set default filenames
90 !---------------------
91 self%filenames_conf(self%index_core) = 'fv_core.res.nc'
92 self%filenames_conf(self%index_trcr) = 'fv_tracer.res.nc'
93 self%filenames_conf(self%index_sfcd) = 'sfc_data.nc'
94 self%filenames_conf(self%index_sfcw) = 'srf_wnd.nc'
95 self%filenames_conf(self%index_cplr) = 'coupler.res'
96 self%filenames_conf(self%index_spec) = 'null'
97 self%filenames_conf(self%index_phys) = 'phy_data.nc'
98 self%filenames_conf(self%index_orog) = 'oro_data.nc'
99 self%filenames_conf(self%index_cold) = 'gfs_data.nc'
100 
101 ! Configuration to parse for the filenames
102 ! ----------------------------------------
103 fileconf(self%index_core) = "filename_core"
104 fileconf(self%index_trcr) = "filename_trcr"
105 fileconf(self%index_sfcd) = "filename_sfcd"
106 fileconf(self%index_sfcw) = "filename_sfcw"
107 fileconf(self%index_cplr) = "filename_cplr"
108 fileconf(self%index_spec) = "filename_spec"
109 fileconf(self%index_phys) = "filename_phys"
110 fileconf(self%index_orog) = "filename_orog"
111 fileconf(self%index_cold) = "filename_cold"
112 
113 
114 ! Set files names based on user input
115 ! -----------------------------------
116 do n = 1, numfiles
117 
118  ! Retrieve user input filenames if available
119  if (f_conf%has(fileconf(n))) then
120  call f_conf%get_or_die(fileconf(n),str)
121  if (len(str) > 128) call abor1_ftn("fv3jedi_io_gfs_mod.setup: "//fileconf(n)//&
122  " too long, max FMS char length= 128")
123  self%filenames_conf(n) = str
124  deallocate(str)
125  endif
126 
127  ! Config filenames to filenames
128  self%filenames(n) = trim(self%filenames_conf(n))
129 
130 enddo
131 
132 ! Option to retrieve Ps from delp
133 ! -------------------------------
134 self%ps_in_file = .false.
135 if (f_conf%has("psinfile")) then
136  call f_conf%get_or_die("psinfile",self%ps_in_file)
137 endif
138 
139 ! Option to skip read/write of coupler file
140 ! -----------------------------------------
141 self%skip_coupler = .false.
142 if (f_conf%has("skip coupler file")) then
143  call f_conf%get_or_die("skip coupler file",self%skip_coupler)
144 endif
145 
146 ! Option to turn off prepending file with date
147 ! --------------------------------------------
148 if (.not.f_conf%get("prepend files with date", self%prepend_date)) then
149  self%prepend_date = .true.
150 endif
151 
152 end subroutine setup_conf
153 
154 ! --------------------------------------------------------------------------------------------------
155 
156 subroutine setup_date(self, vdate)
157 
158 class(fv3jedi_io_gfs), intent(inout) :: self
159 type(datetime), intent(in) :: vdate
160 
161 integer :: n
162 character(len=4) :: yyyy
163 character(len=2) :: mm, dd, hh, min, ss
164 
165 ! Datetime to strings
166 ! -------------------
167 call vdate_to_datestring(vdate, yyyy=yyyy, mm=mm, dd=dd, hh=hh, min=min, ss=ss)
168 
169 do n = 1, numfiles
170 
171  ! Config filenames to filenames
172  self%filenames(n) = trim(self%filenames_conf(n))
173 
174  ! Swap out datetime templates if needed
175  if (index(self%filenames(n),"%yyyy") > 0) &
176  self%filenames(n) = replace_text(self%filenames(n),'%yyyy',yyyy)
177  if (index(self%filenames(n),"%mm" ) > 0) &
178  self%filenames(n) = replace_text(self%filenames(n),'%mm' ,mm )
179  if (index(self%filenames(n),"%dd" ) > 0) &
180  self%filenames(n) = replace_text(self%filenames(n),'%dd' ,dd )
181  if (index(self%filenames(n),"%hh" ) > 0) &
182  self%filenames(n) = replace_text(self%filenames(n),'%hh' ,hh )
183  if (index(self%filenames(n),"%MM" ) > 0) &
184  self%filenames(n) = replace_text(self%filenames(n),'%MM' ,min )
185  if (index(self%filenames(n),"%ss" ) > 0) &
186  self%filenames(n) = replace_text(self%filenames(n),'%ss' ,ss )
187 
188 enddo
189 
190 end subroutine setup_date
191 
192 ! --------------------------------------------------------------------------------------------------
193 
194 subroutine read_meta(self, geom, vdate, calendar_type, date_init)
195 
196 class(fv3jedi_io_gfs), intent(inout) :: self
197 type(fv3jedi_geom), intent(inout) :: geom !< Geometry
198 type(datetime), intent(inout) :: vdate !< DateTime
199 integer, intent(inout) :: calendar_type !< GFS calendar type
200 integer, intent(inout) :: date_init(6) !< GFS date intialized
201 
202 integer :: date(6)
203 integer(kind=c_int) :: idate, isecs
204 
205 type(restart_file_type) :: restart_spec
206 integer :: idrst
207 real(kind=kind_real), allocatable, dimension(:,:) :: grid_lat, grid_lon
208 
209 
210 ! Read Lat-Lon and check consitency with geom
211 ! -------------------------------------------
212 if (trim(self%filenames(self%index_spec)) .ne. "null" .and. trim(self%datapath) .ne. "null") then
213 
214  allocate(grid_lat(geom%isc:geom%iec,geom%jsc:geom%jec))
215  allocate(grid_lon(geom%isc:geom%iec,geom%jsc:geom%jec))
216 
217  idrst = register_restart_field( restart_spec, trim(self%filenames(self%index_spec)), &
218  "grid_latt", grid_lat, domain=geom%domain )
219  idrst = register_restart_field( restart_spec, trim(self%filenames(self%index_spec)), &
220  "grid_lont", grid_lon, domain=geom%domain )
221 
222  call restore_state(restart_spec, directory=trim(adjustl(self%datapath)))
223  call free_restart_type(restart_spec)
224 
225  if ((maxval(abs(grid_lat-rad2deg*geom%grid_lat(geom%isc:geom%iec,geom%jsc:geom%jec)))>1.0e-4) &
226  .or.(maxval(abs(grid_lon-rad2deg*geom%grid_lon(geom%isc:geom%iec,geom%jsc:geom%jec)))>1.0e-4))then
227  call abor1_ftn("Grid in gridspec file does not match that in the geometry")
228  endif
229  deallocate(grid_lat)
230  deallocate(grid_lon)
231 endif
232 
233 ! Get dates from coupler.res
234 !---------------------------
235 if (.not. self%skip_coupler) then
236  open(101, file=trim(adjustl(self%datapath))//'/'//self%filenames(self%index_cplr), form='formatted')
237  read(101, '(i6)') calendar_type
238  read(101, '(6i6)') date_init
239  read(101, '(6i6)') date
240  close(101)
241  idate=date(1)*10000+date(2)*100+date(3)
242  isecs=date(4)*3600+date(5)*60+date(6)
243 else
244  idate = 20000101
245  isecs = 0
246 endif
247 
248 ! Set datetime
249 call datetime_from_ifs(vdate, idate, isecs)
250 
251 end subroutine read_meta
252 
253 ! --------------------------------------------------------------------------------------------------
254 
255 subroutine read_fields(self, geom, fields)
256 
257 implicit none
258 class(fv3jedi_io_gfs), intent(inout) :: self
259 type(fv3jedi_geom), intent(inout) :: geom
260 type(fv3jedi_field), intent(inout) :: fields(:)
261 
262 type(restart_file_type) :: restart(numfiles)
263 logical :: rstflag(numfiles)
264 integer :: n, indexrst, position, var, idrst
265 
266 logical :: havedelp
267 integer :: indexof_ps, indexof_delp
268 real(kind=kind_real), allocatable :: delp(:,:,:)
269 
270 ! Register and read fields
271 ! ------------------------
272 rstflag = .false.
273 
274 ! Check whether delp in fields
275 ! ----------------------------
276 indexof_ps = -1
277 indexof_delp = -1
278 havedelp = has_field(fields, 'delp', indexof_delp)
279 
280 ! Loop over fields and register their restart file
281 ! ------------------------------------------------
282 do var = 1,size(fields)
283 
284  ! If need ps and not in file will compute from delp so read delp in place of ps
285  if (trim(fields(var)%fv3jedi_name) == 'ps' .and. .not.self%ps_in_file) then
286  indexof_ps = var
287  if (havedelp) cycle ! Do not register delp twice
288  deallocate(fields(indexof_ps)%array)
289  allocate(fields(indexof_ps)%array(geom%isc:geom%iec,geom%jsc:geom%jec,1:geom%npz))
290  fields(indexof_ps)%short_name = 'DELP'
291  endif
292 
293  select case (trim(fields(var)%io_file))
294  case("core")
295  indexrst = self%index_core
296  case("tracer")
297  indexrst = self%index_trcr
298  case("surface")
299  indexrst = self%index_sfcd
300  case("surface_wind")
301  indexrst = self%index_sfcw
302  case("physics")
303  indexrst = self%index_phys
304  case("orography")
305  indexrst = self%index_orog
306  case("cold")
307  indexrst = self%index_cold
308  case("default")
309  call abor1_ftn("fv3jedi_io_gfs_mod: Abort, field "//trim(fields(var)%short_name)//&
310  " does not have IOFile specified in the FieldSets metadata or it"&
311  " does not match options in gfs IO module")
312  end select
313 
314  ! Convert fv3jedi position to fms position
315  position = center
316  if (fields(var)%staggerloc == 'northsouth') then
317  position = north
318  elseif (fields(var)%staggerloc == 'eastwest') then
319  position = east
320  endif
321 
322  ! Flag to read this restart
323  rstflag(indexrst) = .true.
324 
325  ! Register this restart
326  idrst = register_restart_field( restart(indexrst), trim(self%filenames(indexrst)), &
327  trim(fields(var)%short_name), fields(var)%array, &
328  domain=geom%domain, position=position )
329 
330 enddo
331 
332 ! Loop over files and read fields
333 ! -------------------------------
334 do n = 1, numfiles
335  if (rstflag(n)) then
336  call restore_state(restart(n), directory=trim(adjustl(self%datapath)))
337  call free_restart_type(restart(n))
338  endif
339 enddo
340 
341 ! Compute ps from DELP
342 ! --------------------
343 if (indexof_ps > 0) then
344  allocate(delp(geom%isc:geom%iec,geom%jsc:geom%jec,1:geom%npz))
345  if (.not. havedelp) then
346  delp = fields(indexof_ps)%array
347  deallocate(fields(indexof_ps)%array)
348  allocate(fields(indexof_ps)%array(geom%isc:geom%iec,geom%jsc:geom%jec,1))
349  else
350  delp = fields(indexof_delp)%array
351  endif
352  fields(indexof_ps)%array(:,:,1) = sum(delp,3)
353  fields(indexof_ps)%short_name = 'ps'
354 endif
355 
356 end subroutine read_fields
357 
358 ! --------------------------------------------------------------------------------------------------
359 
360 subroutine write(self, geom, fields, vdate, calendar_type, date_init)
361 
362 implicit none
363 class(fv3jedi_io_gfs), intent(inout) :: self
364 type(fv3jedi_geom), intent(inout) :: geom !< Geom
365 type(fv3jedi_field), intent(in) :: fields(:) !< Fields to be written
366 type(datetime), intent(in) :: vdate !< DateTime
367 integer, intent(in) :: calendar_type !< GFS calendar type
368 integer, intent(in) :: date_init(6) !< GFS date intialized
369 
370 logical :: rstflag(numfiles)
371 integer :: n, indexrst, position, var, idrst, date(6)
372 integer(kind=c_int) :: idate, isecs
373 type(restart_file_type) :: restart(numfiles)
374 character(len=64) :: datefile
375 
376 ! Get datetime
377 ! ------------
378 call datetime_to_ifs(vdate, idate, isecs)
379 date(1) = idate/10000
380 date(2) = idate/100 - date(1)*100
381 date(3) = idate - (date(1)*10000 + date(2)*100)
382 date(4) = isecs/3600
383 date(5) = (isecs - date(4)*3600)/60
384 date(6) = isecs - (date(4)*3600 + date(5)*60)
385 
386 ! Convert integer datetime into string and prepend file names
387 ! -----------------------------------------------------------
388 write(datefile,'(I4,I0.2,I0.2,A1,I0.2,I0.2,I0.2,A1)') date(1),date(2),date(3),".",&
389  date(4),date(5),date(6),"."
390 
391 if (self%prepend_date) then
392  do n = 1, numfiles
393  self%filenames(n) = trim(datefile)//trim(self%filenames(n))
394  enddo
395 endif
396 
397 rstflag = .false.
398 
399 ! Loop over fields and register their restart file
400 ! ------------------------------------------------
401 do var = 1,size(fields)
402 
403  select case (trim(fields(var)%io_file))
404  case("core")
405  indexrst = self%index_core
406  case("tracer")
407  indexrst = self%index_trcr
408  case("surface")
409  indexrst = self%index_sfcd
410  case("surface_wind")
411  indexrst = self%index_sfcw
412  case("physics")
413  indexrst = self%index_phys
414  case("orography")
415  indexrst = self%index_orog
416  case("cold")
417  indexrst = self%index_cold
418  case("default")
419  call abor1_ftn("fv3jedi_io_gfs_mod: Abort, field "//trim(fields(var)%short_name)//&
420  " does not have IOFile specified in the FieldSets metadata")
421  end select
422 
423  ! Convert fv3jedi position to fms position
424  position = center
425  if (fields(var)%staggerloc == 'northsouth') then
426  position = north
427  elseif (fields(var)%staggerloc == 'eastwest') then
428  position = east
429  endif
430 
431  ! Flag to read this restart
432  rstflag(indexrst) = .true.
433 
434  ! Register this restart
435  idrst = register_restart_field( restart(indexrst), trim(self%filenames(indexrst)), &
436  fields(var)%short_name, fields(var)%array, domain=geom%domain, &
437  position=position, longname = trim(fields(var)%long_name), &
438  units = trim(fields(var)%units) )
439 
440 enddo
441 
442 
443 ! Loop over files and write fields
444 ! -------------------------------
445 do n = 1, numfiles
446  if (rstflag(n)) then
447  call save_restart(restart(n), directory=trim(adjustl(self%datapath)))
448  call free_restart_type(restart(n))
449  endif
450 enddo
451 
452 
453 !Write date/time info in coupler.res
454 !-----------------------------------
455 if (mpp_pe() == mpp_root_pe() .and. .not. self%skip_coupler) then
456  open(101, file = trim(adjustl(self%datapath))//'/'// &
457  trim(adjustl(self%filenames(self%index_cplr))), form='formatted')
458  write( 101, '(i6,8x,a)' ) calendar_type, &
459  '(Calendar: no_calendar=0, thirty_day_months=1, julian=2, gregorian=3, noleap=4)'
460  write( 101, '(6i6,8x,a)') date_init, 'Model start time: year, month, day, hour, minute, second'
461  write( 101, '(6i6,8x,a)') date, 'Current model time: year, month, day, hour, minute, second'
462  close(101)
463 endif
464 
465 end subroutine write
466 
467 ! --------------------------------------------------------------------------------------------------
468 
469 ! Not really needed but prevents gnu compiler bug
470 subroutine dummy_final(self)
471 type(fv3jedi_io_gfs), intent(inout) :: self
472 end subroutine dummy_final
473 
474 ! --------------------------------------------------------------------------------------------------
475 
476 end module fv3jedi_io_gfs_mod
fv3jedi_io_utils_mod::replace_text
character(len(inputstr)+100) function replace_text(inputstr, search, replace)
Definition: fv3jedi_io_utils_mod.f90:93
fv3jedi_field_mod
Definition: fv3jedi_field_mod.f90:6
fv3jedi_field_mod::has_field
logical function, public has_field(fields, field_name, field_index)
Definition: fv3jedi_field_mod.f90:58
fv3jedi_constants_mod::rad2deg
real(kind=kind_real), parameter, public rad2deg
Definition: fv3jedi_constants_mod.f90:13
fv3jedi_io_utils_mod
Definition: fv3jedi_io_utils_mod.f90:6
fv3jedi_geom_mod
Fortran module handling geometry for the FV3 model.
Definition: fv3jedi_geom_mod.f90:8
fv3jedi_io_gfs_mod
Definition: fv3jedi_io_gfs_mod.f90:1
fv3jedi_io_gfs_mod::dummy_final
subroutine dummy_final(self)
Definition: fv3jedi_io_gfs_mod.f90:471
fv3jedi_geom_mod::fv3jedi_geom
Fortran derived type to hold geometry data for the FV3JEDI model.
Definition: fv3jedi_geom_mod.f90:46
fv3jedi_constants_mod
Definition: fv3jedi_constants_mod.f90:6
fv3jedi_io_gfs_mod::setup_date
subroutine setup_date(self, vdate)
Definition: fv3jedi_io_gfs_mod.f90:157
fv3jedi_io_gfs_mod::fv3jedi_io_gfs
Definition: fv3jedi_io_gfs_mod.f90:35
fv3jedi_kinds_mod::kind_real
integer, parameter, public kind_real
Definition: fv3jedi_kinds_mod.f90:14
fv3jedi_io_utils_mod::vdate_to_datestring
subroutine vdate_to_datestring(vdate, datest, date, yyyy, mm, dd, hh, min, ss)
Definition: fv3jedi_io_utils_mod.f90:48
fv3jedi_field_mod::fv3jedi_field
Definition: fv3jedi_field_mod.f90:36
fv3jedi_kinds_mod
Definition: fv3jedi_kinds_mod.f90:6
fv3jedi_io_gfs_mod::write
subroutine write(self, geom, fields, vdate, calendar_type, date_init)
Definition: fv3jedi_io_gfs_mod.f90:361
fv3jedi_io_gfs_mod::setup_conf
subroutine setup_conf(self, f_conf)
Definition: fv3jedi_io_gfs_mod.f90:67
fv3jedi_io_gfs_mod::numfiles
integer, parameter numfiles
Definition: fv3jedi_io_gfs_mod.f90:33
fv3jedi_io_gfs_mod::read_fields
subroutine read_fields(self, geom, fields)
Definition: fv3jedi_io_gfs_mod.f90:256
fv3jedi_io_gfs_mod::read_meta
subroutine read_meta(self, geom, vdate, calendar_type, date_init)
Definition: fv3jedi_io_gfs_mod.f90:195