Subroutine : |
|
DelTime : | real(DP), intent(in)
|
xyzf_QMix(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) : | real(DP), intent(in)
: | $ q $ . 比湿. Specific humidity
|
|
xyr_Press(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in)
: | $ p_s $ . 地表面気圧 (半整数レベル). Surface pressure (half
level)
|
|
xy_SurfH2OVapFlux(0:imax-1, 1:jmax) : | real(DP), intent(inout)
: | 惑星表面水蒸気フラックス. Water vapor flux at the surface
!$ real(DP), intent(inout): | xyf_QMixFlux(0:imax-1, 1:jmax, 1:ncmax)
|
!$ ! 惑星表面比湿フラックス. !$ ! Specific humidity flux at
surface
|
|
Restrict surface flux Now, only the H2O vapor flux is restricted.
subroutine SurfaceFluxUtilLimitFlux( DelTime, xyzf_QMix, xyr_Press, xy_SurfH2OVapFlux )
!
!
!
! Restrict surface flux
! Now, only the H2O vapor flux is restricted.
!
! モジュール引用 ; USE statements
!
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoPut
! 物理定数設定
! Physical constants settings
!
use constants, only: Grav ! $ g $ [m s-2].
! 重力加速度.
! Gravitational acceleration
! 時刻管理
! Time control
!
use timeset, only: TimeN, TimesetClockStart, TimesetClockStop
! デバッグ用ユーティリティ
! Utilities for debug
!
use dc_trace, only: DbgMessage, BeginSub, EndSub
! 宣言文 ; Declaration statements
!
implicit none
real(DP), intent(in):: DelTime
! Time step
real(DP), intent(in):: xyzf_QMix(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
! $ q $ . 比湿. Specific humidity
real(DP), intent(in):: xyr_Press (0:imax-1, 1:jmax, 0:kmax)
! $ p_s $ . 地表面気圧 (半整数レベル).
! Surface pressure (half level)
real(DP), intent(inout):: xy_SurfH2OVapFlux(0:imax-1, 1:jmax)
! 惑星表面水蒸気フラックス.
! Water vapor flux at the surface
!!$ real(DP), intent(inout):: xyf_QMixFlux(0:imax-1, 1:jmax, 1:ncmax)
!!$ ! 惑星表面比湿フラックス.
!!$ ! Specific humidity flux at surface
! 作業変数
! Work variables
!
real(DP):: xyz_DelMass(0:imax-1, 1:jmax, 1:kmax)
!
! Mass in each layer
real(DP):: xy_ConsMass(0:imax-1, 1:jmax)
!
! Constituent mass in each column
real(DP):: xy_SurfFlux(0:imax-1, 1:jmax)
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 altitude
integer:: n ! 組成方向に回る DO ループ用作業変数
! Work variables for DO loop in dimension of constituents
! 実行文 ; Executable statement
!
! 初期化確認
! Initialization check
!
if ( .not. surface_flux_util_inited ) then
call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
end if
! 計算時間計測開始
! Start measurement of computation time
!
call TimesetClockStart( module_name )
do k = 1, kmax
xyz_DelMass(:,:,k) = ( xyr_Press(:,:,k-1) - xyr_Press(:,:,k) ) / Grav
end do
!!$ do n = 1, ncmax
do n = IndexH2OVap, IndexH2OVap
xy_ConsMass = 0.0_DP
do k = kmax, 1, -1
xy_ConsMass = xy_ConsMass + xyz_DelMass(:,:,k) * xyzf_QMix(:,:,k,n)
end do
if ( n == IndexH2OVap ) then
xy_SurfFlux = xy_SurfH2OVapFlux
else
!!$ xy_SurfFlux = xyf_QMixFlux(:,:,n)
end if
do j = 1, jmax
do i = 0, imax-1
if ( - xy_SurfFlux(i,j) * DelTime > xy_ConsMass(i,j) ) then
xy_SurfFlux(i,j) = - xy_ConsMass(i,j) / DelTime !&
!!$ & * ( 1.0_DP - 1.0d-15 )
end if
end do
end do
if ( n == IndexH2OVap ) then
xy_SurfH2OVapFlux = xy_SurfFlux
else
!!$ xyf_QMixFlux(:,:,n) = xy_SurfFlux
end if
end do
! 計算時間計測一時停止
! Pause measurement of computation time
!
call TimesetClockStop( module_name )
end subroutine SurfaceFluxUtilLimitFlux