dyn_spectral_as83_test.f90

Path: dynamics/dyn_spectral_as83_test.f90
Last Update: Sat Jun 14 20:44:17 +0900 2008

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

Test program for "dyn_spectral_as83"

Authors:Yasuhiro MORIKAWA
Version:$Id: dyn_spectral_as83_test.f90,v 1.14 2008-06-14 11:44:17 morikawa Exp $
Tag Name:$Name: dcpam4-20080624-1 $
Copyright:Copyright (C) GFD Dennou Club, 2007. All rights reserved.
License:See COPYRIGHT

Note that Japanese and English are described in parallel.

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

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

Methods

Included Modules

constants dc_types dc_message dyn_spectral_as83 dc_test dc_string dc_args gt4_history

Public Instance methods

Main Program :

[Source]

program dyn_spectral_as83_test
  use constants, only: CONST, Create, Get
  use dc_types, only: DP, STRING
  use dc_message, only: MessageNotify
  use dyn_spectral_as83, only: DYNSPAS83, DynSpAsCreate, DynSpAsClose, DynSpAsPutLine, DynSpAsInitialized, DynSpAsEqualAxes, Dynamics
  use dc_test, only: AssertEqual, AssertGreaterThan, AssertLessThan
  use dc_string, only: StoA
  use dc_args, only: ARGS, DCArgsOpen, DCArgsHelpMsg, DCArgsOption, DCArgsDebug, DCArgsHelp, DCArgsStrict, DCArgsClose
  use gt4_history, only: HistoryGet
  use gt4_history, only: GT_HISTORY, HistoryGet, HistoryCopy, HistoryCreate, HistoryAddVariable, HistoryPut, HistoryClose
  implicit none

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

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

  !---------------------------------------------------------
  !  作業変数
  !  Work variables
  !---------------------------------------------------------
  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(CONST):: const_earth
  real(DP):: PI         ! $ \pi $ .    円周率.         Circular constant
  real(DP):: RPlanet    ! $ a $ .      惑星半径.       Radius of planet
  real(DP):: Omega      ! $ \Omega $ . 回転角速度.     Angular velocity
