Subroutine : | recursive
|
xy_Ps(0:imax-1, 1:jmax) : | real(DP), intent(in)
: | $ p_s (t-\Delta t) $ . 地表面気圧. Surface pressure
|
|
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
: | $ T $ . 温度. Temperature
|
|
xyz_QVap(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
: | $ q $ . 比湿. Specific humidity
|
|
xyr_Temp(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(out), optional
: | $ hat{T} $ . 温度 (半整数レベル). Temperature (half level)
|
|
xyz_VirTemp(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out), optional
: | $ hat{T} $ . 仮温度 Virtual temperature
|
|
xyr_VirTemp(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(out), optional
: | $ hat{T} $ . 仮温度 (半整数レベル). Virtual temperature (half
level)
|
|
xy_SurfVirTemp(0:imax-1, 1:jmax) : | real(DP), intent(out), optional
: | $ hat{T} $ . 仮温度 (惑星表面). Virtual temperature (surface)
|
|
xyz_Press(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out), optional
: | $ p $ . 気圧 (整数レベル). Air pressure (full level)
|
|
xyr_Press(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(out), optional
: | $ hat{p} $ . 気圧 (半整数レベル). Air pressure (half level)
|
|
xy_SurfHeight(0:imax-1,1:jmax) : | real(DP), intent(in ), optional
: | $ z_s $ . 地表面高度. Surface height.
|
|
xy_SurfTemp(0:imax-1,1:jmax) : | real(DP), intent(in ), optional
: | $ T_s $ . 惑星表面温度. Surface temperature.
|
|
xyz_Height(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out), optional
: | 高度 (整数レベル). Height (full level)
|
|
xyr_Height(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(out), optional
: | 高度 (半整数レベル). Height (half level)
|
|
xyz_Exner(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out), optional
: | Exner 関数 (整数レベル). Exner function (full level)
|
|
xyr_Exner(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(out), optional
: | Exner 関数 (半整数レベル). Exner function (half level)
|
|
温度の半整数σレベルの補間, 気圧と高度の算出,
エクスナー関数の計算を行います.
Interpolate temperature on half sigma level, and calculate pressure and
height, and calculate exner function.
recursive subroutine AuxVars( xy_Ps, xyz_Temp, xyz_QVap, xyr_Temp, xyz_VirTemp, xyr_VirTemp, xy_SurfVirTemp, xyz_Press, xyr_Press, xy_SurfHeight, xy_SurfTemp, xyz_Height, xyr_Height, xyz_Exner, xyr_Exner )
!
! 温度の半整数σレベルの補間, 気圧と高度の算出,
! エクスナー関数の計算を行います.
!
! Interpolate temperature on half sigma level,
! and calculate pressure and height,
! and calculate exner function.
! モジュール引用 ; USE statements
!
! 座標データ設定
! Axes data settings
!
use axesset, only: z_Sigma, r_Sigma, z_DelSigma, r_DelSigma
! $ \Delta \sigma $ (半整数).
! $ \Delta \sigma $ (Half)
! 物理定数設定
! Physical constants settings
!
use constants, only: Grav, GasRDry, CpDry, EpsV
! $ \epsilon_v $ .
! 水蒸気分子量比.
! Molecular weight of water vapor
! 時刻管理
! Time control
!
use timeset, only: TimesetClockStart, TimesetClockStop
! 宣言文 ; Declaration statements
!
implicit none
real(DP), intent(in):: xy_Ps (0:imax-1, 1:jmax)
! $ p_s (t-\Delta t) $ . 地表面気圧. Surface pressure
real(DP), intent(in):: xyz_Temp (0:imax-1, 1:jmax, 1:kmax)
! $ T $ . 温度. Temperature
real(DP), intent(in):: xyz_QVap (0:imax-1, 1:jmax, 1:kmax)
! $ q $ . 比湿. Specific humidity
real(DP), intent(out), optional:: xyr_Temp (0:imax-1, 1:jmax, 0:kmax)
! $ \hat{T} $ . 温度 (半整数レベル).
! Temperature (half level)
real(DP), intent(out), optional:: xyz_VirTemp(0:imax-1, 1:jmax, 1:kmax)
! $ \hat{T} $ . 仮温度
! Virtual temperature
real(DP), intent(out), optional:: xyr_VirTemp(0:imax-1, 1:jmax, 0:kmax)
! $ \hat{T} $ . 仮温度 (半整数レベル).
! Virtual temperature (half level)
real(DP), intent(out), optional:: xy_SurfVirTemp(0:imax-1, 1:jmax)
! $ \hat{T} $ . 仮温度 (惑星表面).
! Virtual temperature (surface)
real(DP), intent(out), optional:: xyz_Press (0:imax-1, 1:jmax, 1:kmax)
! $ p $ . 気圧 (整数レベル).
! Air pressure (full level)
real(DP), intent(out), optional:: xyr_Press (0:imax-1, 1:jmax, 0:kmax)
! $ \hat{p} $ . 気圧 (半整数レベル).
! Air pressure (half level)
real(DP), intent(in ), optional:: xy_SurfHeight(0:imax-1,1:jmax)
! $ z_s $ . 地表面高度.
! Surface height.
real(DP), intent(in ), optional:: xy_SurfTemp(0:imax-1,1:jmax)
! $ T_s $ . 惑星表面温度.
! Surface temperature.
real(DP), intent(out), optional:: xyz_Height (0:imax-1, 1:jmax, 1:kmax)
! 高度 (整数レベル).
! Height (full level)
real(DP), intent(out), optional:: xyr_Height (0:imax-1, 1:jmax, 0:kmax)
! 高度 (半整数レベル).
! Height (half level)
real(DP), intent(out), optional:: xyz_Exner (0:imax-1, 1:jmax, 1:kmax)
! Exner 関数 (整数レベル).
! Exner function (full level)
real(DP), intent(out), optional:: xyr_Exner (0:imax-1, 1:jmax, 0:kmax)
! Exner 関数 (半整数レベル).
! Exner function (half level)
! 作業変数
! Work variables
!
real(DP):: xyz_PressWork (0:imax-1, 1:jmax, 1:kmax)
! $ p $ . 気圧 (整数レベル).
! Air pressure (full level)
real(DP):: xyr_PressWork (0:imax-1, 1:jmax, 0:kmax)
! $ \hat{p} $ . 気圧 (半整数レベル).
! Air pressure (half level)
real(DP):: xyr_TempWork (0:imax-1, 1:jmax, 0:kmax)
! $ \hat{T} $ . 温度 (半整数レベル).
! Temperature (half level)
real(DP):: xyz_VirTempWork(0:imax-1, 1:jmax, 1:kmax)
! $ T_v $ . 仮温度.
! Virtual temperature
real(DP):: xyr_VirTempWork(0:imax-1, 1:jmax, 0:kmax)
! $ \hat{T}_v $ . 仮温度 (半整数レベル).
! Virtual temperature (half level)
integer:: k ! 鉛直方向に回る DO ループ用作業変数
! Work variables for DO loop in vertical direction
! 実行文 ; Executable statement
!
! 初期化確認
! Initialization check
!
if ( .not. auxiliary_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
!
if ( present( xyr_Temp ) ) then
call AuxVarsInternalRoutine( xy_Ps, xyz_Temp, xyr_Temp = xyr_Temp )
end if
! 仮温度の計算
! Calculate virtual temperature
!
if ( present( xy_SurfVirTemp ) ) then
if ( .not. present( xy_SurfTemp ) ) then
call MessageNotify( 'E', module_name, 'xy_SurfTemp has to be given in arguments to calculate xy_SurfVirTemp.' )
end if
xy_SurfVirTemp = xy_SurfTemp * ( 1.0_DP + ((( 1.0_DP / EpsV ) - 1.0_DP ) * xyz_QVap(:,:,1) ) )
end if
! 仮温度の計算
! Calculate virtual temperature
!
if ( present( xyz_VirTemp ) ) then
xyz_VirTemp = xyz_Temp * ( 1.0_DP + ((( 1.0_DP / EpsV ) - 1.0_DP ) * xyz_QVap) )
end if
! 仮温度の補間
! Interpolate virtual temperature
!
if ( present( xyr_VirTemp ) ) then
if ( present( xyz_VirTemp ) ) then
xyz_VirTempWork = xyz_VirTemp
else
xyz_VirTempWork = xyz_Temp * ( 1.0_DP + ((( 1.0_DP / EpsV ) - 1.0_DP ) * xyz_QVap) )
end if
call AuxVarsInternalRoutine( xy_Ps, xyz_VirTempWork, xyr_Temp = xyr_VirTemp )
end if
! 気圧の計算
! Calculate pressure
!
if ( present( xyz_Press ) ) then
call AuxVarsInternalRoutine( xy_Ps, xyz_Temp, xyz_Press = xyz_Press )
end if
if ( present( xyr_Press ) ) then
call AuxVarsInternalRoutine( xy_Ps, xyz_Temp, xyr_Press = xyr_Press )
end if
! 高度の計算
! Calculate height
!
if ( present( xyz_Height ) ) then
if ( .not. present( xy_SurfHeight ) ) then
call MessageNotify( 'E', module_name, 'xy_SurfHeight has to be given in arguments to calculate xyz_Height.' )
end if
!!$ if ( present( xyr_Temp ) ) then
!!$ xyr_TempWork = xyr_Temp
!!$ else
!!$ call AuxVarsInternalRoutine( &
!!$ & xy_Ps, xyz_Temp, & ! (in )
!!$ & xyr_Temp = xyr_TempWork & ! (out) optional
!!$ & )
!!$ end if
if ( present( xyz_VirTemp ) .and. present( xyr_VirTemp ) ) then
xyz_VirTempWork = xyz_VirTemp
xyr_VirTempWork = xyr_VirTemp
else
! 計算時間計測一時停止
! Pause measurement of computation time
call TimesetClockStop( module_name )
call AuxVars( xy_Ps, xyz_Temp, xyz_QVap, xyz_VirTemp = xyz_VirTempWork, xyr_VirTemp = xyr_VirTempWork )
! 計算時間計測開始
! Start measurement of computation time
call TimesetClockStart( module_name )
end if
!!$ xyz_Height(:,:,1) = &
!!$ & xy_SurfHeight(:,:) &
!!$ & + GasRDry / Grav * xyz_Temp(:,:,1) * ( 1. - z_Sigma(1) )
!!$ do k = 2, kmax
!!$ xyz_Height(:,:,k) = &
!!$ & xyz_Height(:,:,k-1) &
!!$ & + GasRDry / Grav * xyr_TempWork(:,:,k-1) &
!!$ & * r_DelSigma(k-1) / r_Sigma(k-1)
!!$ end do
xyz_Height(:,:,1) = xy_SurfHeight + GasRDry / Grav * xyz_VirTempWork(:,:,1) * ( 1.0_DP - z_Sigma(1) )
do k = 2, kmax
xyz_Height(:,:,k) = xyz_Height(:,:,k-1) + GasRDry / Grav * xyr_VirTempWork(:,:,k-1) * r_DelSigma(k-1) / r_Sigma(k-1)
end do
end if
if ( present( xyr_Height ) ) then
if ( .not. present( xy_SurfHeight ) ) then
call MessageNotify( 'E', module_name, 'xy_SurfHeight has to be given in arguments to calculate xyr_Height.' )
end if
if ( present( xyz_VirTemp ) ) then
xyz_VirTempWork = xyz_VirTemp
else
! 計算時間計測一時停止
! Pause measurement of computation time
call TimesetClockStop( module_name )
call AuxVars( xy_Ps, xyz_Temp, xyz_QVap, xyz_VirTemp = xyz_VirTempWork )
! 計算時間計測開始
! Start measurement of computation time
call TimesetClockStart( module_name )
end if
xyr_Height(:,:,0) = xy_SurfHeight
do k = 1, kmax
!!$ xyr_Height(:,:,k) = xyr_Height(:,:,k-1) &
!!$ & + GasRDry / Grav * xyz_Temp(:,:,k) &
!!$ & * z_DelSigma(k) / z_Sigma(k)
xyr_Height(:,:,k) = xyr_Height(:,:,k-1) + GasRDry / Grav * xyz_VirTempWork(:,:,k) * z_DelSigma(k) / z_Sigma(k)
end do
end if
! エクスナー関数の計算
! Calculate exner function
!
if ( present( xyz_Exner ) ) then
if ( present( xyz_Press ) ) then
xyz_PressWork = xyz_Press
else
call AuxVarsInternalRoutine( xy_Ps, xyz_Temp, xyz_Press = xyz_PressWork )
end if
xyz_Exner = ( xyz_PressWork / RefPress ) ** ( GasRDry / CpDry )
end if
if ( present( xyr_Exner ) ) then
if ( present( xyr_Press ) ) then
xyr_PressWork = xyr_Press
else
call AuxVarsInternalRoutine( xy_Ps, xyz_Temp, xyr_Press = xyr_PressWork )
end if
xyr_Exner = ( xyr_PressWork / RefPress ) ** ( GasRDry / CpDry )
end if
! 計算時間計測一時停止
! Pause measurement of computation time
!
call TimesetClockStop( module_name )
end subroutine AuxVars