init_sample.f90

Path: main/init_sample.f90
Last Update: Tue Sep 04 18:14:52 JST 2007

初期値データファイル生成プログラムのサンプル

Initial data file generation sample program

Authors:Yasuhiro MORIKAWA
Version:$Id: init_sample.f90,v 1.4 2007/09/04 09:14:52 morikawa Exp $
Tag Name:$Name: dcpam4-20070909 $
Copyright:Copyright (C) GFD Dennou Club, 2007. All rights reserved.
License:See COPYRIGHT

Methods

Included Modules

initial_data constants gt4_history dc_types dc_args dc_trace dc_message dc_string dc_clock dc_iounit

Public Instance methods

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 .

[Source]

program init_sample
  !
  ! 初期値生成のための実行プログラムのサンプルです.
  !
  ! This is sample executable program for initial data generation.
  !

  !---------------------------------------------------------
  !  初期値生成
  !  Generate initial data
  !---------------------------------------------------------
  use initial_data, only: INIDAT, Create, GetAxes, GetData, Close, PutLine

  !---------------------------------------------------------
  !  物理定数
  !  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, Open, HelpMsg, Option, Debug, Help, Strict, Close
  use dc_trace, only: DbgMessage, BeginSub, EndSub
  use dc_message,only: MessageNotify
  use dc_string, only: StoA, toChar
  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 = 'init_sample $Name: dcpam4-20070909 $ :: ' // '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:: y_Lat (:) ! 緯度. 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_Vor (:,:,:)
                              ! $ \zeta (t-\Delta t) $ . 渦度. Vorticity
  real(DP), allocatable:: xyz_Div (:,:,:)
                              ! $ D (t-\Delta t) $ .     発散. Divergence
  real(DP), allocatable:: xyz_Temp (:,:,:)
                              ! $ T (t-\Delta t) $ .     温度. Temperature
  real(DP), allocatable:: xyz_QVap (:,:,:)
                              ! $ q (t-\Delta t) $ .     比湿. Specific humidity
  real(DP), allocatable:: xy_Ps (:,:)
                              ! $ P_s (t-\Delta t) $ .   地表面気圧. Surface pressure

  !---------------------------------------------------------
  !  作業変数
  !  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
  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-20070909 $' // '$Id: init_sample.f90,v 1.4 2007/09/04 09:14:52 morikawa Exp $'
  character(STRING),  parameter:: subname = "init"

continue
  !-------------------------------------------------------------------
  !  コマンドライン引数の取得
  !  Get command line arguments
  !-------------------------------------------------------------------
  call Open( arg )
  call HelpMsg( arg, 'Title', title )
  call HelpMsg( arg, 'Usage', './init_sample [Options]' )
  call HelpMsg( arg, 'Description', '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 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, 'Setup')        ! (in)
  call Create( clk_histput, 'HistoryPut')   ! (in)

  call Start(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 Create( 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( y_Lat(0:jmax-1) )
  allocate( z_Sigma(0:kmax-1) )
  allocate( r_Sigma(0:kmax) )

  call GetAxes( ini_dat = ini_dat, x_Lon = x_Lon,     y_Lat = y_Lat, z_Sigma = z_Sigma, r_Sigma = r_Sigma )       ! (out)

  !-------------------------------------------------------------------
  !  予報変数の割付
  !  Allocations of prediction variables
  !-------------------------------------------------------------------
  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 GetData( ini_dat = ini_dat, xyz_Vor = xyz_Vor, xyz_Div = xyz_Div, xyz_Temp = xyz_Temp, xyz_QVap = xyz_QVap, xy_Ps = xy_Ps )                             ! (out)

  call Stop(clk_setup)   ! (inout)

  !-------------------------------------------------------------------
  !  初期値ファイルへのデータ出力設定
  !  Configure the settings for initial data output
  !-------------------------------------------------------------------
  call Start(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 = '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 = '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 Stop(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 Result( clks = (/clk_setup, clk_histput/), total_auto = .true.)                       ! (in)

  call EndSub(subname)
end program init_sample

[Validate]