!== dcpam サンプル主プログラム ! !== dcpam sample main program ! ! Authors:: Yasuhiro MORIKAWA ! Version:: $Id: dcpam_hs94.f90,v 1.13 2007/07/31 14:35:28 morikawa Exp $ ! Tag Name:: $Name: dcpam4-20070731-1 $ ! Copyright:: Copyright (C) GFD Dennou Club, 2007. All rights reserved. ! License:: See COPYRIGHT[link:../../COPYRIGHT] ! program dcpam_hs94 ! ! Note that Japanese and English are described in parallel. ! ! dcpam のメインプログラムのサンプルです. ! Held and Suarez (1994) ベンチマークテストを行ないます. ! ! This is sample main program of dcpam. ! Held and Suarez (1994) benchmark test is performed. ! !--------------------------------------------------------- ! 初期値生成 ! Generate initial data !--------------------------------------------------------- use initial_data, only: INIDAT, Create, Get, Close, PutLine !--------------------------------------------------------- ! 力学過程 ! Dynamical core !--------------------------------------------------------- use dyn_spectral_as83, only: DYNSPAS83, Create, Close, & & GetAxes, Dynamics, VorDiv2UV, UV2VorDiv !--------------------------------------------------------- ! 物理過程 ! Physical processes !--------------------------------------------------------- !------------------------------------- ! Held and Suarez (1994) use phy_hs94, only: PHYHS94, Create, Close, Forcing !--------------------------------------------------------- ! GCM 用ユーティリティ ! Utilities for GCM !--------------------------------------------------------- !------------------------------------- ! 物理定数 ! Physical constants use constants, only: CONST, Create, Get, PutLine !------------------------------------- ! タイムフィルター ! Time filter use timefilter, only: TFILTER, Create, Filter, Progress !--------------------------------------------------------- ! データ I/O ! Data I/O !--------------------------------------------------------- use gt4_history, only: GT_HISTORY, & & HistoryGet, HistoryCopy, & & HistoryCreate, HistoryAddVariable, HistoryPut, HistoryClose, & & HistoryAddAttr, HistorySetTime !--------------------------------------------------------- ! 汎用ユーティリティ ! Common utilities !--------------------------------------------------------- use dc_types, only: DP, STRING, TOKEN, STDOUT use dc_args, only: ARGS, Open, HelpMsg, Option, Debug, Help, Strict, Close use dc_trace, only: DbgMessage, BeginSub, EndSub use dc_message,only: MessageNotify use dc_string, only: toChar, Printf, StoA use dc_date, only: Create, EvalSec, EvalByUnit, mod, & & operator(*), operator(==), operator(<), operator(/), operator(+) use dc_date_types, only: DC_DIFFTIME use dc_clock, only: CLOCK, Create, Close, Start, Stop, Result, & & Predict, operator(+) use dc_iounit, only: FileOpen implicit none !------------------------------------------------------------------- ! 実験の表題, モデルの名称, 所属機関名 ! Title of a experiment, name of model, sub-organ !------------------------------------------------------------------- character(*), parameter:: title = & & 'dcpam_hs94 $Name: dcpam4-20070731-1 $ :: ' // & & 'DCPAM sample program: Held and Suarez (1994) benchmark 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:: nmax = 10 ! 最大全波数. ! Maximum truncated wavenumber integer:: imax = 32 ! 経度格子点数. ! Number of grid points in longitude integer:: jmax = 16 ! 緯度格子点数. ! Number of grid points in latitude integer:: kmax = 20 ! 鉛直層数. ! Number of vertical level namelist /dcpam_hs94_grid_nml/ & & nmax, imax, jmax, kmax ! 格子点, 最大波数の設定 ! ! Configure grid points and maximum truncated wavenumber !--------------------------------------------------------- ! 物理定数 ! Physical constants !--------------------------------------------------------- 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):: EpsVT ! $ 1/\epsilon_v - 1 $ . integer:: VisOrder ! 超粘性の次数. Order of hyper-viscosity real(DP):: EFoldTime ! 最大波数に対する e-folding time. E-folding time for maximum wavenumber !--------------------------------------------------------- ! 初期値データ ! Initial data !--------------------------------------------------------- logical:: initial_data_prepared = .false. ! 初期値データの有無. ! Presence or absence of initial data character(STRING):: init_nc = 'init.nc' ! 初期値データ netCDF ファイル. ! NetCDF file for initial data character(TOKEN):: init_nc_time_varname = 'time' ! 時刻の変数名. ! Variable name of time. real(DP):: init_nc_timeB = -20.0_DP ! 初期値データ ( $ t-\Delta t $ ) の時刻. ! Time of initial data ( $ t-\Delta t $ ) real(DP):: init_nc_timeN = 0.0_DP ! 初期値データ ( $ t $ ) の時刻. ! Time of initial data ( $ t $ ) namelist /dcpam_hs94_initdata_nml/ & & initial_data_prepared, init_nc, init_nc_time_varname, & & init_nc_timeB, init_nc_timeN ! 初期値データ, リスタートデータの設定 ! ! Configure initial data or restart data type(INIDAT):: ini_dat !--------------------------------------------------------- ! 地形データ (地表 $ \Phi $ ) ! Geography data (surface $ \Phi $ ) !--------------------------------------------------------- logical:: geography_data_prepared = .false. ! 地形データ (地表 $ \Phi $ ) の有無. ! Presence or absence of geography data (surface $ \Phi $ ) character(STRING):: geo_nc = 'geo.nc' ! 地形データ netCDF ファイル. ! NetCDF file for geography data namelist /dcpam_hs94_geodata_nml/ & & geography_data_prepared, geo_nc ! 地形データの設定 ! ! Configure geography data !--------------------------------------------------------- ! OPENMP による並列計算 ! Parallel computing with OPENMP !--------------------------------------------------------- integer:: openmp_threads = 1 ! OPENMP での最大スレッド数. ! Maximum number of threads in OPENMP !------------------------------------------------------------------- ! 現在時刻, 時間ステップ $ \Delta t $ , ! 積分終了時刻, 予測時間表示の設定 ! Configure current time, time step $ \Delta t $ , ! finish time of integral, predicted CPU time !------------------------------------------------------------------- type(DC_DIFFTIME):: current_time ! 現在時刻. Current time. real(DP):: start_time_value = 0.0_DP ! 開始時刻. Start time character(TOKEN):: start_time_unit = 'sec' ! 開始時刻の単位. Unit of start time type(DC_DIFFTIME):: delta_time ! $ \Delta t $ . タイムステップ. Time step real(DP):: delta_time_value = 20.0_DP ! $ \Delta t $ . タイムステップ. Time step character(TOKEN):: delta_time_unit = 'minute' ! タイムステップの単位. Unit of time step type(DC_DIFFTIME):: total_time ! 積分終了時刻. Finish time of integral real(DP):: total_time_value = 7.0_DP ! 積分終了時刻. Finish time of integral character(TOKEN):: total_time_unit = 'days' ! 積分終了時刻の単位. Unit of finish time of integral type(DC_DIFFTIME):: predict_show_interval_time ! 終了予測日時表示間隔. ! Interval of predicted date output real(DP):: predict_show_interval_value = 1.0_DP ! 終了予測日時表示間隔. ! Interval of predicted date output character(TOKEN):: predict_show_interval_unit = 'days' ! 終了予測日時表示間隔 (単位). ! Unit for interval of predicted date output namelist /dcpam_hs94_time_nml/ & & start_time_value, start_time_unit, & & delta_time_value, delta_time_unit, & & total_time_value, total_time_unit, & & predict_show_interval_value, predict_show_interval_unit ! 時刻の設定 ! ! Configure time !--------------------------------------------------------- ! ヒストリファイルへのデータ出力設定 ! Configure the settings for history data output !--------------------------------------------------------- type(DC_DIFFTIME):: history_interval_time ! ヒストリデータの出力間隔. ! Interval of history data output real(DP):: history_interval_value = 0.125_DP ! ヒストリデータの出力間隔の単位. ! Unit for interval of history data output character(TOKEN):: history_interval_unit = 'days' ! ヒストリデータの出力間隔の単位. ! Unit for interval of history data output character(TOKEN):: history_precision = 'float' ! ヒストリデータの精度. ! Precision of history data namelist /dcpam_hs94_history_nml/ & & history_interval_value, history_interval_unit, & & history_precision ! ヒストリファイルへのデータ出力設定 ! ! Configure the settings for history data output character(STRING):: xyz_U_filename = 'U.nc' ! xyz_U の出力ファイル名. ! Filename of "xyz_U" character(STRING):: xyz_V_filename = 'V.nc' ! xyz_V の出力ファイル名. ! Filename of "xyz_V" character(STRING):: xyz_Vor_filename = 'Vor.nc' ! xyz_Vor の出力ファイル名. ! Filename of "xyz_Vor" character(STRING):: xyz_Div_filename = 'Div.nc' ! xyz_Div の出力ファイル名. ! Filename of "xyz_Div" character(STRING):: xyz_Temp_filename = 'Temp.nc' ! xyz_Temp の出力ファイル名. ! Filename of "xyz_Temp" character(STRING):: xy_Ps_filename = 'Ps.nc' ! xy_Ps の出力ファイル名. ! Filename of "xy_Ps" character(STRING):: xyz_QVap_filename = 'QVap.nc' ! xyz_QVap の出力ファイル名. ! Filename of "xyz_QVap" namelist /dcpam_hs94_history_file_nml/ & & xyz_U_filename, & & xyz_V_filename, & & xyz_Vor_filename, & & xyz_Div_filename, & & xyz_Temp_filename, & & xy_Ps_filename, & & xyz_QVap_filename ! ヒストリファイルの名称設定 ! ! Configure names of history files !--------------------------------------------------------- ! リスタートファイルへのデータ出力設定 ! Configure the settings for restart data output !--------------------------------------------------------- type(DC_DIFFTIME):: restart_interval_time ! リスタートデータの出力間隔. ! Interval of restart data output real(DP):: restart_interval_value = 1440.0_DP ! リスタートデータの出力間隔. ! Interval of restart data output character(TOKEN):: restart_interval_unit = 'minute' ! リスタートデータの出力間隔の単位. ! Unit for interval of restart data output character(STRING):: restart_filename = 'dcpam_hs94_restart.nc' ! リスタートデータのファイル名 ! filename of restart data namelist /dcpam_hs94_restart_nml/ & & restart_interval_value, restart_interval_unit, & & restart_filename ! リスタートファイルへのデータ出力設定 ! ! Configure the settings for restart data output !--------------------------------------------------------- ! 配列の定義 ! Declaration of array !--------------------------------------------------------- !------------------------------------- ! 座標変数 ! Coordinate variables real(DP), allocatable:: x_Lon (:) ! 経度. Longitude real(DP), allocatable:: y_Lat (:) ! 緯度. Latitude real(DP), allocatable:: z_Sigma (:) ! $ \sigma $ レベル (整数). ! Full $ \sigma $ level real(DP), allocatable:: r_Sigma (:) ! $ \sigma $ レベル (半整数). ! Half $ \sigma $ level real(DP), allocatable:: z_DelSigma (:) ! $ \Delta \sigma $ (整数). ! $ \Delta \sigma $ (Full) !------------------------------------- ! 予報変数 ! Prediction variables real(DP), allocatable:: xyz_VorB (:,:,:) ! $ \zeta (t-\Delta t) $ . 渦度. Vorticity real(DP), allocatable:: xyz_DivB (:,:,:) ! $ D (t-\Delta t) $ . 発散. Divergence real(DP), allocatable:: xyz_TempB (:,:,:) ! $ T (t-\Delta t) $ . 温度. Temperature real(DP), allocatable:: xyz_QVapB (:,:,:) ! $ q (t-\Delta t) $ . 比湿. Specific humidity real(DP), allocatable:: xy_PsB (:,:) ! $ P_s (t-\Delta t) $ . 地表面気圧. Surface pressure real(DP), allocatable:: xyz_VorN (:,:,:) ! $ \zeta (t) $ . 渦度. Vorticity real(DP), allocatable:: xyz_DivN (:,:,:) ! $ D (t) $ . 発散. Divergence real(DP), allocatable:: xyz_TempN (:,:,:) ! $ T (t) $ . 温度. Temperature real(DP), allocatable:: xyz_QVapN (:,:,:) ! $ q (t) $ . 比湿. Specific humidity real(DP), allocatable:: xy_PsN (:,:) ! $ P_s (t) $ . 地表面気圧. Surface pressure real(DP), allocatable:: xyz_UA (:,:,:) ! $ U (t+\Delta t) $ . 東西風速. Zonal wind real(DP), allocatable:: xyz_VA (:,:,:) ! $ V (t+\Delta t) $ . 南北風速. Meridional wind real(DP), allocatable:: xyz_VorA (:,:,:) ! $ \zeta (t+\Delta t) $ . 渦度. Vorticity real(DP), allocatable:: xyz_DivA (:,:,:) ! $ D (t+\Delta t) $ . 発散. Divergence real(DP), allocatable:: xyz_TempA (:,:,:) ! $ T (t+\Delta t) $ . 温度. Temperature real(DP), allocatable:: xyz_QVapA (:,:,:) ! $ q (t+\Delta t) $ . 比湿. Specific humidity real(DP), allocatable:: xy_PsA (:,:) ! $ P_s (t+\Delta t) $ . 地表面気圧. Surface pressure !------------------------------------- ! 地形データ (地表 $ \Phi $ ) 変数 ! Geography data (surface $ \Phi $ ) variables real(DP), allocatable:: xy_Phis (:,:) ! $ \Phi_s $ . 地表ジオポテンシャル. ! Surface geo-potential !--------------------------------------------------------- ! 作業変数 ! 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:: unit_nml ! NAMELIST ファイルオープン用装置番号. ! Unit number for NAMELIST file open integer:: iostat_nml ! NAMELIST 読み込み時の IOSTAT. ! IOSTAT of NAMELIST read character(STRING):: init_nc_rangeB ! 初期値入力の際の切り出し指定 ( $ t-\Delta t $ ). ! Range of initial data input ( $ t-\Delta t $ ) character(STRING):: init_nc_rangeN ! 初期値入力の際の切り出し指定 ( $ t $ ). ! Range of initial data input ( $ t $ ) type(CONST):: const_earth ! 物理定数. Physical constants. type(DYNSPAS83):: dyn ! 力学過程. ! Dynamical core type(PHYHS94):: phy_hs ! 物理過程 (Held and Suarez (1994)) ! Physical process (Held and Suarez (1994)) type(TFILTER):: tfilt ! タイムフィルター. ! Time filter type(CLOCK):: clk_setup, clk_histget, clk_histput, & & clk_dyn, clk_phy, clk_tfilt ! CPU 時間モニター. ! CPU time monitor type(GT_HISTORY):: gthist_xyz_U, gthist_xyz_V, gthist_xyz_Vor, & & gthist_xyz_Div, gthist_xyz_Temp, gthist_xyz_QVap, & & gthist_xy_Ps, gthist_restart ! ヒストリデータ, リスタートデータ出力. ! Output of history data and restart data character(*), parameter:: version = & & '$Name: dcpam4-20070731-1 $' // & & '$Id: dcpam_hs94.f90,v 1.13 2007/07/31 14:35:28 morikawa Exp $' character(*), parameter:: subname = 'dcpam_hs94' continue !--------------------------------------------------------- ! コマンドライン引数の処理 ! Command line arguments handling !--------------------------------------------------------- call Open( arg ) call HelpMsg( arg, 'Title', title ) call HelpMsg( arg, 'Usage', & & './dcpam_hs94 [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 ) call BeginSub( subname, version=version ) !------------------------------------------------------------------- ! CPU 時間モニターの初期設定 ! Configure the settings for CPU time monitor !------------------------------------------------------------------- call Create( & & clk_setup, & ! (out) & 'Setup') ! (in) call Create( & & clk_histget, & ! (out) & 'HistoryGet') ! (in) call Create( & & clk_histput, & ! (out) & 'HistoryPut') ! (in) call Create( & & clk_dyn, & ! (out) & 'Dynamics') ! (in) call Create( & & clk_phy, & ! (out) & 'Phyisics') ! (in) call Create( & & clk_tfilt, & ! (out) & 'TimeFilter') ! (in) !------------------------------------------------------------------- ! 格子点数・最大全波数の設定 ! Configure the grid points and maximum truncated wavenumber !------------------------------------------------------------------- call Start(clk_setup) ! (inout) !------------------------- ! NAMELIST の読み込み ! Load NAMELIST if ( .not. trim(VAL_namelist) == '' ) then call FileOpen( unit = unit_nml, & ! (out) & file = VAL_namelist, mode = 'r' ) ! (in) read( unit = unit_nml, & ! (in) & nml = dcpam_hs94_grid_nml, iostat = iostat_nml ) ! (out) if ( iostat_nml == 0 ) then call MessageNotify( 'M', subname, & & 'NAMELIST group "%c" is loaded from "%c".', & & c1='dcpam_hs94_grid_nml', c2=trim(VAL_namelist) ) write(STDOUT, nml = dcpam_hs94_grid_nml) else call MessageNotify( 'W', subname, & & 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', & & c1='dcpam_hs94_grid_nml', c2=trim(VAL_namelist), & & i=(/iostat_nml/) ) end if close( unit_nml ) end if !------------------------------------------------------------------- ! 現在時刻, 時間ステップ $ \Delta t $ , ! 積分終了時刻, 予測時間表示の設定 ! Configure current time, time step $ \Delta t $ , ! finish time of integral, predicted CPU time !------------------------------------------------------------------- !------------------------- ! NAMELIST の読み込み ! Load NAMELIST if ( .not. trim(VAL_namelist) == '' ) then call FileOpen( unit = unit_nml, & ! (out) & file = VAL_namelist, mode = 'r' ) ! (in) read( unit = unit_nml, & ! (in) & nml = dcpam_hs94_time_nml, iostat = iostat_nml ) ! (out) if ( iostat_nml == 0 ) then call MessageNotify( 'M', subname, & & 'NAMELIST group "%c" is loaded from "%c".', & & c1='dcpam_hs94_time_nml', c2=trim(VAL_namelist) ) write(STDOUT, nml = dcpam_hs94_time_nml) else call MessageNotify( 'W', subname, & & 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', & & c1='dcpam_hs94_time_nml', c2=trim(VAL_namelist), & & i=(/iostat_nml/) ) end if close( unit_nml ) end if !------------------------- ! DC_DIFFTIME 型変数の設定 ! Configure DC_DIFFTIME type variables call Create( & & current_time, & ! (out) & start_time_value, start_time_unit) ! (in) call Create( & & delta_time, & ! (out) & delta_time_value, delta_time_unit) ! (in) call Create( & & total_time, & ! (out) & total_time_value, total_time_unit) ! (in) call Create( & & predict_show_interval_time, & ! (out) & predict_show_interval_value, & ! (in) & predict_show_interval_unit) ! (in) !------------------------------------------------------------------- ! 地形データ (地表 $ \Phi $ ) の取得 ! Get geography data (surface $ \Phi $ ) !------------------------------------------------------------------- !------------------------- ! NAMELIST の読み込み ! Load NAMELIST if ( .not. trim(VAL_namelist) == '' ) then call FileOpen( unit = unit_nml, & ! (out) & file = VAL_namelist, mode = 'r' ) ! (in) read( unit = unit_nml, & ! (in) & nml = dcpam_hs94_geodata_nml, iostat = iostat_nml ) ! (out) if ( iostat_nml == 0 ) then call MessageNotify( 'M', subname, & & 'NAMELIST group "%c" is loaded from "%c".', & & c1='dcpam_hs94_geodata_nml', c2=trim(VAL_namelist) ) write(STDOUT, nml = dcpam_hs94_geodata_nml) else call MessageNotify( 'W', subname, & & 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', & & c1='dcpam_hs94_geodata_nml', c2=trim(VAL_namelist), & & i=(/iostat_nml/) ) end if close( unit_nml ) end if !------------------------- ! ファイルの読み込み ! Load a file allocate( xy_Phis(0:imax-1, 0:jmax-1) ) if ( geography_data_prepared ) then call HistoryGet( & & geo_nc, 'Phis', & ! (in) & xy_Phis ) ! (out) else xy_Phis = 0.0_DP end if !------------------------------------------------------------------- ! 物理定数の設定 ! Configure the physical constants !------------------------------------------------------------------- call Create( constant = const_earth, & ! (inout) & Cp = 1004.6_DP, RAir = 287.04_DP, & ! (in) & VisOrder = 8, & ! (in) & EFoldTime = 8640.0_DP, & ! (in) & nmlfile = VAL_namelist ) ! (in) call PutLine( constant = const_earth ) ! (in) call Get( constant = const_earth, & ! (in) & PI = PI, RPlanet = RPlanet, & ! (out) & Grav = Grav, Omega = Omega, & ! (out) & Cp = Cp, RAir = RAir, & ! (out) & EpsVT = EpsVT, & ! (out) & VisOrder = VisOrder, & ! (out) & EFoldTime = EFoldTime ) ! (out) !------------------------------------------------------------------- ! 力学過程の設定 ! Configure the settings for dynamical core !------------------------------------------------------------------- !------------------------- ! dyn_spectral_as83 の設定 ! Configure 'dyn_spectral_as83' call Create( dyn_sp_as = dyn, & ! (inout) & nmax = nmax, imax = imax, jmax = jmax, kmax = kmax, & ! (in) & PI = PI, RPlanet = RPlanet, & ! (in) & Grav = Grav, Omega = Omega, & ! (in) & Cp = Cp, RAir = RAir, & ! (in) & EpsVT = EpsVT, & ! (in) & VisOrder = VisOrder, & ! (in) & EFoldTime = EFoldTime, & ! (in) & DelTime = EvalSec(delta_time), & ! (in) & xy_Phis = xy_Phis, & ! (in) & openmp_threads = openmp_threads, & ! (in) & r_SigmaSet = (/ & & 1.00_DP, 0.95_DP, 0.90_DP, 0.85_DP, 0.80_DP, & & 0.75_DP, 0.70_DP, 0.65_DP, 0.60_DP, 0.55_DP, & & 0.50_DP, 0.45_DP, 0.40_DP, 0.35_DP, 0.30_DP, & & 0.25_DP, 0.20_DP, 0.15_DP, 0.10_DP, 0.05_DP, & & 0.0_DP /), & ! (in) & nmlfile = VAL_namelist ) ! (in) !------------------------------------------------------------------- ! 緯度経度データ, 鉛直レベルの設定 ! (リスタートファイル, ヒストリファイル出力用) ! Configure the data of latitude and longitude and vertical level ! for output of restart file and history files !------------------------------------------------------------------- allocate( x_Lon(0:imax-1) ) allocate( y_Lat(0:jmax-1) ) allocate( z_Sigma(0:kmax-1) ) allocate( r_Sigma(0:kmax) ) allocate( z_DelSigma(0:kmax-1) ) call GetAxes( dyn_sp_as = dyn, & ! (inout) & x_Lon = x_Lon, y_Lat = y_Lat, & ! (out) & z_Sigma = z_Sigma, r_Sigma = r_Sigma, & ! (out) & z_DelSigma = z_DelSigma ) ! (out) !--------------------------------------------------------- ! 物理過程の設定 ! Configure the settings for physical processes !--------------------------------------------------------- !------------------------------------- ! Held and Suarez (1994) call Create( phy_hs = phy_hs, & ! (inout) & imax = imax, jmax = jmax, kmax = kmax, & ! (in) & y_Lat = y_Lat, z_Sigma = z_Sigma, & ! (in) & DelTime = EvalSec(delta_time), & ! (in) & Cp = Cp, RAir = RAir, & ! (in) & nmlfile = VAL_namelist ) ! (in) !------------------------------------------------------------------- ! タイムフィルターの設定 ! Configure the settings for time filter !------------------------------------------------------------------- call Create( tfilt, & ! (out) & filter_param = 0.05_DP, & ! (in) & int_time = delta_time, cur_time = current_time, & ! (in) & nmlfile = VAL_namelist ) ! (in) !------------------------------------------------------------------- ! 予報変数の割付 ! Allocations of prediction variables !------------------------------------------------------------------- allocate( xyz_VorB(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_DivB(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_TempB(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_QVapB(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xy_PsB(0:imax-1, 0:jmax-1) ) allocate( xyz_VorN(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_DivN(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_TempN(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_QVapN(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xy_PsN(0:imax-1, 0:jmax-1) ) allocate( xyz_UA(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_VA(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_VorA(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_DivA(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_TempA(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xyz_QVapA(0:imax-1, 0:jmax-1, 0:kmax-1) ) allocate( xy_PsA(0:imax-1, 0:jmax-1) ) call Stop(clk_setup) ! (inout) !------------------------------------------------------------------- ! 初期値データの取得もしくは生成 ! Get or generate initial data !------------------------------------------------------------------- call Start(clk_histget) ! (inout) !------------------------- ! NAMELIST の読み込み ! Load NAMELIST if ( .not. trim(VAL_namelist) == '' ) then call FileOpen( unit = unit_nml, & ! (out) & file = VAL_namelist, mode = 'r' ) ! (in) read( unit = unit_nml, & ! (in) & nml = dcpam_hs94_initdata_nml, iostat = iostat_nml ) ! (out) if ( iostat_nml == 0 ) then call MessageNotify( 'M', subname, & & 'NAMELIST group "%c" is loaded from "%c".', & & c1='dcpam_hs94_initdata_nml', c2=trim(VAL_namelist) ) write(STDOUT, nml = dcpam_hs94_initdata_nml) else call MessageNotify( 'W', subname, & & 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', & & c1='dcpam_hs94_initdata_nml', c2=trim(VAL_namelist), & & i=(/iostat_nml/) ) end if close( unit_nml ) end if !------------------------- ! ファイルの読み込み ! Load a file if ( initial_data_prepared ) then !!$ !------------------------- !!$ ! 座標軸の読み込み !!$ ! Load axes !!$ call HistoryGet( & !!$ & file = init_nc, varname = 'lon', & ! (in) !!$ & array = x_Lon ) ! (out) !!$ call HistoryGet( & !!$ & file = init_nc, varname = 'lon_weight', & ! (in) !!$ & array = x_LonWeight ) ! (out) !!$ call HistoryGet( & !!$ & file = init_nc, varname = 'lat', & ! (in) !!$ & array = y_Lat ) ! (out) !!$ call HistoryGet( & !!$ & file = init_nc, varname = 'lat_weight', & ! (in) !!$ & array = y_LonWeight ) ! (out) !!$ call HistoryGet( & !!$ & file = init_nc, varname = 'sig', & ! (in) !!$ & array = z_Sigma ) ! (out) !!$ call HistoryGet( & !!$ & file = init_nc, varname = 'sigm', & ! (in) !!$ & array = r_Sigma ) ! (out) !------------------------- ! データの読み込み ! Load data init_nc_rangeB = trim(init_nc_time_varname) // '=' // & & trim(toChar(init_nc_timeB)) init_nc_rangeN = trim(init_nc_time_varname) // '=' // & & trim(toChar(init_nc_timeN)) call HistoryGet( & & file = init_nc, varname = 'Vor', & ! (in) & array = xyz_VorB, & ! (out) & range = init_nc_rangeB ) ! (in) call HistoryGet( & & file = init_nc, varname = 'Vor', & ! (in) & array = xyz_VorN, & ! (out) & range = init_nc_rangeN ) ! (in) call HistoryGet( & & file = init_nc, varname = 'Div', & ! (in) & array = xyz_DivB, & ! (out) & range = init_nc_rangeB ) ! (in) call HistoryGet( & & file = init_nc, varname = 'Div', & ! (in) & array = xyz_DivN, & ! (out) & range = init_nc_rangeN ) ! (in) call HistoryGet( & & file = init_nc, varname = 'Temp', & ! (in) & array = xyz_TempB, & ! (out) & range = init_nc_rangeB ) ! (in) call HistoryGet( & & file = init_nc, varname = 'Temp', & ! (in) & array = xyz_TempN, & ! (out) & range = init_nc_rangeN ) ! (in) call HistoryGet( & & file = init_nc, varname = 'QVap', & ! (in) & array = xyz_QVapB, & ! (out) & range = init_nc_rangeB ) ! (in) call HistoryGet( & & file = init_nc, varname = 'QVap', & ! (in) & array = xyz_QVapN, & ! (out) & range = init_nc_rangeN ) ! (in) call HistoryGet( & & file = init_nc, varname = 'Ps', & ! (in) & array = xy_PsB, & ! (out) & range = init_nc_rangeB ) ! (in) call HistoryGet( & & file = init_nc, varname = 'Ps', & ! (in) & array = xy_PsN, & ! (out) & range = init_nc_rangeN ) ! (in) else call Create( ini_dat = ini_dat, & ! (inout) & imax = imax, jmax = jmax, kmax = kmax ) ! (in) !!$ call GetAxes( ini_dat = ini_dat, & ! (inout) !!$ & x_Lon = x_Lon, x_LonWeight = x_LonWeight, & ! (out) !!$ & y_Lat = y_Lat, y_LatWeight = y_LatWeight, & ! (out) !!$ & z_Sigma = z_Sigma, r_Sigma = r_Sigma ) ! (out) !!$ call GetData( ini_dat = ini_dat, & ! (inout) call Get( ini_dat = ini_dat, & ! (inout) & xyz_VorB = xyz_VorB, xyz_DivB = xyz_DivB, & ! (out) & xyz_TempB = xyz_TempB, xyz_QVapB = xyz_QVapB, & ! (out) & xy_PsB = xy_PsB, & ! (out) & xyz_VorN = xyz_VorN, xyz_DivN = xyz_DivN, & ! (out) & xyz_TempN = xyz_TempN, xyz_QVapN = xyz_QVapN, & ! (out) & xy_PsN = xy_PsN ) ! (out) call Close( ini_dat ) ! (inout) end if call Stop(clk_histget) ! (inout) !---------------------------------------------------------------- ! ヒストリファイルへのデータ出力設定 ! Configure the settings for history data output !---------------------------------------------------------------- call Start(clk_histput) ! (inout) !------------------------- ! NAMELIST の読み込み ! Load NAMELIST if ( .not. trim(VAL_namelist) == '' ) then call FileOpen( unit = unit_nml, & ! (out) & file = VAL_namelist, mode = 'r' ) ! (in) read( unit = unit_nml, & ! (in) & nml = dcpam_hs94_history_nml, iostat = iostat_nml ) ! (out) if ( iostat_nml == 0 ) then call MessageNotify( 'M', subname, & & 'NAMELIST group "%c" is loaded from "%c".', & & c1='dcpam_hs94_history_nml', c2=trim(VAL_namelist) ) write(STDOUT, nml = dcpam_hs94_history_nml) else call MessageNotify( 'W', subname, & & 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', & & c1='dcpam_hs94_history_nml', c2=trim(VAL_namelist), & & i=(/iostat_nml/) ) end if close( unit_nml ) end if if ( .not. trim(VAL_namelist) == '' ) then call FileOpen( unit = unit_nml, & ! (out) & file = VAL_namelist, mode = 'r' ) ! (in) read( unit = unit_nml, & ! (in) & nml = dcpam_hs94_history_file_nml, iostat = iostat_nml ) ! (out) if ( iostat_nml == 0 ) then call MessageNotify( 'M', subname, & & 'NAMELIST group "%c" is loaded from "%c".', & & c1='dcpam_hs94_history_file_nml', c2=trim(VAL_namelist) ) write(STDOUT, nml = dcpam_hs94_history_file_nml) else call MessageNotify( 'W', subname, & & 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', & & c1='dcpam_hs94_history_file_nml', c2=trim(VAL_namelist), & & i=(/iostat_nml/) ) end if close( unit_nml ) end if !------------------------- ! DC_DIFFTIME 型変数の設定 ! Configure DC_DIFFTIME type variables call Create( & & history_interval_time, & ! (out) & history_interval_value, history_interval_unit) ! (in) !------------------------- ! xyz_U の出力設定 ! Configure the settings for "xyz_U" output call HistoryCreate( & & history = gthist_xyz_U, & ! (out) & file = xyz_U_filename, title = title, & ! (in) & source = source, institution = institution, & ! (in) & dims = StoA('lon', 'lat', 'sig', 'sigm', 'time'), & ! (in) & dimsizes = (/imax, jmax, kmax, kmax + 1, 0/), & ! (in) & longnames = StoA('longitude', 'latitude', & & 'sigma at layer midpoints', & & 'sigma at layer end-points (half level)', & & 'time'), & ! (in) & units = StoA('degree_east', 'degree_north', & & '1', '1', history_interval_unit), & ! (in) & origin = real(EvalbyUnit(current_time + history_interval_time, & & history_interval_unit)), & ! (in) & interval = real(EvalbyUnit(history_interval_time, & & history_interval_unit)) ) ! (in) call HistoryPut( & & history = gthist_xyz_U, & ! (inout) & varname = 'lon', array = x_Lon / PI * 180.0_DP ) ! (in) call HistoryPut( & & history = gthist_xyz_U, & ! (inout) & varname = 'lat', array = y_Lat / PI * 180.0_DP ) ! (in) call HistoryPut( & & history = gthist_xyz_U, & ! (inout) & varname = 'sig', array = z_Sigma ) ! (in) call HistoryPut( & & history = gthist_xyz_U, & ! (inout) & varname = 'sigm', array = r_Sigma ) ! (in) call HistoryAddAttr( & & history = gthist_xyz_U, & ! (inout) & varname = 'lon', attrname = 'standard_name', & ! (in) & value = 'longitude' ) ! (in) call HistoryAddAttr( & & history = gthist_xyz_U, & ! (inout) & varname = 'lat', attrname = 'standard_name', & ! (in) & value = 'latitude' ) ! (in) call HistoryAddAttr( & & history = gthist_xyz_U, & ! (inout) & varname = 'sig', attrname = 'standard_name', & ! (in) & value = 'atmosphere_sigma_coordinate' ) ! (in) call HistoryAddAttr( & & history = gthist_xyz_U, & ! (inout) & varname = 'sigm', attrname = 'standard_name', & ! (in) & value = 'atmosphere_sigma_coordinate' ) ! (in) call HistoryAddAttr( & & history = gthist_xyz_U, & ! (inout) & varname = 'time', attrname = 'standard_name', & ! (in) & value = 'time' ) ! (in) call HistoryAddAttr( & & history = gthist_xyz_U, & ! (inout) & varname = 'sig', attrname = 'positive', & ! (in) & value = 'down' ) ! (in) call HistoryAddAttr( & & history = gthist_xyz_U, & ! (inout) & varname = 'sigm', attrname = 'positive', & ! (in) & value = 'down' ) ! (in) call HistoryAddVariable( & & history = gthist_xyz_U, & ! (inout) & varname = 'U', & ! (in) & dims = StoA('lon', 'lat', 'sig', 'time'), & ! (in) & longname = 'eastward wind', & ! (in) & units = 'm s-1', xtype = history_precision ) ! (in) call HistoryAddAttr( & & history = gthist_xyz_U, & ! (inout) & varname = 'U', attrname = 'standard_name', & ! (in) & value = 'eastward_wind' ) ! (in) !------------------------- ! xyz_V の出力設定 ! Configure the settings for "xyz_V" output call HistoryCopy( & & hist_dest = gthist_xyz_V, & ! (out) & file = xyz_V_filename, hist_src = gthist_xyz_U) ! (in) call HistoryAddVariable( & & history = gthist_xyz_V, & ! (inout) & varname = 'V', & ! (in) & dims = StoA('lon', 'lat', 'sig', 'time'), & ! (in) & longname = 'northward wind', & ! (in) & units = 'm s-1', xtype = history_precision ) ! (in) call HistoryAddAttr(& & history = gthist_xyz_V, & ! (inout) & varname = 'V', attrname = 'standard_name', & ! (in) & value = 'northward_wind' ) ! (in) !------------------------- ! xyz_Vor の出力設定 ! Configure the settings for "xyz_Vor" output call HistoryCopy( & & hist_dest = gthist_xyz_Vor, & ! (out) & file = xyz_Vor_filename, hist_src = gthist_xyz_U) ! (in) call HistoryAddVariable( & & history = gthist_xyz_Vor, & ! (inout) & varname = 'Vor', & ! (in) & dims = StoA('lon', 'lat', 'sig', 'time'), & ! (in) & longname = 'vorticity', & ! (in) & units = 's-1', xtype = history_precision ) ! (in) call HistoryAddAttr(& & history = gthist_xyz_Vor, & ! (inout) & varname = 'Vor', attrname = 'standard_name', & ! (in) & value = 'atmosphere_relative_vorticity' ) ! (in) !------------------------- ! xyz_Div の出力設定 ! Configure the settings for "xyz_Div" output call HistoryCopy( & & hist_dest = gthist_xyz_Div, & ! (out) & file = xyz_Div_filename, hist_src = gthist_xyz_U) ! (in) call HistoryAddVariable( & & history = gthist_xyz_Div, & ! (inout) & varname = 'Div', & ! (in) & dims = StoA('lon', 'lat', 'sig', 'time'), & ! (in) & longname = 'divergence', & ! (in) & units = 's-1', xtype = history_precision ) ! (in) call HistoryAddAttr(& & history = gthist_xyz_Div, & ! (inout) & varname = 'Div', attrname = 'standard_name', & ! (in) & value = 'divergence_of_wind' ) ! (in) !------------------------- ! xyz_Temp の出力設定 ! Configure the settings for "xyz_Temp" output call HistoryCopy( & & hist_dest = gthist_xyz_Temp, & ! (out) & file = xyz_Temp_filename, hist_src = gthist_xyz_U) ! (in) call HistoryAddVariable( & & history = gthist_xyz_Temp, & ! (inout) & varname = 'Temp', & ! (in) & dims = StoA('lon', 'lat', 'sig', 'time'), & ! (in) & longname = 'temperature', & ! (in) & units = 'K', xtype = history_precision ) ! (in) call HistoryAddAttr(& & history = gthist_xyz_Temp, & ! (inout) & varname = 'Temp', attrname = 'standard_name', & ! (in) & value = 'air_temperature' ) ! (in) !------------------------- ! xyz_QVap の出力設定 ! Configure the settings for "xyz_QVap" output call HistoryCopy( & & hist_dest = gthist_xyz_QVap, & ! (out) & file = xyz_QVap_filename, hist_src = gthist_xyz_U) ! (in) call HistoryAddVariable( & & history = gthist_xyz_QVap, & ! (inout) & varname = 'QVap', & ! (in) & dims = StoA('lon', 'lat', 'sig', 'time'), & ! (in) & longname = 'specific humidity', & ! (in) & units = '1', xtype = history_precision ) ! (in) call HistoryAddAttr(& & history = gthist_xyz_QVap, & ! (inout) & varname = 'QVap', attrname = 'standard_name', & ! (in) & value = 'specific_humidity' ) ! (in) !------------------------- ! xy_Ps の出力設定 ! Configure the settings for "xy_Ps" output call HistoryCopy( & & hist_dest = gthist_xy_Ps, & ! (out) & file = xy_Ps_filename, hist_src = gthist_xyz_U) ! (in) call HistoryAddVariable( & & history = gthist_xy_Ps, & ! (inout) & varname = 'Ps', & ! (in) & dims = StoA('lon', 'lat', 'time'), & ! (in) & longname = 'surface pressure', & ! (in) & units = 'Pa', xtype = history_precision ) ! (in) call HistoryAddAttr(& & history = gthist_xy_Ps, & ! (inout) & varname = 'Ps', attrname = 'standard_name', & ! (in) & value = 'surface_air_pressure' ) ! (in) !------------------------- ! ファイル出力に関してメッセージを表示 ! Print message of file output call MessageNotify( 'M', subname, & & 'History files are created.' ) !---------------------------------------------------------------- ! リスタートファイルへのデータ出力設定 ! Configure the settings for restart data output !---------------------------------------------------------------- !------------------------- ! NAMELIST の読み込み ! Load NAMELIST if ( .not. trim(VAL_namelist) == '' ) then call FileOpen( unit = unit_nml, & ! (out) & file = VAL_namelist, mode = 'r' ) ! (in) read( unit = unit_nml, & ! (in) & nml = dcpam_hs94_restart_nml, iostat = iostat_nml ) ! (out) if ( iostat_nml == 0 ) then call MessageNotify( 'M', subname, & & 'NAMELIST group "%c" is loaded from "%c".', & & c1='dcpam_hs94_restart_nml', c2=trim(VAL_namelist) ) write(STDOUT, nml = dcpam_hs94_restart_nml) else call MessageNotify( 'W', subname, & & 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', & & c1='dcpam_hs94_restart_nml', c2=trim(VAL_namelist), & & i=(/iostat_nml/) ) end if close( unit_nml ) end if !------------------------- ! DC_DIFFTIME 型変数の設定 ! Configure DC_DIFFTIME type variables call Create( & & restart_interval_time, & ! (out) & restart_interval_value, restart_interval_unit) ! (in) call HistoryCreate( & & history = gthist_restart, & ! (out) & file = restart_filename, title = title, & ! (in) & source = source, institution = institution, & ! (in) & dims = StoA('lon', 'lat', 'sig', 'sigm', 'time'), & ! (in) & dimsizes = (/imax, jmax, kmax, kmax + 1, 0/), & ! (in) & longnames = StoA('longitude', 'latitude', & & 'sigma at layer midpoints', & & 'sigma at layer end-points (half level)', & & 'time'), & ! (in) & units = StoA('degree_east', 'degree_north', & & '1', '1', restart_interval_unit), & ! (in) & origin = real(EvalbyUnit(current_time, & & restart_interval_unit)), & ! (in) & interval = real(EvalbyUnit(restart_interval_time, & & restart_interval_unit)) ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'lon', array = x_Lon / PI * 180.0_DP ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'lat', array = y_Lat / PI * 180.0_DP ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'sig', array = z_Sigma ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'sigm', array = r_Sigma ) ! (in) call HistoryAddAttr( & & history = gthist_restart, & ! (inout) & varname = 'lon', attrname = 'standard_name', & ! (in) & value = 'longitude' ) ! (in) call HistoryAddAttr( & & history = gthist_restart, & ! (inout) & varname = 'lat', attrname = 'standard_name', & ! (in) & value = 'latitude' ) ! (in) call HistoryAddAttr( & & history = gthist_restart, & ! (inout) & varname = 'sig', attrname = 'standard_name', & ! (in) & value = 'atmosphere_sigma_coordinate' ) ! (in) call HistoryAddAttr( & & history = gthist_restart, & ! (inout) & varname = 'sigm', attrname = 'standard_name', & ! (in) & value = 'atmosphere_sigma_coordinate' ) ! (in) call HistoryAddAttr( & & history = gthist_restart, & ! (inout) & varname = 'time', attrname = 'standard_name', & ! (in) & value = 'time' ) ! (in) call HistoryAddAttr( & & history = gthist_restart, & ! (inout) & varname = 'sig', attrname = 'positive', & ! (in) & value = 'down' ) ! (in) call HistoryAddAttr( & & history = gthist_restart, & ! (inout) & varname = 'sigm', attrname = 'positive', & ! (in) & value = 'down' ) ! (in) call HistoryAddVariable( & & history = gthist_restart, & ! (inout) & varname = 'Vor', & ! (in) & dims = StoA('lon', 'lat', 'sig', 'time'), & ! (in) & longname = 'vorticity', & ! (in) & units = 's-1', xtype = 'double' ) ! (in) call HistoryAddAttr(& & history = gthist_restart, & ! (inout) & varname = 'Vor', attrname = 'standard_name', & ! (in) & value = 'atmosphere_relative_vorticity' ) ! (in) call HistoryAddVariable( & & history = gthist_restart, & ! (inout) & varname = 'Div', & ! (in) & dims = StoA('lon', 'lat', 'sig', 'time'), & ! (in) & longname = 'divergence', & ! (in) & units = 's-1', xtype = 'double' ) ! (in) call HistoryAddAttr( & & history = gthist_restart, & ! (inout) & varname = 'Div', attrname = 'standard_name', & ! (in) & value = 'divergence_of_wind' ) ! (in) call HistoryAddVariable( & & history = gthist_restart, & ! (inout) & varname = 'Temp', & ! (in) & dims = StoA('lon', 'lat', 'sig', 'time'), & ! (in) & longname = 'temperature', & ! (in) & units = 'K', xtype = 'double' ) ! (in) call HistoryAddAttr(& & history = gthist_restart, & ! (inout) & varname = 'Temp', attrname = 'standard_name', & ! (in) & value = 'air_temperature' ) ! (in) call HistoryAddVariable( & & history = gthist_restart, & ! (inout) & varname = 'QVap', & ! (in) & dims = StoA('lon', 'lat', 'sig', 'time'), & ! (in) & longname = 'specific humidity', & ! (in) & units = '1', xtype = 'double' ) ! (in) call HistoryAddAttr(& & history = gthist_restart, & ! (inout) & varname = 'QVap', attrname = 'standard_name', & ! (in) & value = 'specific_humidity' ) ! (in) call HistoryAddVariable( & & history = gthist_restart, & ! (inout) & varname = 'Ps', & ! (in) & dims = StoA('lon', 'lat', 'time'), & ! (in) & longname = 'surface pressure', & ! (in) & units = 'Pa', xtype = 'double' ) ! (in) call HistoryAddAttr(& & history = gthist_restart, & ! (inout) & varname = 'Ps', attrname = 'standard_name', & ! (in) & value = 'surface_air_pressure' ) ! (in) !------------------------- ! ファイル出力に関してメッセージを表示 ! Print message of file output call MessageNotify( 'M', subname, & & 'Restart file "%c" is created.', & & c1=trim(restart_filename) ) call Stop(clk_histput) ! (inout) MainLoop : do while (current_time < total_time) !---------------------------------------------------------------- ! 力学過程演算 ! Dynamical core !---------------------------------------------------------------- call Start(clk_dyn) ! (inout) call Dynamics( dyn, & ! (inout) & xyz_VorB = xyz_VorB, xyz_DivB = xyz_DivB, & ! (in) & xyz_TempB = xyz_TempB, xyz_QVapB = xyz_QVapB, & ! (in) & xy_PsB = xy_PsB, & ! (in) ! & xyz_VorN = xyz_VorN, xyz_DivN = xyz_DivN, & ! (in) & xyz_TempN = xyz_TempN, xyz_QVapN = xyz_QVapN, & ! (in) & xy_PsN = xy_PsN, & ! (in) ! & xyz_VorA = xyz_VorA, xyz_DivA = xyz_DivA, & ! (out) & xyz_TempA = xyz_TempA, xyz_QVapA = xyz_QVapA, & ! (out) & xy_PsA = xy_PsA ) ! (out) call Stop(clk_dyn) ! (inout) !---------------------------------------------------------------- ! 物理過程 ! Physical processes !---------------------------------------------------------------- !----------------------------------- ! Held and Suarez(1994) の加熱、散逸 ! Heating and dissipation by Held and Suarez(1994) call Start(clk_phy) ! (inout) call VorDiv2UV( dyn, & ! (inout) & xyz_Vor = xyz_VorA, xyz_Div = xyz_DivA, & ! (in) & xyz_U = xyz_UA, xyz_V = xyz_VA ) ! (out) call Forcing( phy_hs = phy_hs, & ! (inout) & xyz_U = xyz_UA, xyz_V = xyz_VA, & ! (inout) & xyz_Temp = xyz_TempA, & ! (inout) & xy_Ps = xy_PsA ) ! (in) call UV2VorDiv( dyn, & ! (inout) & xyz_U = xyz_UA, xyz_V = xyz_VA, & ! (in) & xyz_Vor = xyz_VorA, xyz_Div = xyz_DivA ) ! (out) call Stop(clk_phy) ! (inout) !---------------------------------------------------------------- ! タイムフィルター ! Time filter !---------------------------------------------------------------- call Start(clk_tfilt) ! (inout) call Filter( & & tfilt, & ! (in) & xyz_VorB, & ! (in) & xyz_VorN, & ! (inout) & xyz_VorA) ! (in) call Filter( & & tfilt, & ! (in) & xyz_DivB, & ! (in) & xyz_DivN, & ! (inout) & xyz_DivA) ! (in) call Filter( & & tfilt, & ! (in) & xyz_TempB, & ! (in) & xyz_TempN, & ! (inout) & xyz_TempA) ! (in) call Filter( & & tfilt, & ! (in) & xyz_QVapB, & ! (in) & xyz_QVapN, & ! (inout) & xyz_QVapA) ! (in) call Filter( & & tfilt, & ! (in) & xy_PsB, & ! (in) & xy_PsN, & ! (inout) & xy_PsA) ! (in) call Progress( & & tfilt, & ! (inout) & time=delta_time) ! (in) call Stop(clk_tfilt) ! (inout) !---------------------------------------------------------------- ! ヒストリファイルへのデータ出力 ! History data output !---------------------------------------------------------------- call Start(clk_histput) ! (inout) if ( mod(current_time + delta_time, history_interval_time) == 0 ) then call HistoryPut( & & history = gthist_xyz_Vor, & ! (inout) & varname = 'Vor', array = xyz_VorA ) ! (in) call HistoryPut( & & history = gthist_xyz_Div, & ! (inout) & varname = 'Div', array = xyz_DivA ) ! (in) call HistoryPut( & & history = gthist_xyz_Temp, & ! (inout) & varname = 'Temp', array = xyz_TempA ) ! (in) call HistoryPut( & & history = gthist_xyz_QVap, & ! (inout) & varname = 'QVap', array = xyz_QVapA ) ! (in) call HistoryPut( & & history = gthist_xy_Ps, & ! (inout) & varname = 'Ps', array = xy_PsA ) ! (in) call VorDiv2UV( dyn, & ! (inout) & xyz_Vor = xyz_VorA, xyz_Div = xyz_DivA, & ! (in) & xyz_U = xyz_UA, xyz_V = xyz_VA ) ! (out) call HistoryPut( & & history = gthist_xyz_U, & ! (inout) & varname = 'U', array = xyz_UA ) ! (in) call HistoryPut( & & history = gthist_xyz_V, & ! (inout) & varname = 'V', array = xyz_VA ) ! (in) !--------------------------------- ! ファイル出力に関してメッセージを表示 ! Print message of file output call MessageNotify( 'M', subname, & & 'History data (time=%f %c) is output.', & & d=(/EvalbyUnit(current_time + delta_time, history_interval_unit)/), & & c1=trim(history_interval_unit) ) end if !---------------------------------------------------------------- ! リスタートファイルへのデータ出力 ! Restart data output !---------------------------------------------------------------- if ( mod(current_time + delta_time, restart_interval_time) == 0 ) then !--------------------------------- ! ステップ $ t $ のデータの出力 ! Output data on step $ t $ call HistorySetTime( & & history = gthist_restart, & ! (inout) & time = real( EvalbyUnit(current_time, & & restart_interval_unit) ) ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'Vor', array = xyz_VorN ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'Div', array = xyz_DivN ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'Temp', array = xyz_TempN ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'QVap', array = xyz_QVapN ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'Ps', array = xy_PsN ) ! (in) !--------------------------------- ! ステップ $ t + \Delta t $ のデータの出力 ! Output data on step $ t \Delta t $ call HistorySetTime( & & history = gthist_restart, & ! (inout) & time = real( EvalbyUnit(current_time + delta_time, & & restart_interval_unit) ) ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'Vor', array = xyz_VorA ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'Div', array = xyz_DivA ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'Temp', array = xyz_TempA ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'QVap', array = xyz_QVapA ) ! (in) call HistoryPut( & & history = gthist_restart, & ! (inout) & varname = 'Ps', array = xy_PsA ) ! (in) !--------------------------------- ! ファイル出力に関してメッセージを表示 ! Print message of file output call MessageNotify( 'M', subname, & & 'Restart data (time=%f %a - %f %a, and %f %a) is output to "%c"', & & d=(/ EvalbyUnit(current_time + delta_time, & & restart_interval_unit), & & delta_time_value, & & EvalbyUnit(current_time + delta_time, & & restart_interval_unit) /), & & ca=StoA( trim(restart_interval_unit), & & trim(delta_time_unit), & & trim(restart_interval_unit) ), & & c1=trim(restart_filename) ) end if call Stop(clk_histput) ! (inout) !----------------------------------------------------------------- ! プログラム終了までの予測 CPU 時間および予測日時を表示 ! Print predicted CPU time and date to finish of program !----------------------------------------------------------------- if ( mod(current_time + delta_time, predict_show_interval_time) == 0 ) then call Predict( & & clk = clk_setup + clk_histget + clk_histput & & + clk_dyn + clk_phy + clk_tfilt, & ! (in) & progress = real( ( current_time + delta_time ) / total_time ) ) ! (in) end if !---------------------------------------------------------------- ! 予測変数の時刻付け替え ! Exchange time of prediction variables !---------------------------------------------------------------- xyz_VorB = xyz_VorN xyz_VorN = xyz_VorA xyz_VorA = 0.0_DP xyz_DivB = xyz_DivN xyz_DivN = xyz_DivA xyz_DivA = 0.0_DP xyz_TempB = xyz_TempN xyz_TempN = xyz_TempA xyz_TempA = 0.0_DP xyz_QVapB = xyz_QVapN xyz_QVapN = xyz_QVapA xyz_QVapA = 0.0_DP xy_PsB = xy_PsN xy_PsN = xy_PsA xy_PsA = 0.0_DP !---------------------------------------------------------------- ! 現在時刻の更新 ! Update current time !---------------------------------------------------------------- current_time = current_time + delta_time enddo MainLoop !---------------------------------------------------------------- ! ヒストリファイルへのデータ出力の終了処理 ! Terminate history data output !---------------------------------------------------------------- call HistoryClose( history = gthist_xyz_U ) ! (inout) call HistoryClose( history = gthist_xyz_V ) ! (inout) call HistoryClose( history = gthist_xyz_Vor ) ! (inout) call HistoryClose( history = gthist_xyz_Div ) ! (inout) call HistoryClose( history = gthist_xyz_Temp ) ! (inout) call HistoryClose( history = gthist_xyz_QVap ) ! (inout) call HistoryClose( history = gthist_xy_Ps ) ! (inout) !---------------------------------------------------------------- ! リスタートファイルへのデータ出力の終了処理 ! Terminate restart data output !---------------------------------------------------------------- call HistoryClose( history = gthist_restart ) ! (inout) !---------------------------------------------------------------- ! CPU 時間の総計を表示 ! Print total CPU time !---------------------------------------------------------------- call Result( & & clks = (/clk_setup, clk_histget, clk_histput, & & clk_dyn, clk_phy, clk_tfilt/), & ! (in) & total_auto = .true.) ! (in) call EndSub( subname ) end program dcpam_hs94