Skip to content

Commit

Permalink
Some housekeeping
Browse files Browse the repository at this point in the history
  • Loading branch information
dustinswales committed Dec 5, 2019
1 parent e905e96 commit e93fc1b
Show file tree
Hide file tree
Showing 7 changed files with 213 additions and 205 deletions.
23 changes: 12 additions & 11 deletions physics/GFS_rrtmgp_gas_optics.F90
Original file line number Diff line number Diff line change
@@ -1,19 +1,16 @@
!> \file GFS_rrtmgp_gas_optics.f90
!! This file contains
module GFS_rrtmgp_gas_optics
use machine, only: kind_phys
use GFS_typedefs, only: GFS_control_type,GFS_radtend_type

public GFS_rrtmgp_gas_optics_init,GFS_rrtmgp_gas_optics_run,GFS_rrtmgp_gas_optics_finalize
contains

!! \section arg_table_GFS_rrtmgp_gas_optics_init
!! \htmlinclude GFS_rrtmgp_gas_optics.html
!!

! #########################################################################################
! SUBROUTINE GFS_rrtmgp_gas_optics_init()
! #########################################################################################
!! \section arg_table_GFS_rrtmgp_gas_optics_init
!! \htmlinclude GFS_rrtmgp_gas_optics.html
!!
subroutine GFS_rrtmgp_gas_optics_init(Model, Radtend, errmsg, errflg)
! Inputs
type(GFS_control_type), intent(in) :: &
Expand Down Expand Up @@ -57,13 +54,17 @@ subroutine GFS_rrtmgp_gas_optics_init(Model, Radtend, errmsg, errflg)
enddo
endif
end subroutine GFS_rrtmgp_gas_optics_init
!
subroutine GFS_rrtmgp_gas_optics_run()


! #########################################################################################
! SUBROUTINE GFS_rrtmgp_gas_optics_run
! #########################################################################################
subroutine GFS_rrtmgp_gas_optics_run()
end subroutine GFS_rrtmgp_gas_optics_run
!

! #########################################################################################
! SUBROUTINE GFS_rrtmgp_gas_optics_finalize
! #########################################################################################
subroutine GFS_rrtmgp_gas_optics_finalize()
end subroutine GFS_rrtmgp_gas_optics_finalize
!

end module GFS_rrtmgp_gas_optics
102 changes: 48 additions & 54 deletions physics/GFS_rrtmgp_lw_post.F90
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
!>\file GFS_rrtmgp_lw_post
!!This file contains
module GFS_rrtmgp_lw_post
use machine, only: kind_phys
use GFS_typedefs, only: GFS_coupling_type, &
Expand All @@ -20,10 +18,15 @@ module GFS_rrtmgp_lw_post
public GFS_rrtmgp_lw_post_init,GFS_rrtmgp_lw_post_run,GFS_rrtmgp_lw_post_finalize

contains

! #########################################################################################
! SUBROUTINE GFS_rrtmgp_lw_post_init
! #########################################################################################
subroutine GFS_rrtmgp_lw_post_init()
end subroutine GFS_rrtmgp_lw_post_init

