--- ../dcpam5-20180304-2/src/prepare_data/initial_data.f90	2018-03-04 19:06:02.000000000 +0900
+++ src/prepare_data/initial_data.f90	2020-11-19 10:23:13.976610213 +0900
@@ -901,10 +901,132 @@
     end do
 
 
+    call Polvanietal2004InitDataH2OVap( &
+         & xy_Ps, xyz_Temp, & ! (in)
+         & xyz_QVap         & ! (out)
+         & )
+
   end subroutine Polvanietal2004InitData
 
   !--------------------------------------------------------------------------------------
 
+  subroutine Polvanietal2004InitDataH2OVap( &
+       & xy_Ps, xyz_Temp, & ! (in)
+       & xyz_QVap         & ! (out)
+       & )
+
+    ! モジュール引用 ; USE statements
+    !
+
+    ! MPI 関連ルーチン
+    ! MPI related routines
+    !
+    use mpi_wrapper, only : NProcs
+
+    ! 物理・数学定数設定
+    ! Physical and mathematical constants settings
+    !
+    use constants0, only: &
+      & PI                    ! $ \pi $.
+                              ! 円周率. Circular constant
+
+    ! 物理定数設定
+    ! Physical constants settings
+    !
+    use constants, only: &
+      & GasRDry, &            ! $ R $ [J kg-1 K-1]. 
+                              ! 乾燥大気の気体定数. 
+                              ! Gas constant of air
+         & MolWtDry, &
+                              ! $ M $ [kg mol-1].
+                              ! 乾燥大気の平均分子量.
+                              ! Mean molecular weight of dry air
+         & MolWtWet
+                              ! $ M_v $ [kg mol-1].
+                              ! 凝結成分の平均分子量.
+                              ! Mean molecular weight of condensible elements
+
+    ! 座標データ設定
+    ! Axes data settings
+    !
+    use axesset, only: &
+      & x_Lon, &
+                              ! $ \lambda $ [rad.] . 経度. Longitude
+      & y_Lat, &
+                              ! $ \varphi $ [rad.] . 緯度. Latitude
+      & z_Sigma
+                              ! $ \sigma $ レベル (整数). 
+                              ! Full $ \sigma $ level
+
+    ! 宣言文 ; Declaration statements
+    !
+    implicit none
+
+    real(DP), intent(in ):: xyz_Temp  (0:imax-1, 1:jmax, 1:kmax)
+                              ! $ T $ .   温度. Temperature
+    real(DP), intent(in ):: xy_Ps (0:imax-1, 1:jmax)
+                              ! $ p_s $ . 地表面気圧. Surface pressure
+    real(DP), intent(out):: xyz_QVap  (0:imax-1, 1:jmax, 1:kmax)
+                              ! $ q $ .   比湿. Specific humidity
+
+
+    ! 作業変数
+    ! Work variables
+    !
+    real(DP) :: xyz_Press( 0:imax-1, 1:jmax, 1:kmax )
+
+
+    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
+
+
+    if ( .not. initial_data_inited ) then
+      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
+    end if
+    if ( NProcs > 1 ) then
+      call MessageNotify( 'E', module_name, &
+        & 'Number of process has to be one, when you use an initial condition for Polvani (2004) experiment.' )
+    end if
+
+
+    ! 圧力の計算
+    do k = 1, kmax
+       xyz_Press(:,:,k) = xy_Ps * z_Sigma(k)
+    end do
+
+
+    ! 比湿の計算
+    ! Calculate specific humidity
+    !
+    !   MolWtDry         : 大気の平均分子量
+    !   MolWtWet         : H2O の平均分子量
+    !   x_Lon(i)         : 経度 (radian)
+    !   y_Lat(j)         : 緯度 (radian)
+    !   xyz_Press(i,j,k) : 圧力 (Pa)
+    !   xyz_Temp (i,j,k) : 温度 (K)
+    !   xyz_QVap (i,j,k) : 比湿 (1)
+    !
+    do k = 1, kmax
+       do j = 1, jmax
+          do i = 0, imax-1
+             ! xyz_QVap(i,j,k) = ...
+          end do
+       end do
+    end do
+
+
+
+  end subroutine Polvanietal2004InitDataH2OVap
+
+  !--------------------------------------------------------------------------------------
+
   subroutine VenusInitData( &
     & xyz_U, xyz_V, xyz_Temp, xyz_QVap, xy_Ps & ! (out)
     & )
