intavr_operate_test.f90

Path: shared/intavr_operate_test.f90
Last Update: Mon May 12 11:25:11 +0900 2008

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

Test program for "intavr_operate"

Authors:Yasuhiro MORIKAWA
Version:$Id: intavr_operate_test.f90,v 1.4 2008-05-12 02:25:11 morikawa Exp $
Tag Name:$Name: dcpam4-20080626 $
Copyright:Copyright (C) GFD Dennou Club, 2007. All rights reserved.
License:See COPYRIGHT

Note that Japanese and English are described in parallel.

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

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

Methods

Included Modules

intavr_operate constants dc_test dc_types dc_string dc_args gt4_history

Public Instance methods

Main Program :

[Source]

program intavr_operate_test
  use intavr_operate, only: INTAVROPR, IntAvrOprCreate, IntAvrOprClose, IntAvrOprPutLine, IntAvrOprInitialized, IntLonLat_xy, y_IntLon_xy, IntLon_x, x_IntLat_xy, IntLat_y, AvrLonLat_xy, y_AvrLon_xy, AvrLon_x, x_AvrLat_xy, AvrLat_y, ya_IntLon_xya, ya_AvrLon_xya, xa_IntLat_xya, xa_AvrLat_xya
  use constants, only: CONST, Create, Get
  use dc_test, only: AssertEqual, AssertGreaterThan, AssertLessThan
  use dc_types, only: DP, STRING
  use dc_string, only: StoA, PutLine, toChar
  use dc_args, only: ARGS, Open, HelpMsg, Option, Debug, Help, Strict, Close
  use gt4_history, only: HistoryGet
  implicit none

  !---------------------------------------------------------
  !  実験の表題, モデルの名称, 所属機関名
  !  Title of a experiment, name of model, sub-organ
  !---------------------------------------------------------
  character(*), parameter:: title = 'intavr_operate_test $Name: dcpam4-20080626 $ :: ' // 'Test program of "intavr_operate" 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 = 3
                              ! 鉛直層数. 
                              ! Number of vertical level

  !---------------------------------------------------------
  !  積分用座標重み
  !  Weight for integration
  !---------------------------------------------------------
  real(DP), allocatable:: x_Lon_Weight (:)
                                    ! 経度積分用座標重み. 
                                    ! Weight for integration in longitude
  real(DP), allocatable:: y_Lat_Weight (:)
                                    ! 緯度積分用座標重み. 
                                    ! Weight for integration in latitude

  !---------------------------------------------------------
  !  物理量
  !  Physical values
  !---------------------------------------------------------
  real(DP):: PI         ! $ \pi $ .    円周率.         Circular constant
  real(DP), allocatable:: xy_Temp (:,:)
                              ! $ T $ .     温度. Temperature
  real(DP), allocatable:: xyz_Temp (:,:,:)
                              ! $ T $ .     温度. Temperature
  real(DP), allocatable:: xz_TempIntLat (:,:)
                              ! $ T $ .     温度の緯度積分. 
                              ! Temperature integration in latitude
  real(DP), allocatable:: yz_TempAvrLon (:,:)
                              ! $ T $ .     温度の経度平均. 
                              ! Meridional mean temperature

  real(DP), allocatable:: x_TempIntLatAns (:)
                              ! $ T $ .     温度の緯度積分. 
                              ! Temperature integration in latitude
  real(DP), allocatable:: y_TempAvrLonAns (:)
                              ! $ T $ .     温度の経度平均. 
                              ! Meridional mean temperature

  real(DP):: TempAvrLonLatAns
                              ! $ T $ .     温度の全領域平均. 
                              ! Global mean temperature

  !---------------------------------------------------------
  !  作業変数
  !  Work variables
  !---------------------------------------------------------
  type(ARGS):: arg            ! コマンドライン引数. 
                              ! Command line arguments
  logical:: OPT_namelist      ! -N, --namelist オプションの有無. 
                              ! Existence of '-N', '--namelist' option
  character(STRING):: VAL_namelist
                              ! -N, --namelist オプションの値. 
                              ! Value of '-N', '--namelist' option
  type(INTAVROPR):: intavr_opr00, intavr_opr01, intavr_opr02
  type(CONST):: const_earth

  integer:: k                 ! DO ループ用作業変数
                              ! Work variables for DO loop

