Subroutine : |
|
xy_DeepSubSurfHeatFlux(0:imax-1, 1:jmax) : | real(DP), intent(in )
: | 地中熱フラックス. "Deep subsurface heat flux" Heat flux
at the bottom of surface/soil layer.
|
|
xy_SoilHeatCap(0:imax-1, 1:jmax) : | real(DP), intent(in )
: | 土壌熱容量 (J K-1 kg-1) Specific heat of soil (J K-1 kg-1)
|
|
xy_SoilHeatDiffCoef(0:imax-1, 1:jmax) : | real(DP), intent(in )
: | 土壌熱伝導係数 (J m-3 K-1) Heat conduction coefficient of soil (J
m-3 K-1)
|
|
xy_SurfTemp(0:imax-1, 1:jmax) : | real(DP), intent(in )
: | 地表面温度. Surface temperature
|
|
xyz_SoilTemp(0:imax-1, 1:jmax, 1:kslmax) : | real(DP), intent(in )
: | 土壌温度 (K) Soil temperature (K)
|
|
xy_SurfSnowB(0:imax-1, 1:jmax) : | real(DP), intent(in )
: | 積雪量. Surface snow amount.
|
|
xyr_SoilTempTransCoef(0:imax-1, 1:jmax, 0:kslmax) : | real(DP), intent(out)
: | 輸送係数:土壌温度. Transfer coefficient: soil temperature
|
|
xyr_SoilHeatFlux(0:imax-1, 1:jmax, 0:kslmax) : | real(DP), intent(out)
: | 土壌中の熱フラックス. Heat flux in sub-surface soil
|
|
時間変化率の計算を行います.
Calculate tendencies.
subroutine SubsurfaceDiffusion( xy_DeepSubSurfHeatFlux, xy_SoilHeatCap, xy_SoilHeatDiffCoef, xy_SurfTemp, xyz_SoilTemp, xy_SurfSnowB, xyr_SoilTempTransCoef, xyr_SoilHeatFlux )
!
! 時間変化率の計算を行います.
!
! Calculate tendencies.
!
! モジュール引用 ; USE statements
!
! 時刻管理
! Time control
!
use timeset, only: TimesetClockStart, TimesetClockStop
! 座標データ設定
! Axes data settings
!
use axesset, only: r_SSDepth, z_SSDepth ! subsurface grid at midpoint of layer
! 雪と海氷の定数の設定
! Setting constants of snow and sea ice
!
use constants_snowseaice, only: SnowDens, SnowMaxThermDepth, SnowThermCondCoef
! 宣言文 ; Declaration statements
!
implicit none
real(DP), intent(in ):: xy_DeepSubSurfHeatFlux (0:imax-1, 1:jmax)
! 地中熱フラックス.
! "Deep subsurface heat flux"
! Heat flux at the bottom of surface/soil layer.
real(DP), intent(in ):: xy_SoilHeatCap (0:imax-1, 1:jmax)
! 土壌熱容量 (J K-1 kg-1)
! Specific heat of soil (J K-1 kg-1)
real(DP), intent(in ):: xy_SoilHeatDiffCoef (0:imax-1, 1:jmax)
! 土壌熱伝導係数 (J m-3 K-1)
! Heat conduction coefficient of soil (J m-3 K-1)
real(DP), intent(in ):: xy_SurfTemp (0:imax-1, 1:jmax)
! 地表面温度.
! Surface temperature
real(DP), intent(in ):: xyz_SoilTemp (0:imax-1, 1:jmax, 1:kslmax)
! 土壌温度 (K)
! Soil temperature (K)
real(DP), intent(in ):: xy_SurfSnowB (0:imax-1, 1:jmax)
! 積雪量.
! Surface snow amount.
real(DP), intent(out):: xyr_SoilTempTransCoef (0:imax-1, 1:jmax, 0:kslmax)
! 輸送係数:土壌温度.
! Transfer coefficient: soil temperature
real(DP), intent(out):: xyr_SoilHeatFlux (0:imax-1, 1:jmax, 0:kslmax)
! 土壌中の熱フラックス.
! Heat flux in sub-surface soil
! 作業変数
! Work variables
!
integer:: k ! 鉛直方向に回る DO ループ用作業変数
! Work variables for DO loop in vertical direction
! 実行文 ; Executable statement
!
! 初期化確認
! Initialization check
!
if ( .not. subsurface_diffusion_inited ) then
call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
end if
! 計算時間計測開始
! Start measurement of computation time
!
call TimesetClockStart( module_name )
! 土壌温度計算用の輸送係数の計算
! Calculate transfer coefficient for heat diffusion in the soil
!
k = 0
if ( kslmax == 0 ) then
! This line is used when kslmax == 0, because z_SSDepth(k+1) does not exist.
xyr_SoilTempTransCoef(:,:,k) = 0.0_DP
else
!!$ xyr_SoilTempTransCoef(:,:,k) = &
!!$ & xy_SoilHeatDiffCoef(:,:) / ( z_SSDepth(k+1) - 0.0_DP )
xyr_SoilTempTransCoef(:,:,k) = ( ( z_SSDepth(k+1) - 0.0_DP ) / xy_SoilHeatDiffCoef - min( max( xy_SurfSnowB / SnowDens, 0.0_DP ), SnowMaxThermDepth ) / SnowThermCondCoef )**(-1)
end if
do k = 1, kslmax-1
xyr_SoilTempTransCoef(:,:,k) = xy_SoilHeatDiffCoef(:,:) / ( z_SSDepth(k+1) - z_SSDepth(k) )
end do
k = kslmax
xyr_SoilTempTransCoef(:,:,k) = 0.0_DP
! 土壌中の熱フラックスの計算
! Calculate heat flux in sub-surface soil
!
k = 0
if ( kslmax == 0 ) then
! This line is used when kslmax == 0, because xyz_SoilTemp(:,:,k+1) does not exist.
xyr_SoilHeatFlux(:,:,k) = 0.0_DP
else
xyr_SoilHeatFlux(:,:,k) = - xyr_SoilTempTransCoef(:,:,k) * ( xyz_SoilTemp(:,:,1) - xy_SurfTemp(:,:) )
end if
do k = 1, kslmax-1
xyr_SoilHeatFlux(:,:,k) = - xyr_SoilTempTransCoef(:,:,k) * ( xyz_SoilTemp(:,:,k+1) - xyz_SoilTemp(:,:,k) )
end do
k = kslmax
xyr_SoilHeatFlux(:,:,k) = xy_DeepSubSurfHeatFlux
! 計算時間計測一時停止
! Pause measurement of computation time
!
call TimesetClockStop( module_name )
end subroutine SubsurfaceDiffusion