Class rad_simple
In: radiation/rad_simple.f90

簡単放射モデル

Simple radiation model

Note that Japanese and English are described in parallel.

This is a simple radiation model.

References

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#rad_Simple_nml

Methods

Included Modules

dc_types gridset dc_message constants0 constants axesset rad_simple_SW_V2_0 rad_simple_LW dc_iounit namelist_util

Public Instance methods

Subroutine :
xy_SurfAlbedo( 0:imax-1, 1:jmax ) :real(DP), intent(in )
xy_SurfTemp( 0:imax-1, 1:jmax ) :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_Temp( 0:imax-1, 1:jmax, 1:kmax ) :real(DP), intent(in )
xyz_QH2OVap( 0:imax-1, 1:jmax, 1:kmax ) :real(DP), intent(in )
xyr_RadSUwFlux( 0:imax-1, 1:jmax, 0:kmax ) :real(DP), intent(out)
xyr_RadSDwFlux( 0:imax-1, 1:jmax, 0:kmax ) :real(DP), intent(out)
xyr_RadLUwFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(out)
xyr_RadLDwFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(out)
xyra_DelRadLUwFlux(0:imax-1, 1:jmax, 0:kmax, 0:1) :real(DP), intent(out)
xyra_DelRadLDwFlux(0:imax-1, 1:jmax, 0:kmax, 0:1) :real(DP), intent(out)

[Source]

  subroutine RadSimpleFlux( xy_SurfAlbedo, xy_SurfTemp, xyr_Press, xyz_Press, xyz_Temp, xyz_QH2OVap, xyr_RadSUwFlux, xyr_RadSDwFlux, xyr_RadLUwFlux, xyr_RadLDwFlux, xyra_DelRadLUwFlux, xyra_DelRadLDwFlux )


    ! USE statements
    !

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

    ! 物理・数学定数設定
    ! Physical and mathematical constants settings
    !
    use constants0, only: PI                    ! $ \pi $ .
                              ! 円周率.  Circular constant

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

    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only : y_Lat

    ! 簡単短波放射モデル Ver. 2.0
    ! simple short wave radiation model Ver. 2.0
    !
    use rad_simple_SW_V2_0, only : RadSimpleSWV20Flux

    ! 長波フラックスの計算
    ! Calculate long wave flux
    !
    use rad_simple_LW, only : RadSimpleLWFlux


    real(DP), intent(in ) :: xy_SurfAlbedo( 0:imax-1, 1:jmax )
    real(DP), intent(in ) :: xy_SurfTemp  ( 0:imax-1, 1:jmax )
    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_Temp     ( 0:imax-1, 1:jmax, 1:kmax )
    real(DP), intent(in ) :: xyz_QH2OVap  ( 0:imax-1, 1:jmax, 1:kmax )
    real(DP), intent(out) :: xyr_RadSUwFlux    ( 0:imax-1, 1:jmax, 0:kmax )
    real(DP), intent(out) :: xyr_RadSDwFlux    ( 0:imax-1, 1:jmax, 0:kmax )
    real(DP), intent(out) :: xyr_RadLUwFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(out) :: xyr_RadLDwFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(out) :: xyra_DelRadLUwFlux(0:imax-1, 1:jmax, 0:kmax, 0:1)
    real(DP), intent(out) :: xyra_DelRadLDwFlux(0:imax-1, 1:jmax, 0:kmax, 0:1)


    ! Work variables
    !
    real(DP) :: DistFromStarScld
                               ! Distance between the central star and the planet
    real(DP) :: DiurnalMeanFactor

    real(DP) :: SolarConst
    real(DP) :: SolarFluxTOA
