Class history_file_io
In: io/history_file_io.F90

ヒストリデータ出力

History data output

Note that Japanese and English are described in parallel.

ヒストリデータ出力の初期化, 時刻進行, 登録変数の表示と 終了処理を行います. [gt4f90io ライブラリ]{www.gfd-dennou.org/library/gtool4} の gtool_historyauto モジュールを用います.

各データの出力は, モデルの各プログラム内において, gtool_historyauto モジュールから提供される HistoryAutoAddVariable および HistoryAutoPut を用います.

Methods

Included Modules

gridset dc_types dc_message fileset constants axesset namelist_util timeset gtool_historyauto dc_iounit dc_date_types dc_date dc_string

Public Instance methods

Subroutine :

ヒストリデータファイル出力の終了処理を行います.

Terminate history data files output.

[Source]

  subroutine HistoryFileClose
    !
    ! ヒストリデータファイル出力の終了処理を行います. 
    !
    ! Terminate history data files output. 

    ! モジュール引用 ; USE statements
    !

    ! gtool4 netCDF データの入出力インターフェース (大規模モデル用)
    ! Interface of Input/Output of gtool4 netCDF data (For large models)
    !
    use gtool_historyauto, only: HistoryAutoClose

    ! 宣言文 ; Declaration statements
    !
    implicit none

    ! 作業変数
    ! Work variables
    !

    ! 実行文 ; Executable statement
    !

    call HistoryAutoClose

  end subroutine HistoryFileClose
Subroutine :

history_file_io モジュールの初期化を行います.

"history_file_io" module is initialized.

[Source]

  subroutine HistoryFileOpen
    !
    ! history_file_io モジュールの初期化を行います. 
    !
    !
    ! "history_file_io" module is initialized. 
    !
    !

    ! モジュール引用 ; USE statements
    !

    ! 出力ファイルの基本情報
    ! Basic information for output files
    ! 
    use fileset, only: FileTitle, FileSource, FileInstitution
                              ! データファイルを最終的に変更した組織/個人. 
                              ! Institution or person that changes data files for the last time

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: PI   ! $ \pi $ .
                              ! 円周率.  Circular constant

    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: #ifdef LIB_MPI y_Lat_wholeMPI, z_Sigma_wholeMPI, r_Sigma_wholeMPI, #endif x_Lon_Weight, y_Lat, y_Lat_Weight, z_Sigma, r_Sigma, z_DelSigma, w_Number
                              ! スペクトルデータの添字番号. 
                              ! Subscript of spectral data


    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg

    ! 時刻管理
    ! Time control
    !
    use timeset, only: StartTime, EndTime, StartDate, StartDateValid

    ! gtool4 netCDF データの入出力インターフェース (大規模モデル用)
    ! Interface of Input/Output of gtool4 netCDF data (For large models)
    !
    use gtool_historyauto, only: HistoryAutoCreate, HistoryAutoAddAttr, HistoryAutoAddWeight, HistoryAutoPutAxis, HistoryAutoPutAxisMPI

    ! ファイル入出力補助
    ! File I/O support
    !
    use dc_iounit, only: FileOpen

    ! 日付および時刻の取り扱い
    ! Date and time handler
    !
    use dc_date_types, only: DC_DIFFTIME
                              ! 日時の差を表現するデータ型. 
                              ! Data type for difference about date and time
    use dc_date, only: DCDiffTimeCreate

    ! 文字列操作
    ! Character handling
    !
    use dc_string, only: CPrintf

    ! 種別型パラメタ
    ! Kind type parameter
    !
    use dc_types, only: STDOUT ! 標準出力の装置番号. Unit number of standard output

    ! 宣言文 ; Declaration statements
    !
    implicit none

    ! 作業変数
    ! Work variables
    !
    type(DC_DIFFTIME):: DefaultInt
    logical:: flag_mpi_init
#ifdef LIB_MPI
    integer:: err_mpi
#endif

    ! 実行文 ; Executable statement
    !

    if ( history_file_io_inited ) return
    call InitCheck

    ! デフォルト値の設定
    ! Default values settings
    !
    DefaultIntValue = 1.0
    DefaultIntUnit  = 'day'
    DefaultFilePrefix = ''
!!$    DefaultIntValue = 1.0
!!$    DefaultIntUnit  = 'hrs'
!!$    DefaultFilePrefix = 'data01/'

    call DCDiffTimeCreate( DefaultInt, DefaultIntValue, DefaultIntUnit ) ! (in)

#ifdef LIB_MPI
    ! MPI における初期化が行われているかを確認する. 
    ! Confirm initialization of MPI
    !
    call MPI_Initialized(flag_mpi_init, err_mpi)
#else
    flag_mpi_init = .false.
