Skip to content

Commit

Permalink
Merge pull request #43 from climbfuji/gmtb-gfsphysics-optimization-ar…
Browse files Browse the repository at this point in the history
…guments-time-vary-steps

Optimization of input arguments to time vary steps, moving of sec and blksz from IPD_Data(:)%Tbd to IPD_Control, remove Atm_block from IPD_step 0
  • Loading branch information
climbfuji committed Feb 22, 2018
2 parents cd71836 + 00eb067 commit e8c4997
Show file tree
Hide file tree
Showing 6 changed files with 50 additions and 68 deletions.
12 changes: 4 additions & 8 deletions GFS_layer/GFS_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -151,7 +151,7 @@ subroutine GFS_initialize (Model, Statein, Stateout, Sfcprop, &
Init_parm%gnx, Init_parm%gny, &
Init_parm%dt_dycore, Init_parm%dt_phys, &
Init_parm%bdat, Init_parm%cdat, &
Init_parm%tracer_names)
Init_parm%tracer_names, Init_parm%blksz)

call read_o3data (Model%ntoz, Model%me, Model%master)
call read_h2odata (Model%h2o_phys, Model%me, Model%master)
Expand All @@ -163,7 +163,7 @@ subroutine GFS_initialize (Model, Statein, Stateout, Sfcprop, &
call Sfcprop (nb)%create (Init_parm%blksz(nb), Model)
call Coupling (nb)%create (Init_parm%blksz(nb), Model)
call Grid (nb)%create (Init_parm%blksz(nb), Model)
call Tbd (nb)%create (Init_parm%blksz(nb), Init_parm%blksz(:), nb, Model)
call Tbd (nb)%create (Init_parm%blksz(nb), nb, Model)
call Cldprop (nb)%create (Init_parm%blksz(nb), Model)
call Radtend (nb)%create (Init_parm%blksz(nb), Model)
!--- internal representation of diagnostics
Expand Down Expand Up @@ -264,7 +264,6 @@ end subroutine GFS_initialize
subroutine GFS_time_vary_step (Model, Statein, Stateout, Sfcprop, Coupling, &
Grid, Tbd, Cldprop, Radtend, Diag, Sfccycle)

use physparam, only: ictmflg, isolar
use GFS_phys_time_vary_1, only: GFS_phys_time_vary_1_run
use GFS_phys_time_vary_2, only: GFS_phys_time_vary_2_run
use GFS_rad_time_vary, only: GFS_rad_time_vary_run
Expand All @@ -283,12 +282,9 @@ subroutine GFS_time_vary_step (Model, Statein, Stateout, Sfcprop, Coupling, &
type(GFS_diag_type), intent(inout) :: Diag
type(GFS_sfccycle_type), intent(inout) :: Sfccycle

!--- local variables
real(kind=kind_phys) :: sec

call GFS_phys_time_vary_1_run (Model, sec, Tbd%blkno)
call GFS_phys_time_vary_1_run (Model, Tbd)

call GFS_rad_time_vary_run (Model, Statein, Tbd, sec, ictmflg, isolar)
call GFS_rad_time_vary_run (Model, Statein, Tbd)

call GFS_phys_time_vary_2_run (Grid, Model, Tbd, Sfcprop, Cldprop, Diag, Sfccycle)

Expand Down
29 changes: 17 additions & 12 deletions GFS_layer/GFS_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,8 @@ module GFS_typedefs
!> \section arg_table_GFS_typedefs
!! | local var name | longname | description | units | rank | type | kind | intent | optional |
!! |---------------------------------|--------------------------------------------------------|---------------------------------------------------------|---------------|------|-----------------------|-----------|--------|----------|
!! | IPD_Data(nb)%Cldprop | FV3-GFS_Cldprop_type | derived type GFS_cldprop_type in FV3 | DDT | 0 | GFS_cldprop_type | | none | F |
!! | IPD_Control | FV3-GFS_Control_type | derived type GFS_control_type in FV3 | DDT | 0 | GFS_control_type | | none | F |
!! | IPD_Data(nb)%Cldprop | FV3-GFS_Cldprop_type | derived type GFS_cldprop_type in FV3 | DDT | 0 | GFS_cldprop_type | | none | F |
!! | IPD_Data(nb)%Coupling | FV3-GFS_Coupling_type | derived type GFS_coupling_type in FV3 | DDT | 0 | GFS_coupling_type | | none | F |
!! | IPD_Data(nb)%Intdiag | FV3-GFS_Diag_type | derived type GFS_diag_type in FV3 | DDT | 0 | GFS_diag_type | | none | F |
!! | IPD_Data(nb)%Grid | FV3-GFS_Grid_type | derived type GFS_grid_type in FV3 | DDT | 0 | GFS_grid_type | | none | F |
Expand Down Expand Up @@ -740,6 +740,8 @@ module GFS_typedefs
!! | IPD_Control%zhour | | previous hour diagnostic buckets emptied | h | 0 | real | kind_phys | none | F |
!! | IPD_Control%kdt | index_of_time_step | current forecast iteration | index | 0 | integer | | none | F |
!! | IPD_Control%jdat | | current forecast date and time | | 1 | integer | | none | F |
!! | IPD_Control%sec | seconds_elapsed_since_model_initialization | seconds elapsed since model initialization | s | 0 | real | kind_phys | none | F |
!! | IPD_Control%blksz | horizontal_block_size | for explicit data blocking: block sizes of all blocks | count | 1 | integer | | none | F |
!!
type GFS_control_type

Expand Down Expand Up @@ -767,6 +769,7 @@ module GFS_typedefs
integer :: cny !< number of points in the j-dir for this cubed-sphere face
integer :: lonr !< number of global points in x-dir (i) along the equator
integer :: latr !< number of global points in y-dir (j) along any meridian
integer, pointer :: blksz(:) !< for explicit data blocking

!--- coupling parameters
logical :: cplflx !< default no cplflx collection
Expand Down Expand Up @@ -986,6 +989,7 @@ module GFS_typedefs
integer :: kdt !< current forecast iteration
integer :: jdat(1:8) !< current forecast date and time
!< (yr, mon, day, t-zone, hr, min, sec, mil-sec)
real(kind=kind_phys) :: sec !< seconds since model initialization

contains
procedure :: init => control_initialize
Expand Down Expand Up @@ -1075,8 +1079,6 @@ module GFS_typedefs
!! | IPD_Data(nb)%Tbd%phy_f3d(:,:,3) | air_temperature_at_previous_time_step | air temperature at previous time step | K | 2 | real | kind_phys | none | F |
!! | IPD_Data(nb)%Tbd%phy_f3d(:,:,4) | water_vapor_specific_humidity_at_previous_time_step | water vapor specific humidity at previous time step | kg kg-1 | 2 | real | kind_phys | none | F |
!! | IPD_Data(nb)%Tbd%blkno | block_number | for explicit data blocking: block number of this block | index | 0 | integer | | none | F |
!! | IPD_Data(nb)%Tbd%blksz | horizontal_block_size | for explicit data blocking: block sizes of all blocks | count | 1 | integer | | none | F |
!! | IPD_Data(nb)%Tbd%sec | seconds_elapsed_since_model_initialization | seconds elapsed since model initialization | s | 0 | real | kind_phys | none | F |
!! | IPD_Data(nb)%Tbd%htlwc | tendency_of_air_temperature_due_to_longwave_heating_on_radiation_time_step | total sky heating rate due to longwave radiation | K s-1 | 2 | real | kind_phys | none | F |
!! | IPD_Data(nb)%Tbd%htlw0 | tendency_of_air_temperature_due_to_longwave_heating_assuming_clear_sky_on_radiation_time_step | clear sky heating rate due to longwave radiation | K s-1 | 2 | real | kind_phys | none | F |
!! | IPD_Data(nb)%Tbd%htswc | tendency_of_air_temperature_due_to_shortwave_heating_on_radiation_time_step | total sky heating rate due to shortwave radiation | K s-1 | 2 | real | kind_phys | none | F |
Expand Down Expand Up @@ -1116,8 +1118,8 @@ module GFS_typedefs
real (kind=kind_phys), pointer :: phy_f3d (:,:,:) => null() !< 3d arrays saved for restart

integer :: blkno !< for explicit data blocking: block number of this block
integer, pointer :: blksz (:) => null() !< for explicit data blocking: horizontal block sizes of all blocks
real (kind=kind_phys) :: sec !<

!--- radiation variables that need to be carried over from radiation to physics
real (kind=kind_phys), pointer :: htlwc(:,:) => null() !<
real (kind=kind_phys), pointer :: htlw0(:,:) => null() !<
real (kind=kind_phys), pointer :: htswc(:,:) => null() !<
Expand Down Expand Up @@ -2246,7 +2248,8 @@ end subroutine coupling_create
subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
logunit, isc, jsc, nx, ny, levs, &
cnx, cny, gnx, gny, dt_dycore, &
dt_phys, idat, jdat, tracer_names)
dt_phys, idat, jdat, tracer_names, &
blksz)

