| Path: | main/init_sample.f90 |
| Last Update: | Sat Jun 14 20:44:16 +0900 2008 |
| Authors: | Yasuhiro MORIKAWA |
| Version: | $Id: init_sample.f90,v 1.9 2008-06-14 11:44:16 morikawa Exp $ |
| Tag Name: | $Name: dcpam4-20080626 $ |
| Copyright: | Copyright (C) GFD Dennou Club, 2007. All rights reserved. |
| License: | See COPYRIGHT |
| Main Program : |
初期値生成のための実行プログラムのサンプルです.
This is sample executable program for initial data generation.
This procedure input/output NAMELIST#init_sample_grid_nml, NAMELIST#init_sample_file_nml .
program init_sample
!
! 初期値生成のための実行プログラムのサンプルです.
!
! This is sample executable program for initial data generation.
!
!---------------------------------------------------------
! 初期値生成
! Generate initial data
!---------------------------------------------------------
use initial_data, only: INIDAT, IniDataCreate, IniDataGetAxes, IniDataGet, IniDataClose, IniDataPutLine
!---------------------------------------------------------
! 物理定数
! Physical constants
!---------------------------------------------------------
use constants, only: CONST, Create, Get
!---------------------------------------------------------
! データ I/O
! Data I/O
!---------------------------------------------------------
use gt4_history, only: GT_HISTORY, HistoryCreate, HistoryAddVariable, HistoryPut, HistoryClose, HistoryAddAttr
!---------------------------------------------------------
! 汎用ユーティリティ
! Common utilities
!---------------------------------------------------------
use dc_types, only: DP, STRING, TOKEN, STDOUT
use dc_args, only: ARGS, DCArgsOpen, DCArgsHelpMsg, DCArgsOption, DCArgsDebug, DCArgsHelp, DCArgsStrict, DCArgsClose
use dc_trace, only: DbgMessage, BeginSub, EndSub
use dc_message,only: MessageNotify
use dc_string, only: StoA, toChar
use dc_clock, only: CLOCK, DCClockCreate, DCClockClose, DCClockStart, DCClockStop, DCClockResult, DCClockPredict, operator(+)
use dc_iounit, only: FileOpen
implicit none
!-------------------------------------------------------------------
! 実験の表題, モデルの名称, 所属機関名
! Title of a experiment, name of model, sub-organ
!-------------------------------------------------------------------
character(*), parameter:: title = 'init_sample $Name: dcpam4-20080626 $ :: ' // 'DCPAM sample program: initial data file generation'
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 = 12 ! 鉛直層数.
! Number of vertical level
namelist /init_sample_grid_nml/ nmax, imax, jmax, kmax
! 格子点, 最大波数の設定.
!
! Configure grid points and maximum truncated wavenumber
!-------------------------------------------------------------------
! ファイル名
! Filename
!-------------------------------------------------------------------
character(STRING):: init_nc = 'init_T10L12.nc'
! 初期値データ netCDF ファイル.
! NetCDF file for initial data
namelist /init_sample_file_nml/ init_nc
! ファイル名の設定.
!
! Configure filename
!---------------------------------------------------------
! 物理定数
! Physical constants
!---------------------------------------------------------
real(DP):: PI ! $ \pi $ . 円周率. Circular constant
!---------------------------------------------------------
! 配列の定義
! Declaration of array
!---------------------------------------------------------
!-------------------------------------
! 座標変数
! Coordinate variables
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
!-------------------------------------
! 予報変数
! Prediction variables
real(DP), allocatable:: xyz_U (:,:,:)
! $ u $ . 東西風速. Zonal wind
real(DP), allocatable:: xyz_V (:,:,:)
! $ v $ . 南北風速. Meridional wind
real(DP), allocatable:: xyz_Vor (:,:,:)
! $ \zeta $ . 渦度. Vorticity
real(DP), allocatable:: xyz_Div (:,:,:)
! $ D $ . 発散. Divergence
real(DP), allocatable:: xyz_Temp (:,:,:)
! $ T $ . 温度. Temperature
real(DP), allocatable:: xyz_QVap (:,:,:)
! $ q $ . 比湿. Specific humidity
real(DP), allocatable:: xy_Ps (:,:)
! $ p_s $ . 地表面気圧. Surface pressure
!---------------------------------------------------------
! 作業変数
! Work variables
!---------------------------------------------------------
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
integer:: unit_nml ! NAMELIST ファイルオープン用装置番号.
! Unit number for NAMELIST file open
integer:: iostat_nml ! NAMELIST 読み込み時の IOSTAT.
! IOSTAT of NAMELIST read
type(CONST):: const_earth ! 物理定数. Physical constants.
type(INIDAT):: ini_dat ! 初期値データ生成
! Generation of initial data
type(GT_HISTORY):: gthist_init
! 初期値データ出力.
! Output of initial data
type(CLOCK):: clk_setup, clk_histput
! CPU 時間モニター.
! CPU time monitor
character(*), parameter:: version = '$Name: dcpam4-20080626 $' // '$Id: init_sample.f90,v 1.9 2008-06-14 11:44:16 morikawa Exp $'
character(STRING), parameter:: subname = "init_sample"
continue
!-------------------------------------------------------------------
! コマンドライン引数の取得
! Command line options handling
!-------------------------------------------------------------------
call cmdline_optparse ! これは内部サブルーチン. This is an internal subroutine
call BeginSub(subname, version=version)
!-------------------------------------------------------------------
! CPU 時間モニターの初期設定
! Configure the settings for CPU time monitor
!-------------------------------------------------------------------
call DCClockCreate( clk_setup, 'Setup') ! (in)
call DCClockCreate( clk_histput, 'HistoryPut') ! (in)
call DCClockStart(clk_setup) ! (inout)
!-------------------------------------------------------------------
! 物理定数の設定
! Configure the physical constants
!-------------------------------------------------------------------
call Create( constant = const_earth ) ! (inout)
call Get( constant = const_earth, PI = PI ) ! (out)
!-------------------------------------------------------------------
! 格子点数・最大全波数の設定
! Configure the grid points and maximum truncated wavenumber
!-------------------------------------------------------------------
!-------------------------
! NAMELIST の読み込み
! Load NAMELIST
if ( .not. trim(VAL_namelist) == '' ) then
call FileOpen( unit = unit_nml, file = VAL_namelist, mode = 'r' ) ! (in)
read( unit = unit_nml, nml = init_sample_grid_nml, iostat = iostat_nml ) ! (out)
if ( iostat_nml == 0 ) then
call MessageNotify( 'M', subname, 'NAMELIST group "%c" is loaded from "%c".', c1='init_sample_grid_nml', c2=trim(VAL_namelist) )
write(STDOUT, nml = init_sample_grid_nml)
else
call MessageNotify( 'W', subname, 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', c1='init_sample_grid_nml', c2=trim(VAL_namelist), i=(/iostat_nml/) )
end if
close( unit_nml )
end if
!-------------------------------------------------------------------
! 出力ファイル名の設定
! Configure the output filename
!-------------------------------------------------------------------
!-------------------------
! NAMELIST の読み込み
! Load NAMELIST
if ( .not. trim(VAL_namelist) == '' ) then
call FileOpen( unit = unit_nml, file = VAL_namelist, mode = 'r' ) ! (in)
read( unit = unit_nml, nml = init_sample_file_nml, iostat = iostat_nml ) ! (out)
if ( iostat_nml == 0 ) then
call MessageNotify( 'M', subname, 'NAMELIST group "%c" is loaded from "%c".', c1='init_sample_file_nml', c2=trim(VAL_namelist) )
write(STDOUT, nml = init_sample_file_nml)
else
call MessageNotify( 'W', subname, 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', c1='init_sample_file_nml', c2=trim(VAL_namelist), i=(/iostat_nml/) )
end if
close( unit_nml )
end if
!-------------------------------------------------------------------
! 初期値データ出力の設定
! Configure the settings for initial data generation
!-------------------------------------------------------------------
call IniDataCreate( ini_dat = ini_dat, nmax = nmax, imax = imax, jmax = jmax, kmax = kmax, 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( 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 IniDataGetAxes( ini_dat = ini_dat, x_Lon = x_Lon, x_Lon_Weight = x_Lon_Weight, y_Lat = y_Lat, y_Lat_Weight = y_Lat_Weight, z_Sigma = z_Sigma, r_Sigma = r_Sigma ) ! (out)
!-------------------------------------------------------------------
! 予報変数の割付
! Allocations of prediction variables
!-------------------------------------------------------------------
allocate( xyz_U(0:imax-1, 0:jmax-1, 0:kmax-1) )
allocate( xyz_V(0:imax-1, 0:jmax-1, 0:kmax-1) )
allocate( xyz_Vor(0:imax-1, 0:jmax-1, 0:kmax-1) )
allocate( xyz_Div(0:imax-1, 0:jmax-1, 0:kmax-1) )
allocate( xyz_Temp(0:imax-1, 0:jmax-1, 0:kmax-1) )
allocate( xyz_QVap(0:imax-1, 0:jmax-1, 0:kmax-1) )
allocate( xy_Ps(0:imax-1, 0:jmax-1) )
!-------------------------------------------------------------------
! 初期値データの取得
! Get initial data
!-------------------------------------------------------------------
call IniDataGet( ini_dat = ini_dat, xyz_U = xyz_U, xyz_V = xyz_V, xyz_Vor = xyz_Vor, xyz_Div = xyz_Div, xyz_Temp = xyz_Temp, xyz_QVap = xyz_QVap, xy_Ps = xy_Ps ) ! (out)
call DCClockStop(clk_setup) ! (inout)
!-------------------------------------------------------------------
! 初期値ファイルへのデータ出力設定
! Configure the settings for initial data output
!-------------------------------------------------------------------
call DCClockStart(clk_histput) ! (inout)
call HistoryCreate( history = gthist_init, file = init_nc, title = title, source = source, institution = institution, dims = StoA('lon', 'lat', 'sig', 'sigm'), dimsizes = (/imax, jmax, kmax, kmax + 1/), longnames = StoA('longitude', 'latitude', 'sigma at layer midpoints', 'sigma at layer end-points (half level)'), units = StoA('degree_east', 'degree_north', '1', '1') ) ! (out)
call HistoryPut( history = gthist_init, varname = 'lon', array = x_Lon / PI * 180.0_DP ) ! (in)
call HistoryPut( history = gthist_init, varname = 'lat', array = y_Lat / PI * 180.0_DP ) ! (in)
call HistoryPut( history = gthist_init, varname = 'sig', array = z_Sigma ) ! (in)
call HistoryPut( history = gthist_init, varname = 'sigm', array = r_Sigma ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'lon', attrname = 'standard_name', value = 'longitude' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'lat', attrname = 'standard_name', value = 'latitude' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'sig', attrname = 'standard_name', value = 'atmosphere_sigma_coordinate' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'sigm', attrname = 'standard_name', value = 'atmosphere_sigma_coordinate' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'sig', attrname = 'positive', value = 'down' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'sigm', attrname = 'positive', value = 'down' ) ! (in)
call HistoryAddVariable( history = gthist_init, varname = 'lon_weight', dims = StoA('lon'), longname = 'weight for integration in longitude', units = 'radian', xtype = 'double' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'lon', attrname = 'gt_calc_weight', value = 'lon_weight' ) ! (in)
call HistoryPut( history = gthist_init, varname = 'lon_weight', array = x_Lon_Weight ) ! (in)
call HistoryAddVariable( history = gthist_init, varname = 'lat_weight', dims = StoA('lat'), longname = 'weight for integration in latitude', units = 'radian', xtype = 'double' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'lat', attrname = 'gt_calc_weight', value = 'lat_weight' ) ! (in)
call HistoryPut( history = gthist_init, varname = 'lat_weight', array = y_Lat_Weight ) ! (in)
call HistoryAddVariable( history = gthist_init, varname = 'U', dims = StoA('lon', 'lat', 'sig'), longname = 'eastward wind', units = 'm s-1', xtype = 'double' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'U', attrname = 'standard_name', value = 'eastward_wind' ) ! (in)
call HistoryAddVariable( history = gthist_init, varname = 'V', dims = StoA('lon', 'lat', 'sig'), longname = 'northward wind', units = 'm s-1', xtype = 'double' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'V', attrname = 'standard_name', value = 'northward_wind' ) ! (in)
call HistoryAddVariable( history = gthist_init, varname = 'Vor', dims = StoA('lon', 'lat', 'sig'), longname = 'vorticity', units = 's-1', xtype = 'double' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'Vor', attrname = 'standard_name', value = 'atmosphere_relative_vorticity' ) ! (in)
call HistoryAddVariable( history = gthist_init, varname = 'Div', dims = StoA('lon', 'lat', 'sig'), longname = 'divergence', units = 's-1', xtype = 'double' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'Div', attrname = 'standard_name', value = 'divergence_of_wind' ) ! (in)
call HistoryAddVariable( history = gthist_init, varname = 'Temp', dims = StoA('lon', 'lat', 'sig'), longname = 'temperature', units = 'K', xtype = 'double' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'Temp', attrname = 'standard_name', value = 'air_temperature' ) ! (in)
call HistoryAddVariable( history = gthist_init, varname = 'QVap', dims = StoA('lon', 'lat', 'sig'), longname = 'specific humidity', units = '1', xtype = 'double' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'QVap', attrname = 'standard_name', value = 'specific_humidity' ) ! (in)
call HistoryAddVariable( history = gthist_init, varname = 'Ps', dims = StoA('lon', 'lat'), longname = 'surface pressure', units = 'Pa', xtype = 'double' ) ! (in)
call HistoryAddAttr( history = gthist_init, varname = 'Ps', attrname = 'standard_name', value = 'surface_air_pressure' ) ! (in)
!----------------------------------------------------------------
! 初期値ファイルへのデータ出力
! Initial data output
!----------------------------------------------------------------
call HistoryPut( history = gthist_init, varname = 'U', array = xyz_U ) ! (in)
call HistoryPut( history = gthist_init, varname = 'V', array = xyz_Div ) ! (in)
call HistoryPut( history = gthist_init, varname = 'Vor', array = xyz_Vor ) ! (in)
call HistoryPut( history = gthist_init, varname = 'Div', array = xyz_Div ) ! (in)
call HistoryPut( history = gthist_init, varname = 'Temp', array = xyz_Temp ) ! (in)
call HistoryPut( history = gthist_init, varname = 'QVap', array = xyz_QVap ) ! (in)
call HistoryPut( history = gthist_init, varname = 'Ps', array = xy_Ps ) ! (in)
!----------------------------------------------------------------
! 初期値ファイルへのデータ出力の終了処理
! Terminate initial data output
!----------------------------------------------------------------
call HistoryClose( history = gthist_init ) ! (inout)
call DCClockStop(clk_histput) ! (inout)
!----------------------------------------------------------------
! ファイル出力に関してメッセージを表示
! Print message of file output
!----------------------------------------------------------------
call MessageNotify( 'M', subname, 'Initial data file "%c" is generated.', c1=trim(init_nc) )
!----------------------------------------------------------------
! CPU 時間の総計を表示
! Print total CPU time
!----------------------------------------------------------------
call DCClockResult( clks = (/clk_setup, clk_histput/), total_auto = .true.) ! (in)
call EndSub(subname)
contains
subroutine cmdline_optparse
!
! コマンドライン引数の処理を行います
!
! Handle command line options
!
call DCArgsOpen( arg = arg ) ! (out)
call DCArgsHelpMsg( arg = arg, category = 'Title', msg = title ) ! (in)
call DCArgsHelpMsg( arg = arg, category = 'Usage', msg = './' // trim(subname) // ' [Options]' ) ! (in)
call DCArgsHelpMsg( arg = arg, category = 'Description', msg = 'This program generates an initial data file. ' // 'By default, the filename is "' // trim(init_nc) // '", and ' // 'the resolution is T' // trim(toChar(nmax)) // 'L' // trim(toChar(kmax)) // '. ' // 'In order to change the settings, use NAMELIST file. ' // 'Some samples are prepared as init_sample_***.nml .' )
call DCArgsHelpMsg( arg = arg, category = 'Source', msg = source ) ! (in)
call DCArgsHelpMsg( arg = arg, category = 'Institution', msg = institution ) ! (in)
call DCArgsOption( arg = arg, options = StoA('-N', '--namelist'), flag = OPT_namelist, value = VAL_namelist, 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 init_sample
| Subroutine : |
コマンドライン引数の処理を行います
Handle command line options
subroutine cmdline_optparse
!
! コマンドライン引数の処理を行います
!
! Handle command line options
!
call DCArgsOpen( arg = arg ) ! (out)
call DCArgsHelpMsg( arg = arg, category = 'Title', msg = title ) ! (in)
call DCArgsHelpMsg( arg = arg, category = 'Usage', msg = './' // trim(subname) // ' [Options]' ) ! (in)
call DCArgsHelpMsg( arg = arg, category = 'Description', msg = 'This program generates an initial data file. ' // 'By default, the filename is "' // trim(init_nc) // '", and ' // 'the resolution is T' // trim(toChar(nmax)) // 'L' // trim(toChar(kmax)) // '. ' // 'In order to change the settings, use NAMELIST file. ' // 'Some samples are prepared as init_sample_***.nml .' )
call DCArgsHelpMsg( arg = arg, category = 'Source', msg = source ) ! (in)
call DCArgsHelpMsg( arg = arg, category = 'Institution', msg = institution ) ! (in)
call DCArgsOption( arg = arg, options = StoA('-N', '--namelist'), flag = OPT_namelist, value = VAL_namelist, 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