FV3DYCORE  Version 2.0.0
fv_io.F90
Go to the documentation of this file.
1 !***********************************************************************
2 !* GNU Lesser General Public License
3 !*
4 !* This file is part of the FV3 dynamical core.
5 !*
6 !* The FV3 dynamical core is free software: you can redistribute it
7 !* and/or modify it under the terms of the
8 !* GNU Lesser General Public License as published by the
9 !* Free Software Foundation, either version 3 of the License, or
10 !* (at your option) any later version.
11 !*
12 !* The FV3 dynamical core is distributed in the hope that it will be
13 !* useful, but WITHOUT ANYWARRANTY; without even the implied warranty
14 !* of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
15 !* See the GNU General Public License for more details.
16 !*
17 !* You should have received a copy of the GNU Lesser General Public
18 !* License along with the FV3 dynamical core.
19 !* If not, see <http://www.gnu.org/licenses/>.
20 !***********************************************************************
21 
29 
30 module fv_io_mod
31 
32 ! <table>
33 ! <tr>
34 ! <th>Module Name</th>
35 ! <th>Functions Included</th>
36 ! </tr>
37 ! <tr>
38 ! <td>external_sst_mod</td>
39 ! <td>sst_ncep, sst_anom, use_ncep_sst</td>
40 ! </tr>
41 ! <tr>
42 ! <td>field_manager_mod</td>
43 ! <td>MODEL_ATMOS</td>
44 ! </tr>
45 ! <tr>
46 ! <td>fms_mod</td>
47 ! <td>file_exist</td>
48 ! </tr>
49 ! <tr>
50 ! <td>fms_io_mod</td>
51 ! <td>fms_io_exit, get_tile_string,restart_file_type,
52 ! register_restart_field, save_restart, restore_state,
53 ! set_domain, nullify_domain, set_filename_appendix,
54 ! get_mosaic_tile_file, get_instance_filename,
55 ! save_restart_border, restore_state_border,
56 ! free_restart_type,field_exist</td>
57 ! </tr>
58 ! <tr>
59 ! <td>fv_arrays_mod</td>
60 ! <td>fv_atmos_type, fv_nest_BC_type_3D</td>
61 ! </tr>
62 ! <tr>
63 ! <td>fv_eta_mod</td>
64 ! <td>set_external_eta</td>
65 ! </tr>
66 ! <tr>
67 ! <td>fv_mp_mod</td>
68 ! <td>ng, mp_gather, is_master</td>
69 ! </tr>
70 ! <tr>
71 ! <td>mpp_mod</td>
72 ! <td>mpp_error, FATAL, NOTE, WARNING, mpp_root_pe,
73 ! mpp_sync, mpp_pe, mpp_declare_pelist</td>
74 ! </tr>
75 ! <tr>
76 ! <td>mpp_domains_mod</td>
77 ! <td>domain2d, EAST, WEST, NORTH, CENTER, SOUTH, CORNER,
78 ! mpp_get_compute_domain, mpp_get_data_domain,
79 ! mpp_get_layout, mpp_get_ntile_count,mpp_get_global_domain</td>
80 ! </tr>
81 ! <tr>
82 ! <td>tracer_manager_mod</td>
83 ! <td>tr_get_tracer_names=>get_tracer_names,
84 ! get_tracer_names, get_number_tracers,
85 ! set_tracer_profile, get_tracer_index</td>
86 ! </tr>
87 ! </table>
88 
89  use fms_mod, only: file_exist
90  use fms_io_mod, only: fms_io_exit, get_tile_string, &
91  restart_file_type, register_restart_field, &
92  save_restart, restore_state, &
93  set_domain, nullify_domain, set_filename_appendix, &
94  get_mosaic_tile_file, get_instance_filename, &
95  save_restart_border, restore_state_border, free_restart_type, &
96  field_exist
97  use mpp_mod, only: mpp_error, fatal, note, warning, mpp_root_pe, &
98  mpp_sync, mpp_pe, mpp_declare_pelist
99  use mpp_domains_mod, only: domain2d, east, west, north, center, south, corner, &
100  mpp_get_compute_domain, mpp_get_data_domain, &
101  mpp_get_layout, mpp_get_ntile_count, &
102  mpp_get_global_domain
103  use tracer_manager_mod, only: tr_get_tracer_names=>get_tracer_names, &
104  get_tracer_names, get_number_tracers, &
105  set_tracer_profile, &
106  get_tracer_index
107  use field_manager_mod, only: model_atmos
108  use external_sst_mod, only: sst_ncep, sst_anom, use_ncep_sst
110  use fv_eta_mod, only: set_external_eta
111 
112  use fv_mp_mod, only: mp_gather, is_master
113  use fms_io_mod, only: set_domain
115 
116  implicit none
117  private
118 
123 
124  logical :: module_is_initialized = .false.
125 
126 
127  integer ::grid_xtdimid, grid_ytdimid, haloid, pfullid !For writing BCs
129 
130 contains
131 
132 
134  subroutine fv_io_init()
136  end subroutine fv_io_init
137 
138 
140  subroutine fv_io_exit
142  end subroutine fv_io_exit
143 
144 
146  subroutine fv_io_read_restart(fv_domain,Atm)
147  type(domain2d), intent(inout) :: fv_domain
148  type(fv_atmos_type), intent(inout) :: Atm(:)
149 
150  character(len=64) :: fname, tracer_name
151  character(len=6) :: stile_name
152  integer :: isc, iec, jsc, jec, n, nt, nk, ntracers
153  integer :: ntileMe
154  integer :: ks, ntiles
155  real :: ptop
156 
157  character(len=128) :: tracer_longname, tracer_units
158 
159  ntileme = size(atm(:)) ! This will need mods for more than 1 tile per pe
160 
161  call restore_state(atm(1)%Fv_restart)
162  if (atm(1)%flagstruct%external_eta) then
163  call set_external_eta(atm(1)%ak, atm(1)%bk, atm(1)%ptop, atm(1)%ks)
164  endif
165 
166  if ( use_ncep_sst .or. atm(1)%flagstruct%nudge .or. atm(1)%flagstruct%ncep_ic ) then
167  call mpp_error(note, 'READING FROM SST_RESTART DISABLED')
168  !call restore_state(Atm(1)%SST_restart)
169  endif
170 
171 ! fix for single tile runs where you need fv_core.res.nc and fv_core.res.tile1.nc
172  ntiles = mpp_get_ntile_count(fv_domain)
173  if(ntiles == 1 .and. .not. atm(1)%neststruct%nested) then
174  stile_name = '.tile1'
175  else
176  stile_name = ''
177  endif
178 
179  do n = 1, ntileme
180  call restore_state(atm(n)%Fv_tile_restart)
181 
182 !--- restore data for fv_tracer - if it exists
183  fname = 'INPUT/fv_tracer.res'//trim(stile_name)//'.nc'
184  if (file_exist(fname)) then
185  call restore_state(atm(n)%Tra_restart)
186  else
187  call mpp_error(note,'==> Warning from fv_read_restart: Expected file '//trim(fname)//' does not exist')
188  endif
189 
190 !--- restore data for surface winds - if it exists
191  fname = 'INPUT/fv_srf_wnd.res'//trim(stile_name)//'.nc'
192  if (file_exist(fname)) then
193  call restore_state(atm(n)%Rsf_restart)
194  atm(n)%flagstruct%srf_init = .true.
195  else
196  call mpp_error(note,'==> Warning from fv_read_restart: Expected file '//trim(fname)//' does not exist')
197  atm(n)%flagstruct%srf_init = .false.
198  endif
199 
200  if ( atm(n)%flagstruct%fv_land ) then
201 !--- restore data for mg_drag - if it exists
202  fname = 'INPUT/mg_drag.res'//trim(stile_name)//'.nc'
203  if (file_exist(fname)) then
204  call restore_state(atm(n)%Mg_restart)
205  else
206  call mpp_error(note,'==> Warning from fv_read_restart: Expected file '//trim(fname)//' does not exist')
207  endif
208 !--- restore data for fv_land - if it exists
209  fname = 'INPUT/fv_land.res'//trim(stile_name)//'.nc'
210  if (file_exist(fname)) then
211  call restore_state(atm(n)%Lnd_restart)
212  else
213  call mpp_error(note,'==> Warning from fv_read_restart: Expected file '//trim(fname)//' does not exist')
214  endif
215  endif
216 
217  end do
218 
219  return
220 
221  end subroutine fv_io_read_restart
222 
227  subroutine fv_io_read_tracers(fv_domain,Atm)
228  type(domain2d), intent(inout) :: fv_domain
229  type(fv_atmos_type), intent(inout) :: Atm(:)
230  integer :: n, ntracers, ntprog, nt, isc, iec, jsc, jec, id_restart
231  character(len=6) :: stile_name
232  character(len=64):: fname, tracer_name
233  type(restart_file_type) :: Tra_restart_r
234  integer :: ntiles
235 
236  n = 1
237  isc = atm(n)%bd%isc
238  iec = atm(n)%bd%iec
239  jsc = atm(n)%bd%jsc
240  jec = atm(n)%bd%jec
241  call get_number_tracers(model_atmos, num_tracers=ntracers, num_prog=ntprog)
242 
243 ! fix for single tile runs where you need fv_core.res.nc and fv_core.res.tile1.nc
244  ntiles = mpp_get_ntile_count(fv_domain)
245  if(ntiles == 1 .and. .not. atm(1)%neststruct%nested) then
246  stile_name = '.tile1'
247  else
248  stile_name = ''
249  endif
250 
251  fname = 'fv_tracer.res'//trim(stile_name)//'.nc'
252  do nt = 2, ntprog
253  call get_tracer_names(model_atmos, nt, tracer_name)
254  call set_tracer_profile (model_atmos, nt, atm(n)%q(isc:iec,jsc:jec,:,nt) )
255  id_restart = register_restart_field(tra_restart_r, fname, tracer_name, atm(n)%q(:,:,:,nt), &
256  domain=fv_domain, mandatory=.false., tile_count=n)
257  enddo
258  do nt = ntprog+1, ntracers
259  call get_tracer_names(model_atmos, nt, tracer_name)
260  call set_tracer_profile (model_atmos, nt, atm(n)%qdiag(isc:iec,jsc:jec,:,nt) )
261  id_restart = register_restart_field(tra_restart_r, fname, tracer_name, atm(n)%qdiag(:,:,:,nt), &
262  domain=fv_domain, mandatory=.false., tile_count=n)
263  enddo
264  if (file_exist('INPUT'//trim(fname))) then
265  call restore_state(tra_restart_r)
266  call free_restart_type(tra_restart_r)
267  else
268  call mpp_error(note,'==> Warning from fv_io_read_tracers: Expected file '//trim(fname)//' does not exist')
269  endif
270 
271  return
272 
273  end subroutine fv_io_read_tracers
274 
278  subroutine remap_restart(fv_domain,Atm)
280 
281  type(domain2d), intent(inout) :: fv_domain
282  type(fv_atmos_type), intent(inout) :: Atm(:)
283 
284  character(len=64) :: fname, tracer_name
285  character(len=6) :: stile_name
286  integer :: isc, iec, jsc, jec, n, nt, nk, ntracers, ntprog, ntdiag
287  integer :: isd, ied, jsd, jed
288  integer :: ntiles
289  type(restart_file_type) :: FV_restart_r, FV_tile_restart_r, Tra_restart_r
290  integer :: id_restart
291 
292 !
293 !-------------------------------------------------------------------------
294  real, allocatable:: ak_r(:), bk_r(:)
295  real, allocatable:: u_r(:,:,:), v_r(:,:,:), pt_r(:,:,:), delp_r(:,:,:)
296  real, allocatable:: w_r(:,:,:), delz_r(:,:,:), ze0_r(:,:,:)
297  real, allocatable:: q_r(:,:,:,:), qdiag_r(:,:,:,:)
298 !-------------------------------------------------------------------------
299  integer npz, npz_rst, ng
300  integer i,j,k
301 
302  npz = atm(1)%npz ! run time z dimension
303  npz_rst = atm(1)%flagstruct%npz_rst ! restart z dimension
304  isc = atm(1)%bd%isc; iec = atm(1)%bd%iec; jsc = atm(1)%bd%jsc; jec = atm(1)%bd%jec
305  ng = atm(1)%ng
306 
307  isd = isc - ng; ied = iec + ng
308  jsd = jsc - ng; jed = jec + ng
309 
310 
311 ! call get_number_tracers(MODEL_ATMOS, num_tracers=ntracers)
312  ntprog = size(atm(1)%q,4) ! Temporary until we get tracer manager integrated
313  ntdiag = size(atm(1)%qdiag,4)
314  ntracers = ntprog+ntdiag
315 
316 ! ntileMe = size(Atm(:)) ! This will have to be modified for mult tiles per PE
317 
318 
319 ! Allocate arrays for reading old restart file:
320  allocate ( ak_r(npz_rst+1) )
321  allocate ( bk_r(npz_rst+1) )
322 
323  allocate ( u_r(isc:iec, jsc:jec+1,npz_rst) )
324  allocate ( v_r(isc:iec+1,jsc:jec ,npz_rst) )
325 
326  allocate ( pt_r(isc:iec, jsc:jec, npz_rst) )
327  allocate ( delp_r(isc:iec, jsc:jec, npz_rst) )
328  allocate ( q_r(isc:iec, jsc:jec, npz_rst, ntprog) )
329  allocate (qdiag_r(isc:iec, jsc:jec, npz_rst, ntprog+1:ntracers) )
330 
331  if ( (.not.atm(1)%flagstruct%hydrostatic) .and. (.not.atm(1)%flagstruct%make_nh) ) then
332  allocate ( w_r(isc:iec, jsc:jec, npz_rst) )
333  allocate ( delz_r(isc:iec, jsc:jec, npz_rst) )
334  if ( atm(1)%flagstruct%hybrid_z ) &
335  allocate ( ze0_r(isc:iec, jsc:jec, npz_rst+1) )
336  endif
337 
338  fname = 'fv_core.res.nc'
339  id_restart = register_restart_field(fv_restart_r, fname, 'ak', ak_r(:), no_domain=.true.)
340  id_restart = register_restart_field(fv_restart_r, fname, 'bk', bk_r(:), no_domain=.true.)
341  call restore_state(fv_restart_r)
342  call free_restart_type(fv_restart_r)
343 
344 ! fix for single tile runs where you need fv_core.res.nc and fv_core.res.tile1.nc
345  ntiles = mpp_get_ntile_count(fv_domain)
346  if(ntiles == 1 .and. .not. atm(1)%neststruct%nested) then
347  stile_name = '.tile1'
348  else
349  stile_name = ''
350  endif
351 
352 !!!! A NOTE about file names
353 !!! file_exist() needs the full relative path, including INPUT/
354 !!! But register_restart_field ONLY looks in INPUT/ and so JUST needs the file name!!
355 
356 ! do n = 1, ntileMe
357  n = 1
358  fname = 'fv_core.res'//trim(stile_name)//'.nc'
359  id_restart = register_restart_field(fv_tile_restart_r, fname, 'u', u_r, &
360  domain=fv_domain, position=north,tile_count=n)
361  id_restart = register_restart_field(fv_tile_restart_r, fname, 'v', v_r, &
362  domain=fv_domain, position=east,tile_count=n)
363  if (.not.atm(n)%flagstruct%hydrostatic) then
364  id_restart = register_restart_field(fv_tile_restart_r, fname, 'W', w_r, &
365  domain=fv_domain, mandatory=.false., tile_count=n)
366  id_restart = register_restart_field(fv_tile_restart_r, fname, 'DZ', delz_r, &
367  domain=fv_domain, mandatory=.false., tile_count=n)
368  if ( atm(n)%flagstruct%hybrid_z ) then
369  id_restart = register_restart_field(fv_tile_restart_r, fname, 'ZE0', ze0_r, &
370  domain=fv_domain, mandatory=.false., tile_count=n)
371  endif
372  endif
373  id_restart = register_restart_field(fv_tile_restart_r, fname, 'T', pt_r, &
374  domain=fv_domain, tile_count=n)
375  id_restart = register_restart_field(fv_tile_restart_r, fname, 'delp', delp_r, &
376  domain=fv_domain, tile_count=n)
377  id_restart = register_restart_field(fv_tile_restart_r, fname, 'phis', atm(n)%phis, &
378  domain=fv_domain, tile_count=n)
379  call restore_state(fv_tile_restart_r)
380  call free_restart_type(fv_tile_restart_r)
381  fname = 'fv_srf_wnd.res'//trim(stile_name)//'.nc'
382  if (file_exist('INPUT/'//fname)) then
383  call restore_state(atm(n)%Rsf_restart)
384  atm(n)%flagstruct%srf_init = .true.
385  else
386  call mpp_error(note,'==> Warning from remap_restart: Expected file '//trim(fname)//' does not exist')
387  atm(n)%flagstruct%srf_init = .false.
388  endif
389 
390  if ( atm(n)%flagstruct%fv_land ) then
391 !--- restore data for mg_drag - if it exists
392  fname = 'mg_drag.res'//trim(stile_name)//'.nc'
393  if (file_exist('INPUT/'//fname)) then
394  call restore_state(atm(n)%Mg_restart)
395  else
396  call mpp_error(note,'==> Warning from remap_restart: Expected file '//trim(fname)//' does not exist')
397  endif
398 !--- restore data for fv_land - if it exists
399  fname = 'fv_land.res'//trim(stile_name)//'.nc'
400  if (file_exist('INPUT/'//fname)) then
401  call restore_state(atm(n)%Lnd_restart)
402  else
403  call mpp_error(note,'==> Warning from remap_restart: Expected file '//trim(fname)//' does not exist')
404  endif
405  endif
406 
407  fname = 'fv_tracer.res'//trim(stile_name)//'.nc'
408  if (file_exist('INPUT/'//fname)) then
409  do nt = 1, ntprog
410  call get_tracer_names(model_atmos, nt, tracer_name)
411  call set_tracer_profile (model_atmos, nt, q_r(isc:iec,jsc:jec,:,nt) )
412  id_restart = register_restart_field(tra_restart_r, fname, tracer_name, q_r(:,:,:,nt), &
413  domain=fv_domain, mandatory=.false., tile_count=n)
414  enddo
415  do nt = ntprog+1, ntracers
416  call get_tracer_names(model_atmos, nt, tracer_name)
417  call set_tracer_profile (model_atmos, nt, qdiag_r(isc:iec,jsc:jec,:,nt) )
418  id_restart = register_restart_field(tra_restart_r, fname, tracer_name, qdiag_r(:,:,:,nt), &
419  domain=fv_domain, mandatory=.false., tile_count=n)
420  enddo
421  call restore_state(tra_restart_r)
422  call free_restart_type(tra_restart_r)
423  else
424  call mpp_error(note,'==> Warning from remap_restart: Expected file '//trim(fname)//' does not exist')
425  endif
426 
427 ! ====== PJP added DA functionality ======
428  if (atm(n)%flagstruct%read_increment) then
429  ! print point in middle of domain for a sanity check
430  i = (isc + iec)/2
431  j = (jsc + jec)/2
432  k = npz_rst/2
433  if( is_master() ) write(*,*) 'Calling read_da_inc',pt_r(i,j,k)
434  call read_da_inc(atm(n), atm(n)%domain, atm(n)%bd, npz_rst, ntprog, &
435  u_r, v_r, q_r, delp_r, pt_r, delz_r, isc, jsc, iec, jec, &
436  isc, jsc, iec, jec )
437  if( is_master() ) write(*,*) 'Back from read_da_inc',pt_r(i,j,k)
438  endif
439 ! ====== end PJP added DA functionailty======
440 
441  call rst_remap(npz_rst, npz, isc, iec, jsc, jec, isd, ied, jsd, jed, ntracers, ntprog, &
442  delp_r, u_r, v_r, w_r, delz_r, pt_r, q_r, qdiag_r,&
443  atm(n)%delp, atm(n)%u, atm(n)%v, atm(n)%w, atm(n)%delz, atm(n)%pt, atm(n)%q, &
444  atm(n)%qdiag, ak_r, bk_r, atm(n)%ptop, atm(n)%ak, atm(n)%bk, &
445  atm(n)%flagstruct%hydrostatic, atm(n)%flagstruct%make_nh, atm(n)%domain, &
446  atm(n)%gridstruct%square_domain)
447  !end do
448 
449  deallocate( ak_r )
450  deallocate( bk_r )
451  deallocate( u_r )
452  deallocate( v_r )
453  deallocate( pt_r )
454  deallocate( delp_r )
455  deallocate( q_r )
456  deallocate( qdiag_r )
457 
458  if ( (.not.atm(1)%flagstruct%hydrostatic) .and. (.not.atm(1)%flagstruct%make_nh) ) then
459  deallocate ( w_r )
460  deallocate ( delz_r )
461  if ( atm(1)%flagstruct%hybrid_z ) deallocate ( ze0_r )
462  endif
463 
464  end subroutine remap_restart
465 
469  subroutine fv_io_register_nudge_restart(Atm)
470  type(fv_atmos_type), intent(inout) :: Atm(:)
471  character(len=64) :: fname
472  integer :: id_restart
473 
474 ! use_ncep_sst may not be initialized at this point?
475  call mpp_error(note, 'READING FROM SST_restart DISABLED')
476  if ( use_ncep_sst .or. atm(1)%flagstruct%nudge .or. atm(1)%flagstruct%ncep_ic ) then
477 ! if ( Atm(1)%nudge .or. Atm(1)%ncep_ic ) then
478  fname = 'sst_ncep.res.nc'
479  id_restart = register_restart_field(atm(1)%SST_restart, fname, 'sst_ncep', sst_ncep)
480  id_restart = register_restart_field(atm(1)%SST_restart, fname, 'sst_anom', sst_anom)
481  endif
482 
483  end subroutine fv_io_register_nudge_restart
484 
486  subroutine fv_io_register_restart(fv_domain,Atm)
487  type(domain2d), intent(inout) :: fv_domain
488  type(fv_atmos_type), intent(inout) :: Atm(:)
489 
490  character(len=64) :: fname, tracer_name
491  character(len=6) :: gn, stile_name
492  integer :: id_restart
493  integer :: n, nt, ntracers, ntprog, ntdiag, ntileMe, ntiles
494 
495  ntileme = size(atm(:))
496  ntprog = size(atm(1)%q,4)
497  ntdiag = size(atm(1)%qdiag,4)
498  ntracers = ntprog+ntdiag
499 
500 !--- set the 'nestXX' appendix for all files using fms_io
501  if (atm(1)%grid_number > 1) then
502  write(gn,'(A4, I2.2)') "nest", atm(1)%grid_number
503  else
504  gn = ''
505  end if
506  call set_filename_appendix(gn)
507 
508 !--- fix for single tile runs where you need fv_core.res.nc and fv_core.res.tile1.nc
509  ntiles = mpp_get_ntile_count(fv_domain)
510  if(ntiles == 1 .and. .not. atm(1)%neststruct%nested) then
511  stile_name = '.tile1'
512  else
513  stile_name = ''
514  endif
515 
516 ! use_ncep_sst may not be initialized at this point?
517 #ifndef DYCORE_SOLO
518 ! call mpp_error(NOTE, 'READING FROM SST_RESTART DISABLED')
519 !!$ if ( use_ncep_sst .or. Atm(1)%flagstruct%nudge .or. Atm(1)%flagstruct%ncep_ic ) then
520 !!$ fname = 'sst_ncep'//trim(gn)//'.res.nc'
521 !!$ id_restart = register_restart_field(Atm(1)%SST_restart, fname, 'sst_ncep', sst_ncep)
522 !!$ id_restart = register_restart_field(Atm(1)%SST_restart, fname, 'sst_anom', sst_anom)
523 !!$ endif
524 #endif
525 
526  fname = 'fv_core.res.nc'
527  id_restart = register_restart_field(atm(1)%Fv_restart, fname, 'ak', atm(1)%ak(:), no_domain=.true.)
528  id_restart = register_restart_field(atm(1)%Fv_restart, fname, 'bk', atm(1)%bk(:), no_domain=.true.)
529 
530  do n = 1, ntileme
531  fname = 'fv_core.res'//trim(stile_name)//'.nc'
532  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'u', atm(n)%u, &
533  domain=fv_domain, position=north,tile_count=n)
534  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'v', atm(n)%v, &
535  domain=fv_domain, position=east,tile_count=n)
536  if (.not.atm(n)%flagstruct%hydrostatic) then
537  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'W', atm(n)%w, &
538  domain=fv_domain, mandatory=.false., tile_count=n)
539  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'DZ', atm(n)%delz, &
540  domain=fv_domain, mandatory=.false., tile_count=n)
541  if ( atm(n)%flagstruct%hybrid_z ) then
542  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'ZE0', atm(n)%ze0, &
543  domain=fv_domain, mandatory=.false., tile_count=n)
544  endif
545  endif
546  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'T', atm(n)%pt, &
547  domain=fv_domain, tile_count=n)
548  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'delp', atm(n)%delp, &
549  domain=fv_domain, tile_count=n)
550  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'phis', atm(n)%phis, &
551  domain=fv_domain, tile_count=n)
552 
553  !--- include agrid winds in restarts for use in data assimilation
554  if (atm(n)%flagstruct%agrid_vel_rst) then
555  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'ua', atm(n)%ua, &
556  domain=fv_domain, tile_count=n, mandatory=.false.)
557  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'va', atm(n)%va, &
558  domain=fv_domain, tile_count=n, mandatory=.false.)
559  endif
560 
561  fname = 'fv_srf_wnd.res'//trim(stile_name)//'.nc'
562  id_restart = register_restart_field(atm(n)%Rsf_restart, fname, 'u_srf', atm(n)%u_srf, &
563  domain=fv_domain, tile_count=n)
564  id_restart = register_restart_field(atm(n)%Rsf_restart, fname, 'v_srf', atm(n)%v_srf, &
565  domain=fv_domain, tile_count=n)
566 #ifdef SIM_PHYS
567  id_restart = register_restart_field(rsf_restart(n), fname, 'ts', atm(n)%ts, &
568  domain=fv_domain, tile_count=n)
569 #endif
570 
571  if ( atm(n)%flagstruct%fv_land ) then
572  !-------------------------------------------------------------------------------------------------
573  ! Optional terrain deviation (sgh) and land fraction (oro)
574  fname = 'mg_drag.res'//trim(stile_name)//'.nc'
575  id_restart = register_restart_field(atm(n)%Mg_restart, fname, 'ghprime', atm(n)%sgh, &
576  domain=fv_domain, tile_count=n)
577 
578  fname = 'fv_land.res'//trim(stile_name)//'.nc'
579  id_restart = register_restart_field(atm(n)%Lnd_restart, fname, 'oro', atm(n)%oro, &
580  domain=fv_domain, tile_count=n)
581  endif
582 
583  fname = 'fv_tracer.res'//trim(stile_name)//'.nc'
584  do nt = 1, ntprog
585  call get_tracer_names(model_atmos, nt, tracer_name)
586  ! set all tracers to an initial profile value
587  call set_tracer_profile (model_atmos, nt, atm(n)%q(:,:,:,nt) )
588  id_restart = register_restart_field(atm(n)%Tra_restart, fname, tracer_name, atm(n)%q(:,:,:,nt), &
589  domain=fv_domain, mandatory=.false., tile_count=n)
590  enddo
591  do nt = ntprog+1, ntracers
592  call get_tracer_names(model_atmos, nt, tracer_name)
593  ! set all tracers to an initial profile value
594  call set_tracer_profile (model_atmos, nt, atm(n)%qdiag(:,:,:,nt) )
595  id_restart = register_restart_field(atm(n)%Tra_restart, fname, tracer_name, atm(n)%qdiag(:,:,:,nt), &
596  domain=fv_domain, mandatory=.false., tile_count=n)
597  enddo
598 
599  if ( atm(n)%neststruct%nested ) then
600  call fv_io_register_restart_bcs(atm(n)) !TODO put into fv_io_register_restart
601  endif
602 
603  enddo
604 
605  end subroutine fv_io_register_restart
606 
608  subroutine fv_io_write_restart(Atm, timestamp)
609  type(fv_atmos_type), intent(inout) :: Atm
610  character(len=*), optional, intent(in) :: timestamp
611 
612 !!$ if ( use_ncep_sst .or. Atm%flagstruct%nudge .or. Atm%flagstruct%ncep_ic ) then
613 !!$ call mpp_error(NOTE, 'READING FROM SST_RESTART DISABLED')
614 !!$ !call save_restart(Atm%SST_restart, timestamp)
615 !!$ endif
616 
617  if ( (use_ncep_sst .or. atm%flagstruct%nudge) .and. .not. atm%gridstruct%nested ) then
618  call save_restart(atm%SST_restart, timestamp)
619  endif
620 
621  call save_restart(atm%Fv_restart, timestamp)
622  call save_restart(atm%Fv_tile_restart, timestamp)
623  call save_restart(atm%Rsf_restart, timestamp)
624 
625  if ( atm%flagstruct%fv_land ) then
626  call save_restart(atm%Mg_restart, timestamp)
627  call save_restart(atm%Lnd_restart, timestamp)
628  endif
629 
630  call save_restart(atm%Tra_restart, timestamp)
631 
632 
633  end subroutine fv_io_write_restart
634 
635  subroutine register_bcs_2d(Atm, BCfile_ne, BCfile_sw, fname_ne, fname_sw, &
636  var_name, var, var_bc, istag, jstag)
637  type(fv_atmos_type), intent(in) :: Atm
638  type(restart_file_type), intent(inout) :: BCfile_ne, BCfile_sw
639  character(len=120), intent(in) :: fname_ne, fname_sw
640  character(len=*), intent(in) :: var_name
641  real, dimension(:,:), intent(in), optional :: var
642  type(fv_nest_bc_type_3d), intent(in), optional :: var_bc
643  integer, intent(in), optional :: istag, jstag
644 
645  integer :: npx, npy, i_stag, j_stag
646  integer :: is, ie, js, je, isd, ied, jsd, jed, n
647  integer :: x_halo, y_halo, x_halo_ns, id_restart
648  integer :: layout(2), global_size(2), indices(4)
649  integer, allocatable, dimension(:) :: x1_pelist, y1_pelist
650  integer, allocatable, dimension(:) :: x2_pelist, y2_pelist
651  logical :: is_root_pe
652 
653  i_stag = 0
654  j_stag = 0
655  if (present(istag)) i_stag = i_stag
656  if (present(jstag)) j_stag = j_stag
657  call mpp_get_global_domain(atm%domain, xsize = npx, ysize = npy, position=corner )
658  call mpp_get_data_domain(atm%domain, isd, ied, jsd, jed )
659  call mpp_get_compute_domain(atm%domain, is, ie, js, je )
660  call mpp_get_layout(atm%domain, layout)
661  allocate (x1_pelist(layout(1)))
662  allocate (y1_pelist(layout(2)))
663  allocate (x2_pelist(layout(1)))
664  allocate (y2_pelist(layout(2)))
665  x_halo = is-isd
666  y_halo = js-jsd
667 ! define west and east pelist
668  do n = 1,layout(2)
669  y1_pelist(n)=mpp_root_pe()+layout(1)*n-1
670  y2_pelist(n)=mpp_root_pe()+layout(1)*(n-1)
671  enddo
672 ! define south and north pelist
673  do n = 1,layout(1)
674  x1_pelist(n)=mpp_root_pe()+layout(1)*(layout(2)-1)+(n-1)
675  x2_pelist(n)=mpp_root_pe()+(n-1)
676  enddo
677 ! declare the pelists inside of mpp (creates the MPI communicator)
678  call mpp_declare_pelist(x1_pelist)
679  call mpp_declare_pelist(x2_pelist)
680  call mpp_declare_pelist(y1_pelist)
681  call mpp_declare_pelist(y2_pelist)
682 
683 !EAST & WEST
684 !set defaults for west/east halo regions
685  indices(1) = 1
686  indices(2) = x_halo
687  indices(3) = jsd
688  indices(4) = jed+j_stag
689  global_size(1) = x_halo
690  global_size(2) = npy-1+2*y_halo+j_stag
691 
692 !define west root_pe
693  is_root_pe = .false.
694  if (is.eq.1 .and. js.eq.1) is_root_pe = .true.
695 !register west halo data in t1
696  if (present(var_bc)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
697  trim(var_name)//'_west_t1', &
698  var_bc%west_t1, &
699  indices, global_size, y2_pelist, &
700  is_root_pe, jshift=y_halo)
701 !register west prognostic halo data
702  if (present(var)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
703  trim(var_name)//'_west', &
704  var, indices, global_size, &
705  y2_pelist, is_root_pe, jshift=y_halo)
706 
707 !define east root_pe
708  is_root_pe = .false.
709  if (ie.eq.npx-1 .and. je.eq.npy-1) is_root_pe = .true.
710 !register east halo data in t1
711  if (present(var_bc)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
712  trim(var_name)//'_east_t1', &
713  var_bc%east_t1, &
714  indices, global_size, y1_pelist, &
715  is_root_pe, jshift=y_halo)
716 
717 !reset indices for prognostic variables in the east halo
718  indices(1) = ied-x_halo+1+i_stag
719  indices(2) = ied+i_stag
720 !register east prognostic halo data
721  if (present(var)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
722  trim(var_name)//'_east', &
723  var, indices, global_size, &
724  y1_pelist, is_root_pe, jshift=y_halo, &
725  x_halo=(size(var,1)-x_halo), ishift=-(ie+i_stag))
726 
727 !NORTH & SOUTH
728 !set defaults for north/south halo regions
729  indices(1) = isd
730  indices(2) = ied+i_stag
731  indices(3) = 1
732  indices(4) = y_halo
733  global_size(1) = npx-1+i_stag
734  global_size(2) = y_halo
735 !modify starts and ends for certain pes
736  if (is.eq.1) indices(1) = is
737  if (ie.eq.npx-1) indices(2) = ie+i_stag
738  x_halo_ns = 0
739  if (is.eq.1) x_halo_ns=x_halo
740 
741 !define south root_pe
742  is_root_pe = .false.
743  if (is.eq.1 .and. js.eq.1) is_root_pe = .true.
744 !register south halo data in t1
745  if (present(var_bc)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
746  trim(var_name)//'_south_t1', &
747  var_bc%south_t1, &
748  indices, global_size, x2_pelist, &
749  is_root_pe, x_halo=x_halo_ns)
750 !register south prognostic halo data
751  if (present(var)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
752  trim(var_name)//'_south', &
753  var, indices, global_size, &
754  x2_pelist, is_root_pe, x_halo=x_halo_ns)
755 
756 !define north root_pe
757  is_root_pe = .false.
758  if (ie.eq.npx-1 .and. je.eq.npy-1) is_root_pe = .true.
759 !register north halo data in t1
760  if (present(var_bc)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
761  trim(var_name)//'_north_t1', &
762  var_bc%north_t1, &
763  indices, global_size, x1_pelist, &
764  is_root_pe, x_halo=x_halo_ns)
765 
766 !reset indices for prognostic variables in the north halo
767  indices(3) = jed-y_halo+1+j_stag
768  indices(4) = jed+j_stag
769 !register north prognostic halo data
770  if (present(var)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
771  trim(var_name)//'_north', &
772  var, indices, global_size, &
773  x1_pelist, is_root_pe, x_halo=x_halo_ns, &
774  y_halo=(size(var,2)-y_halo), jshift=-(je+j_stag))
775 
776  end subroutine register_bcs_2d
777 
778 
779  subroutine register_bcs_3d(Atm, BCfile_ne, BCfile_sw, fname_ne, fname_sw, &
780  var_name, var, var_bc, istag, jstag, mandatory)
781  type(fv_atmos_type), intent(in) :: Atm
782  type(restart_file_type), intent(inout) :: BCfile_ne, BCfile_sw
783  character(len=120), intent(in) :: fname_ne, fname_sw
784  character(len=*), intent(in) :: var_name
785  real, dimension(:,:,:), intent(in), optional :: var
786  type(fv_nest_bc_type_3d), intent(in), optional :: var_bc
787  integer, intent(in), optional :: istag, jstag
788  logical, intent(IN), optional :: mandatory
789 
790  integer :: npx, npy, i_stag, j_stag
791  integer :: is, ie, js, je, isd, ied, jsd, jed, n
792  integer :: x_halo, y_halo, x_halo_ns, id_restart
793  integer :: layout(2), global_size(3), indices(4)
794  integer, allocatable, dimension(:) :: x1_pelist, y1_pelist
795  integer, allocatable, dimension(:) :: x2_pelist, y2_pelist
796  logical :: is_root_pe
797 
798  i_stag = 0
799  j_stag = 0
800  if (present(istag)) i_stag = istag
801  if (present(jstag)) j_stag = jstag
802  call mpp_get_global_domain(atm%domain, xsize = npx, ysize = npy, position=corner )
803  call mpp_get_data_domain(atm%domain, isd, ied, jsd, jed )
804  call mpp_get_compute_domain(atm%domain, is, ie, js, je )
805  call mpp_get_layout(atm%domain, layout)
806  allocate (x1_pelist(layout(1)))
807  allocate (y1_pelist(layout(2)))
808  allocate (x2_pelist(layout(1)))
809  allocate (y2_pelist(layout(2)))
810  x_halo = is-isd
811  y_halo = js-jsd
812 ! define west and east pelist
813  do n = 1,layout(2)
814  y1_pelist(n)=mpp_root_pe()+layout(1)*n-1
815  y2_pelist(n)=mpp_root_pe()+layout(1)*(n-1)
816  enddo
817 ! define south and north pelist
818  do n = 1,layout(1)
819  x1_pelist(n)=mpp_root_pe()+layout(1)*(layout(2)-1)+(n-1)
820  x2_pelist(n)=mpp_root_pe()+(n-1)
821  enddo
822 ! declare the pelists inside of mpp (creates the MPI communicator)
823  call mpp_declare_pelist(x1_pelist)
824  call mpp_declare_pelist(x2_pelist)
825  call mpp_declare_pelist(y1_pelist)
826  call mpp_declare_pelist(y2_pelist)
827 
828 !EAST & WEST
829 !set defaults for west/east halo regions
830  indices(1) = 1
831  indices(2) = x_halo
832  indices(3) = jsd
833  indices(4) = jed + j_stag
834  global_size(1) = x_halo
835  global_size(2) = npy-1+2*y_halo + j_stag
836  global_size(3) = atm%npz
837 
838 !define west root_pe
839  is_root_pe = .false.
840  if (is.eq.1 .and. js.eq.1) is_root_pe = .true.
841 !register west halo data in t1
842  if (present(var_bc)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
843  trim(var_name)//'_west_t1', &
844  var_bc%west_t1, &
845  indices, global_size, y2_pelist, &
846  is_root_pe, jshift=y_halo, mandatory=mandatory)
847 !register west prognostic halo data
848  if (present(var)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
849  trim(var_name)//'_west', &
850  var, indices, global_size, &
851  y2_pelist, is_root_pe, jshift=y_halo, mandatory=mandatory)
852 
853 !define east root_pe
854  is_root_pe = .false.
855  if (ie.eq.npx-1 .and. je.eq.npy-1) is_root_pe = .true.
856 !register east halo data in t1
857  if (present(var_bc)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
858  trim(var_name)//'_east_t1', &
859  var_bc%east_t1, &
860  indices, global_size, y1_pelist, &
861  is_root_pe, jshift=y_halo, mandatory=mandatory)
862 
863 !reset indices for prognostic variables in the east halo
864  indices(1) = ied-x_halo+1+i_stag
865  indices(2) = ied+i_stag
866 !register east prognostic halo data
867  if (present(var)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
868  trim(var_name)//'_east', &
869  var, indices, global_size, &
870  y1_pelist, is_root_pe, jshift=y_halo, &
871  x_halo=(size(var,1)-x_halo), ishift=-(ie+i_stag), mandatory=mandatory)
872 
873 !NORTH & SOUTH
874 !set defaults for north/south halo regions
875  indices(1) = isd
876  indices(2) = ied+i_stag
877  indices(3) = 1
878  indices(4) = y_halo
879  global_size(1) = npx-1+i_stag
880  global_size(2) = y_halo
881  global_size(3) = atm%npz
882 !modify starts and ends for certain pes
883  if (is.eq.1) indices(1) = is
884  if (ie.eq.npx-1) indices(2) = ie+i_stag
885  x_halo_ns = 0
886  if (is.eq.1) x_halo_ns=x_halo
887 
888 !define south root_pe
889  is_root_pe = .false.
890  if (is.eq.1 .and. js.eq.1) is_root_pe = .true.
891 !register south halo data in t1
892  if (present(var_bc)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
893  trim(var_name)//'_south_t1', &
894  var_bc%south_t1, &
895  indices, global_size, x2_pelist, &
896  is_root_pe, x_halo=x_halo_ns, mandatory=mandatory)
897 !register south prognostic halo data
898  if (present(var)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
899  trim(var_name)//'_south', &
900  var, indices, global_size, &
901  x2_pelist, is_root_pe, x_halo=x_halo_ns, mandatory=mandatory)
902 
903 !define north root_pe
904  is_root_pe = .false.
905  if (ie.eq.npx-1 .and. je.eq.npy-1) is_root_pe = .true.
906 !register north halo data in t1
907  if (present(var_bc)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
908  trim(var_name)//'_north_t1', &
909  var_bc%north_t1, &
910  indices, global_size, x1_pelist, &
911  is_root_pe, x_halo=x_halo_ns, mandatory=mandatory)
912 
913 !reset indices for prognostic variables in the north halo
914  indices(3) = jed-y_halo+1+j_stag
915  indices(4) = jed+j_stag
916 !register north prognostic halo data
917  if (present(var)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
918  trim(var_name)//'_north', &
919  var, indices, global_size, &
920  x1_pelist, is_root_pe, x_halo=x_halo_ns, &
921  y_halo=(size(var,2)-y_halo), jshift=-(je+j_stag), mandatory=mandatory)
922 
923  end subroutine register_bcs_3d
924 
927  subroutine fv_io_register_restart_bcs(Atm)
928  type(fv_atmos_type), intent(inout) :: Atm
929 
930  integer :: n, ntracers, ntprog, ntdiag
931  character(len=120) :: tname, fname_ne, fname_sw
932 
933  fname_ne = 'fv_BC_ne.res.nc'
934  fname_sw = 'fv_BC_sw.res.nc'
935 
936  ntprog=size(atm%q,4)
937  ntdiag=size(atm%qdiag,4)
938  ntracers=ntprog+ntdiag
939 
940  call set_domain(atm%domain)
941 
942  call register_bcs_2d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
943  fname_ne, fname_sw, 'phis', var=atm%phis)
944  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
945  fname_ne, fname_sw, 'delp', atm%delp, atm%neststruct%delp_BC)
946  do n=1,ntprog
947  call get_tracer_names(model_atmos, n, tname)
948  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
949  fname_ne, fname_sw, trim(tname), atm%q(:,:,:,n), atm%neststruct%q_BC(n), mandatory=.false.)
950  enddo
951  do n=ntprog+1,ntracers
952  call get_tracer_names(model_atmos, n, tname)
953  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
954  fname_ne, fname_sw, trim(tname), var=atm%qdiag(:,:,:,n), mandatory=.false.)
955  enddo
956 #ifndef SW_DYNAMICS
957  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
958  fname_ne, fname_sw, 'pt', atm%pt, atm%neststruct%pt_BC)
959  if ((.not.atm%flagstruct%hydrostatic)) then
960  if (is_master()) print*, 'fv_io_register_restart_BCs: REGISTERING NH BCs'
961  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
962  fname_ne, fname_sw, 'w', atm%w, atm%neststruct%w_BC, mandatory=.false.)
963  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
964  fname_ne, fname_sw, 'delz', var_bc=atm%neststruct%delz_BC, mandatory=.false.)
965 ! fname_ne, fname_sw, 'delz', Atm%delz, Atm%neststruct%delz_BC, mandatory=.false.)
966  endif
967 #ifdef USE_COND
968  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
969  fname_ne, fname_sw,'q_con', var_bc=atm%neststruct%q_con_BC, mandatory=.false.)
970 #ifdef MOIST_CAPPA
971  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
972  fname_ne, fname_sw, 'cappa', var_bc=atm%neststruct%cappa_BC, mandatory=.false.)
973 #endif
974 #endif
975 #endif
976  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
977  fname_ne, fname_sw, 'u', atm%u, atm%neststruct%u_BC, jstag=1)
978  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
979  fname_ne, fname_sw, 'v', atm%v, atm%neststruct%v_BC, istag=1)
980  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
981  fname_ne, fname_sw, 'uc', var_bc=atm%neststruct%uc_BC, istag=1)
982  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
983  fname_ne, fname_sw, 'vc', var_bc=atm%neststruct%vc_BC, jstag=1)
984  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
985  fname_ne, fname_sw, 'divg', var_bc=atm%neststruct%divg_BC, istag=1,jstag=1, mandatory=.false.)
986 
987  return
988  end subroutine fv_io_register_restart_bcs
989 
990 
991  subroutine fv_io_write_bcs(Atm, timestamp)
992  type(fv_atmos_type), intent(inout) :: Atm
993  character(len=*), intent(in), optional :: timestamp
994 
995  call save_restart_border(atm%neststruct%BCfile_ne, timestamp)
996  call save_restart_border(atm%neststruct%BCfile_sw, timestamp)
997 
998  return
999  end subroutine fv_io_write_bcs
1000 
1001 
1002  subroutine fv_io_read_bcs(Atm)
1003  type(fv_atmos_type), intent(inout) :: Atm
1004 
1005  call restore_state_border(atm%neststruct%BCfile_ne)
1006  call restore_state_border(atm%neststruct%BCfile_sw)
1007 
1008  !These do not work yet
1009  !need to modify register_bcs_?d to get ids for registered variables, and then use query_initialized_id
1010  !Atm%neststruct%divg_BC%initialized = field_exist(fname_ne, 'divg_north_t1', Atm%domain)
1011  !Atm%neststruct%w_BC%initialized = field_exist(fname_ne, 'w_north_t1', Atm%domain)
1012  !Atm%neststruct%delz_BC%initialized = field_exist(fname_ne, 'delz_north_t1', Atm%domain)
1013  !if (is_master()) print*, ' BCs: ', Atm%neststruct%divg_BC%initialized, Atm%neststruct%w_BC%initialized, Atm%neststruct%delz_BC%initialized
1014 
1015  return
1016  end subroutine fv_io_read_bcs
1017 
1018 end module fv_io_mod
logical module_is_initialized
Definition: fv_io.F90:124
subroutine, public fv_io_read_bcs(Atm)
Definition: fv_io.F90:1003
The module &#39;fv_mp_mod&#39; is a single program multiple data (SPMD) parallel decompostion/communication m...
Definition: fv_mp_mod.F90:24
subroutine, public fv_io_init()
Initialize the fv core restart facilities.
Definition: fv_io.F90:135
integer pfullid
Definition: fv_io.F90:127
subroutine, public fv_io_read_restart(fv_domain, Atm)
Write the fv core restart quantities.
Definition: fv_io.F90:147
subroutine register_bcs_2d(Atm, BCfile_ne, BCfile_sw, fname_ne, fname_sw, var_name, var, var_bc, istag, jstag)
Definition: fv_io.F90:637
The module &#39;fv_io&#39; contains restart facilities for FV core.
Definition: fv_io.F90:30
subroutine, public fv_io_register_restart(fv_domain, Atm)
The subroutine &#39;fv_io_register_restart&#39; registers model restart fields.
Definition: fv_io.F90:487
subroutine, public fv_io_register_restart_bcs(Atm)
The subroutine &#39;fv_io_register_restart_BCs&#39; registers restarts for nested-grid boundary conditions...
Definition: fv_io.F90:928
subroutine, public read_da_inc(Atm, fv_domain, bd, npz_in, nq, u, v, q, delp, pt, delz, is_in, js_in, ie_in, je_in, isc_in, jsc_in, iec_in, jec_in)
The subroutine &#39;read_da_inc&#39; reads the increments of the diagnostic variables from the DA-generated f...
subroutine register_bcs_3d(Atm, BCfile_ne, BCfile_sw, fname_ne, fname_sw, var_name, var, var_bc, istag, jstag, mandatory)
Definition: fv_io.F90:781
subroutine, public fv_io_read_tracers(fv_domain, Atm)
The subroutine &#39;fv_io_read_tracers&#39; reads in only tracers from restart files.
Definition: fv_io.F90:228
The module &#39;fv_mapz&#39; contains the vertical mapping routines .
Definition: fv_mapz.F90:27
subroutine, public rst_remap(km, kn, is, ie, js, je, isd, ied, jsd, jed, nq, ntp, delp_r, u_r, v_r, w_r, delz_r, pt_r, q_r, qdiag_r, delp, u, v, w, delz, pt, q, qdiag, ak_r, bk_r, ptop, ak, bk, hydrostatic, make_nh, domain, square_domain)
The subroutine &#39;rst_remap&#39; remaps all variables required for a restart.
Definition: fv_mapz.F90:2999
The module &#39;fv_arrays&#39; contains the &#39;fv_atmos_type&#39; and associated datatypes.
Definition: fv_arrays.F90:24
subroutine, public set_external_eta(ak, bk, ptop, ks)
The subroutine &#39;set_external_eta&#39; sets &#39;ptop&#39; (model top) and &#39;ks&#39; (first level of pure pressure coor...
Definition: fv_eta.F90:762
The module &#39;fv_eta&#39; contains routine to set up the reference (Eulerian) pressure coordinate.
Definition: fv_eta.F90:25
integer haloid
Definition: fv_io.F90:127
subroutine, public fv_io_write_bcs(Atm, timestamp)
Definition: fv_io.F90:992
subroutine, public fv_io_exit
Close the fv core restart facilities.
Definition: fv_io.F90:141
&#39;The module &#39;tread_da_increment&#39; contains routines for treating the increments of the prognostic vari...
integer grid_xtdimid
Definition: fv_io.F90:127
subroutine, public fv_io_register_nudge_restart(Atm)
The subroutine &#39;fv_io_register_nudge_restart&#39; registers restarts for SST fields used in HiRAM...
Definition: fv_io.F90:470
integer oneid
Definition: fv_io.F90:128
subroutine, public fv_io_write_restart(Atm, timestamp)
The subroutine &#39;fv_io_write_restart&#39; writes restart files.
Definition: fv_io.F90:609
subroutine, public remap_restart(fv_domain, Atm)
The subroutine &#39;remap_restart&#39; remaps the model state from remap files to a new set of Eulerian coord...
Definition: fv_io.F90:279
integer grid_xtstagdimid
Definition: fv_io.F90:128
integer grid_ytstagdimid
Definition: fv_io.F90:128
integer grid_ytdimid
Definition: fv_io.F90:127