!!$    real(DP) :: QeRatio
    real(DP) :: xyz_SSA       (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_AF        (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xy_InAngle    (0:imax-1, 1:jmax)
    real(DP) :: xyz_DelAtmMass(0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyr_OptDep    (0:imax-1, 1:jmax, 0:kmax)

    real(DP) :: xy_SurfAlbedoLW(0:imax-1, 1:jmax)
    real(DP) :: xy_SurfEmis    (0:imax-1, 1:jmax)

    integer  :: k


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


    do k = 1, kmax
      xyz_DelAtmMass(:,:,k) = ( xyr_Press(:,:,k-1) - xyr_Press(:,:,k ) ) / Grav
    end do


    ! Short wave radiation
    !

    ! 簡単短波放射モデル Ver. 2.0
    ! simple short wave radiation model Ver. 2.0
    !
    call RadSimpleSWV20Flux( xy_SurfAlbedo, xyz_DelAtmMass, xyr_RadSUwFlux, xyr_RadSDwFlux )


    ! Long wave radiation
    !

    xy_SurfAlbedoLW = 0.0_DP
    xy_SurfEmis     = 1.0_DP

    call RadSimpleLWFlux( xy_SurfAlbedoLW, xy_SurfEmis, xyr_Press, xyz_Press, xyz_Temp, xy_SurfTemp, xyz_DelAtmMass, xyz_QH2OVap, xyr_RadLUwFlux, xyr_RadLDwFlux, xyra_DelRadLUwFlux, xyra_DelRadLDwFlux )


  end subroutine RadSimpleFlux
Subroutine :

[Source]

  subroutine RadSimpleInit

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

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

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

    ! 簡単短波放射モデル Ver. 2.0
    ! simple short wave radiation model Ver. 2.0
    !
    use rad_simple_SW_V2_0, only : RadSimpleSWV20Init

    ! 放射フラックス (簡単長波バンドモデル)
    ! Radiation flux (simple longwave band model)
    !
    use rad_simple_LW, only : RadSimpleLWInit


    ! 宣言文 ; Declaration statements
    !

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

    ! NAMELIST 変数群
    ! NAMELIST group name
    !
!!$    namelist /rad_Simple_nml/ &
!!$      & SWOptDepAtRefPress, SWRefPress, SWOrd, &
!!$      & LWOptDepAtRefPress, LWRefPress, LWOrd
          !
          ! デフォルト値については初期化手続 "rad_Simple#RadSimpleInit"
          ! のソースコードを参照のこと.
          !
          ! Refer to source codes in the initialization procedure
          ! "rad_Simple#RadSimpleInit" for the default values.
          !

    if ( rad_Simple_inited ) return


    ! デフォルト値の設定
    ! Default values settings
    !
!!$    SWOptDepAtRefPress =  3.0_DP
!!$    SWRefPress         =  3.0d5
!!$    SWOrd              =  1.0_DP
!!$
!!$    LWOptDepAtRefPress = 80.0_DP
!!$    LWRefPress         =  3.0d5
!!$    LWOrd              =  2.0_DP


    ! 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_Simple_nml,           & ! (out)
!!$        & iostat = iostat_nml )             ! (out)
!!$      close( unit_nml )
!!$
!!$      call NmlutilMsg( iostat_nml, module_name ) ! (in)
!!$    end if


    ! Initialization of modules used in this module
    !

    ! 簡単短波放射モデル Ver. 2.0
    ! simple short wave radiation model Ver. 2.0
    !
    call RadSimpleSWV20Init

    ! 放射フラックス (簡単長波バンドモデル)
    ! Radiation flux (simple longwave band model)
    !
    call RadSimpleLWInit


    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
!!$    call MessageNotify( 'M', module_name, 'SWOptDepAtRefPress = %f', d = (/ SWOptDepAtRefPress /) )
!!$    call MessageNotify( 'M', module_name, 'SWRefPress         = %f', d = (/ SWRefPress /) )
!!$    call MessageNotify( 'M', module_name, 'SWOrd              = %f', d = (/ SWOrd /) )
!!$    call MessageNotify( 'M', module_name, 'LWOptDepAtRefPress = %f', d = (/ LWOptDepAtRefPress /) )
!!$    call MessageNotify( 'M', module_name, 'LWRefPress         = %f', d = (/ LWRefPress /) )
!!$    call MessageNotify( 'M', module_name, 'LWOrd              = %f', d = (/ LWOrd /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )


    rad_Simple_inited = .true.

  end subroutine RadSimpleInit
rad_simple_inited
Variable :
rad_simple_inited = .false. :logical, save, public
: 初期設定フラグ. Initialization flag

Private Instance methods

module_name
Constant :
module_name = ‘rad_simple :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: rad_simple.f90,v 1.5 2013/05/25 06:47:34 yot Exp $’ :character(*), parameter
: モジュールのバージョン Module version