Class restart_file_io
In: io/restart_file_io.f90

リスタートデータ入出力

Restart data input/output

Note that Japanese and English are described in parallel.

リスタートデータの入出力を行います. 入力ファイル, 出力ファイル, データの出力の間隔は NAMELIST#restart_file_io_nml で設定します.

リスタートデータの入力ファイルが指定されない場合, initial_data モジュールから初期値データを取得します.

Restart data is input/output. Settings of input file, output file, and interval of data output is configured by "NAMELIST#restart_file_io_nml".

If input file of restart data is not set, initial data is obtained from "initial_data" module.

Procedures List

RestartFileOpen :リスタートファイルのオープン
RestartFileOutput :リスタートファイルへのデータ出力
RestartFileClose :リスタートファイルのクローズ
RestartFileGet :リスタートファイルの入力
———— :————
RestartFileOpen :Open restart file
RestartFileOutput :Data output to restart file
RestartFileClose :Close restart file
RestartFileGet :Input restart file

NAMELIST

NAMELIST#restart_file_io_nml

Methods

Included Modules

gridset dc_types dc_message gt4_history fileset constants axesset timeset dc_string initial_data namelist_util dc_iounit

Public Instance methods

Subroutine :

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

Terminate restart data files output.

[Source]

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

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

    ! gtool4 データ出力
    ! Gtool4 data output
    !
    use gt4_history, only: HistoryClose

    ! 宣言文 ; Declaration statements
    !
    implicit none

    ! 作業変数
    ! Work variables
    !

    ! 実行文 ; Executable statement
    !
    if ( .not. restart_file_opened ) return

    call HistoryClose( history = gthst_rst ) ! (inout)

    restart_file_opened = .false.
  end subroutine RestartFileClose
Subroutine :
xyz_UB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ u (t-\Delta t) $ . 東西風速. Eastward wind
xyz_VB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ v (t-\Delta t) $ . 南北風速. Northward wind
xyz_TempB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ T (t-\Delta t) $ . 温度. Temperature
xyz_QVapB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ q (t-\Delta t) $ . 比湿. Specific humidity
xy_PsB(0:imax-1, 1:jmax) :real(DP), intent(out)
: $ p_s (t-\Delta t) $ . 地表面気圧. Surface pressure
xyz_UN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ u (t) $ . 東西風速. Eastward wind
xyz_VN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ v (t) $ . 南北風速. Northward wind
xyz_TempN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ T (t) $ . 温度. Temperature
xyz_QVapN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ q (t) $ . 比湿. Specific humidity
xy_PsN(0:imax-1, 1:jmax) :real(DP), intent(out)
: $ p_s (t) $ . 地表面気圧. Surface pressure

リスタートデータの入力を行います.

Input restart data

