Skip to content

Commit

Permalink
Reverted some local changes.
Browse files Browse the repository at this point in the history
  • Loading branch information
dustinswales committed Feb 12, 2020
1 parent 8d42056 commit 6473891
Show file tree
Hide file tree
Showing 6 changed files with 13 additions and 124 deletions.
6 changes: 3 additions & 3 deletions physics/radiation_clouds.f
Original file line number Diff line number Diff line change
Expand Up @@ -2485,10 +2485,10 @@ subroutine progcld5 &
cip (i,k) = 0.0
crp (i,k) = 0.0
csp (i,k) = 0.0
rew (i,k) = reliq_def ! default liq radius to 10 micron
rei (i,k) = reice_def ! default ice radius to 50 micron
rew (i,k) = re_cloud(i,k)
rei (i,k) = re_ice(i,k)
rer (i,k) = rrain_def ! default rain radius to 1000 micron
res (i,k) = rsnow_def
res (i,k) = re_snow(i,K)
! tem2d (i,k) = min( 1.0, max( 0.0, (con_ttp-tlyr(i,k))*0.05 ) )
clwf(i,k) = 0.0
enddo
Expand Down
40 changes: 9 additions & 31 deletions physics/radlw_main.f
Original file line number Diff line number Diff line change
Expand Up @@ -255,9 +255,6 @@ module rrtmg_lw
use module_radlw_avplank, only : totplnk
use module_radlw_ref, only : preflog, tref, chi_mls
!
#ifdef MPI
use mpi
#endif
implicit none
!
private
Expand Down Expand Up @@ -355,15 +352,9 @@ module rrtmg_lw
! ================
contains
! ================
!! \section arg_table_rrtmg_lw_init
!! \htmlinclude rrtmg_lw.html
!!
subroutine rrtmg_lw_init (mpicomm, mpirank, mpiroot)
! Inputs
integer, intent(in) :: mpicomm,mpirank,mpiroot
end subroutine rrtmg_lw_init
subroutine rrtmg_lw_init ()
end subroutine rrtmg_lw_init
!> \defgroup module_radlw_main GFS RRTMG Longwave Module
!! \brief This module includes NCEP's modifications of the RRTMG-LW radiation
Expand All @@ -389,7 +380,7 @@ end subroutine rrtmg_lw_init
!! This model is provided as is without any express or implied warranties.
!! (http://www.rtweb.aer.com/)
!! \section arg_table_rrtmg_lw_run Argument Table
!! \htmlinclude rrtmg_lw.html
!! \htmlinclude rrtmg_lw_run.html
!!
!> \section gen_lwrad RRTMG Longwave Radiation Scheme General Algorithm
!> @{
Expand All @@ -398,7 +389,7 @@ subroutine rrtmg_lw_run &
& gasvmr_ch4, gasvmr_o2, gasvmr_co, gasvmr_cfc11, &
& gasvmr_cfc12, gasvmr_cfc22, gasvmr_ccl4, &
& icseed,aeraod,aerssa,sfemis,sfgtmp, &
& dzlyr,delpin,de_lgth, lon, lat, &
& dzlyr,delpin,de_lgth, &
& npts, nlay, nlp1, lprnt, cld_cf, lslwr, &
& hlwc,topflx,sfcflx,cldtau, & ! --- outputs
& HLW0,HLWB,FLXPRF, & ! --- optional
Expand Down Expand Up @@ -597,7 +588,7 @@ subroutine rrtmg_lw_run &
& cld_od
real (kind=kind_phys), dimension(npts), intent(in) :: sfemis, &
& sfgtmp, de_lgth, lon, lat
& sfgtmp, de_lgth
real (kind=kind_phys), dimension(npts,nlay,nbands),intent(in):: &
& aeraod, aerssa
Expand Down Expand Up @@ -726,6 +717,7 @@ subroutine rrtmg_lw_run &
! endif
! --- ... loop over horizontal npts profiles
lab_do_iplon : do iplon = 1, npts
!> -# Read surface emissivity.
Expand Down Expand Up @@ -1022,7 +1014,6 @@ subroutine rrtmg_lw_run &
if ( lcf1 ) then
cldfrc = ceiling(cldfrc)
call cldprop &
! --- inputs:
& ( cldfrc,clwp,relw,ciwp,reiw,cda1,cda2,cda3,cda4, &
Expand All @@ -1031,8 +1022,6 @@ subroutine rrtmg_lw_run &
& cldfmc, taucld &
& )
!djs taucld(2,:) = taucld(1,:)
! --- ... save computed layer cloud optical depth for output
! rrtm band-7 is apprx 10mu channel (or use spectral mean of bands 6-8)
Expand Down Expand Up @@ -1171,7 +1160,6 @@ subroutine rrtmg_lw_run &
endif ! end if_isubclw_block
!> -# Save outputs.
topflx(iplon)%upfxc = totuflux(nlay)
topflx(iplon)%upfx0 = totuclfl(nlay)
Expand Down Expand Up @@ -1257,19 +1245,8 @@ subroutine rrtmg_lw_run &
end subroutine rrtmg_lw_run
!-----------------------------------
!> @}
!! \section arg_table_rrtmg_lw_finalize Argument Table
!! \htmlinclude rrtmg_lw.html
!!
subroutine rrtmg_lw_finalize (mpicomm, mpirank, mpiroot)
! Inputs
integer, intent(in) :: mpicomm,mpirank,mpiroot
! Local variables
integer :: ierr
#ifdef MPI
call MPI_BARRIER(mpicomm, ierr)
#endif
end subroutine rrtmg_lw_finalize
subroutine rrtmg_lw_finalize ()
end subroutine rrtmg_lw_finalize
Expand Down Expand Up @@ -3671,6 +3648,7 @@ subroutine rtrnmc &

!> -# Process longwave output from band for total and clear streams.
!! Calculate upward, downward, and net flux.

flxfac = wtdiff * fluxfac

do k = 0, nlay
Expand Down
76 changes: 0 additions & 76 deletions physics/radlw_main.meta
Original file line number Diff line number Diff line change
@@ -1,32 +1,3 @@
[ccpp-arg-table]
name = rrtmg_lw_init
type = scheme
[mpirank]
standard_name = mpi_rank
long_name = current MPI rank
units = index
dimensions = ()
type = integer
intent = in
optional = F
[mpiroot]
standard_name = mpi_root
long_name = master MPI rank
units = index
dimensions = ()
type = integer
intent = in
optional = F
[mpicomm]
standard_name = mpi_comm
long_name = MPI communicator
units = index
dimensions = ()
type = integer
intent = in
optional = F

########################################################################
[ccpp-arg-table]
name = rrtmg_lw_run
type = scheme
Expand Down Expand Up @@ -236,24 +207,6 @@
kind = kind_phys
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
[npts]
standard_name = horizontal_loop_extent
long_name = horizontal dimension
Expand Down Expand Up @@ -435,32 +388,3 @@
type = integer
intent = out
optional = F

########################################################################
[ccpp-arg-table]
name = rrtmg_lw_finalize
type = scheme
[mpirank]
standard_name = mpi_rank
long_name = current MPI rank
units = index
dimensions = ()
type = integer
intent = in
optional = F
[mpiroot]
standard_name = mpi_root
long_name = master MPI rank
units = index
dimensions = ()
type = integer
intent = in
optional = F
[mpicomm]
standard_name = mpi_comm
long_name = MPI communicator
units = index
dimensions = ()
type = integer
intent = in
optional = F
6 changes: 0 additions & 6 deletions physics/radlw_param.meta
Original file line number Diff line number Diff line change
Expand Up @@ -23,9 +23,3 @@
units = DDT
dimensions = ()
type = sfcflw_type
[proflw_type]
standard_name = proflw_type
long_name = definition of type proflw_type
units = DDT
dimensions = ()
type = proflw_type
3 changes: 1 addition & 2 deletions physics/radsw_main.f
Original file line number Diff line number Diff line change
Expand Up @@ -1077,15 +1077,14 @@ subroutine rrtmg_sw_run &

if (zcf1 > f_zero) then ! cloudy sky column

cfrac = ceiling(cfrac)
call cldprop &
! --- inputs:
& ( cfrac,cliqp,reliq,cicep,reice,cdat1,cdat2,cdat3,cdat4, &
& zcf1, nlay, ipseed(j1), dz, delgth, &
! --- outputs:
& taucw, ssacw, asycw, cldfrc, cldfmc &
& )

! --- ... save computed layer cloud optical depth for output
! rrtm band 10 is approx to the 0.55 mu spectrum

Expand Down
6 changes: 0 additions & 6 deletions physics/radsw_param.meta
Original file line number Diff line number Diff line change
Expand Up @@ -34,9 +34,3 @@
units = DDT
dimensions = ()
type = cmpfsw_type
[profsw_type]
standard_name = profsw_type
long_name = definition of type profsw_type
units = DDT
dimensions = ()
type = profsw_type

0 comments on commit 6473891

Please sign in to comment.