Class restart_surftemp_io
In: io/restart_surftemp_io.f90

�域;�∽県綺����鴻�帥�若�����若��, �����ゃ���若�水�ュ�阪��

Restart data, initial data of surface temperature input/output

Note that Japanese and English are described in parallel.

�域;�∽県綺������鴻�帥�若�����若�帥������������ゃ���若�帥���ュ�阪����茵����障��. �ュ�����<�ゃ��, �阪�����<�ゃ��, ���若�帥���阪���������� NAMELIST#restart_surftemp_io_nml �ц┃絎����障��.

���鴻�帥�若�����若�帥���ュ�����<�ゃ������絎����������翫��, surface_data �≪�吾�ャ�若���х���������������ゃ���若�帥����緇����障��.

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

If input file of restart data is not set, initial data is generated in "surface_data" module, and obtained data from the module.

Procedures List

RestartSurfTempOpen :���鴻�帥�若�����<�ゃ�������若����
RestartSurfTempOutput :���鴻�帥�若�����<�ゃ���吾�����若�水�阪��
RestartSurfTempClose :���鴻�帥�若�����<�ゃ�������㏍�若��
RestartSurfTempGet :���鴻�帥�若�����<�ゃ�����ュ��
———— :————
RestartSurfTempOpen :Open restart file
RestartSurfTempOutput :Data output to restart file
RestartSurfTempClose :Close restart file
RestartSurfTempGet :Input restart file

NAMELIST

NAMELIST#restart_surftemp_io_nml

Methods

Included Modules

gridset dc_types dc_message gtool_history fileset constants0 axesset timeset dc_string dc_present surface_data netcdf_wrapper restart_file_io namelist_util dc_calendar dc_iounit

Public Instance methods

Subroutine :

���鴻�帥�若�����若�帥���<�ゃ���阪�����篋�������茵����障��.

Terminate restart data files output.

[Source]

  subroutine RestartSurfTempClose
    !
    ! ���鴻�帥�若�����若�帥���<�ゃ���阪�����篋�������茵����障��. 
    !
    ! Terminate restart data files output. 

    ! �≪�吾�ャ�若����� ; USE statements
    !

    ! gtool4 ���若�水�阪��
    ! Gtool4 data output
    !
    use gtool_history, only: HistoryClose

    ! 絎h��� ; Declaration statements
    !

    ! 篏�罐㊤���
    ! Work variables
    !

    ! 絎�茵��� ; Executable statement
    !
    if ( .not. restart_surftemp_opened ) return

    call HistoryClose( history = gthst_rst ) ! (inout)

    restart_surftemp_opened = .false.
  end subroutine RestartSurfTempClose
Subroutine :
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(out)
: �域;�∽県綺�. Surface temperature
xyz_SoilTemp(0:imax-1, 1:jmax, 1:kslmax) :real(DP), intent(out)
xy_SurfMajCompIceB(0:imax-1, 1:jmax) :real(DP), intent(out)
xy_SoilMoistB(0:imax-1, 1:jmax) :real(DP), intent(out)
xy_SurfSnowB(0:imax-1, 1:jmax) :real(DP), intent(out)
xy_SurfMajCompIceN(0:imax-1, 1:jmax) :real(DP), intent(out)
xy_SoilMoistN(0:imax-1, 1:jmax) :real(DP), intent(out)
xy_SurfSnowN(0:imax-1, 1:jmax) :real(DP), intent(out)

���鴻�帥�若�����若�帥���ュ����茵����障��. ���鴻�帥�若�����若�帥��絖����������翫������, surface_data �≪�吾�ャ�若����������, �域;�∽県綺����若�睡������茵����障��.

Input restart data. If restart data is not exist, surface temperature data is created by "surface_data".

