| Path: | main/dcpam_main_primitive.f90 |
| Last Update: | Fri Nov 04 11:49:13 +0900 2011 |
| Authors: | Yoshiyuki O. Takahashi, Yasuhiro MORIKAWA, Satoshi Noda modified by Shin-ichi Takehiro for primitive model. |
| Version: | $Id: dcpam_main_primitive.f90,v 1.4 2011-11-04 02:49:13 takepiro Exp $ |
| Tag Name: | $Name: $ |
| Copyright: | Copyright (C) GFD Dennou Club, 2008-2010. All rights reserved. |
| License: | See COPYRIGHT |
| Main Program : |
Note that Japanese and English are described in parallel.
モデルの使い方については チュートリアル を 参照してください.
See Tutorial for usage of the model.
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/] を
! 参照してください.
!
! See {Tutorial}[link:../../../doc/tutorial/rakuraku/index.htm.en] for usage of the
! model.
!
! モジュール引用 ; USE statements
!
! 力学過程 (スペクトル法, Arakawa and Suarez (1983))
! Dynamical process (Spectral method, Arakawa and Suarez (1983))
!
use dynamics_hspl_vas83, only: Dynamics
! 物理過程のみの計算のための力学過程
! A dynamics for calculation with physical processes only
!
use dynamics_physicsonly, only: DynamicsPhysicsOnly
! Held and Suarez (1994) による強制と散逸
! Forcing and dissipation suggested by Held and Suarez (1994)
!
use held_suarez_1994, only: Hs94Forcing
! 簡単金星計算のための強制
! forcing for simple Venus calculation
!
use venus_simple_forcing, only: VenusSimpleForcing
! 鉛直拡散フラックス (Mellor and Yamada, 1974, レベル 2)
! Vertical diffusion flux (Mellor and Yamada, 1974, Level 2)
!
use vdiffusion_my1974, only: VDiffusion, VDiffusionOutput
! 地表面フラックス
! Surface flux
use surface_flux_bulk, only: SurfaceFlux, SurfaceFluxOutput
! 乾燥対流調節
! Dry convective adjustment
!
! old routine to be deleted
use dryconv_adjust, only: DryConvectAdjust
! new routine
use dry_conv_adjust, only: DryConvAdjust
! 温度の半整数σレベルの補間, 気圧と高度の算出
! 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
! 地面温度の時間積分・地表面放射補正
! Time integration of surface temperature, correction of flux on surface
!
use intg_surftemp, only: IntegralSurfTemp
! 鉛直フィルター (Ishiwatari et al., 2002)
! Vertical filter (Ishiwatari et al., 2002)
!
use vertical_filter, only: VerticalFilter
! タイムフィルター (Asselin, 1972)
! Time filter (Asselin, 1972)
!
use timefilter_asselin1972, only: TimeFilter
! 時刻管理
! Time control
!
use timeset, only: TimesetProgress, TimeB, 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
! 惑星表面特性の設定
! Setting of surface properties
!
use surface_properties, only: SetSurfaceProperties
! ヒストリデータ出力
! History data output
!
use gtool_historyauto, only: HistoryAutoPut, HistoryAutoAllVarFix
! 格子点設定
! Grid points settings
!
use gridset, only: imax, jmax, kmax ! 鉛直層数.
! Number of vertical level
! 種別型パラメタ
! Kind type parameter
!
use dc_types, only: DP, STRING, TOKEN ! キーワード. Keywords.
! 予報変数の値の確認
! Check values of prognostic variables
!
use check_prog_vars, only: CheckProgVars
! 宣言文 ; 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 (m s-1)
real(DP), allocatable:: xyz_VB (:,:,:)
! $ v (t-\Delta t) $ . 南北風速. Northward wind (m s-1)
real(DP), allocatable:: xyz_TempB (:,:,:)
! $ T (t-\Delta t) $ . 温度. Temperature (K)
real(DP), allocatable:: xy_PsB (:,:)
! $ p_s (t-\Delta t) $ . 地表面気圧. Surface pressure (Pa)
real(DP), allocatable:: xyz_UN (:,:,:)
! $ u (t) $ . 東西風速. Eastward wind (m s-1)
real(DP), allocatable:: xyz_VN (:,:,:)
! $ v (t) $ . 南北風速. Northward wind (m s-1)
real(DP), allocatable:: xyz_TempN (:,:,:)
! $ T (t) $ . 温度. Temperature (K)
real(DP), allocatable:: xy_PsN (:,:)
! $ p_s (t) $ . 地表面気圧. Surface pressure (Pa)
real(DP), allocatable:: xyz_UA (:,:,:)
! $ u (t+\Delta t) $ . 東西風速. Eastward wind (m s-1)
real(DP), allocatable:: xyz_VA (:,:,:)
! $ v (t+\Delta t) $ . 南北風速. Northward wind (m s-1)
real(DP), allocatable:: xyz_TempA (:,:,:)
! $ T (t+\Delta t) $ . 温度. Temperature (K)
real(DP), allocatable:: xy_PsA (:,:)
! $ p_s (t+\Delta t) $ . 地表面気圧. Surface pressure (Pa)
! 診断変数, 他
! Diagnostic variables, etc.
!
real(DP), allocatable:: xyz_DUDt (:,:,:)
! $ \DP{u}{t} $ . 東西風速変化 (m s-2)
! Eastward wind tendency (m s-2)
real(DP), allocatable:: xyz_DVDt (:,:,:)
! $ \DP{v}{t} $ . 南北風速変化 (m s-2)
! Northward wind tendency (m s-2)
real(DP), allocatable:: xyz_DTempDt (:,:,:)
! $ \DP{T}{t} $ . 温度変化 (K s-1)
! Temperature tendency (K s-1)
real(DP), allocatable:: xy_SurfHeight (:,:)
! $ z_s $ . 地表面高度 (m)
! Surface height (m)
real(DP), allocatable:: xy_SurfTemp (:,:)
! 地表面温度 (K)
! Surface temperature (K)
real(DP), allocatable:: xy_SurfRoughLength (:,:)
! 地表粗度長 (m)
! Surface rough length (m)
real(DP), allocatable:: xy_SurfHeatCapacity (:,:)
! 地表熱容量 (J m-2 K-1)
! Surface heat capacity (J m-2 K-1)
integer, allocatable:: xy_SurfCond (:,:)
! 地表状態 (0: 固定, 1: 可変) (1)
! Surface condition (0: fixed, 1: variable) (1)
real(DP), allocatable:: xy_GroundTempFlux (:,:)
! 地中熱フラックス (W m-2)
! Ground temperature flux (W m-2)
real(DP), allocatable:: xyr_Temp (:,:,:)
! $ \hat{T} $ . 温度 (半整数レベル) (K)
! Temperature (half level) (K)
real(DP), allocatable:: xyz_Press (:,:,:)
! $ p $ . 気圧 (整数レベル) (Pa)
! Air pressure (full level) (Pa)
real(DP), allocatable:: xyr_Press (:,:,:)
! $ \hat{p} $ . 気圧 (半整数レベル) (Pa)
! Air pressure (half level) (Pa)
real(DP), allocatable:: xyz_Height (:,:,:)
! 高度 (整数レベル) (m)
! Height (full level) (m)
real(DP), allocatable:: xyr_Height (:,:,:)
! 高度 (半整数レベル) (m)
! Height (half level) (m)
real(DP), allocatable:: xyz_Exner (:,:,:)
! Exner 関数 (整数レベル) (1)
! Exner function (full level) (1)
real(DP), allocatable:: xyr_Exner (:,:,:)
! Exner 関数 (半整数レベル) (1)
! Exner function (half level) (1)
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_VelTransCoef (:,:,:)
! 輸送係数:運動量.
! Transfer coefficient: velocity
real(DP), allocatable:: xyr_TempTransCoef (:,:,:)
! 輸送係数:温度.
! Transfer coefficient: temperature
real(DP), allocatable:: xyr_QMixTransCoef(:,:,:)
! 輸送係数:混合比.
! Transfer coefficient: mixing ratio
real(DP), allocatable:: xy_SurfVelTransCoef (:,:)
! 輸送係数:運動量.
! Diffusion coefficient: velocity
real(DP), allocatable:: xy_SurfTempTransCoef (:,:)
! 輸送係数:温度.
! Transfer coefficient: temperature
real(DP), allocatable:: xy_DSurfTempDt (:,:)
! 地表面温度変化率.
! Surface temperature tendency
real(DP), allocatable:: xyz_DTempDtVDiff(:,:,:)
! 鉛直拡散による加熱率 (K s-1)
! Temperature tendency due to vertical diffusion (K s-1)
! 作業変数
! Work variables
!
integer :: IDDynMode ! 使用する力学過程
! Dynamics used for an experiment
integer, parameter:: IDDynModeHSPLVAS83 = 0
integer, parameter:: IDDynModeNoHorAdv = 1
integer :: IDPhyMode ! 使用する物理過程
! Physics used for an experiment
integer, parameter:: IDPhyModeNoPhysics = 0
integer, parameter:: IDPhyModeFullPhysics = 1
integer, parameter:: IDPhyModeHS94 = 2
integer, parameter:: IDPhyModeVenusSimple = 3
integer :: IDPhyTendMethod ! 物理過程による変化率の計算方法
! Method calculating physics tendency
integer, parameter:: IDPhyTendMethodImp1LayModel = 10
integer, parameter:: IDPhyTendMethodImpSoilModel = 11
logical:: FlagVerticalFilter ! flag for use of vertical filter
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.
integer:: n ! 組成方向に回る DO ループ用作業変数
! Work variables for DO loop in dimension of constituents
! 実行文 ; Executable statement
!
! 主プログラムの初期化 (内部サブルーチン)
! Initialization for the main program (Internal subroutine)
!
call MainInit
! 時間積分
! Time integration
!
loop_time : do while ( TimeB < EndTime )
! 地表面高度の設定
! Set surface height
!
call SetSurfaceProperties( xy_SurfHeight = xy_SurfHeight )
select case ( IDPhyMode )
case ( IDPhyModeNoPhysics )
xyz_DUDt = 0.0d0
xyz_DVDt = 0.0d0
xyz_DTempDt = 0.0d0
case ( IDPhyModeHS94 )
! 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)
case ( IDPhyModeVenusSimple )
! 温度の半整数σレベルの補間, 気圧と高度の算出
! Interpolate temperature on half sigma level,
! and calculate pressure and height
!
call AuxVars( xy_PsB, xyz_TempB, xyr_Temp, xyr_Press = xyr_Press, xyz_Press = xyz_Press, xy_SurfHeight = xy_SurfHeight, xyz_Height = xyz_Height, xyz_Exner = xyz_Exner, xyr_Exner = xyr_Exner )
! 簡単金星計算のための強制
! forcing for simple Venus calculation
!
call VenusSimpleForcing( xyz_UB, xyz_VB, xyz_TempB, xy_PsB, xyz_Press, xyr_Press, xyr_Temp, xyz_Height, xyz_Exner, xyr_Exner, xyz_DUDt, xyz_DVDt, xyz_DTempDt )
case ( IDPhyModeFullPhysics )
! 地表面条件の設定
! Configure surface conditions
!
call SetSurfaceProperties( xy_SurfTemp = xy_SurfTemp, xy_SurfRoughLength = xy_SurfRoughLength, xy_SurfHeatCapacity = xy_SurfHeatCapacity )
! 温度の半整数σレベルの補間, 気圧と高度の算出
! Interpolate temperature on half sigma level,
! and calculate pressure and height
!
call AuxVars( xy_PsB, xyz_TempB, xyr_Temp, xyr_Press = xyr_Press, xyz_Press = xyz_Press, xy_SurfHeight = xy_SurfHeight, xyz_Height = xyz_Height, xyr_Height = xyr_Height, xyz_Exner = xyz_Exner, xyr_Exner = xyr_Exner )
! 鉛直拡散フラックス
! Vertical diffusion flux
!
call VDiffusion( xyz_UB, xyz_VB, xyz_TempB, xyr_Temp, xyr_Press, xy_SurfHeight, xyz_Height, xyr_Height, xyz_Exner, xyr_Exner, xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_VelTransCoef, xyr_TempTransCoef )
! 地表面フラックス
! Surface flux
!
call SurfaceFlux( xyz_UB, xyz_VB, xyz_TempB, xyr_Temp, xyr_Press, xy_SurfHeight, xyz_Height, xyz_Exner, xyr_Exner, xy_SurfTemp, xy_SurfRoughLength, xyr_UFlux, xyr_VFlux, xyr_TempFlux, xy_SurfVelTransCoef, xy_SurfTempTransCoef )
! 一部の物理過程の時間変化率の計算 (陰解法)
! Calculate tendency by a part of physical processes (implicit)
!
call PhyImplTendency( xyr_UFlux, xyr_VFlux, xyr_TempFlux, xy_GroundTempFlux, xy_SurfTemp, xy_SurfCond, xy_SurfHeatCapacity, xyr_Press, xyz_Exner, xyr_Exner, xyr_VelTransCoef, xyr_TempTransCoef, xy_SurfVelTransCoef, xy_SurfTempTransCoef, xyz_DUDt, xyz_DVDt, xyz_DTempDtVDiff, xy_DSurfTempDt )
! 非断熱加熱率の総和の計算
! Sum all diabatic heating rates
!
xyz_DTempDt = xyz_DTempDtVDiff
! 鉛直拡散フラックスの出力
! * 出力のみのサブルーチンであり, 計算には影響しない
!
! Output Vertical diffusion fluxes
! * This subroutine works for output only,
! so it does not influence a calculation.
!
call VDiffusionOutput( xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyz_DUDt, xyz_DVDt, xyz_DTempDtVDiff, xyz_Exner, xyr_Exner, xyr_VelTransCoef, xyr_TempTransCoef )
! 地表面フラックスの出力
! * 出力のみのサブルーチンであり, 計算には影響しない
!
! Output surface fluxes
! * This subroutine works for output only,
! so it does not influence a calculation.
!
call SurfaceFluxOutput( xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyz_DUDt, xyz_DVDt, xyz_DTempDtVDiff, xy_SurfTemp, xy_DSurfTempDt, xyr_Press, xyz_Exner, xyr_Exner, xy_SurfVelTransCoef, xy_SurfTempTransCoef )
end select
! 地面温度・土壌温度・土壌水分・積雪量の積分
! Time integration of surface temperature, soil temperature, soil moisture,
! and surface snow amount
!
select case ( IDPhyMode )
case ( IDPhyModeFullPhysics )
! 地面温度・土壌温度の時間積分
! Time integration of surface temperature and soil temperature
!
call IntegralSurfTemp( xy_DSurfTempDt, xy_SurfTemp )
end select
! 力学過程
! Dynamical core
!
select case ( IDDynMode )
case ( IDDynModeHSPLVAS83 )
call Dynamics( xyz_UB, xyz_VB, xyz_TempB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xy_PsN, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xy_SurfHeight, xyz_UA, xyz_VA, xyz_TempA, xy_PsA )
case ( IDDynModeNoHorAdv )
call DynamicsPhysicsOnly( xyz_DUDt, xyz_DVDt, xyz_DTempDt, xy_PsB, xyz_UB, xyz_VB, xyz_TempB, xy_PsA, xyz_UA, xyz_VA, xyz_TempA )
end select
select case ( IDPhyMode )
case ( IDPhyModeFullPhysics )
! 温度の半整数σレベルの補間, 気圧と高度の算出
! 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
! 乾燥対流調節
! Dry convective adjustment
!
! old routine to be deleted
!!$ call DryConvectAdjust( &
!!$ & xyz_Press, xyr_Press, & ! (in)
!!$ & xyz_TempA ) ! (inout)
! new routine
call DryConvAdjust( xyz_TempA, xyz_Press, xyr_Press )
end select
! Vertical filter
! 鉛直フィルタ
!
if ( FlagVerticalFilter ) then
! 温度の半整数σレベルの補間, 気圧と高度の算出
! Interpolate temperature on half sigma level,
! and calculate pressure and height
!
call AuxVars( xy_PsA, xyz_TempA, xyr_Temp = xyr_Temp, xyr_Press = xyr_Press ) ! (out) optional
call VerticalFilter( xyz_UA, xyz_VA, xyz_TempA, xyr_Press, xyr_Temp )
end if
! 時間フィルター
! Time filter
!
if ( .not. flag_initial .or. .not. firstloop ) then
call TimeFilter( xyz_UB, xyz_VB, xyz_TempB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xy_PsN, xyz_UA, xyz_VA, xyz_TempA, xy_PsA ) ! (in)
end if
! 予報変数の値の確認
! Check values of prognostic variables
!
call CheckProgVars( xy_PsA, xyz_UA, xyz_VA, xyz_TempA )
! ヒストリデータ出力
! History data output
!
call HistoryAutoPut( TimeA, 'U', xyz_UA )
call HistoryAutoPut( TimeA, 'V', xyz_VA )
call HistoryAutoPut( TimeA, 'Temp', xyz_TempA )
call HistoryAutoPut( TimeA, 'Ps', xy_PsA )
select case ( IDPhyMode )
case ( IDPhyModeFullPhysics )
call HistoryAutoPut( TimeN, 'SurfTemp', xy_SurfTemp )
end select
! 次の時間ステップに向けて予報変数の入れ替え
! Exchange prediction variables for the next time step
!
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.
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, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xy_PsN ) ! (in)
select case ( IDPhyMode )
case ( IDPhyModeFullPhysics )
! 地表面温度リスタートデータ出力
! Restart data of surface temperature output
!
call RestartSurfTempOutput( xy_SurfTemp ) ! (in)
end select
firstloop = .false.
! 時間積分終了
! Time integration is finished
!
end do loop_time
! 主プログラムの終了処理 (内部サブルーチン)
! Termination for the main program (Internal subroutine)
!
call MainTerminate
contains
!-------------------------------------------------------------------
subroutine MainInit
!
! 主プログラムの初期化手続き.
!
! Initialization procedure for the main program.
!
! MPI
!
use mpi_wrapper, only : MPIWrapperInit
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_primitive'
! 主プログラム名.
! Main program name
character(*), parameter:: version = '$Name: $' // '$Id: dcpam_main_primitive.f90,v 1.4 2011-11-04 02:49:13 takepiro Exp $'
! 主プログラムのバージョン
! Main program version
logical:: FlagDynamics ! 力学過程計算用フラグ
! Flag for dynamics
logical:: FlagFullPhysics ! 全物理過程計算用フラグ
! Flag for full physics
logical:: FlagHS94 ! Held and Suarez (1994) 強制オン/オフ.
! Held and Suarez (1994) forcing on/off.
logical:: FlagVenusSimple ! 金星簡単強制用フラグ
! Flag for simple forcing for Venus
character(STRING):: briefexpldyn
! 実行ファイルの簡潔な説明 (力学過程)
! Brief account of executable file (dynamics)
character(STRING):: briefexplphy
! 実行ファイルの簡潔な説明 (物理過程)
! Brief account of executable file (physics)
integer:: unit_nml ! NAMELIST ファイルオープン用装置番号.
! Unit number for NAMELIST file open
integer:: iostat_nml ! NAMELIST 読み込み時の IOSTAT.
! IOSTAT of NAMELIST read
integer:: n ! 組成方向に回る DO ループ用作業変数
! Work variables for DO loop in dimension of constituents
! NAMELIST 変数群
! NAMELIST group name
!
namelist /dcpam_main_nml/ FlagDynamics, FlagFullPhysics, FlagHS94, FlagVenusSimple, FlagVerticalFilter
!
! デフォルト値については初期化手続 "main/dcpam_main.F90#MainInit"
! のソースコードを参照のこと.
!
! Refer to source codes in the initialization procedure
! "main/dcpam_main.F90#MainInit" for the default values.
!
! 実行文 ; Executable statement
!
! Initialize MPI
!
call MPIWrapperInit
! コマンドライン引数処理
! Command line option parser
!
call OptParseInit(prog_name)
! NAMELIST ファイル名入力
! Input NAMELIST file name
!
call NmlutilInit
! デフォルト値の設定
! Default values settings
!
FlagDynamics = .true.
FlagFullPhysics = .true.
FlagHS94 = .false.
FlagVenusSimple = .false.
FlagVerticalFilter = .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
! Identification of calculation method for dynamics
!
call MessageNotify( 'M', prog_name, 'FlagDynamics=<%b>.', l = (/FlagDynamics/) )
if ( FlagDynamics ) then
IDDynMode = IDDynModeHSPLVAS83
else
IDDynMode = IDDynModeNoHorAdv
end if
! Identification of calculation method for physics
!
if ( FlagFullPhysics .and. FlagHS94 ) then
call MessageNotify( 'E', prog_name, 'FlagFullPhysics=<%b> conflicts with FlagHS94=<%b>.', l = (/FlagFullPhysics, FlagHS94/) )
else if ( FlagFullPhysics .and. FlagVenusSimple ) then
call MessageNotify( 'E', prog_name, 'FlagFullPhysics=<%b> conflicts with FlagVenusSimple=<%b>.', l = (/FlagFullPhysics, FlagVenusSimple/) )
else if ( FlagHS94 .and. FlagVenusSimple ) then
call MessageNotify( 'E', prog_name, 'FlagHS94=<%b> conflicts with FlagVenusSimple=<%b>.', l = (/FlagHS94, FlagVenusSimple/) )
end if
if ( FlagFullPhysics ) then
IDPhyMode = IDPhyModeFullPhysics
else if ( FlagHS94 ) then
IDPhyMode = IDPhyModeHS94
else if ( FlagVenusSimple ) then
IDPhyMode = IDPhyModeVenusSimple
else
IDPhyMode = IDPhyModeNoPhysics
end if
! 計算モードの表示
! Display calculation mode
!
select case ( IDDynMode )
case ( IDDynModeHSPLVAS83 )
briefexpldyn = 'used'
case ( IDDynModeNoHorAdv )
briefexpldyn = 'not used'
end select
select case ( IDPhyMode )
case ( IDPhyModeFullPhysics )
briefexplphy = 'parameterization suite is used'
case ( IDPhyModeHS94 )
briefexplphy = 'forcing for Held and Suarez (1994) dynamical core test'
case ( IDPhyModeVenusSimple )
briefexplphy = 'simple forcing for Venus-like planet'
case ( IDPhyModeNoPhysics )
briefexplphy = 'not used'
end select
call MessageNotify( 'M', prog_name, '' )
call MessageNotify( 'M', prog_name, '+-------------------------------------' )
call MessageNotify( 'M', prog_name, '| Dynamics: %c', c1 = trim(briefexpldyn) )
call MessageNotify( 'M', prog_name, '| Physics : %c', c1 = trim(briefexplphy) )
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( 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( 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( xy_PsA (0:imax-1, 1:jmax) )
! リスタートデータ入力
! Restart data input
!
call RestartFileGet( xyz_UB, xyz_VB, xyz_TempB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, 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( '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, 'Ps', xy_PsN )
if ( FlagFullPhysics ) 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' )
end if ! FlagFullPhysics
! 診断変数の割付
! 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( xy_SurfHeight (0:imax-1, 1:jmax) )
if ( FlagFullPhysics ) then
allocate( xy_SurfRoughLength (0:imax-1, 1:jmax) )
allocate( xy_SurfHeatCapacity (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_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_VelTransCoef (0:imax-1, 1:jmax, 0:kmax) )
allocate( xyr_TempTransCoef(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_DSurfTempDt (0:imax-1, 1:jmax) )
allocate( xyz_DTempDtVDiff(0:imax-1, 1:jmax, 1:kmax) )
! ヒストリデータ出力のためのへの変数登録
! Register of variables for history data output
!
else if ( FlagVenusSimple ) then
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( xyz_Exner (0:imax-1, 1:jmax, 1:kmax) )
allocate( xyr_Exner (0:imax-1, 1:jmax, 0:kmax) )
end if
! 初回だけはオイラー法を用いるため, Δ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
!
! MPI
!
use mpi_wrapper, only : MPIWrapperFinalize
! 力学過程 (スペクトル法, 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
! 座標データ設定
! 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
! 実行文 ; Executable statement
!
! リスタートデータファイルクローズ
! Close restart data file
!
call RestartFileClose
if ( IDPhyMode == IDPhyModeFullPhysics ) 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( xy_PsB )
deallocate( xyz_UN )
deallocate( xyz_VN )
deallocate( xyz_TempN )
deallocate( xy_PsN )
deallocate( xyz_UA )
deallocate( xyz_VA )
deallocate( xyz_TempA )
deallocate( xy_PsA )
! 診断変数の割付解除
! Dellocation of diagnostic variables
!
deallocate( xyz_DUDt )
deallocate( xyz_DVDt )
deallocate( xyz_DTempDt )
deallocate( xy_SurfHeight )
if ( IDPhyMode == IDPhyModeFullPhysics ) then
deallocate( xy_SurfRoughLength )
deallocate( xy_SurfHeatCapacity )
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_UFlux )
deallocate( xyr_VFlux )
deallocate( xyr_TempFlux )
deallocate( xyr_VelTransCoef )
deallocate( xyr_TempTransCoef )
deallocate( xy_SurfVelTransCoef )
deallocate( xy_SurfTempTransCoef )
deallocate( xy_DSurfTempDt )
deallocate( xyz_DTempDtVDiff )
else if ( IDPhyMode == IDPhyModeVenusSimple ) then
deallocate( xyr_Temp )
deallocate( xyz_Press )
deallocate( xyr_Press )
deallocate( xyz_Height )
deallocate( xyz_Exner )
deallocate( xyr_Exner )
end if
! 各モジュール内の変数の割付解除
! Dellocation of variables in modules
!
call DynamicsFinalize
call AuxFinalize
if ( IDPhyMode == IDPhyModeHS94 ) then
call Hs94Finalize
end if
call AxessetFinalize
! 時刻管理終了処理
! Termination of time control
!
call TimesetClose
! Finalize MPI
!
call MPIWrapperFinalize
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.
!
! MPI
!
use mpi_wrapper, only : MPIWrapperInit
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_primitive'
! 主プログラム名.
! Main program name
character(*), parameter:: version = '$Name: $' // '$Id: dcpam_main_primitive.f90,v 1.4 2011-11-04 02:49:13 takepiro Exp $'
! 主プログラムのバージョン
! Main program version
logical:: FlagDynamics ! 力学過程計算用フラグ
! Flag for dynamics
logical:: FlagFullPhysics ! 全物理過程計算用フラグ
! Flag for full physics
logical:: FlagHS94 ! Held and Suarez (1994) 強制オン/オフ.
! Held and Suarez (1994) forcing on/off.
logical:: FlagVenusSimple ! 金星簡単強制用フラグ
! Flag for simple forcing for Venus
character(STRING):: briefexpldyn
! 実行ファイルの簡潔な説明 (力学過程)
! Brief account of executable file (dynamics)
character(STRING):: briefexplphy
! 実行ファイルの簡潔な説明 (物理過程)
! Brief account of executable file (physics)
integer:: unit_nml ! NAMELIST ファイルオープン用装置番号.
! Unit number for NAMELIST file open
integer:: iostat_nml ! NAMELIST 読み込み時の IOSTAT.
! IOSTAT of NAMELIST read
integer:: n ! 組成方向に回る DO ループ用作業変数
! Work variables for DO loop in dimension of constituents
! NAMELIST 変数群
! NAMELIST group name
!
namelist /dcpam_main_nml/ FlagDynamics, FlagFullPhysics, FlagHS94, FlagVenusSimple, FlagVerticalFilter
!
! デフォルト値については初期化手続 "main/dcpam_main.F90#MainInit"
! のソースコードを参照のこと.
!
! Refer to source codes in the initialization procedure
! "main/dcpam_main.F90#MainInit" for the default values.
!
! 実行文 ; Executable statement
!
! Initialize MPI
!
call MPIWrapperInit
! コマンドライン引数処理
! Command line option parser
!
call OptParseInit(prog_name)
! NAMELIST ファイル名入力
! Input NAMELIST file name
!
call NmlutilInit
! デフォルト値の設定
! Default values settings
!
FlagDynamics = .true.
FlagFullPhysics = .true.
FlagHS94 = .false.
FlagVenusSimple = .false.
FlagVerticalFilter = .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
! Identification of calculation method for dynamics
!
call MessageNotify( 'M', prog_name, 'FlagDynamics=<%b>.', l = (/FlagDynamics/) )
if ( FlagDynamics ) then
IDDynMode = IDDynModeHSPLVAS83
else
IDDynMode = IDDynModeNoHorAdv
end if
! Identification of calculation method for physics
!
if ( FlagFullPhysics .and. FlagHS94 ) then
call MessageNotify( 'E', prog_name, 'FlagFullPhysics=<%b> conflicts with FlagHS94=<%b>.', l = (/FlagFullPhysics, FlagHS94/) )
else if ( FlagFullPhysics .and. FlagVenusSimple ) then
call MessageNotify( 'E', prog_name, 'FlagFullPhysics=<%b> conflicts with FlagVenusSimple=<%b>.', l = (/FlagFullPhysics, FlagVenusSimple/) )
else if ( FlagHS94 .and. FlagVenusSimple ) then
call MessageNotify( 'E', prog_name, 'FlagHS94=<%b> conflicts with FlagVenusSimple=<%b>.', l = (/FlagHS94, FlagVenusSimple/) )
end if
if ( FlagFullPhysics ) then
IDPhyMode = IDPhyModeFullPhysics
else if ( FlagHS94 ) then
IDPhyMode = IDPhyModeHS94
else if ( FlagVenusSimple ) then
IDPhyMode = IDPhyModeVenusSimple
else
IDPhyMode = IDPhyModeNoPhysics
end if
! 計算モードの表示
! Display calculation mode
!
select case ( IDDynMode )
case ( IDDynModeHSPLVAS83 )
briefexpldyn = 'used'
case ( IDDynModeNoHorAdv )
briefexpldyn = 'not used'
end select
select case ( IDPhyMode )
case ( IDPhyModeFullPhysics )
briefexplphy = 'parameterization suite is used'
case ( IDPhyModeHS94 )
briefexplphy = 'forcing for Held and Suarez (1994) dynamical core test'
case ( IDPhyModeVenusSimple )
briefexplphy = 'simple forcing for Venus-like planet'
case ( IDPhyModeNoPhysics )
briefexplphy = 'not used'
end select
call MessageNotify( 'M', prog_name, '' )
call MessageNotify( 'M', prog_name, '+-------------------------------------' )
call MessageNotify( 'M', prog_name, '| Dynamics: %c', c1 = trim(briefexpldyn) )
call MessageNotify( 'M', prog_name, '| Physics : %c', c1 = trim(briefexplphy) )
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( 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( 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( xy_PsA (0:imax-1, 1:jmax) )
! リスタートデータ入力
! Restart data input
!
call RestartFileGet( xyz_UB, xyz_VB, xyz_TempB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, 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( '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, 'Ps', xy_PsN )
if ( FlagFullPhysics ) 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' )
end if ! FlagFullPhysics
! 診断変数の割付
! 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( xy_SurfHeight (0:imax-1, 1:jmax) )
if ( FlagFullPhysics ) then
allocate( xy_SurfRoughLength (0:imax-1, 1:jmax) )
allocate( xy_SurfHeatCapacity (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_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_VelTransCoef (0:imax-1, 1:jmax, 0:kmax) )
allocate( xyr_TempTransCoef(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_DSurfTempDt (0:imax-1, 1:jmax) )
allocate( xyz_DTempDtVDiff(0:imax-1, 1:jmax, 1:kmax) )
! ヒストリデータ出力のためのへの変数登録
! Register of variables for history data output
!
else if ( FlagVenusSimple ) then
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( xyz_Exner (0:imax-1, 1:jmax, 1:kmax) )
allocate( xyr_Exner (0:imax-1, 1:jmax, 0:kmax) )
end if
! 初回だけはオイラー法を用いるため, Δ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
!
! MPI
!
use mpi_wrapper, only : MPIWrapperFinalize
! 力学過程 (スペクトル法, 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
! 座標データ設定
! 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
! 実行文 ; Executable statement
!
! リスタートデータファイルクローズ
! Close restart data file
!
call RestartFileClose
if ( IDPhyMode == IDPhyModeFullPhysics ) 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( xy_PsB )
deallocate( xyz_UN )
deallocate( xyz_VN )
deallocate( xyz_TempN )
deallocate( xy_PsN )
deallocate( xyz_UA )
deallocate( xyz_VA )
deallocate( xyz_TempA )
deallocate( xy_PsA )
! 診断変数の割付解除
! Dellocation of diagnostic variables
!
deallocate( xyz_DUDt )
deallocate( xyz_DVDt )
deallocate( xyz_DTempDt )
deallocate( xy_SurfHeight )
if ( IDPhyMode == IDPhyModeFullPhysics ) then
deallocate( xy_SurfRoughLength )
deallocate( xy_SurfHeatCapacity )
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_UFlux )
deallocate( xyr_VFlux )
deallocate( xyr_TempFlux )
deallocate( xyr_VelTransCoef )
deallocate( xyr_TempTransCoef )
deallocate( xy_SurfVelTransCoef )
deallocate( xy_SurfTempTransCoef )
deallocate( xy_DSurfTempDt )
deallocate( xyz_DTempDtVDiff )
else if ( IDPhyMode == IDPhyModeVenusSimple ) then
deallocate( xyr_Temp )
deallocate( xyz_Press )
deallocate( xyr_Press )
deallocate( xyz_Height )
deallocate( xyz_Exner )
deallocate( xyr_Exner )
end if
! 各モジュール内の変数の割付解除
! Dellocation of variables in modules
!
call DynamicsFinalize
call AuxFinalize
if ( IDPhyMode == IDPhyModeHS94 ) then
call Hs94Finalize
end if
call AxessetFinalize
! 時刻管理終了処理
! Termination of time control
!
call TimesetClose
! Finalize MPI
!
call MPIWrapperFinalize
end subroutine MainTerminate