dcpam_ape.f90

Path: main/dcpam_ape.f90
Last Update: Wed Jul 30 17:41:33 +0900 2008

dcpam 水惑星実験用主プログラム

dcpam main program for aqua planet experiments

Authors:Yasuhiro MORIKAWA
Version:$Id: dcpam_ape.f90,v 1.1.1.1 2008-07-30 08:41:33 morikawa Exp $
Tag Name:$Name: dcpam5-20080731 $
Copyright:Copyright (C) GFD Dennou Club, 2008. All rights reserved.
License:See COPYRIGHT

Methods

Included Modules

dyn_hspl_vas83 radiation_band vdiffusion_my1974 cumulus_adjust intpol_half phy_implicit timeset restart_file_io gt4_historyauto dc_types option_parser namelist_util fileset gridset constants axesset history_file_io dc_string

Public Instance methods

Main Program :

Note that Japanese and English are described in parallel.

水惑星, すなわち全球が水に覆われているような惑星大気の計算を 行います.

Calculation of atmosphere on a planet covered with water globally is performed.

[Source]

program dcpam_ape
  !
  ! <b>Note that Japanese and English are described in parallel.</b>
  !
  ! 水惑星, すなわち全球が水に覆われているような惑星大気の計算を
  ! 行います. 
  !
  ! Calculation of 
  ! atmosphere on a planet covered with water globally is performed. 
  !

  ! モジュール引用 ; USE statements
  !

  ! 力学過程 (スペクトル法, Arakawa and Suarez (1983))
  ! Dynamical process (Spectral method, Arakawa and Suarez (1983))
  !
  use dyn_hspl_vas83, only: Dynamics

  ! 放射フラックス
  ! Radiation flux
  !
  use radiation_band, only: RadiationFlux, RadiationCorrect, RadiationDTempDt

  ! 鉛直拡散フラックス (Mellor and Yamada, 1974, レベル 2)
  ! Vertical diffusion flux (Mellor and Yamada, 1974, Level 2)
  !
  use vdiffusion_my1974, only: VerticalDiffusion

  ! 積雲パラメタリゼーション (対流調節)
  ! Cumulus parameterization (convection adjust)
  !
  use cumulus_adjust, only: Cumulus

  ! 温度の半整数σレベルの補間, 気圧とジオポテンシャルの算出
  ! Interpolate temperature on half sigma level, 
  ! and calculate pressure and geo-potential
  !
  use intpol_half, only: IntpolHalfLevel

  ! 陰解法のための行列処理 (一部の物理過程用)
  ! Matrices handling for implicit scheme (for a part of physical processes)
  !
  use phy_implicit, only: PhyImplGetMatrices, PhyImplTendency

  ! 時刻管理
  ! Time control
  !
  use timeset, only: TimesetProgress, Nstep       ! ループ回数. Number of times of loops

  ! リスタートデータ入出力
  ! Restart data input/output
  !
  use restart_file_io, only: RestartFileOutPut

  ! ヒストリデータ出力
  ! History data output
  !
  use gt4_historyauto, only: HistoryAutoPut, HistoryAutoProgress

  ! 種別型パラメタ
  ! Kind type parameter
  !
  use dc_types, only: DP, STRING, TOKEN      ! キーワード.   Keywords. 

  ! 宣言文 ; 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
  !
  real(DP), allocatable:: xyz_DUDt (:,:,:)
                              ! $ \DP{u}{t} $ . 東西風速変化. 
                              ! Zonal wind tendency
  real(DP), allocatable:: xyz_DVDt (:,:,:)
                              ! $ \DP{v}{t} $ . 南北風速変化. 
                              ! Meridional 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_SurfTemp (:,:)
                              ! 地表面温度. 
                              ! Surface temperature
  real(DP), allocatable:: xy_SurfAlbedo (:,:)
                              ! 地表アルベド. 
                              ! Surface albedo
  real(DP), allocatable:: xy_SurfHeatCapacity (:,:)
                              ! 地表熱容量. 
                              ! Surface heat capacity
  integer, allocatable:: xy_SurfCondition (:,:)
                              ! 地表状態. 
                              ! Surface condition
  real(DP), allocatable:: xy_GroundTempFlux (:,:)
                              ! 地中熱フラックス. 
                              ! Ground temperature flux

  real(DP), allocatable:: xyza_UVMtx (:,:,:,:)
                              ! 速度陰解行列. 
                              ! Implicit matrix about velocity 
  real(DP), allocatable:: xyra_TempMtx (:,:,:,:)
                              ! 温度陰解行列. 
                              ! Implicit matrix about temperature
  real(DP), allocatable:: xyza_QVapMtx (:,:,:,:)
                              ! 比湿陰解行列. 
                              ! Implicit matrix about specific humidity

  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_GeoPot (:,:,:)
                              ! $ \phi $ . ジオポテンシャル (整数レベル). 
                              ! Geo-potential (full level)
  real(DP), allocatable:: xyr_GeoPot (:,:,:)
                              ! $ \hat{\phi} $ . ジオポテンシャル (半整数レベル). 
                              ! Geo-potential (half level)

  real(DP), allocatable:: xyr_RadLFlux (:,:,:)
                              ! 長波フラックス. 
                              ! Longwave flux
  real(DP), allocatable:: xyr_RadSFlux (:,:,:)
                              ! 短波 (日射) フラックス. 
                              ! Shortwave (insolation) flux
  real(DP), allocatable:: xya_SurfRadLMtx (:,:,:)
                              ! $ T $ .  陰解行列: 地表. 
                              ! implicit matrix: surface
  real(DP), allocatable:: xyra_DelRadLFlux (:,:,:,:)
                              ! 長波地表温度変化. 
                              ! Surface temperature tendency with longwave

  real(DP), allocatable:: xyr_UFlux (:,:,:)
                              ! 東西風速フラックス. 
                              ! Zonal wind flux
  real(DP), allocatable:: xyr_VFlux (:,:,:)
                              ! 南北風速フラックス. 
                              ! Meridional wind flux
  real(DP), allocatable:: xyr_TempFlux (:,:,:)
                              ! 温度フラックス. 
                              ! Temperature flux
  real(DP), allocatable:: xyr_QVapFlux (:,:,:)
                              ! 比湿フラックス. 
                              ! Specific humidity flux

  real(DP), allocatable:: xy_SurfUVMtx (:,:)
                              ! 速度陰解行列: 地表. 
                              ! Implicit matrix about velocity: surface
  real(DP), allocatable:: xyaa_SurfTempMtx (:,:,:,:)

                              ! 温度陰解行列: 地表. 
                              ! Implicit matrix about temperature: surface
  real(DP), allocatable:: xyaa_SurfQVapMtx (:,:,:,:)
                              ! 比湿陰解行列: 地表. 
                              ! Implicit matrix about specific humidity: surface

  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

  ! 作業変数
  ! Work variables
  !
  integer:: i                 ! 時間方向に回る DO ループ用作業変数. 
                              ! Work variables for DO loop in time
  logical:: firstloop = .true.
                              ! 初回のループであることを示すフラグ. 
                              ! Flag implying first loop

  ! 実行文 ; Executable statement
  !

  ! 主プログラムの初期化 (内部サブルーチン)
  ! Initialization for the main program (Internal subroutine)
  !
  call MainInit


  ! 時間積分
  ! Time integration
  !
  do i = 1, Nstep

    ! 地表面条件の設定
    ! Configure surface conditions
    !
    xy_SurfTemp         = 273.0_DP
    xy_SurfAlbedo       = 0.3_DP
    xy_SurfHeatCapacity = 0.0_DP
    xy_SurfCondition    = 0
    xy_GroundTempFlux   = 0.0_DP

    ! 温度の半整数σレベルの補間, 気圧とジオポテンシャルの算出
    ! Interpolate temperature on half sigma level, 
    ! and calculate pressure and geo-potential
    !
    call IntpolHalfLevel( xy_PsN,     xyz_TempN, xyr_Temp, xyz_Press,  xyr_Press, xyz_GeoPot, xyr_GeoPot )   ! (out)

    ! 陰解法のための行列作成
    ! Create matrices for implicit scheme
    !
    call PhyImplGetMatrices( xyr_Press, xy_SurfHeatCapacity, xy_SurfCondition, xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux, xyza_UVMtx, xyra_TempMtx, xyza_QVapMtx )            ! (out)

    ! 放射フラックス
    ! Radiation flux
    !
    call RadiationFlux( xyz_TempN, xyz_QVapN, xyr_Press, xy_SurfTemp, xy_SurfAlbedo, xyr_RadLFlux, xyr_RadSFlux, xya_SurfRadLMtx, xyra_DelRadLFlux )      ! (out)

    ! 鉛直拡散フラックス
    ! Vertical diffusion flux
    !
    call VerticalDiffusion( xyz_UN,    xyz_VN,    xyz_QVapN, xyz_TempN, xyr_Temp, xyz_Press, xyr_Press, xyz_GeoPot,   xyr_GeoPot, xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux, xyza_UVMtx, xyra_TempMtx, xyza_QVapMtx  )           ! (inout)

    ! 地表面フラックス
    ! Surface flux
    !
    xy_SurfUVMtx     = 0.0_DP
    xyaa_SurfTempMtx = 0.0_DP
    xyaa_SurfQVapMtx = 0.0_DP

    ! 一部の物理過程の時間変化率の計算 (陰解法)
    ! Calculate tendency by a part of physical processes (implicit)
    !
    call PhyImplTendency( xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux, xyr_RadSFlux(:,:,0), xyr_RadLFlux(:,:,0), xy_GroundTempFlux, xyza_UVMtx, xyra_TempMtx, xyza_QVapMtx, xy_SurfUVMtx, xyaa_SurfTempMtx, xyaa_SurfQVapMtx, xya_SurfRadLMtx, xy_SurfCondition, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xyz_DQVapDt, xy_DSurfTempDt )                                    ! (out)

    ! 放射フラックス補正
    ! Radiation flux correction
    !
    call RadiationCorrect( xyz_DTempDt, xy_DSurfTempDt, xyra_DelRadLFlux, xyr_RadLFlux )                                   ! (inout)

    ! 放射による温度変化率
    ! Temperature tendency with radiation
    !
    call RadiationDTempDt( xyr_RadLFlux, xyr_RadSFlux, xyr_Press, xyz_DTempDtRadL, xyz_DTempDtRadS )       ! (out)

    xyz_DTempDt = xyz_DTempDt + xyz_DTempDtRadL + xyz_DTempDtRadS

    ! 力学過程
    ! 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, xyz_UA,   xyz_VA,   xyz_TempA,   xyz_QVapA,   xy_PsA  )   ! (out)

    ! 積雲パラメタリゼーション
    ! Cumulus parameterization
    !
    call Cumulus( xyz_TempN, xyz_QVapN, xyz_Press, xyr_Press )   ! (in)

