!= phy_sponge_layer モジュールのテストプログラム ! != Test program for "phy_sponge_layer" ! ! Authors:: Yasuhiro MORIKAWA ! Version:: $Id: phy_sponge_layer_test.f90,v 1.1 2008-05-12 06:34:48 morikawa Exp $ ! Tag Name:: $Name: dcpam4-20080609-1 $ ! Copyright:: Copyright (C) GFD Dennou Club, 2008. All rights reserved. ! License:: See COPYRIGHT[link:../../../COPYRIGHT] ! ! Note that Japanese and English are described in parallel. ! ! phy_sponge_layer モジュールの動作テストを行うためのプログラムです. ! このプログラムがコンパイルできること, および実行時に ! プログラムが正常終了することを確認してください. ! ! This program checks the operation of "phy_sponge_layer" module. ! Confirm compilation and execution of this program. ! program phy_sponge_layer_test use phy_sponge_layer, only: PHYSPOLAY, PhySpoLayCreate, & & Damping, PhySpoLayClose, & & PhySpoLayPutLine, PhySpoLayInitialized, & & PhySpoLaySetTime 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 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_sponge_layer_test $Name: dcpam4-20080609-1 $ :: ' // & & 'Test program of "phy_sponge_layer" 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 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):: xy_Ps (0:imax-1, 0:jmax-1) ! $ p_s $ . 地表面気圧. Surface pressure real(DP):: xyz_DUDtSpoDamping (0:imax-1, 0:jmax-1, 0:kmax-1) ! $ \DP{u}{t} $ . ! 減衰の効果による東西風速変化. ! Zonal wind tendency by damping effect real(DP):: xyz_DUDtSpoDampingAns (0:imax-1, 0:jmax-1, 0:kmax-1) ! $ \DP{u}{t} $ . ! 減衰の効果による東西風速変化. ! Zonal wind tendency by damping effect real(DP):: xyz_DVDtSpoDamping (0:imax-1, 0:jmax-1, 0:kmax-1) ! $ \DP{v}{t} $ . ! 減衰の効果による南北風速変化. ! Meridional wind tendency by damping effect real(DP):: xyz_DVDtSpoDampingAns (0:imax-1, 0:jmax-1, 0:kmax-1) ! $ \DP{v}{t} $ . ! 減衰の効果による南北風速変化. ! Meridional wind tendency by damping effect !------------------------------------------------------------------- ! 定数 ! Constants !------------------------------------------------------------------- real(DP), parameter:: PI = 3.1415926535897930_DP ! $ \pi $ . 円周率. Circular constant !------------------------------------------------------------------- ! データ入出力 ! Data I/O !------------------------------------------------------------------- type(GT_HISTORY):: gthist !------------------------------------------------------------------- ! 作業変数 ! Work variables !------------------------------------------------------------------- integer:: i, j, 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(PHYSPOLAY):: phy_spo_lay00, phy_spo_lay01 !!$ type(PHYSPOLAY):: phy_spo_lay02, phy_spo_lay03 logical:: err character(*), parameter:: subname = 'phy_sponge_layer_test' continue !------------------------------------------------------------------- ! コマンドライン引数の処理 ! Command line options handling !------------------------------------------------------------------- call cmdline_optparse ! これは内部サブルーチン. This is an internal subroutine !------------------------------------------------------------------- ! 軸データの設定 ! Configure axes data !------------------------------------------------------------------- call HistoryGet ( & & file = 'phy_sponge_layer_test00.nc', varname = 'lon', & ! (in) & array = x_Lon, quiet = .true. ) ! (out) x_Lon = x_Lon * PI / 180.0_DP call HistoryGet ( & & file = 'phy_sponge_layer_test00.nc', varname = 'lon_weight', & ! (in) & array = x_Lon_Weight, quiet = .true. ) ! (out) call HistoryGet ( & & file = 'phy_sponge_layer_test00.nc', varname = 'lat', & ! (in) & array = y_Lat, quiet = .true. ) ! (out) y_Lat = y_Lat * PI / 180.0_DP call HistoryGet ( & & file = 'phy_sponge_layer_test00.nc', varname = 'lat_weight', & ! (in) & array = y_Lat_Weight, quiet = .true. ) ! (out) call HistoryGet ( & & file = 'phy_sponge_layer_test00.nc', varname = 'sig', & ! (in) & array = z_Sigma, quiet = .true. ) ! (out) call HistoryGet ( & & file = 'phy_sponge_layer_test00.nc', varname = 'sigm', & ! (in) & array = r_Sigma, quiet = .true. ) ! (out) do k = 0, kmax - 1 z_DelSigma(k) = r_Sigma(k) - r_Sigma(k+1) enddo !--------------------------------------------------------- ! データ入力 ! Input data !--------------------------------------------------------- call HistoryGet ( & & file = 'phy_sponge_layer_test00.nc', varname = 'U', & ! (in) & array = xyz_U, quiet = .true. ) ! (out) call HistoryGet ( & & file = 'phy_sponge_layer_test00.nc', varname = 'V', & ! (in) & array = xyz_V, quiet = .true. ) ! (out) call HistoryGet ( & & file = 'phy_sponge_layer_test00.nc', varname = 'Ps', & ! (in) & array = xy_Ps, quiet = .true. ) ! (out) !------------------------------------------------------------------- ! 基本の初期設定, 終了処理テスト ! Basic initialization and termination test !------------------------------------------------------------------- call PhySpoLayCreate( & & phy_spo_lay = phy_spo_lay00, & ! (out) & imax = imax, jmax = jmax, kmax = kmax, & ! (in) & x_Lon = x_Lon, y_Lat = y_Lat, z_Sigma = z_Sigma, & ! (in) & DelTime = 600.0_DP ) ! (in) call AssertEqual( 'basic initialization test 1', & & answer = .true., check = PhySpoLayInitialized(phy_spo_lay00) ) !!$ call PhySpoLayPutLine( phy_spo_lay = phy_spo_lay00 ) ! (in) call PhySpoLayClose( phy_spo_lay = phy_spo_lay00 ) ! (inout) call AssertEqual( 'basic termination test 1', & & answer = .false., check = PhySpoLayInitialized(phy_spo_lay00) ) !!$ call PhySpoLayPutLine( phy_spo_lay = phy_spo_lay00 ) ! (in) !------------------------------------------------------------------- ! エラー処理のテスト ! Error handling test !------------------------------------------------------------------- call PhySpoLayCreate( & & phy_spo_lay = phy_spo_lay00, & ! (out) & imax = imax, jmax = jmax, kmax = kmax, & ! (in) & x_Lon = x_Lon, y_Lat = y_Lat, z_Sigma = z_Sigma, & ! (in) & DelTime = 600.0_DP ) ! (in) call PhySpoLayCreate( & & phy_spo_lay = phy_spo_lay00, & ! (out) & imax = imax, jmax = jmax, kmax = kmax, & ! (in) & x_Lon = x_Lon, y_Lat = y_Lat, z_Sigma = z_Sigma, & ! (in) & DelTime = 600.0_DP, & ! (in) & err = err ) ! (out) call AssertEqual( 'error handling related to duplicated initialization test 1', & & answer = .true., check = err ) !!$ call PhySpoLayPutLine( phy_spo_lay = phy_spo_lay00 ) ! (in) call PhySpoLayClose( phy_spo_lay = phy_spo_lay00 ) ! (inout) call PhySpoLayCreate( & & phy_spo_lay = phy_spo_lay00, & ! (out) & imax = imax, jmax = jmax, kmax = kmax, & ! (in) & x_Lon = x_Lon, y_Lat = y_Lat, z_Sigma = z_Sigma, & ! (in) & DelTime = 600.0_DP, & ! (in) & UpperPress = 1.0e5_DP, LowerPress = 1.0e4_DP, & ! (in) & err = err ) ! (out) call AssertEqual( 'error handling related to damping range test 1', & & answer = .true., check = err ) call AssertEqual( 'error handling related to damping range test 2', & & answer = .false., check = PhySpoLayInitialized(phy_spo_lay00) ) call PhySpoLayCreate( & & phy_spo_lay = phy_spo_lay00, & ! (out) & imax = imax, jmax = jmax, kmax = kmax, & ! (in) & x_Lon = x_Lon, y_Lat = y_Lat, z_Sigma = z_Sigma, & ! (in) & DelTime = 600.0_DP, & ! (in) & DampingTime = - 1.0_DP, & ! (in) & err = err ) ! (out) call AssertEqual( 'error handling related to damping time constant test 1', & & answer = .true., check = err ) call AssertEqual( 'error handling related to damping time constant range test 2', & & answer = .false., check = PhySpoLayInitialized(phy_spo_lay00) ) !------------------------------------------------------------------- ! 終了処理に関するエラー処理のテスト ! Error handling related to termination test !------------------------------------------------------------------- call PhySpoLayClose( & & phy_spo_lay = phy_spo_lay00, & ! (inout) & err = err ) ! (out) call AssertEqual( 'error handling related to termination test 1', & & answer = .true., check = err ) !------------------------------------------------------------------- ! Damping テスト ! Damping test !------------------------------------------------------------------- call PhySpoLayCreate( & & phy_spo_lay = phy_spo_lay00, & ! (out) & imax = imax, jmax = jmax, kmax = kmax, & ! (in) & x_Lon = x_Lon, y_Lat = y_Lat, z_Sigma = z_Sigma, & ! (in) & x_Lon_Weight = x_Lon_Weight, & ! (in) & y_Lat_Weight = y_Lat_Weight, & ! (in) & z_DelSigma = z_DelSigma, & ! (in) & DelTime = 600.0_DP ) ! (in) !!$ & DelTime = 600.0_DP, & ! (in) !!$ & history_varlist = 'DUDtSpoDamping, DVDtSpoDamping', & ! (in) !!$ & history_interval_value = 1.0, & ! (in) !!$ & history_interval_unit = 'min', & ! (in) !!$ & history_precision = 'double' ) ! (in) !!$ call PhySpoLayPutLine( phy_spo_lay = phy_spo_lay00 ) ! (in) call Damping( & & phy_spo_lay = phy_spo_lay00, & ! (inout) & xyz_U = xyz_U, xyz_V = xyz_V, xy_Ps = xy_Ps, & ! (in) & xyz_DUDtSpoDamping = xyz_DUDtSpoDamping, & ! (out) & xyz_DVDtSpoDamping = xyz_DVDtSpoDamping ) ! (out) call HistoryGet ( & & file = 'phy_sponge_layer_test01.nc', & ! (in) & varname = 'DUDtSpoDamping', & ! (in) & array = xyz_DUDtSpoDampingAns, quiet = .true. ) ! (out) call HistoryGet ( & & file = 'phy_sponge_layer_test01.nc', & ! (in) & varname = 'DVDtSpoDamping', & ! (in) & array = xyz_DVDtSpoDampingAns, quiet = .true. ) ! (out) call AssertEqual( 'Damping test 1-1', & & answer = xyz_DUDtSpoDampingAns, check = xyz_DUDtSpoDamping, & & significant_digits = 15, ignore_digits = -15 ) call AssertEqual( 'Damping test 1-2', & & answer = xyz_DVDtSpoDampingAns, check = xyz_DVDtSpoDamping, & & significant_digits = 15, ignore_digits = -15 ) call PhySpoLayClose( phy_spo_lay = phy_spo_lay00 ) ! (inout) !------------------------------------------------------------------- ! NAMELIST ファイルの読み込みテスト ! NAMELIST file loading test !------------------------------------------------------------------- call PhySpoLayCreate( & & phy_spo_lay = phy_spo_lay01, & ! (out) & imax = imax, jmax = jmax, kmax = kmax, & ! (in) & x_Lon = x_Lon, y_Lat = y_Lat, z_Sigma = z_Sigma, & ! (in) & x_Lon_Weight = x_Lon_Weight, & ! (in) & y_Lat_Weight = y_Lat_Weight, & ! (in) & z_DelSigma = z_DelSigma, & ! (in) & DelTime = 300.0_DP, & ! (in) & current_time_value = 10.0, & ! (in) & current_time_unit = 'min', & ! (in) & nmlfile = VAL_namelist ) ! (in) call AssertEqual( 'NAMELIST file loading test 1', & & answer = .true., check = PhySpoLayInitialized(phy_spo_lay01) ) !!$ call PhySpoLayPutLine( phy_spo_lay = phy_spo_lay01 ) ! (in) do i = 1, 2 call Damping( & & phy_spo_lay = phy_spo_lay01, & ! (inout) & xyz_U = xyz_U, xyz_V = xyz_V, xy_Ps = xy_Ps, & ! (in) & xyz_DUDtSpoDamping = xyz_DUDtSpoDamping, & ! (out) & xyz_DVDtSpoDamping = xyz_DVDtSpoDamping ) ! (out) !!$ call PhySpoLayPutLine( phy_spo_lay = phy_spo_lay01 ) ! (in) end do call PhySpoLayClose( phy_spo_lay = phy_spo_lay01 ) ! (inout) call HistoryGet ( & & file = 'phy_sponge_layer_test02.nc', & ! (in) & varname = 'DUDtSpoDamping', & ! (in) & array = xyz_DUDtSpoDampingAns, quiet = .true. ) ! (out) call HistoryGet ( & & file = 'phy_sponge_layer_test02.nc', & ! (in) & varname = 'DVDtSpoDamping', & ! (in) & array = xyz_DVDtSpoDampingAns, quiet = .true. ) ! (out) call AssertEqual( 'NAMELIST loading test 1', & & answer = xyz_DUDtSpoDampingAns, check = xyz_DUDtSpoDamping, & & significant_digits = 7, ignore_digits = -10 ) call AssertEqual( 'NAMELIST loading test 2', & & answer = xyz_DVDtSpoDampingAns, check = xyz_DVDtSpoDamping, & & significant_digits = 7, ignore_digits = -10 ) !------------------------------------------------------------------- ! 無効な値に関するエラー処理のテスト ! Error handling related to invalid values test !------------------------------------------------------------------- !!$ call PhySpoLayCreate( & !!$ & phy_spo_lay = phy_spo_lay02, & ! (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 PhySpoLayCreate( & !!$ & phy_spo_lay = phy_spo_lay02, & ! (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 PhySpoLayCreate( & !!$ & phy_spo_lay = phy_spo_lay03, & ! (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 PhySpoLayPutLine( phy_spo_lay = phy_spo_lay03 ) ! (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 Damping( & !!$ & phy_spo_lay = phy_spo_lay03, & ! (inout) !!$ & x_Data1 = x_Data1, y_Data2 = y_Data2 ) ! (inout) !!$ end do !!$ !!$ call PhySpoLaySetTime( & !!$ & phy_spo_lay = phy_spo_lay03, & ! (inout) !!$ & current_time_value = 1.0, current_time_unit = 'minute' ) ! (in) !!$ !!$ call Damping( & !!$ & phy_spo_lay = phy_spo_lay03, & ! (inout) !!$ & x_Data1 = x_Data1, y_Data2 = y_Data2, & ! (inout) !!$ & historyput_flag = .true. ) ! (in) !!$ !!$ call PhySpoLayClose( phy_spo_lay = phy_spo_lay03 ) ! (inout) contains subroutine cmdline_optparse ! ! コマンドライン引数の処理を行います ! ! Handle command line options ! call DCArgsOpen( arg = arg ) ! (out) call DCArgsHelpMsg( arg = arg, & ! (inout) & category = 'Title', msg = title ) ! (in) call DCArgsHelpMsg( arg = arg, & ! (inout) & category = 'Usage', & ! (in) & msg = './' // trim(subname) // & & ' [Options]' ) ! (in) call DCArgsHelpMsg( arg = arg, & ! (inout) & category = 'Source', msg = source ) ! (in) call DCArgsHelpMsg( arg = arg, & ! (inout) & category = 'Institution', & ! (in) & msg = institution ) ! (in) call DCArgsOption( arg = arg, & ! (inout) & options = StoA('-N', '--namelist'), & ! (in) & flag = OPT_namelist, & ! (out) & value = VAL_namelist, & ! (out) & 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_sponge_layer_test