!!$  logical:: err
!!$  character(*), parameter:: subname = 'intavr_operate_test'
continue

  !---------------------------------------------------------
  !  コマンドライン引数の処理
  !  Command line arguments handling
  !---------------------------------------------------------
  call Open( arg )
  call HelpMsg( arg, 'Title', title )
  call HelpMsg( arg, 'Usage', './intavr_operate_test [Options]' )
  call HelpMsg( arg, 'Source', source )
  call HelpMsg( arg, 'Institution', institution )
  call Option( arg, StoA('-N', '--namelist'), OPT_namelist, VAL_namelist, help = 'NAMELIST filename' )
  call Debug( arg ) 
   call Help( arg ) 
   call Strict( arg, severe = .true. )
  call Close( arg )

  !---------------------------------------------------------
  !  物理定数の準備
  !  Prepare physical constants
  !---------------------------------------------------------
  call Create( const_earth ) ! (inout)

  call Get( constant = const_earth, PI = PI )                       ! (out)

  !---------------------------------------------------------
  !  初期設定テスト
  !  Initialization test
  !---------------------------------------------------------
  call IntAvrOprCreate( intavr_opr = intavr_opr00, imax = imax, jmax = jmax, PI = PI )                             ! (in)
  call AssertEqual( 'initialization test 1', answer = .true., check = IntAvrOprInitialized(intavr_opr00) )
  call IntAvrOprPutLine( intavr_opr = intavr_opr00 ) ! (in)

  !---------------------------------------------------------
  !  積分用座標重みの取得
  !  Get weight for integration
  !---------------------------------------------------------
  allocate( x_Lon_Weight (0:imax-1) )
  allocate( y_Lat_Weight (0:jmax-1) )

  call HistoryGet( file = 'intavr_operate_test00.nc', varname = 'lon_weight', array = x_Lon_Weight )        ! (out)
  call HistoryGet( file = 'intavr_operate_test00.nc', varname = 'lat_weight', array = y_Lat_Weight )        ! (out)

  !---------------------------------------------------------
  !  積分用座標重みを使用した初期設定テスト
  !  Initialization test with weight for integration
  !---------------------------------------------------------
  call IntAvrOprCreate( intavr_opr = intavr_opr01, imax = imax, jmax = jmax, PI = PI, x_Lon_Weight = x_Lon_Weight, y_Lat_Weight = y_Lat_Weight )         ! (in)
  call AssertEqual( 'initialization test 2', answer = .true., check = IntAvrOprInitialized(intavr_opr01) )
  call IntAvrOprPutLine( intavr_opr = intavr_opr01 ) ! (in)

  call IntAvrOprCreate( intavr_opr = intavr_opr02, imax = imax, jmax = jmax, PI = PI, kmax = kmax, x_Lon_Weight = x_Lon_Weight, y_Lat_Weight = y_Lat_Weight )         ! (in)

  !---------------------------------------------------------
  !  サンプルデータの入力
  !  Input sample data
  !---------------------------------------------------------
  allocate( xy_Temp (0:imax-1, 0:jmax-1) )
  call HistoryGet( file = 'intavr_operate_test00.nc', varname = 'SurfTemp', array = xy_Temp )                    ! (out)

  allocate( xyz_Temp (0:imax-1, 0:jmax-1, 0:kmax-1) )
  allocate( xz_TempIntLat (0:imax-1,0:kmax-1) )
  allocate( yz_TempAvrLon (0:jmax-1,0:kmax-1) )
  do k = 0, kmax-1
    call HistoryGet( file = 'intavr_operate_test00.nc', varname = 'SurfTemp', array = xyz_Temp(:,:,k) )            ! (out)
  end do

  !---------------------------------------------------------
  !  積分テスト
  !  Integration test
  !---------------------------------------------------------
  allocate( x_TempIntLatAns (0:imax-1) )

  call HistoryGet( file = 'intavr_operate_test01.nc', varname = 'IntLatTemp0', array = x_TempIntLatAns )            ! (out)

  call AssertEqual( 'integration test 1-1', answer = x_TempIntLatAns, check = x_IntLat_xy( xy_Temp, intavr_opr00 ), significant_digits = 15, ignore_digits = -15 )

  call HistoryGet( file = 'intavr_operate_test01.nc', varname = 'IntLatTemp1', array = x_TempIntLatAns )            ! (out)

  call AssertEqual( 'integration test 1-2', answer = x_TempIntLatAns, check = x_IntLat_xy( xy_Temp, intavr_opr01 ), significant_digits = 15, ignore_digits = -15 )

  xz_TempIntLat = xa_IntLat_xya( xyz_Temp, intavr_opr02 )
  do k = 0, kmax-1
    call AssertEqual( 'integration test 2-' // trim(toChar(k+1)), answer = x_TempIntLatAns, check = xz_TempIntLat(:,k), significant_digits = 15, ignore_digits = -15 )
  end do

  !---------------------------------------------------------
  !  平均テスト 1
  !  Average test 1
  !---------------------------------------------------------
  allocate( y_TempAvrLonAns (0:jmax-1) )

  call HistoryGet( file = 'intavr_operate_test01.nc', varname = 'AvrLonTemp0', array = y_TempAvrLonAns )            ! (out)

  call AssertEqual( 'average test 1-1', answer = y_TempAvrLonAns, check = y_AvrLon_xy( xy_Temp, intavr_opr00 ), significant_digits = 15, ignore_digits = -15 )

  call HistoryGet( file = 'intavr_operate_test01.nc', varname = 'AvrLonTemp1', array = y_TempAvrLonAns )            ! (out)

  call AssertEqual( 'average test 1-2', answer = y_TempAvrLonAns, check = y_AvrLon_xy( xy_Temp, intavr_opr01 ), significant_digits = 15, ignore_digits = -15 )

  yz_TempAvrLon = ya_AvrLon_xya( xyz_Temp, intavr_opr02 )
  do k = 0, kmax-1
    call AssertEqual( 'average test 2-' // trim(toChar(k+1)), answer = y_TempAvrLonAns, check = yz_TempAvrLon(:,k), significant_digits = 15, ignore_digits = -15 )
  end do

  !---------------------------------------------------------
  !  平均テスト 2
  !  Average test 2
  !---------------------------------------------------------
  call HistoryGet( file = 'intavr_operate_test01.nc', varname = 'AvrLonLatTemp0', array = TempAvrLonLatAns )           ! (out)

  call AssertEqual( 'average test 2-1', answer = TempAvrLonLatAns, check = AvrLonLat_xy( xy_Temp, intavr_opr00 ), significant_digits = 15, ignore_digits = -15 )

  call HistoryGet( file = 'intavr_operate_test01.nc', varname = 'AvrLonLatTemp1', array = TempAvrLonLatAns )           ! (out)

  call AssertEqual( 'average test 2-2', answer = TempAvrLonLatAns, check = AvrLonLat_xy( xy_Temp, intavr_opr01 ), significant_digits = 15, ignore_digits = -15 )

  !---------------------------------------------------------
  !  終了処理テスト
  !  Termination test
  !---------------------------------------------------------
  call IntAvrOprClose( intavr_opr = intavr_opr00 ) ! (inout)
  call AssertEqual( 'termination test 1', answer = .false., check = IntAvrOprInitialized(intavr_opr00) )
  call IntAvrOprPutLine( intavr_opr = intavr_opr00 ) ! (in)

!!$  call IntAvrOprClose( intavr_opr = intavr_opr02, & ! (inout)
!!$    & err = err )                            ! (out)
!!$  call AssertEqual( 'termination test 2', &
!!$    & answer = .true., check = err )

end program intavr_operate_test

[Validate]