| Class | rad_Mars_NIR | 
| In: | 
                
                radiation/rad_Mars_NIR.f90
                
         | 
Note that Japanese and English are described in parallel.
| !$ ! DryConvAdjust : | 乾燥対流調節 | 
| !$ ! ———— : | ———— | 
| !$ ! DryConvAdjust : | Dry convective adjustment | 
NAMELIST#rad_M_NIR_nml
| Subroutine : | |||
| xyz_Press(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in )
  | ||
| xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out)
  | 
火星計算用近赤外加熱率計算
Calculation of near infrared heating rate in the case of Mars
Calculation schume of solar nir infrared heating rate follows that shown in Forget et al., 1999
  subroutine RadMarsNIR( xyz_Press, xyz_DTempDt )
    !
    ! 火星計算用近赤外加熱率計算
    !
    ! Calculation of near infrared heating rate in the case of Mars
    !
    ! Calculation schume of solar nir infrared heating rate follows
    ! that shown in Forget et al., 1999
    ! モジュール引用 ; USE statements
    !
    ! 時刻管理
    ! Time control
    !
    use timeset, only: DelTime, TimeN, TimesetClockStart, TimesetClockStop
    ! ヒストリデータ出力
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoPut
    ! 日付および時刻の取り扱い
    ! Date and time handler
    !
    use dc_calendar, only: DCCalInquire
    ! 物理・数学定数設定
    ! Physical and mathematical constants settings
    !
    use constants0, only: PI                    ! $ \pi $ .
                              ! 円周率.  Circular constant
    ! 短波入射 (太陽入射)
    ! Short wave (insolation) incoming
    !
    use rad_short_income, only : RadShortIncome
    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(in ):: xyz_Press  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ p $ . 気圧 (整数レベル). 
                              ! Air pressure (full level)
    real(DP), intent(out):: xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax)
                              ! 温度変化率. 
                              ! Temperature tendency
    ! 作業変数
    ! Work variables
    !
    real(DP) :: qnir0
    real(DP) :: RefPress
    real(DP) :: NLTEPress
    integer  :: hour_in_day
    integer  :: min_in_hour
    real(DP) :: sec_in_min
    real(DP) :: DistFromStarScld
    real(DP) :: DiurnalMeanFactor
    real(DP) :: xy_CosZet  (0:imax-1, 1:jmax)
    real(DP) :: xy_CosZetSq(0:imax-1, 1:jmax)
    real(DP) :: MuFac
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude
    integer:: k               ! 鉛直方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in vertical direction
    ! 実行文 ; Executable statement
    !
    ! 計算時間計測開始
    ! Start measurement of computation time
    !
    call TimesetClockStart( module_name )
    ! 初期化
    ! Initialization
    !
    if ( .not. rad_Mars_NIR_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if
    call DCCalInquire( hour_in_day      = hour_in_day  , min_in_hour      = min_in_hour  , sec_in_min       = sec_in_min )
    ! constants
    !
    qnir0     = 1.3_DP / ( hour_in_day * min_in_hour * sec_in_min )
    RefPress  = 700.0_DP
    NLTEPress = 0.0075_DP
    call RadShortIncome( DistFromStarScld   = DistFromStarScld, xy_CosZet          = xy_CosZet, DiurnalMeanFactor  = DiurnalMeanFactor, FlagOutput         = .false. )
    xy_CosZetSq = xy_CosZet**2
    do j = 1, jmax
      do i = 0, imax-1
        if( xy_CosZet(i,j) < 0.0_DP ) then
          do k = 1, kmax
            xyz_DTempDt(i,j,k) = 0.0_DP
          end do
        else
          MuFac = sqrt( ( 1224.0_DP * xy_CosZetSq(i,j) + 1.0d0 ) / 1225.0_DP )
          do k = 1, kmax
            xyz_DTempDt(i,j,k) = qnir0 / DistFromStarScld**2 * sqrt( RefPress / xyz_Press(i,j,k) * MuFac ) / ( 1.0d0 + NLTEPress / xyz_Press(i,j,k) )
          end do
        end if
      end do
    end do
    xyz_DTempDt = xyz_DTempDt * DiurnalMeanFactor
    ! ヒストリデータ出力
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'DTempDtMNIR', xyz_DTempDt )
    ! 計算時間計測一時停止
    ! Pause measurement of computation time
    !
    call TimesetClockStop( module_name )
  end subroutine RadMarsNIR
          | Subroutine : | |||
| xyz_Press(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in )
  | ||
| xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(inout)
  | 
