Class radiation_CL1996
In: radiation/radiation_CL1996.f90

Chou and Lee (1996) による短波放射モデル

Short wave radiation model described by Chou and Lee (1996)

Note that Japanese and English are described in parallel.

短波放射モデル.

This is a model of short wave radiation.

References

 Chou, M.-D., and K.-T. Lee,
   Parameterizations for the absorption of solar radiation by water vapor and ozone,
   J. Atmos. Sci., 53, 1203-1208, 1996.

Procedures List

!$ ! RadiationFluxDennouAGCM :放射フラックスの計算
!$ ! RadiationDTempDt :放射フラックスによる温度変化の計算
!$ ! RadiationFluxOutput :放射フラックスの出力
!$ ! RadiationFinalize :終了処理 (モジュール内部の変数の割り付け解除)
!$ ! ———— :————
!$ ! RadiationFluxDennouAGCM :Calculate radiation flux
!$ ! RadiationDTempDt :Calculate temperature tendency with radiation flux
!$ ! RadiationFluxOutput :Output radiation fluxes
!$ ! RadiationFinalize :Termination (deallocate variables in this module)

NAMELIST

!$ ! NAMELIST#radiation_DennouAGCM_nml

Methods

Included Modules

dc_types gridset constants namelist_util dc_iounit dc_message

Public Instance methods

Subroutine :
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyz_QVap(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyr_Press(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in )
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyz_H2ODelAbsAmt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)

