Skip to content

Commit

Permalink
Moved GFS_rrtmgp_lw_pre.F90 to rrtmgp_lw_pre.F90
Browse files Browse the repository at this point in the history
  • Loading branch information
dustinswales committed Dec 31, 2019
1 parent edcb672 commit 2e161eb
Show file tree
Hide file tree
Showing 2 changed files with 223 additions and 0 deletions.
90 changes: 90 additions & 0 deletions physics/rrtmgp_lw_pre.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,90 @@
module rrtmgp_lw_pre
use physparam
use machine, only: &
kind_phys ! Working type
use GFS_typedefs, only: &
GFS_control_type, & !
GFS_sfcprop_type, & ! Surface fields
GFS_grid_type, & ! Grid and interpolation related data
GFS_statein_type, & !
GFS_radtend_type ! Radiation tendencies needed in physics
use module_radiation_surface, only: &
setemis ! Routine to compute surface-emissivity
use mo_gas_optics_rrtmgp, only: &
ty_gas_optics_rrtmgp

public rrtmgp_lw_pre_run,rrtmgp_lw_pre_init,rrtmgp_lw_pre_finalize

contains

! #########################################################################################
! SUBROUTINE rrtmgp_lw_pre_init
! #########################################################################################
subroutine rrtmgp_lw_pre_init ()
end subroutine rrtmgp_lw_pre_init

! #########################################################################################
! SUBROUTINE rrtmgp_lw_pre_run
! #########################################################################################
!> \section arg_table_rrtmgp_lw_pre_run
!! \htmlinclude rrtmgp_lw_pre.html
!!
subroutine rrtmgp_lw_pre_run (doLWrad, nCol, lon, lat, lsmask, zorl, snowd, sncovr, tsfc, &
nmtvr, hprime, lw_gas_props, sfc_emiss_byband, errmsg, errflg)

! Inputs
logical, intent(in) :: &
doLWrad ! Logical flag for longwave radiation call
integer, intent(in) :: &
nCol, & ! Number of horizontal grid points
nmtvr ! number of topographic variables in GWD
real(kind_phys), dimension(nCol), intent(in) :: &
lon, & ! Longitude
lat, & ! Latitude
lsmask, & ! Land/sea/sea-ice mask
zorl, & ! Surface roughness length (cm)
snowd, & ! water equivalent snow depth (mm)
sncovr, & ! Surface snow are fraction (1)
tsfc ! Surface skin temperature (K)
real(kind_phys), dimension(nCol,nmtvr), intent(in) :: &
hprime ! Standard deviation of subgrid orography

type(ty_gas_optics_rrtmgp),intent(in) :: &
lw_gas_props ! RRTMGP DDT: spectral information for LW calculation

! Outputs
real(kind_phys), dimension(lw_gas_props%get_nband(),ncol), intent(out) :: &
sfc_emiss_byband ! Surface emissivity in each band
character(len=*), intent(out) :: &
errmsg ! Error message
integer, intent(out) :: &
errflg ! Error flag

! Local fields
real(kind_phys), dimension(nCol) :: sfc_emiss

! Initialize CCPP error handling variables
errmsg = ''
errflg = 0

if (.not. doLWrad) return

! #######################################################################################
! Call module_radiation_surface::setemis(),to setup surface emissivity for LW radiation.
! #######################################################################################
call setemis (lon, lat, lsmask, snowd, sncovr, zorl, tsfc, tsfc, hprime(:,1), nCol, sfc_emiss)

! Assign same emissivity to all bands
do iBand=1,lw_gas_props%get_nband()
sfc_emiss_byband(iBand,1:NCOL) = sfc_emiss(1:NCOL)
enddo

end subroutine rrtmgp_lw_pre_run

! #########################################################################################
! SUBROUTINE rrtmgp_lw_pre_finalize
! #########################################################################################
subroutine rrtmgp_lw_pre_finalize ()
end subroutine rrtmgp_lw_pre_finalize

end module rrtmgp_lw_pre
133 changes: 133 additions & 0 deletions physics/rrtmgp_lw_pre.meta
Original file line number Diff line number Diff line change
@@ -0,0 +1,133 @@
[ccpp-arg-table]
name = rrtmgp_lw_pre_run
type = scheme
[doLWrad]
standard_name = flag_to_calc_lw
long_name = logical flags for lw radiation calls
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[nCol]
standard_name = horizontal_loop_extent
long_name = horizontal loop extent
units = count
dimensions = ()
type = integer
intent = in
optional = F
[nmtvr]
standard_name = number_of_statistical_measures_of_subgrid_orography
long_name = number of topographic variables in GWD
units = count
dimensions = ()
type = integer
intent = in
optional = F
[lon]
standard_name = longitude
long_name = longitude
units = radians
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[lat]
standard_name = latitude
long_name = latitude
units = radians
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[lsmask]
standard_name = sea_land_ice_mask_real
long_name = landmask: sea/land/ice=0/1/2
units = flag
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[zorl]
standard_name = surface_roughness_length
long_name = surface roughness length
units = cm
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[snowd]
standard_name = surface_snow_thickness_water_equivalent
long_name = water equivalent snow depth
units = mm
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[sncovr]
standard_name = surface_snow_area_fraction_over_land
long_name = surface snow area fraction
units = frac
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[tsfc]
standard_name = surface_skin_temperature
long_name = surface skin temperature
units = K
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[hprime]
standard_name = statistical_measures_of_subgrid_orography
long_name = orographic metrics
units = various
dimensions = (horizontal_dimension,number_of_statistical_measures_of_subgrid_orography)
type = real
kind = kind_phys
intent = in
optional = F
[lw_gas_props]
standard_name = coefficients_for_lw_gas_optics
long_name = DDT containing spectral information for RRTMGP LW radiation scheme
units = DDT
dimensions = ()
type = ty_gas_optics_rrtmgp
intent = in
optional = F
[sfc_emiss_byband]
standard_name = surface_emissivity_in_each_RRTMGP_LW_band
long_name = surface emissivity in each RRTMGP LW band
units = none
dimensions = (number_of_lw_bands_rrtmgp,horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
units = none
dimensions = ()
type = character
kind = len=*
intent = out
optional = F
[errflg]
standard_name = ccpp_error_flag
long_name = error flag for error handling in CCPP
units = flag
dimensions = ()
type = integer
intent = out
optional = F

0 comments on commit 2e161eb

Please sign in to comment.