!--- modules
use physcons, only: max_lon, max_lat, min_lon, min_lat, &
Expand Down Expand Up @@ -2279,6 +2282,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
integer, intent(in) :: idat(8)
integer, intent(in) :: jdat(8)
character(len=32), intent(in) :: tracer_names(:)
integer, intent(in) :: blksz(:)
!--- local variables
integer :: n
integer :: ios
Expand Down Expand Up @@ -2538,6 +2542,8 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%cny = cny
Model%lonr = gnx
Model%latr = gny
allocate(Model%blksz(1:size(blksz)))
Model%blksz = blksz

!--- coupling parameters
Model%cplflx = cplflx
Expand Down Expand Up @@ -2713,6 +2719,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%zhour = mod(Model%phour,Model%fhzero)
Model%kdt = 0
Model%jdat(1:8) = jdat(1:8)
Model%sec = 0

!--- stored in wam_f107_kp module
f107_kp_size = 56
Expand Down Expand Up @@ -2968,6 +2975,8 @@ subroutine control_print(Model)
print *, ' cny : ', Model%cny
print *, ' lonr : ', Model%lonr
print *, ' latr : ', Model%latr
print *, ' blksz(1) : ', Model%blksz(1)
print *, ' blksz(size(blksz)): ', Model%blksz(size(Model%blksz))
print *, ' '
print *, 'coupling parameters'
print *, ' cplflx : ', Model%cplflx
Expand Down Expand Up @@ -3144,6 +3153,7 @@ subroutine control_print(Model)
print *, ' zhour : ', Model%zhour
print *, ' kdt : ', Model%kdt
print *, ' jdat : ', Model%jdat
print *, ' sec : ', Model%sec
endif