[Source]

  subroutine RestartSurfTempGet( xy_SurfTemp, xyz_SoilTemp, xy_SurfMajCompIceB, xy_SoilMoistB, xy_SurfSnowB, xy_SurfMajCompIceN, xy_SoilMoistN, xy_SurfSnowN )
    !
    ! ���鴻�帥�若�����若�帥���ュ����茵����障��. 
    ! ���鴻�帥�若�����若�帥��絖����������翫������, 
    ! surface_data �≪�吾�ャ�若����������, �域;�∽県綺����若�睡������茵����障��. 
    !
    ! Input restart data. 
    ! If restart data is not exist, 
    ! surface temperature data is created by "surface_data". 


    ! �≪�吾�ャ�若����� ; USE statements
    !

    ! �域;�≪���若�炊�箴�
    ! Prepare surface data
    !
    use surface_data, only: SetSurfData

    ! ���紫���
    ! Time control
    !
    use timeset, only: RestartTime           ! ���鴻�帥�若����紮�����. 
                              ! Retart time of calculation

    ! gtool4 ���若�水�ュ��
    ! Gtool4 data input
    !
    use gtool_history, only: HistoryGet

    ! ��絖�����篏�
    ! Character handling
    !
    use dc_string, only: toChar

    ! NetCDF ���������若���㏍�違����
    ! NetCDF wrapper
    !
    use netcdf_wrapper, only: NWPresentAVarInFile


    ! 絎h��� ; Declaration statements
    !
    real(DP), intent(out) :: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! �域;�∽県綺�. 
                              ! Surface temperature
    real(DP), intent(out) :: xyz_SoilTemp (0:imax-1, 1:jmax, 1:kslmax)
    real(DP), intent(out) :: xy_SurfMajCompIceB(0:imax-1, 1:jmax)
    real(DP), intent(out) :: xy_SoilMoistB     (0:imax-1, 1:jmax)
    real(DP), intent(out) :: xy_SurfSnowB      (0:imax-1, 1:jmax)
    real(DP), intent(out) :: xy_SurfMajCompIceN(0:imax-1, 1:jmax)
    real(DP), intent(out) :: xy_SoilMoistN     (0:imax-1, 1:jmax)
    real(DP), intent(out) :: xy_SurfSnowN      (0:imax-1, 1:jmax)


    ! 篏�罐㊤���
    ! Work variables
    !
    character(TOKEN) :: time_range
                              ! ���祉����絎�. 
                              ! Specification of time
    logical          :: flag_mpi_init
    integer          :: k

    ! 絎�茵��� ; Executable statement
    !

    if ( .not. restart_surftemp_io_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if

    ! The variable name is fixed, 'SurfTemp' (yot, 2011/09/10).
!!$    if ( trim(InputFile) == '' .or. trim(InputName) == '' ) then
    if ( trim(InputFile) == '' ) then

      ! ���若�帥�� surface_data �≪�吾�ャ�若��������緇�
      ! Data is input from "surface_data" module
      !
      call SetSurfData( xy_SurfTemp = xy_SurfTemp )  ! (out) optional

      do k = 1, kslmax
        xyz_SoilTemp(:,:,k) = xy_SurfTemp
      end do

      xy_SurfMajCompIceB = 0.0_DP
      xy_SoilMoistB      = 0.0_DP
      xy_SurfSnowB       = 0.0_DP

      xy_SurfMajCompIceN = xy_SurfMajCompIceB
      xy_SoilMoistN      = xy_SoilMoistB
      xy_SurfSnowN       = xy_SurfSnowB

    else

      ! ���若�帥�� InputFile ������緇�
      ! Data is input from InputFile
      !

      ! ���紙���宴���緇�
      ! Get time information
      !
      time_range = time_name // '=' // toChar( RestartTime )

!!$      flag_mpi_init = .false.
      flag_mpi_init = .true.

      ! ���若�水�ュ��
      ! Data input
      ! 
      call HistoryGet( InputFile, 'SurfTemp', range = time_range, array = xy_SurfTemp, flag_mpi_split = flag_mpi_init )
      if ( kslmax /= 0 ) then
        if ( NWPresentAVarInFile( InputFile, 'SoilTemp' ) ) then
          call HistoryGet( InputFile, 'SoilTemp', range = time_range, array = xyz_SoilTemp, flag_mpi_split = flag_mpi_init )
        else
          do k = 1, kslmax
            xyz_SoilTemp(:,:,k) = xy_SurfTemp
          end do
          call MessageNotify( 'M', module_name, 'Variable, %c, cannot be found in file, %c.', c1 = 'SoilTemp', c2 = trim(InputFile) )
          call MessageNotify( 'M', module_name, 'Values in SoilTemp is assumed to be the same as SurfTemp.' )
        end if
      end if
      if ( NWPresentAVarInFile( InputFile, 'SurfMajCompIceB' ) ) then
        call HistoryGet( InputFile, 'SurfMajCompIceB', range = time_range, array = xy_SurfMajCompIceB, flag_mpi_split = flag_mpi_init )
      else
        xy_SurfMajCompIceB = 0.0_DP
        call MessageNotify( 'M', module_name, 'Variable, %c, cannot be found in file, %c.', c1 = 'SurfMajCompIceB', c2 = trim(InputFile) )
        call MessageNotify( 'M', module_name, 'Values in SurfMajCompIceB is assumed to be zero.' )
      end if
      if ( NWPresentAVarInFile( InputFile, 'SoilMoistB' ) ) then
        call HistoryGet( InputFile, 'SoilMoistB', range = time_range, array = xy_SoilMoistB, flag_mpi_split = flag_mpi_init )
      else
        xy_SoilMoistB = 0.0_DP
        call MessageNotify( 'M', module_name, 'Variable, %c, cannot be found in file, %c.', c1 = 'SoilMoistB', c2 = trim(InputFile) )
        call MessageNotify( 'M', module_name, 'Values in SoilMoistB is assumed to be zero.' )
      end if
      if ( NWPresentAVarInFile( InputFile, 'SurfSnowB' ) ) then
        call HistoryGet( InputFile, 'SurfSnowB', range = time_range, array = xy_SurfSnowB, flag_mpi_split = flag_mpi_init )
      else
        xy_SurfSnowB = 0.0_DP
        call MessageNotify( 'M', module_name, 'Variable, %c, cannot be found in file, %c.', c1 = 'SurfSnowB', c2 = trim(InputFile) )
        call MessageNotify( 'M', module_name, 'Values in SurfSnowB is assumed to be zero.' )
      end if
      if ( NWPresentAVarInFile( InputFile, 'SurfMajCompIceN' ) ) then
        call HistoryGet( InputFile, 'SurfMajCompIceN', range = time_range, array = xy_SurfMajCompIceN, flag_mpi_split = flag_mpi_init )
      else
        xy_SurfMajCompIceN = xy_SurfMajCompIceB
        call MessageNotify( 'M', module_name, 'Variable, %c, cannot be found in file, %c.', c1 = 'SurfMajCompIceN', c2 = trim(InputFile) )
        call MessageNotify( 'M', module_name, 'Values in SurfMajCompIceN is assumed to be the same as SurfMajCompIceB.' )
      end if
      if ( NWPresentAVarInFile( InputFile, 'SoilMoistN' ) ) then
        call HistoryGet( InputFile, 'SoilMoistN', range = time_range, array = xy_SoilMoistN, flag_mpi_split = flag_mpi_init )
      else
        xy_SoilMoistN = xy_SoilMoistB
        call MessageNotify( 'M', module_name, 'Variable, %c, cannot be found in file, %c.', c1 = 'SoilMoistN', c2 = trim(InputFile) )
        call MessageNotify( 'M', module_name, 'Values in SoilMoistN is assumed to be the same as SoilMoistB.' )
      end if
      if ( NWPresentAVarInFile( InputFile, 'SurfSnowN' ) ) then
        call HistoryGet( InputFile, 'SurfSnowN', range = time_range, array = xy_SurfSnowN, flag_mpi_split = flag_mpi_init )
      else
        xy_SurfSnowN = xy_SurfSnowB
        call MessageNotify( 'M', module_name, 'Variable, %c, cannot be found in file, %c.', c1 = 'SurfSnowN', c2 = trim(InputFile) )
        call MessageNotify( 'M', module_name, 'Values in SurfSnowN is assumed to be the same as SurfSnowB.' )
      end if

    end if

  end subroutine RestartSurfTempGet
Subroutine :

restart_surftemp_io �≪�吾�ャ�若������������茵����障��. NAMELIST#restart_surftemp_io_nml ����粋昭�帥��������膓����ц�����障��.

"restart_surftemp_io" module is initialized. "NAMELIST#restart_surftemp_io_nml" is loaded in this procedure.

This procedure input/output NAMELIST#restart_surftemp_io_nml .

[Source]

  subroutine RestartSurfTempInit
    !
    ! restart_surftemp_io �≪�吾�ャ�若������������茵����障��. 
    ! NAMELIST#restart_surftemp_io_nml ����粋昭�帥��������膓����ц�����障��. 
    !
    ! "restart_surftemp_io" module is initialized. 
    ! "NAMELIST#restart_surftemp_io_nml" is loaded in this procedure. 
    !

    ! �≪�吾�ャ�若����� ; USE statements
    !

    ! ���鴻�帥�若�����若�水�ュ�阪��
    ! Restart data input/output
    !
    use restart_file_io, only: restart_file_io_inited, RestartFileIntValue => IntValue, RestartFileIntUnit  => IntUnit
                              ! ���鴻�帥�若�����若�帥���阪����������篏�. 
                              ! Unit for interval of restart data output

    ! ���紫���
    ! Time control
    !
    use timeset, only: RestartTime           ! ���鴻�帥�若����紮�����. 
                              ! Retart time of calculation

    ! NAMELIST ���<�ゃ���ュ�����≪�������若���c������
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg

    ! �����ユ��������宴��
    ! Calendar and Date handler
    !
    use dc_calendar, only: DCCalConvertByUnit

    ! ���<�ゃ���ュ�阪��茖���
    ! File I/O support
    !
    use dc_iounit, only: FileOpen

    ! 腮��ュ�������<��
    ! Kind type parameter
    !
    use dc_types, only: STDOUT ! 罔�羣��阪�����臀����. Unit number of standard output

    ! 絎h��� ; Declaration statements
    !

    ! 篏�罐㊤���
    ! Work variables
    !
    integer:: unit_nml        ! NAMELIST ���<�ゃ�����若���括���臀����. 
                              ! Unit number for NAMELIST file open
    integer:: iostat_nml      ! NAMELIST 茯㏍�粋昭�炊���� IOSTAT. 
                              ! IOSTAT of NAMELIST read

    ! NAMELIST 紊��亥召
    ! NAMELIST group name
    !
    namelist /restart_surftemp_io_nml/ InputFile, OutputFile, IntValue, IntUnit
          !
          ! �����������ゃ���ゃ��������������膓� "restart_surftemp_io#RestartSurfTempInit" 
          ! ���純�若�鴻�潟�若�������с������. 
          !
          ! Refer to source codes in the initialization procedure
          ! "restart_surftemp_io#RestartSurfTempInit" for the default values. 
          !


    ! 絎�茵��� ; Executable statement
    !

    if ( restart_surftemp_io_inited ) return


    ! �����������ゃ��┃絎�
    ! Default values settings
    !
    InputFile  = ''
    ! The variable name is fixed, 'SurfTemp' (yot, 2011/09/10).
!!$    InputName  = 'SurfTemp'
    if ( .not. flag_init_data_save ) then
      OutputFile = 'rst_sst.nc'
    else
      OutputFile = 'sst.nc'
    end if

    if ( restart_file_io_inited ) then
      IntValue   = RestartFileIntValue
      IntUnit    = RestartFileIntUnit
    else
      IntValue   = 365.0_DP
      IntUnit    = 'day'
    end if

    ! 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_surftemp_io_nml, iostat = iostat_nml ) ! (out)
      close( unit_nml )

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

    ! �阪������������┃絎�
    ! Configure time interval of output
    !
    IntTime = DCCalConvertByUnit( IntValue, IntUnit, 'sec' ) ! (in)
    PrevOutputTime = RestartTime

    ! �����違��������
    ! Initialize flag
    !
    flag_output_end = .false.


    ! �医� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, 'Input:: ' )
    call MessageNotify( 'M', module_name, '  InputFile  = %c', c1 = trim(InputFile) )
    ! The variable name is fixed, 'SurfTemp' (yot, 2011/09/10).
