| Class | set_cloud |
| In: |
radiation/set_cloud.f90
|
Note that Japanese and English are described in parallel.
雲の分布を設定.
In this module, the amount of cloud or cloud optical depth are set. This module is under development and is still a preliminary version.
| !$ ! RadiationFluxDennouAGCM : | 放射フラックスの計算 |
| !$ ! ———— : | ———— |
| !$ ! RadiationFluxDennouAGCM : | Calculate radiation flux |
| Subroutine : | |
| xyz_QCloudWater( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(in ) |
| xyz_DQCloudWaterDt( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(inout) |
subroutine SetCloudCloudWaterLossRateInOut( xyz_QCloudWater, xyz_DQCloudWaterDt )
! USE statements
!
! 時刻管理
! Time control
!
use timeset, only: DelTime, TimeN, EndTime, TimesetClockStart, TimesetClockStop
real(DP), intent(in ) :: xyz_QCloudWater ( 0:imax-1, 1:jmax, 1:kmax )
real(DP), intent(inout) :: xyz_DQCloudWaterDt( 0:imax-1, 1:jmax, 1:kmax )
real(DP) :: xyz_QCloudWaterTentative(0:imax-1, 1:jmax, 1:kmax)
! 初期化
! Initialization
!
if ( .not. set_cloud_inited ) call SetCloudInit
! Cloud optical depth
!
if ( FlagCloud ) then
!!$ xyz_DQCloudWaterDt = xyz_DQCloudWaterDt &
!!$ & - xyz_QCloudWater / ( CloudLifeTime + 1.0d-100 )
!!$ ( X_{t+1} - X_{t-1} ) / ( 2 \Delta t ) = Q - X_{t+1} / \tau
!!$
!!$ X_{t+1} / ( 2 \Delta t ) + X_{t+1} / \tau = X_{t-1} / ( 2 \Delta t ) + Q
!!$ ( 1 / ( 2 \Delta t ) + 1 / \tau ) X_{t+1} = X_{t-1} / ( 2 \Delta t ) + Q
!!$ X_{t+1} = ( X_{t-1} / ( 2 \Delta t ) + Q ) / ( 1 / ( 2 \Delta t ) + 1 / \tau )
!!$ xyz_QCloudWaterTentative = xyz_QCloudWater &
!!$ & / ( 1.0_DP + 2.0_DP * DelTime / ( CloudLifeTime + 1.0d-100 ) )
!!$ xyz_DQCloudWaterDt = xyz_DQCloudWaterDt &
!!$ & + ( xyz_QCloudWaterTentative - xyz_QCloudWater ) &
!!$ & / ( 2.0_DP * DelTime )
!!$ xyz_QCloudWaterTentative = &
!!$ & ( xyz_QCloudWater / ( 2.0_DP * DelTime ) + xyz_DQCloudWaterDt ) &
!!$ & / ( 1.0_DP / ( 2.0_DP * DelTime ) + 1.0_DP / ( CloudLifeTime + 1.0d-100 ) )
xyz_QCloudWaterTentative = ( xyz_QCloudWater / ( 2.0_DP * DelTime ) + xyz_DQCloudWaterDt + xyz_DQCloudWaterDtCumSave + xyz_DQCloudWaterDtLSCSave ) / ( 1.0_DP / ( 2.0_DP * DelTime ) + 1.0_DP / ( CloudLifeTime + 1.0d-100 ) )
xyz_DQCloudWaterDt = + ( xyz_QCloudWaterTentative - xyz_QCloudWater ) / ( 2.0_DP * DelTime )
end if
end subroutine SetCloudCloudWaterLossRateInOut
| Subroutine : | |
| Spec : | character(len=*), intent(in ) |
| xyz_DQCloudWaterDt( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP) , intent(in ) |
subroutine SetCloudRegDQCloudWaterDt( Spec, xyz_DQCloudWaterDt )
! メッセージ出力
! Message output
!
use dc_message, only: MessageNotify
character(len=*), intent(in ) :: Spec
real(DP) , intent(in ) :: xyz_DQCloudWaterDt( 0:imax-1, 1:jmax, 1:kmax )
! 初期化
! Initialization
!
if ( .not. set_cloud_inited ) call SetCloudInit
if ( Spec == 'CUM' ) then
xyz_DQCloudWaterDtCumSave = xyz_DQCloudWaterDt
else if ( Spec == 'LSC' ) then
xyz_DQCloudWaterDtLSCSave = xyz_DQCloudWaterDt
else
call MessageNotify( 'E', module_name, '%c is not supported.', c1 = trim( Spec ) )
end if
end subroutine SetCloudRegDQCloudWaterDt
| Variable : | |||
| set_cloud_inited = .false. : | logical, save, public
|
| Subroutine : | |
| xyz_CloudCover( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(out) |
subroutine SetCloudCalcCloudCover( xyz_CloudCover )
! USE statements
!
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoPut
! 時刻管理
! Time control
!
use timeset, only: TimeN, EndTime, TimesetClockStart, TimesetClockStop
real(DP), intent(out) :: xyz_CloudCover( 0:imax-1, 1:jmax, 1:kmax )
! 初期化
! Initialization
!
if ( .not. set_cloud_inited ) call SetCloudInit
! Cloud optical depth
!
if ( .not. FlagCloud ) then
xyz_CloudCover = 0.0_DP
else
xyz_CloudCover = CloudCover
end if
end subroutine SetCloudCalcCloudCover
| Subroutine : | |
| Type : | character(len=*), intent(in ) |
| xyz_TransCloudOneLayer(0:imax-1, 1:jmax, 1:kmax) : | real(DP) , intent(in ) |
| xyrr_CloudOverlapFactor(0:imax-1, 1:jmax, 0:kmax, 0:kmax) : | real(DP) , intent(out) |
subroutine SetCloudCalcOverlapFactor( Type, xyz_TransCloudOneLayer, xyrr_CloudOverlapFactor )
! USE statements
!
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoPut
! メッセージ出力
! Message output
!
use dc_message, only: MessageNotify
! 時刻管理
! Time control
!
use timeset, only: TimeN, EndTime, TimesetClockStart, TimesetClockStop
character(len=*), intent(in ) :: Type
real(DP) , intent(in ) :: xyz_TransCloudOneLayer (0:imax-1, 1:jmax, 1:kmax)
real(DP) , intent(out) :: xyrr_CloudOverlapFactor(0:imax-1, 1:jmax, 0:kmax, 0:kmax)
real(DP) :: xyz_CloudCover(0:imax-1, 1:jmax, 1:kmax)
integer :: k
integer :: kk
! 初期化
! Initialization
!
if ( .not. set_cloud_inited ) call SetCloudInit
! Cloud optical depth
!
if ( .not. FlagCloud ) then
xyrr_CloudOverlapFactor = 1.0_DP
else
call SetCloudCalcCloudCover( xyz_CloudCover )
if ( Type == 'Random_Overlap' ) then
do k = 0, kmax
kk = k
xyrr_CloudOverlapFactor(:,:,k,kk) = 1.0_DP
do kk = k+1, kmax
xyrr_CloudOverlapFactor(:,:,k,kk) = xyrr_CloudOverlapFactor(:,:,k,kk-1) * ( 1.0_DP - xyz_CloudCover(:,:,kk) * ( 1.0_DP - xyz_TransCloudOneLayer(:,:,kk) ) )
end do
end do
do k = 0, kmax
do kk = 0, k-1
xyrr_CloudOverlapFactor(:,:,k,kk) = xyrr_CloudOverlapFactor(:,:,kk,k)
end do
end do
else
call MessageNotify( 'E', module_name, 'Type %c is not supported.', c1 = trim( Type ) )
end if
end if
end subroutine SetCloudCalcOverlapFactor
| Subroutine : |
This procedure input/output NAMELIST#set_cloud_nml .
subroutine SetCloudInit
! ファイル入出力補助
! File I/O support
!
use dc_iounit, only: FileOpen
! NAMELIST ファイル入力に関するユーティリティ
! Utilities for NAMELIST file input
!
use namelist_util, only: namelist_filename, NmlutilMsg, NmlutilAryValid
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoAddVariable
! メッセージ出力
! Message output
!
use dc_message, only: MessageNotify
! 宣言文 ; Declaration statements
!
integer:: unit_nml ! NAMELIST ファイルオープン用装置番号.
! Unit number for NAMELIST file open
integer:: iostat_nml ! NAMELIST 読み込み時の IOSTAT.
! IOSTAT of NAMELIST read
! NAMELIST 変数群
! NAMELIST group name
!
namelist /set_cloud_nml/ FlagCloud, CloudLifeTime, CloudCover
!
! デフォルト値については初期化手続 "set_cloud#setCloudInit"
! のソースコードを参照のこと.
!
! Refer to source codes in the initialization procedure
! "set_cloud#SetCloudInit" for the default values.
!
! デフォルト値の設定
! Default values settings
!
FlagCloud = .true.
CloudLifeTime = 3600.0_DP
CloudCover = 0.5_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 = set_cloud_nml, iostat = iostat_nml ) ! (out)
close( unit_nml )
call NmlutilMsg( iostat_nml, module_name ) ! (in)
end if
!!$ allocate( xy_PRCPSave ( 0:imax-1, 1:jmax ) )
!!$ allocate( xyz_DTempDtCumSave( 0:imax-1, 1:jmax, 1:kmax ) )
!!$ allocate( xyz_DPDtSave ( 0:imax-1, 1:jmax, 1:kmax ) )
allocate( xyz_DQCloudWaterDtCumSave( 0:imax-1, 1:jmax, 1:kmax ) )
allocate( xyz_DQCloudWaterDtLSCSave( 0:imax-1, 1:jmax, 1:kmax ) )
!!$ xy_PRCPSave = 0.0d0
!!$ xyz_DTempDtCumSave = 0.0d0
!!$ xyz_DPDtSave = 0.0d0
xyz_DQCloudWaterDtCumSave = 0.0_DP
xyz_DQCloudWaterDtLSCSave = 0.0_DP
! ヒストリデータ出力のためのへの変数登録
! Register of variables for history data output
!
!!$ call HistoryAutoAddVariable( 'CloudCover', &
!!$ & (/ 'lon ', 'lat ', 'sig ', 'time' /), &
!!$ & 'cloud cover', '1' )
! 印字 ; Print
!
call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
call MessageNotify( 'M', module_name, 'FlagCloud = %b', l = (/ FlagCloud /) )
call MessageNotify( 'M', module_name, 'CloudLifeTime = %f', d = (/ CloudLifeTime /) )
call MessageNotify( 'M', module_name, 'CloudCover = %f', d = (/ CloudCover /) )
call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )
set_cloud_inited = .true.
end subroutine SetCloudInit
| Constant : | |||
| version = ’$Name: dcpam5-20110615 $’ // ’$Id: set_cloud.f90,v 1.4 2011-02-18 04:36:41 yot Exp $’ : | character(*), parameter
|