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

Public Instance methods

Subroutine :

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

"saturate" module is initialized.

[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

    ! 宣言文 ; 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 /saturate_nml/ 
          !
          ! デフォルト値については初期化手続 "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
    !


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


    call SaturateInitCore


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

    saturate_inited = .true.


  end subroutine SaturateInit
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_CalcDQVapSatDTempCore( xyz_Temp, xyz_QVapSat )

    a_DQVapSatDTemp = xyz_DQVapSatDTemp(:,1,1)


  end function a_CalcDQVapSatDTemp
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_CalcQVapSatCore( xyz_Temp, xyz_Press )

    a_QVapSat = xyz_QVapSat(:,1,1)


  end function a_CalcQVapSat
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_CalcDQVapSatDTempCore( xyz_Temp, xyz_QVapSat )

    xy_DQVapSatDTemp = xyz_DQVapSatDTemp(:,:,1)


  end function xy_CalcDQVapSatDTemp
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 :
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
    !

    ! 実行文 ; Executable statement
    !

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


    xyz_DQVapSatDTemp = xyz_CalcDQVapSatDTempCore( xyz_Temp, xyz_QVapSat )


  end function xyz_CalcDQVapSatDTemp
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.

[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(size(xyz_Temp,1), size(xyz_Temp,2), size(xyz_Temp,3))
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !

    ! 実行文 ; Executable statement
    !

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


    xyz_QVapSat = xyz_CalcQVapSatCore( xyz_Temp, xyz_Press )


  end function xyz_CalcQVapSat

Private Instance methods

module_name
Constant :
module_name = ‘saturate :character(*), parameter
: モジュールの名称. Module name
saturate_scheme
Constant :
saturate_scheme = ifdef LIB_SATURATE_NHA1992 elif LIB_SATURATE_DENNOUAGCM elif LIB_SATURATE_DENNOUAGCMEXT else endif :character(*), parameter
version
Constant :
version = ’$Name: dcpam5-20140314 $’ // ’$Id: saturate.F90,v 1.5 2014-02-14 08:12:21 yot Exp $’ :character(*), parameter
: モジュールのバージョン Module version