! #########################################################################################
! SUBROUTINE GFS_rrtmgp_lw_post_run
! #########################################################################################
!> \section arg_table_GFS_rrtmgp_lw_post_run
!! \htmlinclude GFS_rrtmgp_lw_post.html
!!
Expand All @@ -34,70 +37,58 @@ subroutine GFS_rrtmgp_lw_post_run (Model, Grid, Radtend, Coupling, Diag, Statei

! Inputs
type(GFS_control_type), intent(in) :: &
Model ! Fortran DDT containing FV3-GFS model control parameters
Model ! Fortran DDT: FV3-GFS model control parameters
type(GFS_grid_type), intent(in) :: &
Grid ! Fortran DDT containing FV3-GFS grid and interpolation related data
type(GFS_coupling_type), intent(inout) :: &
Coupling ! Fortran DDT containing FV3-GFS fields to/from coupling with other components
type(GFS_radtend_type), intent(inout) :: &
Radtend ! Fortran DDT containing FV3-GFS radiation tendencies
type(GFS_diag_type), intent(inout) :: &
Diag ! Fortran DDT containing FV3-GFS diagnotics data
Grid ! Fortran DDT: FV3-GFS grid and interpolation related data
type(GFS_statein_type), intent(in) :: &
Statein ! Fortran DDT containing FV3-GFS prognostic state data in from dycore
Statein ! Fortran DDT: FV3-GFS prognostic state data in from dycore
integer, intent(in) :: &
im ! Horizontal loop extent
im ! Horizontal loop extent
real(kind_phys), dimension(size(Grid%xlon,1)), intent(in) :: &
tsfa ! Lowest model layer air temperature for radiation
tsfa ! Lowest model layer air temperature for radiation (K)
real(kind_phys), dimension(size(Grid%xlon,1), Model%levs+1), intent(in) :: &
p_lev ! Pressure @ model layer-interfaces (hPa)
p_lev ! Pressure @ model layer-interfaces (hPa)
real(kind_phys), dimension(size(Grid%xlon,1), Model%levs+1), intent(in) :: &
fluxlwUP_allsky, & ! LW All-sky flux (W/m2)
fluxlwDOWN_allsky, & ! LW All-sky flux (W/m2)
fluxlwUP_clrsky, & ! LW Clear-sky flux (W/m2)
fluxlwDOWN_clrsky ! LW All-sky flux (W/m2)
fluxlwUP_allsky, & ! RRTMGP longwave all-sky flux (W/m2)
fluxlwDOWN_allsky, & ! RRTMGP longwave all-sky flux (W/m2)
fluxlwUP_clrsky, & ! RRTMGP longwave clear-sky flux (W/m2)
fluxlwDOWN_clrsky ! RRTMGP longwave clear-sky flux (W/m2)
real(kind_phys), intent(in) :: &
raddt ! Radiation time step
raddt ! Radiation time step
real(kind_phys), dimension(im,NSPC1), intent(in) :: &
aerodp ! Vertical integrated optical depth for various aerosol species
aerodp ! Vertical integrated optical depth for various aerosol species
real(kind_phys), dimension(im,5), intent(in) :: &
cldsa ! Fraction of clouds for low, middle, high, total and BL
cldsa ! Fraction of clouds for low, middle, high, total and BL
integer, dimension(im,3), intent(in) ::&
mbota, & ! vertical indices for low, middle and high cloud tops
mtopa ! vertical indices for low, middle and high cloud bases
mbota, & ! vertical indices for low, middle and high cloud tops
mtopa ! vertical indices for low, middle and high cloud bases
real(kind_phys), dimension(im,Model%levs), intent(in) :: &
cld_frac, & ! Total cloud fraction in each layer
cldtaulw ! approx 10.mu band layer cloud optical depth
cld_frac, & ! Total cloud fraction in each layer
cldtaulw ! approx 10.mu band layer cloud optical depth
real(kind_phys),dimension(size(Grid%xlon,1), Model%levs) :: &
hlwc ! Longwave all-sky heating-rate (K/sec)
hlwc ! Longwave all-sky heating-rate (K/sec)

! Outputs (mandatory)
character(len=*), intent(out) :: &
errmsg
integer, intent(out) :: &
errflg
! real(kind_phys),dimension(size(Grid%xlon,1), Model%levs),intent(out) :: &
! hlwc ! Longwave all-sky heating-rate (K/sec)
! type(topflw_type), dimension(size(Grid%xlon,1)), intent(inout) :: &
! topflx_lw ! radiation fluxes at top, components:
! ! upfxc - total sky upward flux at top (w/m2)
! ! upfx0 - clear sky upward flux at top (w/m2)
! type(sfcflw_type), dimension(size(Grid%xlon,1)), intent(inout) :: &
! sfcflx_lw ! radiation fluxes at sfc, components:
! ! upfxc - total sky upward flux at sfc (w/m2)
! ! upfx0 - clear sky upward flux at sfc (w/m2)
! ! dnfxc - total sky downward flux at sfc (w/m2)
! ! dnfx0 - clear sky downward flux at sfc (w/m2)

type(GFS_coupling_type), intent(inout) :: &
Coupling ! Fortran DDT: FV3-GFS fields to/from coupling with other components
type(GFS_radtend_type), intent(inout) :: &
Radtend ! Fortran DDT: FV3-GFS radiation tendencies
type(GFS_diag_type), intent(inout) :: &
Diag ! Fortran DDT: FV3-GFS diagnotics data

! Outputs (optional)
real(kind_phys), dimension(size(Grid%xlon,1), Model%levs), optional, intent(inout) :: &
hlw0 ! Longwave clear-sky heating rate (K/sec)
hlw0 ! Longwave clear-sky heating rate (K/sec)
type(proflw_type), dimension(size(Grid%xlon,1), Model%levs+1), optional, intent(inout) :: &
flxprf_lw ! 2D radiative fluxes, components:
! upfxc - total sky upward flux (W/m2)
! dnfxc - total sky dnward flux (W/m2)
! upfx0 - clear sky upward flux (W/m2)
! dnfx0 - clear sky dnward flux (W/m2)
flxprf_lw ! 2D radiative fluxes, components:
! upfxc - total sky upward flux (W/m2)
! dnfxc - total sky dnward flux (W/m2)
! upfx0 - clear sky upward flux (W/m2)
! dnfx0 - clear sky dnward flux (W/m2)

! Local variables
integer :: i, j, k, iSFC, iTOA, itop, ibtc
Expand Down Expand Up @@ -133,17 +124,17 @@ subroutine GFS_rrtmgp_lw_post_run (Model, Grid, Radtend, Coupling, Diag, Statei
! Clear-sky heating-rate (optional)
if (l_clrskylw_hr) then
call check_error_msg('GFS_rrtmgp_post',compute_heating_rate( &
fluxlwUP_clrsky, &
fluxlwDOWN_clrsky, &
p_lev, &
hlw0))
fluxlwUP_clrsky, & ! IN - RRTMGP upward longwave clear-sky flux profiles (W/m2)
fluxlwDOWN_clrsky, & ! IN - RRTMGP downward longwave clear-sky flux profiles (W/m2)
p_lev, & ! IN - Pressure @ layer-interfaces (Pa)
hlw0)) ! OUT - Longwave clear-sky heating rate (K/sec)
endif
! All-sky heating-rate (mandatory)
call check_error_msg('GFS_rrtmgp_post',compute_heating_rate( &
fluxlwUP_allsky, &
fluxlwDOWN_allsky, &
p_lev, &
hlwc))
fluxlwUP_allsky, & ! IN - RRTMGP upward longwave all-sky flux profiles (W/m2)
fluxlwDOWN_allsky, & ! IN - RRTMGP downward longwave all-sky flux profiles (W/m2)
p_lev, & ! IN - Pressure @ layer-interfaces (Pa)
hlwc)) ! OUT - Longwave all-sky heating rate (K/sec)

