FV3DYCORE  Version1.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: ng, mp_gather, is_master
113  implicit none
114  private
115 
120 
121  logical :: module_is_initialized = .false.
122 
123 
124  integer ::grid_xtdimid, grid_ytdimid, haloid, pfullid !For writing BCs
126 
127 contains
128 
129 
131  subroutine fv_io_init()
133  end subroutine fv_io_init
134 
135 
137  subroutine fv_io_exit
139  end subroutine fv_io_exit
140 
141 
143  subroutine fv_io_read_restart(fv_domain,Atm)
144  type(domain2d), intent(inout) :: fv_domain
145  type(fv_atmos_type), intent(inout) :: atm(:)
146 
147  character(len=64) :: fname, tracer_name
148  character(len=6) :: stile_name
149  integer :: isc, iec, jsc, jec, n, nt, nk, ntracers
150  integer :: ntileme
151  integer :: ks, ntiles
152  real :: ptop
153 
154  character(len=128) :: tracer_longname, tracer_units
155 
156  ntileme = size(atm(:)) ! This will need mods for more than 1 tile per pe
157 
158  call restore_state(atm(1)%Fv_restart)
159  if (atm(1)%flagstruct%external_eta) then
160  call set_external_eta(atm(1)%ak, atm(1)%bk, atm(1)%ptop, atm(1)%ks)
161  endif
162 
163  if ( use_ncep_sst .or. atm(1)%flagstruct%nudge .or. atm(1)%flagstruct%ncep_ic ) then
164  call mpp_error(note, 'READING FROM SST_RESTART DISABLED')
165  !call restore_state(Atm(1)%SST_restart)
166  endif
167 
168 ! fix for single tile runs where you need fv_core.res.nc and fv_core.res.tile1.nc
169  ntiles = mpp_get_ntile_count(fv_domain)
170  if(ntiles == 1 .and. .not. atm(1)%neststruct%nested) then
171  stile_name = '.tile1'
172  else
173  stile_name = ''
174  endif
175 
176  do n = 1, ntileme
177  call restore_state(atm(n)%Fv_tile_restart)
178 
179 !--- restore data for fv_tracer - if it exists
180  fname = 'INPUT/fv_tracer.res'//trim(stile_name)//'.nc'
181  if (file_exist(fname)) then
182  call restore_state(atm(n)%Tra_restart)
183  else
184  call mpp_error(note,'==> Warning from fv_read_restart: Expected file '//trim(fname)//' does not exist')
185  endif
186 
187 !--- restore data for surface winds - if it exists
188  fname = 'INPUT/fv_srf_wnd.res'//trim(stile_name)//'.nc'
189  if (file_exist(fname)) then
190  call restore_state(atm(n)%Rsf_restart)
191  atm(n)%flagstruct%srf_init = .true.
192  else
193  call mpp_error(note,'==> Warning from fv_read_restart: Expected file '//trim(fname)//' does not exist')
194  atm(n)%flagstruct%srf_init = .false.
195  endif
196 
197  if ( atm(n)%flagstruct%fv_land ) then
198 !--- restore data for mg_drag - if it exists
199  fname = 'INPUT/mg_drag.res'//trim(stile_name)//'.nc'
200  if (file_exist(fname)) then
201  call restore_state(atm(n)%Mg_restart)
202  else
203  call mpp_error(note,'==> Warning from fv_read_restart: Expected file '//trim(fname)//' does not exist')
204  endif
205 !--- restore data for fv_land - if it exists
206  fname = 'INPUT/fv_land.res'//trim(stile_name)//'.nc'
207  if (file_exist(fname)) then
208  call restore_state(atm(n)%Lnd_restart)
209  else
210  call mpp_error(note,'==> Warning from fv_read_restart: Expected file '//trim(fname)//' does not exist')
211  endif
212  endif
213 
214  end do
215 
216  return
217 
218  end subroutine fv_io_read_restart
219 
224  subroutine fv_io_read_tracers(fv_domain,Atm)
225  type(domain2d), intent(inout) :: fv_domain
226  type(fv_atmos_type), intent(inout) :: atm(:)
227  integer :: n, ntracers, ntprog, nt, isc, iec, jsc, jec, id_restart
228  character(len=6) :: stile_name
229  character(len=64):: fname, tracer_name
230  type(restart_file_type) :: tra_restart_r
231  integer :: ntiles
232 
233  n = 1
234  isc = atm(n)%bd%isc
235  iec = atm(n)%bd%iec
236  jsc = atm(n)%bd%jsc
237  jec = atm(n)%bd%jec
238  call get_number_tracers(model_atmos, num_tracers=ntracers, num_prog=ntprog)
239 
240 ! fix for single tile runs where you need fv_core.res.nc and fv_core.res.tile1.nc
241  ntiles = mpp_get_ntile_count(fv_domain)
242  if(ntiles == 1 .and. .not. atm(1)%neststruct%nested) then
243  stile_name = '.tile1'
244  else
245  stile_name = ''
246  endif
247 
248  fname = 'fv_tracer.res'//trim(stile_name)//'.nc'
249  do nt = 2, ntprog
250  call get_tracer_names(model_atmos, nt, tracer_name)
251  call set_tracer_profile (model_atmos, nt, atm(n)%q(isc:iec,jsc:jec,:,nt) )
252  id_restart = register_restart_field(tra_restart_r, fname, tracer_name, atm(n)%q(:,:,:,nt), &
253  domain=fv_domain, mandatory=.false., tile_count=n)
254  enddo
255  do nt = ntprog+1, ntracers
256  call get_tracer_names(model_atmos, nt, tracer_name)
257  call set_tracer_profile (model_atmos, nt, atm(n)%qdiag(isc:iec,jsc:jec,:,nt) )
258  id_restart = register_restart_field(tra_restart_r, fname, tracer_name, atm(n)%qdiag(:,:,:,nt), &
259  domain=fv_domain, mandatory=.false., tile_count=n)
260  enddo
261  if (file_exist('INPUT'//trim(fname))) then
262  call restore_state(tra_restart_r)
263  call free_restart_type(tra_restart_r)
264  else
265  call mpp_error(note,'==> Warning from fv_io_read_tracers: Expected file '//trim(fname)//' does not exist')
266  endif
267 
268  return
269 
270  end subroutine fv_io_read_tracers
271 
275  subroutine remap_restart(fv_domain,Atm)
277 
278  type(domain2d), intent(inout) :: fv_domain
279  type(fv_atmos_type), intent(inout) :: atm(:)
280 
281  character(len=64) :: fname, tracer_name
282  character(len=6) :: stile_name
283  integer :: isc, iec, jsc, jec, n, nt, nk, ntracers, ntprog, ntdiag
284  integer :: isd, ied, jsd, jed
285  integer :: ntiles
286  type(restart_file_type) :: fv_restart_r, fv_tile_restart_r, tra_restart_r
287  integer :: id_restart
288 
289 !
290 !-------------------------------------------------------------------------
291  real, allocatable:: ak_r(:), bk_r(:)
292  real, allocatable:: u_r(:,:,:), v_r(:,:,:), pt_r(:,:,:), delp_r(:,:,:)
293  real, allocatable:: w_r(:,:,:), delz_r(:,:,:), ze0_r(:,:,:)
294  real, allocatable:: q_r(:,:,:,:), qdiag_r(:,:,:,:)
295 !-------------------------------------------------------------------------
296  integer npz, npz_rst, ng
297 
298  npz = atm(1)%npz ! run time z dimension
299  npz_rst = atm(1)%flagstruct%npz_rst ! restart z dimension
300  isc = atm(1)%bd%isc; iec = atm(1)%bd%iec; jsc = atm(1)%bd%jsc; jec = atm(1)%bd%jec
301  ng = atm(1)%ng
302 
303  isd = isc - ng; ied = iec + ng
304  jsd = jsc - ng; jed = jec + ng
305 
306 
307 ! call get_number_tracers(MODEL_ATMOS, num_tracers=ntracers)
308  ntprog = size(atm(1)%q,4) ! Temporary until we get tracer manager integrated
309  ntdiag = size(atm(1)%qdiag,4)
310  ntracers = ntprog+ntdiag
311 
312 ! ntileMe = size(Atm(:)) ! This will have to be modified for mult tiles per PE
313 
314 
315 ! Allocate arrays for reading old restart file:
316  allocate ( ak_r(npz_rst+1) )
317  allocate ( bk_r(npz_rst+1) )
318 
319  allocate ( u_r(isc:iec, jsc:jec+1,npz_rst) )
320  allocate ( v_r(isc:iec+1,jsc:jec ,npz_rst) )
321 
322  allocate ( pt_r(isc:iec, jsc:jec, npz_rst) )
323  allocate ( delp_r(isc:iec, jsc:jec, npz_rst) )
324  allocate ( q_r(isc:iec, jsc:jec, npz_rst, ntprog) )
325  allocate (qdiag_r(isc:iec, jsc:jec, npz_rst, ntprog+1:ntracers) )
326 
327  if ( (.not.atm(1)%flagstruct%hydrostatic) .and. (.not.atm(1)%flagstruct%make_nh) ) then
328  allocate ( w_r(isc:iec, jsc:jec, npz_rst) )
329  allocate ( delz_r(isc:iec, jsc:jec, npz_rst) )
330  if ( atm(1)%flagstruct%hybrid_z ) &
331  allocate ( ze0_r(isc:iec, jsc:jec, npz_rst+1) )
332  endif
333 
334  fname = 'fv_core.res.nc'
335  id_restart = register_restart_field(fv_restart_r, fname, 'ak', ak_r(:), no_domain=.true.)
336  id_restart = register_restart_field(fv_restart_r, fname, 'bk', bk_r(:), no_domain=.true.)
337  call restore_state(fv_restart_r)
338  call free_restart_type(fv_restart_r)
339 
340 ! fix for single tile runs where you need fv_core.res.nc and fv_core.res.tile1.nc
341  ntiles = mpp_get_ntile_count(fv_domain)
342  if(ntiles == 1 .and. .not. atm(1)%neststruct%nested) then
343  stile_name = '.tile1'
344  else
345  stile_name = ''
346  endif
347 
348 ! do n = 1, ntileMe
349  n = 1
350  fname = 'fv_core.res'//trim(stile_name)//'.nc'
351  id_restart = register_restart_field(fv_tile_restart_r, fname, 'u', u_r, &
352  domain=fv_domain, position=north,tile_count=n)
353  id_restart = register_restart_field(fv_tile_restart_r, fname, 'v', v_r, &
354  domain=fv_domain, position=east,tile_count=n)
355  if (.not.atm(n)%flagstruct%hydrostatic) then
356  id_restart = register_restart_field(fv_tile_restart_r, fname, 'W', w_r, &
357  domain=fv_domain, mandatory=.false., tile_count=n)
358  id_restart = register_restart_field(fv_tile_restart_r, fname, 'DZ', delz_r, &
359  domain=fv_domain, mandatory=.false., tile_count=n)
360  if ( atm(n)%flagstruct%hybrid_z ) then
361  id_restart = register_restart_field(fv_tile_restart_r, fname, 'ZE0', ze0_r, &
362  domain=fv_domain, mandatory=.false., tile_count=n)
363  endif
364  endif
365  id_restart = register_restart_field(fv_tile_restart_r, fname, 'T', pt_r, &
366  domain=fv_domain, tile_count=n)
367  id_restart = register_restart_field(fv_tile_restart_r, fname, 'delp', delp_r, &
368  domain=fv_domain, tile_count=n)
369  id_restart = register_restart_field(fv_tile_restart_r, fname, 'phis', atm(n)%phis, &
370  domain=fv_domain, tile_count=n)
371  call restore_state(fv_tile_restart_r)
372  call free_restart_type(fv_tile_restart_r)
373  fname = 'INPUT/fv_srf_wnd.res'//trim(stile_name)//'.nc'
374  if (file_exist(fname)) then
375  call restore_state(atm(n)%Rsf_restart)
376  atm(n)%flagstruct%srf_init = .true.
377  else
378  call mpp_error(note,'==> Warning from remap_restart: Expected file '//trim(fname)//' does not exist')
379  atm(n)%flagstruct%srf_init = .false.
380  endif
381 
382  if ( atm(n)%flagstruct%fv_land ) then
383 !--- restore data for mg_drag - if it exists
384  fname = 'INPUT/mg_drag.res'//trim(stile_name)//'.nc'
385  if (file_exist(fname)) then
386  call restore_state(atm(n)%Mg_restart)
387  else
388  call mpp_error(note,'==> Warning from remap_restart: Expected file '//trim(fname)//' does not exist')
389  endif
390 !--- restore data for fv_land - if it exists
391  fname = 'INPUT/fv_land.res'//trim(stile_name)//'.nc'
392  if (file_exist(fname)) then
393  call restore_state(atm(n)%Lnd_restart)
394  else
395  call mpp_error(note,'==> Warning from remap_restart: Expected file '//trim(fname)//' does not exist')
396  endif
397  endif
398 
399  fname = 'fv_tracer.res'//trim(stile_name)//'.nc'
400  if (file_exist('INPUT'//trim(fname))) then
401  do nt = 1, ntprog
402  call get_tracer_names(model_atmos, nt, tracer_name)
403  call set_tracer_profile (model_atmos, nt, q_r(isc:iec,jsc:jec,:,nt) )
404  id_restart = register_restart_field(tra_restart_r, fname, tracer_name, q_r(:,:,:,nt), &
405  domain=fv_domain, mandatory=.false., tile_count=n)
406  enddo
407  do nt = ntprog+1, ntracers
408  call get_tracer_names(model_atmos, nt, tracer_name)
409  call set_tracer_profile (model_atmos, nt, qdiag_r(isc:iec,jsc:jec,:,nt) )
410  id_restart = register_restart_field(tra_restart_r, fname, tracer_name, qdiag_r(:,:,:,nt), &
411  domain=fv_domain, mandatory=.false., tile_count=n)
412  enddo
413  call restore_state(tra_restart_r)
414  call free_restart_type(tra_restart_r)
415  else
416  call mpp_error(note,'==> Warning from remap_restart: Expected file '//trim(fname)//' does not exist')
417  endif
418 
419  call rst_remap(npz_rst, npz, isc, iec, jsc, jec, isd, ied, jsd, jed, ntracers, ntprog, &
420  delp_r, u_r, v_r, w_r, delz_r, pt_r, q_r, qdiag_r,&
421  atm(n)%delp, atm(n)%u, atm(n)%v, atm(n)%w, atm(n)%delz, atm(n)%pt, atm(n)%q, &
422  atm(n)%qdiag, ak_r, bk_r, atm(n)%ptop, atm(n)%ak, atm(n)%bk, &
423  atm(n)%flagstruct%hydrostatic, atm(n)%flagstruct%make_nh, atm(n)%domain, &
424  atm(n)%gridstruct%square_domain)
425  !end do
426 
427  deallocate( ak_r )
428  deallocate( bk_r )
429  deallocate( u_r )
430  deallocate( v_r )
431  deallocate( pt_r )
432  deallocate( delp_r )
433  deallocate( q_r )
434  deallocate( qdiag_r )
435 
436  if ( (.not.atm(1)%flagstruct%hydrostatic) .and. (.not.atm(1)%flagstruct%make_nh) ) then
437  deallocate ( w_r )
438  deallocate ( delz_r )
439  if ( atm(1)%flagstruct%hybrid_z ) deallocate ( ze0_r )
440  endif
441 
442  end subroutine remap_restart
443 
447  subroutine fv_io_register_nudge_restart(Atm)
448  type(fv_atmos_type), intent(inout) :: atm(:)
449  character(len=64) :: fname
450  integer :: id_restart
451 
452 ! use_ncep_sst may not be initialized at this point?
453  call mpp_error(note, 'READING FROM SST_restart DISABLED')
454 !!$ if ( use_ncep_sst .or. Atm(1)%nudge .or. Atm(1)%ncep_ic ) then
455 !!$ fname = 'sst_ncep.res.nc'
456 !!$ id_restart = register_restart_field(Atm(1)%SST_restart, fname, 'sst_ncep', sst_ncep)
457 !!$ id_restart = register_restart_field(Atm(1)%SST_restart, fname, 'sst_anom', sst_anom)
458 !!$ endif
459 
460  end subroutine fv_io_register_nudge_restart
461 
463  subroutine fv_io_register_restart(fv_domain,Atm)
464  type(domain2d), intent(inout) :: fv_domain
465  type(fv_atmos_type), intent(inout) :: atm(:)
466 
467  character(len=64) :: fname, tracer_name
468  character(len=6) :: gn, stile_name
469  integer :: id_restart
470  integer :: n, nt, ntracers, ntprog, ntdiag, ntileme, ntiles
471 
472  ntileme = size(atm(:))
473  ntprog = size(atm(1)%q,4)
474  ntdiag = size(atm(1)%qdiag,4)
475  ntracers = ntprog+ntdiag
476 
477 !--- set the 'nestXX' appendix for all files using fms_io
478  if (atm(1)%grid_number > 1) then
479  write(gn,'(A4, I2.2)') "nest", atm(1)%grid_number
480  else
481  gn = ''
482  end if
483  call set_filename_appendix(gn)
484 
485 !--- fix for single tile runs where you need fv_core.res.nc and fv_core.res.tile1.nc
486  ntiles = mpp_get_ntile_count(fv_domain)
487  if(ntiles == 1 .and. .not. atm(1)%neststruct%nested) then
488  stile_name = '.tile1'
489  else
490  stile_name = ''
491  endif
492 
493 ! use_ncep_sst may not be initialized at this point?
494 #ifndef DYCORE_SOLO
495  call mpp_error(note, 'READING FROM SST_RESTART DISABLED')
496 !!$ if ( use_ncep_sst .or. Atm(1)%flagstruct%nudge .or. Atm(1)%flagstruct%ncep_ic ) then
497 !!$ fname = 'sst_ncep'//trim(gn)//'.res.nc'
498 !!$ id_restart = register_restart_field(Atm(1)%SST_restart, fname, 'sst_ncep', sst_ncep)
499 !!$ id_restart = register_restart_field(Atm(1)%SST_restart, fname, 'sst_anom', sst_anom)
500 !!$ endif
501 #endif
502 
503  fname = 'fv_core.res.nc'
504  id_restart = register_restart_field(atm(1)%Fv_restart, fname, 'ak', atm(1)%ak(:), no_domain=.true.)
505  id_restart = register_restart_field(atm(1)%Fv_restart, fname, 'bk', atm(1)%bk(:), no_domain=.true.)
506 
507  do n = 1, ntileme
508  fname = 'fv_core.res'//trim(stile_name)//'.nc'
509  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'u', atm(n)%u, &
510  domain=fv_domain, position=north,tile_count=n)
511  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'v', atm(n)%v, &
512  domain=fv_domain, position=east,tile_count=n)
513  if (.not.atm(n)%flagstruct%hydrostatic) then
514  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'W', atm(n)%w, &
515  domain=fv_domain, mandatory=.false., tile_count=n)
516  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'DZ', atm(n)%delz, &
517  domain=fv_domain, mandatory=.false., tile_count=n)
518  if ( atm(n)%flagstruct%hybrid_z ) then
519  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'ZE0', atm(n)%ze0, &
520  domain=fv_domain, mandatory=.false., tile_count=n)
521  endif
522  endif
523  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'T', atm(n)%pt, &
524  domain=fv_domain, tile_count=n)
525  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'delp', atm(n)%delp, &
526  domain=fv_domain, tile_count=n)
527  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'phis', atm(n)%phis, &
528  domain=fv_domain, tile_count=n)
529 
530  !--- include agrid winds in restarts for use in data assimilation
531  if (atm(n)%flagstruct%agrid_vel_rst) then
532  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'ua', atm(n)%ua, &
533  domain=fv_domain, tile_count=n, mandatory=.false.)
534  id_restart = register_restart_field(atm(n)%Fv_tile_restart, fname, 'va', atm(n)%va, &
535  domain=fv_domain, tile_count=n, mandatory=.false.)
536  endif
537 
538  fname = 'fv_srf_wnd.res'//trim(stile_name)//'.nc'
539  id_restart = register_restart_field(atm(n)%Rsf_restart, fname, 'u_srf', atm(n)%u_srf, &
540  domain=fv_domain, tile_count=n)
541  id_restart = register_restart_field(atm(n)%Rsf_restart, fname, 'v_srf', atm(n)%v_srf, &
542  domain=fv_domain, tile_count=n)
543 #ifdef SIM_PHYS
544  id_restart = register_restart_field(rsf_restart(n), fname, 'ts', atm(n)%ts, &
545  domain=fv_domain, tile_count=n)
546 #endif
547 
548  if ( atm(n)%flagstruct%fv_land ) then
549  !-------------------------------------------------------------------------------------------------
550  ! Optional terrain deviation (sgh) and land fraction (oro)
551  fname = 'mg_drag.res'//trim(stile_name)//'.nc'
552  id_restart = register_restart_field(atm(n)%Mg_restart, fname, 'ghprime', atm(n)%sgh, &
553  domain=fv_domain, tile_count=n)
554 
555  fname = 'fv_land.res'//trim(stile_name)//'.nc'
556  id_restart = register_restart_field(atm(n)%Lnd_restart, fname, 'oro', atm(n)%oro, &
557  domain=fv_domain, tile_count=n)
558  endif
559 
560  fname = 'fv_tracer.res'//trim(stile_name)//'.nc'
561  do nt = 1, ntprog
562  call get_tracer_names(model_atmos, nt, tracer_name)
563  ! set all tracers to an initial profile value
564  call set_tracer_profile (model_atmos, nt, atm(n)%q(:,:,:,nt) )
565  id_restart = register_restart_field(atm(n)%Tra_restart, fname, tracer_name, atm(n)%q(:,:,:,nt), &
566  domain=fv_domain, mandatory=.false., tile_count=n)
567  enddo
568  do nt = ntprog+1, ntracers
569  call get_tracer_names(model_atmos, nt, tracer_name)
570  ! set all tracers to an initial profile value
571  call set_tracer_profile (model_atmos, nt, atm(n)%qdiag(:,:,:,nt) )
572  id_restart = register_restart_field(atm(n)%Tra_restart, fname, tracer_name, atm(n)%qdiag(:,:,:,nt), &
573  domain=fv_domain, mandatory=.false., tile_count=n)
574  enddo
575 
576  enddo
577 
578  end subroutine fv_io_register_restart
579 
581  subroutine fv_io_write_restart(Atm, grids_on_this_pe, timestamp)
583  type(fv_atmos_type), intent(inout) :: atm(:)
584  logical, intent(IN) :: grids_on_this_pe(:)
585  character(len=*), optional, intent(in) :: timestamp
586  integer :: n, ntileme
587 
588  ntileme = size(atm(:)) ! This will need mods for more than 1 tile per pe
589 
590  if ( use_ncep_sst .or. atm(1)%flagstruct%nudge .or. atm(1)%flagstruct%ncep_ic ) then
591  call mpp_error(note, 'READING FROM SST_RESTART DISABLED')
592  !call save_restart(Atm(1)%SST_restart, timestamp)
593  endif
594 
595  do n = 1, ntileme
596  if (.not. grids_on_this_pe(n)) cycle
597 
598  if ( (use_ncep_sst .or. atm(n)%flagstruct%nudge) .and. .not. atm(n)%gridstruct%nested ) then
599  call save_restart(atm(n)%SST_restart, timestamp)
600  endif
601 
602  call save_restart(atm(n)%Fv_restart, timestamp)
603  call save_restart(atm(n)%Fv_tile_restart, timestamp)
604  call save_restart(atm(n)%Rsf_restart, timestamp)
605 
606  if ( atm(n)%flagstruct%fv_land ) then
607  call save_restart(atm(n)%Mg_restart, timestamp)
608  call save_restart(atm(n)%Lnd_restart, timestamp)
609  endif
610 
611  call save_restart(atm(n)%Tra_restart, timestamp)
612 
613  end do
614 
615  end subroutine fv_io_write_restart
616 
617  subroutine register_bcs_2d(Atm, BCfile_ne, BCfile_sw, fname_ne, fname_sw, &
618  var_name, var, var_bc, istag, jstag)
619  type(fv_atmos_type), intent(in) :: Atm
620  type(restart_file_type), intent(inout) :: BCfile_ne, BCfile_sw
621  character(len=120), intent(in) :: fname_ne, fname_sw
622  character(len=*), intent(in) :: var_name
623  real, dimension(:,:), intent(in), optional :: var
624  type(fv_nest_BC_type_3D), intent(in), optional :: var_bc
625  integer, intent(in), optional :: istag, jstag
626 
627  integer :: npx, npy, i_stag, j_stag
628  integer :: is, ie, js, je, isd, ied, jsd, jed, n
629  integer :: x_halo, y_halo, x_halo_ns, id_restart
630  integer :: layout(2), global_size(2), indices(4)
631  integer, allocatable, dimension(:) :: x1_pelist, y1_pelist
632  integer, allocatable, dimension(:) :: x2_pelist, y2_pelist
633  logical :: is_root_pe
634 
635  i_stag = 0
636  j_stag = 0
637  if (present(istag)) i_stag = i_stag
638  if (present(jstag)) j_stag = j_stag
639  call mpp_get_global_domain(atm%domain, xsize = npx, ysize = npy, position=corner )
640  call mpp_get_data_domain(atm%domain, isd, ied, jsd, jed )
641  call mpp_get_compute_domain(atm%domain, is, ie, js, je )
642  call mpp_get_layout(atm%domain, layout)
643  allocate (x1_pelist(layout(1)))
644  allocate (y1_pelist(layout(2)))
645  allocate (x2_pelist(layout(1)))
646  allocate (y2_pelist(layout(2)))
647  x_halo = is-isd
648  y_halo = js-jsd
649 ! define west and east pelist
650  do n = 1,layout(2)
651  y1_pelist(n)=mpp_root_pe()+layout(1)*n-1
652  y2_pelist(n)=mpp_root_pe()+layout(1)*(n-1)
653  enddo
654 ! define south and north pelist
655  do n = 1,layout(1)
656  x1_pelist(n)=mpp_root_pe()+layout(1)*(layout(2)-1)+(n-1)
657  x2_pelist(n)=mpp_root_pe()+(n-1)
658  enddo
659 ! declare the pelists inside of mpp (creates the MPI communicator)
660  call mpp_declare_pelist(x1_pelist)
661  call mpp_declare_pelist(x2_pelist)
662  call mpp_declare_pelist(y1_pelist)
663  call mpp_declare_pelist(y2_pelist)
664 
665 !EAST & WEST
666 !set defaults for west/east halo regions
667  indices(1) = 1
668  indices(2) = x_halo
669  indices(3) = jsd
670  indices(4) = jed+j_stag
671  global_size(1) = x_halo
672  global_size(2) = npy-1+2*y_halo+j_stag
673 
674 !define west root_pe
675  is_root_pe = .false.
676  if (is.eq.1 .and. js.eq.1) is_root_pe = .true.
677 !register west halo data in t1
678  if (present(var_bc)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
679  trim(var_name)//'_west_t1', &
680  var_bc%west_t1, &
681  indices, global_size, y2_pelist, &
682  is_root_pe, jshift=y_halo)
683 !register west prognostic halo data
684  if (present(var)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
685  trim(var_name)//'_west', &
686  var, indices, global_size, &
687  y2_pelist, is_root_pe, jshift=y_halo)
688 
689 !define east root_pe
690  is_root_pe = .false.
691  if (ie.eq.npx-1 .and. je.eq.npy-1) is_root_pe = .true.
692 !register east halo data in t1
693  if (present(var_bc)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
694  trim(var_name)//'_east_t1', &
695  var_bc%east_t1, &
696  indices, global_size, y1_pelist, &
697  is_root_pe, jshift=y_halo)
698 
699 !reset indices for prognostic variables in the east halo
700  indices(1) = ied-x_halo+1+i_stag
701  indices(2) = ied+i_stag
702 !register east prognostic halo data
703  if (present(var)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
704  trim(var_name)//'_east', &
705  var, indices, global_size, &
706  y1_pelist, is_root_pe, jshift=y_halo, &
707  x_halo=(size(var,1)-x_halo), ishift=-(ie+i_stag))
708 
709 !NORTH & SOUTH
710 !set defaults for north/south halo regions
711  indices(1) = isd
712  indices(2) = ied+i_stag
713  indices(3) = 1
714  indices(4) = y_halo
715  global_size(1) = npx-1+i_stag
716  global_size(2) = y_halo
717 !modify starts and ends for certain pes
718  if (is.eq.1) indices(1) = is
719  if (ie.eq.npx-1) indices(2) = ie+i_stag
720  x_halo_ns = 0
721  if (is.eq.1) x_halo_ns=x_halo
722 
723 !define south root_pe
724  is_root_pe = .false.
725  if (is.eq.1 .and. js.eq.1) is_root_pe = .true.
726 !register south halo data in t1
727  if (present(var_bc)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
728  trim(var_name)//'_south_t1', &
729  var_bc%south_t1, &
730  indices, global_size, x2_pelist, &
731  is_root_pe, x_halo=x_halo_ns)
732 !register south prognostic halo data
733  if (present(var)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
734  trim(var_name)//'_south', &
735  var, indices, global_size, &
736  x2_pelist, is_root_pe, x_halo=x_halo_ns)
737 
738 !define north root_pe
739  is_root_pe = .false.
740  if (ie.eq.npx-1 .and. je.eq.npy-1) is_root_pe = .true.
741 !register north halo data in t1
742  if (present(var_bc)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
743  trim(var_name)//'_north_t1', &
744  var_bc%north_t1, &
745  indices, global_size, x1_pelist, &
746  is_root_pe, x_halo=x_halo_ns)
747 
748 !reset indices for prognostic variables in the north halo
749  indices(3) = jed-y_halo+1+j_stag
750  indices(4) = jed+j_stag
751 !register north prognostic halo data
752  if (present(var)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
753  trim(var_name)//'_north', &
754  var, indices, global_size, &
755  x1_pelist, is_root_pe, x_halo=x_halo_ns, &
756  y_halo=(size(var,2)-y_halo), jshift=-(je+j_stag))
757 
758  end subroutine register_bcs_2d
759 
760 
761  subroutine register_bcs_3d(Atm, BCfile_ne, BCfile_sw, fname_ne, fname_sw, &
762  var_name, var, var_bc, istag, jstag, mandatory)
763  type(fv_atmos_type), intent(in) :: Atm
764  type(restart_file_type), intent(inout) :: BCfile_ne, BCfile_sw
765  character(len=120), intent(in) :: fname_ne, fname_sw
766  character(len=*), intent(in) :: var_name
767  real, dimension(:,:,:), intent(in), optional :: var
768  type(fv_nest_BC_type_3D), intent(in), optional :: var_bc
769  integer, intent(in), optional :: istag, jstag
770  logical, intent(IN), optional :: mandatory
771 
772  integer :: npx, npy, i_stag, j_stag
773  integer :: is, ie, js, je, isd, ied, jsd, jed, n
774  integer :: x_halo, y_halo, x_halo_ns, id_restart
775  integer :: layout(2), global_size(3), indices(4)
776  integer, allocatable, dimension(:) :: x1_pelist, y1_pelist
777  integer, allocatable, dimension(:) :: x2_pelist, y2_pelist
778  logical :: is_root_pe
779 
780  i_stag = 0
781  j_stag = 0
782  if (present(istag)) i_stag = istag
783  if (present(jstag)) j_stag = jstag
784  call mpp_get_global_domain(atm%domain, xsize = npx, ysize = npy, position=corner )
785  call mpp_get_data_domain(atm%domain, isd, ied, jsd, jed )
786  call mpp_get_compute_domain(atm%domain, is, ie, js, je )
787  call mpp_get_layout(atm%domain, layout)
788  allocate (x1_pelist(layout(1)))
789  allocate (y1_pelist(layout(2)))
790  allocate (x2_pelist(layout(1)))
791  allocate (y2_pelist(layout(2)))
792  x_halo = is-isd
793  y_halo = js-jsd
794 ! define west and east pelist
795  do n = 1,layout(2)
796  y1_pelist(n)=mpp_root_pe()+layout(1)*n-1
797  y2_pelist(n)=mpp_root_pe()+layout(1)*(n-1)
798  enddo
799 ! define south and north pelist
800  do n = 1,layout(1)
801  x1_pelist(n)=mpp_root_pe()+layout(1)*(layout(2)-1)+(n-1)
802  x2_pelist(n)=mpp_root_pe()+(n-1)
803  enddo
804 ! declare the pelists inside of mpp (creates the MPI communicator)
805  call mpp_declare_pelist(x1_pelist)
806  call mpp_declare_pelist(x2_pelist)
807  call mpp_declare_pelist(y1_pelist)
808  call mpp_declare_pelist(y2_pelist)
809 
810 !EAST & WEST
811 !set defaults for west/east halo regions
812  indices(1) = 1
813  indices(2) = x_halo
814  indices(3) = jsd
815  indices(4) = jed + j_stag
816  global_size(1) = x_halo
817  global_size(2) = npy-1+2*y_halo + j_stag
818  global_size(3) = atm%npz
819 
820 !define west root_pe
821  is_root_pe = .false.
822  if (is.eq.1 .and. js.eq.1) is_root_pe = .true.
823 !register west halo data in t1
824  if (present(var_bc)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
825  trim(var_name)//'_west_t1', &
826  var_bc%west_t1, &
827  indices, global_size, y2_pelist, &
828  is_root_pe, jshift=y_halo, mandatory=mandatory)
829 !register west prognostic halo data
830  if (present(var)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
831  trim(var_name)//'_west', &
832  var, indices, global_size, &
833  y2_pelist, is_root_pe, jshift=y_halo, mandatory=mandatory)
834 
835 !define east root_pe
836  is_root_pe = .false.
837  if (ie.eq.npx-1 .and. je.eq.npy-1) is_root_pe = .true.
838 !register east halo data in t1
839  if (present(var_bc)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
840  trim(var_name)//'_east_t1', &
841  var_bc%east_t1, &
842  indices, global_size, y1_pelist, &
843  is_root_pe, jshift=y_halo, mandatory=mandatory)
844 
845 !reset indices for prognostic variables in the east halo
846  indices(1) = ied-x_halo+1+i_stag
847  indices(2) = ied+i_stag
848 !register east prognostic halo data
849  if (present(var)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
850  trim(var_name)//'_east', &
851  var, indices, global_size, &
852  y1_pelist, is_root_pe, jshift=y_halo, &
853  x_halo=(size(var,1)-x_halo), ishift=-(ie+i_stag), mandatory=mandatory)
854 
855 !NORTH & SOUTH
856 !set defaults for north/south halo regions
857  indices(1) = isd
858  indices(2) = ied+i_stag
859  indices(3) = 1
860  indices(4) = y_halo
861  global_size(1) = npx-1+i_stag
862  global_size(2) = y_halo
863  global_size(3) = atm%npz
864 !modify starts and ends for certain pes
865  if (is.eq.1) indices(1) = is
866  if (ie.eq.npx-1) indices(2) = ie+i_stag
867  x_halo_ns = 0
868  if (is.eq.1) x_halo_ns=x_halo
869 
870 !define south root_pe
871  is_root_pe = .false.
872  if (is.eq.1 .and. js.eq.1) is_root_pe = .true.
873 !register south halo data in t1
874  if (present(var_bc)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
875  trim(var_name)//'_south_t1', &
876  var_bc%south_t1, &
877  indices, global_size, x2_pelist, &
878  is_root_pe, x_halo=x_halo_ns, mandatory=mandatory)
879 !register south prognostic halo data
880  if (present(var)) id_restart = register_restart_field(bcfile_sw, trim(fname_sw), &
881  trim(var_name)//'_south', &
882  var, indices, global_size, &
883  x2_pelist, is_root_pe, x_halo=x_halo_ns, mandatory=mandatory)
884 
885 !define north root_pe
886  is_root_pe = .false.
887  if (ie.eq.npx-1 .and. je.eq.npy-1) is_root_pe = .true.
888 !register north halo data in t1
889  if (present(var_bc)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
890  trim(var_name)//'_north_t1', &
891  var_bc%north_t1, &
892  indices, global_size, x1_pelist, &
893  is_root_pe, x_halo=x_halo_ns, mandatory=mandatory)
894 
895 !reset indices for prognostic variables in the north halo
896  indices(3) = jed-y_halo+1+j_stag
897  indices(4) = jed+j_stag
898 !register north prognostic halo data
899  if (present(var)) id_restart = register_restart_field(bcfile_ne, trim(fname_ne), &
900  trim(var_name)//'_north', &
901  var, indices, global_size, &
902  x1_pelist, is_root_pe, x_halo=x_halo_ns, &
903  y_halo=(size(var,2)-y_halo), jshift=-(je+j_stag), mandatory=mandatory)
904 
905  end subroutine register_bcs_3d
906 
909  subroutine fv_io_register_restart_bcs(Atm)
910  type(fv_atmos_type), intent(inout) :: atm
911 
912  integer :: n, ntracers, ntprog, ntdiag
913  character(len=120) :: tname, fname_ne, fname_sw
914 
915  fname_ne = 'fv_BC_ne.res.nc'
916  fname_sw = 'fv_BC_sw.res.nc'
917 
918  ntprog=size(atm%q,4)
919  ntdiag=size(atm%qdiag,4)
920  ntracers=ntprog+ntdiag
921 
922  call set_domain(atm%domain)
923 
924  call register_bcs_2d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
925  fname_ne, fname_sw, 'phis', var=atm%phis)
926  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
927  fname_ne, fname_sw, 'delp', atm%delp, atm%neststruct%delp_BC)
928  do n=1,ntprog
929  call get_tracer_names(model_atmos, n, tname)
930  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
931  fname_ne, fname_sw, trim(tname), atm%q(:,:,:,n), atm%neststruct%q_BC(n), mandatory=.false.)
932  enddo
933  do n=ntprog+1,ntracers
934  call get_tracer_names(model_atmos, n, tname)
935  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
936  fname_ne, fname_sw, trim(tname), var=atm%qdiag(:,:,:,n), mandatory=.false.)
937  enddo
938 #ifndef SW_DYNAMICS
939  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
940  fname_ne, fname_sw, 'pt', atm%pt, atm%neststruct%pt_BC)
941  if ((.not.atm%flagstruct%hydrostatic) .and. (.not.atm%flagstruct%make_nh)) then
942  if (is_master()) print*, 'fv_io_register_restart_BCs: REGISTERING NH BCs', atm%flagstruct%hydrostatic, atm%flagstruct%make_nh
943  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
944  fname_ne, fname_sw, 'w', atm%w, atm%neststruct%w_BC, mandatory=.false.)
945  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
946  fname_ne, fname_sw, 'delz', atm%delz, atm%neststruct%delz_BC, mandatory=.false.)
947  endif
948 #ifdef USE_COND
949  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
950  fname_ne, fname_sw,'q_con', var_bc=atm%neststruct%q_con_BC, mandatory=.false.)
951 #ifdef MOIST_CAPPA
952  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
953  fname_ne, fname_sw, 'cappa', var_bc=atm%neststruct%cappa_BC, mandatory=.false.)
954 #endif
955 #endif
956 #endif
957  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
958  fname_ne, fname_sw, 'u', atm%u, atm%neststruct%u_BC, jstag=1)
959  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
960  fname_ne, fname_sw, 'v', atm%v, atm%neststruct%v_BC, istag=1)
961  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
962  fname_ne, fname_sw, 'uc', var_bc=atm%neststruct%uc_BC, istag=1)
963  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
964  fname_ne, fname_sw, 'vc', var_bc=atm%neststruct%vc_BC, jstag=1)
965  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
966  fname_ne, fname_sw, 'divg', var_bc=atm%neststruct%divg_BC, istag=1,jstag=1, mandatory=.false.)
967  atm%neststruct%divg_BC%initialized = field_exist(fname_ne, 'divg_north_t1', atm%domain)
968 
969 
970  return
971  end subroutine fv_io_register_restart_bcs
972 
973 
974  subroutine fv_io_register_restart_bcs_nh(Atm)
975  type(fv_atmos_type), intent(inout) :: atm
976 
977  integer :: n
978  character(len=120) :: tname, fname_ne, fname_sw
979 
980  fname_ne = 'fv_BC_ne.res.nc'
981  fname_sw = 'fv_BC_sw.res.nc'
982 
983  call set_domain(atm%domain)
984 
985  if (is_master()) print*, 'fv_io_register_restart_BCs_NH: REGISTERING NH BCs', atm%flagstruct%hydrostatic, atm%flagstruct%make_nh
986 #ifndef SW_DYNAMICS
987  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
988  fname_ne, fname_sw, 'w', atm%w, atm%neststruct%w_BC)
989  call register_bcs_3d(atm, atm%neststruct%BCfile_ne, atm%neststruct%BCfile_sw, &
990  fname_ne, fname_sw, 'delz', atm%delz, atm%neststruct%delz_BC)
991 #endif
992 
993  return
994  end subroutine fv_io_register_restart_bcs_nh
995 
996 
998  subroutine fv_io_write_bcs(Atm, timestamp)
999  type(fv_atmos_type), intent(inout) :: atm
1000  character(len=*), intent(in), optional :: timestamp
1001 
1002  call save_restart_border(atm%neststruct%BCfile_ne, timestamp)
1003  call save_restart_border(atm%neststruct%BCfile_sw, timestamp)
1004 
1005  return
1006  end subroutine fv_io_write_bcs
1007 
1009  subroutine fv_io_read_bcs(Atm)
1010  type(fv_atmos_type), intent(inout) :: atm
1011 
1012  call restore_state_border(atm%neststruct%BCfile_ne)
1013  call restore_state_border(atm%neststruct%BCfile_sw)
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:121
subroutine, public fv_io_read_bcs(Atm)
The subroutine &#39;fv_io_read_BCs&#39; reads BCs from a restart file.
Definition: fv_io.F90:1010
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_write_restart(Atm, grids_on_this_pe, timestamp)
The subroutine &#39;fv_io_write_restart&#39; writes restart files.
Definition: fv_io.F90:582
subroutine, public fv_io_init()
Initialize the fv core restart facilities.
Definition: fv_io.F90:132
integer pfullid
Definition: fv_io.F90:124
subroutine, public fv_io_read_restart(fv_domain, Atm)
Write the fv core restart quantities.
Definition: fv_io.F90:144
subroutine register_bcs_2d(Atm, BCfile_ne, BCfile_sw, fname_ne, fname_sw, var_name, var, var_bc, istag, jstag)
Definition: fv_io.F90:619
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:464
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:910
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:763
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:225
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:3018
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:1517
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:124
subroutine, public fv_io_write_bcs(Atm, timestamp)
The subroutine &#39;fv_io_write_BCs&#39; writes BCs to a restart file.
Definition: fv_io.F90:999
subroutine, public fv_io_exit
Close the fv core restart facilities.
Definition: fv_io.F90:138
integer, parameter, public ng
Definition: fv_mp_mod.F90:2716
integer grid_xtdimid
Definition: fv_io.F90:124
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:448
integer oneid
Definition: fv_io.F90:125
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:276
integer grid_xtstagdimid
Definition: fv_io.F90:125
integer grid_ytstagdimid
Definition: fv_io.F90:125
integer grid_ytdimid
Definition: fv_io.F90:124
subroutine, public fv_io_register_restart_bcs_nh(Atm)
Definition: fv_io.F90:975