subroutine OutputFreqUsedVars( xy_PsA, xyz_TempA, xyzf_QMixA, xy_SurfHeight )
!
!
!
! Output frequently used variables
!
! モジュール引用 ; USE statements
!
! 時刻管理
! Time control
!
use timeset, only: DelTime, TimeN, TimeA, TimesetClockStart, TimesetClockStop
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoPut
! 組成に関わる配列の設定
! Settings of array for atmospheric composition
!
use composition, only: ncmax, IndexH2OVap
! 物理定数設定
! Physical constants settings
!
use constants, only: Grav, GasRDry, CpDry
! $ C_p $ [J kg-1 K-1].
! 乾燥大気の定圧比熱.
! Specific heat of air at constant pressure
! 温度の半整数σレベルの補間, 気圧と高度の算出
! Interpolate temperature on half sigma level,
! and calculate pressure and height
!
use auxiliary, only: AuxVars
! 飽和比湿の算出
! Evaluate saturation specific humidity
!
use saturate, only: xyz_CalcQVapSat
! 宣言文 ; Declaration statements
!
real(DP), intent(in ) :: xy_PsA (0:imax-1, 1:jmax)
! Temperature
real(DP), intent(in ) :: xyz_TempA (0:imax-1, 1:jmax, 1:kmax)
! Temperature
real(DP), intent(in ) :: xyzf_QMixA (0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
real(DP), intent(in ) :: xy_SurfHeight(0:imax-1, 1:jmax)
! 作業変数
! Work variables
!
real(DP) :: xyz_Press (0:imax-1, 1:jmax, 1:kmax)
! Pressure
real(DP) :: xyz_Exner (0:imax-1, 1:jmax, 1:kmax)
! Exner function
real(DP) :: xyz_VirTemp (0:imax-1, 1:jmax, 1:kmax)
! Virtual temperature
real(DP) :: xyz_Height (0:imax-1, 1:jmax, 1:kmax)
! Height
real(DP) :: xyz_Rho (0:imax-1, 1:jmax, 1:kmax)
! Pressure
real(DP) :: xyz_PotTemp (0:imax-1, 1:jmax, 1:kmax)
! Potential temperature
real(DP) :: xyz_BVFreqSq (0:imax-1, 1:jmax, 1:kmax)
! Brunt-Vaisalla frequency squared
real(DP) :: xyz_QVapSat(0:imax-1, 1:jmax, 1:kmax)
real(DP) :: xyz_RH (0:imax-1, 1:jmax, 1:kmax)
integer :: xy_KIndex (0:imax-1, 1:jmax)
! K index for reference level used for SLP calc.
real(DP) :: xy_PressRefForSLP (0:imax-1, 1:jmax)
real(DP) :: xy_HeightRefForSLP (0:imax-1, 1:jmax)
real(DP) :: xy_VirTempRefForSLP(0:imax-1, 1:jmax)
real(DP) :: xy_ScaleHeight (0:imax-1, 1:jmax)
real(DP) :: xy_SLP (0:imax-1, 1:jmax)
! Sea level pressure
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
integer :: kp
integer :: kn
! 実行文 ; Executable statement
!
! 初期化確認
! Initialization check
!
if ( .not. output_freq_used_vars_inited ) then
call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
end if
! 計算時間計測開始
! Start measurement of computation time
!
call TimesetClockStart( module_name )
! 温度の半整数σレベルの補間, 気圧と高度の算出
! Interpolate temperature on half sigma level,
! and calculate pressure and height
!
call AuxVars( xy_PsA, xyz_TempA, xyzf_QMixA(:,:,:,IndexH2OVap), xy_SurfHeight = xy_SurfHeight, xyz_Press = xyz_Press, xyz_VirTemp = xyz_VirTemp, xyz_Height = xyz_Height, xyz_Exner = xyz_Exner )
!
xyz_Rho = xyz_Press / ( GasRDry * xyz_TempA )
call HistoryAutoPut( TimeA, 'Rho', xyz_TempA / xyz_Exner )
!
call HistoryAutoPut( TimeA, 'Height', xyz_Height )
!
xyz_PotTemp = xyz_TempA / xyz_Exner
call HistoryAutoPut( TimeA, 'PotTemp', xyz_PotTemp )
!
do k = 1, kmax
kp = max( k - 1, 1 )
kn = min( k + 1, kmax )
xyz_BVFreqSq(:,:,k) = Grav / xyz_PotTemp(:,:,k) * ( xyz_PotTemp(:,:,kn) - xyz_PotTemp(:,:,kp) ) / ( xyz_Height (:,:,kn) - xyz_Height (:,:,kp) )
end do
call HistoryAutoPut( TimeA, 'BVFreqSq', xyz_BVFreqSq )
xy_KIndex = 1
do k = 1, kmax
do j = 1, jmax
do i = 0, imax-1
if ( xyz_Press(i,j,k) / xy_PsA(i,j) > SigmaRefForSLP ) then
xy_KIndex(i,j) = k
end if
end do
end do
end do
do j = 1, jmax
do i = 0, imax-1
xy_PressRefForSLP (i,j) = xyz_Press (i,j,xy_KIndex(i,j))
xy_HeightRefForSLP (i,j) = xyz_Height (i,j,xy_KIndex(i,j))
xy_VirTempRefForSLP(i,j) = xyz_VirTemp(i,j,xy_KIndex(i,j))
end do
end do
xy_SLP = xy_PressRefForSLP * ( 1.0_DP + AdiabLapseRate * ( 0.0_DP - xy_HeightRefForSLP ) / xy_VirTempRefForSLP )**( - Grav / ( GasRDry * AdiabLapseRate ) )
call HistoryAutoPut( TimeA, 'SLP', xy_SLP )
xyz_QVapSat = xyz_CalcQVapSat( xyz_TempA, xyz_Press )
xyz_RH = xyzf_QMixA(:,:,:,IndexH2OVap) / xyz_QVapSat
call HistoryAutoPut( TimeA, 'RH', xyz_RH )
! MEMO
!
! dp/dz = - \rho g
! = - p / (RT) g
! 1/p dp/dz = - g / (RT)
! d(lnp)/dz = - g / (RT)
!
! \int_{z_0}^z d{lnp(z')}/dz' = - \int_{z_0}^z g / (RT(z')) dz'
! ln{p(z)} - ln{p(z_0)} = - g/R \int_{z_0}^z 1/T(z') dz'
! ln{p(z)/p(z_0)}
! = - g/R \int_{z_0}^z 1/T(z') dz'
! = - g/R \int_{z_0}^z 1/{ T(z_0) + \Gamma (z' - z_0) } dz'
! = - g/(R \Gamma) \int_{z_0}^z \Gamma/{ T(z_0) + \Gamma (z' - z_0) } dz'
! = - g/(R \Gamma) [ ln{ T(z_0) + \Gamma (z' - z_0) } ]_{z_0}^z
! = - g/(R \Gamma) [ ln{ T(z_0) + \Gamma (z - z_0) } - ln{ T(z_0) } ]
! = - g/(R \Gamma) ln[ { T(z_0) + \Gamma (z - z_0) } / T(z_0) ]
! = ln[ { T(z_0) + \Gamma (z - z_0) } / T(z_0) ]^{- g/(R \Gamma)}
! p(z)/p(z_0)
! = [ { T(z_0) + \Gamma (z - z_0) } / T(z_0) ]^{- g/(R \Gamma)}
! p(z)
! = p(z_0) [ { T(z_0) + \Gamma (z - z_0) } / T(z_0) ]^{- g/(R \Gamma)}
! = p(z_0) { 1.0 + \Gamma (z - z_0) / T(z_0) }^{- g/(R \Gamma)}
!
! T(z) = T(z_0) + \Gamma (z - z_0)
do j = 1, jmax
do i = 0, imax-1
xy_ScaleHeight(i,j) = GasRDry * xyz_VirTemp(i,j,xy_KIndex(i,j)) / Grav
end do
end do
xy_SLP = xy_PsA * exp( - ( 0.0_DP - xy_SurfHeight ) / xy_ScaleHeight )
call HistoryAutoPut( TimeA, 'SLPTmp', xy_SLP )
! 計算時間計測一時停止
! Pause measurement of computation time
!
call TimesetClockStop( module_name )
end subroutine OutputFreqUsedVars