end subroutine control_print
Expand Down Expand Up @@ -3195,13 +3205,12 @@ end subroutine grid_create
!--------------------
! GFS_tbd_type%create
!--------------------
subroutine tbd_create (Tbd, IM, BLKSZ, BLKNO, Model)
subroutine tbd_create (Tbd, IM, BLKNO, Model)

implicit none

class(GFS_tbd_type) :: Tbd
integer, intent(in) :: IM
integer, dimension(:), intent(in) :: BLKSZ
integer, intent(in) :: BLKNO
type(GFS_control_type), intent(in) :: Model

Expand Down Expand Up @@ -3252,11 +3261,7 @@ subroutine tbd_create (Tbd, IM, BLKSZ, BLKNO, Model)
Tbd%phy_f2d = clear_val
Tbd%phy_f3d = clear_val

allocate (Tbd%blksz (size(BLKSZ)))

Tbd%blkno = BLKNO
Tbd%blksz = BLKSZ
Tbd%sec = clear_val

allocate (Tbd%htlwc (IM,Model%levr+LTP))
allocate (Tbd%htlw0 (IM,Model%levr+LTP))
Expand Down
16 changes: 5 additions & 11 deletions IPD_layer/IPD_CCPP_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ module IPD_CCPP_driver
!-------------------------------
! DH* TODO - CHECK IF WE CAN REMOVE Atm_block completely?
subroutine IPD_step (IPD_Control, IPD_Data, IPD_Diag, IPD_Restart, IPD_Interstitial, &
nBlocks, Atm_block, Init_parm, l_salp_data, l_snupx, ccpp_suite, step, ierr)
nBlocks, Init_parm, l_salp_data, l_snupx, ccpp_suite, step, ierr)

