| Class | cumulus_adjust |
| In: |
cumulus/cumulus_adjust.f90
|
Note that Japanese and English are described in parallel.
対流調節スキームにより, 温度と比湿を調節します. 飽和比湿の計算には Nakajima et al. (1992) を用いています. 詳しくは saturate_nha1992 を参照してください.
Adjust temperature and specific humidity by convective adjustment scheme. Nakajima et al. (1992) is used for calculation of saturation specific humidity. For details, see "saturate_nha1992".
| Cumulus : | 温度と比湿の調節 |
| ———— : | ———— |
| Cumulus : | Adjust temperature and specific humidity |
| Subroutine : | |||
| xyz_Temp(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(inout)
| ||
| xyz_QVap(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(inout)
| ||
| xyz_Press(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
| ||
| xyr_Press(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in)
|
対流調節スキームにより, 温度と比湿を調節します.
Adjust temperature and specific humidity by convective adjustment scheme.
subroutine Cumulus( xyz_Temp, xyz_QVap, xyz_Press, xyr_Press )
!
! 対流調節スキームにより, 温度と比湿を調節します.
!
! Adjust temperature and specific humidity by
! convective adjustment scheme.
!
! モジュール引用 ; USE statements
!
! 物理定数設定
! Physical constants settings
!
use constants, only: GasRUniv, Grav, GasRDry, CpDry, GasRWet, LatentHeat, EpsV
! $ \epsilon_v $ .
! 水蒸気分子量比.
! Molecular weight of water vapor
! 時刻管理
! Time control
!
use timeset, only: DelTime, TimeN, TimesetClockStart, TimesetClockStop
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoPut
! 宣言文 ; Declaration statements
!
implicit none
real(DP), intent(inout):: xyz_Temp (0:imax-1, 1:jmax, 1:kmax)
! $ T $ . 温度. Temperature
real(DP), intent(inout):: xyz_QVap (0:imax-1, 1:jmax, 1:kmax)
! $ q $ . 比湿. Specific humidity
real(DP), intent(in):: xyz_Press (0:imax-1, 1:jmax, 1:kmax)
! $ p $ . 気圧 (整数レベル).
! Air pressure (full level)
real(DP), intent(in):: xyr_Press (0:imax-1, 1:jmax, 0:kmax)
! $ \hat{p} $ . 気圧 (半整数レベル).
! Air pressure (half level)
! 作業変数
! Work variables
!
real(DP):: xy_Rain (0:imax-1, 1:jmax)
! 降水量.
! Precipitation
real(DP):: xyz_DTempDt (0:imax-1, 1:jmax, 1:kmax)
! 温度変化率.
! Temperature tendency
real(DP):: xyz_DQVapDt (0:imax-1, 1:jmax, 1:kmax)
! 比湿変化率.
! Specific humidity tendency
real(DP):: xyz_QVapB (0:imax-1, 1:jmax, 1:kmax)
! 調節前の比湿.
! Specific humidity before adjust.
real(DP):: xyz_TempB (0:imax-1, 1:jmax, 1:kmax)
! 調節前の温度.
! Temperature before adjust.
logical:: xy_Adjust (0:imax-1, 1:jmax)
! 今回調節されたか否か?.
! Whether it was adjusted this time or not?
logical:: xy_AdjustB (0:imax-1, 1:jmax)
! 前回調節されたか否か?.
! Whether it was adjusted last time or not?
real(DP):: xyz_DPressDz (0:imax-1, 1:jmax, 1:kmax)
! $ \DD{p}{z} $
!
real(DP):: xyz_QVapSat (0:imax-1, 1:jmax, 1:kmax)
! 飽和比湿.
! Saturation specific humidity.
real(DP):: xyz_DDPressDDPress (0:imax-1, 1:jmax, 1:kmax)
! $ \DD{p_{k}}{p_{k-1}} $
!
real(DP):: xyz_DPFact (0:imax-1, 1:jmax, 1:kmax)
! $ (R / C_p)
! \frac{p_{k-1} - p_{k}}{2 p_{k-1/2}} $ .
!
! ファクター.
! Factor
real(DP):: TempSat ! $ S_t $ .
! 飽和温度.
! Saturation temperature
real(DP):: DelTempSat
! 調節による飽和温度の変化量.
! Saturation temperature variation by adjustment
real(DP):: DelQVap
! 調節による比湿の変化量.
! Specific humidity variation by adjustment
real(DP):: DelTempUpper
! 調節による温度 (k) の変化量.
! Temperature (k) variation by adjustment
real(DP):: DelTempLower
! 調節による温度 (k-1) の変化量.
! Temperature (k-1) variation by adjustment
real(DP):: DQVapSatDTempUpper
! $ \DD{q^{*}} (k)}{T} $
real(DP):: DQVapSatDTempLower
! $ \DD{q^{*}} (k-1)}{T} $
real(DP):: DHDTempUpper
! $ 1 + \gamma_{k} =
! 1 + \frac{L}{C_p} \DP{q^{*}}{T}_{k} $
real(DP):: DHDTempLower
! $ 1 + \gamma_{k-1} =
! 1 + \frac{L}{C_p} \DP{q^{*}}{T}_{k-1} $
logical:: Adjust
! 今回全領域において一度でも調節されたか否か?.
! Whether it was adjusted even once in global
! this time or not?
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:: itr ! イテレーション方向に回る DO ループ用作業変数
! Work variables for DO loop in iteration direction
! 実行文 ; Executable statement
!
! 計算時間計測開始
! Start measurement of computation time
!
call TimesetClockStart( module_name )
! 初期化
! Initialization
!
if ( .not. cumulus_adjust_inited ) call CumAdjInit
! 調節前 "QVap", "Temp" の保存
! Store "QVap", "Temp" before adjustment
!
xyz_QVapB = xyz_QVap
xyz_TempB = xyz_Temp
! ファクターの計算
! Calculate factor
!
do k = 1, kmax
xyz_DPressDz(:,:,k) = xyr_Press(:,:,k-1) - xyr_Press(:,:,k)
end do
! 飽和比湿計算
! Calculate saturation specific humidity
!
! Nakajima et al. (1992) を用いた飽和比湿の計算
! Calculate saturation specific humidity with Nakajima et al. (1992)
!
xyz_QVapSat = EpsV * ( P0Nha92 / xyz_Press ) * exp ( - LatHeatNha92 / ( GasRUniv * xyz_Temp ) )
!!$ call CalcQVapSat( phy_cumad % phy_sat, & ! (in)
!!$ & xyz_Temp = xyz_Temp, & ! (in)
!!$ & xyz_Press = xyz_Press, & ! (in)
!!$ & xyz_QVapSat = xyz_QVapSat, & ! (out)
!!$ & err = err ) ! (out)
!!$ ! クラウジウスクラペイロンの式より飽和比湿計算
!!$ ! * 273 K の時の飽和水蒸気圧を ES0 (= 611 Pa) としている
!!$ ! * 浅井 冨男, 武田 喬男, 木村 竜治, 1981:
!!$ ! 大気科学講座 2 雲や降水を伴う大気, 東京大学出版会, 249pp.
!!$ ! Calculate saturation specific humidity with Clausius Clapeyron equation
!!$ ! * Saturation vapor pressure is ES0 (= 611 Pa) at 273 K
!!$ !
!!$ xyz_QVapSat = EpsV * ES0 &
!!$ & * exp( EL / RVap * ( 1.0_DP / 273.0_DP - 1.0_DP / xyz_Temp ) ) &
!!$ & / xyz_Press
xyz_DDPressDDPress(:,:,1) = 0.0_DP
do k = 2, kmax
xyz_DDPressDDPress(:,:,k) = xyz_DPressDz(:,:,k) / xyz_DPressDz(:,:,k-1)
xyz_DPFact(:,:,k) = GasRDry / CpDry * ( xyz_Press(:,:,k-1) - xyz_Press(:,:,k) ) / xyr_Press(:,:,k-1) / 2.0_DP
end do
! 調節
! Adjustment
!
xy_AdjustB = .true.
! イテレーション
! Iteration
!
do itr = 1, ItrtMax
xy_Adjust = .false.
do k = 2, kmax
do j = 1, jmax
do i = 0, imax-1
if ( xy_AdjustB(i,j) ) then
TempSat = xyz_Temp(i,j,k-1) - xyz_Temp(i,j,k) + ( xyz_QVapSat(i,j,k-1) - xyz_QVapSat(i,j,k) ) * LatentHeat / CpDry - xyz_DPFact(i,j,k) * ( xyz_Temp(i,j,k-1) + xyz_Temp(i,j,k) )
! 不安定であるならば
! If it is unstable
!
if ( TempSat > TempSatMax(itr) ) then
! .. かつ, 飽和しているならば
! .. and, if it is saturated
!
if ( ( xyz_QVap(i,j,k) / xyz_QVapSat(i,j,k) >= CrtlRH ) .and. ( xyz_QVap(i,j,k-1) / xyz_QVapSat(i,j,k-1) >= CrtlRH ) ) then
DelQVap = xyz_DPressDz(i,j,k-1) * (xyz_QVap(i,j,k-1) - xyz_QVapSat(i,j,k-1) ) + xyz_DPressDz(i,j,k) * (xyz_QVap(i,j,k) - xyz_QVapSat(i,j,k) )
DQVapSatDTempUpper = xyz_QVapSat(i,j,k) * ( LatHeatNha92 / ( GasRUniv * xyz_Temp(i,j,k)**2 ) )
DQVapSatDTempLower = xyz_QVapSat(i,j,k-1) * ( LatHeatNha92 / ( GasRUniv * xyz_Temp(i,j,k-1)**2 ) )
!!$ call CalcDQVapSatDTemp( phy_cumad % phy_sat, & ! (in)
!!$ & Temp = xyz_Temp(i,j,k), & ! (in)
!!$ & Press = xyz_Press(i,j,k), & ! (in)
!!$ & DQVapSatDTemp = DQVapSatDTempUpper ) ! (out)
!!$
!!$ call CalcDQVapSatDTemp( phy_cumad % phy_sat, & ! (in)
!!$ & Temp = xyz_Temp(i,j,k-1), & ! (in)
!!$ & Press = xyz_Press(i,j,k-1), & ! (in)
!!$ & DQVapSatDTemp = DQVapSatDTempLower ) ! (out)
!!$
!!$ DQvapSatDTempUpper = LatentHeat * xyz_QvapSat(i,j,k) &
!!$ & / ( RVap * xyz_Temp(i,j,k) * xyz_Temp(i,j,k) )
!!$
!!$ DQvapSatDTempLower = LatentHeat * xyz_QvapSat(i,j,k-1) &
!!$ & / ( RVap * xyz_Temp(i,j,k-1) * xyz_Temp(i,j,k-1) )
DHDTempUpper = 1.0_DP + LatentHeat/CpDry * DQVapSatDTempUpper
DHDTempLower = 1.0_DP + LatentHeat/CpDry * DQVapSatDTempLower
DelTempSat = TempSat + ( 1.0_DP - xyz_DPFact(i,j,k) / DHDTempLower ) * LatentHeat/CpDry * DelQVap / xyz_DPressDz(i,j,k-1)
! 温度の調節
! Adjust temperature
!
DelTempUpper = DelTempSat / ( ( 1.0_DP + xyz_DDPressDDPress(i,j,k) ) * DHDTempUpper + xyz_DPFact(i,j,k) * ( 1.0_DP - xyz_DDPressDDPress(i,j,k) * DHDTempUpper / DHDTempLower ) )
DelTempLower = - DHDTempUpper / DHDTempLower * xyz_DDPressDDPress(i,j,k) * DelTempUpper + LatentHeat / CpDry * DelQVap / ( xyz_DPressDz(i,j,k-1) * DHDTempLower )
xyz_Temp(i,j,k) = xyz_Temp(i,j,k) + DelTempUpper
xyz_Temp(i,j,k-1) = xyz_Temp(i,j,k-1) + DelTempLower
! 比湿の調節
! Adjust specific humidity
!
xyz_QVap(i,j,k) = xyz_QVapSat(i,j,k) + DQVapSatDTempUpper * DelTempUpper
xyz_QVap(i,j,k-1) = xyz_QVapSat(i,j,k-1) + DQVapSatDTempLower * DelTempLower
xyz_QVapSat(i,j,k) = xyz_QVap(i,j,k)
xyz_QVapSat(i,j,k-1) = xyz_QVap(i,j,k-1)
! 調節したか否か?
! Whether it was adjusted or not?
!
xy_Adjust(i,j) = .true.
end if
end if
end if
end do
end do
end do
Adjust = .false.
do i = 0, imax-1
do j = 1, jmax
xy_AdjustB(i,j) = xy_Adjust(i,j)
Adjust = Adjust .or. xy_Adjust(i,j)
end do
end do
if ( .not. Adjust ) exit
end do
! 比湿変化率, 温度変化率, 降水量の算出
! Calculate specific humidity tendency, temperature tendency, precipitation
!
xy_Rain = 0.0_DP
xyz_DTempDt = 0.0_DP
xyz_DQVapDt = 0.0_DP
xyz_DQVapDt = xyz_DQVapDt + ( xyz_QVap - xyz_QVapB ) / ( 2.0_DP * DelTime )
xyz_DTempDt = xyz_DTempDt + ( xyz_Temp - xyz_TempB ) / ( 2.0_DP * DelTime )
do k = 1, kmax
xy_Rain = xy_Rain + ( xyz_QVapB(:,:,k) - xyz_QVap(:,:,k) ) * xyz_DPressDz(:,:,k) / Grav * LatentHeat / ( 2.0_DP * DelTime )
end do
! ヒストリデータ出力
! History data output
!
call HistoryAutoPut( TimeN, 'RainCumulus', xy_Rain )
call HistoryAutoPut( TimeN, 'DTempDtCumulus', xyz_DTempDt )
call HistoryAutoPut( TimeN, 'DQVapDtCumulus', xyz_DQVapDt )
! 計算時間計測一時停止
! Pause measurement of computation time
!
call TimesetClockStop( module_name )
end subroutine Cumulus
| Variable : | |||
| cumulus_adjust_inited = .false. : | logical, save, public
|
| Subroutine : |
cumulus_adjust モジュールの初期化を行います. NAMELIST#cumulus_adjust_nml の読み込みはこの手続きで行われます.
"cumulus_adjust" module is initialized. "NAMELIST#cumulus_adjust_nml" is loaded in this procedure.
This procedure input/output NAMELIST#cumulus_adjust_nml .
subroutine CumAdjInit
!
! cumulus_adjust モジュールの初期化を行います.
! NAMELIST#cumulus_adjust_nml の読み込みはこの手続きで行われます.
!
! "cumulus_adjust" module is initialized.
! "NAMELIST#cumulus_adjust_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
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoAddVariable
! 宣言文 ; Declaration statements
!
implicit none
integer:: unit_nml ! NAMELIST ファイルオープン用装置番号.
! Unit number for NAMELIST file open
integer:: iostat_nml ! NAMELIST 読み込み時の IOSTAT.
! IOSTAT of NAMELIST read
! NAMELIST 変数群
! NAMELIST group name
!
namelist /cumulus_adjust_nml/ CrtlRH, ItrtMax, TempSatMax
!
! デフォルト値については初期化手続 "cumulus_adjust#CumAdjInit"
! のソースコードを参照のこと.
!
! Refer to source codes in the initialization procedure
! "cumulus_adjust#CumAdjInit" for the default values.
!
! 実行文 ; Executable statement
!
if ( cumulus_adjust_inited ) return
call InitCheck
! デフォルト値の設定
! Default values settings
!
CrtlRH = 0.990_DP
ItrtMax = 10
TempSatMax(1:ItrtMax) = (/ 0.01_DP, 0.02_DP, 0.02_DP, 0.05_DP, 0.05_DP, 0.10_DP, 0.10_DP, 0.20_DP, 0.20_DP, 0.40_DP /)
! 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 = cumulus_adjust_nml, iostat = iostat_nml ) ! (out)
close( unit_nml )
call NmlutilMsg( iostat_nml, module_name ) ! (in)
!!$ if ( iostat_nml == 0 ) write( STDOUT, nml = cumulus_adjust_nml )
end if
! イテレーション回数, 不安定の許容誤差のチェック
! Check number of iteration, admissible error of unstability
!
call NmlutilAryValid( module_name, TempSatMax, 'TempSatMax', ItrtMax, 'ItrtMax' ) ! (in)
! ヒストリデータ出力のためのへの変数登録
! Register of variables for history data output
!
call HistoryAutoAddVariable( 'RainCumulus', (/ 'lon ', 'lat ', 'time' /), 'precipitation by cumulus scheme', 'W m-2' )
call HistoryAutoAddVariable( 'DTempDtCumulus', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'cumulus condensation heating', 'K s-1' )
call HistoryAutoAddVariable( 'DQVapDtCumulus', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'cumulus condensation moistening', 'kg kg-1 s-1' )
! 印字 ; Print
!
call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
call MessageNotify( 'M', module_name, ' CrtlRH = %f', d = (/ CrtlRH /) )
call MessageNotify( 'M', module_name, ' ItrtMax = %d', i = (/ ItrtMax /) )
call MessageNotify( 'M', module_name, ' TempSatMax = (/ %*r /)', r = real( TempSatMax(1:ItrtMax) ), n = (/ ItrtMax /) )
call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )
cumulus_adjust_inited = .true.
end subroutine CumAdjInit
| 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
| Constant : | |||
| LatHeatNha92 = 43655_DP : | real(DP), parameter
|
| Constant : | |||
| P0Nha92 = 1.4e+11_DP : | real(DP), parameter
|
| Variable : | |||
| TempSatMax(1:MaxNmlArySize) : | real(DP), save
|
| Constant : | |||
| module_name = ‘cumulus_adjust‘ : | character(*), parameter
|
| Constant : | |||
| version = ’$Name: dcpam5-20081109-1 $’ // ’$Id: cumulus_adjust.f90,v 1.5 2008-10-06 16:30:13 morikawa Exp $’ : | character(*), parameter
|