Skip to content

Commit

Permalink
Add experimental ability to restart from lat/lon A-grid horizontal wi…
Browse files Browse the repository at this point in the history
…nds (#34)
  • Loading branch information
spencerkclark authored May 8, 2020
1 parent 361a7c7 commit a8d0aa9
Show file tree
Hide file tree
Showing 6 changed files with 294 additions and 44 deletions.
6 changes: 4 additions & 2 deletions FV3/atmos_cubed_sphere/driver/fvGFS/atmosphere.F90
Original file line number Diff line number Diff line change
Expand Up @@ -449,8 +449,10 @@ subroutine atmosphere_init (Time_init, Time, Time_step, Grid_box, area)
if (Atm(mytile)%coarse_graining%write_coarse_restart_files) then
call fv_coarse_restart_init(mytile, Atm(mytile)%npz, Atm(mytile)%flagstruct%nt_prog, &
Atm(mytile)%flagstruct%nt_phys, Atm(mytile)%flagstruct%hydrostatic, &
Atm(mytile)%flagstruct%hybrid_z, Atm(mytile)%flagstruct%agrid_vel_rst, &
Atm(mytile)%flagstruct%fv_land, Atm(mytile)%coarse_graining%domain, &
Atm(mytile)%flagstruct%hybrid_z, Atm(mytile)%flagstruct%fv_land, &
Atm(mytile)%coarse_graining%write_coarse_dgrid_vel_rst, &
Atm(mytile)%coarse_graining%write_coarse_agrid_vel_rst, &
Atm(mytile)%coarse_graining%domain, &
Atm(mytile)%bd, Atm(mytile)%coarse_graining%bd, &
Atm(mytile)%coarse_graining%restart)
endif
Expand Down
4 changes: 4 additions & 0 deletions FV3/atmos_cubed_sphere/model/fv_arrays.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1025,6 +1025,8 @@ module fv_arrays_mod
logical :: write_coarse_restart_files = .false. ! Whether to write coarse restart files
logical :: write_coarse_diagnostics = .false. ! Whether to enable writing coarse diagnostics
logical :: write_only_coarse_intermediate_restarts = .false. ! Whether to write only coarse intermediate restart files (if do_coarse_graining is .true.)
logical :: restart_from_agrid_winds = .false. ! Whether to restart from A-grid winds
logical :: write_optional_dgrid_vel_rst = .false. ! Whether to write out optional D-grid winds when restart_from_agrid_winds is active
!integer, pointer :: test_case
!real, pointer :: alpha
end type fv_flags_type
Expand Down Expand Up @@ -1216,6 +1218,8 @@ module fv_arrays_mod
logical :: write_only_coarse_intermediate_restarts = .false.
type(fv_coarse_diag_type) :: idiag ! container for coarse diagnostic ids
type(coarse_restart_type) :: restart ! container for coarse restart data
logical :: write_coarse_dgrid_vel_rst = .true. ! Whether to write D-grid winds to coarse restart files
logical :: write_coarse_agrid_vel_rst = .false. ! Whether to write A-grid winds to coarse restart files

end type fv_coarse_graining_type

Expand Down
17 changes: 14 additions & 3 deletions FV3/atmos_cubed_sphere/model/fv_control.F90
Original file line number Diff line number Diff line change
Expand Up @@ -339,7 +339,11 @@ module fv_control_mod
logical, pointer :: write_coarse_restart_files
logical, pointer :: write_coarse_diagnostics
logical, pointer :: write_only_coarse_intermediate_restarts

logical, pointer :: restart_from_agrid_winds
logical, pointer :: write_optional_dgrid_vel_rst
logical, pointer :: write_coarse_dgrid_vel_rst
logical, pointer :: write_coarse_agrid_vel_rst

integer :: ntilesMe ! Number of tiles on this process =1 for now

#ifdef OVERLOAD_R4
Expand Down Expand Up @@ -676,7 +680,10 @@ subroutine run_setup(Atm, dt_atmos, grids_on_this_pe, p_split)
ioffset, joffset, check_negative, nudge_ic, halo_update_type, gfs_phil, agrid_vel_rst, &
do_uni_zfull, adj_mass_vmr, fac_n_spl, fhouri, &
regional, bc_update_interval,&
write_coarse_restart_files, write_coarse_diagnostics, write_only_coarse_intermediate_restarts
write_coarse_restart_files, write_coarse_diagnostics,&
write_only_coarse_intermediate_restarts,&
restart_from_agrid_winds, write_optional_dgrid_vel_rst,&
write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst

namelist /test_case_nml/test_case, bubble_do, alpha, nsolitons, soliton_Umax, soliton_size
#ifdef MULTI_GASES
Expand Down Expand Up @@ -1350,7 +1357,11 @@ subroutine setup_pointers(Atm)
write_coarse_restart_files => Atm%flagstruct%write_coarse_restart_files
write_coarse_diagnostics => Atm%flagstruct%write_coarse_diagnostics
write_only_coarse_intermediate_restarts => Atm%flagstruct%write_only_coarse_intermediate_restarts
end subroutine setup_pointers
restart_from_agrid_winds => Atm%flagstruct%restart_from_agrid_winds
write_optional_dgrid_vel_rst => Atm%flagstruct%write_optional_dgrid_vel_rst
write_coarse_dgrid_vel_rst => Atm%coarse_graining%write_coarse_dgrid_vel_rst
write_coarse_agrid_vel_rst => Atm%coarse_graining%write_coarse_agrid_vel_rst
end subroutine setup_pointers


end module fv_control_mod
84 changes: 52 additions & 32 deletions FV3/atmos_cubed_sphere/tools/coarse_grained_restart_files.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,10 +22,12 @@ module coarse_grained_restart_files_mod
contains

subroutine fv_coarse_restart_init(tile_count, nz, nt_prog, &
nt_phys, hydrostatic, hybrid_z, agrid_vel_rst, fv_land, &
nt_phys, hydrostatic, hybrid_z, fv_land, &
write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst, &
coarse_domain, fine_bd, coarse_bd, restart)
integer, intent(in) :: tile_count, nz, nt_prog, nt_phys
logical, intent(in) :: hydrostatic, hybrid_z, agrid_vel_rst, fv_land
logical, intent(in) :: hydrostatic, hybrid_z, fv_land
logical, intent(in) :: write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst
type(domain2d), intent(inout) :: coarse_domain
type(fv_grid_bounds_type), intent(in) :: fine_bd
type(fv_coarse_grid_bounds_type), intent(in) :: coarse_bd
Expand All @@ -39,10 +41,11 @@ subroutine fv_coarse_restart_init(tile_count, nz, nt_prog, &
npz = nz

call allocate_coarse_restart_type(hydrostatic, hybrid_z, &
agrid_vel_rst, fv_land, restart)
fv_land, write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst, &
restart)
call register_coarse_restart_files(tile_count, hydrostatic, &
hybrid_z, agrid_vel_rst, fv_land, &
coarse_domain, restart)
hybrid_z, fv_land, write_coarse_dgrid_vel_rst, &
write_coarse_agrid_vel_rst, coarse_domain, restart)
end subroutine fv_coarse_restart_init