[Source]

  subroutine RestartFileGet( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN )
    !
    ! リスタートデータの入力を行います. 
    !
    ! Input restart data

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

    ! 初期値データ (リスタートデータ) 提供
    ! Prepare initial data (restart data)
    !
    use initial_data, only: InitDataGet

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

    ! gtool4 データ入力
    ! Gtool4 data input
    !
    use gt4_history, only: HistoryGet

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

    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(out):: xyz_UB  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ u (t-\Delta t) $ .   東西風速. Eastward wind
    real(DP), intent(out):: xyz_VB  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ v (t-\Delta t) $ .   南北風速. Northward wind
    real(DP), intent(out):: xyz_TempB  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T (t-\Delta t) $ .   温度. Temperature
    real(DP), intent(out):: xyz_QVapB  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q (t-\Delta t) $ .   比湿. Specific humidity
    real(DP), intent(out):: xy_PsB (0:imax-1, 1:jmax)
                              ! $ p_s (t-\Delta t) $ . 地表面気圧. Surface pressure
    real(DP), intent(out):: xyz_UN  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ u (t) $ .     東西風速. Eastward wind
    real(DP), intent(out):: xyz_VN  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ v (t) $ .     南北風速. Northward wind
    real(DP), intent(out):: xyz_TempN  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T (t) $ .     温度. Temperature
    real(DP), intent(out):: xyz_QVapN  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q (t) $ .     比湿. Specific humidity
    real(DP), intent(out):: xy_PsN (0:imax-1, 1:jmax)
                              ! $ p_s (t) $ .   地表面気圧. Surface pressure

    ! 作業変数
    ! Work variables
    !
    real(DP):: start_time
                              ! 計算開始時刻
                              ! Start time of calculation
    character(TOKEN):: time_range
                              ! 時刻の指定
                              ! Specification of time

    ! 実行文 ; Executable statement
    !

    if ( .not. restart_file_io_inited ) call RestartFileInit

    ! データを initial_data モジュールから取得
    ! Data is input from "initial_data" module
    ! 
    if ( trim(InputFile) == '' ) then
      call InitDataGet( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN )   ! (out)

    ! データを InputFile から取得
    ! Data is input from InputFile
    ! 
    else

      ! 時刻情報の取得
      ! Get time information
      !
      call TimesetGetStartTime( start_time ) ! (out)
      time_range = 'time=' // toChar( start_time )

      ! データ入力
      ! Data input
      ! 
      call HistoryGet( InputFile, 'UB', range = time_range, array = xyz_UB )                        ! (out)
      call HistoryGet( InputFile, 'VB', range = time_range, array = xyz_VB )                        ! (out)
      call HistoryGet( InputFile, 'TempB', range = time_range, array = xyz_TempB )                        ! (out)
      call HistoryGet( InputFile, 'QVapB', range = time_range, array = xyz_QVapB )                        ! (out)
      call HistoryGet( InputFile, 'PsB', range = time_range, array = xy_PsB )                         ! (out)

      call HistoryGet( InputFile, 'UN', range = time_range, array = xyz_UN )                        ! (out)
      call HistoryGet( InputFile, 'VN', range = time_range, array = xyz_VN )                        ! (out)
      call HistoryGet( InputFile, 'TempN', range = time_range, array = xyz_TempN )                        ! (out)
      call HistoryGet( InputFile, 'QVapN', range = time_range, array = xyz_QVapN )                        ! (out)
      call HistoryGet( InputFile, 'PsN', range = time_range, array = xy_PsN )                         ! (out)

    end if

  end subroutine RestartFileGet
Subroutine :

リスタートファイルをオープンします.

A restart file is opened.

