Skip to content

Commit

Permalink
Renamed two modules.
Browse files Browse the repository at this point in the history
  • Loading branch information
dustinswales committed Jun 11, 2019
1 parent b882dff commit 044c880
Show file tree
Hide file tree
Showing 2 changed files with 39 additions and 39 deletions.
34 changes: 17 additions & 17 deletions physics/rrtmgp_lw.F90 → physics/rrtmgp_lw_rte.F90
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
! ###########################################################################################
! ###########################################################################################
module rrtmgp_lw
module rrtmgp_lw_rte
use machine, only: kind_phys
use GFS_typedefs, only: GFS_control_type, GFS_radtend_type, GFS_statein_type
use mo_rte_kind, only: wl
Expand All @@ -12,19 +12,19 @@ module rrtmgp_lw
use mo_source_functions, only: ty_source_func_lw
use rrtmgp_aux, only: check_error_msg

public rrtmgp_lw_init, rrtmgp_lw_run, rrtmgp_lw_finalize
public rrtmgp_lw_rte_init, rrtmgp_lw_rte_run, rrtmgp_lw_rte_finalize
contains

! #########################################################################################
! SUBROUTINE rrtmgp_lw_init
! SUBROUTINE rrtmgp_lw_rte_init
! #########################################################################################
subroutine rrtmgp_lw_init()
end subroutine rrtmgp_lw_init
subroutine rrtmgp_lw_rte_init()
end subroutine rrtmgp_lw_rte_init

