| 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_CloudDelOptDep( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(out) |
subroutine SetCloudLW( xyz_CloudDelOptDep )
! USE statements
!
!
! Physical constants settings
!
use constants, only: Grav, PI ! $ \pi $ .
! Circular constant
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoPut
! 時刻管理
! Time control
!
use timeset, only: TimeN, EndTime, TimesetClockStart, TimesetClockStop
real(DP), intent(out) :: xyz_CloudDelOptDep( 0:imax-1, 1:jmax, 1:kmax )
real(DP) :: xyz_DelLWP ( 0:imax-1, 1:jmax, 1:kmax )
real(DP) :: xyr_CloudOptDep( 0:imax-1, 1:jmax, 0:kmax )
integer :: i
integer :: j
integer :: k
integer :: l
! 初期化
! Initialization
!
if ( .not. set_cloud_inited ) call SetCloudInit
! Cloud optical depth
!
if ( .not. FlagCloud ) then
xyz_DelLWP = 0.0d0
xyz_CloudDelOptDep = 0.0d0
else
!!$ write( 6, * ) 'Cloud optical depth is calculated by precipitation rate.'
do k = 1, kmax
!!$ do j = js, je
do j = 1, jmax
do i = 0, imax-1
if ( ( xyz_DelPRCPCumSave(i,j,k) + xyz_DelPRCPLSCSave(i,j,k) ) > 0.0d0 ) then
xyz_DelLWP(i,j,k) = ( xyz_DelPRCPCumSave(i,j,k) + xyz_DelPRCPLSCSave(i,j,k) ) * FactorCondToCloudLW
else
xyz_DelLWP(i,j,k) = 0.0d0
end if
end do
end do
end do
xyz_CloudDelOptDep = xyz_DelLWP
end if
! ヒストリデータ出力
! History data output
!
!!$ do j = js, je
do j = 1, jmax
xyr_CloudOptDep(:,j,kmax) = 0.0d0
end do
do k = kmax-1, 0, -1
!!$ do j = js, je
do j = 1, jmax
xyr_CloudOptDep(:,j,k) = xyr_CloudOptDep(:,j,k+1) + xyz_CloudDelOptDep(:,j,k+1)
end do
end do
call HistoryAutoPut( TimeN, 'CODLW' , xyr_CloudOptDep(:,:,0) )
call HistoryAutoPut( TimeN, 'DelCODLW', xyz_CloudDelOptDep )
end subroutine SetCloudLW
| Subroutine : | |
| xyz_DPDt( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(in) |
subroutine SetCloudRegDPDt( xyz_DPDt )
real(DP), intent(in) :: xyz_DPDt( 0:imax-1, 1:jmax, 1:kmax )
! 初期化
! Initialization
!
if ( .not. set_cloud_inited ) call SetCloudInit
xyz_DPDtSave = xyz_DPDt
dpdt_registered = .true.
end subroutine SetCloudRegDPDt
| Subroutine : | |||||
| xyz_DelRain( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(in)
|
subroutine SetCloudRegPRCPCum( xyz_DelRain )
!!$ real(DP), intent(in) :: xy_Rain ( 0:imax-1, 1:jmax )
real(DP), intent(in) :: xyz_DelRain( 0:imax-1, 1:jmax, 1:kmax )
!!$ real(DP), intent(in) :: xyz_DTempDt( 0:imax-1, 1:jmax, 1:kmax )
! 初期化
! Initialization
!
if ( .not. set_cloud_inited ) call SetCloudInit
!!$ xy_PRCPSave = xy_Rain
xyz_DelPRCPCumSave = xyz_DelRain
!!$ xyz_DTempDtCumSave = xyz_DTempDt
prcpcum_registered = .true.
end subroutine SetCloudRegPRCPCum
| Subroutine : | |||||
| xyz_DelRain( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(in)
|
subroutine SetCloudRegPRCPLSC( xyz_DelRain )
!!$ real(DP), intent(in) :: xy_Rain ( 0:imax-1, 1:jmax )
real(DP), intent(in) :: xyz_DelRain( 0:imax-1, 1:jmax, 1:kmax )
!!$ real(DP), intent(in) :: xyz_DTempDt( 0:imax-1, 1:jmax, 1:kmax )
! 初期化
! Initialization
!
if ( .not. set_cloud_inited ) call SetCloudInit
!!$ xy_PRCPSave = xy_Rain
xyz_DelPRCPLSCSave = xyz_DelRain
!!$ xyz_DTempDtCumSave = xyz_DTempDt
prcplsc_registered = .true.
end subroutine SetCloudRegPRCPLSC
| Subroutine : | |||
| 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 ) | ||
| xyz_Temp( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(in ) | ||
| xyz_QVap( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(in )
| ||
| xyz_Height( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(in ) | ||
| xyz_CloudDelOptDep( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(out) |
subroutine SetCloudSW( xyz_Press, xyr_Press, xyz_Temp, xyz_QVap, xyz_Height, xyz_CloudDelOptDep )
! USE statements
!
!
! Physical constants settings
!
use constants, only: Grav, PI ! $ \pi $ .
! Circular constant
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoPut
! 時刻管理
! Time control
!
use timeset, only: TimeN, EndTime, TimesetClockStart, TimesetClockStop
real(DP), intent(in ) :: 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 ) :: xyz_Temp ( 0:imax-1, 1:jmax, 1:kmax )
real(DP), intent(in ) :: xyz_QVap ( 0:imax-1, 1:jmax, 1:kmax )
! $ q $ . 混合比. Mass mixing ratio of constituents (1)
real(DP), intent(in ) :: xyz_Height ( 0:imax-1, 1:jmax, 1:kmax )
real(DP), intent(out) :: xyz_CloudDelOptDep( 0:imax-1, 1:jmax, 1:kmax )
real(DP) :: xyz_DelLWP ( 0:imax-1, 1:jmax, 1:kmax )
real(DP) :: xyr_CloudOptDep( 0:imax-1, 1:jmax, 0:kmax )
integer :: i
integer :: j
integer :: k
integer :: l
! 初期化
! Initialization
!
if ( .not. set_cloud_inited ) call SetCloudInit
! Cloud optical depth
!
if ( .not. FlagCloud ) then
xyz_DelLWP = 0.0d0
xyz_CloudDelOptDep = 0.0d0
else
!!$ call RadiationDcpamSWEV1CalcLWP( &
!!$ & xyz_Press, xyr_Press, xyz_Temp, xyz_QVap, xyz_Height, &
!!$ & xyz_DelLWP &
!!$ & )
!!$
!!$ ! This calculation is based Equation (1) of Slingo (1989) and values of
!!$ ! ai = 2.7d-2 m2 g-1, bi = 1.3 micron m2 g-1, and r_{eff} = 10 micron.
!!$ !
!!$ xyz_CloudDelOptDep = xyz_DelLWP * ( 2.7d-2 * 1.0d3 + 1.3d0 * 1.0d3 / 10.0d0 )
!!$ write( 6, * ) 'Cloud optical depth is calculated by precipitation rate.'
do k = 1, kmax
do j = 1, jmax
do i = 0, imax-1
if ( ( xyz_DelPRCPCumSave(i,j,k) + xyz_DelPRCPLSCSave(i,j,k) ) > 0.0d0 ) then
xyz_DelLWP(i,j,k) = ( xyz_DelPRCPCumSave(i,j,k) + xyz_DelPRCPLSCSave(i,j,k) ) * FactorCondToCloudSW
else
xyz_DelLWP(i,j,k) = 0.0d0
end if
end do
end do
end do
xyz_CloudDelOptDep = xyz_DelLWP
end if
! ヒストリデータ出力
! History data output
!
xyr_CloudOptDep(:,:,kmax) = 0.0d0
do k = kmax-1, 0, -1
xyr_CloudOptDep(:,:,k) = xyr_CloudOptDep(:,:,k+1) + xyz_CloudDelOptDep(:,:,k+1)
end do
call HistoryAutoPut( TimeN, 'CODSW' , xyr_CloudOptDep(:,:,0) )
call HistoryAutoPut( TimeN, 'DelCODSW', xyz_CloudDelOptDep )
end subroutine SetCloudSW
| Variable : | |||
| set_cloud_inited = .false. : | logical, save, public
|
| Variable : | |||
| FactorCondToCloudLW : | real(DP), save
|
| Variable : | |||
| FactorCondToCloudSW : | real(DP), save
|
| Variable : | |||
| FlagCloud : | logical , save
|
| Subroutine : | |
| 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 ) |
| xyz_Temp( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(in ) |
| xyz_QVap( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(in ) |
| xyz_Height( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(in ) |
| xyz_DelLWP( 0:imax-1, 1:jmax, 1:kmax ) : | real(DP), intent(out) |
subroutine SetCloudCalcLWP( xyz_Press, xyr_Press, xyz_Temp, xyz_QVap, xyz_Height, xyz_DelLWP )
! 物理定数設定
! Physical constants settings
!
use constants, only: Grav, GasRDry
! $ R $ [J kg-1 K-1].
! 乾燥大気の気体定数.
! Gas constant of air
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoPut
! 時刻管理
! Time control
!
use timeset, only: TimeN, EndTime, TimesetClockStart, TimesetClockStop
! 飽和比湿の算出
! Evaluate saturation specific humidity
!
use saturate, only: xyz_CalcQVapSat
real(DP), intent(in ) :: 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 ) :: xyz_Temp ( 0:imax-1, 1:jmax, 1:kmax )
real(DP), intent(in ) :: xyz_QVap ( 0:imax-1, 1:jmax, 1:kmax )
real(DP), intent(in ) :: xyz_Height( 0:imax-1, 1:jmax, 1:kmax )
real(DP), intent(out) :: xyz_DelLWP( 0:imax-1, 1:jmax, 1:kmax )
integer :: xy_NumCloudLayer ( 0:imax-1, 1:jmax )
real(DP) :: xy_CloudCoverTot ( 0:imax-1, 1:jmax )
real(DP) :: xy_CloudCoverEachLayer( 0:imax-1, 1:jmax )
real(DP) :: xyz_CloudCover ( 0:imax-1, 1:jmax, 1:kmax )
real(DP):: xyz_QVapSat ( 0:imax-1, 1:jmax, 1:kmax )
! 飽和比湿.
! Saturation specific humidity.
real(DP):: xyz_RH ( 0:imax-1, 1:jmax, 1:kmax )
real(DP):: xyz_RHCor ( 0:imax-1, 1:jmax, 1:kmax )
real(DP), parameter :: CloudLiqWatDen0 = 0.18d-3
real(DP) :: xy_ColWatVapor ( 0:imax-1, 1:jmax )
real(DP) :: xy_CloudLiqWatScaleHeight( 0:imax-1, 1:jmax )
real(DP) :: xyz_CloudLiqWatDen ( 0:imax-1, 1:jmax, 1:kmax )
real(DP) :: xyz_DelCloudLiqWat ( 0:imax-1, 1:jmax, 1:kmax )
integer :: i
integer :: j
integer :: k
! 初期化
! Initialization
!
if ( .not. set_cloud_inited ) call SetCloudInit
! 飽和比湿計算
! Calculate saturation specific humidity
!
xyz_QVapSat = xyz_CalcQVapSat( xyz_Temp, xyz_Press )
xyz_RH = xyz_QVap / xyz_QVapSat
xy_NumCloudLayer = 0
do k = 1, kmax
do j = 1, jmax
do i = 0, imax-1
if ( xyz_DTempDtCumSave(i,j,k) > 0.0d0 ) then
xy_NumCloudLayer = xy_NumCloudLayer + 1
end if
end do
end do
end do
xy_CloudCoverTot = 0.0d0
do j = 1, jmax
do i = 0, imax-1
if ( xy_PRCPSave(i,j) >= 0.0d0 ) then
xy_CloudCoverTot(i,j) = 0.20d0 + 0.125d0 * log( 1.0d0 + xy_PRCPSave(i,j) * 86400.0d0 / 1.0d3 * 1.0d3 )
end if
end do
end do
do j = 1, jmax
do i = 0, imax-1
if ( xy_CloudCoverTot(i,j) > 0.8d0 ) then
xy_CloudCoverTot(i,j) = 0.8d0
end if
end do
end do
do j = 1, jmax
do i = 0, imax-1
if ( xy_NumCloudLayer(i,j) == 0 ) then
xy_CloudCoverEachLayer(i,j) = 0.0d0
else
xy_CloudCoverEachLayer(i,j) = 1.0d0 - ( 1.0d0 - xy_CloudCoverTot(i,j) )**(1.0d0/xy_NumCloudLayer(i,j))
end if
end do
end do
do k = 1, kmax
xyz_RHCor(:,:,k) = ( xyz_RH(:,:,k) - xy_CloudCoverEachLayer ) / ( 1.0d0 - xy_CloudCoverEachLayer )
end do
xyz_CloudCover = 0.0d0
! ! Frontal and tropical low-cloud
! !
! do k = 1, kmax
! do j = 1, jmax
! do i = 0, imax-1
! if ( xyz_Press(i,j,k) > 750.0d2 .and. xyz_DPDtSave(i,j,k) < 0.0d0 ) then
! xyz_CloudCover(i,j,k) = ( ( xyz_RHCor(i,j,k) - 0.9d0 ) / 0.1d0 )**2
! end if
! end do
! end do
! end do
do k = 1, kmax
do j = 1, jmax
do i = 0, imax-1
if ( ( xyz_RHCor(i,j,k) > 0.6d0 ) .and. ( xyz_DTempDtCumSave(i,j,k) > 0.0d0 ) ) then
xyz_CloudCover(i,j,k) = xy_CloudCoverEachLayer(i,j)
else
xyz_CloudCover(i,j,k) = 0.0d0
end if
end do
end do
end do
xy_ColWatVapor = 0.0d0
do k = 1, kmax
do j = 1, jmax
do i = 0, imax-1
xy_ColWatVapor = xy_ColWatVapor + xyz_QVap(:,:,k) * ( xyr_Press(:,:,k-1) - xyr_Press(:,:,k) ) / Grav
end do
end do
end do
xy_CloudLiqWatScaleHeight = 700.0d0 * log( 1.0d0 + 1.0d0 * xy_ColWatVapor ) + 1.0d0
do k = 1, kmax
xyz_CloudLiqWatDen(:,:,k) = CloudLiqWatDen0 * exp( - xyz_Height(:,:,k) / xy_CloudLiqWatScaleHeight )
end do
do k = 1, kmax
xyz_DelCloudLiqWat(:,:,k) = xyz_CloudLiqWatDen(:,:,k) * ( xyr_Press(:,:,k-1) - xyr_Press(:,:,k) ) / ( xyz_Press(:,:,k) / ( GasRDry * xyz_Temp(:,:,k) ) * Grav )
end do
xyz_DelLWP = xyz_CloudCover * xyz_DelCloudLiqWat
call HistoryAutoPut( TimeN, 'CloudCover', xyz_CloudCover )
end subroutine SetCloudCalcLWP
| 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/ FactorCondToCloudSW, FactorCondToCloudLW, FlagCloud
!
! デフォルト値については初期化手続 "set_cloud#setCloudInit"
! のソースコードを参照のこと.
!
! Refer to source codes in the initialization procedure
! "set_cloud#SetCloudInit" for the default values.
!
! デフォルト値の設定
! Default values settings
!
FactorCondToCloudSW = 1.0d5
FactorCondToCloudLW = 1.0d5
FlagCloud = .true.
! 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_DelPRCPCumSave( 0:imax-1, 1:jmax, 1:kmax ) )
allocate( xyz_DelPRCPLSCSave( 0:imax-1, 1:jmax, 1:kmax ) )
allocate( xyz_DTempDtCumSave( 0:imax-1, 1:jmax, 1:kmax ) )
allocate( xyz_DPDtSave ( 0:imax-1, 1:jmax, 1:kmax ) )
xy_PRCPSave = 0.0d0
xyz_DelPRCPCumSave = 0.0d0
xyz_DelPRCPLSCSave = 0.0d0
xyz_DTempDtCumSave = 0.0d0
xyz_DPDtSave = 0.0d0
! ヒストリデータ出力のためのへの変数登録
! Register of variables for history data output
!
call HistoryAutoAddVariable( 'CODSW', (/ 'lon ', 'lat ', 'time' /), 'cloud optical depth', '1' )
call HistoryAutoAddVariable( 'DelCODSW', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'cloud optical depth', '1' )
call HistoryAutoAddVariable( 'CODLW', (/ 'lon ', 'lat ', 'time' /), 'cloud optical depth', '1' )
call HistoryAutoAddVariable( 'DelCODLW', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'cloud optical depth', '1' )
call HistoryAutoAddVariable( 'CloudCover', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'cloud cover', '1' )
! 印字 ; Print
!
call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
call MessageNotify( 'M', module_name, 'FactorCondToCloudSW = %f', d = (/ FactorCondToCloudSW /) )
call MessageNotify( 'M', module_name, 'FactorCondToCloudLW = %f', d = (/ FactorCondToCloudLW /) )
call MessageNotify( 'M', module_name, 'FlagCloud = %b', l = (/ FlagCloud /) )
call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )
set_cloud_inited = .true.
end subroutine SetCloudInit
| Constant : | |||
| version = ’$Name: dcpam5-20101015 $’ // ’$Id: set_cloud.f90,v 1.2 2010-10-07 15:36:12 yot Exp $’ : | character(*), parameter
|