! Copy fluxes from RRTGMP types into model radiation types.
! Mandatory outputs
Expand Down Expand Up @@ -235,6 +226,9 @@ subroutine GFS_rrtmgp_lw_post_run (Model, Grid, Radtend, Coupling, Diag, Statei

end subroutine GFS_rrtmgp_lw_post_run

! #########################################################################################
! SUBROUTINE GFS_rrtmgp_lw_post_finalize
! #########################################################################################
subroutine GFS_rrtmgp_lw_post_finalize ()
end subroutine GFS_rrtmgp_lw_post_finalize

Expand Down
43 changes: 25 additions & 18 deletions physics/GFS_rrtmgp_lw_pre.F90
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
!> \file GFS_rrtmgp_lw_pre.f90
!! This file contains
module GFS_rrtmgp_lw_pre
use physparam
use machine, only: &
Expand All @@ -25,44 +23,51 @@ module GFS_rrtmgp_lw_pre

contains

! #########################################################################################
! SUBROUTINE GFS_rrtmgp_lw_pre_init
! #########################################################################################
subroutine GFS_rrtmgp_lw_pre_init ()
end subroutine GFS_rrtmgp_lw_pre_init

! #########################################################################################
! SUBROUTINE GFS_rrtmgp_lw_pre_run
! #########################################################################################
!> \section arg_table_GFS_rrtmgp_lw_pre_run
!! \htmlinclude GFS_rrtmgp_lw_pre.html
!!
subroutine GFS_rrtmgp_lw_pre_run (Model, Grid, Sfcprop, Statein, ncol, p_lay, p_lev, &
tv_lay, relhum, tracer, lw_gas_props, Radtend, Interstitial, aerosolslw, aerodp, errmsg, errflg)
subroutine GFS_rrtmgp_lw_pre_run (Model, Grid, Sfcprop, Statein, ncol, p_lay, p_lev, &
tv_lay, relhum, tracer, lw_gas_props, Radtend, Interstitial, aerosolslw, aerodp, &
errmsg, errflg)

! Inputs
type(GFS_control_type), intent(in) :: &
Model ! Fortran DDT containing FV3-GFS model control parameters
Model ! DDT: FV3-GFS model control parameters
type(GFS_grid_type), intent(in) :: &
Grid ! Fortran DDT containing FV3-GFS grid and interpolation related data
Grid ! DDT: FV3-GFS grid and interpolation related data
type(GFS_sfcprop_type), intent(in) :: &
Sfcprop ! Fortran DDT containing FV3-GFS surface fields
Sfcprop ! DDT: FV3-GFS surface fields
type(GFS_statein_type), intent(in) :: &
Statein ! Fortran DDT containing FV3-GFS prognostic state data in from dycore
Statein ! DDT: FV3-GFS prognostic state data in from dycore
integer, intent(in) :: &
ncol ! Number of horizontal grid points
real(kind_phys), dimension(ncol,Model%levs),intent(in) :: &
p_lay, & ! Layer pressure
tv_lay, & ! Layer virtual-temperature
relhum ! Layer relative-humidity
real(kind_phys), dimension(ncol, Model%levs, 2:Model%ntrac),intent(in) :: &
tracer
tracer ! trace gas concentrations
real(kind_phys), dimension(ncol,Model%levs+1),intent(in) :: &
p_lev ! Interface (level) pressure
type(ty_gas_optics_rrtmgp),intent(in) :: &
lw_gas_props ! RRTMGP DDT containing spectral information for LW calculation
lw_gas_props ! RRTMGP DDT: spectral information for LW calculation

! Outputs
type(GFS_radtend_type), intent(inout) :: &
Radtend ! Fortran DDT containing FV3-GFS radiation tendencies
Radtend ! DDT: FV3-GFS radiation tendencies
type(GFS_interstitial_type), intent(inout) :: &
Interstitial
Interstitial ! DDT: FV3-GFS Interstitial arrays
real(kind_phys), dimension(ncol,Model%levs,lw_gas_props%get_nband(),NF_AELW), intent(out) ::&
aerosolslw ! Aerosol radiative properties in each SW band.
aerosolslw ! Aerosol radiative properties in each SW band.
real(kind_phys), dimension(ncol,NSPC1), intent(inout) :: &
aerodp ! Vertical integrated optical depth for various aerosol species
character(len=*), intent(out) :: &
Expand All @@ -83,9 +88,10 @@ subroutine GFS_rrtmgp_lw_pre_run (Model, Grid, Sfcprop, Statein, ncol, p_lay,
! #######################################################################################
! Call module_radiation_surface::setemis(),to setup surface emissivity for LW radiation.
! #######################################################################################
call setemis (Grid%xlon, Grid%xlat, Sfcprop%slmsk, Sfcprop%snowd, Sfcprop%sncovr, &
Sfcprop%zorl, Sfcprop%tsfc,Sfcprop%tsfc, Sfcprop%hprime(:,1), NCOL, &
Radtend%semis)
call setemis (Grid%xlon, Grid%xlat, Sfcprop%slmsk, Sfcprop%snowd, Sfcprop%sncovr, &
Sfcprop%zorl, Sfcprop%tsfc,Sfcprop%tsfc, Sfcprop%hprime(:,1), NCOL, Radtend%semis)

! Assign same emissivity to all bands
do iBand=1,lw_gas_props%get_nband()
Interstitial%sfc_emiss_byband(iBand,1:NCOL) = Radtend%semis(1:NCOL)
enddo
Expand All @@ -100,8 +106,9 @@ subroutine GFS_rrtmgp_lw_pre_run (Model, Grid, Sfcprop, Statein, ncol, p_lay,

end subroutine GFS_rrtmgp_lw_pre_run

!> \section arg_table_GFS_rrtmgp_lw_pre_finalize Argument Table
!!
! #########################################################################################
! SUBROUTINE GFS_rrtmgp_lw_pre_finalize
! #########################################################################################
subroutine GFS_rrtmgp_lw_pre_finalize ()
end subroutine GFS_rrtmgp_lw_pre_finalize

Expand Down
Loading

0 comments on commit e93fc1b

Please sign in to comment.