subroutine fv_io_write_restart_coarse(Atm, grids_on_this_pe, timestamp)
Expand All @@ -67,12 +70,17 @@ subroutine fv_io_write_restart_coarse(Atm, grids_on_this_pe, timestamp)
enddo
end subroutine fv_io_write_restart_coarse

subroutine allocate_coarse_restart_type(hydrostatic, hybrid_z, agrid_vel_rst, fv_land, restart)
logical, intent(in) :: hydrostatic, hybrid_z, agrid_vel_rst, fv_land
subroutine allocate_coarse_restart_type(hydrostatic, hybrid_z, &
fv_land, write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst, restart)
logical, intent(in) :: hydrostatic, hybrid_z, fv_land
logical, intent(in) :: write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst
type(coarse_restart_type), intent(inout) :: restart

allocate(restart%u(is_coarse:ie_coarse,js_coarse:je_coarse+1,npz))
allocate(restart%v(is_coarse:ie_coarse+1,js_coarse:je_coarse,npz))
if (write_coarse_dgrid_vel_rst) then
allocate(restart%u(is_coarse:ie_coarse,js_coarse:je_coarse+1,npz))
allocate(restart%v(is_coarse:ie_coarse+1,js_coarse:je_coarse,npz))
endif

allocate(restart%u_srf(is_coarse:ie_coarse,js_coarse:je_coarse))
allocate(restart%v_srf(is_coarse:ie_coarse,js_coarse:je_coarse))
allocate(restart%delp(is_coarse:ie_coarse,js_coarse:je_coarse,npz))
Expand All @@ -81,7 +89,7 @@ subroutine allocate_coarse_restart_type(hydrostatic, hybrid_z, agrid_vel_rst, fv
allocate(restart%qdiag(is_coarse:ie_coarse,js_coarse:je_coarse,npz,n_prognostic_tracers+1:n_tracers))
allocate(restart%phis(is_coarse:ie_coarse,js_coarse:je_coarse))

if (agrid_vel_rst) then
if (write_coarse_agrid_vel_rst) then
allocate(restart%ua(is_coarse:ie_coarse,js_coarse:je_coarse,npz))
allocate(restart%va(is_coarse:ie_coarse,js_coarse:je_coarse,npz))
endif
Expand Down Expand Up @@ -120,13 +128,17 @@ subroutine deallocate_coarse_restart_type(restart)
end subroutine deallocate_coarse_restart_type

subroutine register_coarse_restart_files(tile_count, hydrostatic, &
hybrid_z, agrid_vel_rst, fv_land, coarse_domain, restart)
hybrid_z, fv_land, write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst, &
coarse_domain, restart)
integer, intent(in) :: tile_count
logical, intent(in) :: hydrostatic, hybrid_z, agrid_vel_rst, fv_land
logical, intent(in) :: hydrostatic, hybrid_z, fv_land
logical, intent(in) :: write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst
type(domain2d), intent(in) :: coarse_domain
type(coarse_restart_type), intent(inout) :: restart