[Source]

  subroutine RadiationCL1996H2ODelAbsAmt( xyz_Temp, xyz_QVap, xyr_Press, xyz_Press, xyz_H2ODelAbsAmt )


    ! USE statements
    !

    ! 
    ! Grid points settings
    !
    use gridset, only: imax, jmax, kmax    ! 
                               ! Number of vertical level

    !
    ! Physical constants settings
    !
    use constants, only: Grav, PI      ! $ \pi $ .
                                 ! Circular constant

    real(DP), intent(in ):: xyz_Temp        (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ):: xyz_QVap        (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ):: xyr_Press       (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(in ):: xyz_Press       (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(out):: xyz_H2ODelAbsAmt(0:imax-1, 1:jmax, 1:kmax)


    !
    ! Work variables
    !
    real(DP), parameter :: H2OScaleIndex = 0.8_DP
    real(DP), parameter :: RefPress      = 300.0d2
    real(DP), parameter :: RefTemp       = 240.0d0

    integer :: k


    if ( .not. radiation_cl1996_inited ) then
      call RadiationCL1996Init
    end if


    do k = 1, kmax
      xyz_H2ODelAbsAmt(:,:,k) = ( xyz_Press(:,:,k) / RefPress )**H2OScaleIndex * exp( 0.00135_DP * ( xyz_Temp(:,:,k) - RefTemp ) ) * xyz_QVap(:,:,k) * ( xyr_Press(:,:,k-1) - xyr_Press(:,:,k) ) / Grav
    end do


  end subroutine RadiationCL1996H2ODelAbsAmt
Subroutine :
iband :integer , intent(in )
ikdfbin :integer , intent(in )
KDFAbsCoef :real(DP), intent(out)
KDFWeight :real(DP), intent(out)

[Source]

  subroutine RadiationCL1996IRH2OKDFParams( iband, ikdfbin, KDFAbsCoef, KDFWeight )


    ! USE statements
    !

    integer , intent(in ):: iband
    integer , intent(in ):: ikdfbin
    real(DP), intent(out):: KDFAbsCoef
    real(DP), intent(out):: KDFWeight


    !
    ! Work variables
    !
    integer :: l
    integer :: m


    if ( .not. radiation_cl1996_inited ) then
      call RadiationCL1996Init
    end if

    l = iband
    m = ikdfbin

    KDFAbsCoef = a_IRH2Okdfk   (m)

    KDFWeight  = aa_IRH2Okdfdgi(m,l)


  end subroutine RadiationCL1996IRH2OKDFParams
Subroutine :
nbin :integer, intent(out)

[Source]

  subroutine RadiationCL1996IRH2ONumKDFBin( nbin )

    integer, intent(out) :: nbin

    if ( .not. radiation_cl1996_inited ) then
      call RadiationCL1996Init
    end if

    nbin = nkdf

  end subroutine RadiationCL1996IRH2ONumKDFBin
Subroutine :
nbands1 :integer, intent(out)
nbands2 :integer, intent(out)

[Source]

  subroutine RadiationCL1996NumBands( nbands1, nbands2 )

    integer, intent(out) :: nbands1
    integer, intent(out) :: nbands2

    if ( .not. radiation_cl1996_inited ) then
      call RadiationCL1996Init
    end if

    nbands1 = nband1
    nbands2 = nband2

  end subroutine RadiationCL1996NumBands
Subroutine :
iband :integer , intent(in )
UVVISFracSolarFlux :real(DP), intent(out)
UVVISO3AbsCoef :real(DP), intent(out)
UVVISRayScatCoef :real(DP), intent(out)

[Source]

  subroutine RadiationCL1996UVVISParams( iband, UVVISFracSolarFlux, UVVISO3AbsCoef, UVVISRayScatCoef )


    ! USE statements
    !

    integer , intent(in ):: iband
    real(DP), intent(out):: UVVISFracSolarFlux
    real(DP), intent(out):: UVVISO3AbsCoef
    real(DP), intent(out):: UVVISRayScatCoef


    !
    ! Work variables
    !
    integer :: l


    if ( .not. radiation_cl1996_inited ) then
      call RadiationCL1996Init
    end if

    l = iband

    UVVISFracSolarFlux = a_UVVIFracSolarFlux(l)
    UVVISO3AbsCoef     = a_UVVISO3AbsCoef   (l)
    UVVISRayScatCoef   = a_UVVISRayScatCoef (l)


  end subroutine RadiationCL1996UVVISParams

Private Instance methods

Subroutine :

[Source]

  subroutine RadiationCL1996Init


    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg

    ! ファイル入出力補助
    ! File I/O support
    !
    use dc_iounit, only: FileOpen

    ! メッセージ出力
    ! Message output
    !
    use dc_message, only: MessageNotify

!!$    ! ヒストリデータ出力
!!$    ! History data output
!!$    !
!!$    use gtool_historyauto, only: HistoryAutoAddVariable

    !
    ! Physical constants settings
    !
    use constants, only: Grav    ! $ g $ [m s-2].
                                 ! 
                                 ! Gravitational acceleration


!!$    integer:: unit_nml        ! NAMELIST ファイルオープン用装置番号.
!!$                              ! Unit number for NAMELIST file open
!!$    integer:: iostat_nml      ! NAMELIST 読み込み時の IOSTAT.
!!$                              ! IOSTAT of NAMELIST read

!!$    ! NAMELIST 変数群
!!$    ! NAMELIST group name
!!$    !
!!$    namelist /radiation_CL1996_nml/ !&
!!$      & ShortAtmosAlbedo
!!$          !
!!$          ! デフォルト値については初期化手続 "radiation_CL1996#RadiationCL1996Init"
!!$          ! のソースコードを参照のこと.
!!$          !
!!$          ! Refer to source codes in the initialization procedure
!!$          ! "radiation_LH74#RadiationLH74Init" for the default values.
!!$          !

    ! デフォルト値の設定
    ! Default values settings
    !

!!$    ! NAMELIST の読み込み
!!$    ! NAMELIST is input
!!$    !
!!$    if ( trim(namelist_filename) /= '' ) then
!!$      call FileOpen( unit_nml, &          ! (out)
!!$        & namelist_filename, mode = 'r' ) ! (in)
!!$
!!$      rewind( unit_nml )
!!$      read( unit_nml,                     & ! (in)
!!$        & nml = radiation_CL1996_nml,     & ! (out)
!!$        & iostat = iostat_nml )             ! (out)
!!$      close( unit_nml )
!!$
!!$      call NmlutilMsg( iostat_nml, module_name ) ! (in)
!!$    end if



    ! Unit is changed of k from g-1 cm2 to kg-1 m2.
    !
    a_IRH2Okdfk = a_IRH2Okdfk * 1.0d3 * 1.0d-4

    ! Convert unit of O3 absorption coefficient from (cm-atm)^{-1} to (kg m-2)^{-1}
    !   In order to convert unit from cm-1 atm-1 to m2 kg-1, multiply by
    !     1.0d2 / 101325.0d0 * 8.31432d0 / ( 48.0d-3 ) * 273.15d0.
    !
    a_UVVISO3AbsCoef = a_UVVISO3AbsCoef * 1.0d2 / 101325.0d0 * 8.31432d0 / ( 48.0d-3 ) * 273.15d0

    ! Convert unit of Rayleigh scattering coefficient from (mb)^{-1} to (kg m-2)^{-1}
    !   memo:
    !     1    mbar = 1e2 Pa
    !     1e-2 mbar = 1   Pa
    !
    a_UVVISRayScatCoef = a_UVVISRayScatCoef * 1.0d-2 * Grav



    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
!!$    call MessageNotify( 'M', module_name, 'ShortAtmosAlbedo = %f', d = (/ ShortAtmosAlbedo /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )


    radiation_cl1996_inited = .true.

  end subroutine RadiationCL1996Init
a_IRH2Okdfk
Variable :
a_IRH2Okdfk(1:nkdf) :real(DP), save
: k
a_UVVIFracSolarFlux
Variable :
a_UVVIFracSolarFlux(1:nband1) :real(DP), save
a_UVVISO3AbsCoef
Variable :
a_UVVISO3AbsCoef(1:nband1) :real(DP), save
a_UVVISRayScatCoef
Variable :
a_UVVISRayScatCoef(1:nband1) :real(DP), save
aa_IRH2Okdfdgi
Variable :
aa_IRH2Okdfdgi(1:nkdf,nband1+1:nband1+nband2) :real(DP), save
: k dist. func.
module_name
Constant :
module_name = ‘radiation_C1986‘ :character(*), parameter
: モジュールの名称. Module name
nband1
Constant :
nband1 = 8 :integer , parameter
:
  • 14500 to 57143 cm-1 (0.175 to 0.70 micron)
nband2
Constant :
nband2 = 3 :integer , parameter
:
  • 2600 to 14500 cm-1 (0.70-10 micron)
nkdf
Constant :
nkdf = 10 :integer , parameter
radiation_cl1996_inited
Variable :
radiation_cl1996_inited :logical , save
version
Constant :
version = ’$Name: dcpam5-20110221-4 $’ // ’$Id: radiation_CL1996.f90,v 1.1 2010-12-18 13:02:12 yot Exp $’ :character(*), parameter
: モジュールのバージョン Module version