!= phy_neg_moist モジュールのテストプログラム ! != Test program for "phy_neg_moist" ! ! Authors:: Yukiko YAMADA, Yasuhiro MORIKAWA ! Version:: $Id: phy_neg_moist_test.f90,v 1.2 2007-09-25 12:35:29 morikawa Exp $ ! Tag Name:: $Name: dcpam4-20080609-1 $ ! Copyright:: Copyright (C) GFD Dennou Club, 2007. All rights reserved. ! License:: See COPYRIGHT[link:../../../COPYRIGHT] ! ! Note that Japanese and English are described in parallel. ! ! phy_neg_moist モジュールの動作テストを行うためのプログラムです. ! このプログラムがコンパイルできること, および実行時に ! プログラムが正常終了することを確認してください. ! ! This program checks the operation of "phy_neg_moist" module. ! Confirm compilation and execution of this program. ! program phy_neg_moist_test use intavr_operate, only: INTAVROPR, Create, Close, & & PutLine, initialized, AvrLonLat_xy use phy_neg_moist, only: PHYNEGMST, Create, Close, & & PutLine, initialized, RemoveNegQVap 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 use dc_args, only: ARGS, Open, HelpMsg, Option, Debug, Help, Strict, Close 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_neg_moist_test $Name: dcpam4-20080609-1 $ :: ' // & & 'Test program of "phy_neg_moist" 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:: imax = 32 ! 経度格子点数. ! Number of grid points in longitude integer:: jmax = 16 ! 緯度格子点数. ! Number of grid points in latitude integer:: kmax = 12 ! 鉛直層数. ! Number of vertical level !----------------------------------------------------------------- ! 物理定数等の設定 ! Configure physical constants etc. !----------------------------------------------------------------- type(CONST):: const_earth real(DP):: PI ! $ \pi $ . 円周率. Circular constant real(DP):: DelTime ! $ \Delta t $ . タイムステップ. Time step !--------------------------------------------------------- ! 軸データ ! Axes data !--------------------------------------------------------- real(DP), allocatable:: x_Lon (:) ! 経度. Longitude real(DP), allocatable:: x_Lon_Weight (:) ! 経度積分用座標重み. ! Weight for integration in longitude real(DP), allocatable:: y_Lat (:) ! 緯度. Latitude real(DP), allocatable:: y_Lat_Weight (:) ! 緯度積分用座標重み. ! Weight for integration in latitude real(DP), allocatable:: z_Sigma (:) ! $ \sigma $ レベル (整数). ! Full $ \sigma $ level real(DP), allocatable:: r_Sigma (:) ! $ \sigma $ レベル (半整数). ! Half $ \sigma $ level !--------------------------------------------------------- ! 物理量 ! Physical values !--------------------------------------------------------- real(DP), allocatable:: xyz_QVap (:,:,:) ! $ q $ . 比湿. Specific humidity real(DP), allocatable:: xyz_QVapAns (:,:,:) ! $ q $ . 比湿. Specific humidity real(DP), allocatable:: xyz_DNegQVapDt (:,:,:) ! 比湿変化率. ! Specific humidity tendency real(DP), allocatable:: xyz_DNegQVapDtAns (:,:,:) ! 比湿変化率. ! Specific humidity tendency real(DP), allocatable:: xyr_Press (:,:,:) ! $ P_s $ . 地表面気圧 (半整数レベル). ! Surface pressure (half level) real(DP):: QVapAvrLonLatSig ! 比湿の全球平均. ! Global mean specific humidity real(DP):: QVapAvrLonLatSigAns ! 比湿の全球平均. ! Global mean specific humidity !--------------------------------------------------------- ! データ入出力 ! Data I/O !--------------------------------------------------------- type(GT_HISTORY):: gthist !--------------------------------------------------------- ! 作業変数 ! 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 integer:: k ! DO ループ用作業変数 ! Work variables for DO loop type(PHYNEGMST):: phy_neg_mst00, phy_neg_mst01, phy_neg_mst02, phy_neg_mst03 type(INTAVROPR):: intavr_opr logical:: err character(*), parameter:: subname = 'phy_neg_moist_test' continue !--------------------------------------------------------- ! コマンドライン引数の処理 ! Command line arguments handling !--------------------------------------------------------- call Open( arg ) call HelpMsg( arg, 'Title', title ) call HelpMsg( arg, 'Usage', & & './phy_neg_moist_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) DelTime = 600.0_DP call Get( constant = const_earth, & ! (inout) & PI = PI ) ! (out) !--------------------------------------------------------- ! 座標軸データの取得 ! Get axes data !--------------------------------------------------------- allocate( x_Lon (0:imax-1) ) allocate( x_Lon_Weight (0:imax-1) ) allocate( y_Lat (0:jmax-1) ) allocate( y_Lat_Weight (0:jmax-1) ) allocate( z_Sigma (0:kmax-1) ) allocate( r_Sigma (0:kmax) ) call HistoryGet( & & file = 'phy_neg_moist_test00.nc', & ! (in) & varname = 'lon', & ! (in) & array = x_Lon ) ! (out) call HistoryGet( & & file = 'phy_neg_moist_test00.nc', & ! (in) & varname = 'lon_weight', & ! (in) & array = x_Lon_Weight ) ! (out) call HistoryGet( & & file = 'phy_neg_moist_test00.nc', & ! (in) & varname = 'lat', & ! (in) & array = y_Lat ) ! (out) call HistoryGet( & & file = 'phy_neg_moist_test00.nc', & ! (in) & varname = 'lat_weight', & ! (in) & array = y_Lat_Weight ) ! (out) call HistoryGet( & & file = 'phy_neg_moist_test00.nc', & ! (in) & varname = 'sig', & ! (in) & array = z_Sigma ) ! (out) call HistoryGet( & & file = 'phy_neg_moist_test00.nc', & ! (in) & varname = 'sigm', & ! (in) & array = r_Sigma ) ! (out) !--------------------------------------------------------- ! 初期設定テスト ! Initialization test !--------------------------------------------------------- call Create( phy_neg_mst = phy_neg_mst00, & ! (inout) & imax = imax, jmax = jmax, kmax = kmax, & ! (in) & PI = PI, DelTime = DelTime, & ! (in) & x_Lon_Weight = x_Lon_Weight, & ! (in) & y_Lat_Weight = y_Lat_Weight ) ! (in) call AssertEqual( 'initialization test 1', & & answer = .true., check = initialized(phy_neg_mst00) ) call PutLine( phy_neg_mst = phy_neg_mst00 ) ! (in) !--------------------------------------------------------- ! 正答の取得 ! Get correct answer !--------------------------------------------------------- allocate( xyz_QVapAns (0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_DNegQVapDtAns (0:imax-1, 0:jmax-1, 0:kmax-1) ) call HistoryGet( & & file = 'phy_neg_moist_test01.nc', & ! (in) & varname = 'QVap', & ! (in) & array = xyz_QVapAns ) ! (out) call HistoryGet( & & file = 'phy_neg_moist_test01.nc', & ! (in) & varname = 'DNegQVapDt', & ! (in) & array = xyz_DNegQVapDtAns ) ! (out) call HistoryGet( & & file = 'phy_neg_moist_test00.nc', & ! (in) & varname = 'QVapAvrLonLatSig', & ! (in) & array = QVapAvrLonLatSigAns ) ! (out) !--------------------------------------------------------- ! 気圧と比湿の取得 ! Get pressure and specific humidity !--------------------------------------------------------- allocate( xyr_Press (0:imax-1, 0:jmax-1, 0:kmax) ) allocate( xyz_QVap (0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_DNegQVapDt (0:imax-1, 0:jmax-1, 0:kmax-1) ) call HistoryGet( & & file = 'phy_neg_moist_test00.nc', & ! (in) & varname = 'PressM', & ! (in) & array = xyr_Press ) ! (out) call HistoryGet( & & file = 'phy_neg_moist_test00.nc', & ! (in) & varname = 'QVap', & ! (in) & array = xyz_QVap ) ! (out) !--------------------------------------------------------- ! 負の水蒸気除去 ! Remove negative moisture !--------------------------------------------------------- xyz_DNegQVapDt = 0.0_DP call RemoveNegQVap( phy_neg_mst = phy_neg_mst00, & ! (inout) & xyz_QVap = xyz_QVap, & ! (inout) & xyz_DNegQVapDt = xyz_DNegQVapDt, & ! (inout) & xyr_Press = xyr_Press ) ! (in) call AssertEqual( 'RemoveNegQVap test 1', & & answer = xyz_QVapAns, check = xyz_QVap, & & significant_digits = 15, ignore_digits = -15 ) call AssertEqual( 'RemoveNegQVap test 2', & & answer = xyz_DNegQVapDtAns, check = xyz_DNegQVapDt, & & significant_digits = 15, ignore_digits = -15 ) call Create( intavr_opr = intavr_opr, & ! (inout) & imax = imax, jmax = jmax, & ! (in) & PI = PI ) ! (in) QVapAvrLonLatSig = 0.0_DP do k = 0, kmax-1 QVapAvrLonLatSig = & & QVapAvrLonLatSig & & + AvrLonLat_xy( xyz_QVap(:,:,k), intavr_opr ) end do call AssertEqual( 'RemoveNegQVap test 2', & & answer = QVapAvrLonLatSigAns, check = QVapAvrLonLatSig, & & significant_digits = 15, ignore_digits = -15 ) !--------------------------------------------------------- ! 終了処理テスト ! Termination test !--------------------------------------------------------- call Close( phy_neg_mst = phy_neg_mst00 ) ! (inout) call AssertEqual( 'termination test 1', & & answer = .false., check = initialized(phy_neg_mst00) ) call PutLine( phy_neg_mst = phy_neg_mst00 ) ! (in) call Close( phy_neg_mst = phy_neg_mst02, & ! (inout) & err = err ) ! (out) call AssertEqual( 'termination test 2', & & answer = .true., check = err ) !!$ !---------------------------------------------------------------- !!$ ! データ出力 !!$ ! Output data !!$ !---------------------------------------------------------------- !!$ call HistoryCreate( & !!$ & history = gthist, & ! (out) !!$ & file = 'phy_neg_moist_test01.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 = 'QVap', & ! (in) !!$ & dims = StoA('lon', 'lat', 'sig'), & ! (in) !!$ & longname = 'specific humidity', & ! (in) !!$ & units = '1', xtype = 'double' ) ! (in) !!$ call HistoryAddAttr(& !!$ & history = gthist, & ! (inout) !!$ & varname = 'QVap', attrname = 'standard_name', & ! (in) !!$ & value = 'specific_humidity' ) ! (in) !!$ call HistoryPut( & !!$ & history = gthist, & ! (inout) !!$ & varname = 'QVap', array = xyz_QVap ) ! (in) !!$ !!$ !!$ call HistoryAddVariable( & !!$ & history = gthist, & ! (inout) !!$ & varname = 'DNegQVapDt', & ! (in) !!$ & dims = StoA('lon', 'lat', 'sig'), & ! (in) !!$ & longname = 'specific humidity corrction', & ! (in) !!$ & units = '1', xtype = 'double' ) ! (in) !!$ call HistoryPut( & !!$ & history = gthist, & ! (inout) !!$ & varname = 'DNegQVapDt', array = xyz_DNegQVapDt ) ! (in) !!$ !!$ !!$ call HistoryAddVariable( & !!$ & history = gthist, & ! (inout) !!$ & varname = 'QVapAvrLonLatSig', & ! (in) !!$ & dims = StoA(''), & ! (in) !!$ & longname = 'global mean specific humidity', & ! (in) !!$ & units = '1', xtype = 'double' ) ! (in) !!$ call HistoryPut( & !!$ & history = gthist, & ! (inout) !!$ & varname = 'QVapAvrLonLatSig', & ! (in) !!$ & array = (/ QVapAvrLonLatSig /) ) ! (in) !!$ !!$ call HistoryClose( history = gthist ) ! (inout) end program phy_neg_moist_test