!!$    ! 時間フィルター
!!$    ! Time filter
!!$    !
!!$    call TimeFilter( &
!!$      & xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, &   ! (in)
!!$      & xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN, &   ! (inout)
!!$      & xyz_UA, xyz_VA, xyz_TempA, xyz_QVapA, xy_PsA  )   ! (in)

    ! ヒストリデータ出力
    ! History data output
    !
    if ( .not. firstloop ) then
      call HistoryAutoPut( 'U',    xyz_UN )
      call HistoryAutoPut( 'V',    xyz_VN )
      call HistoryAutoPut( 'Temp', xyz_TempN )
      call HistoryAutoPut( 'QVap', xyz_QVapN )
      call HistoryAutoPut( 'Ps',   xy_PsN )
    end if

    ! 予報変数の時刻付け替え
    ! Exchange time of prediction variables
    !
    xyz_UB    = xyz_UN    
     xyz_UN    = xyz_UA    
     xyz_UA    = 0.0_DP
    xyz_VB    = xyz_VN    
     xyz_VN    = xyz_VA    
     xyz_VA    = 0.0_DP
    xyz_TempB = xyz_TempN 
     xyz_TempN = xyz_TempA 
     xyz_TempA = 0.0_DP
    xyz_QVapB = xyz_QVapN 
     xyz_QVapN = xyz_QVapA 
     xyz_QVapA = 0.0_DP
    xy_PsB    = xy_PsN    
     xy_PsN    = xy_PsA    
     xy_PsA    = 0.0_DP

    ! 時刻の進行
    ! Progress time
    !
    call TimesetProgress
    call HistoryAutoProgress

    ! リスタートデータ出力
    ! Restart data output
    !
    if ( .not. firstloop ) then
      call RestartFileOutput( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN  )   ! (in)
    end if

    firstloop = .false.
  end do

  ! 主プログラムの終了処理 (内部サブルーチン)
  ! Termination for the main program (Internal subroutine)
  !
  call MainTerminate



