Class saturate_nha1992
In: saturate/saturate_nha1992.f90

Nakajima et al. (1992) を用いた飽和比湿の算出

Evaluate saturation specific humidity with Nakajima et al. (1992)

Note that Japanese and English are described in parallel.

Nakajima et al. (1992) で用いられた飽和蒸気圧 $ p^{*} $ に関する以下の式 を用い, 飽和比湿および飽和比湿の温度微分の値を算出します.

Saturation specific humidity and temperature derivative of it are calculated with a folloing formula for saturation watar vapor pressure $ p^{*} $ in Nakajima et al. (1992).

\[

   p^{*} (T) = p_0^{*} \exp \left( - \frac{l}{RT} \right).

\]

ここで, $ T $ は温度, $ R $ は普遍気体定数です. $ R $ および潜熱 $ l $ , 水蒸気飽和曲線の定数 $ p_0^{*} $ は以下のように与えられます.

where $ T $ is temperature, $ R $ is the gas constant. $ R $ and latent heat $ l $ , constant for the water vapor saturation curve $ p_0^{*} $ are as follows.

  • $ R = 8.314 $ [J mol-1 K-1]
  • $ l = 43655 $ [J mol-1]
  • $ p_0^{*} = 1.4 times 10^{11} $ [Pa]

飽和水蒸気圧から飽和比湿 $ q^{*} $ を求める際には, 以下の式を用います.

Saturation specific humidity $ q^{*} $ is calculated from saturation watar vapor pressure as follows.

\[

   q^{*} (T, P) = \varepsilon \frac{p^{*} (T)}{p}

\]

ここで $ varepsilon $ は凝結成分と大気の分子量比, $ p $ は気圧です.

where $ varepsilon $ is molecular weight ratio of water vapor to air, $ p $ is air pressure.

従って, 飽和比湿, 飽和比湿の温度変化を求める式は以下のように なります.

Therefore, saturation specific humidity and temperature derivative of it are calculated as follows.

\[

   q^{*} (T, P) = \varepsilon \frac{p_0^{*}}{p} \exp \left( - \frac{l}{RT} \right), \] \[
   \DP{q^{*} (T, P)}{T} = \varepsilon \frac{p_0^{*}}{p} \frac{l}{RT^2} \exp \left( - \frac{l}{RT} \right).

\]

Procedures List

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

Methods

Included Modules

gridset dc_types dc_message constants namelist_util dc_iounit dc_string gtool_historyauto

Public Instance methods

CalcDQVapSatDTemp( Temp, Press, DQVapSatDTemp )
Subroutine :
Temp :real(DP), intent(in)
: $ T $ . 温度. Temperature
Press :real(DP), intent(in)
: $ p $ . 気圧. Air pressure
DQVapSatDTemp :real(DP), intent(out)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.

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

スカラーデータではなくを配列データ与える場合には下記の サブルーチンを用いてください.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and air pressure Press.

If array data is given instead of scalar data, use following subroutines.

Alias for CalcDQVapSatDTemp0