use namelist_soilveg, only: salp_data, snupx, max_vegtyp
use block_control_mod, only: block_control_type
Expand All @@ -55,7 +55,6 @@ subroutine IPD_step (IPD_Control, IPD_Data, IPD_Diag, IPD_Restart, IPD_Interstit
type(IPD_restart_type), target, intent(inout) :: IPD_Restart
type(IPD_interstitial_type), target, intent(inout) :: IPD_Interstitial(:)
integer, target, intent(in) :: nBlocks
type (block_control_type), target, intent(in) , optional :: Atm_block
type(IPD_init_type), target, intent(in) , optional :: Init_parm
real(kind=kind_phys), intent(inout), optional :: l_salp_data
real(kind=kind_phys), intent(inout), optional :: l_snupx(max_vegtyp)
Expand All @@ -76,11 +75,7 @@ subroutine IPD_step (IPD_Control, IPD_Data, IPD_Diag, IPD_Restart, IPD_Interstit

if (step==0) then

if (.not. present(Atm_block)) then
call ccpp_error('Error, IPD init step called without mandatory Atm_block argument')
ierr = 1
return
else if (.not. present(Init_parm)) then
if (.not. present(Init_parm)) then
call ccpp_error('Error, IPD init step called without mandatory Init_parm argument')
ierr = 1
return
Expand All @@ -106,7 +101,6 @@ subroutine IPD_step (IPD_Control, IPD_Data, IPD_Diag, IPD_Restart, IPD_Interstit
call ccpp_fields_add(cdata, 'IPD_Diag', '', c_loc(IPD_Diag), rank=size(shape(IPD_Diag)), dims=shape(IPD_Diag), ierr=ierr)
call ccpp_fields_add(cdata, 'IPD_Restart', '', c_loc(IPD_Restart), ierr=ierr)
call ccpp_fields_add(cdata, 'IPD_Interstitial', '', c_loc(IPD_Interstitial), rank=size(shape(IPD_Interstitial)), dims=shape(IPD_Interstitial), ierr=ierr)
call ccpp_fields_add(cdata, 'Atm_block', '', c_loc(Atm_block), ierr=ierr)
call ccpp_fields_add(cdata, 'Init_parm', '', c_loc(Init_parm), ierr=ierr)
call ccpp_fields_add(cdata, 'salp_data', l_salp_data, ierr=ierr)
call ccpp_fields_add(cdata, 'snupx', l_snupx, ierr=ierr)
Expand All @@ -132,11 +126,11 @@ subroutine IPD_step (IPD_Control, IPD_Data, IPD_Diag, IPD_Restart, IPD_Interstit
end do
end do

! Time vary steps
else if (step==1) then

! DH* TODO - TEST RUNNING THIS OVER ALL BLOCKS USING THREADING?
! Loop over blocks - in general, cannot use OpenMP for this step;
! however, threading may be implemented inside the IPD_setup_step
! Loop over blocks; cannot use OpenMP for this step; however,
! threading may be implemented inside the IPD_setup_step
do nb = 1,nBlocks
nt = 1
call ccpp_run(cdata_block(nb,nt)%suite%ipds(step), cdata_block(nb,nt), ierr)
Expand Down
4 changes: 1 addition & 3 deletions physics/GFS_debug.f90
Original file line number Diff line number Diff line change
Expand Up @@ -109,9 +109,7 @@ subroutine GFS_diagtoscreen_run (Model, Statein, Stateout, Sfcprop, Coupling, &
call print_var(mpirank,omprank,Tbd%blkno, 'Tbd%htlw0', Tbd%htlw0)
call print_var(mpirank,omprank,Tbd%blkno, 'Tbd%htswc', Tbd%htswc)
call print_var(mpirank,omprank,Tbd%blkno, 'Tbd%htsw0', Tbd%htsw0)
call print_var(mpirank,omprank,Tbd%blkno, 'Tbd%sec', Tbd%sec)
call print_var(mpirank,omprank,Tbd%blkno, 'Tbd%blksz(Tbd%blkno)', Tbd%blksz(Tbd%blkno))
!call Interstitial%mprint(mpirank,omprank,Tbd%blkno)
call print_var(mpirank,omprank,Tbd%blkno, 'Model%sec', Model%sec)
end if
!$OMP BARRIER
end do
Expand Down
Loading

0 comments on commit e8c4997

Please sign in to comment.