Class restart_file_io
In: io/restart_file_io.f90

���¹ã�¿ã�¼ã�����¼ã��, �����¤ã���¼ã�¿å�¥å�ºå��

Restart data, initial data input/output

Note that Japanese and English are described in parallel.

���¹ã�¿ã�¼ã�����¼ã�¿ã������������¤ã���¼ã�¿ã���¥å�ºå����è¡����¾ã��. �¥å�����¡ã�¤ã��, �ºå�����¡ã�¤ã��, ���¼ã�¿ã���ºå���������� NAMELIST#restart_file_io_nml �§è¨­å®����¾ã��.

���¹ã�¿ã�¼ã�����¼ã�¿ã���¥å�����¡ã�¤ã������å®����������´å��, initial_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_file_io_nml".

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

Procedures List

RestartFileOpen :���¹ã�¿ã�¼ã��/�����¤ã���¡ã�¤ã�������¼ã����
RestartFileOutput :���¹ã�¿ã�¼ã��/�����¤ã���¡ã�¤ã���¸ã�����¼ã�¿å�ºå��
InitialFileOutput :�����¤ã���¡ã�¤ã���¸ã�����¼ã�¿å�ºå��
RestartFileClose :���¹ã�¿ã�¼ã��/�����¤ã���¡ã�¤ã�������­ã�¼ã��
RestartFileGet :���¹ã�¿ã�¼ã��/�����¤ã���¡ã�¤ã�����¥å��
———— :————
RestartFileOpen :Open restart/initial file
RestartFileOutput :Data output to restart/initial file
InitialFileOutput :Data output to initial file
RestartFileClose :Close restart/initial file
RestartFileGet :Input restart/initial file

NAMELIST

NAMELIST#restart_file_io_nml

Methods

Included Modules

gridset composition dc_types dc_message gtool_history fileset constants0 axesset timeset dc_calendar dc_string dc_present initial_data dc_iounit namelist_util

Public Instance methods

