Skip to content

Commit

Permalink
FV3: this commits #refs 74d870d
Browse files Browse the repository at this point in the history
  • Loading branch information
hsinmulin-NOAA committed Oct 15, 2018
1 parent b2f26f6 commit c5d56c8
Show file tree
Hide file tree
Showing 13 changed files with 1,509 additions and 1,616 deletions.
14 changes: 6 additions & 8 deletions gfsphysics/GFS_layer/GFS_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,6 @@ module GFS_driver
GFS_radtend_type, GFS_diag_type
use module_radiation_driver, only: GFS_radiation_driver, radupdate
use module_physics_driver, only: GFS_physics_driver
use module_radsw_parameters, only: topfsw_type, sfcfsw_type
use module_radlw_parameters, only: topflw_type, sfcflw_type
use funcphys, only: gfuncphys
use gfdl_cloud_microphys_mod, only: gfdl_cloud_microphys_init
use physcons, only: gravit => con_g, rair => con_rd, &
Expand Down Expand Up @@ -213,12 +211,12 @@ subroutine GFS_initialize (Model, Statein, Stateout, Sfcprop, &
si = (Init_parm%ak + Init_parm%bk * p_ref - Init_parm%ak(Model%levr+1)) &
/ (p_ref - Init_parm%ak(Model%levr+1))

call rad_initialize (si, Model%levr, Model%ictm, Model%isol, &
Model%ico2, Model%iaer, Model%ialb, Model%iems, &
Model%ntcw, Model%num_p2d, Model%num_p3d, Model%npdf3d, &
Model%ntoz, Model%iovr_sw, Model%iovr_lw, Model%isubc_sw, &
Model%isubc_lw, Model%crick_proof, Model%ccnorm, &
Model%imp_physics, Model%norad_precip, Model%idate, Model%iflip, Model%me)
call rad_initialize (si, Model%levr, Model%ictm, Model%isol, &
Model%ico2, Model%iaer, Model%ialb, Model%iems, &
Model%ntcw, Model%num_p2d, Model%num_p3d, Model%npdf3d, &
Model%ntoz, Model%iovr_sw, Model%iovr_lw, Model%isubc_sw, &
Model%isubc_lw, Model%icliq_sw, Model%crick_proof, Model%ccnorm,&
Model%imp_physics, Model%norad_precip, Model%idate, Model%iflip, Model%me)
deallocate (si)

! microphysics initialization calls
Expand Down
154 changes: 85 additions & 69 deletions gfsphysics/GFS_layer/GFS_radiation_driver.F90

Large diffs are not rendered by default.

6 changes: 5 additions & 1 deletion gfsphysics/GFS_layer/GFS_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -411,6 +411,7 @@ module GFS_typedefs
!< 1 => use modis based alb
integer :: iems !< use fixed value of 1.0
integer :: iaer !< default aerosol effect in sw only
integer :: icliq_sw !< sw optical property for liquid clouds
integer :: iovr_sw !< sw: max-random overlap clouds
integer :: iovr_lw !< lw: max-random overlap clouds
integer :: ictm !< ictm=0 => use data at initial cond time, if not
Expand Down Expand Up @@ -1526,6 +1527,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
!< 1 => use modis based alb
integer :: iems = 0 !< use fixed value of 1.0
integer :: iaer = 1 !< default aerosol effect in sw only
integer :: icliq_sw = 1 !< sw optical property for liquid clouds
integer :: iovr_sw = 1 !< sw: max-random overlap clouds
integer :: iovr_lw = 1 !< lw: max-random overlap clouds
integer :: ictm = 1 !< ictm=0 => use data at initial cond time, if not
Expand Down Expand Up @@ -1750,7 +1752,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
cplflx, cplwav, cplchm, lsidea, &
!--- radiation parameters
fhswr, fhlwr, levr, nfxr, aero_in, iflip, isol, ico2, ialb, &
isot, iems, iaer, iovr_sw, iovr_lw, ictm, isubc_sw, &
isot, iems, iaer, icliq_sw, iovr_sw, iovr_lw, ictm, isubc_sw,&
isubc_lw, crick_proof, ccnorm, lwhtr, swhtr, &
!--- microphysical parameterizations
ncld, imp_physics, psautco, prautco, evpco, wminco, &
Expand Down Expand Up @@ -1888,6 +1890,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%ialb = ialb
Model%iems = iems
Model%iaer = iaer
Model%icliq_sw = icliq_sw
Model%iovr_sw = iovr_sw
Model%iovr_lw = iovr_lw
Model%ictm = ictm
Expand Down Expand Up @@ -2449,6 +2452,7 @@ subroutine control_print(Model)
print *, ' ialb : ', Model%ialb
print *, ' iems : ', Model%iems
print *, ' iaer : ', Model%iaer
print *, ' icliq_sw : ', Model%icliq_sw
print *, ' iovr_sw : ', Model%iovr_sw
print *, ' iovr_lw : ', Model%iovr_lw
print *, ' ictm : ', Model%ictm
Expand Down
58 changes: 28 additions & 30 deletions gfsphysics/physics/physparam.f
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,7 @@ module physparam !
!!\n =0:input cld opt depth, ignoring iswcice setting
!!\n =1:cloud optical property scheme based on Hu and Stamnes(1993) \cite
!! hu_and_stamnes_1993 method
!!\n =2:cloud optical property scheme based on Hu and Stamnes(1993) -updated
integer,save :: iswcliq = 1

!> SW optical property for ice clouds (only iswcliq>0)
Expand Down Expand Up @@ -165,8 +166,10 @@ module physparam !
!!\n =0:seasonal global distributed OPAC aerosol climatology
!!\n =1:monthly global distributed GOCART aerosol climatology
!!\n =2: GOCART prognostic aerosol model
!!\n =5: OPAC climatoloy with new band mapping
!!\n Opr GFS=0; Opr CFS=n/a
integer, save :: iaermdl = 0

!> aerosol effect control flag
!!\n 3-digit flag 'abc':
!!\n a-stratospheric volcanic aerols
Expand All @@ -175,19 +178,7 @@ module physparam !
!!\n =0:aerosol effect is not included; =1:aerosol effect is included
!!\n Opr GFS/CFS =111; see IAER in run scripts
integer, save :: iaerflg = 0
!> LW aerosols effect control flag
!!\n =.true.:aerosol effect is included in LW radiation
!!\n =.false.:aerosol effect is not included in LW radiation
logical, save :: lalwflg = .true.
!> SW aerosols effect control flag
!!\n =.true.:aerosol effect is included in SW radiation
!!\n =.false.:aerosol effect is not included in SW radiation
logical, save :: laswflg = .true.
!> stratospheric volcanic aerosol effect flag
!!\n =.true.:historical events of stratosphere volcanic aerosol effect
!! is included radiation (limited by data availability)
!!\n =.false.:volcanic aerosol effect is not included in radiation
logical, save :: lavoflg = .true.

!> external aerosols data file: aerosol.dat
character, save :: aeros_file*26
! data aeros_file / 'climaeropac_global.txt ' /
Expand All @@ -203,6 +194,7 @@ module physparam !
!!\n =2:monthly 15 degree horizontal resolution from observations
!!\n Opr GFS/CFS=2; see ICO2 in run scripts
integer, save :: ico2flg = 0

!> controls external data at initial time and data usage during
!! forecast time
!!\n =-2:as in 0,but superimpose with seasonal climatology cycle
Expand All @@ -213,11 +205,13 @@ module physparam !
!!\n =yyyy1:use yyyy year of data, extrapolate when necessary
!!\n Opr GFS/CFS=1; see ICTM in run scripts
integer, save :: ictmflg = 0

!> ozone data source control flag
!!\n =0:use seasonal climatology ozone data
!!\n >0:use prognostic ozone scheme (also depend on other model control
!! variable at initial time)
integer, save :: ioznflg = 1

!> external co2 2d monthly obsv data table: co2historicaldata_2004.txt
character, save :: co2dat_file*26
!> external co2 global annual mean data tb: co2historicaldata_glob.txt
Expand All @@ -239,21 +233,35 @@ module physparam !
!!\n =0:use diagnostic cloud scheme for cloud cover and mean optical properties
!!\n =1:use prognostic cloud scheme for cloud cover and cloud properties
integer, save :: icldflg = 1
!> cloud micorphysics scheme control flag
!!\n =1:modified Zhao/Carr/Sundqvist scheme (Moorthi, 2001)
!!\n =2:Ferrier microphysics scheme (Ferrier et al. 2002)
!!\n =3:as in 1 but with pdf method defined cloud cover
! integer, save :: icmphys = 1

!> cloud overlapping control flag for SW
!!\n =0:use random cloud overlapping method
!!\n =1:use maximum-random cloud overlapping method
!!\n =2:use maximum cloud overlapping method
!!\n =3:use decorrelation length overlapping method
!!\n Opr GFS/CFS=1; see IOVR_SW in run scripts
integer, save :: iovrsw = 1
!> cloud overlapping control flag for LW
!!\n =0:use random cloud overlapping method
!!\n =1:use maximum-random cloud overlapping method
!!\n =2:use maximum cloud overlapping method
!!\n =3:use decorrelation length overlapping method
!!\n Opr GFS/CFS=1; see IOVR_LW in run scripts
integer, save :: iovrlw = 1

!> sub-column cloud approx flag in SW radiation
!!\n =0:no McICA approximation in SW radiation
!!\n =1:use McICA with precribed permutation seeds (test mode)
!!\n =2:use McICA with randomly generated permutation seeds
!!\n Opr GFS/CFS=2; see ISUBC_SW in run scripts
integer, save :: isubcsw = 0
!> sub-column cloud approx flag in LW radiation
!!\n =0:no McICA approximation in LW radiation
!!\n =1:use McICA with prescribed permutation seeds (test mode)
!!\n =2:use McICA with randomly generatedo
!!\n Opr GFS/CFS=2; see ISUBC_LW in run scripts
integer, save :: isubclw = 0

!> eliminating CRICK control flag
logical, save :: lcrick =.false.
!> in-cld condensate control flag
Expand All @@ -271,6 +279,7 @@ module physparam !
!!\n =0:vegetation type based climatological albedo scheme
!!\n =1:seasonal albedo derived from MODIS measurements
integer, save :: ialbflg = 0

!> surface emissivity scheme control flag
!!\n =0:black-body surface emissivity(=1.0)
!!\n =1:vegetation type based climatology emissivity(<1.0)
Expand All @@ -287,18 +296,7 @@ module physparam !

!> vertical profile indexing flag
integer, save :: ivflip = 1
!> sub-column cloud approx flag in SW radiation
!!\n =0:no McICA approximation in SW radiation
!!\n =1:use McICA with precribed permutation seeds (test mode)
!!\n =2:use McICA with randomly generated permutation seeds
!!\n Opr GFS/CFS=2; see ISUBC_SW in run scripts
integer, save :: isubcsw = 0
!> sub-column cloud approx flag in LW radiation
!!\n =0:no McICA approximation in LW radiation
!!\n =1:use McICA with prescribed permutation seeds (test mode)
!!\n =2:use McICA with randomly generatedo
!!\n Opr GFS/CFS=2; see ISUBC_LW in run scripts
integer, save :: isubclw = 0

!> initial permutaion seed for mcica radiation
integer, save :: ipsd0 = 0
integer, save :: ipsdlim = 1e8
Expand Down
38 changes: 23 additions & 15 deletions gfsphysics/physics/rad_initialize.f
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,8 @@ subroutine rad_initialize &
! --- inputs:
& ( si,levr,ictm,isol,ico2,iaer,ialb,iems,ntcw, num_p2d, &
& num_p3d,npdf3d,ntoz,iovr_sw,iovr_lw,isubc_sw,isubc_lw, &
& crick_proof,ccnorm, &
& imp_physics, &
& norad_precip,idate,iflip,me )
& icliq_sw,crick_proof,ccnorm, &
& imp_physics,norad_precip,idate,iflip,me )
! --- outputs: ( none )

