Skip to content

Commit

Permalink
FV3: this commits #refs 46547
Browse files Browse the repository at this point in the history
  • Loading branch information
bensonr committed Apr 10, 2018
1 parent f1b14da commit 3591b5c
Show file tree
Hide file tree
Showing 18 changed files with 3,011 additions and 6,262 deletions.
10 changes: 5 additions & 5 deletions atmos_cubed_sphere/driver/fvGFS/atmosphere.F90
Original file line number Diff line number Diff line change
Expand Up @@ -106,7 +106,7 @@ module atmosphere_mod
! </tr>
! <tr>
! <td>IPD_typedefs_mod</td>
! <td>IPD_data_type, kind_phys</td>
! <td>IPD_data_type, kind_phys => IPD_kind_phys</td>
! </tr>
! <tr>
! <td>mpp_mod</td>
Expand Down Expand Up @@ -165,7 +165,7 @@ module atmosphere_mod
use tracer_manager_mod, only: get_tracer_index, get_number_tracers, &
NO_TRACER
use DYCORE_typedefs, only: DYCORE_data_type
use IPD_typedefs, only: IPD_data_type, kind_phys
use IPD_typedefs, only: IPD_data_type, kind_phys => IPD_kind_phys
use fv_iau_mod, only: IAU_external_data_type

!-----------------
Expand Down Expand Up @@ -1640,9 +1640,9 @@ subroutine atmos_phys_driver_statein (IPD_Data, Atm_block)
!--------------------------------------
! Local GFS-phys consistent parameters:
!--------------------------------------
real(kind=kind_phys), parameter:: p00 = 1.e5
real(kind=kind_phys), parameter:: qmin = 1.0e-10
real(kind=kind_phys):: pk0inv, ptop, pktop
real(kind=kind_phys), parameter :: p00 = 1.e5
real(kind=kind_phys), parameter :: qmin = 1.0e-10
real(kind=kind_phys) :: pk0inv, ptop, pktop
real(kind=kind_phys) :: rTv, dm, qgrs_rad
integer :: nb, blen, npz, i, j, k, ix, k1, dnats, nq_adv

Expand Down
2 changes: 1 addition & 1 deletion atmos_cubed_sphere/makefile
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ endif

LIBRARY = libfv3core.a

FFLAGS += -I../fms -I../fms/include -I../gfsphysics -I../io
FFLAGS += -I../fms -I../fms/include -I../gfsphysics -I ../ipd -I../io

SRCS_f =

Expand Down
6 changes: 3 additions & 3 deletions atmos_cubed_sphere/tools/fv_iau_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,8 @@
!> @author Philip Pegion <[email protected]>
!> @date 09/13/2017
!
! REVISION HISTORY:
! 09/13/2017 - Initial Version based on fv_treat_da_inc.F90
!> REVISION HISTORY:
!> 09/13/2017 - Initial Version based on fv_treat_da_inc.F90
!-------------------------------------------------------------------------------

#ifdef OVERLOAD_R4
Expand Down Expand Up @@ -54,7 +54,7 @@ module fv_iau_mod
get_var3_r4, &
get_var1_real, check_var_exists
use IPD_typedefs, only: IPD_init_type, IPD_control_type, &
kind_phys
kind_phys => IPD_kind_phys
use block_control_mod, only: block_control_type
use fv_treat_da_inc_mod, only: remap_coef
use tracer_manager_mod, only: get_tracer_names,get_tracer_index, get_number_tracers
Expand Down
72 changes: 40 additions & 32 deletions atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -80,14 +80,14 @@ module atmos_model_mod
use block_control_mod, only: block_control_type, define_blocks_packed
use IPD_typedefs, only: IPD_init_type, IPD_control_type, &
IPD_data_type, IPD_diag_type, &
IPD_restart_type, kind_phys
use IPD_driver, only: IPD_initialize, IPD_setup_step, &
IPD_radiation_step, &
IPD_physics_step1, &
IPD_physics_step2
IPD_restart_type, IPD_kind_phys, &
IPD_func0d_proc, IPD_func1d_proc
use IPD_driver, only: IPD_initialize, IPD_step
use physics_abstraction_layer, only: time_vary_step, radiation_step1, physics_step1, physics_step2
use FV3GFS_io_mod, only: FV3GFS_restart_read, FV3GFS_restart_write, &
FV3GFS_IPD_checksum, &
gfdl_diag_register, gfdl_diag_output
FV3GFS_diag_register, FV3GFS_diag_output, &
DIAG_SIZE
use fv_iau_mod, only: iau_external_data_type,getiauforcing,iau_initialize