! #########################################################################################
! SUBROUTINE rrtmgp_lw_run
! SUBROUTINE rrtmgp_lw_rte_run
! #########################################################################################
!! \section arg_table_rrtmgp_lw_run Argument Table
!! \section arg_table_rrtmgp_lw_rte_run Argument Table
!! | local_name | standard_name | long_name | units | rank | type | kind | intent | optional |
!! |-----------------------|-----------------------------------------------------------------------------------------------|---------------------------------------------------------------------|-------|------|-----------------------|-----------|--------|----------|
!! | Model | GFS_control_type_instance | Fortran DDT containing FV3-GFS model control parameters | DDT | 0 | GFS_control_type | | in | F |
Expand All @@ -50,7 +50,7 @@ end subroutine rrtmgp_lw_init
!! | errmsg | ccpp_error_message | error message for error handling in CCPP | none | 0 | character | len=* | out | F |
!! | errflg | ccpp_error_flag | error flag for error handling in CCPP | flag | 0 | integer | | out | F |
!!
subroutine rrtmgp_lw_run(Model, Statein, Radtend, ncol, lw_gas_props, p_lay, t_lay, p_lev, &
subroutine rrtmgp_lw_rte_run(Model, Statein, Radtend, ncol, lw_gas_props, p_lay, t_lay, p_lev, &
skt, sources, optical_props_clrsky, optical_props_cloud, optical_props_aerosol, lslwr,&
fluxUP_allsky, fluxDOWN_allsky, fluxUP_clrsky, fluxDOWN_clrsky, hlw0, hlwb, errmsg, errflg)

Expand Down Expand Up @@ -134,9 +134,9 @@ subroutine rrtmgp_lw_run(Model, Statein, Radtend, ncol, lw_gas_props, p_lay, t_l

! Compute clear-sky fluxes (if requested)
! Clear-sky fluxes are gas+aerosol
call check_error_msg('rrtmgp_lw_run',optical_props_aerosol%increment(optical_props_clrsky))
call check_error_msg('rrtmgp_lw_rte_run',optical_props_aerosol%increment(optical_props_clrsky))
if (l_ClrSky_HR) then
call check_error_msg('rrtmgp_lw_run',rte_lw( &
call check_error_msg('rrtmgp_lw_rte_run',rte_lw( &
optical_props_clrsky, & ! IN - optical-properties
top_at_1, & ! IN - veritcal ordering flag
sources, & ! IN - source function
Expand All @@ -149,8 +149,8 @@ subroutine rrtmgp_lw_run(Model, Statein, Radtend, ncol, lw_gas_props, p_lay, t_l

! All-sky fluxes
! Clear-sky fluxes are (gas+aerosol)+clouds
call check_error_msg('rrtmgp_lw_run',optical_props_cloud%increment(optical_props_clrsky))
call check_error_msg('rrtmgp_lw_run',rte_lw( &
call check_error_msg('rrtmgp_lw_rte_run',optical_props_cloud%increment(optical_props_clrsky))
call check_error_msg('rrtmgp_lw_rte_run',rte_lw( &
optical_props_clrsky, & ! IN - optical-properties
top_at_1, & ! IN - veritcal ordering flag
sources, & ! IN - source function
Expand All @@ -160,13 +160,13 @@ subroutine rrtmgp_lw_run(Model, Statein, Radtend, ncol, lw_gas_props, p_lay, t_l
fluxUP_allsky = flux_allsky%flux_up
fluxDOWN_allsky = flux_allsky%flux_dn

end subroutine rrtmgp_lw_run
end subroutine rrtmgp_lw_rte_run

! #########################################################################################
! SUBROUTINE rrtmgp_lw_finalize
! SUBROUTINE rrtmgp_lw_rte_finalize
! #########################################################################################
subroutine rrtmgp_lw_finalize()
end subroutine rrtmgp_lw_finalize
subroutine rrtmgp_lw_rte_finalize()
end subroutine rrtmgp_lw_rte_finalize


end module rrtmgp_lw
end module rrtmgp_lw_rte
44 changes: 22 additions & 22 deletions physics/rrtmgp_sw.F90 → physics/rrtmgp_sw_rte.F90
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
! ###########################################################################################
! ###########################################################################################
module rrtmgp_sw
module rrtmgp_sw_rte
use machine, only: kind_phys
use GFS_typedefs, only: GFS_control_type, GFS_radtend_type, GFS_statein_type
use mo_rte_kind, only: wl
Expand All @@ -13,20 +13,20 @@ module rrtmgp_sw
use module_radsw_parameters, only: cmpfsw_type
use rrtmgp_aux, only: check_error_msg

public rrtmgp_sw_init, rrtmgp_sw_run, rrtmgp_sw_finalize
public rrtmgp_sw_rte_init, rrtmgp_sw_rte_run, rrtmgp_sw_rte_finalize

contains

! #########################################################################################
! SUBROUTINE rrtmgp_sw_init
! SUBROUTINE rrtmgp_sw_rte_init
! #########################################################################################
subroutine rrtmgp_sw_init()
end subroutine rrtmgp_sw_init
subroutine rrtmgp_sw_rte_init()
end subroutine rrtmgp_sw_rte_init

! #########################################################################################
! SUBROUTINE rrtmgp_sw_run
! SUBROUTINE rrtmgp_sw_rte_run
! #########################################################################################
!! \section arg_table_rrtmgp_sw_run Argument Table
!! \section arg_table_rrtmgp_sw_rte_run Argument Table
!! | local_name | standard_name | long_name | units | rank | type | kind | intent | optional |
!! |-------------------------|------------------------------------------------------------------------------------------------|--------------------------------------------------------------------------|-------|------|-----------------------|-----------|--------|----------|
!! | Model | GFS_control_type_instance | Fortran DDT containing FV3-GFS model control parameters | DDT | 0 | GFS_control_type | | in | F |
Expand Down Expand Up @@ -55,7 +55,7 @@ end subroutine rrtmgp_sw_init
!! | errmsg | ccpp_error_message | error message for error handling in CCPP | none | 0 | character | len=* | out | F |
!! | errflg | ccpp_error_flag | error flag for error handling in CCPP | flag | 0 | integer | | out | F |
!!
subroutine rrtmgp_sw_run(Model, Radtend, Statein, ncol, sw_gas_props, p_lay, t_lay, p_lev, gas_concentrations, &
subroutine rrtmgp_sw_rte_run(Model, Radtend, Statein, ncol, sw_gas_props, p_lay, t_lay, p_lev, gas_concentrations, &
optical_props_clrsky, optical_props_cloud, optical_props_aerosol, &
lsswr, nday, idxday, toa_src, hsw0, hswb, scmpsw, &
fluxUP_allsky, fluxDOWN_allsky, fluxUP_clrsky, fluxDOWN_clrsky, errmsg, errflg)
Expand Down Expand Up @@ -158,25 +158,25 @@ subroutine rrtmgp_sw_run(Model, Radtend, Statein, ncol, sw_gas_props, p_lay, t_l

! Subset the cloud and aerosol radiative properties over daylit points.
! Cloud optics [nDay,Model%levs,nGpts]
call check_error_msg('rrtmgp_sw_run',optical_props_cloud_daylit%alloc_2str(nday, Model%levs, sw_gas_props))
call check_error_msg('rrtmgp_sw_rte_run',optical_props_cloud_daylit%alloc_2str(nday, Model%levs, sw_gas_props))
optical_props_cloud_daylit%tau = optical_props_cloud%tau(idxday,:,:)
optical_props_cloud_daylit%ssa = optical_props_cloud%ssa(idxday,:,:)
optical_props_cloud_daylit%g = optical_props_cloud%g(idxday,:,:)
! Aerosol optics [nDay,Model%levs,nBands]
call check_error_msg('rrtmgp_sw_run',optical_props_aerosol_daylit%alloc_2str(nday, Model%levs, sw_gas_props%get_band_lims_wavenumber()))
call check_error_msg('rrtmgp_sw_rte_run',optical_props_aerosol_daylit%alloc_2str(nday, Model%levs, sw_gas_props%get_band_lims_wavenumber()))
optical_props_aerosol_daylit%tau = optical_props_aerosol%tau(idxday,:,:)
optical_props_aerosol_daylit%ssa = optical_props_aerosol%ssa(idxday,:,:)
optical_props_aerosol_daylit%g = optical_props_aerosol%g(idxday,:,:)
! Clear-sky optics [nDay,Model%levs,nGpts]
call check_error_msg('rrtmgp_sw_run',optical_props_clrsky_daylit%alloc_2str(nday, Model%levs, sw_gas_props))
call check_error_msg('rrtmgp_sw_rte_run',optical_props_clrsky_daylit%alloc_2str(nday, Model%levs, sw_gas_props))
optical_props_clrsky_daylit%tau = optical_props_clrsky%tau(idxday,:,:)
optical_props_clrsky_daylit%ssa = optical_props_clrsky%ssa(idxday,:,:)
optical_props_clrsky_daylit%g = optical_props_clrsky%g(idxday,:,:)

! Similarly, subset the gas concentrations.
do iGas=1,Model%nGases
call check_error_msg('rrtmgp_sw_run',gas_concentrations%get_vmr(trim(Radtend%active_gases(iGas,1)),vmrTemp))
call check_error_msg('rrtmgp_sw_run',gas_concentrations_daylit%set_vmr(trim(Radtend%active_gases(iGas,1)),vmrTemp(idxday,:)))
call check_error_msg('rrtmgp_sw_rte_run',gas_concentrations%get_vmr(trim(Radtend%active_gases(iGas,1)),vmrTemp))
call check_error_msg('rrtmgp_sw_rte_run',gas_concentrations_daylit%set_vmr(trim(Radtend%active_gases(iGas,1)),vmrTemp(idxday,:)))
enddo

! Initialize RRTMGP DDT containing 2D(3D) fluxes
Expand All @@ -192,9 +192,9 @@ subroutine rrtmgp_sw_run(Model, Radtend, Statein, ncol, sw_gas_props, p_lay, t_l

! Compute clear-sky fluxes (if requested)
! Clear-sky fluxes are gas+aerosol
call check_error_msg('rrtmgp_sw_run',optical_props_aerosol_daylit%increment(optical_props_clrsky_daylit))
call check_error_msg('rrtmgp_sw_rte_run',optical_props_aerosol_daylit%increment(optical_props_clrsky_daylit))
if (l_ClrSky_HR) then
call check_error_msg('rrtmgp_sw_run',rte_sw( &
call check_error_msg('rrtmgp_sw_rte_run',rte_sw( &
optical_props_clrsky_daylit, & ! IN - optical-properties
top_at_1, & ! IN - veritcal ordering flag
Radtend%coszen(idxday), & ! IN - Cosine of solar zenith angle
Expand All @@ -208,8 +208,8 @@ subroutine rrtmgp_sw_run(Model, Radtend, Statein, ncol, sw_gas_props, p_lay, t_l
endif

! Compute all-sky fluxes
call check_error_msg('rrtmgp_sw_run',optical_props_cloud_daylit%increment(optical_props_clrsky_daylit))
call check_error_msg('rrtmgp_sw_run',rte_sw( &
call check_error_msg('rrtmgp_sw_rte_run',optical_props_cloud_daylit%increment(optical_props_clrsky_daylit))
call check_error_msg('rrtmgp_sw_rte_run',rte_sw( &
optical_props_clrsky_daylit, & ! IN - optical-properties
top_at_1, & ! IN - veritcal ordering flag
Radtend%coszen(idxday), & ! IN - Cosine of solar zenith angle
Expand All @@ -222,12 +222,12 @@ subroutine rrtmgp_sw_run(Model, Radtend, Statein, ncol, sw_gas_props, p_lay, t_l
fluxDOWN_allsky(idxday,:) = flux_allsky%flux_dn

endif
end subroutine rrtmgp_sw_run
end subroutine rrtmgp_sw_rte_run

! #########################################################################################
! SUBROUTINE rrtmgp_sw_finalize
! SUBROUTINE rrtmgp_sw_rte_finalize
! #########################################################################################
subroutine rrtmgp_sw_finalize()
end subroutine rrtmgp_sw_finalize
subroutine rrtmgp_sw_rte_finalize()
end subroutine rrtmgp_sw_rte_finalize

end module rrtmgp_sw
end module rrtmgp_sw_rte

0 comments on commit 044c880

Please sign in to comment.