Class rad_C1998
In: radiation/rad_C1998.f90

Chou et al (1998) による短波放射用雲モデル

Cloud model for short wave radiation model described by Chou et al (1998)

Note that Japanese and English are described in parallel.

短波放射モデル.

This is a model of short wave radiation.

References

 Chou, M.-D., M. J. Suarez, C.-H. Ho, M. M.-H. Yan, and K.-T. Lee,
   Parameterizations for cloud overlapping and shortwave single-scattering
   properties for use in general circulation and cloud ensemble models,
   J. Climate, 11, 202-214, 1998.

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 dc_message gridset dc_iounit

Public Instance methods

Subroutine :
iband :integer , intent(in )
xyz_REff(0:imax-1, 1:jmax, 1:kmax) :real(DP) , intent(in )
xyz_CloudExtCoef(0:imax-1, 1:jmax, 1:kmax) :real(DP) , intent(out)
xyz_CloudCoAlb(0:imax-1, 1:jmax, 1:kmax) :real(DP) , intent(out)
xyz_CloudAF(0:imax-1, 1:jmax, 1:kmax) :real(DP) , intent(out)

[Source]

  subroutine RadC1998CalcCloudOptProp( Spec, iband, xyz_REff, xyz_CloudExtCoef, xyz_CloudCoAlb, xyz_CloudAF )


    ! USE statements
    !

    character(len=*), intent(in ) :: SPEC
    integer         , intent(in ) :: iband
    real(DP)        , intent(in ) :: xyz_REff        (0:imax-1, 1:jmax, 1:kmax)
    real(DP)        , intent(out) :: xyz_CloudExtCoef(0:imax-1, 1:jmax, 1:kmax)
    real(DP)        , intent(out) :: xyz_CloudCoAlb  (0:imax-1, 1:jmax, 1:kmax)
    real(DP)        , intent(out) :: xyz_CloudAF     (0:imax-1, 1:jmax, 1:kmax)



    !
    ! Work variables
    !
    integer :: l


    ! 初期化確認
    ! Initialization check
    !
    if ( .not. rad_c1998_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    l = iband

    if ( Spec == 'Ice' ) then

      xyz_CloudExtCoef = aa_IceCloudExtCoefParams(1,l) + aa_IceCloudExtCoefParams(2,l) / xyz_REff

      xyz_CloudCoAlb  = aa_IceCloudCoAlbParams(1,l) + aa_IceCloudCoAlbParams(2,l) * xyz_REff + aa_IceCloudCoAlbParams(3,l) * xyz_REff**2

      xyz_CloudAF = aa_IceCloudAFParams(1,l) + aa_IceCloudAFParams(2,l) * xyz_REff + aa_IceCloudAFParams(3,l) * xyz_REff**2

    else if ( Spec == 'Liquid' ) then

      xyz_CloudExtCoef = aa_WatCloudExtCoefParams(1,l) + aa_WatCloudExtCoefParams(2,l) / xyz_REff

      xyz_CloudCoAlb  = aa_WatCloudCoAlbParams(1,l) + aa_WatCloudCoAlbParams(2,l) * xyz_REff + aa_WatCloudCoAlbParams(3,l) * xyz_REff**2

      xyz_CloudAF = aa_WatCloudAFParams(1,l) + aa_WatCloudAFParams(2,l) * xyz_REff + aa_WatCloudAFParams(3,l) * xyz_REff**2

    else
      call MessageNotify( 'E', module_name, 'Unsupported specie, %c', c1 = trim( Spec ) )
    end if


  end subroutine RadC1998CalcCloudOptProp
Subroutine :

[Source]

  subroutine RadC1998Init


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

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

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


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

    integer :: l


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


    if ( rad_c1998_inited ) return


    ! デフォルト値の設定
    ! 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 = rad_C1998_nml,      & ! (out)
!!$        & iostat = iostat_nml )             ! (out)
!!$      close( unit_nml )
!!$
!!$      call NmlutilMsg( iostat_nml, module_name ) ! (in)
!!$    end if


    do l = 1, nband1 + nband2
      ! from g-1 m2 to kg-1 m2
      aa_WatCloudExtCoefParams(1,l) = aa_WatCloudExtCoefParams(1,l) * 1.0d3
      aa_IceCloudExtCoefParams(1,l) = aa_IceCloudExtCoefParams(1,l) * 1.0d3
      ! from g-1 m2 micron to kg-1 m2 m
      aa_WatCloudExtCoefParams(2,l) = aa_WatCloudExtCoefParams(2,l) * 1.0d3 * 1.0d-6
      aa_IceCloudExtCoefParams(2,l) = aa_IceCloudExtCoefParams(2,l) * 1.0d3 * 1.0d-6

      ! from micron-1 to m-1
      aa_WatCloudCoAlbParams  (2,l) = aa_WatCloudCoAlbParams  (2,l) * 1.0d6
      aa_IceCloudCoAlbParams  (2,l) = aa_IceCloudCoAlbParams  (2,l) * 1.0d6
      ! from micron-2 to m-2
      aa_WatCloudCoAlbParams  (3,l) = aa_WatCloudCoAlbParams  (3,l) * 1.0d12
      aa_IceCloudCoAlbParams  (3,l) = aa_IceCloudCoAlbParams  (3,l) * 1.0d12

      ! from micron-1 to m-1
      aa_WatCloudAFParams     (2,l) = aa_WatCloudAFParams     (2,l) * 1.0d6
      aa_IceCloudAFParams     (2,l) = aa_IceCloudAFParams     (2,l) * 1.0d6
      ! from micron-2 to m-2
      aa_WatCloudAFParams     (3,l) = aa_WatCloudAFParams     (3,l) * 1.0d6
      aa_IceCloudAFParams     (3,l) = aa_IceCloudAFParams     (3,l) * 1.0d6
    end do


    ! 印字 ; 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) )


    rad_c1998_inited = .true.

  end subroutine RadC1998Init

Private Instance methods

aa_IceCloudAFParams
Variable :
aa_IceCloudAFParams(1:3, 1:nband1+nband2) :real(DP), save
aa_IceCloudCoAlbParams
Variable :
aa_IceCloudCoAlbParams(1:3, 1:nband1+nband2) :real(DP), save
aa_IceCloudExtCoefParams
Variable :
aa_IceCloudExtCoefParams(1:2, 1:nband1+nband2) :real(DP), save
aa_WatCloudAFParams
Variable :
aa_WatCloudAFParams(1:3, 1:nband1+nband2) :real(DP), save
aa_WatCloudCoAlbParams
Variable :
aa_WatCloudCoAlbParams(1:3, 1:nband1+nband2) :real(DP), save
aa_WatCloudExtCoefParams
Variable :
aa_WatCloudExtCoefParams(1:2, 1:nband1+nband2) :real(DP), save
module_name
Constant :
module_name = ‘rad_C1998 :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)
rad_c1998_inited
Variable :
rad_c1998_inited :logical , save
version
Constant :
version = ’$Name: $’ // ’$Id: rad_C1998.f90,v 1.4 2011/11/30 03:44:09 yot Exp $’ :character(*), parameter
: モジュールのバージョン Module version