#endif

    ! HistoryAutoCreate による初期化
    ! Initialization by "HistoryAutoCreate"
    !
    call HistoryAutoCreate( title = trim(FileTitle) // ' history data', source = FileSource, institution = FileInstitution, dims = (/ 'lon ', 'lat ', 'sig ', 'sigm', 'wn  ', 'time' /), dimsizes = (/ imax, jmax, kmax, kmax + 1, (nmax+1)**2, 0 /), longnames = (/ 'longitude                             ', 'latitude                              ', 'sigma at layer midpoints              ', 'sigma at layer end-points (half level)', 'subscript of spectral data            ', 'time                                  ' /), units = (/ 'degree_east ', 'degree_north', '1           ', '1           ', '1           ', DefaultIntUnit /), xtypes = (/ 'float', 'float', 'float', 'float', 'int  ', 'float' /), origin = StartTime, terminus = EndTime, interval = DefaultInt, origin_date = StartDate, origin_date_invalid = .not. StartDateValid, flag_mpi_gather = flag_mpi_init, file_prefix = DefaultFilePrefix, namelist_filename = namelist_filename )                ! (in) optional


    ! 座標データへの属性の設定
    ! Attributes of axes data settings
    !
    call HistoryAutoAddAttr( varname = 'lon', attrname = 'standard_name', value = 'longitude' )                            ! (in)
    call HistoryAutoAddAttr( varname = 'lat', attrname = 'standard_name', value = 'latitude' )                             ! (in)
    call HistoryAutoAddAttr( varname = 'sig', attrname = 'standard_name', value = 'atmosphere_sigma_coordinate' )          ! (in)
    call HistoryAutoAddAttr( varname = 'sigm', attrname = 'standard_name', value = 'atmosphere_sigma_coordinate' )          ! (in)
    call HistoryAutoAddAttr( varname = 'sig', attrname = 'positive', value = 'down' )                                 ! (in)
    call HistoryAutoAddAttr( varname = 'sigm', attrname = 'positive', value = 'down' )                                 ! (in)

    ! 座標データの設定
    ! Axes data settings
    !
    call HistoryAutoPutAxis( 'lon',  x_Lon / PI * 180.0_DP )  ! (in)
    call HistoryAutoPutAxis( 'lat',  y_Lat / PI * 180.0_DP )  ! (in)
    call HistoryAutoPutAxis( 'sig',  z_Sigma )                ! (in)
    call HistoryAutoPutAxis( 'sigm', r_Sigma )                ! (in)
    call HistoryAutoPutAxis( 'wn',   w_Number )               ! (in)

    ! 座標重みの設定
    ! Axes weights settings
    !
    call HistoryAutoAddWeight( dim = 'lon', weight = x_Lon_Weight, units = 'radian', xtype = 'double' )  ! (in) optional
    call HistoryAutoAddWeight( dim = 'lat', weight = y_Lat_Weight, units = 'radian', xtype = 'double' )  ! (in) optional
    call HistoryAutoAddWeight( dim = 'sig', weight = z_DelSigma, xtype = 'double' )                    ! (in) optional

#ifdef LIB_MPI
    ! MPI 使用時にファイルを一つに統合して出力するための情報の付与
    ! Add information for output to one file when MPI is used
    !
    call HistoryAutoPutAxisMPI( 'lon',  x_Lon_wholeMPI / PI * 180.0_DP )  ! (in)
    call HistoryAutoPutAxisMPI( 'lat',  y_Lat_wholeMPI / PI * 180.0_DP )  ! (in)
    call HistoryAutoPutAxisMPI( 'sig',  z_Sigma_wholeMPI )                ! (in)
    call HistoryAutoPutAxisMPI( 'sigm', r_Sigma_wholeMPI )                ! (in)
    call HistoryAutoPutAxisMPI( 'wn',   w_Number )                        ! (in)

#endif

    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    history_file_io_inited = .true.
  end subroutine HistoryFileOpen
history_file_io_inited
Variable :
history_file_io_inited = .false. :logical, save, public
: 初期設定フラグ. Initialization flag

Private Instance methods

DefaultFilePrefix
Variable :
DefaultFilePrefix :character(STRING)
: ヒストリデータのファイル名の接頭詞 (デフォルト値). Prefixes of history data filenames (default value)
DefaultIntUnit
Variable :
DefaultIntUnit :character(12), save
: ヒストリデータの出力間隔の単位 (デフォルト値). Unit for interval of history data output (default value)
DefaultIntValue
Variable :
DefaultIntValue :real, save
: ヒストリデータの出力間隔の数値 (デフォルト値). Numerical value for interval of history data output (default value)
Subroutine :

依存モジュールの初期化チェック

Check initialization of dependency modules

[Source]

  subroutine InitCheck
    !
    ! 依存モジュールの初期化チェック
    !
    ! Check initialization of dependency modules

    ! モジュール引用 ; USE statements
    !

    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_util_inited

    ! 出力ファイルの基本情報管理
    ! Management basic information for output files
    !
    use fileset, only: fileset_inited

    ! 格子点設定
    ! Grid points settings
    !
    use gridset, only: gridset_inited

    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: axesset_inited

    ! 時刻管理
    ! Time control
    !
    use timeset, only: timeset_inited

    ! 実行文 ; Executable statement
    !

    if ( .not. namelist_util_inited ) call MessageNotify( 'E', module_name, '"namelist_util" module is not initialized.' )

    if ( .not. fileset_inited ) call MessageNotify( 'E', module_name, '"fileset" module is not initialized.' )

    if ( .not. gridset_inited ) call MessageNotify( 'E', module_name, '"gridset" module is not initialized.' )

    if ( .not. axesset_inited ) call MessageNotify( 'E', module_name, '"axesset" module is not initialized.' )

    if ( .not. timeset_inited ) call MessageNotify( 'E', module_name, '"timeset" module is not initialized.' )

  end subroutine InitCheck
module_name
Constant :
module_name = ‘history_file_io :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: dcpam5-20090126 $’ // ’$Id: history_file_io.F90,v 1.3 2009-01-06 10:42:20 morikawa Exp $’ :character(*), parameter
: モジュールのバージョン Module version

[Validate]