phy_jupiter_case00_test.f90

Path: physics/phy_jupiter_case00_test.f90
Last Update: Sat Jun 14 20:44:15 +0900 2008

phy_jupiter_case00 モジュールのテストプログラム

Test program for "phy_jupiter_case00"

Authors:Yasuhiro MORIKAWA
Version:$Id: phy_jupiter_case00_test.f90,v 1.4 2008-06-14 11:44:15 morikawa Exp $
Tag Name:$Name: dcpam4-20080626 $
Copyright:Copyright (C) GFD Dennou Club, 2008. All rights reserved.
License:See COPYRIGHT

Note that Japanese and English are described in parallel.

phy_jupiter_case00 モジュールの動作テストを行うためのプログラムです. このプログラムがコンパイルできること, および実行時に プログラムが正常終了することを確認してください.

This program checks the operation of "phy_jupiter_case00" module. Confirm compilation and execution of this program.

Methods

Included Modules

phy_jupiter_case00 dc_test dc_types dc_string dc_args const_provider gt4_history

Public Instance methods

Main Program :

[Source]

program phy_jupiter_case00_test
  use phy_jupiter_case00, only: PHYJP, PhyJpCreate, PhysicsJupiter, PhysicsJupiterAdjust, PhyJpClose, PhyJpPutLine, PhyJpInitialized, PhyJpSetTime
  use dc_test, only: AssertEqual, AssertGreaterThan, AssertLessThan
  use dc_types, only: DP, STRING
  use dc_string, only: StoA, PutLine
  use dc_args, only: ARGS, DCArgsOpen, DCArgsHelpMsg, DCArgsOption, DCArgsDebug, DCArgsHelp, DCArgsStrict, DCArgsClose
  use const_provider, only: ConstGet
  use gt4_history, only: GT_HISTORY, HistoryCreate, HistoryAddVariable, HistoryPut, HistoryClose, HistoryAddAttr, HistoryGet
  implicit none

  !-------------------------------------------------------------------
  !  実験の表題, モデルの名称, 所属機関名
  !  Title of a experiment, name of model, sub-organ
  !-------------------------------------------------------------------
  character(*), parameter:: title = 'phy_jupiter_case00_test $Name: dcpam4-20080626 $ :: ' // 'Test program of "phy_jupiter_case00" module'
  character(*), parameter:: source = 'dcmodel project: hierarchical numerical models ' // '(See http://www.gfd-dennou.org/library/dcmodel)'
  character(*), parameter:: institution = 'GFD Dennou Club (See http://www.gfd-dennou.org)'

  !-------------------------------------------------------------------
  !  格子点数・最大全波数
  !  Grid points and maximum truncated wavenumber
  !-------------------------------------------------------------------
  integer, parameter:: imax = 32
                              ! 経度格子点数. 
                              ! Number of grid points in longitude
  integer, parameter:: jmax = 16
                              ! 緯度格子点数. 
                              ! Number of grid points in latitude
  integer, parameter:: kmax = 8
                              ! 鉛直層数. 
                              ! Number of vertical level

  !-------------------------------------------------------------------
  !  軸データ
  !  Axes data
  !-------------------------------------------------------------------
  real(DP):: x_Lon (0:imax-1)
                              ! 経度. Longitude
  real(DP):: y_Lat (0:jmax-1)
                              ! 緯度. Latitude
  real(DP):: z_Sigma (0:kmax-1)
                              ! $ \sigma $ レベル (整数). 
                              ! Full $ \sigma $ level
  real(DP):: r_Sigma (0:kmax)
                              ! $ \sigma $ レベル (半整数). 
                              ! Half $ \sigma $ level
  real(DP):: x_Lon_Weight (0:imax-1)
                              ! 経度積分用座標重み. 
                              ! Weight for integration in longitude
  real(DP):: y_Lat_Weight (0:jmax-1)
                              ! 緯度積分用座標重み. 
                              ! Weight for integration in latitude
  real(DP):: z_DelSigma (0:kmax-1)
                              ! $ \Delta \sigma $ (整数). 
                              ! $ \Delta \sigma $ (Full)

  !-----------------------------------------------------------------
  !  物理定数等
  !  physical constants etc.
  !-----------------------------------------------------------------
  real(DP):: PI
                              ! $ \pi $ .
                              ! 円周率.  Circular constant
  real(DP):: FKarm
                              ! $ k $ .
                              ! カルマン定数. 
                              ! Karman constant

  real(DP):: Grav
                              ! $ g $ [m s-2]. 
                              ! 重力加速度. 
                              ! Gravitational acceleration
  real(DP):: CpDry
                              ! $ C_p $ [J kg-1 K-1]. 
                              ! 乾燥大気の定圧比熱. 
                              ! Specific heat of air at constant pressure
  real(DP):: GasRDry
                              ! $ R $ [J kg-1 K-1]. 
                              ! 乾燥大気の気体定数. 
                              ! Gas constant of air
  real(DP):: LatentHeat
                              ! $ L $ [J kg-1] . 
                              ! 凝結の潜熱. 
                              ! Latent heat of condensation
  real(DP):: GasRWet
                              ! $ R_v $ [J kg-1 K-1]. 
                              ! 凝結成分の気体定数. 
                              ! Gas constant of condensible elements
  real(DP):: EpsV
                              ! $ \epsilon_v $ . 
                              ! 水蒸気分子量比. 
                              ! Molecular weight of water vapor

  real(DP):: ES0       ! $ e^{*} $ (273K) .      0 ℃での飽和蒸気圧. Saturated vapor pressure at 0 degrees C

  !-------------------------------------------------------------------
  !  物理量
  !  Physical values
  !-------------------------------------------------------------------
  real(DP):: xyz_U (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ u $ . 東西風速. Zonal wind
  real(DP):: xyz_V (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ v $ . 南北風速. Meridional wind

  real(DP):: xyz_Temp (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ T $ .     温度. Temperature
  real(DP):: xy_Ps (0:imax-1, 0:jmax-1)
                              ! $ p_s $ .   地表面気圧. Surface pressure
  real(DP):: xyz_QVap (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ q $ .     比湿. Specific humidity
  real(DP):: xyz_DUDt (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \DP{u}{t} $ . 
                              ! 東西風速変化. 
                              ! Zonal wind tendency
  real(DP):: xyz_DVDt (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \DP{v}{t} $ . 
                              ! 南北風速変化. 
                              ! Meridional wind tendency
  real(DP):: xyz_DTempDt (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \DP{T}{t} $ . 
                              ! 温度変化. 
                              ! Temperature tendency
  real(DP):: xyz_DQVapDt (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \DP{q}{t} $ . 
                              ! 比湿変化. 
                              ! Temperature tendency

  real(DP):: xyz_UAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ u $ . 東西風速. Zonal wind
  real(DP):: xyz_VAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ v $ . 南北風速. Meridional wind

  real(DP):: xyz_TempAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ T $ .     温度. Temperature
  real(DP):: xy_PsAns (0:imax-1, 0:jmax-1)
                              ! $ p_s $ .   地表面気圧. Surface pressure
  real(DP):: xyz_QVapAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ q $ .     比湿. Specific humidity
  real(DP):: xyz_DUDtAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \DP{u}{t} $ . 
                              ! 東西風速変化. 
                              ! Zonal wind tendency
  real(DP):: xyz_DVDtAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \DP{v}{t} $ . 
                              ! 南北風速変化. 
                              ! Meridional wind tendency
  real(DP):: xyz_DTempDtAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \DP{T}{t} $ . 
                              ! 温度変化. 
                              ! Temperature tendency
  real(DP):: xyz_DQVapDtAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \DP{q}{t} $ . 
                              ! 比湿変化. 
                              ! Temperature tendency

  !-------------------------------------------------------------------
  !  データ入出力
  !  Data I/O
  !-------------------------------------------------------------------
  type(GT_HISTORY):: gthist

  !-------------------------------------------------------------------
  !  作業変数
  !  Work variables
  !-------------------------------------------------------------------
  integer:: k                 ! DO ループ用作業変数
                              ! Work variables for DO loop
  type(ARGS):: arg            ! コマンドライン引数. 
                              ! Command line options
  logical:: OPT_namelist      ! -N, --namelist オプションの有無. 
                              ! Existence of '-N', '--namelist' option
  character(STRING):: VAL_namelist
                              ! -N, --namelist オプションの値. 
                              ! Value of '-N', '--namelist' option

  type(PHYJP):: phy_jp00, phy_jp01
!!$  type(PHYJP):: phy_jp02, phy_jp03
  logical:: err
  character(*), parameter:: subname = 'phy_jupiter_case00_test'
continue

  !-------------------------------------------------------------------
  !  コマンドライン引数の処理
  !  Command line options handling
  !-------------------------------------------------------------------
  call cmdline_optparse ! これは内部サブルーチン. This is an internal subroutine
  !-------------------------------------------------------------------
  !  物理定数の設定
  !  Configure a physical constant
  !-------------------------------------------------------------------
  call ConstGet( planet = 'earth', PI = PI, GasRDry = GasRDry, Grav = Grav, CpDry = CpDry, LatentHeat = LatentHeat, GasRWet = GasRWet, EpsV = EpsV, FKarm = FKarm )                                  ! (out)

  ES0 = 611.0_DP


  !-------------------------------------------------------------------
  !  軸データの設定
  !  Configure axes data
  !-------------------------------------------------------------------
  call HistoryGet ( file = 'phy_jupiter_case00_test00.nc', varname = 'lon', array = x_Lon, quiet = .true. )                 ! (out)
  x_Lon = x_Lon * PI / 180.0_DP

  call HistoryGet ( file = 'phy_jupiter_case00_test00.nc', varname = 'lon_weight', array = x_Lon_Weight, quiet = .true. )                 ! (out)

  call HistoryGet ( file = 'phy_jupiter_case00_test00.nc', varname = 'lat', array = y_Lat, quiet = .true. )                 ! (out)
  y_Lat = y_Lat * PI / 180.0_DP

  call HistoryGet ( file = 'phy_jupiter_case00_test00.nc', varname = 'lat_weight', array = y_Lat_Weight, quiet = .true. )                 ! (out)

  call HistoryGet ( file = 'phy_jupiter_case00_test00.nc', varname = 'sig', array = z_Sigma, quiet = .true. )                 ! (out)

  call HistoryGet ( file = 'phy_jupiter_case00_test00.nc', varname = 'sigm', array = r_Sigma, quiet = .true. )                 ! (out)

  do k = 0, kmax - 1
    z_DelSigma(k) = r_Sigma(k) - r_Sigma(k+1)
  enddo

  !-------------------------------------------------------------------
  !  基本の初期設定, 終了処理テスト
  !  Basic initialization and termination test
  !-------------------------------------------------------------------
  call PhyJpCreate( phy_jp = phy_jp00, imax = imax, jmax = jmax, kmax = kmax, x_Lon = x_Lon, y_Lat = y_Lat, z_Sigma = z_Sigma, r_Sigma = r_Sigma, x_Lon_Weight = x_Lon_Weight, y_Lat_Weight = y_Lat_Weight, DelTime = 1200.0_DP, GasRDry = GasRDry, Grav = Grav, CpDry = CpDry, LatentHeat = LatentHeat, GasRWet = GasRWet, EpsV = EpsV, ES0 = ES0, FKarm = FKarm )          ! (in)

  call AssertEqual( 'basic initialization test 1', answer = .true., check = PhyJpInitialized(phy_jp00) )
  call PhyJpPutLine( phy_jp = phy_jp00 ) ! (in)

  call PhyJpClose( phy_jp = phy_jp00 ) ! (inout)
  call AssertEqual( 'basic termination test 1', answer = .false., check = PhyJpInitialized(phy_jp00) )
  call PhyJpPutLine( phy_jp = phy_jp00 ) ! (in)

  !-------------------------------------------------------------------
  !  終了処理に関するエラー処理のテスト
  !  Error handling related to termination test
  !-------------------------------------------------------------------
  call PhyJpClose( phy_jp = phy_jp00, err = err )                                    ! (out)
  call AssertEqual( 'error handling related to termination test 1', answer = .true., check = err )

  !---------------------------------------------------------
  !  予報変数を入力
  !  Input predictional variables
  !---------------------------------------------------------
  call HistoryGet( file = 'phy_jupiter_case00_test00.nc', varname = 'U', array = xyz_U )               ! (out)

  call HistoryGet( file = 'phy_jupiter_case00_test00.nc', varname = 'V', array = xyz_V )               ! (out)

  call HistoryGet( file = 'phy_jupiter_case00_test00.nc', varname = 'Temp', array = xyz_Temp )            ! (out)

  call HistoryGet( file = 'phy_jupiter_case00_test00.nc', varname = 'QVap', array = xyz_QVap )            ! (out)

  call HistoryGet( file = 'phy_jupiter_case00_test00.nc', varname = 'Ps', array = xy_Ps )               ! (out)

  !-------------------------------------------------------------------
  !  PhysicsJupiter テスト
  !  PhysicsJupiter test
  !-------------------------------------------------------------------
  call PhyJpCreate( phy_jp = phy_jp01, imax = imax, jmax = jmax, kmax = kmax, x_Lon = x_Lon, y_Lat = y_Lat, z_Sigma = z_Sigma, r_Sigma = r_Sigma, x_Lon_Weight = x_Lon_Weight, y_Lat_Weight = y_Lat_Weight, DelTime = 1200.0_DP, GasRDry = GasRDry, Grav = Grav, CpDry = CpDry, LatentHeat = LatentHeat, GasRWet = GasRWet, EpsV = EpsV, ES0 = ES0, FKarm = FKarm )          ! (in)

  call PhysicsJupiter( phy_jp = phy_jp01, xyz_U = xyz_U,       xyz_V = xyz_V, xyz_Temp = xyz_Temp,    xy_Ps = xy_Ps, xyz_QVap = xyz_QVap, xyz_DUDt = xyz_DUDt, xyz_DVDt = xyz_DVDt, xyz_DTempDt = xyz_DTempDt, xyz_DQVapDt = xyz_DQVapDt )                 ! (out)

  call HistoryGet( file = 'phy_jupiter_case00_test01.nc', varname = 'DUDtJp', array = xyz_DUDtAns )                           ! (out)
  call HistoryGet( file = 'phy_jupiter_case00_test01.nc', varname = 'DVDtJp', array = xyz_DVDtAns )                           ! (out)
  call HistoryGet( file = 'phy_jupiter_case00_test01.nc', varname = 'DTempDtJp', array = xyz_DTempDtAns )                           ! (out)
  call HistoryGet( file = 'phy_jupiter_case00_test01.nc', varname = 'DQVapDtJp', array = xyz_DQVapDtAns )                           ! (out)

  call AssertEqual( 'PhysicsJupiter test 1', answer = xyz_DUDtAns, check = xyz_DUDt, significant_digits = 15, ignore_digits = -15 )
  call AssertEqual( 'PhysicsJupiter test 2', answer = xyz_DVDtAns, check = xyz_DVDt, significant_digits = 15, ignore_digits = -15 )
  call AssertEqual( 'PhysicsJupiter test 3', answer = xyz_DTempDtAns, check = xyz_DTempDt, significant_digits = 15, ignore_digits = -15 )
  call AssertEqual( 'PhysicsJupiter test 4', answer = xyz_DQVapDtAns, check = xyz_DQVapDt, significant_digits = 15, ignore_digits = -15 )

  !---------------------------------------------------------
  !  PhysicsJupiterAdjust テスト
  !  PhysicsJupiterAdjust test
  !---------------------------------------------------------
  call PhysicsJupiterAdjust( phy_jp = phy_jp01, xyz_Temp = xyz_Temp, xy_Ps = xy_Ps, xyz_QVap = xyz_QVap )                       ! (inout)

  call HistoryGet( file = 'phy_jupiter_case00_test02.nc', varname = 'Temp', array = xyz_TempAns )                           ! (out)
  call HistoryGet( file = 'phy_jupiter_case00_test02.nc', varname = 'QVap', array = xyz_QVapAns )                           ! (out)
  call HistoryGet( file = 'phy_jupiter_case00_test02.nc', varname = 'Ps', array = xy_PsAns )                            ! (out)

  call AssertEqual( 'PhysicsAdjust test 1', answer = xyz_TempAns, check = xyz_Temp, significant_digits = 15, ignore_digits = -15 )
  call AssertEqual( 'PhysicsAdjust test 2', answer = xyz_QVapAns, check = xyz_QVap, significant_digits = 15, ignore_digits = -15 )
  call AssertEqual( 'PhysicsAdjust test 3', answer = xy_PsAns, check = xy_Ps, significant_digits = 15, ignore_digits = -15 )


  !-------------------------------------------------------------------
  !  重複初期設定に関するエラー処理のテスト
  !  Error handling related to duplicated initialization test
  !-------------------------------------------------------------------
!!$  call PhyJpCreate( &
!!$    & phy_jp = phy_jp00 & ! (inout)
!!$    & , imax = imax, jmax = jmax, &              ! (in)
!!$    & x_Lon = x_Lon, y_Lat = y_Lat, &            ! (in)
!!$    & CoefAlpha = 0.0001_DP, DelTime = 0.5_DP &  ! (in)
!!$    & )
!!$  call PhyJpCreate( &
!!$    & phy_jp = phy_jp00, & ! (inout)
!!$    & imax = imax, jmax = jmax, &                ! (in)
!!$    & x_Lon = x_Lon, y_Lat = y_Lat, &            ! (in)
!!$    & CoefAlpha = 0.0001_DP, DelTime = 0.5_DP, & ! (in)
!!$    & err = err )                             ! (out)
!!$  call AssertEqual( 'error handling related to duplicated initialization test 1', &
!!$    & answer = .true., check = err )
!!$  call PhyJpPutLine( phy_jp = phy_jp00 ) ! (in)
!!$  call PhyJpClose( phy_jp = phy_jp00 ) ! (inout)


  !-------------------------------------------------------------------
  !  NAMELIST ファイルの読み込みテスト
  !  NAMELIST file loading test
  !-------------------------------------------------------------------
!!$  call PhyJpCreate( &
!!$    & phy_jp = phy_jp01, & ! (out)
!!$    & imax = imax, jmax = jmax, &                  ! (in)
!!$    & x_Lon = x_Lon, y_Lat = y_Lat, &              ! (in)
!!$    & CoefAlpha = - 0.0001_DP, DelTime = 0.5_DP, & ! (in)
!!$    & nmlfile = VAL_namelist )                ! (in)
!!$  call AssertEqual( 'NAMELIST file loading test 1', &
!!$    & answer = .true., check = PhyJpInitialized(phy_jp01) )
!!$  call PhyJpPutLine( phy_jp = phy_jp01 ) ! (in)
!!$  call PhyJpClose( phy_jp = phy_jp01 ) ! (inout)

  !-------------------------------------------------------------------
  !  無効な値に関するエラー処理のテスト
  !  Error handling related to invalid values test
  !-------------------------------------------------------------------
!!$  call PhyJpCreate( &
!!$    & phy_jp = phy_jp02, & ! (out)
!!$    & imax = imax, jmax = jmax, &                  ! (in)
!!$    & x_Lon = x_Lon, y_Lat = y_Lat, &              ! (in)
!!$    & CoefAlpha = - 0.0001_DP, DelTime = 0.5_DP, & ! (in)
!!$    & err = err )                                  ! (out)
!!$  call AssertEqual( 'error handling related to invalid values test 1', &
!!$    & answer = .true., check = err )

!!$  call PhyJpCreate( &
!!$    & phy_jp = phy_jp02, & ! (inout)
!!$    & imax = imax, jmax = jmax, &                  ! (in)
!!$    & x_Lon = x_Lon, y_Lat = y_Lat, &              ! (in)
!!$    & CoefAlpha = 0.0001_DP, DelTime = - 0.5_DP, & ! (in)
!!$    & err = err )                                  ! (out)
!!$  call AssertEqual( 'error handling related to invalid values test 2', &
!!$    & answer = .true., check = err )

  !-------------------------------------------------------------------
  !  ヒストリデータ出力テスト
  !  History data output test
  !-------------------------------------------------------------------
!!$  call PhyJpCreate( &
!!$    & phy_jp = phy_jp03, & ! (out)
!!$    & imax = imax, jmax = jmax, &              ! (in)
!!$    & x_Lon = x_Lon, y_Lat = y_Lat, &          ! (in)
!!$    & CoefAlpha = 0.01_DP, DelTime = 0.5_DP, & ! (in)
!!$    & current_time_value = 0.0, &              ! (in)
!!$    & current_time_unit = 'sec', &             ! (in)
!!$    & history_varlist = 'Data2', &             ! (in)
!!$    & history_interval_value = 2.0, &          ! (in)
!!$    & history_interval_unit = 'sec', &         ! (in)
!!$    & history_precision = 'float', &           ! (in)
!!$    & history_fileprefix = 'AP_' )             ! (in)
!!$  call PhyJpPutLine( phy_jp = phy_jp03 ) ! (in)
!!$
!!$  do i = 0, imax-1
!!$    x_Data1(i) = i * 1.0_DP
!!$  end do
!!$  do j = 0, jmax-1
!!$    y_Data2(j) = j * 1.1_DP
!!$  end do
!!$
!!$  do i = 1, 12
!!$    call PhyJpCalculation( &
!!$      & phy_jp = phy_jp03, & ! (inout)
!!$      & x_Data1 = x_Data1, y_Data2 = y_Data2 ) ! (inout)
!!$  end do
!!$
!!$  call PhyJpSetTime( &
!!$    & phy_jp = phy_jp03, & ! (inout)
!!$    & current_time_value = 1.0, current_time_unit = 'minute' ) ! (in)
!!$
!!$  call PhyJpCalculation( &
!!$    & phy_jp = phy_jp03, & ! (inout)
!!$    & x_Data1 = x_Data1, y_Data2 = y_Data2, & ! (inout)
!!$    & historyput_flag = .true. )              ! (in)
!!$
!!$  call PhyJpClose( phy_jp = phy_jp03 ) ! (inout)

!!$  !----------------------------------------------------------------
!!$  !  データ出力
!!$  !  Output data
!!$  !----------------------------------------------------------------
!!$  call HistoryCreate( &
!!$    & history = gthist, &                                ! (out)
!!$    & file = 'phy_jupiter_case00_test02.nc', &        ! (in)
!!$    & title = title, &                                   ! (in)
!!$    & source = source, institution = institution, &      ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig', 'sigm'), &        ! (in)
!!$    & dimsizes = (/imax, jmax, kmax, kmax + 1/), &       ! (in)
!!$    & longnames = &
!!$    &  StoA('longitude', 'latitude', &
!!$    &       'sigma at layer midpoints', &
!!$    &       'sigma at layer end-points (half level)'), & ! (in)
!!$    & units = StoA('degree_east', 'degree_north', &
!!$    &              '1', '1') )                           ! (out)
!!$
!!$  call HistoryPut( &
!!$    & history = gthist, &               ! (out)
!!$    & varname = 'lon', array = x_Lon )  ! (in)
!!$  call HistoryPut( &
!!$    & history = gthist, &               ! (out)
!!$    & varname = 'lat', array = y_Lat  ) ! (in)
!!$  call HistoryPut( &
!!$    & history = gthist, &                ! (out)
!!$    & varname = 'sig', array = z_Sigma ) ! (in)
!!$  call HistoryPut( &
!!$    & history = gthist, &                 ! (out)
!!$    & varname = 'sigm', array = r_Sigma ) ! (in)
!!$
!!$  call HistoryAddAttr( &
!!$    & history = gthist, &                    ! (inout)
!!$    & varname = 'lon', attrname = 'standard_name', & ! (in)
!!$    & value = 'longitude' )                          ! (in)
!!$  call HistoryAddAttr( &
!!$    & history = gthist, &                    ! (inout)
!!$    & varname = 'lat', attrname = 'standard_name', & ! (in)
!!$    & value = 'latitude' )                           ! (in)
!!$
!!$  call HistoryAddAttr( &
!!$    & history = gthist, &                              ! (inout)
!!$    & varname = 'sig', attrname = 'standard_name', &   ! (in)
!!$    & value = 'atmosphere_sigma_coordinate' )          ! (in)
!!$  call HistoryAddAttr( &
!!$    & history = gthist, &                              ! (inout)
!!$    & varname = 'sigm', attrname = 'standard_name', &  ! (in)
!!$    & value = 'atmosphere_sigma_coordinate' )          ! (in)
!!$  call HistoryAddAttr( &
!!$    & history = gthist, &                         ! (inout)
!!$    & varname = 'sig', attrname = 'positive', &   ! (in)
!!$    & value = 'down' )                            ! (in)
!!$  call HistoryAddAttr( &
!!$    & history = gthist, &                         ! (inout)
!!$    & varname = 'sigm', attrname = 'positive', &  ! (in)
!!$    & value = 'down' )                            ! (in)
!!$
!!$
!!$  call HistoryAddVariable( &
!!$    & history = gthist, &                  ! (inout)
!!$    & varname = 'Temp', &                  ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig'), &  ! (in)
!!$    & longname = 'temperature', &          ! (in)
!!$    & units = 'K', xtype = 'double' )      ! (in)
!!$  call HistoryPut( &
!!$    & history = gthist, &                  ! (inout)
!!$    & varname = 'Temp', array = xyz_Temp ) ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & history = gthist, &                  ! (inout)
!!$    & varname = 'QVap', &                  ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig'), &  ! (in)
!!$    & longname = 'specific humidity', &          ! (in)
!!$    & units = 'kg kg-1', xtype = 'double' )      ! (in)
!!$  call HistoryPut( &
!!$    & history = gthist, &                  ! (inout)
!!$    & varname = 'QVap', array = xyz_QVap ) ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & history = gthist, &                  ! (inout)
!!$    & varname = 'Ps', &                    ! (in)
!!$    & dims = StoA('lon', 'lat'), &         ! (in)
!!$    & longname = 'surface pressure', &     ! (in)
!!$    & units = 'Pa', xtype = 'double' )     ! (in)
!!$  call HistoryPut( &
!!$    & history = gthist, &                  ! (inout)
!!$    & varname = 'Ps', array = xy_Ps )      ! (in)
!!$
!!$  call HistoryClose( history = gthist ) ! (inout)

contains

  subroutine cmdline_optparse
    !
    ! コマンドライン引数の処理を行います
    !
    ! Handle command line options
    !
    call DCArgsOpen( arg = arg )               ! (out)

    call DCArgsHelpMsg( arg = arg, category = 'Title', msg = title )      ! (in)
    call DCArgsHelpMsg( arg = arg, category = 'Usage', msg = './' // trim(subname) // ' [Options]' )                   ! (in)
    call DCArgsHelpMsg( arg = arg, category = 'Source', msg = source )    ! (in)
    call DCArgsHelpMsg( arg = arg, category = 'Institution', msg = institution )                    ! (in)

    call DCArgsOption( arg = arg, options = StoA('-N', '--namelist'), flag = OPT_namelist, value = VAL_namelist, help = "Namelist filename")           ! (in)

    call DCArgsDebug( arg = arg )  ! (inout)
    call DCArgsHelp( arg = arg )   ! (inout)
    call DCArgsStrict( arg = arg ) ! (inout)

    call DCArgsClose( arg = arg )  ! (inout)
  end subroutine cmdline_optparse

end program phy_jupiter_case00_test

Private Instance methods

Subroutine :

コマンドライン引数の処理を行います

Handle command line options

[Source]

  subroutine cmdline_optparse
    !
    ! コマンドライン引数の処理を行います
    !
    ! Handle command line options
    !
    call DCArgsOpen( arg = arg )               ! (out)

    call DCArgsHelpMsg( arg = arg, category = 'Title', msg = title )      ! (in)
    call DCArgsHelpMsg( arg = arg, category = 'Usage', msg = './' // trim(subname) // ' [Options]' )                   ! (in)
    call DCArgsHelpMsg( arg = arg, category = 'Source', msg = source )    ! (in)
    call DCArgsHelpMsg( arg = arg, category = 'Institution', msg = institution )                    ! (in)

    call DCArgsOption( arg = arg, options = StoA('-N', '--namelist'), flag = OPT_namelist, value = VAL_namelist, help = "Namelist filename")           ! (in)

    call DCArgsDebug( arg = arg )  ! (inout)
    call DCArgsHelp( arg = arg )   ! (inout)
    call DCArgsStrict( arg = arg ) ! (inout)

    call DCArgsClose( arg = arg )  ! (inout)
  end subroutine cmdline_optparse

[Validate]