Subroutine :
xyz_U(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ u $ . �±è¥¿é¢���. Eastward wind
xyz_V(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ v $ . �������. Northward wind
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ T $ . æ¸�º¦. Temperature
xyzf_QMix(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(in)
: $ q $ . ��. Specific humidity
xy_Ps(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ p_s $ . �°è¡¨�¢æ���. Surface pressure

�����¤ã���¼ã�¿ã���ºå����è¡����¾ã��.

Output initial data

[Source]

  subroutine InitialFileOutput( xyz_U, xyz_V, xyz_Temp, xyzf_QMix, xy_Ps )
    !
    ! �����¤ã���¼ã�¿ã���ºå����è¡����¾ã��. 
    !
    ! Output initial data

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! ���»ç���
    ! Time control
    !
    use timeset, only: TimeN, EndTime, InitialDate           ! è¨�ç®���å§��¥æ��. 
                              ! Start date of calculation

    ! gtool4 ���¼ã�¿å�ºå��
    ! Gtool4 data output
    !
    use gtool_history, only: HistoryPut, HistorySetTime

    ! �����¥æ��������±ã��
    ! Calendar and Date handler
    !
    use dc_calendar, only: DCCalDateInquire

    ! çµ��¿è¾¼�¿é�¢æ�� PRESENT ���¡å¼µ���¢æ��
    ! Extended functions of intrinsic function "PRESENT"
    !
    use dc_present, only: present_and_true

    ! 宣�� ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xyz_U    (0:imax-1, 1:jmax, 1:kmax)
                              ! $ u $ .     �±è¥¿é¢���. Eastward wind
    real(DP), intent(in):: xyz_V    (0:imax-1, 1:jmax, 1:kmax)
                              ! $ v $ .     �������. Northward wind
    real(DP), intent(in):: xyz_Temp (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T $ .     æ¸�º¦. Temperature
    real(DP), intent(in):: xyzf_QMix(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ q $ .     ��. Specific humidity
    real(DP), intent(in):: xy_Ps    (0:imax-1, 1:jmax)
                              ! $ p_s $ .   �°è¡¨�¢æ���. Surface pressure

    ! �業��
    ! Work variables
    !
    character(STRING):: date_str        ! �¥æ����¹´���¥æ����ç§�å½¢å�. 
                                        ! Date with year-month-day hour:minute:second format
    integer          :: n


    ! ���� ; Executable statement
    !
    if ( .not. restart_file_opened ) call RestartFileOpen( flag_init_data = .true. )

    ! �����¤å�ºå���§ã�������������§ã����
    ! Check initial data output
    !
    if ( .not. flag_init_data_save ) then
      call MessageNotify( 'E', module_name, 'Now, restart data output mode.' )
    end if

    ! ���»ã��¨­å®�
    ! Set time
    !
    call HistorySetTime( timed = TimeN, history = gthst_rst )

    ! "TimeN" ��å¹´æ���¥æ����ç§�è¡�������� "datetime" å¤��°ã�¸å�ºå��
    ! Put "TimeN" on "datetime" variable with year-month-day hour:minute:second format
    !
    call DCCalDateInquire( date_str   = date_str, elapse_sec = TimeN, date       = InitialDate ) ! (in) optional

    call HistoryPut( 'datetime', date_str, history = gthst_rst )    ! (inout) optional

    ! ���¼ã�¿å�ºå��
    ! Data output
    !
    call HistoryPut( 'U', xyz_U, history = gthst_rst )       ! (in)
    call HistoryPut( 'V', xyz_V, history = gthst_rst )       ! (in)
    call HistoryPut( 'Temp', xyz_Temp, history = gthst_rst ) ! (in)
    do n = 1, ncmax
      call HistoryPut( a_QMixName(n), xyzf_QMix(:,:,:,n), history = gthst_rst ) ! (in)
    end do
    call HistoryPut( 'Ps', xy_Ps, history = gthst_rst )      ! (in)


  end subroutine InitialFileOutput
InputFile
Variable :
InputFile :character(STRING), save, public
: �¥å���������¹ã�¿ã�¼ã�����¼ã�¿ã�����¡ã�¤ã���� Filename of input restart data
IntTime
Variable :
IntTime :real(DP), save, public
: ���¹ã�¿ã�¼ã�����¼ã�¿ã���ºå������ [ç§�]. Interval of restart data output [sec]
IntUnit
Variable :
IntUnit :character(TOKEN), save, public
: ���¹ã�¿ã�¼ã�����¼ã�¿ã���ºå������ (��ä½�). Interval of restart data output (unit)
IntValue
Variable :
IntValue :real(DP), save, public
: ���¹ã�¿ã�¼ã�����¼ã�¿ã���ºå������ (�°å��). Interval of restart data output (numerical value)
OutputFile
Variable :
OutputFile :character(STRING), save, public
: �ºå���������¹ã�¿ã�¼ã�����¼ã�¿ã�����¡ã�¤ã���� Filename of output restart data
Subroutine :

���¹ã�¿ã�¼ã�����¼ã�¿ã���¡ã�¤ã���ºå�����äº�������è¡����¾ã��.

Terminate restart data files output.

[Source]

  subroutine RestartFileClose
    !
    ! ���¹ã�¿ã�¼ã�����¼ã�¿ã���¡ã�¤ã���ºå�����äº�������è¡����¾ã��. 
    !
    ! Terminate restart data files output. 

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! gtool4 ���¼ã�¿å�ºå��
    ! Gtool4 data output
    !
    use gtool_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
xyzf_QMixB(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :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
xyzf_QMixN(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(out)
: $ q (t) $ . ��. Specific humidity
xy_PsN(0:imax-1, 1:jmax) :real(DP), intent(out)
: $ p_s (t) $ . �°è¡¨�¢æ���. Surface pressure
flag_initial :logical , intent(out), optional
: ���¹ã�¿ã�¼ã�����¼ã�¿ã��読ã�¿è¾¼���´å������, .false. ��, �����¤ã���¼ã�¿ã��読ã�¿è¾¼���´å������ .true. ��è¿����¾ã��.

If restart data is loaded, .false. is returned. On the other hand, if initial data is loaded, .true. is returned.

���¹ã�¿ã�¼ã��/�����¤ã���¼ã�¿ã���¥å����è¡����¾ã��. ���¹ã�¿ã�¼ã��/�����¤ã���¼ã�¿ã���¡ã�¤ã����å­����������´å������, initial_data �¢ã�¸ã�¥ã�¼ã����������, �����¤ç������è¡����¾ã��.

Input restart/initial data. If a restart/initial data file is not exist, initial data is created by "initial_data".

[Source]

  subroutine RestartFileGet( xyz_UB, xyz_VB, xyz_TempB, xyzf_QMixB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyzf_QMixN, xy_PsN, flag_initial )
    !
    ! ���¹ã�¿ã�¼ã��/�����¤ã���¼ã�¿ã���¥å����è¡����¾ã��. 
    ! ���¹ã�¿ã�¼ã��/�����¤ã���¼ã�¿ã���¡ã�¤ã����å­����������´å������, 
    ! initial_data �¢ã�¸ã�¥ã�¼ã����������, �����¤ç������è¡����¾ã��. 
    !
    ! Input restart/initial data. 
    ! If a restart/initial data file is not exist, 
    ! initial data is created by "initial_data". 


    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! ���»ç���
    ! Time control
    !
    use timeset, only: DelTime               ! $ \Delta t $ [s]

    ! �����¤ã���¼ã�� (���¹ã�¿ã�¼ã�����¼ã��) ��ä¾�
    ! Prepare initial data (restart data)
    !
    use initial_data, only: SetInitData

    ! ���»ç���
    ! Time control
    !
    use timeset, only: TimesetSetInitialDate, TimesetSetTimeN, TimesetSetCalendar, RestartTime           ! ���¹ã�¿ã�¼ã����å§�����. 
                              ! Restart time of calculation

    ! gtool4 ���¼ã�¿å�¥å��
    ! Gtool4 data input
    !
    use gtool_history, only: HistoryGet, HistoryGetAttr

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

    ! ���¡ã�¤ã���¥å�ºå��è£���
    ! File I/O support
    !
    use dc_iounit, only: FileOpen


    ! 宣�� ; 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):: xyzf_QMixB  (0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ 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):: xyzf_QMixN  (0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ q (t) $ .     ��. Specific humidity
    real(DP), intent(out):: xy_PsN      (0:imax-1, 1:jmax)
                              ! $ p_s (t) $ .   �°è¡¨�¢æ���. Surface pressure
    logical , intent(out), optional:: flag_initial
                              ! ���¹ã�¿ã�¼ã�����¼ã�¿ã��読ã�¿è¾¼���´å������, 
                              ! .false. ��, �����¤ã���¼ã�¿ã��読ã�¿è¾¼���´å������
                              ! .true. ��è¿����¾ã��. 
                              ! 
                              ! If restart data is loaded, .false. is returned.
                              ! On the other hand, if initial data is loaded, 
                              ! .true. is returned. 

    ! �業��
    ! Work variables
    !
    integer:: flag_rst        ! �����¤ã���¼ã�¿ã�����¥å������ 0, 
                              ! ���¹ã�¿ã�¼ã�����¼ã�¿å�¥å������ 1. 
                              ! 
                              ! If initial data is input, this value is 0. 
                              ! If restart data is input, this value is 1.

    character(STRING):: time_range
                              ! ���»ã����å®�. 
                              ! Specification of time
    character(TOKEN):: dummy_str
                              ! �¥å�����§ã�������������¼å���
                              ! Dummy variable for check of input
    logical:: get_err
                              ! �¥å�����������¼ã������. 
                              ! Error flag for input
    real(DP):: returned_time
                              ! �¥å�����¼ã�¿ã������. 
                              ! Time of input data.
    logical:: flag_time_exist
                              ! �¥å�����¼ã�¿ã�����»ç����������. 
                              ! Flag for time of input data.

    integer:: origin_year, origin_month, origin_day, origin_hour, origin_min
                              ! è¨�ç®���å§���¹´���¥æ����. 
    real(DP):: origin_sec
                              ! ��������. 
    character(TOKEN):: cal_type
                              ! �����¿ã�¤ã��. 
    integer:: month_in_year, hour_in_day, min_in_hour
    integer, pointer:: day_in_month_ptr(:) => null()
    real(DP):: sec_in_min
                              ! �����細���
    real(DP):: rst_time
                              ! ���¹ã�¿ã�¼ã�����¼ã�¿ã���¡ã�¤ã������å¾����������»å���
                              ! Time variable from a restart data file

    logical:: flag_mpi_init

    integer :: n


    ! ���� ; Executable statement
    !

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

    ! ���¼ã�¿ã�� initial_data �¢ã�¸ã�¥ã�¼ã��������å¾�
    ! Data is input from "initial_data" module
    ! 
    if ( trim(InputFile) == '' ) then
      call SetInitData( xyz_UB, xyz_VB, xyz_TempB, xyzf_QMixB(:,:,:,IndexH2OVap), xy_PsB )   ! (out)

      ! The variables below are initialized here, temporarily. 
      !
      xyzf_QMixB(:,:,:,1:IndexH2OVap-1)     = 0.0_DP
      xyzf_QMixB(:,:,:,IndexH2OVap+1:ncmax) = 0.0_DP

      call MessageNotify( 'M', module_name, 'Initial data (not restart data) is input ' // 'from a module "initial_data". ' // '*B (t-dt) and *N (t) are same.' )

      xyz_UN     = xyz_UB
      xyz_VN     = xyz_VB
      xyz_TempN  = xyz_TempB
      xyzf_QMixN = xyzf_QMixB
      xy_PsN     = xy_PsB

      if ( present(flag_initial) ) flag_initial = .true.

    ! ���¼ã�¿ã�� InputFile ������å¾�
    ! Data is input from InputFile
    ! 
    else

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

      ! ���¡ã�¤ã�������¡ã��確è�
      ! Conform an existence of an input file
      ! 
      call HistoryGetAttr( InputFile, 'lon', 'units', dummy_str, flag_mpi_split = flag_mpi_init, err = get_err )                               ! (out)

      if ( get_err ) then
        call MessageNotify( 'E', module_name, 'restart/initial data file "%c" is not found.', c1 = trim(InputFile) )
      end if

      ! ���»æ���±ã���å¾�
      ! Get time information
      !
      time_range = 'time=' // toChar( RestartTime )

      ! �����¤ã���¼ã�¿ã�����¹ã�¿ã�¼ã�����¼ã�¿ã�������§ã����
      ! Check whether input data is initial data or restart data
      ! 
      call HistoryGet( InputFile, 'flag_rst', flag_rst, err = get_err, quiet = .true., flag_mpi_split = flag_mpi_init )        ! (in) optional

      if ( get_err ) then
        ! flag_rst å¤��°ã��読ã�¿è¾¼�������´å�������������������¤ã���¼ã�¿ã�������
        !
        flag_rst = 0
        if ( present(flag_initial) ) flag_initial = .true.

      else if ( flag_rst == 0 ) then
        if ( present(flag_initial) ) flag_initial = .true.

      else
        if ( present(flag_initial) ) flag_initial = .false.
      end if

      ! ��������¼ã�¿ã�����¡ã�����§ã���� ("U", "UB" ����)
      ! Check existence or nonexistence of physical data (only "U", "UB")
      ! 
      if ( flag_rst == 0 ) then
        call HistoryGet( InputFile, 'U', xyz_UB, err = get_err, quiet = .true., flag_mpi_split = flag_mpi_init )        ! (in) optional

        if ( get_err ) then
          call MessageNotify( 'E', module_name, 'One of necessary variables "U" for start of calculation ' // 'cannot be read from "%c"', c1 = trim(InputFile) )
        end if

      else

        call HistoryGet( InputFile, 'UB', xyz_UB, range = time_range, quiet = .true., err = get_err, returned_time = returned_time, flag_time_exist = flag_time_exist, flag_mpi_split = flag_mpi_init )        ! (in) optional

        if ( get_err ) then
          call MessageNotify( 'E', module_name, 'One of necessary variables "UB" for restart ' // 'cannot be read from "%c"', c1 = trim(InputFile) )
        end if
      end if

      ! �����¤ã���¼ã�¿ã���¥å�������´å����çµ��������� 0 ��¨­å®�
      ! Set 0 to elapsed time, when initial data is input
      !
      if ( flag_rst == 0 ) then
        call TimesetSetTimeN( 0.0_DP )
      end if

      ! ������å§��¥æ����çµ������»ã����¿è¾¼�¿ã����¸ã��設å�
      ! Input and overwrite calendar, start date, and elapsed time
      !
      if ( flag_rst /= 0 ) then

        ! ������¿è¾¼��
        ! Input calendar
        !
        call HistoryGetAttr( InputFile, 'time', 'calendar', cal_type, flag_mpi_split = flag_mpi_init )          ! (in) optional

        call HistoryGetAttr( InputFile, 'time', 'month_in_year', month_in_year, flag_mpi_split = flag_mpi_init )          ! (in) optional

        allocate( day_in_month_ptr(month_in_year) )
        call HistoryGetAttr( InputFile, 'time', 'day_in_month', day_in_month_ptr, flag_mpi_split = flag_mpi_init )          ! (in) optional

        call HistoryGetAttr( InputFile, 'time', 'hour_in_day', hour_in_day, flag_mpi_split = flag_mpi_init )          ! (in) optional

        call HistoryGetAttr( InputFile, 'time', 'min_in_hour', min_in_hour, flag_mpi_split = flag_mpi_init )          ! (in) optional

        call HistoryGetAttr( InputFile, 'time', 'sec_in_min', sec_in_min, flag_mpi_split = flag_mpi_init )          ! (in) optional

        ! ������¸ã��設å�
        ! Overwrite calendar
        !
        call TimesetSetCalendar( cal_type, month_in_year, day_in_month_ptr, hour_in_day, min_in_hour, sec_in_min ) ! (in)

        deallocate( day_in_month_ptr )

        ! ��å§��¥æ������¿è¾¼��
        ! Input start date
        !
        call HistoryGetAttr( InputFile, 'time', 'origin_year', origin_year, flag_mpi_split = flag_mpi_init )        ! (in) optional

        call HistoryGetAttr( InputFile, 'time', 'origin_month', origin_month, flag_mpi_split = flag_mpi_init )        ! (in) optional

        call HistoryGetAttr( InputFile, 'time', 'origin_day', origin_day, flag_mpi_split = flag_mpi_init )        ! (in) optional

        call HistoryGetAttr( InputFile, 'time', 'origin_hour', origin_hour, flag_mpi_split = flag_mpi_init )        ! (in) optional

        call HistoryGetAttr( InputFile, 'time', 'origin_min', origin_min, flag_mpi_split = flag_mpi_init )        ! (in) optional

        call HistoryGetAttr( InputFile, 'time', 'origin_sec', origin_sec, flag_mpi_split = flag_mpi_init )        ! (in) optional

        ! ��å§��¥æ������¸ã��設å�
        ! Overwrite start date
        !
        call TimesetSetInitialDate( origin_year, origin_month, origin_day, origin_hour, origin_min,   origin_sec )  ! (in)

        ! çµ�����������¿è¾¼��
        ! Input elapsed time
        !
        call HistoryGet( InputFile, 'time', range = time_range, array = rst_time, flag_mpi_split = flag_mpi_init )          ! (in) optional

        call MessageNotify( 'M', module_name, '  Specified RestartTime from a NAMELIST file            = <%f>, ', d = (/ RestartTime /) )
        call MessageNotify( 'M', module_name, '  Actual initial value of TimeN  from a restart file  = <%f>', d = (/ rst_time /) )

        ! çµ�����������¸ã��設å�
        ! Overwrite elapsed time
        !
        call TimesetSetTimeN( rst_time )

      end if

      ! ���¼ã�¿å�¥å��
      ! Data input
      ! 
      if ( flag_rst == 0 ) then
        call HistoryGet( InputFile, 'U', array = xyz_UB, flag_mpi_split = flag_mpi_init )  ! (in) optional
        call HistoryGet( InputFile, 'V', array = xyz_VB, flag_mpi_split = flag_mpi_init )  ! (in) optional
        call HistoryGet( InputFile, 'Temp', array = xyz_TempB, flag_mpi_split = flag_mpi_init )  ! (in) optional
        do n = 1, ncmax
          call HistoryGet( InputFile, trim(a_QMixName(n)), array = xyzf_QMixB(:,:,:,n), flag_mpi_split = flag_mpi_init )
        end do
        call HistoryGet( InputFile, 'Ps', array = xy_PsB, flag_mpi_split = flag_mpi_init )  ! (in) optional

        call MessageNotify( 'M', module_name, 'Initial data (not restart data) is input ' // 'from a data file "%c". ' // '*B (t-dt) and *N (t) are same.', c1 = trim(InputFile) )

        xyz_UN     = xyz_UB
        xyz_VN     = xyz_VB
        xyz_TempN  = xyz_TempB
        xyzf_QMixN = xyzf_QMixB
        xy_PsN     = xy_PsB

      else
        call HistoryGet( InputFile, 'UB', range = time_range, array = xyz_UB, flag_mpi_split = flag_mpi_init )        ! (in) optional
        call HistoryGet( InputFile, 'VB', range = time_range, array = xyz_VB, flag_mpi_split = flag_mpi_init )        ! (in) optional
        call HistoryGet( InputFile, 'TempB', range = time_range, array = xyz_TempB, flag_mpi_split = flag_mpi_init )           ! (in) optional
        do n = 1, ncmax
          call HistoryGet( InputFile, trim(a_QMixName(n))//'B', range = time_range, array = xyzf_QMixB(:,:,:,n), flag_mpi_split = flag_mpi_init )
        end do
        call HistoryGet( InputFile, 'PsB', range = time_range, array = xy_PsB, flag_mpi_split = flag_mpi_init )         ! (in) optional

        call HistoryGet( InputFile, 'UN', range = time_range, array = xyz_UN, flag_mpi_split = flag_mpi_init )        ! (in) optional
        call HistoryGet( InputFile, 'VN', range = time_range, array = xyz_VN, flag_mpi_split = flag_mpi_init )        ! (in) optional
        call HistoryGet( InputFile, 'TempN', range = time_range, array = xyz_TempN, flag_mpi_split = flag_mpi_init )           ! (in) optional
        do n = 1, ncmax
          call HistoryGet( InputFile, trim(a_QMixName(n))//'N', range = time_range, array = xyzf_QMixN(:,:,:,n), flag_mpi_split = flag_mpi_init )
        end do
        call HistoryGet( InputFile, 'PsN', range = time_range, array = xy_PsN, flag_mpi_split = flag_mpi_init )         ! (in) optional

        call MessageNotify( 'M', module_name, 'Restart data (not initial data) is input ' // 'from a data file "%c". ', c1 = trim(InputFile) )
      end if

    end if

  end subroutine RestartFileGet
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: RestartTime           ! ���¹ã�¿ã�¼ã����å§�����. 
                              ! Restart time of calculation

    ! NAMELIST ���¡ã�¤ã���¥å�����¢ã�������¼ã���£ã������
    ! 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

    ! �����¤ã���¼ã�� (���¹ã�¿ã�¼ã�����¼ã��) ��ä¾�
    ! Prepare initial data (restart data)
    !
    use initial_data, only: InitDataInit


    ! 宣�� ; 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

    ! 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


    ! �����������¤ã��¨­å®�
    ! Default values settings
    !
    InputFile  = ''
    if ( .not. flag_init_data_save ) then
      OutputFile = 'rst.nc'
    else
      OutputFile = 'init.nc'
    end if
    IntValue   = 365.0d0
    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

    ! �ºå������������¨­å®�
    ! Configure time interval of output
    !
    IntTime = DCCalConvertByUnit( IntValue, IntUnit, 'sec' ) ! (in)
    PrevOutputTime = RestartTime

    ! �����°ã��������
    ! Initialize flag
    !
    flag_output_end = .false.


    ! Initialization of modules used in this module

    ! �����¤ã���¼ã�� (���¹ã�¿ã�¼ã�����¼ã��) ��ä¾�
    ! Prepare initial data (restart data)
    !
    call InitDataInit


    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, 'Input:: ' )
    if ( trim(InputFile) /= '' ) then
      call MessageNotify( 'M', module_name, '  InputFile  = %c', c1 = trim(InputFile) )
    else
      call MessageNotify( 'M', module_name, '  InputFile  = <Non>' )
      call MessageNotify( 'M', module_name, '  ** Initial data is generated in "initial_data" module' )
    end if
    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_file_io_inited = .true.

  end subroutine RestartFileInit
Subroutine :
flag_init_data :logical, intent(in), optional
: �����¤ã���¼ã�¿ã��ä½��������´å����, ������°ã�� .true. ��ä¸����¾ã��.

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

���¹ã�¿ã�¼ã��/�����¤ã���¡ã�¤ã�������¼ã���³ã���¾ã��.

A restart/initial data file is opened.

[Source]

  subroutine RestartFileOpen( flag_init_data )
    !
    ! ���¹ã�¿ã�¼ã��/�����¤ã���¡ã�¤ã�������¼ã���³ã���¾ã��. 
    !
    ! A restart/initial data 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_Sigma, r_Sigma, z_DelSigma
                              ! $ \Delta \sigma $ (�´æ��). 
                              ! $ \Delta \sigma $ (Full)

    ! ���»ç���
    ! Time control
    !
    use timeset, only: DelTime, RestartTime, InitialDate           ! è¨�ç®���å§��¥æ��. 
                              ! Start date of calculation

    ! gtool4 ���¼ã�¿å�ºå��
    ! Gtool4 data output
    !
    use gtool_history, only: HistoryCreate, HistoryAddVariable, HistoryPut, HistoryAddAttr

    ! �����¥æ��������±ã��
    ! Calendar and Date handler
    !
    use dc_calendar, only: DCCalInquire, DCCalDateInquire

    ! ��������
    ! Character handling
    !
    use dc_string, only: CPrintf, LChar

    ! çµ��¿è¾¼�¿é�¢æ�� PRESENT ���¡å¼µ���¢æ��
    ! Extended functions of intrinsic function "PRESENT"
    !
    use dc_present, only: present_and_true

    ! 宣�� ; Declaration statements
    !
    implicit none
    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

    integer:: InitialYear, InitialMonth, InitialDay, InitialHour, InitialMin
                              ! è¨�ç®���å§���¹´���¥æ����. 
    real(DP):: InitialSec
                              ! ��������. 

    character(TOKEN):: cal_type
                              ! �����¿ã�¤ã��. 
    integer:: month_in_year, hour_in_day, min_in_hour
    integer, pointer:: day_in_month_ptr(:) => null()
    real(DP):: sec_in_min
                              ! �����細���

    logical:: flag_mpi_init

    integer :: n


    ! ���� ; Executable statement
    !

    ! ������
    ! Initialization
    !
    flag_init_data_save = present_and_true( flag_init_data )

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

    if ( restart_file_opened ) return

    ! è¡������������¡ã���»ã�¼ã�¸ã��¨­å®�
    ! Configure message added to title
    !
    if ( .not. flag_init_data_save ) then
      title_msg = ' restart data'
    else
      title_msg = ' initial data'
    end if

    ! ���»æ���±ã���å¾�
    ! Get time information
    !
    if ( .not. flag_init_data_save ) then
      origin_time = RestartTime + IntTime
    else
      origin_time = RestartTime
    end if

    flag_mpi_init = .false.

    ! ���¹ã�¿ã�¼ã�����¡ã�¤ã�������¼ã����
    ! Open a restart file
    !
    call HistoryCreate( file = OutputFile, title = trim(FileTitle) // trim(title_msg), source = FileSource, institution = FileInstitution, dims = (/ 'lon    ', 'lat    ', 'sig    ', 'sigm   ', 'timestr', 'time   ' /), dimsizes = (/ imax, jmax, kmax, kmax + 1, TOKEN, 0 /), longnames = (/ 'longitude                             ', 'latitude                              ', 'sigma at layer midpoints              ', 'sigma at layer end-points (half level)', 'number of characters for datetime     ', 'time                                  ' /), units = (/ 'degree_east ', 'degree_north', '1           ', '1           ', '1           ', 'sec         ' /), xtypes = (/'double', 'double', 'double', 'double', 'int   ', 'double'/), origind = origin_time, intervald = IntTime, flag_mpi_split = .true., history = gthst_rst )          ! (out) optional


    ! �� ������è¨�ç®����¼ã�¿ã�������������§ã�����������������°ã������
    !    ä½������������§ã����������ä¸�è¨� flag_rst 設å�å®�äº�å¾� 
    !    ���¤ä�å®� (morikawa  2010/06/13)
    !
    ! $ \Delta t $ ���¢ã�������±ã��追å��. 
    ! Add information about $ \Delta t $. 
    !
!!$    if ( .not. flag_init_data_save ) then
!!$      call HistoryAddVariable( &
!!$        & varname = 'deltime', &             ! (in)
!!$        & dims = (/''/), &                   ! (in)
!!$        & longname = 'delta time', &         ! (in)
!!$        & units = 'sec', xtype = 'double', & ! (in)
!!$        & history = gthst_rst )              ! (inout)
!!$      call HistoryPut( &
!!$        & varname = 'deltime', &            ! (in)
!!$        & array = (/ DelTime /), &          ! (in)
!!$        & history = gthst_rst )             ! (inout)
!!$    end if

    ! ��å§��¥æ�����±ã�� "time" ����§ã������¨­å®�
    ! Set start date information as attributes of "time"
    !
    call DCCalDateInquire( InitialYear, InitialMonth, InitialDay, InitialHour, InitialMin,   InitialSec, date = InitialDate )               ! (in)

    call HistoryAddAttr( 'time', attrname = 'origin', value = 'origin_year origin_month origin_day origin_hour origin_min origin_sec', history = gthst_rst )              ! (inout)
    call HistoryAddAttr( 'time', attrname = 'origin_year', value = InitialYear, history = gthst_rst )               ! (inout)
    call HistoryAddAttr( 'time', attrname = 'origin_month', value = InitialMonth, history = gthst_rst )                ! (inout)
    call HistoryAddAttr( 'time', attrname = 'origin_day', value = InitialDay, history = gthst_rst )               ! (inout)
    call HistoryAddAttr( 'time', attrname = 'origin_hour', value = InitialHour, history = gthst_rst )                ! (inout)
    call HistoryAddAttr( 'time', attrname = 'origin_min', value = InitialMin, history = gthst_rst )               ! (inout)
    call HistoryAddAttr( 'time', attrname = 'origin_sec', value = InitialSec, history = gthst_rst )               ! (inout)

    ! �����±ã�� "time" ����§ã������¨­å®�
    ! Set calendar information as attributes of "time"
    !
    call DCCalInquire( cal_type         = cal_type, month_in_year    = month_in_year, day_in_month_ptr = day_in_month_ptr , hour_in_day      = hour_in_day  , min_in_hour      = min_in_hour  , sec_in_min       = sec_in_min )         ! (out)

    call HistoryAddAttr( 'time', attrname = 'calendar', value = cal_type, history = gthst_rst )            ! (inout)
    call HistoryAddAttr( 'time', attrname = 'month_in_year', value = month_in_year, history = gthst_rst )                 ! (inout)
    call HistoryAddAttr( 'time', attrname = 'day_in_month', value = day_in_month_ptr, history = gthst_rst )                ! (inout)
    call HistoryAddAttr( 'time', attrname = 'hour_in_day', value = hour_in_day, history = gthst_rst )               ! (inout)
    call HistoryAddAttr( 'time', attrname = 'min_in_hour', value = min_in_hour, history = gthst_rst )               ! (inout)
    call HistoryAddAttr( 'time', attrname = 'sec_in_min', value = sec_in_min, history = gthst_rst )              ! (inout)

    deallocate( day_in_month_ptr )

    ! ��è¨�ç®����¼ã�¿ç���������°è¨­å®�
    ! Set flag for a restart data file. 
    !
    call HistoryAddVariable( varname = 'flag_rst', dims = (/''/), longname = 'flag for restart data', units = '1', xtype = 'int', history = gthst_rst )                 ! (inout)
    call HistoryAddAttr( varname = 'flag_rst', attrname = 'comment', value = 'If this value is nonzero, this file provides restart data', history = gthst_rst )                 ! (inout)

    if ( flag_init_data_save ) then
      call HistoryPut( varname = 'flag_rst', array = (/ 0 /), history = gthst_rst )                 ! (inout)
    else
      call HistoryPut( varname = 'flag_rst', array = (/ 1 /), history = gthst_rst )                 ! (inout)
    end if

    ! å¹´æ���¥æ����ç§�å½¢å����¥æ�����±å��°ã��¨­å®�
    ! Set a date information variable with year-month-day hour:minute:second format
    !
    call HistoryAddVariable( varname = 'datetime', dims =  (/'timestr', 'time   ' /), longname = 'time represented as strings', units = '1', xtype = 'char', history = gthst_rst )                       ! (inout) optional

    ! 座æ����¼ã�¿ã��¨­å®�
    ! Axes data settings
    !
    call HistoryAddAttr( 'lon', attrname = 'standard_name', value = 'longitude', history = gthst_rst )                    ! (inout)
    call HistoryAddAttr( 'lat', attrname = 'standard_name', value = 'latitude', history = gthst_rst )                    ! (inout)
    call HistoryAddAttr( 'sig', attrname = 'standard_name', value = 'atmosphere_sigma_coordinate', history = gthst_rst )                    ! (inout)
    call HistoryAddAttr( 'sigm', attrname = 'standard_name', value = 'atmosphere_sigma_coordinate', history = gthst_rst )                    ! (inout)
    call HistoryAddAttr( 'time', attrname = 'standard_name', value = 'time', history = gthst_rst )                    ! (inout)
    call HistoryAddAttr( 'sig', attrname = 'positive', value = 'down', history = gthst_rst )                    ! (inout)
    call HistoryAddAttr( 'sigm', attrname = 'positive', value = 'down', history = gthst_rst )                    ! (inout)

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

    ! 座æ����¿ã��¨­å®�
    ! Axes weights settings
    !
    call HistoryAddVariable( 'lon_weight', (/'lon'/), 'weight for integration in longitude', 'radian', xtype = 'double', history = gthst_rst )                              ! (inout)
    call HistoryAddAttr( 'lon', attrname = 'gt_calc_weight', value = 'lon_weight', history = gthst_rst )                     ! (inout)
    call HistoryPut( 'lon_weight', x_Lon_Weight, history = gthst_rst )                     ! (inout)

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

    call HistoryAddVariable( 'sig_weight', (/'sig'/), 'weight for integration in sigma', '1', xtype = 'double', history = gthst_rst )                     ! (inout)
    call HistoryAddAttr( 'sig', attrname = 'gt_calc_weight', value = 'sig_weight', history = gthst_rst )                     ! (inout)
    call HistoryPut( 'sig_weight', z_DelSigma, history = gthst_rst )                     ! (inout)


    ! äº��±å��°ã��¨­å®�
    ! Predictional variables settings
    !
    if ( flag_init_data_save ) then

      ! �������¼ã�¿ã���¡ã�¤ã����
      ! For initial data file
      !
      call HistoryAddVariable( 'U', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'eastward wind', 'm s-1', xtype = 'double', history = gthst_rst )                               ! (inout)
      call HistoryAddVariable( 'V', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'northward wind', 'm s-1', xtype = 'double', history = gthst_rst )                               ! (inout)
      call HistoryAddVariable( 'Temp', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'temperature', 'K', xtype = 'double', history = gthst_rst )                               ! (inout)
      do n = 1, ncmax
        call HistoryAddVariable( a_QMixName(n), (/ 'lon ', 'lat ', 'sig ', 'time' /), a_QMixLongName(n), 'kg kg-1', xtype = 'double', history = gthst_rst )
      end do
      call HistoryAddVariable( 'Ps', (/ 'lon ', 'lat ', 'time' /), 'surface pressure', 'Pa', xtype = 'double', history = gthst_rst )                               ! (inout)

    else

      ! ���¹ã�¿ã�¼ã�����¼ã�¿ã���¡ã�¤ã����
      ! For restart data file
      !
      call HistoryAddVariable( 'UB', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'eastward wind (at t-\Delta t)', 'm s-1', xtype = 'double', history = gthst_rst )                               ! (inout)
      call HistoryAddVariable( 'VB', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'northward wind (at t-\Delta t)', 'm s-1', xtype = 'double', history = gthst_rst )                               ! (inout)
      call HistoryAddVariable( 'TempB', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'temperature (at t-\Delta t)', 'K', xtype = 'double', history = gthst_rst )                               ! (inout)
      do n = 1, ncmax
        call HistoryAddVariable( trim(a_QMixName(n))//'B', (/ 'lon ', 'lat ', 'sig ', 'time' /), a_QMixLongName(n), 'kg kg-1', xtype = 'double', history = gthst_rst )
      end do
      call HistoryAddVariable( 'PsB', (/ 'lon ', 'lat ', 'time' /), 'surface pressure (at t-\Delta t)', 'Pa', xtype = 'double', history = gthst_rst )                               ! (inout)

      call HistoryAddVariable( 'UN', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'eastward wind (at t)', 'm s-1', xtype = 'double', history = gthst_rst )                               ! (inout)
      call HistoryAddVariable( 'VN', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'northward wind (at t)', 'm s-1', xtype = 'double', history = gthst_rst )                               ! (inout)
      call HistoryAddVariable( 'TempN', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'temperature (at t)', 'K', xtype = 'double', history = gthst_rst )                               ! (inout)
      do n = 1, ncmax
        call HistoryAddVariable( trim(a_QMixName(n))//'N', (/ 'lon ', 'lat ', 'sig ', 'time' /), a_QMixLongName(n), 'kg kg-1', xtype = 'double', history = gthst_rst )
      end do
      call HistoryAddVariable( 'PsN', (/ 'lon ', 'lat ', 'time' /), 'surface pressure (at t)', 'Pa', xtype = 'double', history = gthst_rst )                               ! (inout)
    end if

    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
xyzf_QMixB(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :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
xyzf_QMixN(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :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, xyzf_QMixB, xy_PsB, xyz_UN, xyz_VN, xyz_TempN, xyzf_QMixN, xy_PsN )
    !
    ! ���¹ã�¿ã�¼ã�����¼ã�¿ã���ºå����è¡����¾ã��. 
    !
    ! Output restart data

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! ���»ç���
    ! Time control
    !
    use timeset, only: TimeN, EndTime, InitialDate           ! è¨�ç®���å§��¥æ��. 
                              ! Start date of calculation

    ! gtool4 ���¼ã�¿å�ºå��
    ! Gtool4 data output
    !
    use gtool_history, only: HistoryPut, HistorySetTime

    ! �����¥æ��������±ã��
    ! Calendar and Date handler
    !
    use dc_calendar, only: DCCalDateInquire

    ! çµ��¿è¾¼�¿é�¢æ�� PRESENT ���¡å¼µ���¢æ��
    ! Extended functions of intrinsic function "PRESENT"
    !
    use dc_present, only: present_and_true

    ! 宣�� ; 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):: xyzf_QMixB (0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ 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):: xyzf_QMixN (0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ q (t) $ .     ��. Specific humidity
    real(DP), intent(in):: xy_PsN     (0:imax-1, 1:jmax)
                              ! $ p_s (t) $ .   �°è¡¨�¢æ���. Surface pressure

    ! �業��
    ! Work variables
    !
    logical:: flag_output
                              ! �ºå����������. 
                              ! Flag for output
    character(TOKEN):: date_str         ! �¥æ����¹´���¥æ����ç§�å½¢å�. 
                                        ! Date with year-month-day hour:minute:second format
    integer :: n


    ! ���� ; Executable statement
    !
    if ( .not. restart_file_opened ) call RestartFileOpen

    ! ���¹ã�¿ã�¼ã�����¼ã�¿å�ºå���§ã�������������§ã����
    ! Check restart data output
    !
    if ( flag_init_data_save ) then
      call MessageNotify( 'E', module_name, 'Now, initial data output mode.' )
    end if

    ! �ºå���¿ã�¤ã���³ã�°ã�����§ã����
    ! 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 )

    ! "TimeN" ��å¹´æ���¥æ����ç§�è¡�������� "datetime" å¤��°ã�¸å�ºå��
    ! Put "TimeN" on "datetime" variable with year-month-day hour:minute:second format
    !
    call DCCalDateInquire( date_str   = date_str, elapse_sec = TimeN, date       = InitialDate ) ! (in) optional

    call HistoryPut( 'datetime', date_str, history = gthst_rst )    ! (inout) optional

    ! ���¼ã�¿å�ºå��
    ! 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)
    do n = 1, ncmax
      call HistoryPut( trim(a_QMixName(n))//'B', xyzf_QMixB(:,:,:,n), history = gthst_rst ) ! (in)
    end do
    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)
    do n = 1, ncmax
      call HistoryPut( trim(a_QMixName(n))//'N', xyzf_QMixN(:,:,:,n), history = gthst_rst ) ! (in)
    end do
    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

PrevOutputTime
Variable :
PrevOutputTime :real(DP), save
: �������ºå������. Previous output time
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_file_io :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã������ç§�. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: restart_file_io.f90,v 1.26 2013/09/30 03:03:42 yot Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version