contains



  subroutine MainInit
    !
    ! 主プログラムの初期化手続き. 
    !
    ! Initialization procedure for the main program. 
    !

    ! コマンドライン引数処理
    ! Command line option parser
    !
    use option_parser, only: OptParseInit

    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: NmlutilInit

    ! 時刻管理
    ! Time control
    !
    use timeset, only: TimesetInit

    ! 出力ファイルの基本情報管理
    ! 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

    ! ヒストリデータ出力
    ! History data output
    !
    use history_file_io, only: HistoryFileOpen
    use gt4_historyauto, only: HistoryAutoAddVariable, HistoryAutoPut

    ! 文字列操作
    ! Character handling
    !
    use dc_string, only: StoA

    ! 実行文 ; Executable statement
    !

    ! コマンドライン引数処理
    ! Command line option parser
    !
    call OptParseInit

    ! NAMELIST ファイル名入力
    ! Input NAMELIST file name
    !
    call NmlutilInit

    ! 時刻管理
    ! 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  )   ! (out)

    ! リスタートデータ出力
    ! Restart data output
    !
    call RestartFileOpen

    ! リスタートファイルへ初期値データ出力
    ! Output initial data to a restart file
    !
    call RestartFileOutput( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN  )   ! (in)

    ! ヒストリデータファイルの初期化
    ! 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' )

    call HistoryAutoAddVariable( 'V' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'northwardward wind', 'm s-1' )

    call HistoryAutoAddVariable( 'Temp' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'temperature', 'K' )

    call HistoryAutoAddVariable( 'QVap' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'specific humidity', 'kg kg-1' )

    call HistoryAutoAddVariable( 'Ps' , (/ 'lon ', 'lat ', 'time' /), 'surface pressure', 'Pa' )

    ! ヒストリデータ出力 (スタート時刻)
    ! History data output (Start time)
    !
    call HistoryAutoPut( 'U', xyz_UN )
    call HistoryAutoPut( 'V', xyz_VN )
    call HistoryAutoPut( 'Temp', xyz_TempN )
    call HistoryAutoPut( 'QVap', xyz_QVapN )
    call HistoryAutoPut( 'Ps', xy_PsN )


    ! 診断変数の割付
    ! 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_SurfTemp         (0:imax-1, 1:jmax) )
    allocate( xy_SurfAlbedo       (0:imax-1, 1:jmax) )
    allocate( xy_SurfHeatCapacity (0:imax-1, 1:jmax) )
    allocate( xy_SurfCondition    (0:imax-1, 1:jmax) )
    allocate( xy_GroundTempFlux   (0:imax-1, 1:jmax) )

    allocate( xyza_UVMtx   (0:imax-1, 1:jmax, 1:kmax, -1:1) )
    allocate( xyra_TempMtx (0:imax-1, 1:jmax, 0:kmax, -1:1) )
    allocate( xyza_QVapMtx (0:imax-1, 1:jmax, 1:kmax, -1:1) )

    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_GeoPot (0:imax-1, 1:jmax, 1:kmax) )
    allocate( xyr_GeoPot (0:imax-1, 1:jmax, 0:kmax) )

    allocate( xyr_RadLFlux     (0:imax-1, 1:jmax, 0:kmax) )
    allocate( xyr_RadSFlux     (0:imax-1, 1:jmax, 0:kmax) )
    allocate( xya_SurfRadLMtx  (0:imax-1, 1:jmax,         -1:1) )
    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( xy_SurfUVMtx     (0:imax-1, 1:jmax) )
    allocate( xyaa_SurfTempMtx (0:imax-1, 1:jmax, 0:1, -1:1) )
    allocate( xyaa_SurfQVapMtx (0:imax-1, 1:jmax, 0:1, -1:1) )

    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) )

  end subroutine MainInit



  subroutine MainTerminate
    !
    ! 主プログラムの終了処理手続き. 
    !
    ! Termination procedure for the main program. 
    !

    ! 時刻管理
    ! Time control
    !
    use timeset, only: TimesetClose

    ! リスタートデータ入出力
    ! Restart data input/output
    !
    use restart_file_io, only: RestartFileClose

    ! ヒストリデータ出力
    ! History data output
    !
    use history_file_io, only: HistoryFileClose

    ! 実行文 ; Executable statement
    !

    ! リスタートデータファイルクローズ
    ! Close restart data input
    !
    call RestartFileClose

    ! ヒストリデータファイルクローズ
    ! Close history data input
    !
    call HistoryFileClose

    ! 時刻管理終了処理
    ! Termination of time control
    !
    call TimesetClose

  end subroutine MainTerminate