火星計算用近赤外加熱率計算
Calculation of near infrared heating rate in the case of Mars
Calculation schume of solar nir infrared heating rate follows that shown in Forget et al., 1999
  subroutine RadMarsNIRINOUT( xyz_Press, xyz_DTempDt )
    !
    ! 火星計算用近赤外加熱率計算
    !
    ! Calculation of near infrared heating rate in the case of Mars
    !
    ! Calculation schume of solar nir infrared heating rate follows
    ! that shown in Forget et al., 1999
    ! モジュール引用 ; USE statements
    !
    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(in   ):: xyz_Press (0:imax-1, 1:jmax, 1:kmax)
                              ! $ p $ . 気圧 (整数レベル). 
                              ! Air pressure (full level)
    real(DP), intent(inout):: xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax)
                              ! 温度変化率. 
                              ! Temperature tendency
    ! 作業変数
    ! Work variables
    !
    real(DP) :: xyz_DTempDtLocal(0:imax-1, 1:jmax, 1:kmax)
    ! 実行文 ; Executable statement
    !
    ! 初期化
    ! Initialization
    !
    if ( .not. rad_Mars_NIR_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if
    call RadMarsNIR( xyz_Press, xyz_DTempDtLocal )
    xyz_DTempDt = xyz_DTempDt + xyz_DTempDtLocal
  end subroutine RadMarsNIRINOUT
          | Subroutine : | 
rad_Mars_NIR モジュールの初期化を行います. NAMELIST#rad_Mars_NIR_nml の読み込みはこの手続きで行われます.
"rad_Mars_NIR" module is initialized. "NAMELIST#rad_Mars_NIR_nml" is loaded in this procedure.
This procedure input/output NAMELIST#rad_Mars_NIR_nml .
  subroutine RadMarsNIRInit
    !
    ! rad_Mars_NIR モジュールの初期化を行います. 
    ! NAMELIST#rad_Mars_NIR_nml の読み込みはこの手続きで行われます. 
    !
    ! "rad_Mars_NIR" module is initialized. 
    ! "NAMELIST#rad_Mars_NIR_nml" is loaded in this procedure. 
    !
    ! モジュール引用 ; USE statements
    !
    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg, NmlutilAryValid
    ! ファイル入出力補助
    ! File I/O support
    !
    use dc_iounit, only: FileOpen
    ! 種別型パラメタ
    ! Kind type parameter
    !
    use dc_types, only: STDOUT ! 標準出力の装置番号. Unit number of standard output
    ! 文字列操作
    ! Character handling
    !
    use dc_string, only: StoA
    ! ヒストリデータ出力
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoAddVariable
    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: AxnameX, AxnameY, AxnameZ, AxnameT
    ! 短波入射 (太陽入射)
    ! Short wave (insolation) incoming
    !
    use rad_short_income, only : RadShortIncomeInit
    ! 宣言文 ; Declaration statements
    !
    implicit none
    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_Mars_NIR_nml/ FlagUse
          ! デフォルト値については初期化手続 "dry_conv_adjust#DryConvAdjustInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "dry_conv_adjust#DryConvAdjustInit" for the default values. 
          !
    ! 実行文 ; Executable statement
    !
    if ( rad_Mars_NIR_inited ) return
    ! デフォルト値の設定
    ! Default values settings
    !
    FlagUse = .true.
    ! NAMELIST の読み込み
    ! NAMELIST is input
    !
    if ( trim(namelist_filename) /= '' ) then
      call FileOpen( unit_nml, namelist_filename, mode = 'r' ) ! (in)
      rewind( unit_nml )
      read( unit_nml, nml = rad_Mars_NIR_nml, iostat = iostat_nml )         ! (out)
      close( unit_nml )
      call NmlutilMsg( iostat_nml, module_name ) ! (in)
    end if
    ! ヒストリデータ出力のためのへの変数登録
    ! Register of variables for history data output
    !
    call HistoryAutoAddVariable( 'DTempDtMNIR', (/ AxnameX, AxnameY, AxnameZ, AxnameT /), 'near infrared heating rate', 'K s-1' )
    ! Initialization of modules used in this module
    !
    ! 短波入射 (太陽入射)
    ! Short wave (insolation) incoming
    !
    call RadShortIncomeInit
    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, '  FlagUse    = %b', l = (/ FlagUse /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )
    rad_Mars_NIR_inited = .true.
  end subroutine RadMarsNIRInit
          | Variable : | |||
| rad_Mars_NIR_inited = .false. : | logical, save, public
  | 
| Constant : | |||
| module_name = ‘rad_Mars_NIR‘ : | character(*), parameter
  | 
| Constant : | |||
| version = ’$Name: dcpam5-20140204-5 $’ // ’$Id: rad_Mars_NIR.f90,v 1.4 2012-10-08 12:48:44 yot Exp $’ : | character(*), parameter
  |