Class saturate
In: saturate/saturate.F90

飽和比湿の算出

Evaluate saturation specific humidity

Note that Japanese and English are described in parallel.

飽和比湿および飽和比湿の温度微分の値を算出します.

Saturation specific humidity and temperature derivative of it are calculated.

飽和比湿の計算にはデフォルトでは, Dennou AGCM で用いた式を用いる (saturate_DennouAGCM 参照). また, Config.mk の CPPFLAGS に -DLIB_SATURATE_NHA1992 を指定すると Nakajima et al. (1992) を用いる (saturate_tnha1992 参照).

By default, a formula used by Dennou AGCM is used for calculation of saturation specific humidity (See "saturate_DennouAGCM"). If "-DLIB_SATURATE_NHA1992" is specified to "CPPFLAGS" in Config.mk, Nakajima et al. (1992) is used (See "saturate_nha1992").

References

Procedures List

CalcQVapSat :飽和比湿の計算
CalcDQVapSatDTemp :飽和比湿の温度微分の計算
———— :————
CalcQVapSat :Calculate saturation specific humidity
CalcDQVapSatDTemp :Calculate temperature derivative of saturation specific humidity

Methods

Included Modules

dc_types dc_message saturate_nha1992 saturate_DennouAGCM namelist_util dc_iounit dc_string gtool_historyauto snowice_frac

Public Instance methods

Function :
DQVapSatDTemp :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
Temp :real(DP), intent(in)
: $ T $ . 温度. Temperature
QVapSat :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

