!= phy_neg_moist_test 用 netCDF ファイル生成プログラム ! != NetCDF file generation program for "phy_neg_moist_test" ! ! Authors:: Yasuhiro MORIKAWA ! Version:: $Id: phy_neg_moist_test_prepnc00.f90,v 1.2 2008-06-14 11:44:14 morikawa Exp $ ! Tag Name:: $Name: dcpam4-20080626 $ ! 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_test で使用する netCDF ファイルを作成する開発者用 ! プログラムです. ! ! This is a program for developers that generates ! netCDF data for "phy_neg_moist_test" ! program phy_neg_moist_test_prepnc00 use intavr_operate, only: INTAVROPR, Create, Close, & & PutLine, initialized, AvrLonLat_xy use spline_data, only: SPLDAT, Create, Close, & & PutLine, initialized, GetSpline use constants, only: CONST, Create, Get use dc_test, only: AssertEqual 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_prepnc00 $Name: dcpam4-20080626 $ :: ' // & & 'NetCDF file generation program for "phy_neg_moist_test"' 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 !----------------------------------------------------------------- real(DP):: RAir ! $ R $ . 大気気体定数. Gas constant of air real(DP):: Grav ! $ g $ . 重力加速度. Gravitational acceleration !--------------------------------------------------------- ! 軸データ ! 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:: xyr_Press (:,:,:) ! $ p_s $ . 地表面気圧 (半整数レベル). ! Surface pressure (half level) real(DP), allocatable:: xyz_QVap (:,:,:) ! $ q (t-\Delta t) $ . 比湿. Specific humidity real(DP):: QVapMax ! 比湿の最大値 ! Maximum value of specific humidity real(DP), allocatable:: x_QVapCoeff (:) ! 比湿の係数 ! Specific humidity coefficient real(DP), allocatable:: y_QVapCoeff (:) ! 比湿の係数 ! Specific humidity coefficient real(DP), allocatable:: z_QVapCoeff (:) ! 比湿の係数 ! Specific humidity coefficient real(DP):: QVapAvrLonLatSig ! 比湿の全球平均. ! Global mean specific humidity !--------------------------------------------------------- ! データ入出力 ! Data I/O !--------------------------------------------------------- type(GT_HISTORY):: gthist character(STRING):: default_output_file = 'phy_neg_moist_test00.nc' character(STRING):: output_file !--------------------------------------------------------- ! 作業変数 ! Work variables !--------------------------------------------------------- type(ARGS):: arg ! コマンドライン引数. ! Command line arguments logical:: OPT_output ! -o, --output オプションの有無. ! Existence of '-o', '--output' option character(STRING):: VAL_output ! -o, --output オプションの値. ! Value of '-o', '--output' option integer:: i, j, k ! DO ループ用作業変数 ! Work variables for DO loop type(CONST):: const_earth type(INTAVROPR):: intavr_opr type(SPLDAT):: spl_dat_qvapx, spl_dat_qvapy, spl_dat_qvapz real(DP):: PI ! $ \pi $ . 円周率. Circular constant continue !--------------------------------------------------------- ! コマンドライン引数の処理 ! Command line arguments handling !--------------------------------------------------------- call Open( arg ) call HelpMsg( arg, 'Title', title ) call HelpMsg( arg, 'Usage', & & './phy_neg_moist_test_prepnc00 [Options]' ) call HelpMsg( arg, 'Source', source ) call HelpMsg( arg, 'Institution', institution ) call Option( arg, StoA('-o', '--output'), & & OPT_output, VAL_output, & & help = 'Output filename (default: ' // trim(default_output_file) // ' )' ) call Debug( arg ) ; call Help( arg ) ; call Strict( arg, severe = .true. ) call Close( arg ) if ( VAL_output == '' ) then output_file = default_output_file else output_file = VAL_output end if !--------------------------------------------------------- ! 物理定数の設定 ! Configure a physical constant !--------------------------------------------------------- call Create( constant = const_earth ) ! (inout) call Get( constant = const_earth, & ! (inout) & PI = PI, RAir = RAir, Grav = Grav ) ! (out) !--------------------------------------------------------- ! 軸データの設定 ! Configure 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) ) x_Lon = & & (/ 0.0, 11.25, 22.5, 33.75, 45.0, 56.25, 67.5, 78.75, & & 90.0, 101.25, 112.5, 123.75, 135.0, 146.25, 157.5, 168.75, & & 180.0, 191.25, 202.5, 213.75, 225.0, 236.25, 247.5, 258.75, & & 270.0, 281.25, 292.5, 303.75, 315.0, 326.25, 337.5, 348.75 /) x_Lon_Weight = 0.196349540849362 y_Lat = & & (/ -81.65059, -70.83464, -59.95486, -49.06072, & & -38.16121, -27.25921, -16.35593, -5.45204, & & 5.45204, 16.35593, 27.25921, 38.16121, & & 49.06072, 59.95486, 70.83464, 81.65059 /) y_Lat_Weight = & & (/ 0.0271524594117541, 0.0622535239386478, 0.0951585116824929, 0.124628971255534, & & 0.149595988816577, 0.169156519395003, 0.182603415044924, 0.189450610455069, & & 0.189450610455069, 0.182603415044924, 0.169156519395003, 0.149595988816577, & & 0.124628971255534, 0.0951585116824929, 0.0622535239386478, 0.0271524594117541 /) z_Sigma = & & (/ 0.994997, 0.9799879, 0.9499499, 0.8897859, & & 0.7996277, 0.689378, 0.5641075, 0.4286365, & & 0.2879657, 0.1572454, 0.07398598, 0.02074752 /) r_Sigma = & & (/ 1.0, 0.99, 0.97, 0.93, 0.85, 0.75, & & 0.63, 0.5, 0.36, 0.22, 0.1, 0.05, 0.0 /) !--------------------------------------------------------- ! 気圧 (半整数レベル) の設定 ! Configure pressure on half level !--------------------------------------------------------- allocate( xyr_Press(0:imax-1, 0:jmax-1, 0:kmax) ) call HistoryGet( & & file = 'phy_interpolate_test01.nc', & ! (in) & varname = 'PressM', & ! (in) & array = xyr_Press ) ! (out) !--------------------------------------------------------- ! 比湿の設定 ! Configure specific humidity !--------------------------------------------------------- QVapMax = 2.0e-5_DP allocate( xyz_QVap(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( x_QVapCoeff (0:imax-1) ) allocate( y_QVapCoeff (0:jmax-1) ) allocate( z_QVapCoeff (0:kmax-1) ) call Create( spl_dat = spl_dat_qvapx, & ! (inout) & knots_num = 8, & & x_knots = & & (/ 0.0_DP, 45.0_DP, 90.0_DP, 135.0_DP, & & 180.0_DP, 225.0_DP, 270.0_DP, 315.0_DP /), & ! (in) & x_value = & & (/ 0.5_DP, 0.8_DP, 1.0_DP, 0.8_DP, & & 0.5_DP -0.01_DP, 0.3_DP, -0.01_DP/) ) ! (in) call GetSpline( spl_dat = spl_dat_qvapx, & & a_Dim = x_Lon, & ! (in) & a_Data = x_QVapCoeff ) ! (out) call PutLine(x_QVapCoeff, indent=' x_QVapCoeff=') call Create( spl_dat = spl_dat_qvapy, & ! (inout) & knots_num = 13, & & x_knots = & & (/ -90.0_DP, -75.0_DP, -60.0_DP, -45.0_DP, -30.0_DP, -15.0_DP, & & 0.0_DP, 15.0_DP, 30.0_DP, 45.0_DP, 60.0_DP, 75.0_DP, & & 90.0_DP /), & ! (in) & x_value = & & (/ 0.05_DP, 0.1_DP, 0.2_DP, 0.4_DP, 0.7_DP, 0.9_DP, & & 1.0_DP, 0.9_DP, 0.7_DP, 0.4_DP, 0.2_DP, 0.1_DP, & & 0.05_DP /) ) ! (in) call GetSpline( spl_dat = spl_dat_qvapy, & & a_Dim = y_Lat, & ! (in) & a_Data = y_QVapCoeff ) ! (out) call PutLine(y_QVapCoeff, indent=' y_QVapCoeff=') call Create( spl_dat = spl_dat_qvapz, & ! (inout) & knots_num = 3, & & x_knots = & & (/ 1.0_DP, 0.5_DP, 0.0_DP /), & ! (in) & x_value = & & (/ 1.0_DP, 0.5_DP, 0.0_DP /) ) ! (in) call GetSpline( spl_dat = spl_dat_qvapz , & & a_Dim = z_Sigma, & ! (in) & a_Data = z_QVapCoeff ) ! (out) call PutLine(z_QVapCoeff, indent=' z_QVapCoeff=') do k = 0, kmax - 1 do j = 0, jmax - 1 do i = 0, imax - 1 xyz_QVap(i,j,k) = & & QVapMax * x_QVapCoeff(i) * y_QVapCoeff(j) * z_QVapCoeff(k) end do end do end do call PutLine(xyz_QVap, indent=' xyz_QVap=') 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 !---------------------------------------------------------------- ! データ出力 ! Output data !---------------------------------------------------------------- call HistoryCreate( & & history = gthist, & ! (out) & file = output_file, & ! (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 = 'lon_weight', & ! (in) & dims = StoA('lon'), & ! (in) & longname = 'weight for integration in longitude', & ! (in) & units = 'radian', xtype = 'double' ) ! (in) call HistoryAddAttr( & & history = gthist, & ! (inout) & varname = 'lon', attrname = 'gt_calc_weight', & ! (in) & value = 'lon_weight' ) ! (in) call HistoryPut( & & history = gthist, & ! (inout) & varname = 'lon_weight', array = x_Lon_Weight ) ! (in) call HistoryAddVariable( & & history = gthist, & ! (inout) & varname = 'lat_weight', & ! (in) & dims = StoA('lat'), & ! (in) & longname = 'weight for integration in latitude', & ! (in) & units = 'radian', xtype = 'double' ) ! (in) call HistoryAddAttr( & & history = gthist, & ! (inout) & varname = 'lat', attrname = 'gt_calc_weight', & ! (in) & value = 'lat_weight' ) ! (in) call HistoryPut( & & history = gthist, & ! (inout) & varname = 'lat_weight', array = y_Lat_Weight ) ! (in) call HistoryAddVariable( & & history = gthist, & ! (inout) & varname = 'PressM', & ! (in) & dims = StoA('lon', 'lat', 'sigm'), & ! (in) & longname = 'air pressure', & ! (in) & units = 'Pa', xtype = 'double' ) ! (in) call HistoryAddAttr( & & history = gthist, & ! (inout) & varname = 'PressM', attrname = 'standard_name', & ! (in) & value = 'air_pressure' ) ! (in) call HistoryPut( & & history = gthist, & ! (inout) & varname = 'PressM', array = xyr_Press ) ! (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 = '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_prepnc00