!!$    call MessageNotify( 'M', module_name, '  InputName  = %c', c1 = trim(InputName) )
    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, '-- version = %c', c1 = trim(version) )

    restart_surftemp_io_inited = .true.

  end subroutine RestartSurfTempInit
Subroutine :
flag_init_data :logical, intent(in), optional
: �����ゃ���若�帥��篏��������翫����, ������違�� .true. ��筝����障��.

If initial data is created, give ".true." to this argument.

���鴻�帥�若�����<�ゃ�������若���潟���障��.

A restart file is opened.

[Source]

  subroutine RestartSurfTempOpen( flag_init_data )
    !
    ! ���鴻�帥�若�����<�ゃ�������若���潟���障��. 
    !
    ! 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 and mathematical constants settings
    !
    use constants0, only: PI                    ! $ \pi $.
                              ! �����. Circular constant

    ! 綺ф����若�粋┃絎�
    ! Axes data settings
    !
    use axesset, only: x_Lon, x_Lon_Weight, y_Lat, y_Lat_Weight, z_SSDepth
                              ! �遺����弱��鴻��訓��
                              ! subsurface grid at midpoint of layer

    ! ���紫���
    ! Time control
    !
    use timeset, only: DelTime, RestartTime           ! ���鴻�帥�若����紮�����. 
                              ! Retart time of calculation

    ! gtool4 ���若�水�阪��
    ! Gtool4 data output
    !
    use gtool_history, only: HistoryCreate, HistoryAddVariable, HistoryPut, HistoryAddAttr

    ! ��絖�����篏�
    ! Character handling
    !
    use dc_string, only: StoA, CPrintf, LChar

    ! 腟��粋昭�翠�∽�� PRESENT ���≦宍���∽��
    ! Extended functions of intrinsic function "PRESENT"
    !
    use dc_present, only: present_and_true

    ! 絎h��� ; Declaration statements
    !
    logical, intent(in), optional:: flag_init_data
                              ! �����ゃ���若�帥��篏��������翫����, 
                              ! ������違�� .true. ��筝����障��. 
                              ! 
                              ! If initial data is created, 
                              ! give ".true." to this argument. 

    ! 篏�罐㊤���
    ! Work variables
    !
    character(STRING):: title_msg
                              ! 茵������������<���祉�若��. 
                              ! Message added to title
    real(DP):: origin_time
                              ! 荐�膊���紮�����. 
                              ! Start time of calculation
    character(STRING):: time_unit
                              ! �ユ������篏�. Units of date and time

    logical:: flag_mpi_init

    ! 絎�茵��� ; Executable statement
    !

    ! ������
    ! Initialization
    !
    flag_init_data_save = present_and_true( flag_init_data )
    if ( .not. restart_surftemp_io_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if
    if ( restart_surftemp_opened ) return

    ! 茵������������<���祉�若�吾��┃絎�
    ! Configure message added to title
    !
    if ( .not. flag_init_data_save ) then
      title_msg = ' restart data of surface temperature'
    else
      title_msg = ' initial data of surface temperature'
    end if

    ! ���紙���宴���緇�
    ! Get time information
    !
    if ( .not. flag_init_data_save ) then
      origin_time = RestartTime + IntTime
    else
      origin_time = RestartTime
    end if

    time_unit = IntUnit

    flag_mpi_init = .true.

    ! ���鴻�帥�若�����<�ゃ�������若����
    ! Open a restart file
    !
    if ( kslmax /= 0 ) then
      call HistoryCreate( file = OutputFile, title = trim(FileTitle) // trim(title_msg), source = FileSource, institution = FileInstitution, dims = StoA( 'lon', 'lat', 'dep', time_name ), dimsizes = (/ imax, jmax, kslmax, 0 /), longnames = StoA( 'longitude', 'latitude', 'depth   ', time_name ), units = StoA( 'degree_east', 'degree_north', 'm           ', time_unit ), origind = origin_time, intervald = IntValue, flag_mpi_split = flag_mpi_init, history = gthst_rst )
    else
      call HistoryCreate( file = OutputFile, title = trim(FileTitle) // trim(title_msg), source = FileSource, institution = FileInstitution, dims = StoA( 'lon', 'lat', time_name ), dimsizes = (/ imax, jmax, 0 /), longnames = StoA( 'longitude', 'latitude', time_name ), units = StoA( 'degree_east', 'degree_north', time_unit ), xtypes = (/'double', 'double', 'double'/), origind = origin_time, intervald = IntValue, flag_mpi_split = flag_mpi_init, history = gthst_rst )
    end if

    ! 綺ф����若�帥��┃絎�
    ! Axes data settings
    !
    call HistoryAddAttr( varname = 'lon', attrname = 'standard_name', value = 'longitude', history = gthst_rst )
    call HistoryAddAttr( varname = 'lat', attrname = 'standard_name', value = 'latitude', history = gthst_rst )
    if ( kslmax /= 0 ) then
      call HistoryAddAttr( varname = 'dep', attrname = 'standard_name', value = 'depth', history = gthst_rst )
    end if
    call HistoryAddAttr( varname = time_name, attrname = 'standard_name', value = 'time', history = gthst_rst )

    call HistoryPut( varname = 'lon', array = x_Lon / PI * 180.0_DP, history = gthst_rst )
    call HistoryPut( varname = 'lat', array = y_Lat / PI * 180.0_DP, history = gthst_rst )
    if ( kslmax /= 0 ) then
      call HistoryPut( varname = 'dep', array = z_SSDepth, history = gthst_rst )
    end if

    ! 綺ф����帥��┃絎�
    ! 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)

    ! 篋��怨��違��┃絎�
    ! Predictional variables settings
    !
    call HistoryAddVariable( varname = 'SurfTemp', dims = StoA('lon', 'lat', time_name), longname = 'surface temperature', units = 'K', xtype = 'double', history = gthst_rst )
    if ( kslmax /= 0 ) then
      call HistoryAddVariable( varname = 'SoilTemp', dims = StoA('lon', 'lat', 'dep', time_name), longname = 'soil temperature', units = 'K', xtype = 'double', history = gthst_rst )
    end if
    call HistoryAddVariable( varname = 'SurfMajCompIceB', dims = StoA('lon', 'lat', time_name), longname = 'major component ice amount on the surface', units = 'kg m-2', xtype = 'double', history = gthst_rst )
    call HistoryAddVariable( varname = 'SoilMoistB', dims = StoA('lon', 'lat', time_name), longname = 'soil moisture', units = 'kg m-2', xtype = 'double', history = gthst_rst )
    call HistoryAddVariable( varname = 'SurfSnowB', dims = StoA('lon', 'lat', time_name), longname = 'snow amount on the surface', units = 'kg m-2', xtype = 'double', history = gthst_rst )
    call HistoryAddVariable( varname = 'SurfMajCompIceN', dims = StoA('lon', 'lat', time_name), longname = 'major component ice amount on the surface', units = 'kg m-2', xtype = 'double', history = gthst_rst )
    call HistoryAddVariable( varname = 'SoilMoistN', dims = StoA('lon', 'lat', time_name), longname = 'soil moisture', units = 'kg m-2', xtype = 'double', history = gthst_rst )
    call HistoryAddVariable( varname = 'SurfSnowN', dims = StoA('lon', 'lat', time_name), longname = 'snow amount on the surface', units = 'kg m-2', xtype = 'double', history = gthst_rst )

    restart_surftemp_opened = .true.
  end subroutine RestartSurfTempOpen
Subroutine :
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(in)
: �域;�∽県綺�. Surface temperature
xyz_SoilTemp(0:imax-1, 1:jmax, 1:kslmax) :real(DP), intent(in), optional
xy_SurfMajCompIceB(0:imax-1, 1:jmax) :real(DP), intent(in), optional
xy_SoilMoistB(0:imax-1, 1:jmax) :real(DP), intent(in), optional
xy_SurfSnowB(0:imax-1, 1:jmax) :real(DP), intent(in), optional
xy_SurfMajCompIceN(0:imax-1, 1:jmax) :real(DP), intent(in), optional
xy_SoilMoistN(0:imax-1, 1:jmax) :real(DP), intent(in), optional
xy_SurfSnowN(0:imax-1, 1:jmax) :real(DP), intent(in), optional

���鴻�帥�若�����若�帥���阪����茵����障��.

Output restart data

[Source]

  subroutine RestartSurfTempOutput( xy_SurfTemp, xyz_SoilTemp, xy_SurfMajCompIceB, xy_SoilMoistB, xy_SurfSnowB, xy_SurfMajCompIceN, xy_SoilMoistN, xy_SurfSnowN )
    !
    ! ���鴻�帥�若�����若�帥���阪����茵����障��. 
    !
    ! Output restart data

    ! �≪�吾�ャ�若����� ; USE statements
    !

    ! gtool4 ���若�水�阪��
    ! Gtool4 data output
    !
    use gtool_history, only: HistoryPut, HistorySetTime

    ! ���紫���
    ! Time control
    !
    use timeset, only: TimeN, EndTime               ! 荐�膊�腟�篋�����. 
                              ! End time of calculation

    ! 腟��粋昭�翠�∽�� PRESENT ���≦宍���∽��
    ! Extended functions of intrinsic function "PRESENT"
    !
    use dc_present, only: present_and_true

    ! 絎h��� ; Declaration statements
    !
    real(DP), intent(in)           :: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! �域;�∽県綺�. 
                              ! Surface temperature
    real(DP), intent(in), optional :: xyz_SoilTemp      (0:imax-1, 1:jmax, 1:kslmax)
    real(DP), intent(in), optional :: xy_SurfMajCompIceB(0:imax-1, 1:jmax)
    real(DP), intent(in), optional :: xy_SoilMoistB     (0:imax-1, 1:jmax)
    real(DP), intent(in), optional :: xy_SurfSnowB      (0:imax-1, 1:jmax)
    real(DP), intent(in), optional :: xy_SurfMajCompIceN(0:imax-1, 1:jmax)
    real(DP), intent(in), optional :: xy_SoilMoistN     (0:imax-1, 1:jmax)
    real(DP), intent(in), optional :: xy_SurfSnowN      (0:imax-1, 1:jmax)

    ! 篏�罐㊤���
    ! Work variables
    !
    logical:: flag_output
                              ! �阪����������. 
                              ! Flag for output

    ! 絎�茵��� ; Executable statement
    !

    if ( .not. restart_surftemp_opened ) call RestartSurfTempOpen

    ! �阪���帥�ゃ���潟�違�����с����
    ! Check output timing
    !
    flag_output = TimeN - PrevOutputTime >= IntTime
    if ( TimeN >= EndTime .and. .not. flag_output_end ) then
      flag_output = .true.
      flag_output_end = .true.
    end if
    flag_output = ( .not. TimeN == PrevOutputTime ) .and. flag_output
    flag_output = flag_init_data_save .or. flag_output

    if ( .not. flag_output ) return

    ! 罨≦������, 篁������阪�� (絽���) ���� ��篆�絖�
    ! Save output time (expected) in this time, for next time
    !
    PrevOutputTime = PrevOutputTime + IntTime

    ! ���祉��┃絎�
    ! Set time
    !
    call HistorySetTime( timed = TimeN, history = gthst_rst )

    ! ���若�水�阪��
    ! Data output
    !
    call HistoryPut( 'SurfTemp'  , xy_SurfTemp  , history = gthst_rst ) ! (in)
    if ( present( xyz_SoilTemp ) ) then
      if ( kslmax /= 0 ) then
        call HistoryPut( 'SoilTemp'  , xyz_SoilTemp , history = gthst_rst ) ! (in)
      end if
    end if
    if ( present( xy_SurfMajCompIceB ) ) then
      call HistoryPut( 'SurfMajCompIceB', xy_SurfMajCompIceB, history = gthst_rst ) ! (in)
    end if
    if ( present( xy_SoilMoistB ) ) then
      call HistoryPut( 'SoilMoistB', xy_SoilMoistB, history = gthst_rst ) ! (in)
    end if
    if ( present( xy_SurfSnowB ) ) then
      call HistoryPut( 'SurfSnowB' , xy_SurfSnowB , history = gthst_rst ) ! (in)
    end if
    if ( present( xy_SurfMajCompIceN ) ) then
      call HistoryPut( 'SurfMajCompIceN', xy_SurfMajCompIceN, history = gthst_rst ) ! (in)
    end if
    if ( present( xy_SoilMoistN ) ) then
      call HistoryPut( 'SoilMoistN', xy_SoilMoistN, history = gthst_rst ) ! (in)
    end if
    if ( present( xy_SurfSnowN ) ) then
      call HistoryPut( 'SurfSnowN' , xy_SurfSnowN , history = gthst_rst ) ! (in)
    end if

  end subroutine RestartSurfTempOutput
restart_surftemp_io_inited
Variable :
restart_surftemp_io_inited = .false. :logical, save, public
: ����荐㊤�������. Initialization flag
restart_surftemp_opened
Variable :
restart_surftemp_opened = .false. :logical, save, public
: ���鴻�帥�若�����<�ゃ�������若���潟���≪����������. Flag of restart file open

Private Instance methods

InputFile
Variable :
InputFile :character(STRING), save
: �ュ���������鴻�帥�若�����若�帥�����<�ゃ���� Filename of input restart data
IntTime
Variable :
IntTime :real(DP), save
: ���鴻�帥�若�����若�帥���阪������. Time 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
PrevOutputTime
Variable :
PrevOutputTime :real(DP), save
: �������阪������. Previous output time
deltime_name
Constant :
deltime_name = ‘deltime‘ :character(*), parameter
: �t ����医�� Variable name of Delta t
flag_init_data_save
Variable :
flag_init_data_save :logical, save
: �����ゃ���若�帥��篏��������翫����, ������違�� .true. ��筝����障��.

If initial data is created, give ".true." to this argument.

flag_output_end
Variable :
flag_output_end :logical, save
: 荐�膊���腟����祉���阪��絎�篋���������. Flag for completion of output at the end time of calculation
gthst_rst
Variable :
gthst_rst :type(GT_HISTORY), save
: ���鴻�帥�若�����若�睡�� gtool_history#GT_HISTORY 紊��� "gtool_history#GT_HISTORY" variable for restart data
module_name
Constant :
module_name = ‘restart_surftemp_io :character(*), parameter
: �≪�吾�ャ�若������腱�. Module name
time_name
Constant :
time_name = ‘time‘ :character(*), parameter
: ���祉���������医�� Variable name of time dimension
version
Constant :
version = ’$Name: $’ // ’$Id: restart_surftemp_io.f90,v 1.11 2014/05/07 09:39:18 murashin Exp $’ :character(*), parameter
: �≪�吾�ャ�若�������若�吾�с�� Module version