!= Module HistoryFileIO_3d_dry ! ! Authors:: SUGIYAMA Ko-ichiro, ODAKA Masatsugu ! Version:: $Id: historyfileio_3d_dry.f90,v 1.3 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 ! !ファイル出力. 長い時間ステップの値を出力. ! !== Error Handling ! !== Known Bugs ! !== Note ! !== Future Plans ! module HistoryFileIO_3d_dry ! !ファイル出力. 長い時間ステップの値を出力. ! !モジュール読み込み use dc_types, only: DP use gtool_history, only: HistoryCreate, HistoryPut, HistoryAddVariable, & & HistoryClose, gt_history use dc_message, only: MessageNotify use gridset_3d,only: x_X, &!X 座標軸(スカラー格子点) & y_Y, &!Z 座標軸(スカラー格子点) & z_Z, &!Z 座標軸(スカラー格子点) & FileNX, &!X 方向の格子点(ファイル出力) & FileNY, &!Y 方向の格子点(ファイル出力) & FileNZ, &!Z 方向の格子点(ファイル出力) & FileXMin, &!X 方向の配列の下限(ファイル出力) & FileXMax, &!X 方向の配列の上限(ファイル出力) & FileYMin, &!Y 方向の配列の下限(ファイル出力) & FileYMax, &!Y 方向の配列の上限(ファイル出力) & FileZMin, &!Z 方向の配列の下限(ファイル出力) & FileZMax, &!Z 方向の配列の上限(ファイル出力) & DimXMin, &!X 方向の配列の下限 & DimXMax, &!X 方向の配列の上限 & DimYMin, &!Y 方向の配列の下限 & DimYMax, &!Y 方向の配列の上限 & DimZMin, &!Z 方向の配列の下限 & DimZMax, &!Z 方向の配列の上限 & SpcNum !凝縮成分の数 use basicset_3d, only: xyz_ExnerBasicZ, &!基本場のエクスナー関数 & xyz_DensBasicZ, &!基本場の密度 & xyz_PotTempBasicZ, &!基本場の温位 & xyz_VelSoundBasicZ, &!基本場の音速 & xyz_PressBasicZ, &!基本場の圧力 & xyz_TempBasicZ, &!基本場の温度 ! & xyza_MixRtBasicZ, &!基本場の混合比 ! & xyz_EffMolWtBasicZ, &!基本場の分子量効果 & SpcWetSymbol !湿潤成分の化学種名 use fileset_3d, only: HistoryFile, &!ヒストリファイル名 & exptitle, &!データの表題 & expsrc, &!データを作成する手順 & expinst, &!最終変更者・組織 & FileNum, &!ヒストリファイルの数 & gt_hist !gt_history 型構造体変数 use StorePotTemp_3d, only: StorePotTempMeanXY, & & z_Adv, z_Turb, z_Disp, z_Diff, & & z_Rad, z_Cond, z_Flux,z_Damp !暗黙の型宣言禁止 implicit none !属性の指定 private !関数を public に指定 public HistoryFile_Open public HistoryFile_OutPut public HistoryFile_Close contains !!!------------------------------------------------------------------------ subroutine HistoryFile_Open( ) ! !ヒストリファイルの定義 ! !暗黙の型宣言禁止 implicit none !変数定義 integer :: s ! ループ添字 !----------------------------------------------------------- ! ヒストリー作成 !----------------------------------------------------------- call MessageNotify ( "M", & & "HistoryFile_Open", & & "HistoryCreate" ) do s = 1, FileNum call HistoryCreate( & & file = HistoryFile(s), & & title = exptitle, & & source = expsrc, & & institution = expinst, & & dims=(/'x','y','z','t'/), & & dimsizes=(/FileNX, FileNY, FileNZ, 0/), & & longnames=(/'X-coordinate', & & 'Y-coordinate', & & 'Z-coordinate', & & 'Time '/), & & units=(/'m ','m ','m ','sec'/), origin=0.0, & & xtypes=(/'double', 'double', 'double', 'double'/), & & interval=0.0, & & history=gt_hist(s), quiet=.true. ) call HistoryPut('x', x_X( FileXMin: FileXMax ), gt_hist(s) ) call HistoryPut('y', y_Y( FileYMin: FileYMax ), gt_hist(s) ) call HistoryPut('z', z_Z( FileZMin: FileZMax ), gt_hist(s) ) end do !----------------------------------------------------------- ! 予報変数の出力 !----------------------------------------------------------- call MessageNotify ( "M", & & "HistoryFile_Open", & & "HistoryAddVariable" ) !無次元圧力の擾乱 call HistoryAddVariable( & & varname='Exner', & & dims=(/'x','y','z','t'/), & & longname='disturbunce of nondimensional pressure', & & units=' ', & & xtype='double', & & history=gt_hist(1) ) !温位の擾乱 call HistoryAddVariable( & & varname='PotTemp', & & dims=(/'x','y','z','t'/), & & longname='disturbunce of potential temperature', & & units='K', & & xtype='double', & & history=gt_hist(2) ) !水平速度 call HistoryAddVariable( & & varname='VelX', & & dims=(/'x','y','z','t'/), & & longname='zonal velocity', & & units='m.s-1', & & xtype='double', & & history=gt_hist(3) ) !水平速度 call HistoryAddVariable( & & varname='VelY', & & dims=(/'x','y','z','t'/), & & longname='meridional velocity', & & units='m.s-1', & & xtype='double', & & history=gt_hist(4) ) !鉛直速度 call HistoryAddVariable( & & varname='VelZ', & & dims=(/'x','y','z','t'/), & & longname='vertical velocity', & & units='m.s-1', & & xtype='double', & & history=gt_hist(5) ) !渦粘性係数(運動量) call HistoryAddVariable( & & varname='Km', & & dims=(/'x','y','z','t'/), & & longname='turbulet diffusion coefficient', & & units='m2.s-1', & & xtype='double', & & history=gt_hist(6) ) !渦粘性係数(熱) call HistoryAddVariable( & & varname='Kh', & & dims=(/'x','y','z','t'/), & & longname='turbulet diffusion coefficient for heat', & & units='m2.s-1', & & xtype='double', & & history=gt_hist(7) ) call HistoryAddVariable( & & varname='VorX', & & dims=(/'x','y','z','t'/), & & longname='vorticity', & & units='m.s-1', & & xtype='double', & & history=gt_hist(10) ) call HistoryAddVariable( & & varname='VorY', & & dims=(/'x','y','z','t'/), & & longname='vorticity', & & units='m.s-1', & & xtype='double', & & history=gt_hist(11) ) call HistoryAddVariable( & & varname='VorZ', & & dims=(/'x','y','z','t'/), & & longname='vorticity', & & units='m.s-1', & & xtype='double', & & history=gt_hist(12) ) !---------------------------------------------------------------- ! Stored Mixing Ratio !---------------------------------------------------------------- do s = 1, SpcNum call HistoryAddVariable( & & varname=trim(SpcWetSymbol(s))//'_Mean', & & dims=(/'z','t'/), & & longname='Horiizontal Mean of ' & & //trim(SpcWetSymbol(s))//' Mixing Ratio', & & units='kg.kg-1', & & xtype='double', & & history=gt_hist(12+s) ) end do !---------------------------------------------------------------- ! 静的安定度 !---------------------------------------------------------------- call HistoryAddVariable( & & varname='Stab', & & dims=(/'z','t'/), & & longname='Static Stability', & & units='s-2', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname='StabTemp', & & dims=(/'z','t'/), & & longname='Static Stability contributed by temperature', & & units='s-2', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname='StabMolWt', & & dims=(/'z','t'/), & & longname='Static Stability contributed by Molecular Weight',& & units='s-2', & & xtype='double', & & history=gt_hist(9) ) !---------------------------------------------------------------- ! 温位の時間変化 !---------------------------------------------------------------- call HistoryAddVariable( & & varname='PotTempAdv', & & dims=(/'z','t'/), & & longname='Advection term of potential temperature', & & units='K.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname='PotTempTurb',& & dims=(/'z','t'/), & & longname='Turbulence term of potential temperature', & & units='K.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname='PotTempDisp',& & dims=(/'z','t'/), & & longname='Dissipation term of potential temperature', & & units='K.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname='PotTempRad', & & dims=(/'z','t'/), & & longname='Radiation term of potential temperature', & & units='K.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname='PotTempDiff',& & dims=(/'z','t'/), & & longname='Numerical diffusion term of potential temperature',& & units='K.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname='PotTempCond',& & dims=(/'z','t'/), & & longname='Latent heat term of potential temperature', & & units='K.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname='PotTempFlux',& & dims=(/'z','t'/), & & longname='Surface Flux term of potential temperature', & & units='K.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname='PotTempDamp',& & dims=(/'z','t'/), & & longname='Newtonian Cooling term of potential temperature', & & units='K.s-1', & & xtype='double', & & history=gt_hist(9) ) !---------------------------------------------------------------- ! Mixing Ratio time change !---------------------------------------------------------------- do s = 1, SpcNum call HistoryAddVariable( & & varname=trim(SpcWetSymbol(s))//'_Adv', & & dims=(/'z','t'/), & & longname='Advection term of ' & & //trim(SpcWetSymbol(s))//' mixing ratio', & & units='kg.kg-1.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname=trim(SpcWetSymbol(s))//'_Turb', & & dims=(/'z','t'/), & & longname='Turbulence term of ' & & //trim(SpcWetSymbol(s))//' mixing ratio', & & units='kg.kg-1.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname=trim(SpcWetSymbol(s))//'_Diff', & & dims=(/'z','t'/), & & longname='Diffusion term of ' & & //trim(SpcWetSymbol(s))//' mixing ratio', & & units='kg.kg-1.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname=trim(SpcWetSymbol(s))//'_Flux', & & dims=(/'z','t'/), & & longname='Surface Flux term of ' & & //trim(SpcWetSymbol(s))//' mixing ratio', & & units='kg.kg-1.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname=trim(SpcWetSymbol(s))//'_Rain', & & dims=(/'z','t'/), & & longname='Fall Rain term of ' & & //trim(SpcWetSymbol(s))//' mixing ratio', & & units='kg.kg-1.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname=trim(SpcWetSymbol(s))//'_Fill1', & & dims=(/'z','t'/), & & longname='Filling Negative term 1 of ' & & //trim(SpcWetSymbol(s))//' mixing ratio', & & units='kg.kg-1.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname=trim(SpcWetSymbol(s))//'_Fill2', & & dims=(/'z','t'/), & & longname='Filling Negative term 2 of ' & & //trim(SpcWetSymbol(s))//' mixing ratio', & & units='kg.kg-1.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname=trim(SpcWetSymbol(s))//'_Cond', & & dims=(/'z','t'/), & & longname='Condensation term of ' & & //trim(SpcWetSymbol(s))//' mixing ratio', & & units='kg.kg-1.s-1', & & xtype='double', & & history=gt_hist(9) ) call HistoryAddVariable( & & varname=trim(SpcWetSymbol(s))//'_Asln', & & dims=(/'z','t'/), & & longname='Asselin time filter term of ' & & //trim(SpcWetSymbol(s))//' mixing ratio', & & units='kg.kg-1.s-1', & & xtype='double', & & history=gt_hist(9) ) end do !----------------------------------------------------------- ! 基本場の出力 !----------------------------------------------------------- !無次元圧力の基本場 call HistoryAddVariable( & & varname='ExnerBasicZ',& & dims=(/'x','y','z'/), & & longname='nondimensional pressure', units='1',& & xtype='double', & & history=gt_hist(8) ) !温位の基本場 call HistoryAddVariable( & & varname='PotTempBasicZ',& & dims=(/'x','y','z'/), & & longname='potential temperature', & & units='K', & & xtype='double', & & history=gt_hist(8) ) !仮温位の基本場 ! call HistoryAddVariable( & ! & varname='VPotTempBasicZ',& ! & dims=(/'x','y','z'/), & ! & longname='vertial potential temperature', & ! & units='K', & ! & xtype='double', & ! & history=gt_hist(8) ) !密度の基本場 call HistoryAddVariable( & & varname='DensBasicZ', & & dims=(/'x','y','z'/), & & longname='density', & & units='Kg.m-3', & & xtype='double', & & history=gt_hist(8) ) !音波速度の基本場 call HistoryAddVariable( & & varname='VelSoundBasicZ',& & dims=(/'x','y','z'/), & & longname='sound velocity',& & units='m.s-2', & & xtype='double', & & history=gt_hist(8) ) !温度の基本場 call HistoryAddVariable( & & varname='TempBasicZ', & & dims=(/'x','y','z'/), & & longname='Temperature of basic state', & & units='K', & & xtype='double', & & history=gt_hist(8) ) !圧力の基本場 call HistoryAddVariable( & & varname='PressBasicZ',& & dims=(/'x','y','z'/), & & longname='Pressure of basic state', & & units='Pa', & & xtype='double', & & history=gt_hist(8) ) !混合比の基本場 ! do s = 1, SpcNum ! call HistoryAddVariable( & ! & varname=trim(SpcWetSymbol(s))//'BasicZ',& ! & dims=(/'x','y','z'/), & ! & longname=trim(SpcWetSymbol(s))//' Mixing Ratio of basic state', & ! & units='kg.kg-1', & ! & xtype='double', & ! & history=gt_hist(8) ) ! end do !分子量効果 ! call HistoryAddVariable( & ! & varname='EffMolWtBasicZ', & ! & dims=(/'x','y','z'/), & ! & longname='Effect of Mole Weight', & ! & units='1', & ! & xtype='double', & ! & history=gt_hist(8) ) !------------------------------------------------------------- ! 基本場のファイル出力 !------------------------------------------------------------- call MessageNotify ( "M", & & "HistoryFile_Open", & & "HistoryPut (BasicZ)" ) call HistoryPut( & & 'DensBasicZ', & & xyz_DensBasicZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(8) ) call HistoryPut( & & 'ExnerBasicZ', & & xyz_ExnerBasicZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(8) ) call HistoryPut( & & 'PotTempBasicZ',& & xyz_PotTempBasicZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(8) ) ! call HistoryPut( & ! & 'VPotTempBasicZ',& ! & xyz_PotTempBasicZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax) & ! & / xyz_EffMolWtBasicZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax),& ! & gt_hist(8) ) call HistoryPut( & & 'VelSoundBasicZ', & & xyz_VelSoundBasicZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(8) ) call HistoryPut( & & 'TempBasicZ', & & xyz_TempBasicZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(8) ) call HistoryPut( & & 'PressBasicZ', & & xyz_PressBasicZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(8) ) ! do s = 1, SpcNum ! call HistoryPut( & ! & trim(SpcWetSymbol(s))//'BasicZ', & ! & xyza_MixRtBasicZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax, s), & ! & gt_hist(8) ) ! end do ! call HistoryPut( & ! & 'EffMolWtBasicZ', & ! & xyz_EffMolWtBasicZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & ! & gt_hist(8) ) end subroutine HistoryFile_Open !!!--------------------------------------------------------------------------- subroutine HistoryFile_OutPut( & & Time, & & xyz_PotTemp, & & xyz_Exner, & & pyz_VelX, & & xqz_VelY, & & xyr_VelZ, & & xyz_Km, & & xyz_Kh & ) ! !予報変数のヒストリファイルへの出力. 出力時には半格子点の位置でプロット. ! !モジュール読み込み use xyz_module, only: xyz_avr_pyz, xyz_avr_xqz, xyz_avr_xyr, & & xyz_avr_xqr, xyz_avr_pyr, xyz_avr_pqz use xyz_deriv_module, only : xqr_dy_xyr, xqr_dz_xqz, & & pyr_dz_pyz, pyr_dx_xyr, & & pqz_dx_xqz, pqz_dy_pyz !暗黙の型宣言禁止 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) real(DP) :: xyz_VelX(DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP) :: xyz_VelY(DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP) :: xyz_VelZ(DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP) :: xyz_VorX(DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP) :: xyz_VorY(DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) real(DP) :: xyz_VorZ(DimXMin:DimXMax,DimYMin:DimYMax,DimZMin:DimZMax) integer :: s !---------------------------------------------------------------- ! 格子点位置を変換 !---------------------------------------------------------------- xyz_VelX = xyz_avr_pyz( pyz_VelX ) xyz_VelY = xyz_avr_xqz( xqz_VelY ) xyz_VelZ = xyz_avr_xyr( xyr_VelZ ) xyz_VorX = xyz_avr_xqr(xqr_dy_xyr( xyr_VelZ ) - xqr_dz_xqz( xqz_VelY )) xyz_VorY = xyz_avr_pyr(pyr_dz_pyz( pyz_VelX ) - pyr_dx_xyr( xyr_VelZ )) xyz_VorZ = xyz_avr_pqz(pqz_dx_xqz( xqz_VelY ) - pqz_dy_pyz( pyz_VelX )) !---------------------------------------------------------------- ! 値を出力 !---------------------------------------------------------------- do s = 1, 12 + SpcNum call HistoryPut( 't', Time, gt_hist(s) ) end do call HistoryPut( & & 'Exner', & & xyz_Exner(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(1) ) call HistoryPut( & & 'PotTemp', & & xyz_PotTemp(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(2) ) call HistoryPut( & & 'VelX', & & xyz_VelX(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(3) ) call HistoryPut( & & 'VelY', & & xyz_VelY(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(4) ) call HistoryPut( & & 'VelZ', & & xyz_VelZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(5) ) call HistoryPut( & & 'Km', & & xyz_Km(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(6) ) call HistoryPut( & & 'Kh', & & xyz_Kh(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(7) ) call HistoryPut( & & 'VorX', & & xyz_VorX(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(10) ) call HistoryPut( & & 'VorY', & & xyz_VorY(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(11) ) call HistoryPut( & & 'VorZ', & & xyz_VorZ(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax), & & gt_hist(12) ) ! do s = 1, SpcNum ! call HistoryPut( & ! & trim(SpcWetSymbol(s)), & ! & xyza_MixRt(FileXMin:FileXMax,FileYMin:FileYMax,FileZMin:FileZMax, s), & ! & gt_hist(9+s) ) ! end do !---------------------------------------------------------------- ! 解析値を出力 !---------------------------------------------------------------- call StorePotTempMeanXY() call HistoryPut( & & 'PotTempAdv', & & z_Adv(FileZMin:FileZMax), & & gt_hist(9) ) call HistoryPut( & & 'PotTempTurb', & & z_Turb(FileZMin:FileZMax), & & gt_hist(9) ) call HistoryPut( & & 'PotTempDisp', & & z_Disp(FileZMin:FileZMax), & & gt_hist(9) ) call HistoryPut( & & 'PotTempDiff', & & z_Diff(FileZMin:FileZMax),& & gt_hist(9) ) call HistoryPut( & & 'PotTempRad', & & z_Rad(FileZMin:FileZMax), & & gt_hist(9) ) call HistoryPut( & & 'PotTempCond', & & z_Cond(FileZMin:FileZMax), & & gt_hist(9) ) call HistoryPut( & & 'PotTempFlux', & & z_Flux(FileZMin:FileZMax), & & gt_hist(9) ) call HistoryPut( & & 'PotTempDamp', & & z_Damp(FileZMin:FileZMax), & & gt_hist(9) ) ! call HistoryPut( & ! & 'StabTemp', & ! & z_StabTemp(FileZMin:FileZMax), & ! & gt_hist(9) ) ! call HistoryPut( & ! & 'StabMolWt', & ! & z_StabMolWt(FileZMin:FileZMax), & ! & gt_hist(9) ) ! do s = 1, SpcNum ! call HistoryPut( & ! & trim(SpcWetSymbol(s))//'_Adv', & ! & za_Adv(FileZMin:FileZMax, s), & ! & gt_hist(9) ) ! call HistoryPut( & ! & trim(SpcWetSymbol(s))//'_Turb', & ! & za_Turb(FileZMin:FileZMax, s), & ! & gt_hist(9) ) ! call HistoryPut( & ! & trim(SpcWetSymbol(s))//'_Diff', & ! & za_Diff(FileZMin:FileZMax, s), & ! & gt_hist(9) ) ! call HistoryPut( & ! & trim(SpcWetSymbol(s))//'_Flux', & ! & za_Flux(FileZMin:FileZMax, s), & ! & gt_hist(9) ) ! call HistoryPut( & ! & trim(SpcWetSymbol(s))//'_Rain', & ! & za_Rain(FileZMin:FileZMax, s), & ! & gt_hist(9) ) ! call HistoryPut( & ! & trim(SpcWetSymbol(s))//'_Fill1', & ! & za_Fill1(FileZMin:FileZMax, s), & ! & gt_hist(9) ) ! call HistoryPut( & ! & trim(SpcWetSymbol(s))//'_Fill2', & ! & za_Fill2(FileZMin:FileZMax, s), & ! & gt_hist(9) ) ! call HistoryPut( & ! & trim(SpcWetSymbol(s))//'_Cond', & ! & za_cond(FileZMin:FileZMax, s), & ! & gt_hist(9) ) ! call HistoryPut( & ! & trim(SpcWetSymbol(s))//'_Asln', & ! & za_Asln(FileZMin:FileZMax, s), & ! & gt_hist(9) ) ! end do end subroutine HistoryFile_OutPut !!!-------------------------------------------------------------------------- subroutine HistoryFile_Close ! !ヒストリファイルのクローズ ! !暗黙の型宣言禁止 implicit none !変数定義 integer :: s ! ループ添字 !ファイルを閉じる do s = 1, FileNum call HistoryClose(gt_hist(s),quiet=.true.) end do end subroutine HistoryFile_Close end module HistoryFileIO_3d_dry