!= Module ReStartFileIO_3d ! ! Authors:: SUGIYAMA Ko-ichiro, ODAKA Masatsugu ! Version:: $Id: restartfileio_3d.f90,v 1.9 2011-03-01 04:38:29 sugiyama Exp $ ! Tag Name:: $Name: arare4-20120911 $ ! Copyright:: Copyright (C) GFD Dennou Club, 2007. All rights reserved. ! License:: See COPYRIGHT[link:../../COPYRIGHT] ! !== Overview ! !リスタート用の場の情報を netCDF ファイルに出力するためのルーチン ! !== Error Handling ! !== Known Bugs ! !== Note ! !速度を評価する格子位置と, 軸として入力してある座標値は整合的でないことに注意 ! !== Future Plans ! module ReStartFileIO_3d ! !リスタート用の場の情報を netCDF ファイルに出力するためのルーチン ! !モジュール読み込み use gtool_history use dc_types, only : DP use dc_message, only: MessageNotify use dc_string, only : toChar use gridset_3d,only: x_X, &!X 座標軸(スカラー格子点) & y_Y, &!Y 座標軸(スカラー格子点) & z_Z, &!Z 座標軸(スカラー格子点) & DimXMin, &!X 方向の配列の下限 & DimXMax, &!X 方向の配列の上限 & DimYMin, &!Y 方向の配列の下限 & DimYMax, &!Y 方向の配列の上限 & DimZMin, &!Z 方向の配列の下限 & DimZMax, &!Z 方向の配列の上限 & RegXMin, &! 物理領域の X 方向の下限 & RegXMax, &! 物理領域の X 方向の上限 & SpcNum !凝縮成分の数 use timeset, only: DelTimeLong use fileset_3d, only: RestartFile, &!リスタートファイル名 & InitFile, &!初期ファイル名 & exptitle, &!データの表題 & expsrc, &!データを作成する手順 & expinst !最終変更者・組織 use basicset_3d,only: BasicSetArray_Init, &! & PressBasis, &!温位の基準圧力 & GasRDry, &!乾燥成分の定圧比熱 & CpDry, &!乾燥成分の定圧比熱 & CvDry, &!乾燥成分の定積比熱 & MolWtDry, &!乾燥成分の分子量 & Grav, &!重力加速度 & SpcWetMolFr, &!凝縮成分の初期モル比 & MolWtWet, &!凝縮成分の分子量 & GasRUniv !普遍気体定数 !暗黙の型宣言禁止 implicit none !属性の指定 private !関数を public に指定 public ReStartFile_Open public ReStartFile_OutPut public ReStartFile_Close public ReStartFile_Get type(GT_HISTORY) :: rstat save rstat contains subroutine ReStartFile_Open( ) ! !リスタートファイルの書き出し ! use basicset_3d, only: xyz_ExnerBasicZ, &!基本場のエクスナー関数 & xyz_DensBasicZ, &!基本場の密度 & xyz_PotTempBasicZ, &!基本場の温位 & xyz_VelSoundBasicZ, &!基本場の音速 & xyz_PressBasicZ, &!基本場の圧力 & xyz_TempBasicZ, &!基本場の温度 & xyza_MixRtBasicZ, &!基本場の混合比 & xyz_EffMolWtBasicZ !基本場の分子量効果 !暗黙の型宣言禁止 implicit none !変数定義 real(4) :: SpcID(SpcNum) integer :: N, L, M integer :: s SpcID = 0.0d0 do s = 1, SpcNum SpcID(s) = real( s, 4 ) end do N = size(x_X, 1) L = size(y_Y, 1) M = size(z_Z, 1) !------------------------------------------------------------- ! ヒストリー作成 !------------------------------------------------------------- call HistoryCreate( & & file = ReStartFile, & & title = exptitle, & & source = expsrc, & & institution = expinst, & & dims=(/'x','y','z','s','t'/), & & dimsizes=(/N, L, M, SpcNum, 0/), & & longnames=(/'X-coordinate', & & 'Y-coordinate', & & 'Z-coordinate', & & 'Species Num ', & & 'Time '/), & & units=(/'m ','m ','m ','1 ','sec'/), & & xtypes=(/'double', 'double', 'double', 'double', 'double'/), & & origin=0.0, interval=1.0, & & history=rstat, quiet=.true. ) !------------------------------------------------------------- ! 変数出力 !------------------------------------------------------------- call HistoryPut('x', x_X, rstat ) call HistoryPut('y', y_Y, rstat ) call HistoryPut('z', z_Z, rstat ) call HistoryPut('s', real(SpcID, 4), rstat ) !無次元圧力の基本場 call HistoryAddVariable( & & varname='ExnerBasicZ', dims=(/'x','y','z'/), & & longname='nondimensional pressure', units='1',& & xtype='double', history=rstat ) !温位の基本場 call HistoryAddVariable( & & varname='PotTempBasicZ', dims=(/'x','y','z'/), & & longname='potential temperature', & & units='K', xtype='double', history=rstat ) !密度の基本場 call HistoryAddVariable( & & varname='DensBasicZ', dims=(/'x','y','z'/), & & longname='density', & & units='Kg.m-3', xtype='double', history=rstat ) !音波速度の基本場 call HistoryAddVariable( & & varname='VelSoundBasicZ', dims=(/'x','y','z'/), & & longname='sound velocity', & & units='m.s-2', xtype='double', history=rstat ) !温度の基本場 call HistoryAddVariable( & & varname='TempBasicZ', dims=(/'x','y','z'/), & & longname='Temperature of basic state', & & units='K', xtype='double', history=rstat ) !圧力の基本場 call HistoryAddVariable( & & varname='PressBasicZ', dims=(/'x','y','z'/), & & longname='Pressure of basic state', & & units='Pa', xtype='double', history=rstat ) !水蒸気混合比の基本場 call HistoryAddVariable( & & varname='MixRtBasicZ', dims=(/'x','y','z','s'/), & & longname='Mixing ratio of Condensible volatiles', & & units='kg.kg-1', xtype='double', history=rstat ) !分子量効果 call HistoryAddVariable( & & varname='EffMolWtBasicZ', dims=(/'x','y','z'/), & & longname='Effect of Mole Weight', & & units='1', xtype='double', history=rstat ) !無次元圧力 call HistoryAddVariable( & & varname='Exner', dims=(/'x','y','z','t'/), & & longname='nondimensional pressure', & & units='1', & & xtype='double', history=rstat ) !温位の擾乱 call HistoryAddVariable( & & varname='PotTemp', dims=(/'x','y','z','t'/), & & longname='virtual potential temperature', & & units='K', & & xtype='double', history=rstat ) !速度 call HistoryAddVariable( & & varname='VelX', dims=(/'x','y','z','t'/), & & longname='zonal velocity', & & units='m.s-1', & & xtype='double', history=rstat ) !速度 call HistoryAddVariable( & & varname='VelY', dims=(/'x','y','z','t'/), & & longname='meridional velocity', & & units='m.s-1', & & xtype='double', history=rstat ) !速度 call HistoryAddVariable( & & varname='VelZ', dims=(/'x','y','z','t'/), & & longname='vertical velocity', & & units='m.s-1', & & xtype='double', history=rstat ) !渦粘性係数 call HistoryAddVariable( & & varname='Km', dims=(/'x','y','z','t'/), & & longname='Km', & & units='m2.s-1', & & xtype='double', history=rstat ) !渦粘性係数 call HistoryAddVariable( & & varname='Kh', dims=(/'x','y','z','t'/), & & longname='Kh', & & units='m2.s-1', & & xtype='double', history=rstat ) !混合比 call HistoryAddVariable( & & varname='MixRt', dims=(/'x','y','z','s','t'/), & & longname='Mixing Ratio', & & units='kg.kg-1"', & & xtype='double', history=rstat ) !------------------------------------------------------------- ! 基本場のファイル出力 !------------------------------------------------------------- call HistoryPut( 'DensBasicZ', xyz_DensBasicZ , rstat) call HistoryPut( 'ExnerBasicZ', xyz_ExnerBasicZ , rstat) call HistoryPut( 'PotTempBasicZ', xyz_PotTempBasicZ , rstat) call HistoryPut( 'VelSoundBasicZ', xyz_VelSoundBasicZ , rstat) call HistoryPut( 'TempBasicZ', xyz_TempBasicZ , rstat) call HistoryPut( 'PressBasicZ', xyz_PressBasicZ , rstat) call HistoryPut( 'MixRtBasicZ', xyza_MixRtBasicZ , rstat) call HistoryPut( 'EffMolWtBasicZ', xyz_EffMolWtBasicZ, rstat) end subroutine ReStartFile_Open subroutine ReStartFile_OutPut( & & Time, xyz_PotTemp, xyz_Exner, pyz_VelX, xqz_VelY, xyr_VelZ, & & xyza_MixRt, xyz_Km , xyz_Kh & & ) ! !リスタートファイルに予報変数を書き出す ! !暗黙の型宣言禁止 implicit none !変数定義 real(DP), intent(in) :: Time real(DP), intent(in) :: pyz_VelX & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(in) :: xqz_VelY & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(in) :: xyr_VelZ & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(in) :: xyz_Exner & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(in) :: xyz_PotTemp & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(in) :: xyz_Km & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(in) :: xyz_Kh & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(in) :: xyza_MixRt & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax, SpcNum) !------------------------------------------------------------------ ! ファイル出力 !------------------------------------------------------------------ call HistoryPut( 't', Time , rstat) call HistoryPut( 'VelX', pyz_VelX , rstat) call HistoryPut( 'VelY', xqz_VelY , rstat) call HistoryPut( 'VelZ', xyr_VelZ , rstat) call HistoryPut( 'Exner', xyz_Exner , rstat) call HistoryPut( 'PotTemp', xyz_PotTemp , rstat) call HistoryPut( 'Km', xyz_Km , rstat) call HistoryPut( 'Kh', xyz_Kh , rstat) call HistoryPut( 'MixRt', xyza_MixRt , rstat) end subroutine ReStartFile_OutPut subroutine ReStartFile_Close ! !リスタートファイルのクローズ ! !モジュール読み込み use gtool_history !暗黙の型宣言禁止 implicit none !ファイルを閉じる call HistoryClose(rstat, quiet=.true.) end subroutine ReStartFile_Close subroutine ReStartFile_Get( & & ReStartTime, & & xyz_PotTempB, xyz_ExnerB, pyz_VelXB, xqz_VelYB, xyr_VelZB, & & xyza_MixRtB, xyz_KmB, xyz_KhB, & & xyz_PotTempN, xyz_ExnerN, pyz_VelXN, xqz_VelYN, xyr_VelZN, & & xyza_MixRtN, xyz_KmN, xyz_KhN ) ! !リスタートファイルから情報取得 ! !暗黙の型宣言禁止 implicit none !変数定義 real(DP), intent(out) :: ReStartTime(2) real(DP), intent(out) :: pyz_VelXN & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xqz_VelYN & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyr_VelZN & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyz_ExnerN & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyz_PotTempN & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyz_KmN & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyz_KhN & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyza_MixRtN & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax,SpcNum) real(DP), intent(out) :: pyz_VelXB & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xqz_VelYB & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyr_VelZB & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyz_ExnerB & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyz_PotTempB & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyz_KmB & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyz_KhB & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP), intent(out) :: xyza_MixRtB & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax,SpcNum) real(DP) :: DelTime real(DP) :: Var3D & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP) :: Var3Ds & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax,2) real(DP) :: Var4D & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax,SpcNum) real(DP) :: Var4Ds & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax,SpcNum, 2) real(DP) :: xyz_ExnerBasicZ & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) !基本場のエクスナー関数 real(DP) :: xyz_DensBasicZ & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) !基本場の密度 real(DP) :: xyz_PotTempBasicZ & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) !基本場の温位 real(DP) :: xyz_VelSoundBasicZ & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) !基本場の音速 real(DP) :: xyz_PressBasicZ & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) !基本場の圧力 real(DP) :: xyz_TempBasicZ & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) !基本場の温度 real(DP) :: xyza_MixRtBasicZ & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax, SpcNum) !基本場の混合比 real(DP) :: xyz_EffMolWtBasicZ & & (DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) !基本場の分子量効果 character(30) :: name !変数名 character(10) :: step(2) integer :: t !------------------------------------------------------------- ! Get a Value from netCDF File !------------------------------------------------------------- do t = 1, 2 step(t) = 't=^' // adjustl(toChar(t)) end do do t = 1, 2 name = "t" call HistoryGet( InitFile, name, ReStartTime(t), step(t) ) end do do t = 1, 2 name = "VelX" call HistoryGet( InitFile, name, Var3Ds(:,:,:,t), step(t) ) end do pyz_VelXB = Var3Ds(:,:,:,1) pyz_VelXN = Var3Ds(:,:,:,2) do t = 1, 2 name = "VelY" call HistoryGet( InitFile, name, Var3Ds(:,:,:,t), step(t) ) end do xqz_VelYB = Var3Ds(:,:,:,1) xqz_VelYN = Var3Ds(:,:,:,2) do t = 1, 2 name = "VelZ" call HistoryGet( InitFile, name, Var3Ds(:,:,:,t), step(t) ) end do xyr_VelZB = Var3Ds(:,:,:,1) xyr_VelZN = Var3Ds(:,:,:,2) do t = 1, 2 name = "Exner" call HistoryGet( InitFile, name, Var3Ds(:,:,:,t), step(t) ) end do xyz_ExnerB = Var3Ds(:,:,:,1) xyz_ExnerN = Var3Ds(:,:,:,2) do t = 1, 2 name = "PotTemp" call HistoryGet( InitFile, name, Var3Ds(:,:,:,t), step(t) ) end do xyz_PotTempB = Var3Ds(:,:,:,1) xyz_PotTempN = Var3Ds(:,:,:,2) do t = 1, 2 name = "Km" call HistoryGet( InitFile, name, Var3Ds(:,:,:,t), step(t) ) end do xyz_KmB = Var3Ds(:,:,:,1) xyz_KmN = Var3Ds(:,:,:,2) do t = 1, 2 name = "Kh" call HistoryGet( InitFile, name, Var3Ds(:,:,:,t), step(t) ) end do xyz_KhB = Var3Ds(:,:,:,1) xyz_KhN = Var3Ds(:,:,:,2) do t = 1, 2 name = "MixRt" call HistoryGet( InitFile, name, Var4Ds(:,:,:,:,t), step(t) ) end do xyza_MixRtB = Var4Ds(:,:,:,:,1) xyza_MixRtN = Var4Ds(:,:,:,:,2) !------------------------------------------------------------- ! 基本場の取得 !------------------------------------------------------------- name = "DensBasicZ" call HistoryGet( InitFile, name, Var3D ) xyz_DensBasicZ = Var3D name = "ExnerBasicZ" call HistoryGet( InitFile, name, Var3D ) xyz_ExnerBasicZ = Var3D name = "PotTempBasicZ" call HistoryGet( InitFile, name, Var3D ) xyz_PotTempBasicZ = Var3D name = "VelSoundBasicZ" call HistoryGet( InitFile, name, Var3D ) xyz_VelSoundBasicZ = Var3D name = "TempBasicZ" call HistoryGet( InitFile, name, Var3D ) xyz_TempBasicZ = Var3D name = "PressBasicZ" call HistoryGet( InitFile, name, Var3D ) xyz_PressBasicZ = Var3D name = "MixRtBasicZ" call HistoryGet( InitFile, name, Var4D ) xyza_MixRtBasicZ = Var4D name = "EffMolWtBasicZ" call HistoryGet( InitFile, name, Var3D ) xyz_EffMolWtBasicZ = Var3D !---------------------------------------------------------- ! 時間刻みのチェック !---------------------------------------------------------- DelTime = ReStartTime(2) - ReStartTime(1) if ( DelTime /= real(DelTimeLong, 4) ) then call MessageNotify( "W", & & "ReStartFile_Get", & & "DelTime in InitFile is not the same as DelTimeLong") call MessageNotify( "M", & & "ReStartFile_Get", & & "DelTime=%d", d=(/DelTime/) ) call MessageNotify( "M", & & "ReStartFile_Get", & & "DelTimeLong=%d", d=(/DelTimeLong/) ) end if !---------------------------------------------------------- ! BasicSet モジュールに値を設定 !---------------------------------------------------------- call BasicSetArray_Init( & & xyz_PressBasicZ, xyz_ExnerBasicZ, xyz_TempBasicZ, & & xyz_PotTempBasicZ, xyz_DensBasicZ, xyz_VelSoundBasicZ, & & xyza_MixRtBasicZ, xyz_EffMolWtBasicZ & & ) end subroutine ReStartFile_Get end module ReStartFileIO_3d