| Class | phy_implicit_sdh | 
| In: | phy_implicit/phy_implicit_sdh.f90 | 
Note that Japanese and English are described in parallel.
| PhyImplTendency : | 時間変化率の計算 | 
| PhyImplEvalRadLFluxA : | 長波フラックス補正 | 
| ———— : | ———— | 
| PhyImplTendency : | Calculate tendency | 
| PhyImplEvalRadLFluxA : | Longwave flux correction | 
| Subroutine : | |||
| FlagPhyImpSoilModelSO : | logical , intent(in) 
 | ||
| xyr_MomFluxX(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_MomFluxY(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_HeatFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyrf_QMixFlux(0:imax-1, 1:jmax, 0:kmax, 1:ncmax) : | real(DP), intent(in) 
 | ||
| xyr_SoilHeatFlux(0:imax-1, 1:jmax, 0:kslmax) : | real(DP), intent(in) 
 | ||
| xyr_RadSFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_RadLFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xy_DeepSubSurfHeatFlux(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfTemp(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xyz_SoilTemp(0:imax-1, 1:jmax, 1:kslmax) : | real(DP), intent(in) 
 | ||
| xy_SurfHumidCoef(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfCond(0:imax-1, 1:jmax) : | integer, intent(in) 
 | ||
| xy_SurfHeatCapacity(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SoilHeatCap(0:imax-1, 1:jmax) : | real(DP), intent(in ) 
 | ||
| xy_SoilHeatDiffCoef(0:imax-1, 1:jmax) : | real(DP), intent(in ) 
 | ||
| xy_SeaIceConc(0:imax-1,1:jmax) : | real(DP), intent(in) 
 | ||
| xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1) : | real(DP), intent(in) 
 | ||
| xyr_Press(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyz_Exner(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyr_Exner(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_VelTransCoef(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_TempTransCoef(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_QMixTransCoef(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xy_SurfVelTransCoef(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfTempTransCoef(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfQVapTransCoef(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xyr_SoilTempTransCoef(0:imax-1, 1:jmax, 0:kslmax) : | real(DP), intent(in) 
 | ||
| xy_SurfSnowB(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xyz_DUDt(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out) 
 | ||
| xyz_DVDt(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out) 
 | ||
| xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(out) 
 | ||
| xyzf_DQMixDt(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) : | real(DP), intent(out) 
 | ||
| xy_DSurfTempDt(0:imax-1, 1:jmax) : | real(DP), intent(out) 
 | ||
| xyz_DSoilTempDt(0:imax-1, 1:jmax, 1:kslmax) : | real(DP), intent(out) 
 | ||
| xy_DSoilMoistDt(0:imax-1, 1:jmax) : | real(DP), intent(out) 
 | ||
| xy_DSurfSnowDt(0:imax-1, 1:jmax) : | real(DP), intent(out) 
 | 
時間変化率の計算を行います.
Calculate tendencies.
  subroutine PhyImplSDHTendency( FlagPhyImpSoilModelSO, xyr_MomFluxX, xyr_MomFluxY, xyr_HeatFlux, xyrf_QMixFlux, xyr_SoilHeatFlux, xyr_RadSFlux, xyr_RadLFlux, xy_DeepSubSurfHeatFlux, xy_SurfTemp, xyz_SoilTemp, xy_SurfHumidCoef, xy_SurfCond, xy_SurfHeatCapacity, xy_SoilHeatCap, xy_SoilHeatDiffCoef, xy_SeaIceConc, xyra_DelRadLFlux, xyr_Press, xyz_Exner, xyr_Exner, xyr_VelTransCoef, xyr_TempTransCoef, xyr_QMixTransCoef, xy_SurfVelTransCoef, xy_SurfTempTransCoef, xy_SurfQVapTransCoef, xyr_SoilTempTransCoef, xy_SurfSnowB, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xyzf_DQMixDt, xy_DSurfTempDt, xyz_DSoilTempDt, xy_DSoilMoistDt, xy_DSurfSnowDt )
    !
    ! 時間変化率の計算を行います. 
    !
    ! Calculate tendencies. 
    !
    ! モジュール引用 ; USE statements
    !
    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: r_SSDepth, z_SSDepth         ! subsurface grid at midpoint of layer
    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: Grav, CpDry, LatentHeat, GasRDry
                              ! $ R $ [J kg-1 K-1]. 
                              ! 乾燥大気の気体定数. 
                              ! Gas constant of air
    ! 雪と海氷の定数の設定
    ! Setting constants of snow and sea ice
    !
    use constants_snowseaice, only: TempCondWater, SeaIceVolHeatCap   , SeaIceThermCondCoef, SeaIceThreshold, SeaIceThickness, TempBelowSeaIce
    ! 時刻管理
    ! Time control
    !
    use timeset, only: DelTime, TimeN, TimesetClockStart, TimesetClockStop
    ! バケツモデル
    ! bucket model
    !
    use Bucket_Model, only: FlagBucketModel, FlagBucketModelSnow
    ! 陰解法による時間積分のためのルーチン
    ! Routines for time integration with implicit scheme
    !
    use phy_implicit_utils, only : PhyImplLUDecomp3, PhyImplLUSolve3
    ! 宣言文 ; Declaration statements
    !
    implicit none
    logical , intent(in):: FlagPhyImpSoilModelSO
                              ! flag for use of slab ocean
    real(DP), intent(in):: xyr_MomFluxX (0:imax-1, 1:jmax, 0:kmax)
                              ! 東西方向運動量フラックス. 
                              ! Eastward momentum flux
    real(DP), intent(in):: xyr_MomFluxY (0:imax-1, 1:jmax, 0:kmax)
                              ! 南北方向運動量フラックス. 
                              ! Northward momentum flux
    real(DP), intent(in):: xyr_HeatFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 熱フラックス. 
                              ! Heat flux
    real(DP), intent(in):: xyrf_QMixFlux(0:imax-1, 1:jmax, 0:kmax, 1:ncmax)
                              ! 比湿フラックス. 
                              ! Specific humidity flux
    real(DP), intent(in):: xyr_SoilHeatFlux (0:imax-1, 1:jmax, 0:kslmax)
                              ! 土壌中の熱フラックス (W m-2)
                              ! Heat flux in sub-surface soil (W m-2)
    real(DP), intent(in):: xyr_RadSFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 短波 (日射) フラックス. 
                              ! Shortwave (insolation) flux
    real(DP), intent(in):: xyr_RadLFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 長波フラックス. 
                              ! Longwave flux
    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_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_SurfHumidCoef (0:imax-1, 1:jmax)
                              ! 地表湿潤度. 
                              ! Surface humidity coefficient
    integer, intent(in):: xy_SurfCond (0:imax-1, 1:jmax)
                              ! 地表状態. 
                              ! Surface condition
    real(DP), intent(in):: xy_SurfHeatCapacity (0:imax-1, 1:jmax)
                              ! 地表熱容量. 
                              ! Surface heat capacity
    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_SeaIceConc(0:imax-1,1:jmax)
                              ! 海氷密度 (0 <= xy_SeaIceConc <= 1)
                              ! Sea ice concentration (0 <= xy_SeaIceConc <= 1)
    real(DP), intent(in):: xyra_DelRadLFlux (0:imax-1, 1:jmax, 0:kmax, 0:1)
                              ! 長波地表温度変化. 
                              ! Surface temperature tendency with longwave
    real(DP), intent(in):: xyr_Press (0:imax-1, 1:jmax, 0:kmax)
                              ! $ \hat{p} $ . 気圧 (半整数レベル). 
                              ! Air pressure (half level)
    real(DP), intent(in):: xyz_Exner (0:imax-1, 1:jmax, 1:kmax)
                              ! Exner 関数 (整数レベル). 
                              ! Exner function (full level)
    real(DP), intent(in):: xyr_Exner (0:imax-1, 1:jmax, 0:kmax)
                              ! Exner 関数 (半整数レベル). 
                              ! Exner function (half level)
    real(DP), intent(in):: xyr_VelTransCoef (0:imax-1, 1:jmax, 0:kmax)
                              ! 輸送係数:運動量. 
                              ! Transfer coefficient: velocity
    real(DP), intent(in):: xyr_TempTransCoef (0:imax-1, 1:jmax, 0:kmax)
                              ! 輸送係数:温度. 
                              ! Transfer coefficient: temperature
    real(DP), intent(in):: xyr_QMixTransCoef(0:imax-1, 1:jmax, 0:kmax)
                              ! 輸送係数:質量. 
                              ! Transfer coefficient: mass of constituents
    real(DP), intent(in):: xy_SurfVelTransCoef (0:imax-1, 1:jmax)
                              ! 輸送係数:運動量. 
                              ! Diffusion coefficient: velocity
    real(DP), intent(in):: xy_SurfTempTransCoef (0:imax-1, 1:jmax)
                              ! 輸送係数:温度. 
                              ! Transfer coefficient: temperature
    real(DP), intent(in):: xy_SurfQVapTransCoef (0:imax-1, 1:jmax)
                              ! 輸送係数:比湿. 
                              ! Transfer coefficient: specific humidity
    real(DP), intent(in):: xyr_SoilTempTransCoef (0:imax-1, 1:jmax, 0:kslmax)
                              ! 輸送係数:土壌温度.
                              ! Transfer coefficient: soil temperature
    real(DP), intent(in):: xy_SurfSnowB (0:imax-1, 1:jmax)
                              ! 積雪量.
                              ! Surface snow amount.
    real(DP), intent(out):: xyz_DUDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{u}{t} $ . 東西風速変化. 
                              ! Eastward wind tendency
    real(DP), intent(out):: xyz_DVDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{v}{t} $ . 南北風速変化. 
                              ! Northward wind tendency
    real(DP), intent(out):: xyz_DTempDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{T}{t} $ . 温度変化. 
                              ! Temperature tendency
    real(DP), intent(out):: xyzf_DQMixDt(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ \DP{q}{t} $ . 質量混合比変化. 
                              ! Mass mixing ratio tendency
    real(DP), intent(out):: xy_DSurfTempDt (0:imax-1, 1:jmax)
                              ! 地表面温度変化率 (K s-1)
                              ! Surface temperature tendency (K s-1)
    real(DP), intent(out):: xyz_DSoilTempDt (0:imax-1, 1:jmax, 1:kslmax)
                              ! $ \DP{Tg}{t} $ . 土壌温度変化 (K s-1)
                              ! Temperature tendency (K s-1)
    real(DP), intent(out):: xy_DSoilMoistDt (0:imax-1, 1:jmax)
                              ! 土壌温度時間変化率 (kg m-2 s-1)
                              ! Soil temperature tendency (kg m-2 s-1)
    real(DP), intent(out):: xy_DSurfSnowDt (0:imax-1, 1:jmax)
                              ! 積雪率時間変化率 (kg m-2 s-1)
                              ! Surface snow amount tendency (kg m-2 s-1)
    ! 作業変数
    ! Work variables
    !
    real(DP):: xyza_UVMtx (0:imax-1, 1:jmax, 1:kmax, -1:1)
                              ! 速度陰解行列. 
                              ! Implicit matrix about velocity 
    real(DP):: xyra_TempMtx(0:imax-1, 1:jmax, 0:kmax, -1:1)
                              ! 温度陰解行列. 
                              ! Implicit matrix about temperature
    real(DP):: xyza_QMixMtx(0:imax-1, 1:jmax, 1:kmax, -1:1)
                              ! 質量混合比陰解行列. 
                              ! Implicit matrix about mass mixing ratio
    real(DP):: xyaa_SurfMtx(0:imax-1, 1:jmax, 0:0, -1:1)
                              ! 惑星表面エネルギー収支用陰解行列
                              ! Implicit matrix for surface energy balance
    real(DP):: xy_SurfRH(0:imax-1,1:jmax)
    real(DP):: xyza_UVLUMtx (0:imax-1, 1:jmax, 1:kmax,-1:1)
                              ! LU 行列. 
                              ! LU matrix
!!$    real(DP):: xyza_TempQVapLUMtx (0:imax-1, 1:jmax, -kmax:kmax, -1:1)
!!$                              ! LU 行列. 
!!$                              ! LU matrix
!!$    real(DP):: xyz_DelTempQVap (0:imax-1, 1:jmax, -kmax:kmax)
!!$                              ! $ T q $ の時間変化. 
!!$                              ! Tendency of $ T q $ 
!!$
!!$    real(DP):: xyza_TempLUMtx (0:imax-1, 1:jmax, 0:kmax, -1:1)
!!$                              ! LU 行列.
!!$                              ! LU matrix
!!$    real(DP):: xyz_DelTempLUVec (0:imax-1, 1:jmax, 0:kmax)
!!$                              ! $ T q $ の時間変化.
!!$                              ! Tendency of $ T q $
    real(DP):: xyza_QMixLUMtx (0:imax-1, 1:jmax, 1:kmax, -1:1)
                              ! LU 行列.
                              ! LU matrix
    real(DP):: xyz_DelQMixLUVec (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q $ の時間変化.
                              ! Tendency of $ q $
!!$    real(DP):: xy_SurfQVapSat (0:imax-1, 1:jmax)
!!$                              ! 地表飽和比湿. 
!!$                              ! Saturated specific humidity on surface
!!$    real(DP):: xy_SurfDQVapSatDTemp (0:imax-1, 1:jmax)
!!$                              ! 地表飽和比湿変化. 
!!$                              ! Saturated specific humidity tendency on surface
    real(DP):: xyaa_SoilTempMtx (0:imax-1, 1:jmax, 1:kslmax,-1:1)
                              ! 土壌温度拡散方程式の行列
                              ! Matrix for diffusion equation of soil temperature
    real(DP):: xyaa_TempSoilTempLUMtx (0:imax-1, 1:jmax, -kslmax:kmax, -1:1)
                              ! LU 行列.
                              ! LU matrix
    real(DP):: xya_DelTempSoilTempLUVec (0:imax-1, 1:jmax, -kslmax:kmax)
                              ! $ T, Tg $ の時間変化.
                              ! Tendency of $ T $ and $ Tg |
    real(DP):: SurfSnowATentative
                              ! 積雪量の仮の値 (kg m-2)
                              ! pseudo value of surface snow amount (kg m-2)
    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:: l               ! 行列用 DO ループ用作業変数
                              ! Work variables for DO loop of matrices
    integer:: n               ! 組成方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in dimension of constituents
    ! 実行文 ; Executable statement
    !
    ! 計算時間計測開始
    ! Start measurement of computation time
    !
    call TimesetClockStart( module_name )
    ! 初期化
    ! Initialization
    !
    if ( .not. phy_implicit_sdh_inited ) call PhyImplInit
!!$    if ( .not. FlagSSModel ) then
!!$      call MessageNotify( 'E', module_name, 'FlagSSModel has to be true.' )
!!$    end if
    ! FlagBucketModel は関係ないよね?
    ! SSModel 強制にした時点で, 水蒸気は地面と分離したから. 
!!$    if ( .not. FlagBucketModel ) then
!!$      call MessageNotify( 'E', module_name, 'FlagBucketModel has to be true.' )
!!$    end if
    ! 陰解法のための行列作成
    ! Create matrices for implicit scheme
    !
    ! 鉛直拡散スキームの輸送係数から陰解行列の計算 (速度)
    ! Calculate implicit matrices from transfer coefficient of vertical diffusion scheme (velocity)
    !
    k = 1
    xyza_UVMtx  (:,:,k,-1) = 0.0d0
    xyza_UVMtx  (:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2. * DelTime ) + xy_SurfVelTransCoef(:,:) + xyr_VelTransCoef(:,:,k  )
    xyza_UVMtx  (:,:,k, 1) = - xyr_VelTransCoef(:,:,k)
    do k = 2, kmax-1
      xyza_UVMtx  (:,:,k,-1) = - xyr_VelTransCoef(:,:,k-1)
      xyza_UVMtx  (:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2. * DelTime ) + xyr_VelTransCoef(:,:,k-1) + xyr_VelTransCoef(:,:,k  )
      xyza_UVMtx  (:,:,k, 1) = - xyr_VelTransCoef(:,:,k)
    end do
    k = kmax
    xyza_UVMtx  (:,:,k,-1) = - xyr_VelTransCoef(:,:,k-1)
    xyza_UVMtx  (:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2. * DelTime ) + xyr_VelTransCoef(:,:,k-1)
    xyza_UVMtx  (:,:,k, 1) = 0.0d0
    ! 鉛直拡散スキームの輸送係数から陰解行列の計算 (温度)
    ! Calculate implicit matrices from transfer coefficient of vertical diffusion scheme (temperature)
    !
    k = 1
    xyra_TempMtx(:,:,k,-1) = - CpDry * xy_SurfTempTransCoef(:,:)
    xyra_TempMtx(:,:,k, 0) = - CpDry * ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2. * DelTime ) + CpDry * xyr_Exner(:,:,k-1) / xyz_Exner(:,:,k  ) * xy_SurfTempTransCoef(:,:) + CpDry * xyr_Exner(:,:,k  ) / xyz_Exner(:,:,k  ) * xyr_TempTransCoef(:,:,k  )
    xyra_TempMtx(:,:,k, 1) = - CpDry * xyr_Exner(:,:,k  ) / xyz_Exner(:,:,k+1) * xyr_TempTransCoef(:,:,k  )
    do k = 2, kmax-1
      xyra_TempMtx(:,:,k,-1) = - CpDry * xyr_Exner(:,:,k-1) / xyz_Exner(:,:,k-1) * xyr_TempTransCoef(:,:,k-1)
      xyra_TempMtx(:,:,k, 0) = - CpDry * ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2. * DelTime ) + CpDry * xyr_Exner(:,:,k-1) / xyz_Exner(:,:,k  ) * xyr_TempTransCoef(:,:,k-1) + CpDry * xyr_Exner(:,:,k  ) / xyz_Exner(:,:,k  ) * xyr_TempTransCoef(:,:,k  )
      xyra_TempMtx(:,:,k, 1) = - CpDry * xyr_Exner(:,:,k  ) / xyz_Exner(:,:,k+1) * xyr_TempTransCoef(:,:,k  )
    end do
    k = kmax
    xyra_TempMtx(:,:,k,-1) = - CpDry * xyr_Exner(:,:,k-1) / xyz_Exner(:,:,k-1) * xyr_TempTransCoef(:,:,k-1)
    xyra_TempMtx(:,:,k, 0) = - CpDry * ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2. * DelTime ) + CpDry * xyr_Exner(:,:,k-1) / xyz_Exner(:,:,k  ) * xyr_TempTransCoef(:,:,k-1)
    xyra_TempMtx(:,:,k, 1) = 0.0d0
    ! 鉛直拡散スキームの輸送係数から陰解行列の計算 (比湿)
    ! Calculate implicit matrices from transfer coefficient of vertical diffusion scheme (specific humidity)
    !
    k = 1
    xyza_QMixMtx(:,:,k,-1) = 0.0d0
    xyza_QMixMtx(:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2. * DelTime ) + xyr_QMixTransCoef(:,:,k  )
    xyza_QMixMtx(:,:,k, 1) = - xyr_QMixTransCoef(:,:,k  )
    do k = 2, kmax-1
      xyza_QMixMtx(:,:,k,-1) = - xyr_QMixTransCoef(:,:,k-1)
      xyza_QMixMtx(:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2. * DelTime ) + xyr_QMixTransCoef(:,:,k-1) + xyr_QMixTransCoef(:,:,k  )
      xyza_QMixMtx(:,:,k, 1) = - xyr_QMixTransCoef(:,:,k  )
    end do
    k = kmax
    xyza_QMixMtx(:,:,k,-1) = - xyr_QMixTransCoef(:,:,k-1)
    xyza_QMixMtx(:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2. * DelTime ) + xyr_QMixTransCoef(:,:,k-1)
    xyza_QMixMtx(:,:,k, 1) = 0.0d0
    ! 土壌温度計算用の輸送係数から陰解行列の計算 (土壌温度)
    ! Calculate implicit matrices by using transfer coefficient (soil temperature)
    !
    if ( kslmax /= 0 ) then ! xyr_SoilTempMtx is not used when kslmax = 0.
      do k = 1, kslmax-1
        xyaa_SoilTempMtx(:,:,k,-1) = - xyr_SoilTempTransCoef(:,:,k-1)
        xyaa_SoilTempMtx(:,:,k, 0) = xy_SoilHeatCap(:,:) * ( r_SSDepth(k) - r_SSDepth(k-1) ) / ( 2. * DelTime ) + xyr_SoilTempTransCoef(:,:,k-1) + xyr_SoilTempTransCoef(:,:,k  )
        xyaa_SoilTempMtx(:,:,k, 1) = - xyr_SoilTempTransCoef(:,:,k  )
      end do
      k = kslmax
      xyaa_SoilTempMtx(:,:,k,-1) = - xyr_SoilTempTransCoef(:,:,k-1)
      xyaa_SoilTempMtx(:,:,k, 0) = xy_SoilheatCap(:,:) * ( r_SSDepth(k) - r_SSDepth(k-1) ) / ( 2. * DelTime ) + xyr_SoilTempTransCoef(:,:,k-1)
      xyaa_SoilTempMtx(:,:,k, 1) = 0.0d0
    end if
    ! 地表面過程の輸送係数から陰解行列の計算
    ! Calculate implicit matrices from transfer coefficient of surface process
    !
    do i = 0, imax-1
      do j = 1, jmax
        if ( xy_SurfCond(i,j) >= 1 ) then
          ! land
          xyaa_SurfMtx(i,j,0,-1) = xyr_SoilTempTransCoef(i,j,0)
          xyaa_SurfMtx(i,j,0, 0) = xy_SurfHeatCapacity(i,j) / ( 2. * DelTime ) + CpDry * xy_SurfTempTransCoef(i,j) + xyra_DelRadLFlux(i,j,0,0) - xyr_SoilTempTransCoef(i,j,0)
          xyaa_SurfMtx(i,j,0, 1) = - CpDry * xyr_Exner(i,j,0) / xyz_Exner(i,j,1) * xy_SurfTempTransCoef(i,j) + xyra_DelRadLFlux(i,j,0,1)
        else
          ! ocean
          if ( xy_SeaIceConc(i,j) > SeaIceThreshold ) then
            ! sea ice
            xyaa_SurfMtx(i,j,0,-1) = 0.0d0
            xyaa_SurfMtx(i,j,0, 0) = SeaIceVolHeatCap / ( 2.0d0 * DelTime ) + CpDry * xy_SurfTempTransCoef(i,j) + xyra_DelRadLFlux(i,j,0,0) + SeaIceThermCondCoef / SeaIceThickness
            xyaa_SurfMtx(i,j,0, 1) = - CpDry * xyr_Exner(i,j,0) / xyz_Exner(i,j,1) * xy_SurfTempTransCoef(i,j) + xyra_DelRadLFlux(i,j,0,1)
          else if ( FlagPhyImpSoilModelSO ) then
            ! mixed layer ocean
            xyaa_SurfMtx(i,j,0,-1) = 0.0d0
            xyaa_SurfMtx(i,j,0, 0) = SOHeatCapacity / ( 2. * DelTime ) + CpDry * xy_SurfTempTransCoef(i,j) + xyra_DelRadLFlux(i,j,0,0)
            xyaa_SurfMtx(i,j,0, 1) = - CpDry * xyr_Exner(i,j,0) / xyz_Exner(i,j,1) * xy_SurfTempTransCoef(i,j) + xyra_DelRadLFlux(i,j,0,1)
          else
            ! open ocean
            xyaa_SurfMtx(i,j,0,-1) = 0.0d0
            xyaa_SurfMtx(i,j,0, 0) = 1.0d0
            xyaa_SurfMtx(i,j,0, 1) = 0.0d0
          end if
        end if
      end do
    end do
    do j = 1, jmax
      do i = 0, imax-1
        if ( xy_SurfCond(i,j) >= 1 ) then
          ! land
          xy_SurfRH(i,j) = - xyr_RadSFlux(i,j,0) - xyr_RadLFlux(i,j,0) - xyr_HeatFlux(i,j,0) - LatentHeat * xyrf_QMixFlux(i,j,0,IndexH2OVap) + xyr_SoilHeatFlux(i,j,0)
        else
          ! ocean
          if ( xy_SeaIceConc(i,j) > SeaIceThreshold ) then
            ! sea ice
            xy_SurfRH(i,j) = - xyr_RadSFlux(i,j,0) - xyr_RadLFlux(i,j,0) - xyr_HeatFlux(i,j,0) - LatentHeat * xyrf_QMixFlux(i,j,0,IndexH2OVap) - SeaIceThermCondCoef * ( xy_SurfTemp(i,j) - TempBelowSeaIce ) / SeaIceThickness
          else if ( FlagPhyImpSoilModelSO ) then
            ! mixed layer ocean
            xy_SurfRH(i,j) = - xyr_RadSFlux(i,j,0) - xyr_RadLFlux(i,j,0) - xyr_HeatFlux(i,j,0) - LatentHeat * xyrf_QMixFlux(i,j,0,IndexH2OVap) !&
!!$              & + xy_DeepSubSurfHeatFlux(i,j)
          else
            ! open ocean
            xy_SurfRH(i,j) = 0.0d0
          end if
        end if
      end do
    end do
    ! 東西風速, 南北風速の計算
    ! Calculate eastward and northward wind
    !
    xyza_UVLUMtx = xyza_UVMtx
    call PhyImplLUDecomp3( xyza_UVLUMtx, imax * jmax, kmax ) ! (in)
    do k = 1, kmax
      xyz_DUDt(:,:,k) = - ( xyr_MomFluxX(:,:,k) - xyr_MomFluxX(:,:,k-1) )
      xyz_DVDt(:,:,k) = - ( xyr_MomFluxY(:,:,k) - xyr_MomFluxY(:,:,k-1) )
    end do
    call PhyImplLUSolve3( xyz_DUDt, xyza_UVLUMtx, 1, imax * jmax, kmax ) ! (in)
    call PhyImplLUSolve3( xyz_DVDt, xyza_UVLUMtx, 1, imax * jmax, kmax ) ! (in)
    do k = 1, kmax
      xyz_DUDt(:,:,k) = xyz_DUDt(:,:,k) / ( 2. * DelTime )
      xyz_DVDt(:,:,k) = xyz_DVDt(:,:,k) / ( 2. * DelTime )
    end do
    ! 温度と比湿の計算
    ! Calculate temperature and specific humidity
    !
    do l = -1, 1
      do k = 1, kslmax
        xyaa_TempSoilTempLUMtx(:,:,-k,-l) = xyaa_SoilTempMtx(:,:,k,l)
      end do
      k = 0
      xyaa_TempSoilTempLUMtx(:,:, k, l) = xyaa_SurfMtx(:,:,0,l)
      do k = 1, kmax
        xyaa_TempSoilTempLUMtx(:,:, k, l) = xyra_TempMtx(:,:,k,l)
      end do
    end do
    call PhyImplLUDecomp3( xyaa_TempSoilTempLUMtx, imax * jmax, kmax + 1 + kslmax )
    do k = 1, kslmax
      xya_DelTempSoilTempLUVec(:,:,-k) = - ( xyr_SoilHeatFlux(:,:,k) - xyr_SoilHeatFlux(:,:,k-1) )
    end do
    k = 0
    xya_DelTempSoilTempLUVec(:,:,0) = xy_SurfRH(:,:)
    do k = 1, kmax
      xya_DelTempSoilTempLUVec(:,:,k) = - ( xyr_HeatFlux(:,:,k) - xyr_HeatFlux(:,:,k-1) )
    end do
    call PhyImplLUSolve3( xya_DelTempSoilTempLUVec, xyaa_TempSoilTempLUMtx, 1, imax * jmax , kmax + 1 + kslmax )
    do k = 1, kslmax
      do j = 1, jmax
        do i = 0, imax-1
          if ( xy_SurfCond(i,j) >= 1 ) then
            xyz_DSoilTempDt(i,j,k) = xya_DelTempSoilTempLUVec(i,j,-k) / ( 2. * DelTime )
          else
            xyz_DSoilTempDt(i,j,k) = 0.0d0
          end if
        end do
      end do
    end do
    do j = 1, jmax
      do i = 0, imax-1
        if ( xy_SurfCond(i,j) >= 1 ) then
          ! land
          xy_DSurfTempDt(i,j) = xya_DelTempSoilTempLUVec(i,j,0) / ( 2. * DelTime )
        else
          ! ocean
          if ( xy_SeaIceConc(i,j) > SeaIceThreshold ) then
            ! sea ice
            xy_DSurfTempDt(i,j) = xya_DelTempSoilTempLUVec(i,j,0) / ( 2. * DelTime )
          else if ( FlagPhyImpSoilModelSO ) then
            ! mixed layer ocean
            xy_DSurfTempDt(i,j) = xya_DelTempSoilTempLUVec(i,j,0) / ( 2. * DelTime )
          else
            ! open ocean
            xy_DSurfTempDt(i,j) = 0.
          end if
        end if
      end do
    end do
    do k = 1, kmax
      xyz_DTempDt(:,:,k) = xya_DelTempSoilTempLUVec(:,:,k) / ( 2. * DelTime )
    end do
    !
    ! Calculation of tendencies of soil moisture and surface snow amount
    !
    if ( FlagBucketModel ) then
      if ( FlagBucketModelSnow ) then
        ! Evaporation is subtracted from surface snow and soil moisture
        !
        xy_DSurfSnowDt = - xyrf_QMixFlux(:,:,0,IndexH2OVap)
        do j = 1, jmax
          do i = 0, imax-1
            SurfSnowATentative = xy_SurfSnowB(i,j) + xy_DSurfSnowDt(i,j) * 2.0d0 * DelTime
            if ( SurfSnowATentative < 0.0d0 ) then
              xy_DSoilMoistDt(i,j) = SurfSnowATentative / ( 2.0d0 * DelTime )
              xy_DSurfSnowDt (i,j) = - xy_SurfSnowB(i,j) / ( 2.0d0 * DelTime )
            else
              xy_DSoilMoistDt(i,j) = 0.0d0
            end if
          end do
        end do
      else
        ! Evaporation is subtracted from soil moisture
        !
        xy_DSoilMoistDt = - xyrf_QMixFlux(:,:,0,IndexH2OVap)
        xy_DSurfSnowDt  = 0.0d0
      end if
    else
      xy_DSoilMoistDt = 0.0d0
      xy_DSurfSnowDt  = 0.0d0
    end if
    call PhyImplSDHSnowMeltCorrection( xyr_HeatFlux, xyrf_QMixFlux(:,:,:,IndexH2OVap), xyr_SoilHeatFlux, xyr_SoilTempTransCoef, xyr_RadSFlux, xyr_RadLFlux, xy_DeepSubSurfHeatFlux, xy_SurfTemp, xyz_SoilTemp, xy_SurfSnowB, xy_SurfCond, xy_SurfHeatCapacity, xy_SoilHeatCap, xy_SoilHeatDiffCoef, xyra_DelRadLFlux, xyz_Exner, xyr_Exner, xy_SurfTempTransCoef, xyz_DTempDt, xy_DSurfTempDt, xyz_DSoilTempDt, xy_DSoilMoistDt, xy_DSurfSnowDt )
    call PhyImplSDHSeaIceCorrection( xy_SurfCond, xy_SeaIceConc, xy_SurfTemp, xy_DSurfTempDt )
    do l = -1, 1
      do k = 1, kmax
        xyza_QMixLUMtx(:,:,k,l) = xyza_QMixMtx(:,:,k,l)
      end do
    end do
    call PhyImplLUDecomp3( xyza_QMixLUMtx, imax * jmax, kmax )
    do n = 1, ncmax
      do k = 1, kmax
        xyz_DelQMixLUVec(:,:,k) = - ( xyrf_QMixFlux(:,:,k,n) - xyrf_QMixFlux(:,:,k-1,n) )
      end do
      call PhyImplLUSolve3( xyz_DelQMixLUVec, xyza_QMixLUMtx, 1, imax * jmax , kmax )
      do k = 1, kmax
        xyzf_DQMixDt(:,:,k,n) = xyz_DelQMixLUVec(:,:,k) / ( 2. * DelTime )
      end do
    end do
    !#########################################################
!!$    ! code for debug, this will be removed, (Y. O. Takahashi, 2009/04/07)
!!$    i = 1
!!$    j = jmax / 2
!!$    write( 6, * ) &
!!$      & - xyr_RadSFlux(i,j,0),                                                      &
!!$      & - ( xyr_RadLFlux(i,j,0)                                                     &
!!$      &   + xyra_DelRadLFlux(i,j,0,0) * xy_DSurfTempDt(i,j) * ( 2.0d0 * DelTime )   &
!!$      &   + xyra_DelRadLFlux(i,j,0,1) * xyz_DTempDt(i,j,1) * ( 2.0d0 * DelTime ) ), &
!!$      & - ( xyr_HeatFlux(i,j,0)                                                     &
!!$      &   - CpDry * xyr_Exner(i,j,0) * xy_SurfTempTransCoef(i,j)                    &
!!$      &     * ( xyz_DTempDt(i,j,1) / xyz_Exner(i,j,1)                               &
!!$      &       - xy_DSurfTempDt(i,j) / xyr_Exner(i,j,0) ) * ( 2.0d0 * DelTime ) ),   &
!!$      & - LatentHeat                                                                &
!!$!      &   * ( xyr_QVapFlux(i,j,0)                                                   &
!!$!      &     - xy_SurfQVapTransCoef(i,j)                                             &
!!$!      &       * ( xyz_DQVapDt(i,j,1)                                                &
!!$!      &         - xy_SurfDQVapSatDTemp(i,j) * xy_DSurfTempDt(i,j) )                 &
!!$!      &       * ( 2.0d0 * DelTime ) ) !, &
!!$      &   * xyr_QVapFlux(i,j,0) !,                                                    &
!!$!      & + xy_DeepSubSurfHeatFlux(i,j)
!!$
!!$    xy_SurfQVapSat(i,j) =                                                           &
!!$      & - xyr_RadSFlux(i,j,0)                                                       &
!!$      & - ( xyr_RadLFlux(i,j,0)                                                     &
!!$      &   + xyra_DelRadLFlux(i,j,0,0) * xy_DSurfTempDt(i,j) * ( 2.0d0 * DelTime )   &
!!$      &   + xyra_DelRadLFlux(i,j,0,1) * xyz_DTempDt(i,j,1) * ( 2.0d0 * DelTime ) )  &
!!$      & - ( xyr_HeatFlux(i,j,0)                                                     &
!!$      &   - CpDry * xyr_Exner(i,j,0) * xy_SurfTempTransCoef(i,j)                    &
!!$      &     * ( xyz_DTempDt(i,j,1) / xyz_Exner(i,j,1)                               &
!!$      &       - xy_DSurfTempDt(i,j) / xyr_Exner(i,j,0) ) * ( 2.0d0 * DelTime ) )    &
!!$      & - LatentHeat                                                                &
!!$!      &   * ( xyr_QVapFlux(i,j,0)                                                   &
!!$!      &     - xy_SurfQVapTransCoef(i,j)                                             &
!!$!      &       * ( xyz_DQVapDt(i,j,1)                                                &
!!$!      &         - xy_SurfDQVapSatDTemp(i,j) * xy_DSurfTempDt(i,j) )                 &
!!$!      &       * ( 2.0d0 * DelTime ) )
!!$      &   * xyr_QVapFlux(i,j,0)
!!$    write( 6, * ) '# sum ', xy_SurfQVapSat(i,j)
    !#########################################################
    ! 計算時間計測一時停止
    ! Pause measurement of computation time
    !
    call TimesetClockStop( module_name )
  end subroutine PhyImplSDHTendency
          | Variable : | |||
| phy_implicit_sdh_inited = .false. : | logical, save, public 
 | 
| Subroutine : | 
依存モジュールの初期化チェック
Check initialization of dependency modules
  subroutine InitCheck
    !
    ! 依存モジュールの初期化チェック
    !
    ! Check initialization of dependency modules
    ! モジュール引用 ; USE statements
    !
    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_util_inited
    ! 格子点設定
    ! Grid points settings
    !
    use gridset, only: gridset_inited
    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: constants_inited
    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: axesset_inited
    ! 時刻管理
    ! Time control
    !
    use timeset, only: timeset_inited
    ! 実行文 ; Executable statement
    !
    if ( .not. namelist_util_inited ) call MessageNotify( 'E', module_name, '"namelist_util" module is not initialized.' )
    if ( .not. gridset_inited ) call MessageNotify( 'E', module_name, '"gridset" module is not initialized.' )
    if ( .not. constants_inited ) call MessageNotify( 'E', module_name, '"constants" module is not initialized.' )
    if ( .not. axesset_inited ) call MessageNotify( 'E', module_name, '"axesset" module is not initialized.' )
    if ( .not. timeset_inited ) call MessageNotify( 'E', module_name, '"timeset" module is not initialized.' )
  end subroutine InitCheck
          | Subroutine : | 
phy_implicit モジュールの初期化を行います. NAMELIST#phy_implicit_nml の読み込みはこの手続きで行われます.
"phy_implicit" module is initialized. "NAMELIST#phy_implicit_nml" is loaded in this procedure.
This procedure input/output NAMELIST#phy_implicit_sdh_nml .
  subroutine PhyImplInit
    !
    ! phy_implicit モジュールの初期化を行います. 
    ! NAMELIST#phy_implicit_nml の読み込みはこの手続きで行われます. 
    !
    ! "phy_implicit" module is initialized. 
    ! "NAMELIST#phy_implicit_nml" is loaded in this procedure. 
    !
    ! モジュール引用 ; USE statements
    !
    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg, NmlutilAryValid
    ! ファイル入出力補助
    ! File I/O support
    !
    use dc_iounit, only: FileOpen
    ! 種別型パラメタ
    ! Kind type parameter
    !
    use dc_types, only: STDOUT ! 標準出力の装置番号. Unit number of standard output
    ! 文字列操作
    ! Character handling
    !
    use dc_string, only: StoA
    ! 宣言文 ; Declaration statements
    !
    implicit none
    ! 作業変数
    ! Work variables
    !
    integer:: unit_nml        ! NAMELIST ファイルオープン用装置番号. 
                              ! Unit number for NAMELIST file open
    integer:: iostat_nml      ! NAMELIST 読み込み時の IOSTAT. 
                              ! IOSTAT of NAMELIST read
    ! NAMELIST 変数群
    ! NAMELIST group name
    !
    namelist /phy_implicit_sdh_nml/ SOHeatCapacity          ! Slab ocean heat capacity (J m-2 K-1)
          !
          ! デフォルト値については初期化手続 "phy_implicit#PhyImplInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "phy_implicit#PhyImplInit" for the default values. 
          !
    ! 実行文 ; Executable statement
    !
    if ( phy_implicit_sdh_inited ) return
    call InitCheck
    ! デフォルト値の設定
    ! Default values settings
    !
    SOHeatCapacity = 4.187d3 * 1.0d3 * 60.0d0
                         ! 4.187d3 (J (kg K)-1) * 1.0d3 (kg m-3) * 60.0d0 (m)
    ! NAMELIST の読み込み
    ! NAMELIST is input
    !
    if ( trim(namelist_filename) /= '' ) then
      call FileOpen( unit_nml, namelist_filename, mode = 'r' ) ! (in)
      rewind( unit_nml )
      read( unit_nml, nml = phy_implicit_sdh_nml, iostat = iostat_nml )          ! (out)
      close( unit_nml )
      call NmlutilMsg( iostat_nml, module_name ) ! (in)
    end if
    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, '  SOHeatCapacity = %f', d = (/ SOHeatCapacity /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )
    phy_implicit_sdh_inited = .true.
  end subroutine PhyImplInit
          | Subroutine : | |||
| xy_SurfCond(0:imax-1, 1:jmax) : | integer , intent(in ) 
 | ||
| xy_SeaIceConc(0:imax-1,1:jmax) : | real(DP), intent(in ) 
 | ||
| xy_SurfTemp(0:imax-1, 1:jmax) : | real(DP), intent(in ) 
 | ||
| xy_DSurfTempDt(0:imax-1, 1:jmax) : | real(DP), intent(inout) 
 | 
融雪による時間変化率の修正を行います.
Correction of tendencies due to melt of snow.
  subroutine PhyImplSDHSeaIceCorrection( xy_SurfCond, xy_SeaIceConc, xy_SurfTemp, xy_DSurfTempDt )
    !
    ! 融雪による時間変化率の修正を行います. 
    !
    ! Correction of tendencies due to melt of snow. 
    !
    ! モジュール引用 ; USE statements
    !
    ! 雪と海氷の定数の設定
    ! Setting constants of snow and sea ice
    !
    use constants_snowseaice, only: TempCondWater, SeaIceThermCondCoef, SeaIceThreshold
    ! 時刻管理
    ! Time control
    !
    use timeset, only: DelTime, TimeN, TimesetClockStart, TimesetClockStop
    ! ヒストリデータ出力
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoPut
    ! バケツモデル
    ! bucket model
    !
    use Bucket_Model, only: FlagBucketModel, FlagBucketModelSnow
    ! 宣言文 ; Declaration statements
    !
    implicit none
    integer , intent(in   ):: xy_SurfCond (0:imax-1, 1:jmax)
                              ! 地表状態. 
                              ! Surface condition
    real(DP), intent(in   ):: xy_SeaIceConc(0:imax-1,1:jmax)
                              ! 海氷密度 (0 <= xy_SeaIceConc <= 1)
                              ! Sea ice concentration (0 <= xy_SeaIceConc <= 1)
    real(DP), intent(in   ):: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! 地表面温度. 
                              ! Surface temperature
    real(DP), intent(inout):: xy_DSurfTempDt (0:imax-1, 1:jmax)
                              ! 地表面温度変化率 (K s-1)
                              ! Surface temperature tendency (K s-1)
    ! 作業変数
    ! Work variables
    !
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude
    ! 実行文 ; Executable statement
    !
!!$    ! 計算時間計測開始
!!$    ! Start measurement of computation time
!!$    !
!!$    call TimesetClockStart( module_name )
    ! 初期化
    ! Initialization
    !
    if ( .not. phy_implicit_sdh_inited ) call PhyImplInit
    !
    ! check flag of snow melt
    !
    if ( ( .not. FlagBucketModel ) .or. ( .not. FlagBucketModelSnow ) ) return
    do j = 1, jmax
      do i = 0, imax-1
        if ( ( xy_SurfCond  (i,j) == 0               ) .and. ( xy_SeaIceConc(i,j) >  SeaIceThreshold ) .and. ( xy_SurfTemp(i,j) + xy_DSurfTempDt(i,j) * DelTime > TempCondWater ) ) then
          xy_DSurfTempDt(i,j) = ( TempCondWater - xy_SurfTemp(i,j) ) / DelTime
        end if
      end do
    end do
!!$    ! 計算時間計測一時停止
!!$    ! Pause measurement of computation time
!!$    !
!!$    call TimesetClockStop( module_name )
  end subroutine PhyImplSDHSeaIceCorrection
          | Subroutine : | |||
| xyr_HeatFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_QVapFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_SoilHeatFlux(0:imax-1, 1:jmax, 0:kslmax) : | real(DP), intent(in) 
 | ||
| xyr_SoilTempTransCoef(0:imax-1, 1:jmax, 0:kslmax) : | real(DP), intent(in) 
 | ||
| xyr_RadSFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_RadLFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xy_DeepSubSurfHeatFlux(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfTemp(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xyz_SoilTemp(0:imax-1, 1:jmax, 1:kslmax) : | real(DP), intent(in) 
 | ||
| xy_SurfSnowB(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfCond(0:imax-1, 1:jmax) : | integer, intent(in) 
 | ||
| xy_SurfHeatCapacity(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SoilHeatCap(0:imax-1, 1:jmax) : | real(DP), intent(in ) 
 | ||
| xy_SoilHeatDiffCoef(0:imax-1, 1:jmax) : | real(DP), intent(in ) 
 | ||
| xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1) : | real(DP), intent(in) 
 | ||
| xyz_Exner(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyr_Exner(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xy_SurfTempTransCoef(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in ) 
 | ||
| xy_DSurfTempDt(0:imax-1, 1:jmax) : | real(DP), intent(inout) 
 | ||
| xyz_DSoilTempDt(0:imax-1, 1:jmax, 1:kslmax) : | real(DP), intent(inout) 
 | ||
| xy_DSoilMoistDt(0:imax-1, 1:jmax) : | real(DP), intent(inout) 
 | ||
| xy_DSurfSnowDt(0:imax-1, 1:jmax) : | real(DP), intent(inout) 
 | 
融雪による時間変化率の修正を行います.
Correction of tendencies due to melt of snow.
  subroutine PhyImplSDHSnowMeltCorrection( xyr_HeatFlux, xyr_QVapFlux, xyr_SoilHeatFlux, xyr_SoilTempTransCoef, xyr_RadSFlux, xyr_RadLFlux, xy_DeepSubSurfHeatFlux, xy_SurfTemp, xyz_SoilTemp, xy_SurfSnowB, xy_SurfCond, xy_SurfHeatCapacity, xy_SoilHeatCap, xy_SoilHeatDiffCoef, xyra_DelRadLFlux, xyz_Exner, xyr_Exner, xy_SurfTempTransCoef, xyz_DTempDt, xy_DSurfTempDt, xyz_DSoilTempDt, xy_DSoilMoistDt, xy_DSurfSnowDt )
    !
    ! 融雪による時間変化率の修正を行います. 
    !
    ! Correction of tendencies due to melt of snow. 
    !
    ! モジュール引用 ; USE statements
    !
    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: r_SSDepth, z_SSDepth         ! subsurface grid at midpoint of layer
    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: CpDry, LatentHeat, LatentHeatFusion
                              ! $ L $ [J kg-1] . 
                              ! 融解の潜熱. 
                              ! Latent heat of fusion
    ! 雪と海氷の定数の設定
    ! Setting constants of snow and sea ice
    !
    use constants_snowseaice, only: TempCondWater
    ! 時刻管理
    ! Time control
    !
    use timeset, only: DelTime, TimeN, TimesetClockStart, TimesetClockStop
    ! ヒストリデータ出力
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoPut
    ! バケツモデル
    ! bucket model
    !
    use Bucket_Model, only: FlagBucketModel, FlagBucketModelSnow
    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xyr_HeatFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 熱フラックス. 
                              ! Heat flux
    real(DP), intent(in):: xyr_QVapFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 比湿フラックス. 
                              ! Specific humidity flux
    real(DP), intent(in):: xyr_SoilHeatFlux (0:imax-1, 1:jmax, 0:kslmax)
                              ! 土壌中の熱フラックス (W m-2)
                              ! Heat flux in sub-surface soil (W m-2)
    real(DP), intent(in):: xyr_SoilTempTransCoef (0:imax-1, 1:jmax, 0:kslmax)
                              ! 輸送係数:土壌温度.
                              ! Transfer coefficient: soil temperature
    real(DP), intent(in):: xyr_RadSFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 短波 (日射) フラックス. 
                              ! Shortwave (insolation) flux
    real(DP), intent(in):: xyr_RadLFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 長波フラックス. 
                              ! Longwave flux
    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_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.
    integer, intent(in):: xy_SurfCond (0:imax-1, 1:jmax)
                              ! 地表状態. 
                              ! Surface condition
    real(DP), intent(in):: xy_SurfHeatCapacity (0:imax-1, 1:jmax)
                              ! 地表熱容量. 
                              ! Surface heat capacity
    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):: xyra_DelRadLFlux (0:imax-1, 1:jmax, 0:kmax, 0:1)
                              ! 長波地表温度変化. 
                              ! Surface temperature tendency with longwave
    real(DP), intent(in):: xyz_Exner (0:imax-1, 1:jmax, 1:kmax)
                              ! Exner 関数 (整数レベル). 
                              ! Exner function (full level)
    real(DP), intent(in):: xyr_Exner (0:imax-1, 1:jmax, 0:kmax)
                              ! Exner 関数 (半整数レベル). 
                              ! Exner function (half level)
    real(DP), intent(in):: xy_SurfTempTransCoef (0:imax-1, 1:jmax)
                              ! 輸送係数:温度. 
                              ! Transfer coefficient: temperature
    real(DP), intent(in ):: xyz_DTempDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{T}{t} $ . 温度変化. 
                              ! Temperature tendency
    real(DP), intent(inout):: xy_DSurfTempDt (0:imax-1, 1:jmax)
                              ! 地表面温度変化率 (K s-1)
                              ! Surface temperature tendency (K s-1)
    real(DP), intent(inout):: xyz_DSoilTempDt (0:imax-1, 1:jmax, 1:kslmax)
                              ! $ \DP{Tg}{t} $ . 土壌温度変化 (K s-1)
                              ! Temperature tendency (K s-1)
    real(DP), intent(inout):: xy_DSoilMoistDt (0:imax-1, 1:jmax)
                              ! 土壌温度時間変化率 (kg m-2 s-1)
                              ! Soil temperature tendency (kg m-2 s-1)
    real(DP), intent(inout):: xy_DSurfSnowDt (0:imax-1, 1:jmax)
                              ! 積雪率時間変化率 (kg m-2 s-1)
                              ! Surface snow amount tendency (kg m-2 s-1)
    ! 作業変数
    ! Work variables
    !
    real(DP):: LatentHeatFluxByMelt
    real(DP):: SenHeatFluxA
    real(DP):: LatHeatFluxA
    real(DP):: CondHeatFluxA
    real(DP):: ValueAlpha
    real(DP):: SurfTempATentative
    real(DP):: SoilTempATentative
    real(DP):: SurfSnowATentative
    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
    ! 実行文 ; Executable statement
    !
!!$    ! 計算時間計測開始
!!$    ! Start measurement of computation time
!!$    !
!!$    call TimesetClockStart( module_name )
    ! 初期化
    ! Initialization
    !
    if ( .not. phy_implicit_sdh_inited ) call PhyImplInit
    !
    ! check flag of snow melt
    !
    if ( ( .not. FlagBucketModel ) .or. ( .not. FlagBucketModelSnow ) ) return
    if ( kslmax == 0 ) then
      do j = 1, jmax
        do i = 0, imax-1
          SurfSnowATentative = xy_SurfSnowB(i,j) + xy_DSurfSnowDt(i,j) * 2.0d0 * DelTime
          SurfTempATentative = xy_SurfTemp(i,j) + xy_DSurfTempDt(i,j) * 2.0d0 * DelTime
          if ( ( xy_SurfCond (i,j)  >= 1             ) .and. ( SurfSnowATentative >  0.0d0         ) .and. ( SurfTempATentative >  TempCondWater ) ) then
            ! if all snow is melting, 
            LatentHeatFluxByMelt = SurfSnowATentative * LatentHeatFusion / ( 2.0d0 * DelTime )
            SenHeatFluxA = xyr_HeatFlux(i,j,0) - CpDry * xyr_Exner(i,j,0) * xy_SurfTempTransCoef(i,j) * ( xyz_DTempDt(i,j,1) / xyz_Exner(i,j,1) - xy_DSurfTempDt(i,j) / xyr_Exner(i,j,0) ) * ( 2.0d0 * DelTime )
            ! NOTICE: LatentHeatFlux^{n+1} = LatentHeatFlux^{n-1} due to mass 
            !         conservation
            LatHeatFluxA = LatentHeat * xyr_QVapFlux(i,j,0)
            CondHeatFluxA = xy_DeepSubSurfHeatFlux(i,j)
            ValueAlpha = xyr_RadSFlux(i,j,0) + xyr_RadLFlux(i,j,0) - xyra_DelRadLFlux(i,j,0,0) * xy_SurfTemp(i,j) + xyra_DelRadLFlux(i,j,0,1) * xyz_DTempDt(i,j,1) * ( 2.0d0 * DelTime ) + SenHeatFluxA + LatHeatFluxA + LatentHeatFluxByMelt
            SurfTempATentative = xy_SurfHeatCapacity(i,j) / ( 2.0d0 * DelTime ) * xy_SurfTemp(i,j) - ValueAlpha + CondHeatFluxA
            SurfTempATentative = SurfTempATentative / ( xy_SurfHeatCapacity(i,j) / ( 2.0d0 * DelTime ) + xyra_DelRadLFlux(i,j,0,0) )
            if ( SurfTempATentative >= TempCondWater ) then
              xy_DSurfTempDt(i,j) = ( SurfTempATentative - xy_SurfTemp(i,j) ) / ( 2.0d0 * DelTime )
!!$              xy_SoilMoistA(i,j) = &
!!$                & xy_SoilMoistA(i,j) &
!!$                & + LatentHeatFluxByMelt * ( 2.0d0 * DelTime ) / LatentHeatFusion
!!$              xy_SurfSnowA(i,j) = &
!!$                & xy_SurfSnowA(i,j) &
!!$                & - LatentHeatFluxByMelt * ( 2.0d0 * DelTime ) / LatentHeatFusion
              xy_DSoilMoistDt(i,j) = xy_DSoilMoistDt(i,j) + LatentHeatFluxByMelt / LatentHeatFusion
              xy_DSurfSnowDt(i,j) = xy_DSurfSnowDt (i,j) - LatentHeatFluxByMelt / LatentHeatFusion
            else
              ! if part of snow is melting, 
              SurfTempATentative = TempCondWater
              ValueAlpha = xyr_RadSFlux(i,j,0) + xyr_RadLFlux(i,j,0) + xyra_DelRadLFlux(i,j,0,0) * SurfTempATentative - xyra_DelRadLFlux(i,j,0,0) * xy_SurfTemp(i,j) + xyra_DelRadLFlux(i,j,0,1) * xyz_DTempDt(i,j,1) * ( 2.0d0 * DelTime ) + SenHeatFluxA + LatHeatFluxA - CondHeatFluxA
              LatentHeatFluxByMelt = xy_SurfHeatCapacity(i,j) * ( SurfTempATentative - xy_SurfTemp(i,j) ) / ( 2.0d0 * DelTime ) - ValueAlpha
              xy_DSurfTempDt(i,j) = ( SurfTempATentative - xy_SurfTemp(i,j) ) / ( 2.0d0 * DelTime )
!!$              xy_SoilMoistA(i,j) = &
!!$                & xy_SoilMoistA(i,j) &
!!$                & + LatentHeatFluxByMelt * ( 2.0d0 * DelTime ) / LatentHeatFusion
!!$              xy_SurfSnowA(i,j) = &
!!$                & xy_SurfSnowA(i,j) &
!!$                & - LatentHeatFluxByMelt * ( 2.0d0 * DelTime ) / LatentHeatFusion
              xy_DSoilMoistDt(i,j) = xy_DSoilMoistDt(i,j) + LatentHeatFluxByMelt / LatentHeatFusion
              xy_DSurfSnowDt(i,j) = xy_DSurfSnowDt (i,j) - LatentHeatFluxByMelt / LatentHeatFusion
            end if
            SurfSnowATentative = xy_SurfSnowB(i,j) + xy_DSurfSnowDt(i,j) * 2.0d0 * DelTime
            if ( SurfSnowATentative < 0.0d0 ) then
              xy_DSurfSnowDt(i,j) = - xy_SurfSnowB(i,j) / ( 2.0d0 * DelTime )
            end if
          end if
        end do
      end do
    else
      do j = 1, jmax
        do i = 0, imax-1
          SurfSnowATentative = xy_SurfSnowB(i,j) + xy_DSurfSnowDt(i,j) * 2.0d0 * DelTime
          SoilTempATentative = xyz_SoilTemp(i,j,1) + xyz_DSoilTempDt(i,j,1) * 2.0d0 * DelTime
          if ( ( xy_SurfCond (i,j)  >= 1            ) .and. ( SurfSnowATentative >  0.0d0        ) .and. ( SoilTempATentative > TempCondWater ) ) then
            ! if all snow is melting, 
            LatentHeatFluxByMelt = SurfSnowATentative * LatentHeatFusion / ( 2.0d0 * DelTime )
            SenHeatFluxA = xyr_HeatFlux(i,j,0) - CpDry * xyr_Exner(i,j,0) * xy_SurfTempTransCoef(i,j) * ( xyz_DTempDt(i,j,1) / xyz_Exner(i,j,1) - xy_DSurfTempDt(i,j) / xyr_Exner(i,j,0) ) * ( 2.0d0 * DelTime )
            ! NOTICE: LatentHeatFlux^{n+1} = LatentHeatFlux^{n-1} due to mass conservation
            LatHeatFluxA = LatentHeat * xyr_QVapFlux(i,j,0)
            CondHeatFluxA = xyr_SoilHeatFlux(i,j,1) - xyr_SoilTempTransCoef(i,j,1) * ( xyz_DSoilTempDt(i,j,2) - xyz_DSoilTempDt(i,j,1) ) * ( 2.0d0 * DelTime )
            ValueAlpha = xyr_RadSFlux(i,j,0) + xyr_RadLFlux(i,j,0) - xyra_DelRadLFlux(i,j,0,0) * xy_SurfTemp(i,j) + xyra_DelRadLFlux(i,j,0,1) * xyz_DTempDt(i,j,1) * ( 2.0d0 * DelTime ) + SenHeatFluxA + LatHeatFluxA + LatentHeatFluxByMelt
            ValueAlpha = ValueAlpha * ( r_SSDepth(0) - z_SSDepth(1) ) / xy_SoilHeatDiffCoef(i,j)
            SurfTempATentative = - ( xy_SoilHeatCap(i,j) / ( 2.0d0 * DelTime ) + xy_SoilHeatDiffCoef(i,j) / ( ( r_SSDepth(0) - r_SSDepth(1) ) * ( r_SSDepth(0) - z_SSDepth(1) ) ) ) * ValueAlpha + xy_SoilHeatCap(i,j) / ( 2.0d0 * DelTime ) * xyz_SoilTemp(i,j,1) + CondHeatFluxA / ( r_SSDepth(0) - r_SSDepth(1) )
            SurfTempATentative = SurfTempATentative / ( xy_SoilHeatCap(i,j) / ( 2.0d0 * DelTime ) * ( 1.0d0 + ( r_SSDepth(0) - z_SSDepth(1) ) / xy_SoilHeatDiffCoef(i,j) * xyra_DelRadLFlux(i,j,0,0) ) + xyra_DelRadLFlux(i,j,0,0) / ( r_SSDepth(0) - r_SSDepth(1) ) )
            SoilTempATentative = ( 1.0d0 + ( r_SSDepth(0) - z_SSDepth(1) ) / xy_SoilHeatDiffCoef(i,j) * xyra_DelRadLFlux(i,j,0,0) ) * SurfTempATentative + ValueAlpha
            if ( SoilTempATentative >= TempCondWater ) then
              xyz_DSoilTempDt(i,j,1) = ( SoilTempATentative - xyz_SoilTemp(i,j,1) ) / ( 2.0d0 * DelTime )
              xy_DSurfTempDt(i,j) = ( SurfTempATentative - xy_SurfTemp(i,j) ) / ( 2.0d0 * DelTime )
!!$              xy_SoilMoistA(i,j) = &
!!$                & xy_SoilMoistA(i,j) &
!!$                & + LatentHeatFluxByMelt * ( 2.0d0 * DelTime ) / LatentHeatFusion
!!$              xy_SurfSnowA(i,j) = &
!!$                & xy_SurfSnowA(i,j) &
!!$                & - LatentHeatFluxByMelt * ( 2.0d0 * DelTime ) / LatentHeatFusion
              xy_DSoilMoistDt(i,j) = xy_DSoilMoistDt(i,j) + LatentHeatFluxByMelt / LatentHeatFusion
              xy_DSurfSnowDt(i,j) = xy_DSurfSnowDt (i,j) - LatentHeatFluxByMelt / LatentHeatFusion
            else
              ! if part of snow is melting, 
              SoilTempATentative = TempCondWater
              SurfTempATentative = ( r_SSDepth(0) - r_SSDepth(1) ) * ( r_SSDepth(0) - z_SSDepth(1) ) / xy_SoilHeatDiffCoef(i,j) * ( ( xy_SoilHeatCap(i,j) / ( 2.0d0 * DelTime ) + xy_SoilHeatDiffCoef(i,j) / ( ( r_SSDepth(0) - r_SSDepth(1) ) * ( r_SSDepth(0) - z_SSDepth(1) ) ) ) * SoilTempATentative - xy_SoilHeatCap(i,j) / ( 2.0d0 * DelTime ) * xyz_SoilTemp(i,j,1) - CondHeatFluxA / ( r_SSDepth(0) - r_SSDepth(1) ) )
              LatentHeatFluxByMelt = - xy_SoilHeatDiffCoef(i,j) * ( SurfTempATentative - SoilTempATentative ) / ( r_SSDepth(0) - z_SSDepth(1) ) - xyr_RadSFlux(i,j,0) - ( xyr_RadLFlux(i,j,0) + xyra_DelRadLFlux(i,j,0,0) * ( SurfTempATentative - xy_SurfTemp(i,j) ) + xyra_DelRadLFlux(i,j,0,1) * xyz_DTempDt(i,j,1) * ( 2.0d0 * DelTime ) ) - SenHeatFluxA - LatHeatFluxA
              xyz_DSoilTempDt(i,j,1) = ( SoilTempATentative - xyz_SoilTemp(i,j,1) ) / ( 2.0d0 * DelTime )
              xy_DSurfTempDt(i,j) = ( SurfTempATentative - xy_SurfTemp(i,j) ) / ( 2.0d0 * DelTime )
!!$              xy_SoilMoistA(i,j) = &
!!$                & xy_SoilMoistA(i,j) &
!!$                & + LatentHeatFluxByMelt * ( 2.0d0 * DelTime ) / LatentHeatFusion
!!$              xy_SurfSnowA(i,j) = &
!!$                & xy_SurfSnowA(i,j) &
!!$                & - LatentHeatFluxByMelt * ( 2.0d0 * DelTime ) / LatentHeatFusion
              xy_DSoilMoistDt(i,j) = xy_DSoilMoistDt(i,j) + LatentHeatFluxByMelt / LatentHeatFusion
              xy_DSurfSnowDt(i,j) = xy_DSurfSnowDt (i,j) - LatentHeatFluxByMelt / LatentHeatFusion
            end if
            SurfSnowATentative = xy_SurfSnowB(i,j) + xy_DSurfSnowDt(i,j) * 2.0d0 * DelTime
            if ( SurfSnowATentative < 0.0d0 ) then
              xy_DSurfSnowDt(i,j) = - xy_SurfSnowB(i,j) / ( 2.0d0 * DelTime )
            end if
          end if
        end do
      end do
    end if
!!$    ! 計算時間計測一時停止
!!$    ! Pause measurement of computation time
!!$    !
!!$    call TimesetClockStop( module_name )
  end subroutine PhyImplSDHSnowMeltCorrection
          | Constant : | |||
| module_name = ‘phy_implicit_sdh‘ : | character(*), parameter 
 | 
| Constant : | |||
| version = ’$Name: dcpam5-20110327 $’ // ’$Id: phy_implicit_sdh.f90,v 1.3 2010-09-28 22:44:23 yot Exp $’ : | character(*), parameter 
 |