LCOV - code coverage report
Current view: top level - physics/rrtmgp - radconstants.F90 (source / functions) Hit Total Coverage
Test: coverage.info Lines: 66 98 67.3 %
Date: 2025-03-13 19:21:45 Functions: 5 5 100.0 %

          Line data    Source code
       1             : module radconstants
       2             : 
       3             : ! This module contains constants that are specific to the radiative transfer
       4             : ! code used in the RRTMGP model.
       5             : 
       6             : use shr_kind_mod,         only: r8 => shr_kind_r8
       7             : use mo_gas_optics_rrtmgp, only: ty_gas_optics_rrtmgp
       8             : use cam_abortutils,       only: endrun
       9             : 
      10             : implicit none
      11             : private
      12             : save
      13             : 
      14             : ! Number of bands in SW and LW.  These values must match data in the RRTMGP coefficients datasets.
      15             : ! But they are needed to allocate space in the physics buffer and need to be available before the
      16             : ! RRTMGP datasets are read.  So they are set as parameters here and checked in the 
      17             : ! set_wavenumber_bands subroutine after the datasets are read.
      18             : integer, parameter, public :: nswbands = 14
      19             : integer, parameter, public :: nlwbands = 16
      20             : 
      21             : ! Band limits (set from data in RRTMGP coefficient datasets)
      22             : real(r8), target :: wavenumber_low_shortwave(nswbands)
      23             : real(r8), target :: wavenumber_high_shortwave(nswbands)
      24             : real(r8), target :: wavenumber_low_longwave(nlwbands)
      25             : real(r8), target :: wavenumber_high_longwave(nlwbands)
      26             : 
      27             : logical :: wavenumber_boundaries_set = .false.
      28             : 
      29             : ! First and last g-point for each band.
      30             : integer, public, protected :: band2gpt_sw(2,nswbands)
      31             : 
      32             : integer, public, protected :: nswgpts  ! number of SW g-points
      33             : integer, public, protected :: nlwgpts  ! number of LW g-points
      34             : 
      35             : ! These are indices to specific bands for diagnostic output and COSP input.
      36             : integer, public, protected :: idx_sw_diag = -1     ! band contains 500-nm wave
      37             : integer, public, protected :: idx_nir_diag = -1    ! band contains 1000-nm wave
      38             : integer, public, protected :: idx_uv_diag = -1     ! band contains 400-nm wave
      39             : integer, public, protected :: idx_lw_diag = -1     ! band contains 1000 cm-1 wave (H20 window)
      40             : integer, public, protected :: idx_sw_cloudsim = -1 ! band contains 670-nm wave (for COSP)
      41             : integer, public, protected :: idx_lw_cloudsim = -1 ! band contains 10.5 micron wave (for COSP)
      42             : 
      43             : ! GASES TREATED BY RADIATION (line spectra)
      44             : ! These names are recognized by RRTMGP.  They are in the coefficients files as
      45             : ! lower case strings.  These upper case names are used by CAM's namelist and 
      46             : ! rad_constituents module.
      47             : integer, public, parameter :: gasnamelength = 5
      48             : integer, public, parameter :: nradgas = 8
      49             : character(len=gasnamelength), public, parameter :: gaslist(nradgas) &
      50             :    = (/'H2O  ','O3   ', 'O2   ', 'CO2  ', 'N2O  ', 'CH4  ', 'CFC11', 'CFC12'/)
      51             : 
      52             : ! what is the minimum mass mixing ratio that can be supported by radiation implementation?
      53             : real(r8), public, parameter :: minmmr(nradgas) = epsilon(1._r8)
      54             : 
      55             : public :: &
      56             :    set_wavenumber_bands,       &
      57             :    get_sw_spectral_boundaries, &
      58             :    get_lw_spectral_boundaries, &
      59             :    get_band_index_by_value,    &
      60             :    rad_gas_index
      61             : 
      62             : !=========================================================================================
      63             : contains
      64             : !=========================================================================================
      65             : 
      66        1536 : subroutine set_wavenumber_bands(kdist_sw, kdist_lw)
      67             : 
      68             :    ! Set the low and high limits of the wavenumber grid for sw and lw.
      69             :    ! Values come from RRTMGP coefficients datasets, and are stored in the
      70             :    ! kdist objects.
      71             :    !
      72             :    ! Set band indices for bands containing specific wavelengths.
      73             : 
      74             :    ! Arguments
      75             :    type(ty_gas_optics_rrtmgp), intent(in) :: kdist_sw
      76             :    type(ty_gas_optics_rrtmgp), intent(in) :: kdist_lw
      77             : 
      78             :    ! Local variables
      79             :    integer :: istat
      80        1536 :    real(r8), allocatable :: values(:,:)
      81             : 
      82             :    character(len=128) :: errmsg
      83             :    character(len=*), parameter :: sub = 'set_wavenumber_bands'
      84             :    !----------------------------------------------------------------------------
      85             : 
      86             :    ! Check that number of sw/lw bands in gas optics files matches the parameters.
      87        1536 :    if (kdist_sw%get_nband() /= nswbands) then
      88           0 :       write(errmsg,'(a,i4,a,i4)') 'number of sw bands in file, ', kdist_sw%get_nband(), &
      89           0 :          ", doesn't match parameter nswbands= ", nswbands
      90           0 :       call endrun(sub//': ERROR: '//trim(errmsg))
      91             :    end if
      92        1536 :    if (kdist_lw%get_nband() /= nlwbands) then
      93           0 :       write(errmsg,'(a,i4,a,i4)') 'number of lw bands in file, ', kdist_lw%get_nband(), &
      94           0 :          ", doesn't match parameter nlwbands= ", nlwbands
      95           0 :       call endrun(sub//': ERROR: '//trim(errmsg))
      96             :    end if
      97             : 
      98        1536 :    nswgpts = kdist_sw%get_ngpt()
      99        1536 :    nlwgpts = kdist_lw%get_ngpt()
     100             : 
     101             :    ! SW band bounds in cm^-1
     102        1536 :    allocate( values(2,nswbands), stat=istat )
     103        1536 :    if (istat/=0) then
     104           0 :       call endrun(sub//': ERROR allocating array: values(2,nswbands)')
     105             :    end if
     106        1536 :    values = kdist_sw%get_band_lims_wavenumber()
     107       23040 :    wavenumber_low_shortwave = values(1,:)
     108       23040 :    wavenumber_high_shortwave = values(2,:)
     109             : 
     110             :    ! First and last g-point for each SW band:
     111       66048 :    band2gpt_sw = kdist_sw%get_band_lims_gpoint()
     112             : 
     113             :    ! Indices into specific bands
     114        1536 :    idx_sw_diag     = get_band_index_by_value('sw', 500.0_r8, 'nm')
     115        1536 :    idx_nir_diag    = get_band_index_by_value('sw', 1000.0_r8, 'nm')
     116        1536 :    idx_uv_diag     = get_band_index_by_value('sw', 400._r8, 'nm')
     117        1536 :    idx_sw_cloudsim = get_band_index_by_value('sw', 0.67_r8, 'micron')
     118             : 
     119        1536 :    deallocate(values)
     120             : 
     121             :    ! LW band bounds in cm^-1
     122        1536 :    allocate( values(2,nlwbands), stat=istat )
     123        1536 :    if (istat/=0) then
     124           0 :       call endrun(sub//': ERROR allocating array: values(2,nlwbands)')
     125             :    end if
     126        1536 :    values = kdist_lw%get_band_lims_wavenumber()
     127       26112 :    wavenumber_low_longwave = values(1,:)
     128       26112 :    wavenumber_high_longwave = values(2,:)
     129             : 
     130             :    ! Indices into specific bands
     131        1536 :    idx_lw_diag     = get_band_index_by_value('lw', 1000.0_r8, 'cm^-1')
     132        1536 :    idx_lw_cloudsim = get_band_index_by_value('lw', 10.5_r8, 'micron')
     133             : 
     134        1536 :    wavenumber_boundaries_set = .true.
     135             : 
     136        1536 : end subroutine set_wavenumber_bands
     137             : 
     138             : !=========================================================================================
     139             : 
     140        3072 : subroutine get_sw_spectral_boundaries(low_boundaries, high_boundaries, units)
     141             : 
     142             :    ! provide spectral boundaries of each shortwave band
     143             : 
     144             :    real(r8),    intent(out) :: low_boundaries(nswbands), high_boundaries(nswbands)
     145             :    character(*), intent(in) :: units ! requested units
     146             : 
     147             :    character(len=*), parameter :: sub = 'get_sw_spectral_boundaries'
     148             :    !----------------------------------------------------------------------------
     149             : 
     150        3072 :    if (.not. wavenumber_boundaries_set) then
     151           0 :       call endrun(sub//': ERROR, wavenumber boundaries not set. ')
     152             :    end if
     153             : 
     154        1536 :    select case (units)
     155             :    case ('inv_cm','cm^-1','cm-1')
     156        1536 :       low_boundaries = wavenumber_low_shortwave
     157        1536 :       high_boundaries = wavenumber_high_shortwave
     158             :    case('m','meter','meters')
     159           0 :       low_boundaries = 1.e-2_r8/wavenumber_high_shortwave
     160           0 :       high_boundaries = 1.e-2_r8/wavenumber_low_shortwave
     161             :    case('nm','nanometer','nanometers')
     162       23040 :       low_boundaries = 1.e7_r8/wavenumber_high_shortwave
     163       23040 :       high_boundaries = 1.e7_r8/wavenumber_low_shortwave
     164             :    case('um','micrometer','micrometers','micron','microns')
     165           0 :       low_boundaries = 1.e4_r8/wavenumber_high_shortwave
     166           0 :       high_boundaries = 1.e4_r8/wavenumber_low_shortwave
     167             :    case('cm','centimeter','centimeters')
     168           0 :       low_boundaries  = 1._r8/wavenumber_high_shortwave
     169           0 :       high_boundaries = 1._r8/wavenumber_low_shortwave
     170             :    case default
     171        3072 :       call endrun(sub//': ERROR, requested spectral units not recognized: '//units)
     172             :    end select
     173             : 
     174        3072 : end subroutine get_sw_spectral_boundaries
     175             : 
     176             : !=========================================================================================
     177             : 
     178        1536 : subroutine get_lw_spectral_boundaries(low_boundaries, high_boundaries, units)
     179             : 
     180             :    ! provide spectral boundaries of each longwave band
     181             : 
     182             :    real(r8), intent(out) :: low_boundaries(nlwbands), high_boundaries(nlwbands)
     183             :    character(*), intent(in) :: units ! requested units
     184             : 
     185             :    character(len=*), parameter :: sub = 'get_lw_spectral_boundaries'
     186             :    !----------------------------------------------------------------------------
     187             : 
     188        1536 :    if (.not. wavenumber_boundaries_set) then
     189           0 :       call endrun(sub//': ERROR, wavenumber boundaries not set. ')
     190             :    end if
     191             : 
     192           0 :    select case (units)
     193             :    case ('inv_cm','cm^-1','cm-1')
     194           0 :       low_boundaries  = wavenumber_low_longwave
     195           0 :       high_boundaries = wavenumber_high_longwave
     196             :    case('m','meter','meters')
     197           0 :       low_boundaries  = 1.e-2_r8/wavenumber_high_longwave
     198           0 :       high_boundaries = 1.e-2_r8/wavenumber_low_longwave
     199             :    case('nm','nanometer','nanometers')
     200           0 :       low_boundaries  = 1.e7_r8/wavenumber_high_longwave
     201           0 :       high_boundaries = 1.e7_r8/wavenumber_low_longwave
     202             :    case('um','micrometer','micrometers','micron','microns')
     203       26112 :       low_boundaries  = 1.e4_r8/wavenumber_high_longwave
     204       26112 :       high_boundaries = 1.e4_r8/wavenumber_low_longwave
     205             :    case('cm','centimeter','centimeters')
     206           0 :       low_boundaries  = 1._r8/wavenumber_high_longwave
     207           0 :       high_boundaries = 1._r8/wavenumber_low_longwave
     208             :    case default
     209        1536 :       call endrun(sub//': ERROR, requested spectral units not recognized: '//units)
     210             :    end select
     211             : 
     212        1536 : end subroutine get_lw_spectral_boundaries
     213             : 
     214             : !=========================================================================================
     215             : 
     216      389176 : integer function rad_gas_index(gasname)
     217             : 
     218             :    ! return the index in the gaslist array of the specified gasname
     219             : 
     220             :    character(len=*),intent(in) :: gasname
     221             :    integer :: igas
     222             : 
     223      389176 :    rad_gas_index = -1
     224     1751292 :    do igas = 1, nradgas
     225     1751292 :       if (trim(gaslist(igas)).eq.trim(gasname)) then
     226      389176 :          rad_gas_index = igas
     227      389176 :          return
     228             :       endif
     229             :    enddo
     230           0 :    call endrun ("rad_gas_index: can not find gas with name "//gasname)
     231           0 : end function rad_gas_index
     232             : 
     233             : !=========================================================================================
     234             : 
     235        9216 : function get_band_index_by_value(swlw, targetvalue, units) result(ans)
     236             : 
     237             :    ! Find band index for requested wavelength/wavenumber.
     238             : 
     239             :    character(len=*), intent(in) :: swlw        ! sw or lw bands
     240             :    real(r8),         intent(in) :: targetvalue  
     241             :    character(len=*), intent(in) :: units       ! units of targetvalue
     242             :    integer :: ans
     243             : 
     244             :    ! local
     245        9216 :    real(r8), pointer, dimension(:) :: lowboundaries, highboundaries
     246             :    real(r8) :: tgt
     247             :    integer  :: nbnds, i
     248             : 
     249             :    character(len=128) :: errmsg
     250             :    character(len=*), parameter :: sub = 'get_band_index_by_value'
     251             :    !----------------------------------------------------------------------------
     252             : 
     253        6144 :    select case (swlw)
     254             :    case ('sw','SW','shortwave')
     255        6144 :       nbnds = nswbands
     256        6144 :       lowboundaries  => wavenumber_low_shortwave
     257        6144 :       highboundaries => wavenumber_high_shortwave
     258             :    case ('lw', 'LW', 'longwave')
     259        3072 :       nbnds = nlwbands
     260        3072 :       lowboundaries  => wavenumber_low_longwave
     261        3072 :       highboundaries => wavenumber_high_longwave
     262             :    case default
     263           0 :       call endrun('radconstants.F90: get_band_index_by_value: type of bands not recognized: '//swlw)
     264             :    end select
     265             : 
     266             :    ! band info is in cm^-1 but target value may be other units,
     267             :    ! so convert targetvalue to cm^-1
     268        1536 :    select case (units)
     269             :    case ('inv_cm','cm^-1','cm-1')
     270        1536 :       tgt = targetvalue
     271             :    case('m','meter','meters')
     272           0 :       tgt = 1.0_r8 / (targetvalue * 1.e2_r8)
     273             :    case('nm','nanometer','nanometers')
     274        4608 :       tgt = 1.0_r8 / (targetvalue * 1.e-7_r8)
     275             :    case('um','micrometer','micrometers','micron','microns')
     276        3072 :       tgt = 1.0_r8 / (targetvalue * 1.e-4_r8)
     277             :    case('cm','centimeter','centimeters')
     278           0 :       tgt = 1._r8/targetvalue
     279             :    case default
     280        9216 :       call endrun('radconstants.F90: get_band_index_by_value: units not recognized: '//units)
     281             :    end select
     282             : 
     283             :    ! now just loop through the array
     284        9216 :    ans = 0
     285       84480 :    do i = 1,nbnds
     286       84480 :       if ((tgt > lowboundaries(i)) .and. (tgt <= highboundaries(i))) then
     287             :          ans = i
     288             :          exit
     289             :       end if
     290             :    end do
     291             : 
     292        9216 :    if (ans == 0) then
     293           0 :       write(errmsg,'(f10.3,a,a)') targetvalue, ' ', trim(units)
     294           0 :       call endrun(sub//': band not found containing wave: '//trim(errmsg))
     295             :    end if
     296             :    
     297        9216 : end function get_band_index_by_value
     298             : 
     299             : !=========================================================================================
     300             : 
     301             : end module radconstants

Generated by: LCOV version 1.14