program ArareAnal
!----- モジュール読み込み ------
!----- 型宣言, 文字列処理 ----
use dc_types, only : STRING
use dc_string, only : StoA
!----- メッセージ出力 -----
use dc_message, only: MessageNotify
!----- コマンドライン引数解析 -----
use dc_args, only : ARGS, Open, Debug, Help, Strict, Close, Option
!----- 管理モジュール -----
! 化学量計算モジュール
use chemcalc, only: xz_SvapPress
! 入出力ファイル名管理モジュール
use fileset, only : fileset_init
! デバッグ出力管理モジュール
use debugset, only : debugset_init
! 時間管理モジュール
use timeset, only : timeset_init, TimeDisp, TImeInt
! 格子点管理モジュール
use gridset, only : gridset_init, DelX, DelZ, DimXMin, DimXMax, DimZMin, DimZMax, SpcNum
! 基本場設定モジュール
use basicset, only : basicset_init, MolWtDry, MolWtWet, CpDry, PressBasis, GasRDry, SpcWetID, SpcWetMolfr, xza_MixRtBasicZ, xz_PotTempBasicZ, xz_ExnerBasicZ, xz_TempBasicZ, xz_PressBasicZ
! 積算値管理モジュール
use storeset, only : storeset_init
use storeset2, only : store2set_init
!----- 下請けモジュール -----
!微分平均演算
use average
!----- 力学過程 -----
! 力学過程計算用関数モジュール
use DynFunc, only : xr_Buoy
!----- 物理過程 -----
! ! 湿潤飽和調節法計算用モジュール
! use MoistAdjust, only : MoistAdjust_Init, MoistAdjustSvapPress, MoistAdjustNH4SH
! 雲物理パラメタリゼーション
use WarmRainPrm, only : WarmRainPrm_Init, WarmRainPrm_prm
! 湿潤気塊の浮力計算用モジュール
use MoistBuoyancy,only : MoistBuoy_Init, xr_BuoyMolWt, xr_BuoyDrag
! 断熱上昇気塊の温度減率計算用モジュール
use ECCM, only : eccm_init, eccm_stab, eccm_molfr
!暗黙の型宣言禁止
implicit none
!変数定義
real(8), allocatable :: xz_PotTemp(:,:)
real(8), allocatable :: xz_PotTempAll(:,:)
real(8), allocatable :: xz_Exner(:,:)
real(8), allocatable :: pz_VelX(:,:)
real(8), allocatable :: xr_VelZ(:,:)
! real(8), allocatable :: xz_Km(:,:)
real(8), allocatable :: xza_MixRt(:,:,:)
real(8), allocatable :: xza_MixRtAll(:,:,:)
real(8), allocatable :: xza_MixRtSat(:,:,:)
real(8), allocatable :: xza_MixRtEq(:,:,:)
real(8), allocatable :: za_MolFrEq(:,:)
real(8), allocatable :: xz_Temp(:,:)
real(8), allocatable :: xz_VPotTemp(:,:)
real(8), allocatable :: xz_VPotTempAll(:,:)
real(8), allocatable :: xz_Dens(:,:)
real(8), allocatable :: xz_BuoyAll(:,:)
real(8), allocatable :: xz_BuoyTemp(:,:)
real(8), allocatable :: xz_BuoyMolWt(:,:)
real(8), allocatable :: xz_BuoyDrag(:,:)
real(8), allocatable :: xz_Stab(:,:)
real(8), allocatable :: xz_StabTemp(:,:)
real(8), allocatable :: xz_StabMolWt(:,:)
real(8) :: AnalTime
real(8) :: Hum
real(8), allocatable :: xz_TempAll(:,:)
real(8), allocatable :: xz_PressAll(:,:)
real(8), allocatable :: xz_EffMolWt(:,:)
real(8), allocatable :: xza_MixRtDivMolWt(:,:,:)
real(8), allocatable :: xz_EqConst(:,:)
real(8), allocatable :: xz_EqConstSat(:,:)
real(8), allocatable :: xz_StrmFunc(:,:)
real(8), allocatable :: xz_Cloud(:,:)
real(8), allocatable :: xz_Rain(:,:)
integer :: LoopNum, LoopNum2
integer :: GasNum(10)
integer :: CloudNum(10)
integer :: RainNum(10)
integer :: NH3Num
integer :: H2SNum
integer :: NH4SHNum
integer :: t, s, i, k
character(50) :: cfgfile
!----- コマンドライン行き数解析用変数 -----
type(ARGS) :: arg ! コマンドライン引数情報
logical :: OPT_namelist ! コマンドライン引数用論理変数
character(STRING) :: VAL_namelist ! コマンドライン引数の値
!----------------------------------------------------------------------
! 変数参照型モジュールの初期化
!----------------------------------------------------------------------
!NAMELIST ファイルの取得
! gtool5 ライブラリの dc_args モジュールを利用.
! 指定可能なオプションは以下の通り.
!
! -N=VAL, --namelist=VAL
! specify Namelist file (default is 'arare.conf').
!
! -D=VAL, --debug=VAL
! call dc_trace#SetDebug (display a lot of messages for debug).
! VAL is unit number (default is standard output)
!
! -h=VAL, -H=VAL, --help=VAL
! display this help and exit. VAL is unit number (default is
! standard output)
!
call Open(arg)
call Option(arg, StoA('-N', '--namelist'), OPT_namelist, VAL_namelist, help="specify Namelist file (default is 'arare.conf')." )
! "-N/--namelist" オプションの設定
call Debug(arg) ! デバッグオプションの自動設定
call Help(arg) ! ヘルプオプションの自動設定
call Strict(arg) ! 無効なオプション指定時に警告を表示
!"-N/-namelist" オプションの解釈
! 与えられていない場合はデフォルト値 (arare.conf) を
! NAMLIST ファイル名とする.
!
if (OPT_namelist) then
call MessageNotify( "M", "main", "Namelist file is '%c'", c1=trim(VAL_namelist) )
cfgfile=trim(VAL_namelist)
else
call MessageNotify( "W", "main", "Namelist file is not specified." )
call MessageNotify( "M", "main", "Use default Namelist file (arare.conf)." )
cfgfile="arare.conf"
end if
call Close(arg)
!時刻に関する設定の初期化
! NAMELIST から必要な情報を読み取り, 時間関連の変数の設定を行う.
call timeset_init(cfgfile)
!格子点情報の初期化
! NAMELIST から情報を得て, 格子点を計算する
call gridset_init(cfgfile)
!基本場の情報の初期化
! NAMELIST から情報を得て, 基本場を設定する.
call basicset_init(cfgfile)
!I/O ファイル名の初期化
! NAMELIST ファイル名を指定し, deepconv/arare の
! 出力ファイル名を NAMELIST から得る
call fileset_init(cfgfile)
! NAMELIST から情報を得て, 基本場を設定する.
call storeset_init( )
call store2set_init( )
!内部変数の初期化. とりあえずゼロを入れて値を確定させておく.
call ArareAlloc
!NetCDF ファイルの作成と基本場の取得
call AnalFile_Open( )
call AnalFile_OpenDens( )
!基本場の取得
call AnalFile_BasicZ_Get( )
!----------------------------------------------------------------------
! パッケージ型モジュールの初期化
! デフォルトの値から変更する必要のあるルーチンのみ初期化
!----------------------------------------------------------------------
call ECCM_Init
! call Damping_Init( cfgfile ) !波の減衰係数の初期化
! call NumDiffusion_Init() !数値拡散項の初期化
! call Turbulence_Init() !乱流計算の初期化
! call MoistAdjust_Init() !湿潤飽和調整法の初期化
call WarmRainPrm_Init( cfgfile ) !暖かい雨のパラメタリゼーションの初期化
! call Radiation_Init( cfgfile ) !放射強制の初期化
call MoistBuoy_Init() !分子量に対する浮力計算ルーチンの初期化
call WarmRainPrm_prm( LoopNum, LoopNum2, RainNum, CloudNum, GasNum, NH3Num, H2SNum, NH4SHNum )
!----------------------------------------------------------------------
! 解析値の計算開始
! 時刻を進めながら, ファイルの値を得る
!----------------------------------------------------------------------
do t = 1, int( TimeInt / TimeDisp ) + 1
!----------------------------------------------------------------
! ヒストリファイルを開き値を得る.
!----------------------------------------------------------------
call AnalFile_Get( t, AnalTime, xz_PotTemp, xz_Exner, pz_VelX, xr_VelZ, xza_MixRt )
write(*,*) t, AnalTime
!----------------------------------------------------------------
! 初期化
!----------------------------------------------------------------
xz_Cloud = 0.0d0
xz_Rain = 0.0d0
xza_MixRtAll = xza_MixRt + xza_MixRtBasicZ
!----------------------------------------------------------------
! 温度・圧力の計算
!----------------------------------------------------------------
xz_PressAll = PressBasis * ((xz_Exner + xz_ExnerBasicZ ) ** (CpDry / GasRDry))
xz_PotTempAll = xz_PotTemp + xz_PotTempBasicZ
xz_TempAll = ( xz_Exner + xz_ExnerBasicZ ) * xz_PotTempAll
xz_Temp = xz_TempAll - xz_ExnerBasicZ * xz_PotTempBasicZ
!----------------------------------------------------------------
! 密度, 仮温位の計算
!----------------------------------------------------------------
xza_MixRtDivMolWt = 0.0d0
do s = 1, 3
xza_MixRtDivMolWt(:,:,s) = xza_MixRtAll(:,:,s) / MolWtWet(s)
end do
xz_EffMolWt = (1.0d0 / MolWtDry) / ((1.0d0 / MolWtDry) + sum(xza_MixRtDivMolWt,3)) * (1.0d0 + sum(xza_MixRtAll,3))
xz_Dens = xz_PressAll * xz_EffMolWt / (GasRDry * xz_TempAll)
xz_VPotTemp = xz_PotTemp / xz_EffMolWt
xz_VPotTempAll = xz_PotTempAll / xz_EffMolWt
!----------------------------------------------------------------
! 流線関数
!----------------------------------------------------------------
do k = 1, DimZMax-1
xz_StrmFunc(:,k+1) = xz_StrmFunc(:,k) - pz_VelX(:,k) * DelZ
end do
do i = 1, DimXMax-1
xz_StrmFunc(i+1,:) = xz_StrmFunc(i,:) + xr_VelZ(i,:) * DelX
end do
!----------------------------------------------------------------
! 浮力
!----------------------------------------------------------------
xz_BuoyTemp = xz_avr_xr( xr_Buoy( xz_PotTemp ) )
xz_BuoyMolWt = xz_avr_xr( xr_BuoyMolWt( xza_MixRt ) )
xz_BuoyDrag = xz_avr_xr( xr_BuoyDrag( xza_MixRt ) )
xz_BuoyAll = xz_BuoyTemp + xz_BuoyMolWt + xz_BuoyDrag
!----------------------------------------------------------------
! 雲混合比, 雨混合比をまとめる
!----------------------------------------------------------------
do s = 1, LoopNum2
xz_Cloud = xz_Cloud + xza_MixRt(:,:,CloudNum(s))
xz_Rain = xz_Rain + xza_MixRt(:,:,RainNum(s))
end do
!----------------------------------------------------------------
! 飽和蒸気圧と平衡定数
!----------------------------------------------------------------
!飽和蒸気圧
if (LoopNum /= 0 ) then
do s = 1, LoopNum
xza_MixRtSat(:,:,GasNum(s)) = xz_SvapPress(SpcWetID(CloudNum(s)), xz_TempAll) * MolWtWet(CloudNum(s)) / (MolWtDry * xz_PressAll)
end do
end if
!平衡定数
if ( NH4SHNum /= 0 ) then
xz_EqConstSat = 61.781d0 - 10834.0d0 / xz_TempAll - dlog(1.0d2)
xz_EqConst = dlog( ( xz_PressAll ** 2.0d0 ) * max( xza_MixRtAll(:,:,NH3Num), 1.0d-20 ) * max( xza_MixRtAll(:,:,H2SNum), 1.0d-20 ) * ( MolWtDry ** 2.0d0) / ( MolWtWet(NH3Num) ) / ( MolWtWet(H2SNum) ) )
end if
!湿度 100 % の時の混合比を求める
Hum = 1.0d0
call ECCM_MolFr( SpcWetMolFr(1:SpcNum), Hum, xz_TempBasicZ(1,:), xz_PressBasicZ(i,:), za_MolFrEq )
!分子量から混合比への変換. 水平方向には一様
do s = 1, SpcNum
do i = DimXMin, DimXMax
xza_MixRtEq(i,:,s) = za_MolFrEq(:,s) * MolWtWet(s) / MolWtDry
end do
end do
!----------------------------------------------------------------
! 安定度の計算
!----------------------------------------------------------------
call ECCM_Stab( xz_PotTemp, xz_Exner, xza_MixRt, xz_Stab, xz_StabTemp, xz_StabMolWt)
!----------------------------------------------------------------
! ファイル出力
!----------------------------------------------------------------
if ( mod(t, 10) == 1 ) call AnalFile_OutPut( AnalTime )
call AnalFile_OutPutDens( AnalTime )
end do
!----------------------------------------------------------------
! ファイルを閉じる
!----------------------------------------------------------------
call AnalFile_Close
contains
subroutine AnalFile_Close( )
!
!解析ファイルのクローズ
!
use gtool_history, only: HistoryClose
use fileset, only: gt_hist
call HistoryClose( gt_hist(1) )
call HistoryClose( gt_hist(2) )
end subroutine AnalFile_Close
subroutine AnalFile_Open( )
!
!解析ファイルの定義
!
use gtool_history, only: HistoryCreate, HistoryPut, HistoryAddVariable
use fileset, only: gt_hist, exptitle, expsrc, expinst, HistoryFilePrefix
use gridset, only: FileNX, FileNZ, s_X, s_Z, FileXMin, FileXMax, FileZMin, FileZMax
use basicset, only: SpcWetSymbol
!暗黙の型宣言禁止
implicit none
!変数定義
character(50) :: File
integer :: s
File = trim(HistoryFilePrefix)// '_anal.nc'
!-----------------------------------------------------------
! ヒストリー作成
!-----------------------------------------------------------
call HistoryCreate( file = trim(File), title = exptitle, source = expsrc, institution = expinst, dims=(/'x','z','t'/), dimsizes=(/FileNX, FileNZ, 0/), longnames=(/'X-coordinate', 'Z-coordinate', 'Time '/), units=(/'m','m','s'/), origin=0.0, interval=0.0, history=gt_hist(1) )
!-----------------------------------------------------------
! 軸の出力
!-----------------------------------------------------------
call HistoryPut('x', s_X( FileXMin: FileXMax ), history=gt_hist(1) )
call HistoryPut('z', s_Z( FileZMin: FileZMax ), history=gt_hist(1) )
!-----------------------------------------------------------
! 解析用の変数の出力
!-----------------------------------------------------------
!仮温位の擾乱
call HistoryAddVariable( varname='VPotTemp', dims=(/'x','z','t'/), longname='disturbunce of virtual potential temperature', units='K', xtype='double' , history=gt_hist(1) )
!仮温位
call HistoryAddVariable( varname='VPotTempAll', dims=(/'x','z','t'/), longname='virtual potential temperature', units='K', xtype='double' , history=gt_hist(1) )
!温位の擾乱
call HistoryAddVariable( varname='PotTempAll', dims=(/'x','z','t'/), longname='potential temperature', units='K', xtype='double' , history=gt_hist(1) )
!温度擾乱
call HistoryAddVariable( varname='Temp', dims=(/'x','z','t'/), longname='disturbunce of temperature', units='K', xtype='double' , history=gt_hist(1) )
!温度
call HistoryAddVariable( varname='TempAll', dims=(/'x','z','t'/), longname='temperature', units='K', xtype='double' , history=gt_hist(1) )
!圧力
call HistoryAddVariable( varname='PressAll', dims=(/'x','z','t'/), longname='Pressure', units='Pa', xtype='double' , history=gt_hist(1) )
!密度
call HistoryAddVariable( varname='Dens', dims=(/'x','z','t'/), longname='Density', units='kg m|-2"', xtype='double' , history=gt_hist(1) )
!-----------------------------------------------------------
! 浮力関連
!-----------------------------------------------------------
!全浮力
call HistoryAddVariable( varname='BuoyAll', dims=(/'x','z','t'/), longname='Buoyancy', units=' ', xtype='double' , history=gt_hist(1) )
!浮力(温度の寄与)
call HistoryAddVariable( varname='BuoyTemp', dims=(/'x','z','t'/), longname='Buoyancy (Temp)', units=' ', xtype='double' , history=gt_hist(1) )
!浮力(分子量の寄与)
call HistoryAddVariable( varname='BuoyMolWt', dims=(/'x','z','t'/), longname='Buoyancy (MolWt)', units=' ', xtype='double' , history=gt_hist(1) )
!浮力(引きずりの寄与)
call HistoryAddVariable( varname='BuoyDrag', dims=(/'x','z','t'/), longname='Buoyancy (Drag)', units=' ', xtype='double' , history=gt_hist(1) )
!-----------------------------------------------------------
! 安定度関連
!-----------------------------------------------------------
!安定度
call HistoryAddVariable( varname='Stab', dims=(/'x','z','t'/), longname='Static Stability', units='s|-2" ', xtype='double' , history=gt_hist(1) )
!安定度(温度の寄与)
call HistoryAddVariable( varname='StabTemp', dims=(/'x','z','t'/), longname='Static Stability (Temp)', units='s|-2" ', xtype='double' , history=gt_hist(1) )
!安定度(分子量の寄与)
call HistoryAddVariable( varname='StabMolWt', dims=(/'x','z','t'/), longname='Static Stability (MolWt)', units='s|-2" ', xtype='double' , history=gt_hist(1) )
!-----------------------------------------------------------
! 飽和蒸気圧と平衡定数
!-----------------------------------------------------------
do s = 1, 2
!飽和混合比
call HistoryAddVariable( varname=trim(SpcWetSymbol(s))//'Sat', dims=(/'x','z','t'/), longname='Saturated '//trim(SpcWetSymbol(s))//' Mixing Ratio', units='kg kg|-1"', xtype='double' , history=gt_hist(1) )
end do
do s = 1, 3
!熱平衡状態での混合比
call HistoryAddVariable( varname=trim(SpcWetSymbol(s))//'Eq', dims=(/'x','z','t'/), longname='Equilibrium '//trim(SpcWetSymbol(s))//' Mixing Ratio', units='kg kg|-1"', xtype='double' , history=gt_hist(1) )
end do
call HistoryAddVariable( varname='EqConstSat', dims=(/'x','z','t'/), longname='Equilibrium Constant of NH4SH', units='kg kg|-1"', xtype='double' , history=gt_hist(1) )
call HistoryAddVariable( varname='EqConst', dims=(/'x','z','t'/), longname='log (P_H2O P_NH3) ', units='kg kg|-1"', xtype='double' , history=gt_hist(1) )
!----------------------------------------------------------------
! 雲と雨
!----------------------------------------------------------------
call HistoryAddVariable( varname='Cloud', dims=(/'x','z','t'/), longname='All Clouds Mixing Ratio', units='kg kg|-1"', xtype='double' , history=gt_hist(1) )
call HistoryAddVariable( varname='Rain', dims=(/'x','z','t'/), longname='All Rains Mixing Ratio', units='kg kg|-1"', xtype='double' , history=gt_hist(1) )
!----------------------------------------------------------------
! 流線関数
!----------------------------------------------------------------
call HistoryAddVariable( varname='StrmFunc', dims=(/'x','z','t'/), longname='Stream Function', units='m|2" s', xtype='double' , history=gt_hist(1) )
end subroutine AnalFile_Open
subroutine AnalFile_OutPut( Time )
use gtool_history, only: HistoryPut
use fileset, only: gt_hist
use gridset, only: FileXMin, FileXMax, FileZMin, FileZMax
use basicset, only: SpcWetSymbol
!暗黙の型宣言禁止
implicit none
!変数定義
real(8), intent(in) :: Time
!----------------------------------------------------------------
! 値を出力
!----------------------------------------------------------------
call HistoryPut( 't', Time, history=gt_hist(1) )
call HistoryPut( 'Temp', xz_Temp(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'TempAll', xz_TempAll(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'VPotTemp', xz_VPotTemp(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'VPotTempAll', xz_VPotTempAll(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'PotTempAll', xz_PotTempAll(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'PressAll', xz_PressAll(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'Dens', xz_Dens(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'BuoyAll', xz_BuoyAll(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'BuoyTemp', xz_BuoyTemp(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'BuoyMolWt', xz_BuoyMolWt(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'BuoyDrag', xz_BuoyDrag(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
do s = 1, 2
call HistoryPut( trim(SpcWetSymbol(s))//'Sat', xza_MixRtSat(FileXMin:FileXMax, FileZMin:FileZMax, s), history=gt_hist(1) )
end do
do s = 1, 3
call HistoryPut( trim(SpcWetSymbol(s))//'Eq', xza_MixRtEq(FileXMin:FileXMax, FileZMin:FileZMax, s), history=gt_hist(1) )
end do
call HistoryPut( 'EqConstSat', xz_EqConstSat(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'EqConst', xz_EqConst(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'Cloud', xz_Cloud(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'Rain', xz_Rain(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'Stab', xz_Stab(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'StabTemp', xz_StabTemp(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'StabMolWt', xz_StabMolWt(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'StrmFunc', xz_StrmFunc(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
call HistoryPut( 'Dens', xz_Dens(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(1) )
end subroutine AnalFile_OutPut
subroutine AnalFile_OpenDens( )
!
!解析ファイルの定義
!
use gtool_history, only: HistoryCreate, HistoryPut, HistoryAddVariable
use fileset, only: gt_hist, exptitle, expsrc, expinst, HistoryFilePrefix
use gridset, only: FileNX, FileNZ, s_X, s_Z, FileXMin, FileXMax, FileZMin, FileZMax
!暗黙の型宣言禁止
implicit none
!変数定義
integer :: s
character(50) :: File
!ファイル名の指定
File = trim(HistoryFilePrefix)// '_Dens.nc'
!-----------------------------------------------------------
! ヒストリー作成
!-----------------------------------------------------------
call HistoryCreate( file = File, title = exptitle, source = expsrc, institution = expinst, dims=(/'x','z','t'/), dimsizes=(/FileNX, FileNZ, 0/), longnames=(/'X-coordinate', 'Z-coordinate', 'Time '/), units=(/'m','m','s'/), origin=0.0, interval=0.0, history=gt_hist(2) )
!-----------------------------------------------------------
! 軸の出力
!-----------------------------------------------------------
call HistoryPut('x', s_X( FileXMin: FileXMax ), history=gt_hist(2) )
call HistoryPut('z', s_Z( FileZMin: FileZMax ), history=gt_hist(2) )
!-----------------------------------------------------------
! 解析用の変数の出力
!-----------------------------------------------------------
!密度
call HistoryAddVariable( varname='Dens', dims=(/'x','z','t'/), longname='Density', units='kg m|-2"', xtype='double', history=gt_hist(2) )
end subroutine AnalFile_OpenDens
subroutine AnalFile_OutPutDens( Time )
use fileset, only: gt_hist
use gridset, only: FileXMin, FileXMax, FileZMin, FileZMax
use gtool_history, only: HistoryPut
!暗黙の型宣言禁止
implicit none
!変数定義
real(8), intent(in) :: Time
!----------------------------------------------------------------
! 値を出力
!----------------------------------------------------------------
call HistoryPut( 't', Time, history=gt_hist(2) )
call HistoryPut( 'Dens', xz_Dens(FileXMin:FileXMax, FileZMin:FileZMax), history=gt_hist(2) )
end subroutine AnalFile_OutPutDens
!!!------------------------------------------------------------------------------!!!
subroutine AnalFile_Get( i, AnalTime, xz_PotTemp, xz_Exner, pz_VelX, xr_VelZ, xza_MixRt )
use dc_string
use gtool_history, only : HistoryGet
use fileset, only : HistoryFile
use gridset, only : DimXMin, DimXMax, DimZMin, DimZMax, SpcNum, FileXMin, FileXMax, FileZMin, FileZMax
use basicset, only : SpcWetSymbol
use boundary, only : xz_BoundaryXCyc_xz, xz_BoundaryZSym_xz, xza_BoundaryXCyc_xza, xza_BoundaryZSym_xza, pz_BoundaryXCyc_pz, pz_BoundaryZSym_pz, xr_BoundaryXCyc_xr, xr_BoundaryZAntiSym_xr
!暗黙の型宣言禁止
implicit none
!変数定義
integer, intent(in) :: i
real(8), intent(out) :: AnalTime
real(8), intent(out) :: pz_VelX(DimXMin:DimXMax,DimZMin:DimZMax)
real(8), intent(out) :: xr_VelZ(DimXMin:DimXMax,DimZMin:DimZMax)
real(8), intent(out) :: xz_Exner(DimXMin:DimXMax,DimZMin:DimZMax)
real(8), intent(out) :: xz_PotTemp(DimXMin:DimXMax,DimZMin:DimZMax)
real(8), intent(out) :: xza_MixRt(DimXMin:DimXMax,DimZMin:DimZMax,1:SpcNum)
character(30) :: name !変数名
character(10) :: step
step = '^' // adjustl(toChar(i))
!-------------------------------------------------------------
!Get a Value from netCDF File
!-------------------------------------------------------------
name = "t"
call HistoryGet( HistoryFile(1), name, AnalTime, step )
!-------------------------------------------------------------
! Get a Value from netCDF File
!-------------------------------------------------------------
name = "Exner"
call HistoryGet( HistoryFile(1), name, xz_Exner(FileXMin:FileXMax, FileZMin:FileZMax), range=step )
xz_Exner = xz_BoundaryXCyc_xz( xz_Exner )
xz_Exner = xz_BoundaryZSym_xz( xz_Exner )
name = "PotTemp"
call HistoryGet( HistoryFile(2), name, xz_PotTemp(FileXMin:FileXMax, FileZMin:FileZMax), range=step )
xz_PotTemp = xz_BoundaryXCyc_xz( xz_PotTemp )
xz_PotTemp = xz_BoundaryZSym_xz( xz_PotTemp )
name = "VelX"
call HistoryGet( HistoryFile(3), name, pz_VelX(FileXMin:FileXMax, FileZMin:FileZMax), range=step )
pz_VelX = pz_BoundaryXCyc_pz( pz_VelX )
pz_VelX = pz_BoundaryZSym_pz( pz_VelX )
name = "VelZ"
call HistoryGet( HistoryFile(4), name, xr_VelZ(FileXMin:FileXMax, FileZMin:FileZMax), range=step )
xr_VelZ = xr_BoundaryXCyc_xr( xr_VelZ )
xr_VelZ = xr_BoundaryZAntiSym_xr( xr_VelZ )
! name = "Km"
! call HistoryGet( HistoryFile(5), name, xz_Km(FileXMin:FileXMax, FileZMin:FileZMax), range=step )
! xz_Km = xz_BoundaryXCyc_xz( xz_Km )
! xz_Km = xz_BoundaryZSym_xz( xz_Km )
do s = 1, SpcNum
name = trim(SpcWetSymbol(s))
call HistoryGet( HistoryFile(8+s), name, xza_MixRt(FileXMin:FileXMax, FileZMin:FileZMax, s), range=step )
end do
xza_MixRt = xza_BoundaryXCyc_xza( xza_MixRt )
xza_MixRt = xza_BoundaryZSym_xza( xza_MixRt )
end subroutine AnalFile_Get
subroutine AnalFile_BasicZ_Get( )
use dc_string
use gtool_history, only: HistoryGet
use fileset, only: HistoryFile
use basicset, only: BasicSetArray_Init, SpcWetSymbol
use gridset, only: DimXMin, DimXMax, DimZMin, DimZMax, SpcNum, FileXMin, FileXMax, FileZMin, FileZMax
use boundary, only: xz_BoundaryXCyc_xz, xz_BoundaryZSym_xz, xza_BoundaryXCyc_xza, xza_BoundaryZSym_xza, pz_BoundaryXCyc_pz, pz_BoundaryZSym_pz, xr_BoundaryXCyc_xr, xr_BoundaryZAntiSym_xr
!暗黙の型宣言禁止
implicit none
!変数定義
real(8) :: xz_DensBZ(DimXMin:DimXMax, DimZMin:DimZMax)
real(8) :: xz_PotTempBZ(DimXMin:DimXMax, DimZMin:DimZMax)
real(8) :: xz_ExnerBZ(DimXMin:DimXMax, DimZMin:DimZMax)
real(8) :: xza_MixRtBZ(DimXMin:DimXMax, DimZMin:DimZMax,1:SpcNum)
real(8) :: xz_EffMolWtBZ(DimXMin:DimXMax, DimZMin:DimZMax)
real(8) :: xz_PressBZ(DimXMin:DimXMax, DimZMin:DimZMax)
real(8) :: xz_TempBZ(DimXMin:DimXMax, DimZMin:DimZMax)
real(8) :: xz_VelSoundBZ(DimXMin:DimXMax, DimZMin:DimZMax)
character(30) :: name !変数名
!-------------------------------------------------------------
! 基本場の取得
!-------------------------------------------------------------
name = "TempBasicZ"
call HistoryGet( HistoryFile(7), name, xz_TempBZ(FileXMin:FileXMax, FileZMin:FileZMax) )
xz_TempBZ = xz_BoundaryXCyc_xz( xz_TempBZ )
xz_TempBZ = xz_BoundaryZSym_xz( xz_TempBZ )
name = "PressBasicZ"
call HistoryGet( HistoryFile(7), name, xz_PressBZ(FileXMin:FileXMax, FileZMin:FileZMax) )
xz_PressBZ = xz_BoundaryXCyc_xz( xz_PressBZ )
xz_PressBZ = xz_BoundaryZSym_xz( xz_PressBZ )
name = "ExnerBasicZ"
call HistoryGet( HistoryFile(7), name, xz_ExnerBZ(FileXMin:FileXMax, FileZMin:FileZMax) )
xz_ExnerBZ = xz_BoundaryXCyc_xz( xz_ExnerBZ )
xz_ExnerBZ = xz_BoundaryZSym_xz( xz_ExnerBZ )
name = "PotTempBasicZ"
call HistoryGet( HistoryFile(7), name, xz_PotTempBZ(FileXMin:FileXMax, FileZMin:FileZMax) )
xz_PotTempBZ = xz_BoundaryXCyc_xz( xz_PotTempBZ )
xz_PotTempBZ = xz_BoundaryZSym_xz( xz_PotTempBZ )
name = "DensBasicZ"
call HistoryGet( HistoryFile(7), name, xz_DensBZ(FileXMin:FileXMax, FileZMin:FileZMax) )
xz_DensBZ = xz_BoundaryXCyc_xz( xz_DensBZ )
xz_DensBZ = xz_BoundaryZSym_xz( xz_DensBZ )
name = "VelSoundBasicZ"
call HistoryGet( HistoryFile(7), name, xz_VelSoundBZ(FileXMin:FileXMax, FileZMin:FileZMax) )
xz_VelSoundBZ = xz_BoundaryXCyc_xz( xz_VelSoundBZ )
xz_VelSoundBZ = xz_BoundaryZSym_xz( xz_VelSoundBZ )
name = "EffMolWtBasicZ"
call HistoryGet( HistoryFile(7), name, xz_EffMolWtBZ(FileXMin:FileXMax, FileZMin:FileZMax) )
xz_EffMolWtBZ = xz_BoundaryXCyc_xz( xz_EffMolWtBZ )
xz_EffMolWtBZ = xz_BoundaryZSym_xz( xz_EffMolWtBZ )
do s = 1, SpcNum
name = trim(SpcWetSymbol(s))//'BasicZ'
call HistoryGet( HistoryFile(7), name, xza_MixRtBZ(FileXMin:FileXMax, FileZMin:FileZMax, s) )
end do
xza_MixRtBZ = xza_BoundaryXCyc_xza( xza_MixRtBZ )
xza_MixRtBZ = xza_BoundaryZSym_xza( xza_MixRtBZ )
!----------------------------------------------------------
! BasicSet モジュールに値を設定
!----------------------------------------------------------
call BasicSetArray_Init( xz_PressBZ, xz_ExnerBZ, xz_TempBZ, xz_PotTempBZ, xz_DensBZ, xz_VelSoundBZ, xza_MixRtBZ, xz_EffMolWtBZ )
end subroutine AnalFile_BasicZ_Get
subroutine ArareAlloc
use gridset, only: DimXMin, DimXMax, DimZMin, DimZMax, SpcNum
!基本場, 擾乱場の取得.
allocate( xz_PotTemp(DimXMin:DimXMax, DimZMin:DimZMax ), xz_PotTempAll(DimXMin:DimXMax, DimZMin:DimZMax ), xz_Exner(DimXMin:DimXMax, DimZMin:DimZMax ), pz_VelX(DimXMin:DimXMax, DimZMin:DimZMax ), xr_VelZ(DimXMin:DimXMax, DimZMin:DimZMax ), xza_MixRt(DimXMin:DimXMax, DimZMin:DimZMax, 1:SpcNum ), xza_MixRtAll(DimXMin:DimXMax, DimZMin:DimZMax, 1:SpcNum ), xza_MixRtSat(DimXMin:DimXMax, DimZMin:DimZMax, 1:SpcNum ), xza_MixRtEq(DimXMin:DimXMax, DimZMin:DimZMax, 1:SpcNum ), za_MolFrEq(DimZMin:DimZMax, 1:SpcNum ), xz_Temp(DimXMin:DimXMax, DimZMin:DimZMax ), xz_VPotTemp(DimXMin:DimXMax, DimZMin:DimZMax ), xz_VPotTempAll(DimXMin:DimXMax, DimZMin:DimZMax ), xz_Dens(DimXMin:DimXMax, DimZMin:DimZMax), xz_Stab(DimXMin:DimXMax, DimZMin:DimZMax ), xz_StabTemp(DimXMin:DimXMax, DimZMin:DimZMax ), xz_StabMolWt(DimXMin:DimXMax, DimZMin:DimZMax ), xz_TempAll(DimXMin:DimXMax, DimZMin:DimZMax ), xz_PressAll(DimXMin:DimXMax, DimZMin:DimZMax ), xz_EqConstSat(DimXMin:DimXMax, DimZMin:DimZMax ), xz_EqConst(DimXMin:DimXMax, DimZMin:DimZMax ), xz_EffMolWt(DimXMin:DimXMax, DimZMin:DimZMax ), xza_MixRtDivMolWt(DimXMin:DimXMax,DimZMin:DimZMax,SpcNum), xz_StrmFunc(DimXMin:DimXMax, DimZMin:DimZMax ), xz_Cloud(DimXMin:DimXMax, DimZMin:DimZMax ), xz_Rain(DimXMin:DimXMax, DimZMin:DimZMax ), xz_BuoyAll(DimXMin:DimXMax, DimZMin:DimZMax ), xz_BuoyTemp(DimXMin:DimXMax, DimZMin:DimZMax ), xz_BuoyMolWt(DimXMin:DimXMax, DimZMin:DimZMax ), xz_BuoyDrag(DimXMin:DimXMax, DimZMin:DimZMax ) )
LoopNum = 0
LoopNum2 = 0
RainNum = 0
CloudNum = 0
GasNum = 0
NH3Num = 0
H2SNum = 0
NH4SHNum = 0
xz_StrmFunc = 0.0d0
xza_MixRtSat = 0.0d0
xza_MixRtDivMolWt = 0.0d0
end subroutine ArareAlloc
end program ArareAnal