Skip to content

Commit

Permalink
Merge pull request #221 from laurenchilutti/202210release
Browse files Browse the repository at this point in the history
Public Release 202210 on behalf of the GFDL Weather and Climate Dynamics division
  • Loading branch information
laurenchilutti authored Oct 17, 2022
2 parents c0747f2 + 03d282a commit d2e5bef
Show file tree
Hide file tree
Showing 32 changed files with 9,274 additions and 11,374 deletions.
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
# GFDL_atmos_cubed_sphere

The source contained herein reflects the 202204 release of the Finite Volume Cubed-Sphere Dynamical Core (FV3) from GFDL
The source contained herein reflects the 202210 release of the Finite Volume Cubed-Sphere Dynamical Core (FV3) from GFDL

The GFDL Microphysics is also available within this repository.

Expand Down
16 changes: 16 additions & 0 deletions RELEASE.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,19 @@
# RELEASE NOTES for FV3 202210: Summary
FV3-202210-public --- October 2022
Lucas Harris, GFDL [email protected]

This version has been tested with SHiELD physics release 202210
and with FMS release 2022.03 from https://github.com/NOAA-GFDL/FMS

This release includes the following:
- Release of the GFDL Microphysics Version 3
- Fix pressure-coarse-graining weighting from AI2's fork of FV3GFS
- Add A-grid restart functionality from AI2's fork of FV3GFS
- Fix for telescoping nest and GFS FIX file read
- Total precipitation diag field has changed from prec to pret
- Clean-up of the diagnostic messages to stdout


# RELEASE NOTES for FV3 202204: Summary
FV3-202204-public --- April 2022
Lucas Harris, GFDL [email protected]
Expand Down
51 changes: 31 additions & 20 deletions driver/SHiELD/atmosphere.F90
Original file line number Diff line number Diff line change
Expand Up @@ -83,8 +83,8 @@ module atmosphere_mod