! ================= subprogram documentation block ================ !
Expand Down Expand Up @@ -83,9 +82,17 @@ subroutine rad_initialize &
! ntoz : ozone data control flag !
! =0: use climatological ozone profile !
! >0: use interactive ozone profile !
! icliq_sw : sw optical property for liquid clouds !
! =0:input cld opt depth, ignoring iswcice setting !
! =1:cloud optical property scheme based on Hu and !
! Stamnes(1993) \cite hu_and_stamnes_1993 method !
! =2:cloud optical property scheme based on Hu and !
! Stamnes(1993) -updated !
! iovr_sw/iovr_lw : control flag for cloud overlap (sw/lw rad) !
! =0: random overlapping clouds !
! =1: max/ran overlapping clouds !
! =2: maximum overlap clouds (mcica only) !
! =3: decorrelation-length overlap (mcica only) !
! isubc_sw/isubc_lw: sub-column cloud approx control flag (sw/lw rad) !
! =0: with out sub-column cloud approximation !
! =1: mcica sub-col approx. prescribed random seed !
Expand All @@ -105,9 +112,11 @@ subroutine rad_initialize &
! =================================================================== !
!
use physparam, only : isolar , ictmflg, ico2flg, ioznflg, iaerflg,&
& iaermdl, laswflg, lalwflg, lavoflg, icldflg, &
! & iaermdl, laswflg, lalwflg, lavoflg, icldflg, &
& iaermdl, icldflg, &
& iovrsw , iovrlw , lcrick , lcnorm , lnoprec, &
& ialbflg, iemsflg, isubcsw, isubclw, ivflip , ipsd0, &
& iswcliq, &
& kind_phys
use module_radiation_driver, only : radinit
Expand All @@ -117,7 +126,7 @@ subroutine rad_initialize &
! --- input:
integer, intent(in) :: levr, ictm, isol, ico2, iaer, num_p2d, &
& ntcw, ialb, iems, num_p3d, npdf3d, ntoz, iovr_sw, iovr_lw, &
& isubc_sw, isubc_lw, iflip, me, idate(4)
& isubc_sw, isubc_lw, icliq_sw, iflip, me, idate(4)
real (kind=kind_phys), intent(in) :: si(levr+1)
integer, intent(in) :: imp_physics
Expand All @@ -127,7 +136,6 @@ subroutine rad_initialize &
! --- output: ( none )
! --- local:
integer :: icld
!
!===> ... start here
!
Expand All @@ -144,20 +152,19 @@ subroutine rad_initialize &
else
iaerflg = mod(iaer, 1000)
endif
laswflg= (mod(iaerflg,10) > 0) ! control flag for sw tropospheric aerosol
lalwflg= (mod(iaerflg/10,10) > 0) ! control flag for lw tropospheric aerosol
lavoflg= (iaerflg >= 100) ! control flag for stratospheric volcanic aeros
iaermdl = iaer/1000 ! control flag for aerosol scheme selection
if ( iaermdl < 0 .or. iaermdl > 2) then
if ( iaermdl < 0 .or. (iaermdl>2 .and. iaermdl/=5) ) then
print *, ' Error -- IAER flag is incorrect, Abort'
stop 7777
endif
if ( ntcw > 0 ) then
! if ( ntcw > 0 ) then
icldflg = 1 ! prognostic cloud optical prop scheme
else
icldflg = 0 ! diagnostic cloud optical prop scheme
endif
! else
! icldflg = 0 ! no support for diag cloud opt prop scheme
! endif
iswcliq = icliq_sw ! optical property for liquid clouds for sw
iovrsw = iovr_sw ! cloud overlapping control flag for sw
iovrlw = iovr_lw ! cloud overlapping control flag for lw
Expand Down Expand Up @@ -186,7 +193,8 @@ subroutine rad_initialize &
& ' iaer=',iaer,' ialb=',ialb,' iems=',iems,' ntcw=',ntcw
print *,' np3d=',num_p3d,' ntoz=',ntoz,' iovr_sw=',iovr_sw, &
& ' iovr_lw=',iovr_lw,' isubc_sw=',isubc_sw, &
& ' isubc_lw=',isubc_lw,' iflip=',iflip,' me=',me
& ' isubc_lw=',isubc_lw,' icliq_sw=',icliq_sw, &
& ' iflip=',iflip,' me=',me
print *,' crick_proof=',crick_proof, &
& ' ccnorm=',ccnorm,' norad_precip=',norad_precip
endif
Expand Down
Loading

0 comments on commit c5d56c8

Please sign in to comment.