CalcDQVapSatDTemp( xy_Temp, xy_Press, xy_DQVapSatDTemp )
Subroutine :
xy_Temp(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_Press(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure
xy_DQVapSatDTemp(0:imax-1, 1:jmax) :real(DP), intent(out)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.

温度 xy_Temp と気圧 xy_Press を用い, 飽和比湿の温度微分 xy_DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity xy_DQVapSatDTemp using temperature xy_Temp and air pressure xy_Press.

Alias for CalcDQVapSatDTemp2

CalcDQVapSatDTemp( xyz_Temp, xyz_Press, xyz_DQVapSatDTemp )
Subroutine :
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure
xyz_DQVapSatDTemp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 xyz_Temp と気圧 xyz_Press を用い, 飽和比湿の温度微分 xyz_DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity xyz_DQVapSatDTemp using temperature xyz_Temp and air pressure xyz_Press.

Alias for CalcDQVapSatDTemp3

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

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

スカラーデータではなくを配列データ与える場合には下記の サブルーチンを用いてください.

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

If array data is given instead of scalar data, use following subroutines.

Alias for CalcQVapSat0

CalcQVapSat( xy_Temp, xy_Press, xy_QVapSat )
Subroutine :
xy_Temp(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_Press(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure
xy_QVapSat(0:imax-1, 1:jmax) :real(DP), intent(out)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 xy_Temp と気圧 xy_Press を用い, 飽和比湿 xy_QVapSat を求めます.

Calculate saturation specific humidity xy_QVapSat using temperature xy_Temp and air pressure xy_Press.

Alias for CalcQVapSat2

CalcQVapSat( xyz_Temp, xyz_Press, xyz_QVapSat )
Subroutine :
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure
xyz_QVapSat(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 xyz_Temp と気圧 xyz_Press を用い, 飽和比湿 xyz_QVapSat を求めます.

Calculate saturation specific humidity xyz_QVapSat using temperature xyz_Temp and air pressure xyz_Press.

Alias for CalcQVapSat3

saturate_nha1992_inited
Variable :
saturate_nha1992_inited = .false. :logical, save, public
: 初期設定フラグ. Initialization flag

Private Instance methods

Subroutine :
Temp :real(DP), intent(in)
: $ T $ . 温度. Temperature
Press :real(DP), intent(in)
: $ p $ . 気圧. Air pressure
DQVapSatDTemp :real(DP), intent(out)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.

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

スカラーデータではなくを配列データ与える場合には下記の サブルーチンを用いてください.

Calculate temperature derivative of saturation specific humidity DQVapSatDTemp using temperature Temp and air pressure Press.

If array data is given instead of scalar data, use following subroutines.

[Source]

  subroutine CalcDQVapSatDTemp0( Temp, Press, DQVapSatDTemp )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿の温度微分 *DQVapSatDTemp* を求めます. 
    !
    ! スカラーデータではなくを配列データ与える場合には下記の
    ! サブルーチンを用いてください. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *DQVapSatDTemp* using
    ! temperature *Temp* and air pressure *Press*. 
    !
    ! If array data is given instead of scalar data, 
    ! use following subroutines. 
    !

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

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: GasRUniv, EpsV                  ! $ \epsilon_v $ . 
                              ! 水蒸気分子量比. 
                              ! Molecular weight of water vapor

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: Temp
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: Press
                              ! $ p $ . 気圧. Air pressure
    real(DP), intent(out):: DQVapSatDTemp
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !

    ! 実行文 ; Executable statement
    !

    ! 飽和比湿の温度微分の計算
    ! Calculate temperature derivative of saturation specific humidity
    !
    DQVapSatDTemp = EpsV * ( P0 / Press ) * ( LatentHeat / ( GasRUniv * Temp**2 ) ) * exp ( - LatentHeat / ( GasRUniv * Temp ) )

  end subroutine CalcDQVapSatDTemp0
Subroutine :
xy_Temp(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_Press(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure
xy_DQVapSatDTemp(0:imax-1, 1:jmax) :real(DP), intent(out)
: $ DP{q^{*}}{T} $ . 飽和比湿の温度微分. Temperature derivative of saturation specific humidity.

温度 xy_Temp と気圧 xy_Press を用い, 飽和比湿の温度微分 xy_DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity xy_DQVapSatDTemp using temperature xy_Temp and air pressure xy_Press.

[Source]

  subroutine CalcDQVapSatDTemp2( xy_Temp, xy_Press, xy_DQVapSatDTemp )
    !
    ! 温度 *xy_Temp* と気圧 *xy_Press* を用い, 
    ! 飽和比湿の温度微分 *xy_DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *xy_DQVapSatDTemp* using
    ! temperature *xy_Temp* and air pressure *xy_Press*. 
    !

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

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xy_Temp (0:imax-1, 1:jmax)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xy_Press (0:imax-1, 1:jmax)
                              ! $ p $ . 気圧. Air pressure
    real(DP), intent(out):: xy_DQVapSatDTemp (0:imax-1, 1:jmax)
                              ! $ \DP{q^{*}}{T} $ . 飽和比湿の温度微分. 
                              ! Temperature derivative of saturation specific humidity. 

    ! 作業変数
    ! Work variables
    !
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude

    ! 実行文 ; Executable statement
    !

    ! 初期化
    ! Initialization
    !
    if ( .not. saturate_nha1992_inited ) call SaturateInit

    ! 飽和比湿の温度微分の計算
    ! Calculate saturation specific humidity
    !
    do i = 0, imax - 1
      do j = 1, jmax
        call CalcDQVapSatDTemp0( xy_Temp(i,j), xy_Press(i,j), xy_DQVapSatDTemp(i,j) )           ! (out)
      end do
    end do

  end subroutine CalcDQVapSatDTemp2
Subroutine :
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure
xyz_DQVapSatDTemp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 xyz_Temp と気圧 xyz_Press を用い, 飽和比湿の温度微分 xyz_DQVapSatDTemp を求めます.

Calculate temperature derivative of saturation specific humidity xyz_DQVapSatDTemp using temperature xyz_Temp and air pressure xyz_Press.

[Source]

  subroutine CalcDQVapSatDTemp3( xyz_Temp, xyz_Press, xyz_DQVapSatDTemp )
    !
    ! 温度 *xyz_Temp* と気圧 *xyz_Press* を用い, 
    ! 飽和比湿の温度微分 *xyz_DQVapSatDTemp* を求めます. 
    !
    ! Calculate temperature derivative of saturation specific humidity 
    ! *xyz_DQVapSatDTemp* using
    ! temperature *xyz_Temp* and air pressure *xyz_Press*. 
    !

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

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xyz_Temp (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xyz_Press (0:imax-1, 1:jmax, 1:kmax)
                              ! $ p $ . 気圧. Air pressure
    real(DP), intent(out):: xyz_DQVapSatDTemp (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    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
    !

    ! 初期化
    ! Initialization
    !
    if ( .not. saturate_nha1992_inited ) call SaturateInit

    ! 飽和比湿の温度微分の計算
    ! Calculate saturation specific humidity
    !
    do i = 0, imax - 1
      do j = 1, jmax
        do k = 1, kmax
          call CalcDQVapSatDTemp( xyz_Temp(i,j,k), xyz_Press(i,j,k), xyz_DQVapSatDTemp(i,j,k) )              ! (out)
        end do
      end do
    end do

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

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

スカラーデータではなくを配列データ与える場合には下記の サブルーチンを用いてください.

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

If array data is given instead of scalar data, use following subroutines.

[Source]

  subroutine CalcQVapSat0( Temp, Press, QVapSat )
    !
    ! 温度 *Temp* と気圧 *Press* を用い, 
    ! 飽和比湿 *QVapSat* を求めます. 
    !
    ! スカラーデータではなくを配列データ与える場合には下記の
    ! サブルーチンを用いてください. 
    !
    ! Calculate saturation specific humidity *QVapSat* using
    ! temperature *Temp* and air pressure *Press*. 
    !
    ! If array data is given instead of scalar data, 
    ! use following subroutines. 
    !

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

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: GasRUniv, EpsV                  ! $ \epsilon_v $ . 
                              ! 水蒸気分子量比. 
                              ! Molecular weight of water vapor

    ! 宣言文 ; Declaration statements
    !
    implicit none

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

    ! 作業変数
    ! Work variables
    !

    ! 実行文 ; Executable statement
    !

    ! 飽和比湿の計算
    ! Calculate saturation specific humidity
    !
    QVapSat = EpsV * ( P0 / Press ) * exp ( - LatentHeat / ( GasRUniv * Temp ) )

  end subroutine CalcQVapSat0
Subroutine :
xy_Temp(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_Press(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure
xy_QVapSat(0:imax-1, 1:jmax) :real(DP), intent(out)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 xy_Temp と気圧 xy_Press を用い, 飽和比湿 xy_QVapSat を求めます.

Calculate saturation specific humidity xy_QVapSat using temperature xy_Temp and air pressure xy_Press.

[Source]

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

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

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xy_Temp (0:imax-1, 1:jmax)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xy_Press (0:imax-1, 1:jmax)
                              ! $ p $ . 気圧. Air pressure
    real(DP), intent(out):: xy_QVapSat (0:imax-1, 1:jmax)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude

    ! 実行文 ; Executable statement
    !

    ! 初期化
    ! Initialization
    !
    if ( .not. saturate_nha1992_inited ) call SaturateInit

    ! 飽和比湿の計算
    ! Calculate saturation specific humidity
    !
    do i = 0, imax - 1
      do j = 1, jmax
        call CalcQVapSat0( xy_Temp(i,j), xy_Press(i,j), xy_QVapSat(i,j) )                 ! (out)
      end do
    end do

  end subroutine CalcQVapSat2
Subroutine :
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ p $ . 気圧. Air pressure
xyz_QVapSat(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ q^{*} $ . 飽和比湿. Saturation specific humidity

温度 xyz_Temp と気圧 xyz_Press を用い, 飽和比湿 xyz_QVapSat を求めます.

Calculate saturation specific humidity xyz_QVapSat using temperature xyz_Temp and air pressure xyz_Press.

[Source]

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

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

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xyz_Temp (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T $ . 温度. Temperature
    real(DP), intent(in):: xyz_Press (0:imax-1, 1:jmax, 1:kmax)
                              ! $ p $ . 気圧. Air pressure
    real(DP), intent(out):: xyz_QVapSat (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q^{*} $ . 飽和比湿. Saturation specific humidity

    ! 作業変数
    ! Work variables
    !
    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
    !

    ! 初期化
    ! Initialization
    !
    if ( .not. saturate_nha1992_inited ) call SaturateInit

    ! 飽和比湿の計算
    ! Calculate saturation specific humidity
    !
    do i = 0, imax - 1
      do j = 1, jmax
        do k = 1, kmax
          call CalcQVapSat0( xyz_Temp(i,j,k), xyz_Press(i,j,k), xyz_QVapSat(i,j,k) )                    ! (out)
        end do
      end do
    end do

  end subroutine CalcQVapSat3
Subroutine :

依存モジュールの初期化チェック

Check initialization of dependency modules

[Source]

  subroutine InitCheck
    !
    ! 依存モジュールの初期化チェック
    !
    ! Check initialization of dependency modules

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

    ! 格子点設定
    ! Grid points settings
    !
    use gridset, only: gridset_inited

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: constants_inited

    ! 実行文 ; Executable statement
    !

    if ( .not. gridset_inited ) call MessageNotify( 'E', module_name, '"gridset" module is not initialized.' )

    if ( .not. constants_inited ) call MessageNotify( 'E', module_name, '"constants" module is not initialized.' )

  end subroutine InitCheck
LatentHeat
Constant :
LatentHeat = 43655_DP :real(DP), parameter
: $ l $ [J mol-1]. 水の凝結の潜熱. Latent heat of condensation of water vapor
P0
Constant :
P0 = 1.4e+11_DP :real(DP), parameter
: $ p_0^{*} $ [Pa]. 水蒸気飽和曲線の定数. constant for water vapor saturation curve
Subroutine :

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

"saturate_nha1992" module is initialized.

[Source]

  subroutine SaturateInit
    !
    ! saturate_nha1992 モジュールの初期化を行います. 
    !
    !
    ! "saturate_nha1992" 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_nha1992_nml/ 
          !
          ! デフォルト値については初期化手続 "saturate_nha1992#SaturateInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "saturate_nha1992#SaturateInit" for the default values. 
          !

    ! 実行文 ; Executable statement
    !

    if ( saturate_nha1992_inited ) return
    call InitCheck

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

    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )
    saturate_nha1992_inited = .true.
  end subroutine SaturateInit
module_name
Constant :
module_name = ‘saturate_nha1992 :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: dcpam5-20081118 $’ // ’$Id: saturate_nha1992.f90,v 1.2 2008-09-23 18:00:35 morikawa Exp $’ :character(*), parameter
: モジュールのバージョン Module version

[Validate]