call register_fv_core_coarse(tile_count, hydrostatic, hybrid_z, agrid_vel_rst, coarse_domain, restart)
call register_fv_core_coarse(tile_count, hydrostatic, hybrid_z, &
write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst, &
coarse_domain, restart)
call register_fv_tracer_coarse(tile_count, coarse_domain, restart)
call register_fv_srf_wnd_coarse(tile_count, coarse_domain, restart)
if (fv_land) then
Expand All @@ -136,9 +148,11 @@ subroutine register_coarse_restart_files(tile_count, hydrostatic, &
end subroutine register_coarse_restart_files

subroutine register_fv_core_coarse(tile_count, hydrostatic, hybrid_z, &
agrid_vel_rst, coarse_domain, restart)
write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst, coarse_domain, &
restart)
integer, intent(in) :: tile_count
logical, intent(in) :: hydrostatic, hybrid_z, agrid_vel_rst
logical, intent(in) :: hydrostatic, hybrid_z
logical, intent(in) :: write_coarse_dgrid_vel_rst, write_coarse_agrid_vel_rst
type(domain2d), intent(in) :: coarse_domain
type(coarse_restart_type), intent(inout) :: restart

Expand All @@ -147,11 +161,22 @@ subroutine register_fv_core_coarse(tile_count, hydrostatic, hybrid_z, &

filename = 'fv_core_coarse.res.nc'

id_restart = register_restart_field(restart%fv_core_coarse, &
filename, 'u', restart%u, domain=coarse_domain, position=NORTH, tile_count=tile_count)
id_restart = register_restart_field(restart%fv_core_coarse, &
filename, 'v', restart%v, domain=coarse_domain, position=EAST, tile_count=tile_count)

if (write_coarse_dgrid_vel_rst) then
id_restart = register_restart_field(restart%fv_core_coarse, &
filename, 'u', restart%u, domain=coarse_domain, position=NORTH, &
tile_count=tile_count)
id_restart = register_restart_field(restart%fv_core_coarse, &
filename, 'v', restart%v, domain=coarse_domain, position=EAST, &
tile_count=tile_count)
endif

if (write_coarse_agrid_vel_rst) then
id_restart = register_restart_field(restart%fv_core_coarse, &
filename, 'ua', restart%ua, domain=coarse_domain, tile_count=tile_count)
id_restart = register_restart_field(restart%fv_core_coarse, &
filename, 'va', restart%va, domain=coarse_domain, tile_count=tile_count)
endif

if (.not. hydrostatic) then
id_restart = register_restart_field(restart%fv_core_coarse, &
filename, 'W', restart%w, domain=coarse_domain, mandatory=.false., tile_count=tile_count)
Expand All @@ -169,13 +194,6 @@ subroutine register_fv_core_coarse(tile_count, hydrostatic, hybrid_z, &
filename, 'delp', restart%delp, domain=coarse_domain, tile_count=tile_count)
id_restart = register_restart_field(restart%fv_core_coarse, &
filename, 'phis', restart%phis, domain=coarse_domain, tile_count=tile_count)

if (agrid_vel_rst) then
id_restart = register_restart_field(restart%fv_core_coarse, &
filename, 'ua', restart%ua, domain=coarse_domain, mandatory=.false., tile_count=tile_count)
id_restart = register_restart_field(restart%fv_core_coarse, &
filename, 'va', restart%va, domain=coarse_domain, mandatory=.false., tile_count=tile_count)
endif
end subroutine register_fv_core_coarse

subroutine register_fv_tracer_coarse(tile_count, coarse_domain, restart)
Expand Down Expand Up @@ -282,10 +300,12 @@ subroutine coarse_grain_fv_core_restart_data_on_model_levels(Atm, mass)
type(fv_atmos_type), intent(inout) :: Atm
real, intent(in) :: mass(is:ie,js:je,1:npz)

call weighted_block_edge_average_x(Atm%gridstruct%dx(is:ie,js:je+1), &
Atm%u(is:ie,js:je+1,1:npz), Atm%coarse_graining%restart%u)
call weighted_block_edge_average_y(Atm%gridstruct%dy(is:ie+1,js:je), &
Atm%v(is:ie+1,js:je,1:npz), Atm%coarse_graining%restart%v)
if (Atm%coarse_graining%write_coarse_dgrid_vel_rst) then
call weighted_block_edge_average_x(Atm%gridstruct%dx(is:ie,js:je+1), &
Atm%u(is:ie,js:je+1,1:npz), Atm%coarse_graining%restart%u)
call weighted_block_edge_average_y(Atm%gridstruct%dy(is:ie+1,js:je), &
Atm%v(is:ie+1,js:je,1:npz), Atm%coarse_graining%restart%v)
endif

if (.not. Atm%flagstruct%hydrostatic) then
call weighted_block_average(mass(is:ie,js:je,1:npz), &
Expand All @@ -305,7 +325,7 @@ subroutine coarse_grain_fv_core_restart_data_on_model_levels(Atm, mass)
call weighted_block_average(Atm%gridstruct%area(is:ie,js:je), &
Atm%phis(is:ie,js:je), Atm%coarse_graining%restart%phis)

if (Atm%flagstruct%agrid_vel_rst) then
if (Atm%coarse_graining%write_coarse_agrid_vel_rst) then
call weighted_block_average(mass(is:ie,js:je,1:npz), &
Atm%ua(is:ie,js:je,1:npz), Atm%coarse_graining%restart%ua)
call weighted_block_average(mass(is:ie,js:je,1:npz), &
Expand Down
Loading

0 comments on commit a8d0aa9

Please sign in to comment.