sst_sample.f90

Path: main/sst_sample.f90
Last Update: Sun Mar 02 23:22:06 +0900 2008

地表面データファイル生成プログラムのサンプル

Surface data file generation sample program

Authors:Yasuhiro MORIKAWA
Version:$Id: sst_sample.f90,v 1.5 2008-03-02 14:22:06 morikawa Exp $
Tag Name:$Name: dcpam4-20080609-1 $
Copyright:Copyright (C) GFD Dennou Club, 2007. All rights reserved.
License:See COPYRIGHT

Methods

Included Modules

surface_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#sst_sample_grid_nml, NAMELIST#sst_sample_file_nml .

[Source]

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

  !---------------------------------------------------------
  !  地表面データ生成
  !  Generate surface data
  !---------------------------------------------------------
  use surface_data, only: SRFDAT, SurfDataCreate, SurfDataClose, SurfDataPutLine, SurfDataInitialized, SurfDataGetAxes, SurfDataGet

  !---------------------------------------------------------
  !  物理定数
  !  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 = 'sst_sample $Name: dcpam4-20080609-1 $ :: ' // 'DCPAM sample program: surface 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

  namelist /sst_sample_grid_nml/ nmax, imax, jmax
                              ! 格子点, 最大波数の設定. 
                              !
                              ! Configure grid points and maximum truncated wavenumber

  !-------------------------------------------------------------------
  !  ファイル名
  !  Filename
  !-------------------------------------------------------------------
  character(STRING):: sst_nc = 'sst_T10.nc'
                              ! 地表面データ netCDF ファイル
                              ! NetCDF file for surface data

  namelist /sst_sample_file_nml/ sst_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

  !-------------------------------------
  !  地表面データ
  !  Surface data
  real(DP), allocatable:: xy_SurfTemp (:,:)
                              ! 地表面温度. 
                              ! Surface temperature

  !---------------------------------------------------------
  !  作業変数
  !  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(SRFDAT):: srf_dat      ! 地表面データ生成
                              ! Generation of surface data
  type(GT_HISTORY):: gthist_sst
                              ! 地表面データ出力. 
                              ! Output of surface data
  type(CLOCK):: clk_setup, clk_histput
                              ! CPU 時間モニター. 
                              ! CPU time monitor

  character(*), parameter:: version = '$Name: dcpam4-20080609-1 $' // '$Id: sst_sample.f90,v 1.5 2008-03-02 14:22:06 morikawa Exp $'
  character(STRING),  parameter:: subname = "sst_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 = sst_sample_grid_nml, iostat = iostat_nml ) ! (out)
    if ( iostat_nml == 0 ) then
      call MessageNotify( 'M', subname, 'NAMELIST group "%c" is loaded from "%c".', c1='sst_sample_grid_nml', c2=trim(VAL_namelist) )
      write(STDOUT, nml = sst_sample_grid_nml)
    else
      call MessageNotify( 'W', subname, 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', c1='sst_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 = sst_sample_file_nml, iostat = iostat_nml ) ! (out)
    if ( iostat_nml == 0 ) then
      call MessageNotify( 'M', subname, 'NAMELIST group "%c" is loaded from "%c".', c1='sst_sample_file_nml', c2=trim(VAL_namelist) )
      write(STDOUT, nml = sst_sample_file_nml)
    else
      call MessageNotify( 'W', subname, 'NAMELIST group "%c" is not found in "%c" (iostat=%d).', c1='sst_sample_file_nml', c2=trim(VAL_namelist), i=(/iostat_nml/) )
    end if
    close( unit_nml )
  end if

  !-------------------------------------------------------------------
  !  地表面データ出力の設定
  !  Configure the settings for surface data generation
  !-------------------------------------------------------------------
  call SurfDataCreate( srf_dat = srf_dat, nmax = nmax, imax = imax, jmax = jmax, PI = PI, 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) )

  call SurfDataGetAxes( srf_dat = srf_dat, x_Lon = x_Lon, x_Lon_Weight = x_Lon_Weight, y_Lat = y_Lat, y_Lat_Weight = y_Lat_Weight )  ! (out)

  !-------------------------------------------------------------------
  !  予報変数の割付
  !  Allocations of prediction variables
  !-------------------------------------------------------------------
  allocate( xy_SurfTemp(0:imax-1, 0:jmax-1) )

  !-------------------------------------------------------------------
  !  地表面データの取得
  !  Get surface data
  !-------------------------------------------------------------------
  call SurfDataGet( srf_dat = srf_dat, xy_SurfTemp = xy_SurfTemp )        ! (out)

  call SurfDataClose( srf_dat = srf_dat ) ! (inout)

  call DCClockStop(clk_setup)   ! (inout)

  !-------------------------------------------------------------------
  !  地表面データファイルへのデータ出力設定
  !  Configure the settings for surface data output
  !-------------------------------------------------------------------
  call DCClockStart(clk_histput)   ! (inout)

  call HistoryCreate( history = gthist_sst, file = sst_nc, title = title, source = source, institution = institution, dims = StoA('lon', 'lat'), dimsizes = (/imax, jmax/), longnames = StoA('longitude', 'latitude'), units = StoA('degree_east', 'degree_north') ) ! (out)

  call HistoryPut( history = gthist_sst, varname = 'lon', array = x_Lon / PI * 180.0_DP ) ! (in)
  call HistoryPut( history = gthist_sst, varname = 'lat', array = y_Lat / PI * 180.0_DP ) ! (in)

  call HistoryAddAttr( history = gthist_sst, varname = 'lon', attrname = 'standard_name', value = 'longitude' )                          ! (in)
  call HistoryAddAttr( history = gthist_sst, varname = 'lat', attrname = 'standard_name', value = 'latitude' )                           ! (in)

  call HistoryAddVariable( history = gthist_sst, varname = 'lon_weight', dims = StoA('lon'), longname = 'weight for integration in longitude', units = 'radian', xtype = 'double' )                ! (in)
  call HistoryAddAttr( history = gthist_sst, varname = 'lon', attrname = 'gt_calc_weight', value = 'lon_weight' )                          ! (in)
  call HistoryPut( history = gthist_sst, varname = 'lon_weight', array = x_Lon_Weight ) ! (in)

  call HistoryAddVariable( history = gthist_sst, varname = 'lat_weight', dims = StoA('lat'), longname = 'weight for integration in latitude', units = 'radian', xtype = 'double' )               ! (in)
  call HistoryAddAttr( history = gthist_sst, varname = 'lat', attrname = 'gt_calc_weight', value = 'lat_weight' )                          ! (in)
  call HistoryPut( history = gthist_sst, varname = 'lat_weight', array = y_Lat_Weight ) ! (in)

  call HistoryAddVariable( history = gthist_sst, varname = 'SurfTemp', dims = StoA('lon', 'lat'), longname = 'Surface Temperature', units = 'K', xtype = 'double' )               ! (in)
  call HistoryAddAttr( history = gthist_sst, varname = 'SurfTemp', attrname = 'standard_name', value = 'surface_temperature' )                     ! (in)

  !----------------------------------------------------------------
  !  地表面データファイルへのデータ出力
  !  Surface data output
  !----------------------------------------------------------------
  call HistoryPut( history = gthist_sst, varname = 'SurfTemp', array = xy_SurfTemp ) ! (in)

  !----------------------------------------------------------------
  !  地表面データファイルへのデータ出力の終了処理
  !  Terminate surface data output
  !----------------------------------------------------------------
  call HistoryClose( history = gthist_sst )  ! (inout)

  call DCClockStop(clk_histput)   ! (inout)

  !----------------------------------------------------------------
  !  ファイル出力に関してメッセージを表示
  !  Print message of file output
  !----------------------------------------------------------------
  call MessageNotify( 'M', subname, 'Surface data file "%c" is generated.', c1=trim(sst_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 surface data file. ' // 'By default, the filename is "' // trim(sst_nc) // '", and ' // 'the resolution is T' // trim(toChar(nmax)) // '. ' // 'In order to change the settings, use NAMELIST file. ' // 'Some samples are prepared as sst_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 sst_sample

Private Instance methods

Subroutine :

コマンドライン引数の処理を行います

Handle command line options

[Source]

  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 surface data file. ' // 'By default, the filename is "' // trim(sst_nc) // '", and ' // 'the resolution is T' // trim(toChar(nmax)) // '. ' // 'In order to change the settings, use NAMELIST file. ' // 'Some samples are prepared as sst_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

[Validate]