Subroutine : |
|
xyz_Exner(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
|
xy_SurfHeight(0:imax-1, 1:jmax) : | real(DP), intent(in)
|
xyz_Height(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
|
xyz_DUDtPhy(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
: | $ left(DP{u}{t}right)^{phy} $ . 外力項 (物理過程) による東西風速変化.
Eastward wind tendency by external force terms (physical processes)
|
|
xyz_DVDtPhy(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
: | $ left(DP{v}{t}right)^{phy} $ . 外力項 (物理過程) による南北風速変化.
Northward wind tendency by external force terms (physicalprocesses)
|
|
xyz_DTempDtPhy(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
: | $ left(DP{T}{t}right)^{phy} $ . 外力項 (物理過程) による温度変化.
Temperature tendency by external force terms (physical processes)
|
|
xyzf_DQMixDtPhy(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) : | real(DP), intent(in)
: | $ left(DP{q}{t}right)^{phy} $ . 外力項 (物理過程) による比湿変化.
Temperature tendency by external force terms (physical processes)
|
|
xy_PsB(0:imax-1, 1:jmax) : | real(DP), intent(in )
: | $ p_s $ . 地表面気圧 (半整数レベル). Surface pressure (half level)
|
|
xyz_UB(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in )
: | $ u $ . 東西風速. Eastward wind
|
|
xyz_VB(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in )
: | $ v $ . 南北風速. Northward wind
|
|
xyz_TempB(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in )
: | $ T $ . 温度 (整数レベル). Temperature (full level)
|
|
xyzf_QMixB(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) : | real(DP), intent(in )
: | $ q $ . 比湿. Specific humidity
|
|
xy_PsN(0:imax-1, 1:jmax) : | real(DP), intent(in)
: | $ p_s (t) $ . 地表面気圧. Surface pressure
|
|
xyz_UN(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
: | $ u (t) $ . 東西風速. Eastward wind
|
|
xyz_VN(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
: | $ v (t) $ . 南北風速. Northward wind
|
|
xyz_TempN(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
: | $ T (t) $ . 温度. Temperature
|
|
xyzf_QMixN(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) : | real(DP), intent(in)
: | $ q (t) $ . 比湿. Specific humidity
|
|
xy_PsA(0:imax-1, 1:jmax) : | real(DP), intent(out)
: | $ p_s $ . 地表面気圧 (半整数レベル). Surface pressure (half level)
|
|
xyz_UA(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out)
: | $ u $ . 東西風速. Eastward wind
|
|
xyz_VA(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out)
: | $ v $ . 南北風速. Northward wind
|
|
xyz_TempA(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out)
: | $ T $ . 温度 (整数レベル). Temperature (full level)
|
|
xyzf_QMixA(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) : | real(DP), intent(out)
: | $ q $ . 比湿. Specific humidity
|
|
subroutine DynamicsPhysicsOnly( xyz_Exner, xy_SurfHeight, xyz_Height, xyz_DUDtPhy, xyz_DVDtPhy, xyz_DTempDtPhy, xyzf_DQMixDtPhy, xy_PsB, xyz_UB, xyz_VB, xyz_TempB, xyzf_QMixB, xy_PsN, xyz_UN, xyz_VN, xyz_TempN, xyzf_QMixN, xy_PsA, xyz_UA, xyz_VA, xyz_TempA, xyzf_QMixA )
! モジュール引用 ; USE statements
!
! 時刻管理
! Time control
!
use timeset, only: DelTime, TimeN, TimesetClockStart, TimesetClockStop
! デバッグ用ユーティリティ
! Utilities for debug
!
use dc_trace, only: DbgMessage, BeginSub, EndSub
! 組成に関わる配列の設定
! Settings of array for atmospheric composition
!
use composition, only: ncmax, CompositionInqFlagAdv
! 1 次元計算用力学過程ユーティリティモジュール
! Utility module for dynamics for 1-D calculation
!
use dynamics_1d_utils, only : Dynamics1DUtilsVerAdv
!!$ ! 質量の補正
!!$ ! Mass fixer
!!$ !
!!$ use mass_fixer, only: MassFixerColumn
! 宣言文 ; Declaration statements
!
real(DP), intent(in):: xyz_Exner (0:imax-1, 1:jmax, 1:kmax)
real(DP), intent(in):: xy_SurfHeight (0:imax-1, 1:jmax)
real(DP), intent(in):: xyz_Height (0:imax-1, 1:jmax, 1:kmax)
real(DP), intent(in):: xyz_DUDtPhy (0:imax-1, 1:jmax, 1:kmax)
! $ \left(\DP{u}{t}\right)^{phy} $ .
! 外力項 (物理過程) による東西風速変化.
! Eastward wind tendency by external force terms (physical processes)
real(DP), intent(in):: xyz_DVDtPhy (0:imax-1, 1:jmax, 1:kmax)
! $ \left(\DP{v}{t}\right)^{phy} $ .
! 外力項 (物理過程) による南北風速変化.
! Northward wind tendency by external force terms (physicalprocesses)
real(DP), intent(in):: xyz_DTempDtPhy (0:imax-1, 1:jmax, 1:kmax)
! $ \left(\DP{T}{t}\right)^{phy} $ .
! 外力項 (物理過程) による温度変化.
! Temperature tendency by external force terms (physical processes)
real(DP), intent(in):: xyzf_DQMixDtPhy (0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
! $ \left(\DP{q}{t}\right)^{phy} $ .
! 外力項 (物理過程) による比湿変化.
! Temperature tendency by external force terms (physical processes)
real(DP), intent(in ):: xy_PsB(0:imax-1, 1:jmax)
! $ p_s $ . 地表面気圧 (半整数レベル).
! Surface pressure (half level)
real(DP), intent(in ):: xyz_UB(0:imax-1, 1:jmax, 1:kmax)
! $ u $ . 東西風速. Eastward wind
real(DP), intent(in ):: xyz_VB(0:imax-1, 1:jmax, 1:kmax)
! $ v $ . 南北風速. Northward wind
real(DP), intent(in ):: xyz_TempB(0:imax-1, 1:jmax, 1:kmax)
! $ T $ . 温度 (整数レベル).
! Temperature (full level)
real(DP), intent(in ):: xyzf_QMixB(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
! $ q $ . 比湿. Specific humidity
real(DP), intent(in):: xy_PsN (0:imax-1, 1:jmax)
! $ p_s (t) $ . 地表面気圧. Surface pressure
real(DP), intent(in):: xyz_UN (0:imax-1, 1:jmax, 1:kmax)
! $ u (t) $ . 東西風速. Eastward wind
real(DP), intent(in):: xyz_VN (0:imax-1, 1:jmax, 1:kmax)
! $ v (t) $ . 南北風速. Northward wind
real(DP), intent(in):: xyz_TempN (0:imax-1, 1:jmax, 1:kmax)
! $ T (t) $ . 温度. Temperature
real(DP), intent(in):: xyzf_QMixN(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
! $ q (t) $ . 比湿. Specific humidity
real(DP), intent(out):: xy_PsA(0:imax-1, 1:jmax)
! $ p_s $ . 地表面気圧 (半整数レベル).
! Surface pressure (half level)
real(DP), intent(out):: xyz_UA(0:imax-1, 1:jmax, 1:kmax)
! $ u $ . 東西風速. Eastward wind
real(DP), intent(out):: xyz_VA(0:imax-1, 1:jmax, 1:kmax)
! $ v $ . 南北風速. Northward wind
real(DP), intent(out):: xyz_TempA(0:imax-1, 1:jmax, 1:kmax)
! $ T $ . 温度 (整数レベル).
! Temperature (full level)
real(DP), intent(out):: xyzf_QMixA(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
! $ q $ . 比湿. Specific humidity
! 作業変数
! Work variables
!
real(DP) :: xyz_PotTempB (0:imax-1, 1:jmax, 1:kmax)
real(DP) :: xyz_W (0:imax-1, 1:jmax, 1:kmax)
real(DP) :: xyz_DUDtAdv (0:imax-1, 1:jmax, 1:kmax)
real(DP) :: xyz_DVDtAdv (0:imax-1, 1:jmax, 1:kmax)
real(DP) :: xyz_DPotTempDtAdv(0:imax-1, 1:jmax, 1:kmax)
real(DP) :: xyzf_DQMixDtAdv (0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
real(DP) :: xyz_UT (0:imax-1, 1:jmax, 1:kmax)
real(DP) :: xyz_VT (0:imax-1, 1:jmax, 1:kmax)
real(DP) :: DelTimeX2
integer:: k
integer:: n
! 実行文 ; Executable statement
!
! 初期化確認
! Initialization check
!
if ( .not. dynamics_physicsonly_inited ) then
call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
end if
! 計算時間計測開始
! Start measurement of computation time
!
call TimesetClockStart( module_name )
DelTimeX2 = 2.0_DP * DelTime
xyz_PotTempB = xyz_TempB / xyz_Exner
if ( TimeN >= WTimeInit ) then
if ( WHeight > 0.0_DP ) then
do k = 1, kmax
xyz_W(:,:,k) = WMagnitude * min( xyz_Height(:,:,k) - xy_SurfHeight, WHeight ) / WHeight
end do
else
xyz_W = 0.0_DP
end if
else
xyz_W = 0.0_DP
end if
! 1 次元計算用力学過程ユーティリティモジュール
! Utility module for dynamics for 1-D calculation
!
call Dynamics1DUtilsVerAdv( xyz_W, xyz_Height, xyz_UB, xyz_DUDtAdv )
call Dynamics1DUtilsVerAdv( xyz_W, xyz_Height, xyz_VB, xyz_DVDtAdv )
call Dynamics1DUtilsVerAdv( xyz_W, xyz_Height, xyz_PotTempB, xyz_DPotTempDtAdv )
do n = 1, ncmax
if ( CompositionInqFlagAdv( n ) ) then
call Dynamics1DUtilsVerAdv( xyz_W, xyz_Height, xyzf_QMixB(:,:,:,n), xyzf_DQMixDtAdv(:,:,:,n) )
else
xyzf_DQMixDtAdv(:,:,:,n) = 0.0_DP
end if
end do
xy_PsA = xy_PsB
if ( FlagDynExp ) then
xyz_UA = xyz_UB + ( xyz_DUDtAdv + xyz_CorPar * xyz_VB + xyz_DUDtPhy ) * DelTimeX2
xyz_VA = xyz_VB + ( xyz_DVDtAdv - xyz_CorPar * xyz_UB + xyz_DVDtPhy ) * DelTimeX2
else
xyz_UT = xyz_UB + ( xyz_DUDtAdv + xyz_DUDtPhy ) * DelTimeX2
xyz_VT = xyz_VB + ( xyz_DVDtAdv + xyz_DVDtPhy ) * DelTimeX2
xyz_UA = ( xyz_UT + DelTimeX2 * xyz_CorPar * ( xyz_VT - VGeo + DelTimeX2 * xyz_CorPar * UGeo ) ) / ( 1.0_DP + ( DelTimeX2 * xyz_CorPar )**2 )
xyz_VA = ( xyz_VT - DelTimeX2 * xyz_CorPar * ( xyz_UT - UGeo - DelTimeX2 * xyz_CorPar * VGeo ) ) / ( 1.0_DP + ( DelTimeX2 * xyz_CorPar )**2 )
end if
!!$ xyz_TempA = xyz_TempB + xyz_DTempDtPhy * 2.0d0 * DelTime
xyz_TempA = xyz_PotTempB + ( xyz_DPotTempDtAdv + xyz_DTempDtPhy / xyz_Exner ) * DelTimeX2
xyz_TempA = xyz_TempA * xyz_Exner
xyzf_QMixA = xyzf_QMixB + ( xyzf_DQMixDtAdv + xyzf_DQMixDtPhy ) * DelTimeX2
xyzf_QMixA = max( xyzf_QMixA, 0.0_DP )
end subroutine DynamicsPhysicsOnly