!-----------------------------------------------------------------------
Expand All @@ -104,26 +104,27 @@ module atmos_model_mod

!<PUBLICTYPE >
type atmos_data_type
type (domain2d) :: domain ! domain decomposition
integer :: axes(4) ! axis indices (returned by diag_manager) for the atmospheric grid
! (they correspond to the x, y, pfull, phalf axes)
real, pointer, dimension(:,:) :: lon_bnd => null() ! local longitude axis grid box corners in radians.
real, pointer, dimension(:,:) :: lat_bnd => null() ! local latitude axis grid box corners in radians.
real(kind=kind_phys), pointer, dimension(:,:) :: lon => null() ! local longitude axis grid box centers in radians.
real(kind=kind_phys), pointer, dimension(:,:) :: lat => null() ! local latitude axis grid box centers in radians.
type (time_type) :: Time ! current time
type (time_type) :: Time_step ! atmospheric time step.
type (time_type) :: Time_init ! reference time.
integer, pointer :: pelist(:) =>null() ! pelist where atmosphere is running.
integer :: layout(2) ! computer task laytout
logical :: pe ! current pe.
real(kind=8), pointer, dimension(:) :: ak, bk
real, pointer, dimension(:,:) :: lon_bnd => null() ! local longitude axis grid box corners in radians.
real, pointer, dimension(:,:) :: lat_bnd => null() ! local latitude axis grid box corners in radians.
real(kind=IPD_kind_phys), pointer, dimension(:,:) :: lon => null() ! local longitude axis grid box centers in radians.
real(kind=IPD_kind_phys), pointer, dimension(:,:) :: lat => null() ! local latitude axis grid box centers in radians.
real(kind=IPD_kind_phys), pointer, dimension(:,:) :: dx, dy
real(kind=8), pointer, dimension(:,:) :: area
real(kind=8), pointer, dimension(:,:,:) :: layer_hgt, level_hgt
type(domain2d) :: domain ! domain decomposition
type(time_type) :: Time ! current time
type(time_type) :: Time_step ! atmospheric time step.
type(time_type) :: Time_init ! reference time.
type(grid_box_type) :: grid ! hold grid information needed for 2nd order conservative flux exchange
! to calculate gradient on cubic sphere grid.
integer :: layout(2) ! computer task laytout
real(kind=8), pointer, dimension(:) :: ak, bk
real(kind=kind_phys), pointer, dimension(:,:) :: dx, dy
real(kind=8), pointer, dimension(:,:) :: area
real(kind=8), pointer, dimension(:,:,:) :: layer_hgt, level_hgt
type(IPD_diag_type), pointer, dimension(:) :: Diag
end type atmos_data_type
! to calculate gradient on cubic sphere grid.
!</PUBLICTYPE >

integer :: fv3Clock, getClock, updClock, setupClock, radClock, physClock
Expand All @@ -146,7 +147,7 @@ module atmos_model_mod
!----------------
type(IPD_control_type) :: IPD_Control
type(IPD_data_type), allocatable :: IPD_Data(:) ! number of blocks
type(IPD_diag_type) :: IPD_Diag(250)
type(IPD_diag_type), target :: IPD_Diag(DIAG_SIZE)
type(IPD_restart_type) :: IPD_Restart

! IAU container
Expand Down Expand Up @@ -191,6 +192,8 @@ subroutine update_atmos_radiation_physics (Atmos)
type (atmos_data_type), intent(in) :: Atmos
!--- local variables---
integer :: nb, jdat(8)
procedure(IPD_func0d_proc), pointer :: Func0d => NULL()
procedure(IPD_func1d_proc), pointer :: Func1d => NULL()