[Source]

  function CalcDQVapSatDTemp( Temp, QVapSat ) result( DQVapSatDTemp )
    !
    ! 温度 *Temp* と飽和比湿 *QVapSat* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and saturation specific humidity *QVapSat*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: Temp
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: QVapSat
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: DQVapSatDTemp
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (1:1, 1:1, 1:1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_QVapSat(1:1, 1:1, 1:1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: xyz_DQVapSatDTemp(1:1, 1:1, 1:1)
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 


    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp   (1,1,1) = Temp
    xyz_QVapSat(1,1,1) = QVapSat

    xyz_DQVapSatDTemp = xyz_CalcDQVapSatDTemp( xyz_Temp, xyz_QVapSat )

    DQVapSatDTemp = xyz_DQVapSatDTemp(1,1,1)


  end function CalcDQVapSatDTemp
Function :
DQVapSatDTemp :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
Temp :real(DP), intent(in)
: $ T $ . 温度. Temperature
QVapSat :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

[Source]

  function CalcDQVapSatDTempOnLiq( Temp, QVapSat ) result( DQVapSatDTemp )
    !
    ! 温度 *Temp* と飽和比湿 *QVapSat* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and saturation specific humidity *QVapSat*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: Temp
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: QVapSat
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: DQVapSatDTemp
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (1:1, 1:1, 1:1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_QVapSat(1:1, 1:1, 1:1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: xyz_DQVapSatDTemp(1:1, 1:1, 1:1)
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 


    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp   (1,1,1) = Temp
    xyz_QVapSat(1,1,1) = QVapSat

    xyz_DQVapSatDTemp = xyz_CalcDQVapSatDTempOnLiq( xyz_Temp, xyz_QVapSat )

    DQVapSatDTemp = xyz_DQVapSatDTemp(1,1,1)


  end function CalcDQVapSatDTempOnLiq
Function :
DQVapSatDTemp :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
Temp :real(DP), intent(in)
: $ T $ . 温度. Temperature
QVapSat :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

[Source]

  function CalcDQVapSatDTempOnSol( Temp, QVapSat ) result( DQVapSatDTemp )
    !
    ! 温度 *Temp* と飽和比湿 *QVapSat* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and saturation specific humidity *QVapSat*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: Temp
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: QVapSat
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: DQVapSatDTemp
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (1:1, 1:1, 1:1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_QVapSat(1:1, 1:1, 1:1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: xyz_DQVapSatDTemp(1:1, 1:1, 1:1)
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 


    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp   (1,1,1) = Temp
    xyz_QVapSat(1,1,1) = QVapSat

    xyz_DQVapSatDTemp = xyz_CalcDQVapSatDTempOnSol( xyz_Temp, xyz_QVapSat )

    DQVapSatDTemp = xyz_DQVapSatDTemp(1,1,1)


  end function CalcDQVapSatDTempOnSol
Function :
QVapSat :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
Temp :real(DP), intent(in)
: $ T $ . 温度. Temperature
Press :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

[Source]

  function CalcQVapSat( Temp, Press ) result( QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: Temp
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: Press
                              ! $ p $ . 気圧. Air pressure

    real(DP):: QVapSat
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (1, 1, 1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_Press  (1, 1, 1)
                              ! $ p $ . 気圧. Air pressure
    real(DP):: xyz_QVapSat(1, 1, 1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp (:,1,1) = Temp
    xyz_Press(:,1,1) = Press

    xyz_QVapSat = xyz_CalcQVapSat( xyz_Temp, xyz_Press )

    QVapSat = xyz_QVapSat(1,1,1)


  end function CalcQVapSat
Function :
QVapSat :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
Temp :real(DP), intent(in)
: $ T $ . 温度. Temperature
Press :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

[Source]

  function CalcQVapSatOnLiq( Temp, Press ) result( QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: Temp
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: Press
                              ! $ p $ . 気圧. Air pressure

    real(DP):: QVapSat
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (1, 1, 1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_Press  (1, 1, 1)
                              ! $ p $ . 気圧. Air pressure
    real(DP):: xyz_QVapSat(1, 1, 1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp (:,1,1) = Temp
    xyz_Press(:,1,1) = Press

    xyz_QVapSat = xyz_CalcQVapSatOnLiq( xyz_Temp, xyz_Press )

    QVapSat = xyz_QVapSat(1,1,1)


  end function CalcQVapSatOnLiq
Function :
QVapSat :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
Temp :real(DP), intent(in)
: $ T $ . 温度. Temperature
Press :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

[Source]

  function CalcQVapSatOnSol( Temp, Press ) result( QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: Temp
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: Press
                              ! $ p $ . 気圧. Air pressure

    real(DP):: QVapSat
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (1, 1, 1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_Press  (1, 1, 1)
                              ! $ p $ . 気圧. Air pressure
    real(DP):: xyz_QVapSat(1, 1, 1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp (:,1,1) = Temp
    xyz_Press(:,1,1) = Press

    xyz_QVapSat = xyz_CalcQVapSatOnSol( xyz_Temp, xyz_Press )

    QVapSat = xyz_QVapSat(1,1,1)


  end function CalcQVapSatOnSol
Subroutine :

saturate モジュールの初期化を行います.

"saturate" module is initialized.

This procedure input/output NAMELIST#saturate_nml .

[Source]

  subroutine SaturateInit
    !
    ! saturate モジュールの初期化を行います. 
    !
    !
    ! "saturate" module is initialized. 
    !

    ! モジュール引用 ; USE statements
    !

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

    ! ファイル入出力補助
    ! 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

    ! 雪, 氷の割合
    ! snow/ice fraction
    !
    use snowice_frac, only : SnowIceFracInit

    ! 宣言文 ; Declaration statements
    !
    implicit none

    character(STRING) :: SaturateWatIceFracType

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

    ! NAMELIST 変数群
    ! NAMELIST group name
    !
    namelist /saturate_nml/ SaturateWatIceFracType, TempWatLim, TempIceLim
          !
          ! デフォルト値については初期化手続 "saturate#SaturateInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "saturate#SaturateInit" for the default values. 
          !

    ! 実行文 ; Executable statement
    !

    if ( saturate_inited ) return

    ! デフォルト値の設定
    ! Default values settings
    !
    SaturateWatIceFracType = 'Lin'

!!$    TempWatLim          = 273.15_DP
!!$    TempIceLim          = 273.15_DP - 40.0_DP
    TempWatLim          = 0.0_DP
    TempIceLim          = 0.0_DP


    ! 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 = saturate_nml, iostat = iostat_nml )   ! (out)
      close( unit_nml )

      call NmlutilMsg( iostat_nml, module_name ) ! (in)
    end if


    select case ( SaturateWatIceFracType )
    case ( 'Lin' )
      IDWatIceFracMethod = IDWatIceFracMethodLin
    case ( 'Quad' )
      IDWatIceFracMethod = IDWatIceFracMethodQuad
    case default
      call MessageNotify( 'E', module_name, 'SaturateWatIceFracType=<%c> is not supported.', c1 = trim(SaturateWatIceFracType) )
    end select


    ! Initialization of modules used in this module
    !

    call SaturateInitCore

    ! 雪, 氷の割合
    ! snow/ice fraction
    !
    call SnowIceFracInit


    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, 'Scheme of saturation = %c', c1 = saturate_scheme )
    call MessageNotify( 'M', module_name, 'SaturateWatIceFracType = %c', c1 = trim(SaturateWatIceFracType) )
    call MessageNotify( 'M', module_name, 'TempWatLim             = %f', d = (/TempWatLim/) )
    call MessageNotify( 'M', module_name, 'TempIceLim             = %f', d = (/TempIceLim/) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    saturate_inited = .true.


  end subroutine SaturateInit
SaturateWatFraction( Temp, WatFrac )
Subroutine :
Temp :real(DP), intent(in )
WatFrac :real(DP), intent(out)

Alias for SaturateWatFraction0D

SaturateWatFraction( xyz_Temp, xyz_WatFrac )
Subroutine :
xyz_Temp(:,:,:) :real(DP), intent(in )
xyz_WatFrac(:,:,:) :real(DP), intent(out)

Alias for SaturateWatFraction3D

Function :
a_DQVapSatDTemp(size(a_Temp,1)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
a_Temp(:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
a_QVapSat(:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

[Source]

  function a_CalcDQVapSatDTemp( a_Temp, a_QVapSat ) result( a_DQVapSatDTemp )
    !
    ! 温度 *Temp* と飽和比湿 *QVapSat* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and saturation specific humidity *QVapSat*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: a_Temp   (:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: a_QVapSat(:)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: a_DQVapSatDTemp(size(a_Temp,1))
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (size(a_Temp,1), 1:1, 1:1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_QVapSat(size(a_Temp,1), 1:1, 1:1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: xyz_DQVapSatDTemp(size(a_Temp,1), 1:1, 1:1)
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 


    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp   (:,1,1) = a_Temp
    xyz_QVapSat(:,1,1) = a_QVapSat

    xyz_DQVapSatDTemp = xyz_CalcDQVapSatDTemp( xyz_Temp, xyz_QVapSat )

    a_DQVapSatDTemp = xyz_DQVapSatDTemp(:,1,1)


  end function a_CalcDQVapSatDTemp
Function :
a_DQVapSatDTemp(size(a_Temp,1)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
a_Temp(:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
a_QVapSat(:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

[Source]

  function a_CalcDQVapSatDTempOnLiq( a_Temp, a_QVapSat ) result( a_DQVapSatDTemp )
    !
    ! 温度 *Temp* と飽和比湿 *QVapSat* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and saturation specific humidity *QVapSat*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: a_Temp   (:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: a_QVapSat(:)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: a_DQVapSatDTemp(size(a_Temp,1))
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (size(a_Temp,1), 1:1, 1:1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_QVapSat(size(a_Temp,1), 1:1, 1:1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: xyz_DQVapSatDTemp(size(a_Temp,1), 1:1, 1:1)
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 


    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp   (:,1,1) = a_Temp
    xyz_QVapSat(:,1,1) = a_QVapSat

    xyz_DQVapSatDTemp = xyz_CalcDQVapSatDTempOnLiq( xyz_Temp, xyz_QVapSat )

    a_DQVapSatDTemp = xyz_DQVapSatDTemp(:,1,1)


  end function a_CalcDQVapSatDTempOnLiq
Function :
a_DQVapSatDTemp(size(a_Temp,1)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
a_Temp(:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
a_QVapSat(:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

[Source]

  function a_CalcDQVapSatDTempOnSol( a_Temp, a_QVapSat ) result( a_DQVapSatDTemp )
    !
    ! 温度 *Temp* と飽和比湿 *QVapSat* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and saturation specific humidity *QVapSat*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: a_Temp   (:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: a_QVapSat(:)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: a_DQVapSatDTemp(size(a_Temp,1))
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (size(a_Temp,1), 1:1, 1:1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_QVapSat(size(a_Temp,1), 1:1, 1:1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: xyz_DQVapSatDTemp(size(a_Temp,1), 1:1, 1:1)
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 


    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp   (:,1,1) = a_Temp
    xyz_QVapSat(:,1,1) = a_QVapSat

    xyz_DQVapSatDTemp = xyz_CalcDQVapSatDTempOnSol( xyz_Temp, xyz_QVapSat )

    a_DQVapSatDTemp = xyz_DQVapSatDTemp(:,1,1)


  end function a_CalcDQVapSatDTempOnSol
Function :
a_QVapSat(size(a_Temp,1)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
a_Temp(:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
a_Press(:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

[Source]

  function a_CalcQVapSat( a_Temp, a_Press ) result( a_QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: a_Temp (:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: a_Press(:)
                              ! $ p $ . 気圧. Air pressure

    real(DP):: a_QVapSat(size(a_Temp,1))
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (size(a_Temp,1), 1, 1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_Press  (size(a_Temp,1), 1, 1)
                              ! $ p $ . 気圧. Air pressure
    real(DP):: xyz_QVapSat(size(a_Temp,1), 1, 1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp (:,1,1) = a_Temp
    xyz_Press(:,1,1) = a_Press

    xyz_QVapSat = xyz_CalcQVapSat( xyz_Temp, xyz_Press )

    a_QVapSat = xyz_QVapSat(:,1,1)


  end function a_CalcQVapSat
Function :
a_QVapSat(size(a_Temp,1)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
a_Temp(:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
a_Press(:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

[Source]

  function a_CalcQVapSatOnLiq( a_Temp, a_Press ) result( a_QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: a_Temp (:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: a_Press(:)
                              ! $ p $ . 気圧. Air pressure

    real(DP):: a_QVapSat(size(a_Temp,1))
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (size(a_Temp,1), 1, 1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_Press  (size(a_Temp,1), 1, 1)
                              ! $ p $ . 気圧. Air pressure
    real(DP):: xyz_QVapSat(size(a_Temp,1), 1, 1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp (:,1,1) = a_Temp
    xyz_Press(:,1,1) = a_Press

    xyz_QVapSat = xyz_CalcQVapSatOnLiq( xyz_Temp, xyz_Press )

    a_QVapSat = xyz_QVapSat(:,1,1)


  end function a_CalcQVapSatOnLiq
Function :
a_QVapSat(size(a_Temp,1)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
a_Temp(:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
a_Press(:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

[Source]

  function a_CalcQVapSatOnSol( a_Temp, a_Press ) result( a_QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: a_Temp (:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: a_Press(:)
                              ! $ p $ . 気圧. Air pressure

    real(DP):: a_QVapSat(size(a_Temp,1))
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp   (size(a_Temp,1), 1, 1)
                              ! $ T $ . 温度. Temperature
    real(DP):: xyz_Press  (size(a_Temp,1), 1, 1)
                              ! $ p $ . 気圧. Air pressure
    real(DP):: xyz_QVapSat(size(a_Temp,1), 1, 1)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp (:,1,1) = a_Temp
    xyz_Press(:,1,1) = a_Press

    xyz_QVapSat = xyz_CalcQVapSatOnSol( xyz_Temp, xyz_Press )

    a_QVapSat = xyz_QVapSat(:,1,1)


  end function a_CalcQVapSatOnSol
saturate_inited
Variable :
saturate_inited = .false. :logical, save, public
: 初期設定フラグ. Initialization flag
Function :
xy_DQVapSatDTemp(size(xy_Temp,1), size(xy_Temp,2)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
xy_Temp(:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_QVapSat(:,:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

[Source]

  function xy_CalcDQVapSatDTemp( xy_Temp, xy_QVapSat ) result( xy_DQVapSatDTemp )
    !
    ! 温度 *Temp* と飽和比湿 *QVapSat* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and saturation specific humidity *QVapSat*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xy_Temp   (:,:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xy_QVapSat(:,:)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: xy_DQVapSatDTemp(size(xy_Temp,1), size(xy_Temp,2))
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp         (size(xy_Temp,1), size(xy_Temp,2), 1)
    real(DP):: xyz_QVapSat      (size(xy_Temp,1), size(xy_Temp,2), 1)
    real(DP):: xyz_DQVapSatDTemp(size(xy_Temp,1), size(xy_Temp,2), 1)

    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp   (:,:,1) = xy_Temp
    xyz_QVapSat(:,:,1) = xy_QVapSat

    xyz_DQVapSatDTemp = xyz_CalcDQVapSatDTemp( xyz_Temp, xyz_QVapSat )

    xy_DQVapSatDTemp = xyz_DQVapSatDTemp(:,:,1)


  end function xy_CalcDQVapSatDTemp
Function :
xy_DQVapSatDTemp(size(xy_Temp,1), size(xy_Temp,2)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
xy_Temp(:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_QVapSat(:,:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

[Source]

  function xy_CalcDQVapSatDTempOnLiq( xy_Temp, xy_QVapSat ) result( xy_DQVapSatDTemp )
    !
    ! 温度 *Temp* と飽和比湿 *QVapSat* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and saturation specific humidity *QVapSat*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xy_Temp   (:,:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xy_QVapSat(:,:)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: xy_DQVapSatDTemp(size(xy_Temp,1), size(xy_Temp,2))
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp         (size(xy_Temp,1), size(xy_Temp,2), 1)
    real(DP):: xyz_QVapSat      (size(xy_Temp,1), size(xy_Temp,2), 1)
    real(DP):: xyz_DQVapSatDTemp(size(xy_Temp,1), size(xy_Temp,2), 1)

    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp   (:,:,1) = xy_Temp
    xyz_QVapSat(:,:,1) = xy_QVapSat

    xyz_DQVapSatDTemp = xyz_CalcDQVapSatDTempOnLiq( xyz_Temp, xyz_QVapSat )

    xy_DQVapSatDTemp = xyz_DQVapSatDTemp(:,:,1)


  end function xy_CalcDQVapSatDTempOnLiq
Function :
xy_DQVapSatDTemp(size(xy_Temp,1), size(xy_Temp,2)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
xy_Temp(:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_QVapSat(:,:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

[Source]

  function xy_CalcDQVapSatDTempOnSol( xy_Temp, xy_QVapSat ) result( xy_DQVapSatDTemp )
    !
    ! 温度 *Temp* と飽和比湿 *QVapSat* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and saturation specific humidity *QVapSat*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xy_Temp   (:,:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xy_QVapSat(:,:)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: xy_DQVapSatDTemp(size(xy_Temp,1), size(xy_Temp,2))
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_Temp         (size(xy_Temp,1), size(xy_Temp,2), 1)
    real(DP):: xyz_QVapSat      (size(xy_Temp,1), size(xy_Temp,2), 1)
    real(DP):: xyz_DQVapSatDTemp(size(xy_Temp,1), size(xy_Temp,2), 1)

    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp   (:,:,1) = xy_Temp
    xyz_QVapSat(:,:,1) = xy_QVapSat

    xyz_DQVapSatDTemp = xyz_CalcDQVapSatDTempOnSol( xyz_Temp, xyz_QVapSat )

    xy_DQVapSatDTemp = xyz_DQVapSatDTemp(:,:,1)


  end function xy_CalcDQVapSatDTempOnSol
Function :
xy_QVapSat(size(xy_Temp,1), size(xy_Temp,2)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
xy_Temp(:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_Press(:,:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

[Source]

  function xy_CalcQVapSat( xy_Temp, xy_Press ) result( xy_QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xy_Temp (:,:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xy_Press(:,:)
                              ! $ p $ . 気圧. Air pressure

    real(DP):: xy_QVapSat(size(xy_Temp,1), size(xy_Temp,2))
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    real(DP) :: xyz_Temp   (size(xy_Temp,1),size(xy_Temp,2),1)
    real(DP) :: xyz_Press  (size(xy_Temp,1),size(xy_Temp,2),1)
    real(DP) :: xyz_QVapSat(size(xy_Temp,1),size(xy_Temp,2),1)


    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp (:,:,1) = xy_Temp
    xyz_Press(:,:,1) = xy_Press

    xyz_QVapSat = xyz_CalcQVapSat( xyz_Temp, xyz_Press )

    xy_QVapSat = xyz_QVapSat(:,:,1)


  end function xy_CalcQVapSat
Function :
xy_QVapSat(size(xy_Temp,1), size(xy_Temp,2)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
xy_Temp(:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_Press(:,:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

[Source]

  function xy_CalcQVapSatOnLiq( xy_Temp, xy_Press ) result( xy_QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xy_Temp (:,:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xy_Press(:,:)
                              ! $ p $ . 気圧. Air pressure

    real(DP):: xy_QVapSat(size(xy_Temp,1), size(xy_Temp,2))
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    real(DP) :: xyz_Temp   (size(xy_Temp,1),size(xy_Temp,2),1)
    real(DP) :: xyz_Press  (size(xy_Temp,1),size(xy_Temp,2),1)
    real(DP) :: xyz_QVapSat(size(xy_Temp,1),size(xy_Temp,2),1)


    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp (:,:,1) = xy_Temp
    xyz_Press(:,:,1) = xy_Press

    xyz_QVapSat = xyz_CalcQVapSatOnLiq( xyz_Temp, xyz_Press )

    xy_QVapSat = xyz_QVapSat(:,:,1)


  end function xy_CalcQVapSatOnLiq
Function :
xy_QVapSat(size(xy_Temp,1), size(xy_Temp,2)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
xy_Temp(:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_Press(:,:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

[Source]

  function xy_CalcQVapSatOnSol( xy_Temp, xy_Press ) result( xy_QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xy_Temp (:,:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xy_Press(:,:)
                              ! $ p $ . 気圧. Air pressure

    real(DP):: xy_QVapSat(size(xy_Temp,1), size(xy_Temp,2))
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    real(DP) :: xyz_Temp   (size(xy_Temp,1),size(xy_Temp,2),1)
    real(DP) :: xyz_Press  (size(xy_Temp,1),size(xy_Temp,2),1)
    real(DP) :: xyz_QVapSat(size(xy_Temp,1),size(xy_Temp,2),1)


    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_Temp (:,:,1) = xy_Temp
    xyz_Press(:,:,1) = xy_Press

    xyz_QVapSat = xyz_CalcQVapSatOnSol( xyz_Temp, xyz_Press )

    xy_QVapSat = xyz_QVapSat(:,:,1)


  end function xy_CalcQVapSatOnSol
Function :
xyz_DQVapSatDTemp(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
xyz_Temp(:,:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_QVapSat(:,:,:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

[Source]

  function xyz_CalcDQVapSatDTemp( xyz_Temp, xyz_QVapSat ) result( xyz_DQVapSatDTemp )
    !
    ! 温度 *Temp* と飽和比湿 *QVapSat* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and saturation specific humidity *QVapSat*. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xyz_Temp   (:,:,:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xyz_QVapSat(:,:,:)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity
    real(DP):: xyz_DQVapSatDTemp(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3))
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_DQVapSatDTempOnLiq(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3))
    real(DP):: xyz_DQVapSatDTempOnSol(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3))
    real(DP):: xyz_WatFrac           (size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3))


    ! 実行文 ; Executable statement
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_DQVapSatDTempOnLiq = xyz_CalcDQVapSatDTempOnLiq( xyz_Temp, xyz_QVapSat )
    xyz_DQVapSatDTempOnSol = xyz_CalcDQVapSatDTempOnSol( xyz_Temp, xyz_QVapSat )

    call SaturateWatFraction( xyz_Temp, xyz_WatFrac )

    xyz_DQVapSatDTemp = xyz_WatFrac              * xyz_DQVapSatDTempOnLiq + ( 1.0_DP - xyz_WatFrac ) * xyz_DQVapSatDTempOnSol


  end function xyz_CalcDQVapSatDTemp
xyz_CalcDQVapSatDTempOnLiq( xyz_Temp, xyz_QVapSat ) result(xyz_DQVapSatDTemp)
Function :
xyz_DQVapSatDTemp(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
xyz_Temp(:,:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_QVapSat(:,:,:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

Original external subprogram is saturate_DennouAGCM#xyz_CalcDQVapSatDTempOnLiq

xyz_CalcDQVapSatDTempOnLiq( xyz_Temp, xyz_QVapSat ) result(xyz_DQVapSatDTemp)
Function :
xyz_DQVapSatDTemp(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
xyz_Temp(:,:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_QVapSat(:,:,:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

Original external subprogram is saturate_nha1992#xyz_CalcDQVapSatDTempOnLiq

xyz_CalcDQVapSatDTempOnSol( xyz_Temp, xyz_QVapSat ) result(xyz_DQVapSatDTemp)
Function :
xyz_DQVapSatDTemp(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
xyz_Temp(:,:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_QVapSat(:,:,:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

Original external subprogram is saturate_DennouAGCM#xyz_CalcDQVapSatDTempOnSol

xyz_CalcDQVapSatDTempOnSol( xyz_Temp, xyz_QVapSat ) result(xyz_DQVapSatDTemp)
Function :
xyz_DQVapSatDTemp(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3)) :real(DP)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.
xyz_Temp(:,:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_QVapSat(:,:,:) :real(DP), intent(in)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 Temp と飽和比湿 QVapSat を用い, 飽和比湿の温度微分 DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and saturation specific humidity QVapSat.

Original external subprogram is saturate_nha1992#xyz_CalcDQVapSatDTempOnSol

Function :
xyz_QVapSat(1:size(xyz_Temp,1), 1:size(xyz_Temp,2), 1:size(xyz_Temp,3)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
xyz_Temp(:,:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_Press(:,:,:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

[Source]

  function xyz_CalcQVapSat( xyz_Temp, xyz_Press ) result( xyz_QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !

    ! モジュール引用 ; USE statements
    !


    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xyz_Temp (:,:,:)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xyz_Press(:,:,:)
                              ! $ p $ . 気圧. Air pressure

    real(DP):: xyz_QVapSat(1:size(xyz_Temp,1), 1:size(xyz_Temp,2), 1:size(xyz_Temp,3))
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_QVapSatOnLiq(1:size(xyz_Temp,1), 1:size(xyz_Temp,2), 1:size(xyz_Temp,3))
    real(DP):: xyz_QVapSatOnSol(1:size(xyz_Temp,1), 1:size(xyz_Temp,2), 1:size(xyz_Temp,3))
    real(DP):: xyz_WatFrac     (1:size(xyz_Temp,1), 1:size(xyz_Temp,2), 1:size(xyz_Temp,3))


    ! 実行文 ; Executable statement
    !

    ! 初期化確認
    ! Initialization check
    !

    if ( .not. saturate_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyz_QVapSatOnLiq = xyz_CalcQVapSatOnLiq( xyz_Temp, xyz_Press )
    xyz_QVapSatOnSol = xyz_CalcQVapSatOnSol( xyz_Temp, xyz_Press )

    call SaturateWatFraction( xyz_Temp, xyz_WatFrac )

    xyz_QVapSat = xyz_WatFrac              * xyz_QVapSatOnLiq + ( 1.0_DP - xyz_WatFrac ) * xyz_QVapSatOnSol


  end function xyz_CalcQVapSat
xyz_CalcQVapSatOnLiq( xyz_Temp, xyz_Press ) result(xyz_QVapSat)
Function :
xyz_QVapSat(1:size(xyz_Temp,1), 1:size(xyz_Temp,2), 1:size(xyz_Temp,3)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
xyz_Temp(:,:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_Press(:,:,:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

Original external subprogram is saturate_DennouAGCM#xyz_CalcQVapSatOnLiq

xyz_CalcQVapSatOnLiq( xyz_Temp, xyz_Press ) result(xyz_QVapSat)
Function :
xyz_QVapSat(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
xyz_Temp(:,:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_Press(:,:,:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

Original external subprogram is saturate_nha1992#xyz_CalcQVapSatOnLiq

xyz_CalcQVapSatOnSol( xyz_Temp, xyz_Press ) result(xyz_QVapSat)
Function :
xyz_QVapSat(1:size(xyz_Temp,1), 1:size(xyz_Temp,2), 1:size(xyz_Temp,3)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
xyz_Temp(:,:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_Press(:,:,:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

Original external subprogram is saturate_DennouAGCM#xyz_CalcQVapSatOnSol

xyz_CalcQVapSatOnSol( xyz_Temp, xyz_Press ) result(xyz_QVapSat)
Function :
xyz_QVapSat(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3)) :real(DP)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity
xyz_Temp(:,:,:) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_Press(:,:,:) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure

温度 Temp と気圧 Press を用い, 飽和比湿 QVapSat を求めます.

Calculate saturation specific humidity QVapSat using temperature Temp and air pressure Press.

Original external subprogram is saturate_nha1992#xyz_CalcQVapSatOnSol

Private Instance methods

IDWatIceFracMethod
Variable :
IDWatIceFracMethod :integer , save
IDWatIceFracMethodLin
Constant :
IDWatIceFracMethodLin = 1 :integer , parameter
IDWatIceFracMethodQuad
Constant :
IDWatIceFracMethodQuad = 2 :integer , parameter
Subroutine :
Temp :real(DP), intent(in )
WatFrac :real(DP), intent(out)

[Source]

  subroutine SaturateWatFraction0D( Temp, WatFrac )

    ! USE statements
    !

    real(DP), intent(in ) :: Temp
    real(DP), intent(out) :: WatFrac


    real(DP) :: xyz_Temp   (1,1,1)
    real(DP) :: xyz_WatFrac(1,1,1)

    ! 実行文 ; Executable statement
    !

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


    xyz_Temp = Temp
    call SaturateWatFraction3D( xyz_Temp, xyz_WatFrac )
    WatFrac = xyz_WatFrac(1,1,1)


  end subroutine SaturateWatFraction0D
Subroutine :
xyz_Temp(:,:,:) :real(DP), intent(in )
xyz_WatFrac(:,:,:) :real(DP), intent(out)

[Source]

  subroutine SaturateWatFraction3D( xyz_Temp, xyz_WatFrac )

    ! USE statements
    !

!!$    real(DP), intent(in ) :: xyz_Temp   (0:imax-1, 1:jmax, 1:kmax)
!!$    real(DP), intent(out) :: xyz_WatFrac(0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xyz_Temp   (:,:,:)
    real(DP), intent(out) :: xyz_WatFrac(:,:,:)


    ! 実行文 ; Executable statement
    !

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


!!$    if ( FlagSnow ) then

    if ( TempWatLim == TempIceLim ) then
      xyz_WatFrac = ( sign( 1.0_DP, xyz_Temp - TempWatLim ) + 1.0_DP ) / 2.0_DP
    else
      select case ( IDWatIceFracMethod )
      case ( IDWatIceFracMethodLin  )
        xyz_WatFrac =   ( xyz_Temp - TempIceLim ) / ( TempWatLim - TempIceLim )
      case ( IDWatIceFracMethodQuad )
        xyz_WatFrac = ( max( xyz_Temp - TempIceLim, 0.0_DP ) / ( TempWatLim - TempIceLim ) )**2
      end select
      xyz_WatFrac = max( min( xyz_WatFrac, 1.0_DP ), 0.0_DP )
    end if

!!$    else
!!$
!!$      xyz_WatFrac = 1.0_DP
!!$
!!$    end if


  end subroutine SaturateWatFraction3D
TempIceLim
Variable :
TempIceLim :real(DP), save
TempWatLim
Variable :
TempWatLim :real(DP), save
module_name
Constant :
module_name = ‘saturate :character(*), parameter
: モジュールの名称. Module name
saturate_scheme
Constant :
saturate_scheme = ifdef LIB_SATURATE_NHA1992 elif LIB_SATURATE_DENNOUAGCM else endif :character(*), parameter
version
Constant :
version = ’$Name: $’ // ’$Id: saturate.F90,v 1.7 2015/01/29 12:07:16 yot Exp $’ :character(*), parameter
: モジュールのバージョン Module version