[Source]

  subroutine RestartFileOpen
    !
    ! リスタートファイルをオープンします. 
    !
    ! A restart file is opened. 
    !

    ! モジュール引用 ; 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: x_Lon, x_Lon_Weight, y_Lat, y_Lat_Weight, z_Sigma, r_Sigma, z_DelSigma
                              ! $ \Delta \sigma $ (整数). 
                              ! $ \Delta \sigma $ (Full)

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

    ! gtool4 データ出力
    ! Gtool4 data output
    !
    use gt4_history, only: HistoryCreate, HistoryAddVariable, HistoryPut, HistoryAddAttr

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

    ! 宣言文 ; Declaration statements
    !
    implicit none

    ! 作業変数
    ! Work variables
    !
    real(DP):: origin_time
                              ! 計算開始時刻. 
                              ! Start time of calculation

    ! 実行文 ; Executable statement
    !

    ! 初期化
    ! Initialization
    !
    if ( .not. restart_file_io_inited ) call RestartFileInit
    if ( restart_file_opened ) return

    ! 時刻情報の取得
    ! Get time information
    !
    call TimesetGetStartTime( origin_time, IntUnit )

    ! リスタートファイルのオープン
    ! Open a restart file
    !
    call HistoryCreate( file = OutputFile, title = trim(FileTitle) // ' restart data', source = FileSource, institution = FileInstitution, dims = StoA( 'lon', 'lat', 'sig', 'sigm', 'time' ), dimsizes = (/ imax, jmax, kmax, kmax + 1, 0 /), longnames = StoA( 'longitude', 'latitude', 'sigma at layer midpoints', 'sigma at layer end-points (half level)', 'time' ), units = StoA( 'degree_east', 'degree_north', '1', '1', IntUnit ), origin = real( origin_time ), interval = real( IntValue ), history = gthst_rst )                                    ! (out)

    ! $ \Delta t $ に関する情報を追加
    ! Add information about $ \Delta t $
    !
    call HistoryAddVariable( varname = 'deltime', dims = StoA(''), longname = 'delta time', units = 's', xtype = 'float', history = gthst_rst )             ! (inout)
    call HistoryPut( varname = 'deltime', array = (/ DelTime /), history = gthst_rst )             ! (inout)

    ! 座標データの設定
    ! Axes data settings
    !
    call HistoryAddAttr( varname = 'lon', attrname = 'standard_name', value = 'longitude', history = gthst_rst )                            ! (inout)
    call HistoryAddAttr( varname = 'lat', attrname = 'standard_name', value = 'latitude', history = gthst_rst )                            ! (inout)
    call HistoryAddAttr( varname = 'sig', attrname = 'standard_name', value = 'atmosphere_sigma_coordinate', history = gthst_rst )                            ! (inout)
    call HistoryAddAttr( varname = 'sigm', attrname = 'standard_name', value = 'atmosphere_sigma_coordinate', history = gthst_rst )                            ! (inout)
    call HistoryAddAttr( varname = 'time', attrname = 'standard_name', value = 'time', history = gthst_rst )                            ! (inout)
    call HistoryAddAttr( varname = 'sig', attrname = 'positive', value = 'down', history = gthst_rst )                            ! (inout)
    call HistoryAddAttr( varname = 'sigm', attrname = 'positive', value = 'down', history = gthst_rst )                            ! (inout)

    call HistoryPut( varname = 'lon', array = x_Lon / PI * 180.0_DP, history = gthst_rst )            ! (inout)
    call HistoryPut( varname = 'lat', array = y_Lat / PI * 180.0_DP, history = gthst_rst )            ! (inout)
    call HistoryPut( varname = 'sig', array = z_Sigma, history = gthst_rst )            ! (inout)
    call HistoryPut( varname = 'sigm', array = r_Sigma, history = gthst_rst )            ! (inout)

    ! 座標重みの設定
    ! Axes weights settings
    !
    call HistoryAddVariable( varname = 'lon_weight', dims = StoA('lon'), longname = 'weight for integration in longitude', units = 'radian', xtype = 'double', history = gthst_rst )                               ! (inout)
    call HistoryAddAttr( varname = 'lon', attrname = 'gt_calc_weight', value = 'lon_weight', history = gthst_rst )                               ! (inout)
    call HistoryPut( varname = 'lon_weight', array = x_Lon_Weight, history = gthst_rst )                               ! (inout)

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

    call HistoryAddVariable( varname = 'sig_weight', dims = StoA('sig'), longname = 'weight for integration in sigma', units = '1', xtype = 'double', history = gthst_rst )                               ! (inout)
    call HistoryAddAttr( varname = 'sig', attrname = 'gt_calc_weight', value = 'sig_weight', history = gthst_rst )                               ! (inout)
    call HistoryPut( varname = 'sig_weight', array = z_DelSigma, history = gthst_rst )                               ! (inout)

    ! 予報変数の設定
    ! Predictional variables settings
    !
    call HistoryAddVariable( varname = 'UB', dims = StoA('lon', 'lat', 'sig', 'time'), longname = 'eastward wind (at t-\Delta t)', units = 'm s-1', xtype = 'double', history = gthst_rst )                               ! (inout)
    call HistoryAddVariable( varname = 'VB', dims = StoA('lon', 'lat', 'sig', 'time'), longname = 'northward wind (at t-\Delta t)', units = 'm s-1', xtype = 'double', history = gthst_rst )                               ! (inout)
    call HistoryAddVariable( varname = 'TempB', dims = StoA('lon', 'lat', 'sig', 'time'), longname = 'temperature (at t-\Delta t)', units = 'K', xtype = 'double', history = gthst_rst )                               ! (inout)
    call HistoryAddVariable( varname = 'QVapB', dims = StoA('lon', 'lat', 'sig', 'time'), longname = 'specific humidity (at t-\Delta t)', units = 'kg kg-1', xtype = 'double', history = gthst_rst )                               ! (inout)
    call HistoryAddVariable( varname = 'PsB', dims = StoA('lon', 'lat', 'time'), longname = 'surface pressure (at t-\Delta t)', units = 'Pa', xtype = 'double', history = gthst_rst )                               ! (inout)

    call HistoryAddVariable( varname = 'UN', dims = StoA('lon', 'lat', 'sig', 'time'), longname = 'eastward wind (at t)', units = 'm s-1', xtype = 'double', history = gthst_rst )                               ! (inout)
    call HistoryAddVariable( varname = 'VN', dims = StoA('lon', 'lat', 'sig', 'time'), longname = 'northward wind (at t)', units = 'm s-1', xtype = 'double', history = gthst_rst )                               ! (inout)
    call HistoryAddVariable( varname = 'TempN', dims = StoA('lon', 'lat', 'sig', 'time'), longname = 'temperature (at t)', units = 'K', xtype = 'double', history = gthst_rst )                               ! (inout)
    call HistoryAddVariable( varname = 'QVapN', dims = StoA('lon', 'lat', 'sig', 'time'), longname = 'specific humidity (at t)', units = 'kg kg-1', xtype = 'double', history = gthst_rst )                               ! (inout)
    call HistoryAddVariable( varname = 'PsN', dims = StoA('lon', 'lat', 'time'), longname = 'surface pressure (at t)', units = 'Pa', xtype = 'double', history = gthst_rst )                               ! (inout)

    restart_file_opened = .true.
  end subroutine RestartFileOpen
Subroutine :
xyz_UB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ u (t-\Delta t) $ . 東西風速. Eastward wind
xyz_VB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ v (t-\Delta t) $ . 南北風速. Northward wind
xyz_TempB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ T (t-\Delta t) $ . 温度. Temperature
xyz_QVapB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ q (t-\Delta t) $ . 比湿. Specific humidity
xy_PsB(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ p_s (t-\Delta t) $ . 地表面気圧. Surface pressure
xyz_UN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ u (t) $ . 東西風速. Eastward wind
xyz_VN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ v (t) $ . 南北風速. Northward wind
xyz_TempN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ T (t) $ . 温度. Temperature
xyz_QVapN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ q (t) $ . 比湿. Specific humidity
xy_PsN(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ p_s (t) $ . 地表面気圧. Surface pressure

リスタートデータの出力を行います.

Output restart data

[Source]

  subroutine RestartFileOutput( xyz_UB, xyz_VB, xyz_TempB, xyz_QVapB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyz_QVapN, xy_PsN )
    !
    ! リスタートデータの出力を行います. 
    !
    ! Output restart data

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

    ! gtool4 データ出力
    ! Gtool4 data output
    !
    use gt4_history, only: HistoryPut

    ! 時刻管理
    ! Time control
    !
    use timeset, only: Cstep  ! 現在のステップ数. 
                              ! Current steps

    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xyz_UB  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ u (t-\Delta t) $ .   東西風速. Eastward wind
    real(DP), intent(in):: xyz_VB  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ v (t-\Delta t) $ .   南北風速. Northward wind
    real(DP), intent(in):: xyz_TempB  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T (t-\Delta t) $ .   温度. Temperature
    real(DP), intent(in):: xyz_QVapB  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q (t-\Delta t) $ .   比湿. Specific humidity
    real(DP), intent(in):: xy_PsB (0:imax-1, 1:jmax)
                              ! $ p_s (t-\Delta t) $ . 地表面気圧. Surface pressure
    real(DP), intent(in):: xyz_UN  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ u (t) $ .     東西風速. Eastward wind
    real(DP), intent(in):: xyz_VN  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ v (t) $ .     南北風速. Northward wind
    real(DP), intent(in):: xyz_TempN  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T (t) $ .     温度. Temperature
    real(DP), intent(in):: xyz_QVapN  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q (t) $ .     比湿. Specific humidity
    real(DP), intent(in):: xy_PsN (0:imax-1, 1:jmax)
                              ! $ p_s (t) $ .   地表面気圧. Surface pressure

    ! 作業変数
    ! Work variables
    !


    ! 実行文 ; Executable statement
    !

    if ( .not. restart_file_opened ) call RestartFileOpen

    ! 出力タイミングのチェック
    ! Check output timing
    !
    if ( mod( Cstep - 1, IntStep ) /= 0 ) return

    ! データ出力
    ! Data output
    !
    call HistoryPut( 'UB', xyz_UB, history = gthst_rst ) ! (in)
    call HistoryPut( 'VB', xyz_VB, history = gthst_rst ) ! (in)
    call HistoryPut( 'TempB', xyz_TempB, history = gthst_rst ) ! (in)
    call HistoryPut( 'QVapB', xyz_QVapB, history = gthst_rst ) ! (in)
    call HistoryPut( 'PsB', xy_PsB, history = gthst_rst ) ! (in)

    call HistoryPut( 'UN', xyz_UN, history = gthst_rst ) ! (in)
    call HistoryPut( 'VN', xyz_VN, history = gthst_rst ) ! (in)
    call HistoryPut( 'TempN', xyz_TempN, history = gthst_rst ) ! (in)
    call HistoryPut( 'QVapN', xyz_QVapN, history = gthst_rst ) ! (in)
    call HistoryPut( 'PsN', xy_PsN, history = gthst_rst ) ! (in)

  end subroutine RestartFileOutput
restart_file_io_inited
Variable :
restart_file_io_inited = .false. :logical, save, public
: 初期設定フラグ. Initialization flag
restart_file_opened
Variable :
restart_file_opened = .false. :logical, save, public
: リスタートファイルのオープンに関するフラグ. Flag of restart file open

Private Instance methods

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

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: constants_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. constants_inited ) call MessageNotify( 'E', module_name, '"constants" 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
InputFile
Variable :
InputFile :character(STRING), save
: 入力するリスタートデータのファイル名 filename of input restart data
IntStep
Variable :
IntStep :integer
: リスタートデータの出力間隔ステップ数 Number of step of interval of restart data output
IntUnit
Variable :
IntUnit :character(TOKEN)
: リスタートデータの出力間隔の単位. Unit for interval of restart data output
IntValue
Variable :
IntValue :real(DP), save
: リスタートデータの出力間隔. Interval of restart data output
OutputFile
Variable :
OutputFile :character(STRING), save
: 出力するリスタートデータのファイル名 filename of output restart data
Subroutine :

restart_file_io モジュールの初期化を行います. NAMELIST#restart_file_io_nml の読み込みはこの手続きで行われます.

"restart_file_io" module is initialized. "NAMELIST#restart_file_io_nml" is loaded in this procedure.

This procedure input/output NAMELIST#restart_file_io_nml .

[Source]

  subroutine RestartFileInit
    !
    ! restart_file_io モジュールの初期化を行います. 
    ! NAMELIST#restart_file_io_nml の読み込みはこの手続きで行われます. 
    !
    ! "restart_file_io" module is initialized. 
    ! "NAMELIST#restart_file_io_nml" is loaded in this procedure. 
    !

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

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

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

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

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

    ! 宣言文 ; Declaration statements
    !
    implicit none

    ! 作業変数
    ! Work variables
    !
    integer:: unit_nml        ! NAMELIST ファイルオープン用装置番号. 
                              ! Unit number for NAMELIST file open
    integer:: iostat_nml      ! NAMELIST 読み込み時の IOSTAT. 
                              ! IOSTAT of NAMELIST read

    real(DP):: delta_time
                              ! $ \Delta t $

    ! NAMELIST 変数群
    ! NAMELIST group name
    !
    namelist /restart_file_io_nml/ InputFile, OutputFile, IntValue, IntUnit
          !
          ! デフォルト値については初期化手続 "restart_file_io#RestartFileInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "restart_file_io#RestartFileInit" for the default values. 
          !


    ! 実行文 ; Executable statement
    !

    if ( restart_file_io_inited ) return
    call InitCheck

    ! デフォルト値の設定
    ! Default values settings
    !
    InputFile  = ''
    OutputFile = 'restart.nc'
    IntValue   = 1.0_DP
    IntUnit    = 'day'

    ! NAMELIST の読み込み
    ! NAMELIST is input
    !
    if ( trim(namelist_filename) /= '' ) then
      call FileOpen( unit_nml, namelist_filename, mode = 'r' ) ! (in)

      rewind( unit_nml )
      read( unit_nml, nml = restart_file_io_nml, iostat = iostat_nml ) ! (out)
      close( unit_nml )

      call NmlutilMsg( iostat_nml, module_name ) ! (in)
      if ( iostat_nml == 0 ) write( STDOUT, nml = restart_file_io_nml )
    end if


    ! 出力ステップ数の算出
    ! Calculate number of step of output 
    !
    call TimesetGetDelTime( delta_time, IntUnit )

    IntStep = max( 1, nint( IntValue / delta_time ) )


    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, 'Input:: ' )
    call MessageNotify( 'M', module_name, '  InputFile  = %c', c1 = trim(InputFile) )
    call MessageNotify( 'M', module_name, 'Output:: ' )
    call MessageNotify( 'M', module_name, '  OutputFile = %c', c1 = trim(OutputFile) )
    call MessageNotify( 'M', module_name, '  IntTime    = %f [%c]', d = (/ IntValue /), c1 = trim(IntUnit) )
    call MessageNotify( 'M', module_name, '  IntStep    = %d', i = (/ IntStep /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    restart_file_io_inited = .true.
  end subroutine RestartFileInit
gthst_rst
Variable :
gthst_rst :type(GT_HISTORY), save
: リスタートデータ用 gt4_history#GT_HISTORY 変数 "gt4_history#GT_HISTORY" variable for restart data
module_name
Constant :
module_name = ‘restart_file_io :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: dcpam5-20080812 $’ // ’$Id: restart_file_io.f90,v 1.4 2008-08-11 21:51:02 morikawa Exp $’ :character(*), parameter
: モジュールのバージョン Module version

[Validate]