if (mpp_pe() == mpp_root_pe() .and. debug) write(6,*) "statein driver"
!--- get atmospheric state from the dynamic core
Expand Down Expand Up @@ -218,20 +221,22 @@ subroutine update_atmos_radiation_physics (Atmos)
IPD_Control%jdat(:) = jdat(:)
!--- execute the IPD atmospheric setup step
call mpp_clock_begin(setupClock)
call IPD_setup_step (IPD_Control, IPD_Data, IPD_Diag, IPD_Restart)
Func1d => time_vary_step
call IPD_step (IPD_Control, IPD_Data(:), IPD_Diag, IPD_Restart, IPD_func1d=Func1d)
call mpp_clock_end(setupClock)

if (mpp_pe() == mpp_root_pe() .and. debug) write(6,*) "radiation driver"

!--- execute the IPD atmospheric radiation subcomponent (RRTM)

call mpp_clock_begin(radClock)
Func0d => radiation_step1
!$OMP parallel do default (none) &
!$OMP schedule (dynamic,1), &
!$OMP shared (Atm_block, IPD_Control, IPD_Data, IPD_Diag, IPD_Restart) &
!$OMP shared (Atm_block, IPD_Control, IPD_Data, IPD_Diag, IPD_Restart, Func0d) &
!$OMP private (nb)
do nb = 1,Atm_block%nblks
call IPD_radiation_step (IPD_Control, IPD_Data(nb), IPD_Diag, IPD_Restart)
call IPD_step (IPD_Control, IPD_Data(nb:nb), IPD_Diag, IPD_Restart, IPD_func0d=Func0d)
enddo
call mpp_clock_end(radClock)

Expand All @@ -245,12 +250,13 @@ subroutine update_atmos_radiation_physics (Atmos)
!--- execute the IPD atmospheric physics step1 subcomponent (main physics driver)

call mpp_clock_begin(physClock)
Func0d => physics_step1
!$OMP parallel do default (none) &
!$OMP schedule (dynamic,1), &
!$OMP shared (Atm_block, IPD_Control, IPD_Data, IPD_Diag, IPD_Restart) &
!$OMP shared (Atm_block, IPD_Control, IPD_Data, IPD_Diag, IPD_Restart, Func0d) &
!$OMP private (nb)
do nb = 1,Atm_block%nblks
call IPD_physics_step1 (IPD_Control, IPD_Data(nb), IPD_Diag, IPD_Restart)
call IPD_step (IPD_Control, IPD_Data(nb:nb), IPD_Diag, IPD_Restart, IPD_func0d=Func0d)
enddo
call mpp_clock_end(physClock)

Expand All @@ -264,12 +270,13 @@ subroutine update_atmos_radiation_physics (Atmos)
!--- execute the IPD atmospheric physics step2 subcomponent (stochastic physics driver)

call mpp_clock_begin(physClock)
Func0d => physics_step2
!$OMP parallel do default (none) &
!$OMP schedule (dynamic,1), &
!$OMP shared (Atm_block, IPD_Control, IPD_Data, IPD_Diag, IPD_Restart) &
!$OMP shared (Atm_block, IPD_Control, IPD_Data, IPD_Diag, IPD_Restart, Func0d) &
!$OMP private (nb)
do nb = 1,Atm_block%nblks
call IPD_physics_step2 (IPD_Control, IPD_Data(nb), IPD_Diag, IPD_Restart)
call IPD_step (IPD_Control, IPD_Data(nb:nb), IPD_Diag, IPD_Restart, IPD_func0d=Func0d)
enddo
call mpp_clock_end(physClock)

Expand Down Expand Up @@ -305,7 +312,7 @@ subroutine atmos_model_init (Atmos, Time_init, Time, Time_step)
integer :: isc, iec, jsc, jec
integer :: isd, ied, jsd, jed
integer :: blk, ibs, ibe, jbs, jbe
real(kind=kind_phys) :: dt_phys
real(kind=IPD_kind_phys) :: dt_phys
real, allocatable :: q(:,:,:,:), p_half(:,:,:)
character(len=80) :: control
character(len=64) :: filename, filename2, pelist_name
Expand Down Expand Up @@ -422,6 +429,7 @@ subroutine atmos_model_init (Atmos, Time_init, Time, Time_step)
#endif

