Path: | main/dcpam_main.F90 |
Last Update: | Wed Mar 18 18:40:37 +0900 2009 |
Authors: | Yasuhiro MORIKAWA |
Version: | $Id: dcpam_main.F90,v 1.35 2009-03-18 09:40:37 morikawa Exp $ |
Tag Name: | $Name: dcpam5-20090319 $ |
Copyright: | Copyright (C) GFD Dennou Club, 2008-2009. All rights reserved. |
License: | See COPYRIGHT |
Main Program : |
Note that Japanese and English are described in parallel.
以下のいずれかの計算を行います. 切り替えについては チュートリアル を 参照してください.
Following any calculation is performed. See Tutorial for switch of them.
This procedure input/output NAMELIST#dcpam_main_nml .
program dcpam_main ! ! <b>Note that Japanese and English are described in parallel.</b> ! ! 以下のいずれかの計算を行います. 切り替えについては ! {チュートリアル}[link:../../../doc/tutorial/rakuraku/] を ! 参照してください. ! ! * 水惑星, すなわち全球が水に覆われているような惑星大気の計算 ! * Held and Suarez (1994) ベンチマークテスト ! ! Following any calculation is performed. ! See {Tutorial}[link:../../../doc/tutorial/rakuraku/index.htm.en] ! for switch of them. ! ! * Calculation of atmosphere on a planet covered with water globally ! * Held and Suarez (1994) benchmark test ! !== References ! ! * Held, I. M., Suarez, M. J., 1994: ! A proposal for the intercomparison of the dynamical cores of ! atmospheric general circuation models. ! <i>Bull. Am. Meteor. Soc.</i>, <b>75</b>, 1825--1830. ! ! モジュール引用 ; USE statements ! ! 力学過程 (スペクトル法, Arakawa and Suarez (1983)) ! Dynamical process (Spectral method, Arakawa and Suarez (1983)) ! use dynamics_hspl_vas83, only: Dynamics ! Held and Suarez (1994) による強制と散逸 ! Forcing and dissipation suggested by Held and Suarez (1994) ! use held_suarez_1994, only: Hs94Forcing ! 放射フラックス (バンドモデル) ! Radiation flux (band model) ! use radiation_band, only: RadiationFlux, RadiationDTempDt, RadiationFluxOutput ! 鉛直拡散フラックス (Mellor and Yamada, 1974, レベル 2) ! Vertical diffusion flux (Mellor and Yamada, 1974, Level 2) ! use vdiffusion_my1974, only: VerticalDiffusion, VerticalDiffusionOutput ! 積雲パラメタリゼーション (対流調節) ! Cumulus parameterization (convection adjust) ! use cumulus_adjust, only: Cumulus ! 大規模凝結 ! Large scale condensation ! use lscond, only: LScaleCond ! 地表面フラックス ! Surface flux use surface_flux_bulk, only: SurfaceFlux, SurfaceFluxOutput ! 乾燥対流調節 ! Dry convective adjustment ! use dryconv_adjust, only: DryConvectAdjust ! 負の水蒸気除去 ! Remove negative moisture ! use negative_moist, only: RemoveNegMoist ! 温度の半整数σレベルの補間, 気圧と高度の算出 ! Interpolate temperature on half sigma level, ! and calculate pressure and height ! use auxiliary, only: AuxVars ! 陰解法のための行列処理 (一部の物理過程用) ! Matrices handling for implicit scheme (for a part of physical processes) ! use phy_implicit, only: PhyImplTendency, PhyImplEvalRadLFluxA ! 地面温度の時間積分・地表面放射補正 ! Time integration of surface temperature, correction of flux on surface ! use intg_surftemp, only: IntegralSurfTemp ! タイムフィルター (Asselin, 1972) ! Time filter (Asselin, 1972) ! use timefilter_asselin1972, only: TimeFilter ! 時刻管理 ! Time control ! use timeset, only: TimesetProgress, TimeN, TimeA, EndTime, DelTime ! $ \Delta t $ [s] ! リスタートデータ入出力 ! Restart data input/output ! use restart_file_io, only: RestartFileOutPut ! 地表面温度リスタートデータ入出力 ! Restart data of surface temperature input/output ! use restart_surftemp_io, only: RestartSurfTempOutPut ! 地表面データファイルの入力 ! Ground data file input ! use ground_file_io, only: GroundFileGet ! ヒストリデータ出力 ! History data output ! use gtool_historyauto, only: HistoryAutoPut, HistoryAutoAllVarFix ! 格子点設定 ! Grid points settings ! use gridset, only: imax, jmax, kmax ! 鉛直層数. ! Number of vertical level ! 日付および時刻の取り扱い ! Date and time handler ! use dc_date, only: operator(==), operator(<), operator(>), operator(<=), operator(>=), operator(+), operator(-), operator(*), operator(/), DCDiffTimePutLine ! 種別型パラメタ ! Kind type parameter ! use dc_types, only: DP, STRING, TOKEN ! キーワード. Keywords. #ifdef LIB_MPI ! MPI ライブラリ ! MPI library ! use mpi #endif ! 宣言文 ; Declaration statements ! implicit none ! 予報変数 (ステップ $ t-\Delta t $ , $ t $ , $ t+\Delta t $ ) ! Prediction variables (Step $ t-\Delta t $ , $ t $ , $ t+\Delta t $ ) ! real(DP), allocatable:: xyz_UB (:,:,:) ! $ u (t-\Delta t) $ . 東西風速. Eastward wind real(DP), allocatable:: xyz_VB (:,:,:) ! $ v (t-\Delta t) $ . 南北風速. Northward wind real(DP), allocatable:: xyz_TempB (:,:,:) ! $ T (t-\Delta t) $ . 温度. Temperature real(DP), allocatable:: xyz_QVapB (:,:,:) ! $ q (t-\Delta t) $ . 比湿. Specific humidity real(DP), allocatable:: xy_PsB (:,:) ! $ p_s (t-\Delta t) $ . 地表面気圧. Surface pressure real(DP), allocatable:: xyz_UN (:,:,:) ! $ u (t) $ . 東西風速. Eastward wind real(DP), allocatable:: xyz_VN (:,:,:) ! $ v (t) $ . 南北風速. Northward wind real(DP), allocatable:: xyz_TempN (:,:,:) ! $ T (t) $ . 温度. Temperature real(DP), allocatable:: xyz_QVapN (:,:,:) ! $ q (t) $ . 比湿. Specific humidity real(DP), allocatable:: xy_PsN (:,:) ! $ p_s (t) $ . 地表面気圧. Surface pressure real(DP), allocatable:: xyz_UA (:,:,:) ! $ u (t+\Delta t) $ . 東西風速. Eastward wind real(DP), allocatable:: xyz_VA (:,:,:) ! $ v (t+\Delta t) $ . 南北風速. Northward wind real(DP), allocatable:: xyz_TempA (:,:,:) ! $ T (t+\Delta t) $ . 温度. Temperature real(DP), allocatable:: xyz_QVapA (:,:,:) ! $ q (t+\Delta t) $ . 比湿. Specific humidity real(DP), allocatable:: xy_PsA (:,:) ! $ p_s (t+\Delta t) $ . 地表面気圧. Surface pressure ! 診断変数, 他 ! Diagnostic variables, etc. ! real(DP), allocatable:: xyz_DUDt (:,:,:) ! $ \DP{u}{t} $ . 東西風速変化. ! Eastward wind tendency real(DP), allocatable:: xyz_DVDt (:,:,:) ! $ \DP{v}{t} $ . 南北風速変化. ! Northward wind tendency real(DP), allocatable:: xyz_DTempDt (:,:,:) ! $ \DP{T}{t} $ . 温度変化. ! Temperature tendency real(DP), allocatable:: xyz_DQVapDt (:,:,:) ! $ \DP{q}{t} $ . 比湿変化. ! Temperature tendency real(DP), allocatable:: xy_SurfHeight (:,:) ! $ z_s $ . 地表面高度. ! Surface height. real(DP), allocatable:: xy_SurfTemp (:,:) ! 地表面温度. ! Surface temperature real(DP), allocatable:: xy_SurfAlbedo (:,:) ! 地表アルベド. ! Surface albedo real(DP), allocatable:: xy_SurfHumidCoef (:,:) ! 地表湿潤度. ! Surface humidity coefficient real(DP), allocatable:: xy_SurfRoughLength (:,:) ! 地表粗度長. ! Surface rough length real(DP), allocatable:: xy_SurfHeatCapacity (:,:) ! 地表熱容量. ! Surface heat capacity integer, allocatable:: xy_SurfCond (:,:) ! 地表状態 (0: 固定, 1: 可変). ! Surface condition (0: fixed, 1: variable) real(DP), allocatable:: xy_GroundTempFlux (:,:) ! 地中熱フラックス. ! Ground temperature flux real(DP), allocatable:: xyr_Temp (:,:,:) ! $ \hat{T} $ . 温度 (半整数レベル). ! Temperature (half level) real(DP), allocatable:: xyz_Press (:,:,:) ! $ p $ . 気圧 (整数レベル). ! Air pressure (full level) real(DP), allocatable:: xyr_Press (:,:,:) ! $ \hat{p} $ . 気圧 (半整数レベル). ! Air pressure (half level) real(DP), allocatable:: xyz_Height (:,:,:) ! 高度 (整数レベル). ! Height (full level) real(DP), allocatable:: xyr_Height (:,:,:) ! 高度 (半整数レベル). ! Height (half level) real(DP), allocatable:: xyz_Exner (:,:,:) ! Exner 関数 (整数レベル). ! Exner function (full level) real(DP), allocatable:: xyr_Exner (:,:,:) ! Exner 関数 (半整数レベル). ! Exner function (half level) real(DP), allocatable:: xyr_RadLFlux (:,:,:) ! 長波フラックス. ! Longwave flux real(DP), allocatable:: xyr_RadLFluxA (:,:,:) ! $ t-\Delta t $ における変化率を元に ! 算出された $ t+\Delta t $ における ! 長波フラックス. ! ただし, これが直接次のステップ $ t $ における ! 長波フラックスとして用いられるわけではない. ! ! Longwave flux at $ t+\Delta t $ ! calculated from the tendency at ! $ t-\Delta t $ . ! However, this is not used directly as ! Longwave flux at next step $ t $ . ! real(DP), allocatable:: xyr_RadSFlux (:,:,:) ! 短波 (日射) フラックス. ! Shortwave (insolation) flux real(DP), allocatable:: xyra_DelRadLFlux (:,:,:,:) ! 長波地表温度変化. ! Surface temperature tendency with longwave real(DP), allocatable:: xyr_UFlux (:,:,:) ! 東西風速フラックス. ! Eastward wind flux real(DP), allocatable:: xyr_VFlux (:,:,:) ! 南北風速フラックス. ! Northward wind flux real(DP), allocatable:: xyr_TempFlux (:,:,:) ! 温度フラックス. ! Temperature flux real(DP), allocatable:: xyr_QVapFlux (:,:,:) ! 比湿フラックス. ! Specific humidity flux real(DP), allocatable:: xyr_VelTransCoef (:,:,:) ! 輸送係数:運動量. ! Transfer coefficient: velocity real(DP), allocatable:: xyr_TempTransCoef (:,:,:) ! 輸送係数:温度. ! Transfer coefficient: temperature real(DP), allocatable:: xyr_QVapTransCoef (:,:,:) ! 輸送係数:比湿. ! Transfer coefficient: specific humidity real(DP), allocatable:: xy_SurfVelTransCoef (:,:) ! 輸送係数:運動量. ! Diffusion coefficient: velocity real(DP), allocatable:: xy_SurfTempTransCoef (:,:) ! 輸送係数:温度. ! Transfer coefficient: temperature real(DP), allocatable:: xy_SurfQVapTransCoef (:,:) ! 輸送係数:比湿. ! Transfer coefficient: specific humidity real(DP), allocatable:: xy_DSurfTempDt (:,:) ! 地表面温度変化率. ! Surface temperature tendency real(DP), allocatable:: xyz_DTempDtRadL (:,:,:) ! 長波加熱率. ! Temperature tendency with longwave real(DP), allocatable:: xyz_DTempDtRadS (:,:,:) ! 短波加熱率. ! Temperature tendency with shortwave real(DP), allocatable:: xy_Rain (:,:) ! 降水量. ! Precipitation real(DP), allocatable:: xyz_DTempDtCond (:,:,:) ! 凝結加熱率. ! Condensation heating real(DP), allocatable:: xyz_DQVapDtCond (:,:,:) ! 凝結比湿変化. ! Condensation specific humidity tendency real(DP), allocatable:: xyz_DNegQVap1Dt (:,:,:) ! 負の水蒸気除去に関する比湿変化率 (1). ! Specific humidity tendency by elimination of negative moist (1) real(DP), allocatable:: xyz_DNegQVap2Dt (:,:,:) ! 負の水蒸気除去に関する比湿変化率 (2). ! Specific humidity tendency by elimination of negative moist (2) ! 作業変数 ! Work variables ! logical:: FlagAPE ! 物理過程 (APE) 計算オン/オフ. ! Physical processes (APE) calculation on/off. logical:: FlagHS94 ! Held and Suarez (1994) 強制オン/オフ. ! Held and Suarez (1994) forcing on/off. logical:: firstloop = .true. ! 初回のループであることを示すフラグ. ! Flag implying first loop logical:: flag_initial ! 内部サブルーチン MainInit で設定されます. ! リスタートデータを読み込む場合には, ! .false. が, 初期値データを読み込む場合には ! .true. が設定されます. ! ! This variable is set in an internal ! subroutine "MainInit". ! If restart data is loaded, .false. is set. ! On the other hand, if initial data is loaded, ! .true. is set. ! 実行文 ; Executable statement ! ! 主プログラムの初期化 (内部サブルーチン) ! Initialization for the main program (Internal subroutine) ! call MainInit ! 時間積分 ! Time integration ! do while ( TimeN <= EndTime ) if ( .not. FlagAPE ) then ! 地表面条件の設定 ! Configure surface conditions ! call GroundFileGet( xy_SurfHeight = xy_SurfHeight ) ! (inout) optional end if if ( FlagHS94 ) then ! Held and Suarez (1994) による強制と散逸 ! Forcing and dissipation suggested by Held and Suarez (1994) ! call Hs94Forcing( xyz_UB, xyz_VB, xyz_TempB, xy_PsB, xyz_DUDt, xyz_DVDt, xyz_DTempDt ) ! (out) xyz_DQVapDt = 0. end if if ( FlagAPE ) then ! 地表面条件の設定 ! Configure surface conditions ! call GroundFileGet( xy_SurfTemp, xy_SurfAlbedo, xy_SurfHumidCoef, xy_SurfRoughLength, xy_SurfHeatCapacity, xy_GroundTempFlux, xy_SurfCond, xy_SurfHeight ) ! (inout) optional ! 温度の半整数σレベルの補間, 気圧と高度の算出 ! Interpolate temperature on half sigma level, ! and calculate pressure and height ! call AuxVars( xy_PsB, xyz_TempB, xyr_Temp, xyr_Press = xyr_Press, xyz_Height = xyz_Height, xyr_Height = xyr_Height, xyz_Exner = xyz_Exner, xyr_Exner = xyr_Exner ) ! (out) optional ! 放射フラックス (バンドモデル) ! Radiation flux (band model) ! call RadiationFlux( xyz_TempB, xyz_QVapB, xyr_Press, xy_SurfTemp, xy_SurfAlbedo, xyr_RadLFlux, xyr_RadSFlux, xyra_DelRadLFlux, flag_rst = .not. flag_initial ) ! (in) optional ! 鉛直拡散フラックス ! Vertical diffusion flux ! call VerticalDiffusion( xyz_UB, xyz_VB, xyz_QVapB, xyz_TempB, xyr_Temp, xyr_Press, xyz_Height, xyr_Height, xyz_Exner, xyr_Exner, xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux, xyr_VelTransCoef, xyr_TempTransCoef, xyr_QVapTransCoef ) ! (out) ! 地表面フラックス ! Surface flux ! call SurfaceFlux( xyz_UB, xyz_VB, xyz_TempB, xyr_Temp, xyz_QVapB, xyr_Press, xyz_Height, xyz_Exner, xyr_Exner, xy_SurfTemp, xy_SurfHumidCoef, xy_SurfRoughLength, xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux, xy_SurfVelTransCoef, xy_SurfTempTransCoef, xy_SurfQVapTransCoef ) ! (out) ! 一部の物理過程の時間変化率の計算 (陰解法) ! Calculate tendency by a part of physical processes (implicit) ! call PhyImplTendency( xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux, xyr_RadSFlux, xyr_RadLFlux, xy_GroundTempFlux, xy_SurfTemp, xy_SurfHumidCoef, xy_SurfCond, xy_SurfHeatCapacity, xyra_DelRadLFlux, xyr_Press, xyz_Exner, xyr_Exner, xyr_VelTransCoef, xyr_TempTransCoef, xyr_QVapTransCoef, xy_SurfVelTransCoef, xy_SurfTempTransCoef, xy_SurfQVapTransCoef, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xyz_DQVapDt, xy_DSurfTempDt ) ! (out) ! 鉛直拡散フラックスの出力 ! * 出力のみのサブルーチンであり, 計算には影響しない ! ! Output Vertical diffusion fluxes ! * This subroutine works for output only, ! so it does not influence a calculation. ! call VerticalDiffusionOutput( xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xyz_DQVapDt, xyz_Exner, xyr_Exner, xyr_VelTransCoef, xyr_TempTransCoef, xyr_QVapTransCoef ) ! (in) ! 地表面フラックスの出力 ! * 出力のみのサブルーチンであり, 計算には影響しない ! ! Output surface fluxes ! * This subroutine works for output only, ! so it does not influence a calculation. ! call SurfaceFluxOutput( xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xyz_DQVapDt, xy_SurfTemp, xy_DSurfTempDt, xyr_Press, xyz_Exner, xyr_Exner, xy_SurfHumidCoef, xy_SurfVelTransCoef, xy_SurfTempTransCoef, xy_SurfQVapTransCoef ) ! (in) ! 放射フラックスの出力 ! * 出力のみのサブルーチンであり, 計算には影響しない ! ! Output radiation fluxes ! * This subroutine works for output only, ! so it does not influence a calculation. ! call RadiationFluxOutput( xyr_RadSFlux, xyr_RadLFlux, xyra_DelRadLFlux, xy_DSurfTempDt ) ! (in) ! $ t+\Delta t $ の長波フラックス算出 ! * ここで算出された値が直接次のステップ $ t $ における ! 長波フラックスとして用いられるわけではない ! ! Evaluate longwave flux at $ t+\Delta t $ ! * The evaluated value is not used directly as ! Longwave flux at next step $ t $ . ! call PhyImplEvalRadLFluxA( xyr_RadLFlux, xyz_DTempDt, xy_DSurfTempDt, xyra_DelRadLFlux, xyr_RadLFluxA ) ! (out) ! 放射による温度変化率 ! Temperature tendency with radiation ! call RadiationDTempDt( xyr_RadLFluxA, xyr_RadSFlux, xyr_Press, xyz_DTempDtRadL, xyz_DTempDtRadS ) ! (out) xyz_DTempDt = xyz_DTempDt + xyz_DTempDtRadL + xyz_DTempDtRadS ! 地面温度の時間積分・地表面放射補正 ! Time integration of surface temperature, correction of flux on surface ! call IntegralSurfTemp( xy_DSurfTempDt, xy_SurfTemp ) ! (inout) end if ! FlagAPE ! 力学過程 ! Dynamical core ! call Dynamics( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xyz_DQVapDt, xy_SurfHeight, xyz_UA, xyz_VA, xyz_TempA, xyz_QVapA, xy_PsA ) ! (out) if ( FlagAPE ) then ! 温度の半整数σレベルの補間, 気圧と高度の算出 ! Interpolate temperature on half sigma level, ! and calculate pressure and height ! call AuxVars( xy_PsA, xyz_TempA, xyz_Press = xyz_Press, xyr_Press = xyr_Press ) ! (out) optional ! 負の水蒸気除去 (1) ! Remove negative moisture (1) ! xyz_DNegQVap1Dt = 0. call RemoveNegMoist( xyr_Press = xyr_Press, xyz_QVap = xyz_QVapA, xyz_DNegQVapDt = xyz_DNegQVap1Dt ) ! (inout) ! 積雲パラメタリゼーション ! Cumulus parameterization ! xy_Rain = 0. xyz_DTempDtCond = 0. xyz_DQVapDtCond = 0. call Cumulus( xyz_TempA, xyz_QVapA, xy_Rain, xyz_DTempDtCond, xyz_DQVapDtCond, xyz_Press, xyr_Press ) ! (in) ! 大規模凝結 ! Large scale condensation ! call LScaleCond( xyz_TempA, xyz_QVapA, xy_Rain, xyz_DTempDtCond, xyz_DQVapDtCond, xyz_Press, xyr_Press ) ! (in) ! 乾燥対流調節 ! Dry convective adjustment ! call DryConvectAdjust( xyz_Press, xyr_Press, xyz_TempA ) ! (inout) ! 負の水蒸気除去 (2) ! Remove negative moisture (2) ! xyz_DNegQVap2Dt = 0. call RemoveNegMoist( xyr_Press = xyr_Press, xyz_QVap = xyz_QVapA, xyz_DNegQVapDt = xyz_DNegQVap2Dt ) ! (inout) end if ! FlagAPE ! 時間フィルター ! Time filter ! if ( .not. flag_initial .or. .not. firstloop ) then call TimeFilter( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN, xyz_UA, xyz_VA, xyz_TempA, xyz_QVapA, xy_PsA ) ! (in) end if ! ヒストリデータ出力 ! History data output ! call HistoryAutoPut( TimeA, 'U', xyz_UA ) call HistoryAutoPut( TimeA, 'V', xyz_VA ) call HistoryAutoPut( TimeA, 'Temp', xyz_TempA ) call HistoryAutoPut( TimeA, 'QVap', xyz_QVapA ) call HistoryAutoPut( TimeA, 'Ps', xy_PsA ) if ( FlagAPE ) then call HistoryAutoPut( TimeN, 'SurfTemp', xy_SurfTemp ) call HistoryAutoPut( TimeN, 'Rain', xy_Rain ) call HistoryAutoPut( TimeN, 'DTempDtCond', xyz_DTempDtCond ) call HistoryAutoPut( TimeN, 'DQVapDtCond', xyz_DQVapDtCond ) end if ! 予報変数の時刻付け替え ! Exchange time of prediction variables ! xyz_UB = xyz_UN xyz_UN = xyz_UA xyz_UA = 0. xyz_VB = xyz_VN xyz_VN = xyz_VA xyz_VA = 0. xyz_TempB = xyz_TempN xyz_TempN = xyz_TempA xyz_TempA = 0. xyz_QVapB = xyz_QVapN xyz_QVapN = xyz_QVapA xyz_QVapA = 0. xy_PsB = xy_PsN xy_PsN = xy_PsA xy_PsA = 0. ! 時刻の進行 ! Progress time ! call TimesetProgress ! NAMELIST から読み込んだ変数名に無効なものが存在したかどうかをチェック ! HistoryAutoAddVariable で登録した変数名を印字 ! ! Check that invalid variable names are loaded from NAMELIST or not ! Print registered variable names by "HistoryAutoAddVariable" ! if ( firstloop ) call HistoryAutoAllVarFix ! リスタートデータ出力 ! Restart data output ! call RestartFileOutput( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN ) ! (in) if ( FlagAPE ) then ! 地表面温度リスタートデータ出力 ! Restart data of surface temperature output ! call RestartSurfTempOutput( xy_SurfTemp ) ! (in) end if firstloop = .false. ! 時間積分終了 ! Time integration is finished ! end do ! 主プログラムの終了処理 (内部サブルーチン) ! Termination for the main program (Internal subroutine) ! call MainTerminate contains !------------------------------------------------------------------- subroutine MainInit ! ! 主プログラムの初期化手続き. ! ! Initialization procedure for the main program. ! #ifdef LIB_MPI ! メッセージ出力 ! Message output ! use dc_message, only: MessageSuppressMPI #endif use dc_message, only: MessageNotify ! コマンドライン引数処理 ! Command line option parser ! use option_parser, only: OptParseInit ! NAMELIST ファイル入力に関するユーティリティ ! Utilities for NAMELIST file input ! use namelist_util, only: NmlutilInit, NmlutilMsg, namelist_filename ! 時刻管理 ! Time control ! use timeset, only: TimesetInit, TimesetDelTimeHalf, TimeN ! ステップ $ t $ の時刻. Time of step $ t $. ! 出力ファイルの基本情報管理 ! Management basic information for output files ! use fileset, only: FilesetInit ! 格子点設定 ! Grid points settings ! use gridset, only: GridsetInit, imax, jmax, kmax ! 鉛直層数. ! Number of vertical level ! 物理定数設定 ! Physical constants settings ! use constants, only: ConstantsInit ! 座標データ設定 ! Axes data settings ! use axesset, only: AxessetInit ! リスタートデータ入出力 ! Restart data input/output ! use restart_file_io, only: RestartFileOpen, RestartFileGet ! 地表面温度リスタートデータ入出力 ! Restart data of surface temperature input/output ! use restart_surftemp_io, only: RestartSurfTempOpen, RestartSurfTempGet ! ヒストリデータ出力 ! History data output ! use history_file_io, only: HistoryFileOpen use gtool_historyauto, only: HistoryAutoAddVariable, HistoryAutoPut ! 種別型パラメタ ! Kind type parameter ! use dc_types, only: STDOUT ! 標準出力の装置番号. Unit number of standard output ! ファイル入出力補助 ! File I/O support ! use dc_iounit, only: FileOpen ! 宣言文 ; Declaration statements ! implicit none character(*), parameter:: prog_name = 'dcpam_main' ! 主プログラム名. ! Main program name character(*), parameter:: version = '$Name: dcpam5-20090319 $' // '$Id: dcpam_main.F90,v 1.35 2009-03-18 09:40:37 morikawa Exp $' ! 主プログラムのバージョン ! Main program version character(STRING):: brief ! 実行ファイルの簡潔な説明 ! Brief account of executable file integer:: unit_nml ! NAMELIST ファイルオープン用装置番号. ! Unit number for NAMELIST file open integer:: iostat_nml ! NAMELIST 読み込み時の IOSTAT. ! IOSTAT of NAMELIST read ! NAMELIST 変数群 ! NAMELIST group name ! namelist /dcpam_main_nml/ FlagAPE, FlagHS94 ! ! デフォルト値については初期化手続 "main/dcpam_main.F90#MainInit" ! のソースコードを参照のこと. ! ! Refer to source codes in the initialization procedure ! "main/dcpam_main.F90#MainInit" for the default values. ! #ifdef LIB_MPI integer :: myrank_mpi, nprocs_mpi, err_mpi ! MPI の初期化の際に使用される変数. ! Variables used for initialization of MPI. #endif ! 実行文 ; Executable statement ! #ifdef LIB_MPI ! MPI 初期化 ! Initialization of MPI ! CALL MPI_Init(err_mpi) CALL MPI_Comm_Rank(mpi_comm_world, myrank_mpi, err_mpi) CALL MPI_Comm_Size(mpi_comm_world, nprocs_mpi, err_mpi) #endif #ifdef LIB_MPI ! メッセージ出力 ! Message output ! call MessageSuppressMPI( rank = 0 ) #endif ! コマンドライン引数処理 ! Command line option parser ! call OptParseInit(prog_name) ! NAMELIST ファイル名入力 ! Input NAMELIST file name ! call NmlutilInit ! デフォルト値の設定 ! Default values settings ! FlagAPE = .true. FlagHS94 = .false. ! 計算モードの設定 ! Configure calculation mode ! if ( trim(namelist_filename) /= '' ) then call FileOpen( unit_nml, namelist_filename, mode = 'r' ) ! (in) rewind( unit_nml ) read( unit_nml, nml = dcpam_main_nml, iostat = iostat_nml ) ! (out) close( unit_nml ) call NmlutilMsg( iostat_nml, prog_name ) ! (in) if ( iostat_nml == 0 ) write( STDOUT, nml = dcpam_main_nml ) end if if ( FlagAPE .and. FlagHS94 ) then call MessageNotify( 'E', prog_name, 'FlagAPE=<%b> and FlagHS94=<%b> are conflicted.', l = (/FlagAPE, FlagHS94/) ) end if ! 計算モードの表示 ! Display calculation mode ! brief = '' if ( FlagHS94 ) brief = 'Held and Suarez (1994) benchmark test' if ( FlagAPE ) brief = 'Aqua Planet Experiment' if ( trim(brief) == '' ) brief = 'Only Dynamical process' call MessageNotify( 'M', prog_name, '' ) call MessageNotify( 'M', prog_name, '+-------------------------------------' ) call MessageNotify( 'M', prog_name, '| Run: %c', c1 = trim(brief) ) call MessageNotify( 'M', prog_name, '| -- version = %c', c1 = trim(version) ) call MessageNotify( 'M', prog_name, '+-------------------------------------' ) call MessageNotify( 'M', prog_name, '' ) ! 時刻管理 ! Time control ! call TimesetInit ! 出力ファイルの基本情報管理 ! Management basic information for output files ! call FilesetInit ! 格子点設定 ! Grid points settings ! call GridsetInit ! 物理定数設定 ! Physical constants settings ! call ConstantsInit ! 座標データ設定 ! Axes data settings ! call AxessetInit ! 予報変数の割付 ! Allocation of prediction variables ! allocate( xyz_UB (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_VB (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_TempB (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_QVapB (0:imax-1, 1:jmax, 1:kmax) ) allocate( xy_PsB (0:imax-1, 1:jmax) ) allocate( xyz_UN (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_VN (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_TempN (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_QVapN (0:imax-1, 1:jmax, 1:kmax) ) allocate( xy_PsN (0:imax-1, 1:jmax) ) allocate( xyz_UA (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_VA (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_TempA (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_QVapA (0:imax-1, 1:jmax, 1:kmax) ) allocate( xy_PsA (0:imax-1, 1:jmax) ) ! リスタートデータ入力 ! Restart data input ! call RestartFileGet( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN, flag_initial ) ! (out) optional ! リスタートデータファイルの初期化 ! Initialization of restart data file ! call RestartFileOpen ! ヒストリデータファイルの初期化 ! Initialization of history data files ! call HistoryFileOpen ! ヒストリデータ出力のためのへの変数登録 ! Register of variables for history data output ! call HistoryAutoAddVariable( 'U' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'eastward wind', 'm s-1' ) ! (in) call HistoryAutoAddVariable( 'V' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'northward wind', 'm s-1' ) ! (in) call HistoryAutoAddVariable( 'Temp' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'temperature', 'K' ) ! (in) call HistoryAutoAddVariable( 'QVap' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'specific humidity', 'kg kg-1' ) ! (in) call HistoryAutoAddVariable( 'Ps' , (/ 'lon ', 'lat ', 'time' /), 'surface pressure', 'Pa' ) ! (in) ! ヒストリデータ出力 (スタート時刻) ! History data output (Start time) ! call HistoryAutoPut( TimeN, 'U', xyz_UN ) call HistoryAutoPut( TimeN, 'V', xyz_VN ) call HistoryAutoPut( TimeN, 'Temp', xyz_TempN ) call HistoryAutoPut( TimeN, 'QVap', xyz_QVapN ) call HistoryAutoPut( TimeN, 'Ps', xy_PsN ) if ( FlagAPE ) then ! 地表面温度の割付 ! Allocation of surface temperature ! allocate( xy_SurfTemp (0:imax-1, 1:jmax) ) ! 地表面温度リスタートデータ入力 ! Restart data of surface temperature input ! call RestartSurfTempGet( xy_SurfTemp ) ! (out) ! 地表面温度リスタートデータファイルの初期化 ! Initialization of restart data file of surface temperature ! call RestartSurfTempOpen ! ヒストリデータ出力のためのへの変数登録 ! Register of variables for history data output ! call HistoryAutoAddVariable( 'SurfTemp' , (/ 'lon ', 'lat ', 'time' /), 'surface temperature', 'K' ) call HistoryAutoAddVariable( 'Rain', (/ 'lon ', 'lat ', 'time' /), 'precipitation', 'W m-2' ) call HistoryAutoAddVariable( 'DTempDtCond' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'condensation heating', 'K s-1' ) call HistoryAutoAddVariable( 'DQVapDtCond' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'condensation moistening', 'kg kg-1 s-1' ) end if ! FlagAPE ! 診断変数の割付 ! Allocation of diagnostic variables ! allocate( xyz_DUDt (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DVDt (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DTempDt (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DQVapDt (0:imax-1, 1:jmax, 1:kmax) ) allocate( xy_SurfHeight (0:imax-1, 1:jmax) ) if ( FlagAPE ) then allocate( xy_SurfAlbedo (0:imax-1, 1:jmax) ) allocate( xy_SurfHumidCoef (0:imax-1, 1:jmax) ) allocate( xy_SurfRoughLength (0:imax-1, 1:jmax) ) allocate( xy_SurfHeatCapacity (0:imax-1, 1:jmax) ) allocate( xy_SurfCond (0:imax-1, 1:jmax) ) allocate( xy_GroundTempFlux (0:imax-1, 1:jmax) ) allocate( xyr_Temp (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyz_Press (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyr_Press (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyz_Height (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyr_Height (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyz_Exner (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyr_Exner (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_RadLFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_RadLFluxA (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_RadSFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyra_DelRadLFlux (0:imax-1, 1:jmax, 0:kmax, 0:1) ) allocate( xyr_UFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_VFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_TempFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_QVapFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_VelTransCoef (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_TempTransCoef (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_QVapTransCoef (0:imax-1, 1:jmax, 0:kmax) ) allocate( xy_SurfVelTransCoef (0:imax-1, 1:jmax) ) allocate( xy_SurfTempTransCoef (0:imax-1, 1:jmax) ) allocate( xy_SurfQVapTransCoef (0:imax-1, 1:jmax) ) allocate( xy_DSurfTempDt (0:imax-1, 1:jmax) ) allocate( xyz_DTempDtRadL (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DTempDtRadS (0:imax-1, 1:jmax, 1:kmax) ) allocate( xy_Rain (0:imax-1, 1:jmax) ) allocate( xyz_DTempDtCond (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DQVapDtCond (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DNegQVap1Dt (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DNegQVap2Dt (0:imax-1, 1:jmax, 1:kmax) ) end if ! FlagAPE ! 初回だけはオイラー法を用いるため, Δt を半分に ! Delta t is reduced to half in order to use Euler method at initial step ! if ( flag_initial ) then call TimesetDelTimeHalf end if end subroutine MainInit !------------------------------------------------------------------- subroutine MainTerminate ! ! 主プログラムの終了処理手続き. ! ! Termination procedure for the main program. ! ! モジュール引用 ; USE statements ! ! 力学過程 (スペクトル法, Arakawa and Suarez (1983)) ! Dynamical process (Spectral method, Arakawa and Suarez (1983)) ! use dynamics_hspl_vas83, only: DynamicsFinalize ! Held and Suarez (1994) による強制と散逸 ! Forcing and dissipation suggested by Held and Suarez (1994) ! use held_suarez_1994, only: Hs94Finalize ! 放射フラックス (バンドモデル) ! Radiation flux (band model) ! use radiation_band, only: RadiationFinalize ! 座標データ設定 ! Axes data settings ! use axesset, only: AxessetFinalize ! 温度の半整数σレベルの補間, 気圧と高度の算出 ! Interpolate temperature on half sigma level, ! and calculate pressure and height ! use auxiliary, only: AuxFinalize ! 時刻管理 ! Time control ! use timeset, only: TimesetClose ! リスタートデータ入出力 ! Restart data input/output ! use restart_file_io, only: RestartFileClose ! 地表面温度リスタートデータ入出力 ! Restart data of surface temperature input/output ! use restart_surftemp_io, only: RestartSurfTempClose ! ヒストリデータ出力 ! History data output ! use history_file_io, only: HistoryFileClose ! 宣言文 ; Declaration statements ! implicit none #ifdef LIB_MPI integer :: err_mpi ! MPI の終了処理の際に使用される変数. ! Variable used for termination of MPI. #endif ! 実行文 ; Executable statement ! ! リスタートデータファイルクローズ ! Close restart data file ! call RestartFileClose if ( FlagAPE ) then ! 地表面温度リスタートデータファイルクローズ ! Close restart data file of surface temperature ! call RestartSurfTempClose end if ! ヒストリデータファイルクローズ ! Close history data files ! call HistoryFileClose ! 予報変数の割付解除 ! Deallocation of prediction variables ! deallocate( xyz_UB ) deallocate( xyz_VB ) deallocate( xyz_TempB ) deallocate( xyz_QVapB ) deallocate( xy_PsB ) deallocate( xyz_UN ) deallocate( xyz_VN ) deallocate( xyz_TempN ) deallocate( xyz_QVapN ) deallocate( xy_PsN ) deallocate( xyz_UA ) deallocate( xyz_VA ) deallocate( xyz_TempA ) deallocate( xyz_QVapA ) deallocate( xy_PsA ) ! 診断変数の割付解除 ! Dellocation of diagnostic variables ! deallocate( xyz_DUDt ) deallocate( xyz_DVDt ) deallocate( xyz_DTempDt ) deallocate( xyz_DQVapDt ) deallocate( xy_SurfHeight ) if ( FlagAPE ) then deallocate( xy_SurfAlbedo ) deallocate( xy_SurfHumidCoef ) deallocate( xy_SurfRoughLength ) deallocate( xy_SurfHeatCapacity ) deallocate( xy_SurfCond ) deallocate( xy_GroundTempFlux ) deallocate( xyr_Temp ) deallocate( xyz_Press ) deallocate( xyr_Press ) deallocate( xyz_Height ) deallocate( xyr_Height ) deallocate( xyz_Exner ) deallocate( xyr_Exner ) deallocate( xyr_RadLFlux ) deallocate( xyr_RadLFluxA ) deallocate( xyr_RadSFlux ) deallocate( xyra_DelRadLFlux ) deallocate( xyr_UFlux ) deallocate( xyr_VFlux ) deallocate( xyr_TempFlux ) deallocate( xyr_QVapFlux ) deallocate( xyr_VelTransCoef ) deallocate( xyr_TempTransCoef ) deallocate( xyr_QVapTransCoef ) deallocate( xy_SurfVelTransCoef ) deallocate( xy_SurfTempTransCoef ) deallocate( xy_SurfQVapTransCoef ) deallocate( xy_DSurfTempDt ) deallocate( xyz_DTempDtRadL ) deallocate( xyz_DTempDtRadS ) deallocate( xy_Rain ) deallocate( xyz_DTempDtCond ) deallocate( xyz_DQVapDtCond ) deallocate( xyz_DNegQVap1Dt ) deallocate( xyz_DNegQVap2Dt ) end if ! FlagAPE ! 各モジュール内の変数の割付解除 ! Dellocation of variables in modules ! call DynamicsFinalize call AuxFinalize if ( FlagHS94 ) then call Hs94Finalize end if if ( FlagAPE ) then ! 割付解除とリスタートファイルの終了処理 ! Dellocation and close a restart file ! call RadiationFinalize end if call AxessetFinalize ! 時刻管理終了処理 ! Termination of time control ! call TimesetClose #ifdef LIB_MPI ! MPI 終了処理 ! Termination of MPI ! call MPI_Finalize(err_mpi) #endif end subroutine MainTerminate end program dcpam_main
Subroutine : |
主プログラムの初期化手続き.
Initialization procedure for the main program.
This procedure input/output NAMELIST#dcpam_main_nml .
subroutine MainInit ! ! 主プログラムの初期化手続き. ! ! Initialization procedure for the main program. ! #ifdef LIB_MPI ! メッセージ出力 ! Message output ! use dc_message, only: MessageSuppressMPI #endif use dc_message, only: MessageNotify ! コマンドライン引数処理 ! Command line option parser ! use option_parser, only: OptParseInit ! NAMELIST ファイル入力に関するユーティリティ ! Utilities for NAMELIST file input ! use namelist_util, only: NmlutilInit, NmlutilMsg, namelist_filename ! 時刻管理 ! Time control ! use timeset, only: TimesetInit, TimesetDelTimeHalf, TimeN ! ステップ $ t $ の時刻. Time of step $ t $. ! 出力ファイルの基本情報管理 ! Management basic information for output files ! use fileset, only: FilesetInit ! 格子点設定 ! Grid points settings ! use gridset, only: GridsetInit, imax, jmax, kmax ! 鉛直層数. ! Number of vertical level ! 物理定数設定 ! Physical constants settings ! use constants, only: ConstantsInit ! 座標データ設定 ! Axes data settings ! use axesset, only: AxessetInit ! リスタートデータ入出力 ! Restart data input/output ! use restart_file_io, only: RestartFileOpen, RestartFileGet ! 地表面温度リスタートデータ入出力 ! Restart data of surface temperature input/output ! use restart_surftemp_io, only: RestartSurfTempOpen, RestartSurfTempGet ! ヒストリデータ出力 ! History data output ! use history_file_io, only: HistoryFileOpen use gtool_historyauto, only: HistoryAutoAddVariable, HistoryAutoPut ! 種別型パラメタ ! Kind type parameter ! use dc_types, only: STDOUT ! 標準出力の装置番号. Unit number of standard output ! ファイル入出力補助 ! File I/O support ! use dc_iounit, only: FileOpen ! 宣言文 ; Declaration statements ! implicit none character(*), parameter:: prog_name = 'dcpam_main' ! 主プログラム名. ! Main program name character(*), parameter:: version = '$Name: dcpam5-20090319 $' // '$Id: dcpam_main.F90,v 1.35 2009-03-18 09:40:37 morikawa Exp $' ! 主プログラムのバージョン ! Main program version character(STRING):: brief ! 実行ファイルの簡潔な説明 ! Brief account of executable file integer:: unit_nml ! NAMELIST ファイルオープン用装置番号. ! Unit number for NAMELIST file open integer:: iostat_nml ! NAMELIST 読み込み時の IOSTAT. ! IOSTAT of NAMELIST read ! NAMELIST 変数群 ! NAMELIST group name ! namelist /dcpam_main_nml/ FlagAPE, FlagHS94 ! ! デフォルト値については初期化手続 "main/dcpam_main.F90#MainInit" ! のソースコードを参照のこと. ! ! Refer to source codes in the initialization procedure ! "main/dcpam_main.F90#MainInit" for the default values. ! #ifdef LIB_MPI integer :: myrank_mpi, nprocs_mpi, err_mpi ! MPI の初期化の際に使用される変数. ! Variables used for initialization of MPI. #endif ! 実行文 ; Executable statement ! #ifdef LIB_MPI ! MPI 初期化 ! Initialization of MPI ! CALL MPI_Init(err_mpi) CALL MPI_Comm_Rank(mpi_comm_world, myrank_mpi, err_mpi) CALL MPI_Comm_Size(mpi_comm_world, nprocs_mpi, err_mpi) #endif #ifdef LIB_MPI ! メッセージ出力 ! Message output ! call MessageSuppressMPI( rank = 0 ) #endif ! コマンドライン引数処理 ! Command line option parser ! call OptParseInit(prog_name) ! NAMELIST ファイル名入力 ! Input NAMELIST file name ! call NmlutilInit ! デフォルト値の設定 ! Default values settings ! FlagAPE = .true. FlagHS94 = .false. ! 計算モードの設定 ! Configure calculation mode ! if ( trim(namelist_filename) /= '' ) then call FileOpen( unit_nml, namelist_filename, mode = 'r' ) ! (in) rewind( unit_nml ) read( unit_nml, nml = dcpam_main_nml, iostat = iostat_nml ) ! (out) close( unit_nml ) call NmlutilMsg( iostat_nml, prog_name ) ! (in) if ( iostat_nml == 0 ) write( STDOUT, nml = dcpam_main_nml ) end if if ( FlagAPE .and. FlagHS94 ) then call MessageNotify( 'E', prog_name, 'FlagAPE=<%b> and FlagHS94=<%b> are conflicted.', l = (/FlagAPE, FlagHS94/) ) end if ! 計算モードの表示 ! Display calculation mode ! brief = '' if ( FlagHS94 ) brief = 'Held and Suarez (1994) benchmark test' if ( FlagAPE ) brief = 'Aqua Planet Experiment' if ( trim(brief) == '' ) brief = 'Only Dynamical process' call MessageNotify( 'M', prog_name, '' ) call MessageNotify( 'M', prog_name, '+-------------------------------------' ) call MessageNotify( 'M', prog_name, '| Run: %c', c1 = trim(brief) ) call MessageNotify( 'M', prog_name, '| -- version = %c', c1 = trim(version) ) call MessageNotify( 'M', prog_name, '+-------------------------------------' ) call MessageNotify( 'M', prog_name, '' ) ! 時刻管理 ! Time control ! call TimesetInit ! 出力ファイルの基本情報管理 ! Management basic information for output files ! call FilesetInit ! 格子点設定 ! Grid points settings ! call GridsetInit ! 物理定数設定 ! Physical constants settings ! call ConstantsInit ! 座標データ設定 ! Axes data settings ! call AxessetInit ! 予報変数の割付 ! Allocation of prediction variables ! allocate( xyz_UB (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_VB (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_TempB (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_QVapB (0:imax-1, 1:jmax, 1:kmax) ) allocate( xy_PsB (0:imax-1, 1:jmax) ) allocate( xyz_UN (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_VN (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_TempN (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_QVapN (0:imax-1, 1:jmax, 1:kmax) ) allocate( xy_PsN (0:imax-1, 1:jmax) ) allocate( xyz_UA (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_VA (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_TempA (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_QVapA (0:imax-1, 1:jmax, 1:kmax) ) allocate( xy_PsA (0:imax-1, 1:jmax) ) ! リスタートデータ入力 ! Restart data input ! call RestartFileGet( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN, flag_initial ) ! (out) optional ! リスタートデータファイルの初期化 ! Initialization of restart data file ! call RestartFileOpen ! ヒストリデータファイルの初期化 ! Initialization of history data files ! call HistoryFileOpen ! ヒストリデータ出力のためのへの変数登録 ! Register of variables for history data output ! call HistoryAutoAddVariable( 'U' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'eastward wind', 'm s-1' ) ! (in) call HistoryAutoAddVariable( 'V' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'northward wind', 'm s-1' ) ! (in) call HistoryAutoAddVariable( 'Temp' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'temperature', 'K' ) ! (in) call HistoryAutoAddVariable( 'QVap' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'specific humidity', 'kg kg-1' ) ! (in) call HistoryAutoAddVariable( 'Ps' , (/ 'lon ', 'lat ', 'time' /), 'surface pressure', 'Pa' ) ! (in) ! ヒストリデータ出力 (スタート時刻) ! History data output (Start time) ! call HistoryAutoPut( TimeN, 'U', xyz_UN ) call HistoryAutoPut( TimeN, 'V', xyz_VN ) call HistoryAutoPut( TimeN, 'Temp', xyz_TempN ) call HistoryAutoPut( TimeN, 'QVap', xyz_QVapN ) call HistoryAutoPut( TimeN, 'Ps', xy_PsN ) if ( FlagAPE ) then ! 地表面温度の割付 ! Allocation of surface temperature ! allocate( xy_SurfTemp (0:imax-1, 1:jmax) ) ! 地表面温度リスタートデータ入力 ! Restart data of surface temperature input ! call RestartSurfTempGet( xy_SurfTemp ) ! (out) ! 地表面温度リスタートデータファイルの初期化 ! Initialization of restart data file of surface temperature ! call RestartSurfTempOpen ! ヒストリデータ出力のためのへの変数登録 ! Register of variables for history data output ! call HistoryAutoAddVariable( 'SurfTemp' , (/ 'lon ', 'lat ', 'time' /), 'surface temperature', 'K' ) call HistoryAutoAddVariable( 'Rain', (/ 'lon ', 'lat ', 'time' /), 'precipitation', 'W m-2' ) call HistoryAutoAddVariable( 'DTempDtCond' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'condensation heating', 'K s-1' ) call HistoryAutoAddVariable( 'DQVapDtCond' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'condensation moistening', 'kg kg-1 s-1' ) end if ! FlagAPE ! 診断変数の割付 ! Allocation of diagnostic variables ! allocate( xyz_DUDt (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DVDt (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DTempDt (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DQVapDt (0:imax-1, 1:jmax, 1:kmax) ) allocate( xy_SurfHeight (0:imax-1, 1:jmax) ) if ( FlagAPE ) then allocate( xy_SurfAlbedo (0:imax-1, 1:jmax) ) allocate( xy_SurfHumidCoef (0:imax-1, 1:jmax) ) allocate( xy_SurfRoughLength (0:imax-1, 1:jmax) ) allocate( xy_SurfHeatCapacity (0:imax-1, 1:jmax) ) allocate( xy_SurfCond (0:imax-1, 1:jmax) ) allocate( xy_GroundTempFlux (0:imax-1, 1:jmax) ) allocate( xyr_Temp (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyz_Press (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyr_Press (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyz_Height (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyr_Height (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyz_Exner (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyr_Exner (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_RadLFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_RadLFluxA (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_RadSFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyra_DelRadLFlux (0:imax-1, 1:jmax, 0:kmax, 0:1) ) allocate( xyr_UFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_VFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_TempFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_QVapFlux (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_VelTransCoef (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_TempTransCoef (0:imax-1, 1:jmax, 0:kmax) ) allocate( xyr_QVapTransCoef (0:imax-1, 1:jmax, 0:kmax) ) allocate( xy_SurfVelTransCoef (0:imax-1, 1:jmax) ) allocate( xy_SurfTempTransCoef (0:imax-1, 1:jmax) ) allocate( xy_SurfQVapTransCoef (0:imax-1, 1:jmax) ) allocate( xy_DSurfTempDt (0:imax-1, 1:jmax) ) allocate( xyz_DTempDtRadL (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DTempDtRadS (0:imax-1, 1:jmax, 1:kmax) ) allocate( xy_Rain (0:imax-1, 1:jmax) ) allocate( xyz_DTempDtCond (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DQVapDtCond (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DNegQVap1Dt (0:imax-1, 1:jmax, 1:kmax) ) allocate( xyz_DNegQVap2Dt (0:imax-1, 1:jmax, 1:kmax) ) end if ! FlagAPE ! 初回だけはオイラー法を用いるため, Δt を半分に ! Delta t is reduced to half in order to use Euler method at initial step ! if ( flag_initial ) then call TimesetDelTimeHalf end if end subroutine MainInit
Subroutine : |
主プログラムの終了処理手続き.
Termination procedure for the main program.
subroutine MainTerminate ! ! 主プログラムの終了処理手続き. ! ! Termination procedure for the main program. ! ! モジュール引用 ; USE statements ! ! 力学過程 (スペクトル法, Arakawa and Suarez (1983)) ! Dynamical process (Spectral method, Arakawa and Suarez (1983)) ! use dynamics_hspl_vas83, only: DynamicsFinalize ! Held and Suarez (1994) による強制と散逸 ! Forcing and dissipation suggested by Held and Suarez (1994) ! use held_suarez_1994, only: Hs94Finalize ! 放射フラックス (バンドモデル) ! Radiation flux (band model) ! use radiation_band, only: RadiationFinalize ! 座標データ設定 ! Axes data settings ! use axesset, only: AxessetFinalize ! 温度の半整数σレベルの補間, 気圧と高度の算出 ! Interpolate temperature on half sigma level, ! and calculate pressure and height ! use auxiliary, only: AuxFinalize ! 時刻管理 ! Time control ! use timeset, only: TimesetClose ! リスタートデータ入出力 ! Restart data input/output ! use restart_file_io, only: RestartFileClose ! 地表面温度リスタートデータ入出力 ! Restart data of surface temperature input/output ! use restart_surftemp_io, only: RestartSurfTempClose ! ヒストリデータ出力 ! History data output ! use history_file_io, only: HistoryFileClose ! 宣言文 ; Declaration statements ! implicit none #ifdef LIB_MPI integer :: err_mpi ! MPI の終了処理の際に使用される変数. ! Variable used for termination of MPI. #endif ! 実行文 ; Executable statement ! ! リスタートデータファイルクローズ ! Close restart data file ! call RestartFileClose if ( FlagAPE ) then ! 地表面温度リスタートデータファイルクローズ ! Close restart data file of surface temperature ! call RestartSurfTempClose end if ! ヒストリデータファイルクローズ ! Close history data files ! call HistoryFileClose ! 予報変数の割付解除 ! Deallocation of prediction variables ! deallocate( xyz_UB ) deallocate( xyz_VB ) deallocate( xyz_TempB ) deallocate( xyz_QVapB ) deallocate( xy_PsB ) deallocate( xyz_UN ) deallocate( xyz_VN ) deallocate( xyz_TempN ) deallocate( xyz_QVapN ) deallocate( xy_PsN ) deallocate( xyz_UA ) deallocate( xyz_VA ) deallocate( xyz_TempA ) deallocate( xyz_QVapA ) deallocate( xy_PsA ) ! 診断変数の割付解除 ! Dellocation of diagnostic variables ! deallocate( xyz_DUDt ) deallocate( xyz_DVDt ) deallocate( xyz_DTempDt ) deallocate( xyz_DQVapDt ) deallocate( xy_SurfHeight ) if ( FlagAPE ) then deallocate( xy_SurfAlbedo ) deallocate( xy_SurfHumidCoef ) deallocate( xy_SurfRoughLength ) deallocate( xy_SurfHeatCapacity ) deallocate( xy_SurfCond ) deallocate( xy_GroundTempFlux ) deallocate( xyr_Temp ) deallocate( xyz_Press ) deallocate( xyr_Press ) deallocate( xyz_Height ) deallocate( xyr_Height ) deallocate( xyz_Exner ) deallocate( xyr_Exner ) deallocate( xyr_RadLFlux ) deallocate( xyr_RadLFluxA ) deallocate( xyr_RadSFlux ) deallocate( xyra_DelRadLFlux ) deallocate( xyr_UFlux ) deallocate( xyr_VFlux ) deallocate( xyr_TempFlux ) deallocate( xyr_QVapFlux ) deallocate( xyr_VelTransCoef ) deallocate( xyr_TempTransCoef ) deallocate( xyr_QVapTransCoef ) deallocate( xy_SurfVelTransCoef ) deallocate( xy_SurfTempTransCoef ) deallocate( xy_SurfQVapTransCoef ) deallocate( xy_DSurfTempDt ) deallocate( xyz_DTempDtRadL ) deallocate( xyz_DTempDtRadS ) deallocate( xy_Rain ) deallocate( xyz_DTempDtCond ) deallocate( xyz_DQVapDtCond ) deallocate( xyz_DNegQVap1Dt ) deallocate( xyz_DNegQVap2Dt ) end if ! FlagAPE ! 各モジュール内の変数の割付解除 ! Dellocation of variables in modules ! call DynamicsFinalize call AuxFinalize if ( FlagHS94 ) then call Hs94Finalize end if if ( FlagAPE ) then ! 割付解除とリスタートファイルの終了処理 ! Dellocation and close a restart file ! call RadiationFinalize end if call AxessetFinalize ! 時刻管理終了処理 ! Termination of time control ! call TimesetClose #ifdef LIB_MPI ! MPI 終了処理 ! Termination of MPI ! call MPI_Finalize(err_mpi) #endif end subroutine MainTerminate