use mpp_domains_mod, only: mpp_get_data_domain, mpp_get_compute_domain
use gfdl_mp_mod, only: gfdl_mp_init, gfdl_mp_end
use cld_eff_rad_mod, only: cld_eff_rad_init
use diag_manager_mod, only: send_data
use external_aero_mod, only: load_aero, read_aero, clean_aero
use coarse_graining_mod, only: coarse_graining_init
use coarse_grained_diagnostics_mod, only: fv_coarse_diag_init, fv_coarse_diag
use coarse_grained_restart_files_mod, only: fv_coarse_restart_init
Expand Down Expand Up @@ -283,8 +283,8 @@ subroutine atmosphere_init (Time_init, Time, Time_step, Grid_box, area, IAU_Data
!--- allocate pref
allocate(pref(npz+1,2), dum1d(npz+1))

call gfdl_mp_init(input_nml_file, stdlog())
call cld_eff_rad_init(input_nml_file, stdlog())
call gfdl_mp_init(input_nml_file, stdlog(), Atm(mygrid)%flagstruct%hydrostatic)

call fv_restart(Atm(mygrid)%domain, Atm, dt_atmos, seconds, days, cold_start, &
Atm(mygrid)%gridstruct%grid_type, mygrid)

Expand All @@ -294,6 +294,13 @@ subroutine atmosphere_init (Time_init, Time, Time_step, Grid_box, area, IAU_Data
!I've had trouble getting this to work with multiple grids at a time; worth revisiting?
call fv_diag_init(Atm(mygrid:mygrid), Atm(mygrid)%atmos_axes, Time, npx, npy, npz, Atm(mygrid)%flagstruct%p_ref)

if (Atm(mygrid)%flagstruct%do_aerosol) then
call load_aero(Atm(mygrid), Time)
call read_aero(isc, iec, jsc, jec, npz, nq, Time, Atm(mygrid)%pe(isc:iec,:,jsc:jec), &
Atm(mygrid)%peln(isc:iec,:,jsc:jec), Atm(mygrid)%q(isc:iec,jsc:jec,:,:), &
Atm(mygrid)%flagstruct%kord_tr, Atm(mygrid)%flagstruct%fill)
endif

if (Atm(mygrid)%coarse_graining%write_coarse_diagnostics) then
call fv_coarse_diag_init(Atm, Time, Atm(mygrid)%atmos_axes(3), &
Atm(mygrid)%atmos_axes(4), Atm(mygrid)%coarse_graining)
Expand Down Expand Up @@ -338,7 +345,6 @@ subroutine atmosphere_init (Time_init, Time, Time_step, Grid_box, area, IAU_Data
endif
call fv_io_register_nudge_restart ( Atm )


if ( Atm(mygrid)%flagstruct%na_init>0 ) then
if ( .not. Atm(mygrid)%flagstruct%hydrostatic ) then
call prt_maxmin('Before adi: W', Atm(mygrid)%w, isc, iec, jsc, jec, Atm(mygrid)%ng, npz, 1.)
Expand Down Expand Up @@ -449,6 +455,12 @@ subroutine atmosphere_dynamics ( Time )
isd, ied, jsd, jed )
endif

if (Atm(mygrid)%flagstruct%do_aerosol) then
call read_aero(isc, iec, jsc, jec, npz, nq, Time, Atm(mygrid)%pe(isc:iec,:,jsc:jec), &
Atm(mygrid)%peln(isc:iec,:,jsc:jec), Atm(mygrid)%q(isc:iec,jsc:jec,:,:), &
Atm(mygrid)%flagstruct%kord_tr, Atm(mygrid)%flagstruct%fill)
endif

!save ps to ps_dt before dynamics update
ps_dt(:,:)=Atm(n)%ps(:,:)

Expand Down Expand Up @@ -578,10 +590,12 @@ subroutine atmosphere_end (Time, Grid_box )!rab, Radiation, Physics)
! initialize domains for writing global physics data
if ( Atm(mygrid)%flagstruct%nudge ) call fv_nwp_nudge_end

if (Atm(mygrid)%flagstruct%do_inline_mp) then
call gfdl_mp_end ( )
if (Atm(mygrid)%flagstruct%do_aerosol) then
call clean_aero()
endif

call gfdl_mp_end ( )

if (first_diag) then
call timing_on('FV_DIAG')
call fv_diag(Atm(mygrid:mygrid), zvir, fv_time, Atm(mygrid)%flagstruct%print_freq)
Expand Down Expand Up @@ -655,13 +669,8 @@ subroutine atmosphere_control_data (i1, i2, j1, j2, kt, p_hydro, hydro, tile_num

if (present(p_hydro)) p_hydro = Atm(mygrid)%flagstruct%phys_hydrostatic
if (present( hydro)) hydro = Atm(mygrid)%flagstruct%hydrostatic
if (present(tile_num)) then
if (Atm(mygrid)%gridstruct%nested) then
tile_num = Atm(mygrid)%tile_of_mosaic + 6
else
tile_num = Atm(mygrid)%tile_of_mosaic
endif
endif
if (present(tile_num)) tile_num = Atm(mygrid)%global_tile

end subroutine atmosphere_control_data


Expand Down Expand Up @@ -1385,13 +1394,6 @@ subroutine atmosphere_state_update (Time, IPD_Data, IAU_Data, Atm_block)
enddo
enddo

if (is_master()) then
fhr=time_type_to_real( Time_next - Atm(n)%Time_init )/3600.
if (fhr <= 12.0 .or. (fhr - int(fhr)) == 0.0) then
write(555,*) fhr, psdt_mean
endif
endif

!LMH 7jan2020: Update PBL and other clock tracers, if present
tracer_clock = time_type_to_real(Time_next - Atm(n)%Time_init)*1.e-6
lat_thresh = 15.*pi/180.
Expand Down Expand Up @@ -1769,10 +1771,19 @@ subroutine atmos_phys_driver_statein (IPD_Data, Atm_block)
do ix = 1, blen
i = Atm_block%index(nb)%ii(ix)
j = Atm_block%index(nb)%jj(ix)
IPD_Data(nb)%Statein%prew(ix) = _DBL_(_RL_(Atm(mygrid)%inline_mp%prew(i,j)))
IPD_Data(nb)%Statein%prer(ix) = _DBL_(_RL_(Atm(mygrid)%inline_mp%prer(i,j)))
IPD_Data(nb)%Statein%prei(ix) = _DBL_(_RL_(Atm(mygrid)%inline_mp%prei(i,j)))
IPD_Data(nb)%Statein%pres(ix) = _DBL_(_RL_(Atm(mygrid)%inline_mp%pres(i,j)))
IPD_Data(nb)%Statein%preg(ix) = _DBL_(_RL_(Atm(mygrid)%inline_mp%preg(i,j)))
do k = 1, npz
k1 = npz+1-k ! flipping the index
IPD_Data(nb)%Statein%prefluxw(ix,k) = _DBL_(_RL_(Atm(mygrid)%inline_mp%prefluxw(i,j,k1)))
IPD_Data(nb)%Statein%prefluxr(ix,k) = _DBL_(_RL_(Atm(mygrid)%inline_mp%prefluxr(i,j,k1)))
IPD_Data(nb)%Statein%prefluxi(ix,k) = _DBL_(_RL_(Atm(mygrid)%inline_mp%prefluxi(i,j,k1)))
IPD_Data(nb)%Statein%prefluxs(ix,k) = _DBL_(_RL_(Atm(mygrid)%inline_mp%prefluxs(i,j,k1)))
IPD_Data(nb)%Statein%prefluxg(ix,k) = _DBL_(_RL_(Atm(mygrid)%inline_mp%prefluxg(i,j,k1)))
enddo
enddo
endif

Expand Down
8 changes: 1 addition & 7 deletions driver/solo/atmosphere.F90
Original file line number Diff line number Diff line change
Expand Up @@ -51,9 +51,7 @@ module atmosphere_mod
use fv_restart_mod, only: fv_restart
use fv_dynamics_mod, only: fv_dynamics
use fv_nesting_mod, only: twoway_nesting
use gfdl_cld_mp_mod, only: gfdl_cld_mp_init, gfdl_cld_mp_end
use gfdl_mp_mod, only: gfdl_mp_init, gfdl_mp_end
use cld_eff_rad_mod, only: cld_eff_rad_init
use fv_nwp_nudge_mod, only: fv_nwp_nudge_init, fv_nwp_nudge_end, do_adiabatic_init
use field_manager_mod, only: MODEL_ATMOS
use tracer_manager_mod, only: get_tracer_index
Expand Down Expand Up @@ -163,12 +161,9 @@ subroutine atmosphere_init ( Time_init, Time, Time_step )
if ( grids_on_this_pe(n) ) then
call fv_phys_init(isc,iec,jsc,jec,Atm(n)%npz,Atm(n)%flagstruct%nwat, Atm(n)%ts, Atm(n)%pt(isc:iec,jsc:jec,:), &
Time, axes, Atm(n)%gridstruct%agrid(isc:iec,jsc:jec,2))
! if ( Atm(n)%flagstruct%nwat==6) call gfdl_cld_mp_init(mpp_pe(), &
! mpp_root_pe(), input_nml_file, stdlog())
! if ( Atm(n)%flagstruct%nwat==6) call cld_eff_rad_init(input_nml_file)
endif
endif
if (.not. Atm(n)%flagstruct%adiabatic) call gfdl_mp_init (input_nml_file, stdlog())
if (.not. Atm(n)%flagstruct%adiabatic) call gfdl_mp_init (input_nml_file, stdlog(), Atm(n)%flagstruct%hydrostatic)



Expand Down Expand Up @@ -534,7 +529,6 @@ subroutine atmosphere_end

do n=1,ngrids
if ( Atm(n)%flagstruct%moist_phys .and. Atm(n)%flagstruct%nwat==6 .and. grids_on_this_pe(N)) call gfdl_mp_end
!if ( Atm(n)%flagstruct%moist_phys .and. Atm(n)%flagstruct%nwat==6 .and. grids_on_this_pe(N)) call gfdl_cld_mp_end
enddo

call fv_end(Atm, mytile)
Expand Down
8 changes: 3 additions & 5 deletions driver/solo/fv_phys.F90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ module fv_phys_mod
use fv_arrays_mod, only: radius, omega ! scaled for small earth

use time_manager_mod, only: time_type, get_time
use gfdl_cld_mp_mod, only: gfdl_cld_mp_driver, qsmith, wet_bulb
use gfdl_mp_mod, only: mqs3d, wet_bulb, c_liq
use hswf_mod, only: Held_Suarez_Tend
use fv_sg_mod, only: fv_subgrid_z
use fv_update_phys_mod, only: fv_update_phys
Expand Down Expand Up @@ -70,8 +70,6 @@ module fv_phys_mod

real, parameter:: e0 = 610.71 ! saturation vapor pressure at T0
real, parameter:: tice = 273.16
! real, parameter:: c_liq = 4.1855e+3 ! GFS
real, parameter:: c_liq = 4218.0 ! IFS
real, parameter:: cp_vap = cp_vapor ! 1846.
! For consistency, cv_vap derived FMS constants:
real, parameter:: cv_vap = cp_vap - rvgas ! 1384.5
Expand Down Expand Up @@ -899,8 +897,8 @@ subroutine GFDL_sim_phys(npx, npy, npz, is, ie, js, je, ng, nq, nwat, pk, pkz,

if( do_mon_obkv ) then

call qsmith(ie-is+1, je-js+1, 1, sst, ps, q3(is:ie,js:je,km,sphum), qs)
call qsmith(ie-is+1, je-js+1, 1, sst, ps, qs, qs) ! Iterate once
call mqs3d(ie-is+1, je-js+1, 1, sst, ps, q3(is:ie,js:je,km,sphum), qs)
call mqs3d(ie-is+1, je-js+1, 1, sst, ps, qs, qs) ! Iterate once

! Need to save ustar in a restart file (sim_phys)
! Because u_star is prognostic but not saved
Expand Down
3 changes: 1 addition & 2 deletions driver/solo/qs_tables.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@
module qs_tables_mod

use constants_mod, only: rdgas, rvgas, cp_air, cp_vapor, hlv
use gfdl_mp_mod, only: c_liq

implicit none
logical:: qs_table_is_initialized = .false.
Expand All @@ -30,8 +31,6 @@ module qs_tables_mod

real, parameter:: e0 = 610.71 ! saturation vapor pressure at T0
real, parameter:: tice = 273.16
! real, parameter:: c_liq = 4190. ! heat capacity of water at 0C
real, parameter:: c_liq = 4218.0 ! heat capacity of water at 0C
real, parameter:: cp_vap = cp_vapor ! 1846.
! For consistency, cv_vap derived FMS constants:
real, parameter:: cv_vap = cp_vap - rvgas ! 1384.5
Expand Down
Loading

0 comments on commit d2e5bef

Please sign in to comment.