end program dcpam_ape

Private Instance methods

Subroutine :

主プログラムの初期化手続き.

Initialization procedure for the main program.

[Source]

  subroutine MainInit
    !
    ! 主プログラムの初期化手続き. 
    !
    ! Initialization procedure for the main program. 
    !

    ! コマンドライン引数処理
    ! Command line option parser
    !
    use option_parser, only: OptParseInit

    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: NmlutilInit

    ! 時刻管理
    ! Time control
    !
    use timeset, only: TimesetInit

    ! 出力ファイルの基本情報管理
    ! 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

    ! ヒストリデータ出力
    ! History data output
    !
    use history_file_io, only: HistoryFileOpen
    use gt4_historyauto, only: HistoryAutoAddVariable, HistoryAutoPut

    ! 文字列操作
    ! Character handling
    !
    use dc_string, only: StoA

    ! 実行文 ; Executable statement
    !

    ! コマンドライン引数処理
    ! Command line option parser
    !
    call OptParseInit

    ! NAMELIST ファイル名入力
    ! Input NAMELIST file name
    !
    call NmlutilInit

    ! 時刻管理
    ! 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  )   ! (out)

    ! リスタートデータ出力
    ! Restart data output
    !
    call RestartFileOpen

    ! リスタートファイルへ初期値データ出力
    ! Output initial data to a restart file
    !
    call RestartFileOutput( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN  )   ! (in)

    ! ヒストリデータファイルの初期化
    ! 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' )

    call HistoryAutoAddVariable( 'V' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'northwardward wind', 'm s-1' )

    call HistoryAutoAddVariable( 'Temp' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'temperature', 'K' )

    call HistoryAutoAddVariable( 'QVap' , (/ 'lon ', 'lat ', 'sig ', 'time' /), 'specific humidity', 'kg kg-1' )

    call HistoryAutoAddVariable( 'Ps' , (/ 'lon ', 'lat ', 'time' /), 'surface pressure', 'Pa' )

    ! ヒストリデータ出力 (スタート時刻)
    ! History data output (Start time)
    !
    call HistoryAutoPut( 'U', xyz_UN )
    call HistoryAutoPut( 'V', xyz_VN )
    call HistoryAutoPut( 'Temp', xyz_TempN )
    call HistoryAutoPut( 'QVap', xyz_QVapN )
    call HistoryAutoPut( 'Ps', xy_PsN )


    ! 診断変数の割付
    ! 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_SurfTemp         (0:imax-1, 1:jmax) )
    allocate( xy_SurfAlbedo       (0:imax-1, 1:jmax) )
    allocate( xy_SurfHeatCapacity (0:imax-1, 1:jmax) )
    allocate( xy_SurfCondition    (0:imax-1, 1:jmax) )
    allocate( xy_GroundTempFlux   (0:imax-1, 1:jmax) )

    allocate( xyza_UVMtx   (0:imax-1, 1:jmax, 1:kmax, -1:1) )
    allocate( xyra_TempMtx (0:imax-1, 1:jmax, 0:kmax, -1:1) )
    allocate( xyza_QVapMtx (0:imax-1, 1:jmax, 1:kmax, -1:1) )

    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_GeoPot (0:imax-1, 1:jmax, 1:kmax) )
    allocate( xyr_GeoPot (0:imax-1, 1:jmax, 0:kmax) )

    allocate( xyr_RadLFlux     (0:imax-1, 1:jmax, 0:kmax) )
    allocate( xyr_RadSFlux     (0:imax-1, 1:jmax, 0:kmax) )
    allocate( xya_SurfRadLMtx  (0:imax-1, 1:jmax,         -1:1) )
    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( xy_SurfUVMtx     (0:imax-1, 1:jmax) )
    allocate( xyaa_SurfTempMtx (0:imax-1, 1:jmax, 0:1, -1:1) )
    allocate( xyaa_SurfQVapMtx (0:imax-1, 1:jmax, 0:1, -1:1) )

    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) )

  end subroutine MainInit
Subroutine :

主プログラムの終了処理手続き.

Termination procedure for the main program.

[Source]

  subroutine MainTerminate
    !
    ! 主プログラムの終了処理手続き. 
    !
    ! Termination procedure for the main program. 
    !

    ! 時刻管理
    ! Time control
    !
    use timeset, only: TimesetClose

    ! リスタートデータ入出力
    ! Restart data input/output
    !
    use restart_file_io, only: RestartFileClose

    ! ヒストリデータ出力
    ! History data output
    !
    use history_file_io, only: HistoryFileClose

    ! 実行文 ; Executable statement
    !

    ! リスタートデータファイルクローズ
    ! Close restart data input
    !
    call RestartFileClose

    ! ヒストリデータファイルクローズ
    ! Close history data input
    !
    call HistoryFileClose

    ! 時刻管理終了処理
    ! Termination of time control
    !
    call TimesetClose

  end subroutine MainTerminate

[Validate]