mo_rte_config.F90 Source File


This file depends on

sourcefile~~mo_rte_config.f90~~EfferentGraph sourcefile~mo_rte_config.f90 mo_rte_config.F90 sourcefile~mo_rte_kind.f90 mo_rte_kind.F90 sourcefile~mo_rte_config.f90->sourcefile~mo_rte_kind.f90

Files dependent on this one

sourcefile~~mo_rte_config.f90~~AfferentGraph sourcefile~mo_rte_config.f90 mo_rte_config.F90 sourcefile~mo_rte_lw.f90 mo_rte_lw.F90 sourcefile~mo_rte_lw.f90->sourcefile~mo_rte_config.f90 sourcefile~mo_optical_props.f90 mo_optical_props.F90 sourcefile~mo_rte_lw.f90->sourcefile~mo_optical_props.f90 sourcefile~mo_fluxes.f90 mo_fluxes.F90 sourcefile~mo_rte_lw.f90->sourcefile~mo_fluxes.f90 sourcefile~mo_source_functions.f90 mo_source_functions.F90 sourcefile~mo_rte_lw.f90->sourcefile~mo_source_functions.f90 sourcefile~mo_optical_props.f90->sourcefile~mo_rte_config.f90 sourcefile~mo_fluxes.f90->sourcefile~mo_rte_config.f90 sourcefile~mo_fluxes.f90->sourcefile~mo_optical_props.f90 sourcefile~mo_rte_sw.f90 mo_rte_sw.F90 sourcefile~mo_rte_sw.f90->sourcefile~mo_rte_config.f90 sourcefile~mo_rte_sw.f90->sourcefile~mo_optical_props.f90 sourcefile~mo_rte_sw.f90->sourcefile~mo_fluxes.f90 sourcefile~mo_source_functions.f90->sourcefile~mo_optical_props.f90

Contents

Source Code


Source Code

! This code is part of RRTM for GCM Applications - Parallel (RRTMGP)
!
! Contacts: Robert Pincus and Eli Mlawer
! email:  rrtmgp@aer.com
!
! Copyright 2020-  Atmospheric and Environmental Research,
!    Regents of the University of Colorado,
!    Trustees of Columbia University in the City of New York
! All right reserved.
!
! Use and duplication is permitted under the terms of the
!    BSD 3-clause license, see http://opensource.org/licenses/BSD-3-Clause

!> -------------------------------------------------------------------------------------------------
!>
!> ## Control input sanitization in Fortan front-end
!>   Provides public access to two proteced module variables
!>
!> -------------------------------------------------------------------------------------------------
module mo_rte_config
  use mo_rte_kind, only: wl
  implicit none
  private

  logical(wl), protected, public :: check_extents = .true.
  logical(wl), protected, public :: check_values  = .true.

  !> Specify checking of extents and values individually, or all checks together
  interface rte_config_checks
    module procedure rte_config_checks_each, rte_config_checks_all
  end interface
  public :: rte_config_checks
contains
  ! --------------------------------------------------------------
  !> Do extents and/or values checks within RTE+RRTMGP Fortran classes
  subroutine rte_config_checks_each(extents, values)
    logical(wl), intent(in) :: extents, values

    check_extents = extents
    check_values  = values
  end subroutine rte_config_checks_each
  ! --------------------------------------------------------------
  !> Do all checks within RTE+RRTMGP Fortran classes
  subroutine rte_config_checks_all(do_checks)
    logical(wl), intent(in) :: do_checks

    check_extents = do_checks
    check_values  = do_checks
  end subroutine rte_config_checks_all
  ! --------------------------------------------------------------
end module mo_rte_config