!!$  real(DP):: Grav       ! $ g $ .      重力加速度.     Gravitational acceleration
  real(DP):: Cp         ! $ C_p $ .    大気定圧比熱.   Specific heat of air at constant pressure
  real(DP):: RAir       ! $ R $ .      大気気体定数.   Gas constant of air
  real(DP):: EpsV       ! $ \epsilon_v $ .        水蒸気分子量比. Molecular weight ratio of water vapor
  integer:: VisOrder    ! 超粘性の次数.  Order of hyper-viscosity
  real(DP):: EFoldTime  ! 最大波数に対する e-folding time. E-folding time for maximum wavenumber
  type(DYNSPAS83):: dyn_sp_as00, dyn_sp_as01, dyn_sp_as02
  real(DP):: DelTime
  logical:: err

  

  real(DP), allocatable:: x_Lon (:)
  real(DP), allocatable:: y_Lat (:)
  real(DP), allocatable:: z_Sigma (:)
  real(DP), allocatable:: r_Sigma (:)


  real(DP):: xyz_VorB (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \zeta (t-\Delta t) $ . 渦度. Vorticity
  real(DP):: xyz_DivB (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ D (t-\Delta t) $ .     発散. Divergence
  real(DP):: xyz_TempB (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ T (t-\Delta t) $ .     温度. Temperature
  real(DP):: xy_PsB (0:imax-1, 0:jmax-1)
                              ! $ p_s (t-\Delta t) $ .   地表面気圧. Surface pressure
  real(DP):: xyz_QVapB (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ q (t-\Delta t) $ .     比湿. Specific humidity
  real(DP):: xyz_VorN (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \zeta (t) $ . 渦度. Vorticity
  real(DP):: xyz_DivN (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ D (t) $ .     発散. Divergence
  real(DP):: xyz_TempN (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ T (t) $ .     温度. Temperature
  real(DP):: xy_PsN (0:imax-1, 0:jmax-1)
                              ! $ p_s (t) $ .   地表面気圧. Surface pressure
  real(DP):: xyz_QVapN (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ q (t) $ .     比湿. Specific humidity

  real(DP):: xyz_VorA (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \zeta (t+\Delta t) $ . 渦度. Vorticity
  real(DP):: xyz_DivA (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ D (t+\Delta t) $ .     発散. Divergence
  real(DP):: xyz_TempA (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ T (t+\Delta t) $ .     温度. Temperature
  real(DP):: xy_PsA (0:imax-1, 0:jmax-1)
                              ! $ p_s (t+\Delta t) $ .   地表面気圧. Surface pressure
  real(DP):: xyz_QVapA (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ q (t+\Delta t) $ .     比湿. Specific humidity

  real(DP):: xyz_VorAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \zeta (t+\Delta t) $ . 渦度. Vorticity
  real(DP):: xyz_DivAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ D (t+\Delta t) $ .     発散. Divergence
  real(DP):: xyz_TempAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ T (t+\Delta t) $ .     温度. Temperature
  real(DP):: xy_PsAns (0:imax-1, 0:jmax-1)
                              ! $ p_s (t+\Delta t) $ .   地表面気圧. Surface pressure
  real(DP):: xyz_QVapAns (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ q (t+\Delta t) $ .     比湿. Specific humidity

  real(DP):: xyz_VorAnsG (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \zeta (t+\Delta t) $ . 渦度. Vorticity
  real(DP):: xyz_DivAnsG (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ D (t+\Delta t) $ .     発散. Divergence
  real(DP):: xyz_TempAnsG (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ T (t+\Delta t) $ .     温度. Temperature
  real(DP):: xy_PsAnsG (0:imax-1, 0:jmax-1)
                              ! $ p_s (t+\Delta t) $ .   地表面気圧. Surface pressure
  real(DP):: xyz_QVapAnsG (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ q (t+\Delta t) $ .     比湿. Specific humidity

  real(DP):: xyz_VorAnsL (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ \zeta (t+\Delta t) $ . 渦度. Vorticity
  real(DP):: xyz_DivAnsL (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ D (t+\Delta t) $ .     発散. Divergence
  real(DP):: xyz_TempAnsL (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ T (t+\Delta t) $ .     温度. Temperature
  real(DP):: xy_PsAnsL (0:imax-1, 0:jmax-1)
                              ! $ p_s (t+\Delta t) $ .   地表面気圧. Surface pressure
  real(DP):: xyz_QVapAnsL (0:imax-1, 0:jmax-1, 0:kmax-1)
                              ! $ q (t+\Delta t) $ .     比湿. Specific humidity

  character(*), parameter:: subname = 'dyn_spectral_as83_test'
continue

  !---------------------------------------------------------
  !  コマンドライン引数の処理
  !  Command line options handling
  !---------------------------------------------------------
  call cmdline_optparse ! これは内部サブルーチン. This is internal subroutine

  !---------------------------------------------------------
  !  物理定数の準備
  !  Prepare physical constants
  !---------------------------------------------------------
  call Create( const_earth, Omega = 7.292e-5_DP ) ! (inout)

  DelTime = 480.0_DP

  call Get( constant = const_earth, PI = PI, RPlanet = RPlanet, Omega = Omega, Cp = Cp, RAir = RAir, EpsV = EpsV, VisOrder = VisOrder, EFoldTime = EFoldTime ) ! (out)

  !---------------------------------------------------------
  !  初期設定テスト
  !  Initialization test
  !---------------------------------------------------------
  call DynSpAsCreate( dyn_sp_as = dyn_sp_as00, nmax = nmax, imax = imax, jmax = jmax, kmax = kmax, PI = PI, RPlanet = RPlanet, Omega = Omega, Cp = Cp, RAir = RAir, EpsV = EpsV, VisOrder = VisOrder, EFoldTime = EFoldTime, DelTime = DelTime, current_time_value = 0.0, current_time_unit = 'sec', history_varlist = 'SigmaDot, DPiDt', history_interval_value = 8.0, history_interval_unit = 'min' )               ! (in)

  call AssertEqual( 'initialization test 1', answer = .true., check = DynSpAsInitialized(dyn_sp_as00) )
  call DynSpAsPutLine( dyn_sp_as00 ) ! (in)

  call DynSpAsCreate( dyn_sp_as = dyn_sp_as01, nmax = nmax, imax = imax, jmax = jmax, kmax = kmax, PI = PI, RPlanet = RPlanet, Omega = Omega, Cp = Cp, RAir = RAir, EpsV = EpsV, VisOrder = VisOrder, EFoldTime = EFoldTime, DelTIme = DelTime, time_integration_scheme = 'Explicit', wa_module_initialized = .true., current_time_value = 16.0, current_time_unit = 'min', nmlfile = VAL_namelist )                      ! (in)
  call AssertEqual( 'initialization test 2', answer = .true., check = DynSpAsInitialized(dyn_sp_as01) )
  call DynSpAsPutLine( dyn_sp_as01 ) ! (in)


  !---------------------------------------------------------
  !  DynSpAsEqualAxes テスト
  !  "DynSpAsEqualAxes" test
  !---------------------------------------------------------
  allocate( x_Lon (0:63) )
  allocate( y_Lat (0:31) )
  allocate( z_Sigma (0:19) )
  allocate( r_Sigma (0:20) )

  call HistoryGet ( file = 'dyn_spectral_as83_test00.nc', varname = 'lon', array = x_Lon, quiet = .true. )                          ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test00.nc', varname = 'lat', array = y_Lat, quiet = .true. )                          ! (out)

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

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

  call DynSpAsEqualAxes( dyn_sp_as = dyn_sp_as00, x_Lon = x_Lon,     y_Lat = y_Lat, z_Sigma = z_Sigma, r_Sigma = r_Sigma, err = err )                                    ! (out)

  call AssertEqual( '"EqualAxes" test 1', answer = .false., check = err )

  !---------------------------------------------------------
  !  Dynamics テスト用の初期値データ読み込み
  !  Load initial data for "Dynamics" test
  !---------------------------------------------------------
  call HistoryGet ( file = 'dyn_spectral_as83_test01.nc', varname = 'Vor', array = xyz_VorB, range='time=253428', quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test01.nc', varname = 'Div', array = xyz_DivB, range='time=253428', quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test01.nc', varname = 'Temp', array = xyz_TempB, range='time=253428', quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test01.nc', varname = 'Ps', array = xy_PsB, range='time=253428', quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test01.nc', varname = 'QVap', array = xyz_QVapB, range='time=253428', quiet = .false. )  ! (out)


  call HistoryGet ( file = 'dyn_spectral_as83_test01.nc', varname = 'Vor', array = xyz_VorN, range='time=253440', quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test01.nc', varname = 'Div', array = xyz_DivN, range='time=253440', quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test01.nc', varname = 'Temp', array = xyz_TempN, range='time=253440', quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test01.nc', varname = 'Ps', array = xy_PsN, range='time=253440', quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test01.nc', varname = 'QVap', array = xyz_QVapN, range='time=253440', quiet = .false. )  ! (out)


  !---------------------------------------------------------
  !  Dynamics テスト (セミインプリシット法)
  !  "Dynamics" test (Semi-implicit scheme)
  !---------------------------------------------------------
  call HistoryGet ( file = 'dyn_spectral_as83_test02.nc', varname = 'Vor', array = xyz_VorAns, quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test02.nc', varname = 'Div', array = xyz_DivAns, quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test02.nc', varname = 'Temp', array = xyz_TempAns, quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test02.nc', varname = 'Ps', array = xy_PsAns, quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test02.nc', varname = 'QVap', array = xyz_QVapAns, quiet = .false. )  ! (out)


  call Dynamics ( dyn_sp_as = dyn_sp_as00, xyz_VorB  = xyz_VorB,  xyz_DivB  = xyz_DivB, xyz_TempB = xyz_TempB, xyz_QVapB = xyz_QVapB, xy_PsB    = xy_PsB, xyz_VorN  = xyz_VorN,  xyz_DivN  = xyz_DivN, xyz_TempN = xyz_TempN, xyz_QVapN = xyz_QVapN, xy_PsN    = xy_PsN, xyz_VorA  = xyz_VorA,  xyz_DivA  = xyz_DivA, xyz_TempA = xyz_TempA, xyz_QVapA = xyz_QVapA, xy_PsA    = xy_PsA )                            ! (out)

!!$  call HistoryCreate( &
!!$    & file = 'dyn_spectral_as83_test02.nc', &               ! (in)
!!$    & title = 'Test data for ' // &
!!$    &   '"Dynamics#dyn_spectral_as83_test" ' // &
!!$    &   '(Semi-implicit scheme)', &                        ! (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') )                              ! (in)
!!$
!!$  call HistoryPut( &
!!$    & varname = 'lon', array = x_Lon / PI * 180.0_DP )  ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'lat', array = y_Lat / PI * 180.0_DP )  ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'sig', array = z_Sigma )  ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'sigm', array = r_Sigma )  ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & varname = 'Vor', &                            ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig'), &           ! (in)
!!$    & longname = 'vorticity', &                     ! (in)
!!$    & units = 's-1', xtype = 'double' )             ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & varname = 'Div', &                            ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig'), &           ! (in)
!!$    & longname = 'divergence', &                    ! (in)
!!$    & units = 's-1', xtype = 'double' )             ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & varname = 'Temp', &                           ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig'), &           ! (in)
!!$    & longname = 'temperature', &                   ! (in)
!!$    & units = 'K', xtype = 'double' )               ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & varname = 'QVap', &                           ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig'), &           ! (in)
!!$    & longname = 'specific humidity', &             ! (in)
!!$    & units = '1', xtype = 'double' )               ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & varname = 'Ps', &                       ! (in)
!!$    & dims = StoA('lon', 'lat'), &            ! (in)
!!$    & longname = 'surface pressure', &        ! (in)
!!$    & units = 'Pa', xtype = 'double' )        ! (in)
!!$
!!$  call HistoryPut( &
!!$    & varname = 'Vor', array = xyz_VorA )   ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'Div', array = xyz_DivA )   ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'Temp', array = xyz_TempA )   ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'QVap', array = xyz_QVapA )   ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'Ps', array = xy_PsA )   ! (in)
!!$
!!$  call HistoryClose

  call MessageNotify( 'M', subname, 'Testing "Dynamics" (Semi-implicit scheme) ...' )

  where ( xyz_VorAns < 0.0_DP )
    xyz_VorAnsG = xyz_VorAns + 1.0e-16_DP
    xyz_VorAnsL = xyz_VorAns - 1.0e-16_DP
  elsewhere
    xyz_VorAnsG = xyz_VorAns - 1.0e-16_DP
    xyz_VorAnsL = xyz_VorAns + 1.0e-16_DP
  end where

  call AssertGreaterThan( 'xyz_Vor test 1-1', answer = xyz_VorAnsG * 0.999999999_DP, check = xyz_VorA )

  call AssertLessThan( 'xyz_Vor test 1-1', answer = xyz_VorAnsL * 1.000000001_DP, check = xyz_VorA )

  where ( xyz_DivAns < 0.0_DP )
    xyz_DivAnsG = xyz_DivAns + 1.0e-16_DP
    xyz_DivAnsL = xyz_DivAns - 1.0e-16_DP
  elsewhere
    xyz_DivAnsG = xyz_DivAns - 1.0e-16_DP
    xyz_DivAnsL = xyz_DivAns + 1.0e-16_DP
  end where

  call AssertGreaterThan( 'xyz_Div test 1-1', answer = xyz_DivAnsG * 0.999999999_DP, check = xyz_DivA )

  call AssertLessThan( 'xyz_Div test 1-1', answer = xyz_DivAnsL * 1.000000001_DP, check = xyz_DivA )

  where ( xyz_TempAns < 0.0_DP )
    xyz_TempAnsG = xyz_TempAns + 1.0e-16_DP
    xyz_TempAnsL = xyz_TempAns - 1.0e-16_DP
  elsewhere
    xyz_TempAnsG = xyz_TempAns - 1.0e-16_DP
    xyz_TempAnsL = xyz_TempAns + 1.0e-16_DP
  end where

  call AssertGreaterThan( 'xyz_Temp test 1-1', answer = xyz_TempAnsG * 0.999999999_DP, check = xyz_TempA )

  call AssertLessThan( 'xyz_Temp test 1-1', answer = xyz_TempAnsL * 1.000000001_DP, check = xyz_TempA )

  where ( xy_PsAns < 0.0_DP )
    xy_PsAnsG = xy_PsAns + 1.0e-16_DP
    xy_PsAnsL = xy_PsAns - 1.0e-16_DP
  elsewhere
    xy_PsAnsG = xy_PsAns - 1.0e-16_DP
    xy_PsAnsL = xy_PsAns + 1.0e-16_DP
  end where

  call AssertGreaterThan( 'xy_Ps test 1-1', answer = xy_PsAnsG * 0.999999999_DP, check = xy_PsA )

  call AssertLessThan( 'xy_Ps test 1-1', answer = xy_PsAnsL * 1.000000001_DP, check = xy_PsA )

  where ( xyz_QVapAns < 0.0_DP )
    xyz_QVapAnsG = xyz_QVapAns + 1.0e-16_DP
    xyz_QVapAnsL = xyz_QVapAns - 1.0e-16_DP
  elsewhere
    xyz_QVapAnsG = xyz_QVapAns - 1.0e-16_DP
    xyz_QVapAnsL = xyz_QVapAns + 1.0e-16_DP
  end where

  call AssertGreaterThan( 'xyz_QVap test 1-1', answer = xyz_QVapAnsG * 0.999999999_DP, check = xyz_QVapA )

  call AssertLessThan( 'xyz_QVap test 1-1', answer = xyz_QVapAnsL * 1.000000001_DP, check = xyz_QVapA )



  !---------------------------------------------------------
  !  Dynamics テスト (エクスプリシット法)
  !  "Dynamics" test (Explicit scheme)
  !---------------------------------------------------------
  call HistoryGet ( file = 'dyn_spectral_as83_test03.nc', varname = 'Vor', array = xyz_VorAns, quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test03.nc', varname = 'Div', array = xyz_DivAns, quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test03.nc', varname = 'Temp', array = xyz_TempAns, quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test03.nc', varname = 'Ps', array = xy_PsAns, quiet = .false. )  ! (out)

  call HistoryGet ( file = 'dyn_spectral_as83_test03.nc', varname = 'QVap', array = xyz_QVapAns, quiet = .false. )  ! (out)

  call Dynamics ( dyn_sp_as = dyn_sp_as01, xyz_VorB  = xyz_VorB,  xyz_DivB  = xyz_DivB, xyz_TempB = xyz_TempB, xyz_QVapB = xyz_QVapB, xy_PsB    = xy_PsB, xyz_VorN  = xyz_VorN,  xyz_DivN  = xyz_DivN, xyz_TempN = xyz_TempN, xyz_QVapN = xyz_QVapN, xy_PsN    = xy_PsN, xyz_VorA  = xyz_VorA,  xyz_DivA  = xyz_DivA, xyz_TempA = xyz_TempA, xyz_QVapA = xyz_QVapA, xy_PsA    = xy_PsA )                            ! (out)

!!$  call HistoryCreate( &
!!$    & file = 'dyn_spectral_as83_test03.nc', &               ! (in)
!!$    & title = 'Test data for ' // &
!!$    &   '"Dynamics#dyn_spectral_as83_test" ' // &
!!$    &   '(Explicit scheme)', &                              ! (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') )                              ! (in)
!!$
!!$  call HistoryPut( &
!!$    & varname = 'lon', array = x_Lon / PI * 180.0_DP )  ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'lat', array = y_Lat / PI * 180.0_DP )  ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'sig', array = z_Sigma )  ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'sigm', array = r_Sigma )  ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & varname = 'Vor', &                            ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig'), &           ! (in)
!!$    & longname = 'vorticity', &                     ! (in)
!!$    & units = 's-1', xtype = 'double' )             ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & varname = 'Div', &                            ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig'), &           ! (in)
!!$    & longname = 'divergence', &                    ! (in)
!!$    & units = 's-1', xtype = 'double' )             ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & varname = 'Temp', &                           ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig'), &           ! (in)
!!$    & longname = 'temperature', &                   ! (in)
!!$    & units = 'K', xtype = 'double' )               ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & varname = 'QVap', &                           ! (in)
!!$    & dims = StoA('lon', 'lat', 'sig'), &           ! (in)
!!$    & longname = 'specific humidity', &             ! (in)
!!$    & units = '1', xtype = 'double' )               ! (in)
!!$
!!$  call HistoryAddVariable( &
!!$    & varname = 'Ps', &                       ! (in)
!!$    & dims = StoA('lon', 'lat'), &            ! (in)
!!$    & longname = 'surface pressure', &        ! (in)
!!$    & units = 'Pa', xtype = 'double' )        ! (in)
!!$
!!$  call HistoryPut( &
!!$    & varname = 'Vor', array = xyz_VorA )   ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'Div', array = xyz_DivA )   ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'Temp', array = xyz_TempA )   ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'QVap', array = xyz_QVapA )   ! (in)
!!$  call HistoryPut( &
!!$    & varname = 'Ps', array = xy_PsA )   ! (in)
!!$
!!$  call HistoryClose

  call MessageNotify( 'M', subname, 'Testing "Dynamics" (Explicit scheme) ...' )

  where ( xyz_VorAns < 0.0_DP )
    xyz_VorAnsG = xyz_VorAns + 1.0e-16_DP
    xyz_VorAnsL = xyz_VorAns - 1.0e-16_DP
  elsewhere
    xyz_VorAnsG = xyz_VorAns - 1.0e-16_DP
    xyz_VorAnsL = xyz_VorAns + 1.0e-16_DP
  end where

  call AssertGreaterThan( 'xyz_Vor test 1-1', answer = xyz_VorAnsG * 0.999999999_DP, check = xyz_VorA )

  call AssertLessThan( 'xyz_Vor test 1-1', answer = xyz_VorAnsL * 1.000000001_DP, check = xyz_VorA )

  where ( xyz_DivAns < 0.0_DP )
    xyz_DivAnsG = xyz_DivAns + 1.0e-16_DP
    xyz_DivAnsL = xyz_DivAns - 1.0e-16_DP
  elsewhere
    xyz_DivAnsG = xyz_DivAns - 1.0e-16_DP
    xyz_DivAnsL = xyz_DivAns + 1.0e-16_DP
  end where

  call AssertGreaterThan( 'xyz_Div test 1-1', answer = xyz_DivAnsG * 0.999999999_DP, check = xyz_DivA )

  call AssertLessThan( 'xyz_Div test 1-1', answer = xyz_DivAnsL * 1.000000001_DP, check = xyz_DivA )

  where ( xyz_TempAns < 0.0_DP )
    xyz_TempAnsG = xyz_TempAns + 1.0e-16_DP
    xyz_TempAnsL = xyz_TempAns - 1.0e-16_DP
  elsewhere
    xyz_TempAnsG = xyz_TempAns - 1.0e-16_DP
    xyz_TempAnsL = xyz_TempAns + 1.0e-16_DP
  end where

  call AssertGreaterThan( 'xyz_Temp test 1-1', answer = xyz_TempAnsG * 0.999999999_DP, check = xyz_TempA )

  call AssertLessThan( 'xyz_Temp test 1-1', answer = xyz_TempAnsL * 1.000000001_DP, check = xyz_TempA )

  where ( xy_PsAns < 0.0_DP )
    xy_PsAnsG = xy_PsAns + 1.0e-16_DP
    xy_PsAnsL = xy_PsAns - 1.0e-16_DP
  elsewhere
    xy_PsAnsG = xy_PsAns - 1.0e-16_DP
    xy_PsAnsL = xy_PsAns + 1.0e-16_DP
  end where

  call AssertGreaterThan( 'xy_Ps test 1-1', answer = xy_PsAnsG * 0.999999999_DP, check = xy_PsA )

  call AssertLessThan( 'xy_Ps test 1-1', answer = xy_PsAnsL * 1.000000001_DP, check = xy_PsA )

  where ( xyz_QVapAns < 0.0_DP )
    xyz_QVapAnsG = xyz_QVapAns + 1.0e-16_DP
    xyz_QVapAnsL = xyz_QVapAns - 1.0e-16_DP
  elsewhere
    xyz_QVapAnsG = xyz_QVapAns - 1.0e-16_DP
    xyz_QVapAnsL = xyz_QVapAns + 1.0e-16_DP
  end where

  call AssertGreaterThan( 'xyz_QVap test 1-1', answer = xyz_QVapAnsG * 0.999999999_DP, check = xyz_QVapA )

  call AssertLessThan( 'xyz_QVap test 1-1', answer = xyz_QVapAnsL * 1.000000001_DP, check = xyz_QVapA )

  !---------------------------------------------------------
  !  終了処理テスト
  !  Termination test
  !---------------------------------------------------------
  call DynSpAsClose( dyn_sp_as00 ) ! (inout)
  call AssertEqual( 'termination test 1', answer = .false., check = DynSpAsInitialized(dyn_sp_as00) )
  call DynSpAsPutLine( dyn_sp_as00 )

  call DynSpAsClose( dyn_sp_as02, err )                         ! (out)
  call AssertEqual( 'termination test 2', answer = .true., check = err )

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 dyn_spectral_as83_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]