call IPD_initialize (IPD_Control, IPD_Data, IPD_Diag, IPD_Restart, Init_parm)
Atmos%Diag => IPD_Diag

Atm(mytile)%flagstruct%do_skeb = IPD_Control%do_skeb

Expand All @@ -441,7 +449,7 @@ subroutine atmos_model_init (Atmos, Time_init, Time, Time_step)
!rab call atmosphere_tracer_postinit (IPD_Data, Atm_block)

call atmosphere_nggps_diag (Time, init=.true.)
call gfdl_diag_register (Time, IPD_Data(:)%Sfcprop, IPD_Data(:)%Cldprop, IPD_Data(:)%IntDiag, IPD_Data(:)%grid, Atm_block, IPD_Control, Atmos%axes)
call FV3GFS_diag_register (IPD_Diag, Time, Atm_block, IPD_Control, Atmos%lon, Atmos%lat, Atmos%axes)
call FV3GFS_restart_read (IPD_Data, IPD_Restart, Atm_block, IPD_Control, Atmos%domain)

!--- set the initial diagnostic timestamp
Expand Down Expand Up @@ -524,7 +532,7 @@ subroutine update_atmos_model_state (Atmos)
type (atmos_data_type), intent(inout) :: Atmos
!--- local variables
integer :: isec,seconds
real(kind=kind_phys) :: time_int, time_intfull
real(kind=IPD_kind_phys) :: time_int, time_intfull

call set_atmosphere_pelist()
call mpp_clock_begin(fv3Clock)
Expand All @@ -549,7 +557,7 @@ subroutine update_atmos_model_state (Atmos)
time_intfull = real(seconds)
if (mpp_pe() == mpp_root_pe()) write(6,*) ' gfs diags time since last bucket empty: ',time_int/3600.,'hrs'
call atmosphere_nggps_diag(Atmos%Time)
call gfdl_diag_output(Atmos%Time, Atm_block, IPD_Control%nx, IPD_Control%ny, &
call FV3GFS_diag_output(Atmos%Time, IPD_DIag, Atm_block, IPD_Control%nx, IPD_Control%ny, &
IPD_Control%levs, 1, 1, 1.d0, time_int, time_intfull)
if (mod(isec,3600*nint(IPD_Control%fhzero)) == 0) diag_time = Atmos%Time
call diag_send_complete_instant (Atmos%Time)
Expand Down
25 changes: 25 additions & 0 deletions gfsphysics/GFS_layer/GFS_abstraction_layer.F90
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
module physics_abstraction_layer

use machine, only: kind_phys
use GFS_typedefs, only: init_type => GFS_init_type, &
control_type => GFS_control_type, &
statein_type => GFS_statein_type, &
Expand All @@ -12,12 +13,27 @@ module physics_abstraction_layer
radtend_type => GFS_radtend_type, &
intdiag_type => GFS_diag_type

use GFS_restart, only: restart_type => GFS_restart_type, &
restart_populate => GFS_restart_populate

use GFS_diagnostics, only: diagnostic_type => GFS_externaldiag_type, &
diagnostic_populate => GFS_externaldiag_populate

use GFS_driver, only: initialize => GFS_initialize, &
time_vary_step => GFS_time_vary_step, &
radiation_step1 => GFS_radiation_driver, &
physics_step1 => GFS_physics_driver, &
physics_step2 => GFS_stochastic_driver

integer :: num_time_vary_steps = 1
integer :: num_rad_steps = 1
integer :: num_phys_steps = 2

!-------------------------
! public physics dataspec
!-------------------------
public kind_phys

!----------------------
! public physics types
!----------------------
Expand All @@ -32,6 +48,15 @@ module physics_abstraction_layer
public cldprop_type
public radtend_type
public intdiag_type
public restart_type
public diagnostic_type

!------------------
! public variables
!------------------
public num_time_vary_steps
public num_rad_steps
public num_phys_steps

!--------------------------
! public physics functions
Expand Down
Loading

0 comments on commit 3591b5c

Please sign in to comment.