Class timeset
In: setup/timeset.f90

���»ç���

Time control

Note that Japanese and English are described in parallel.

���»æ���±ã�������è¡����¾ã��.

Information of time is controlled.

Variables List

TimeB :�¹ã������ $ t - Delta t $ ������
TimeN :�¹ã������ $ t $ ������
TimeA :�¹ã������ $ t + Delta t $ ������
DelTime :$ Delta t $ [s] (å®��°å�����°å��)
RestartTime :���¹ã�¿ã�¼ã����å§�����
EndTime :��������
InitialDate :è¨�ç®���å§��¥æ��
———— :————
TimeB :Time of step $ t - Delta t $
TimeN :Time of step $ t $
TimeA :Time of step $ t + Delta t $
DelTime :$ Delta t $ [s] (numerical value of float type)
RestartTime :Restart time of calculation
EndTime :End time of calculation
InitialDate :Start date of calculation

Procedures List

TimesetInit :timeset �¢ã�¸ã�¥ã�¼ã����������
TimesetDelTimeHalf :�t ���������������
TimesetProgress :���»ã���²è�
TimesetSetTimeN :TimeN ��¨­å®�
TimesetSetInitialDate :è¨�ç®���å§��¥æ����¨­å®�
TimesetClockStart :�����������
TimesetClockStop :�������������
TimesetClose :timeset �¢ã�¸ã�¥ã�¼ã�����äº�����
———— :————
TimesetInit :Initialize "timeset" module
TimesetDelTimeHalf :Reduce delta t to half temporarily
TimesetProgress :Progress time
TimesetSetTimeN :Set TimeN
TimesetSetInitialDate :Set start date
TimesetClockStart :Start measurement of computation time
TimesetClockStop :Pause measurement of computation time
TimesetClose :Terminate "timeset" module

NAMELIST

NAMELIST#timeset_nml

Methods

Included Modules

dc_types dc_message dc_clock dc_calendar namelist_util dc_iounit dc_string

Public Instance methods

DelTime
Variable :
DelTime :real(DP), save, public
: $ Delta t $ [s]
EndDate
Variable :
EndDate :type(DC_CAL_DATE), save, public
: è¨�ç®�çµ�äº����¥æ��
EndTime
Variable :
EndTime :real(DP), save, public
: ��������. End time of calculation
InitialDate
Variable :
InitialDate :type(DC_CAL_DATE), save, public
: è¨�ç®���å§��¥æ��. Start date of calculation
RestartTime
Variable :
RestartTime :real(DP), save, public
: ���¹ã�¿ã�¼ã����å§�����. Restart time of calculation
TimeA
Variable :
TimeA :real(DP), save, public
: �¹ã������ $ t + Delta t $ ������. Time of step $ t + Delta t $.
TimeB
Variable :
TimeB :real(DP), save, public
: �¹ã������ $ t - Delta t $ ������. Time of step $ t - Delta t $.
TimeN
Variable :
TimeN :real(DP), save, public
: �¹ã������ $ t $ ������. Time of step $ t $.
Subroutine :
name :character(*), intent(in)
: �¢ã�¸ã�¥ã�¼ã������ç§�. Name of module

���­ã�°ã������ä½� (主ã���¢ã�¸ã�¥ã�¼ã�����³å�) ����������è¨�æ¸�����å§����¾ã��.

Start measurement of computation time by program unit (expected modules).

[Source]

  subroutine TimesetClockStart( name )
    !
    ! ���­ã�°ã������ä½� (主ã���¢ã�¸ã�¥ã�¼ã�����³å�) ����������è¨�æ¸�����å§����¾ã��. 
    !
    ! Start measurement of computation time by program unit
    ! (expected modules). 

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

    ! CPU ������
    ! CPU time monitor
    !
    use dc_clock, only: DCClockCreate, DCClockStart

    ! 宣�� ; Declaration statements
    !
    character(*), intent(in):: name
                              ! �¢ã�¸ã�¥ã�¼ã������ç§�. 
                              ! Name of module

    ! �業��
    ! Work variables
    !
    integer:: i               ! clocks, clocks_name �� DO ���¼ã�����業å���
                              ! Work variables for DO loop for "clocks", "clocks_name"

    ! ���� ; Executable statement
    !

    if ( .not. CpuTimeMoniter ) return

    do i = 1, clk_proc_num
      if ( trim(clocks_name(i)) == trim(name) ) then
        call DCClockStart( clocks(i) ) ! (in)
        return
      end if
    end do

    call DCClockCreate( clocks(clk_proc_num + 1), name ) ! (in)
    call DCClockStart( clocks(clk_proc_num + 1) ) ! (in)
    clocks_name(clk_proc_num + 1) = name
    clk_proc_num = clk_proc_num + 1

  end subroutine TimesetClockStart
Subroutine :
name :character(*), intent(in)
: �¢ã�¸ã�¥ã�¼ã������ç§�. Name of module

���­ã�°ã������ä½� (主ã���¢ã�¸ã�¥ã�¼ã�����³å�) ����������è¨�æ¸���ä¸�����æ­¢ã���¾ã��.

Pause measurement of computation time by program unit (expected modules).

[Source]

  subroutine TimesetClockStop( name )
    !
    ! ���­ã�°ã������ä½� (主ã���¢ã�¸ã�¥ã�¼ã�����³å�) ����������è¨�æ¸���ä¸�����æ­¢ã���¾ã��.
    !
    ! Pause measurement of computation time by program unit
    ! (expected modules). 

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

    ! CPU ������
    ! CPU time monitor
    !
    use dc_clock, only: DCClockStop

    ! 宣�� ; Declaration statements
    !
    character(*), intent(in):: name
                              ! �¢ã�¸ã�¥ã�¼ã������ç§�. 
                              ! Name of module

    ! �業��
    ! Work variables
    !
    integer:: i               ! clocks, clocks_name �� DO ���¼ã�����業å���
                              ! Work variables for DO loop for "clocks", "clocks_name"

    ! ���� ; Executable statement
    !

    if ( .not. CpuTimeMoniter ) return

    do i = 1, clk_proc_num
      if ( trim(clocks_name(i)) == trim(name) ) then
        call DCClockStop( clocks(i) ) ! (in)
        return
      end if
    end do

    call MessageNotify( 'W', module_name, ' name "%c" is not found in "TimesetClockStop"', c1 = trim(name) )

  end subroutine TimesetClockStop
Subroutine :

è¨�ç®��������è¨���è¡�¤º���¾ã��.

Total computation time is printed.

[Source]

  subroutine TimesetClose
    !
    ! è¨�ç®��������è¨���è¡�¤º���¾ã��. 
    !
    ! Total computation time is printed. 

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

    ! CPU ������
    ! CPU time monitor
    !
    use dc_clock, only: DCClockStop, DCClockResult, DCClockSetName, operator(+), operator(-)

    ! 宣�� ; Declaration statements
    !
    integer:: i               ! clocks, clocks_name �� DO ���¼ã�����業å���
                              ! Work variables for DO loop for "clocks", "clocks_name"

    ! �業��
    ! Work variables
    !

    ! ���� ; Executable statement
    !

    if ( .not. CpuTimeMoniter ) return

    ! CPU ����è¨�æ¸��äº� (�¢ã�������)
    ! Stop CPU time monitoring (for entire model)
    !
    call DCClockStop( clocks(1) ) ! (in)

    ! ����������� CPU ���������
    ! Calculate CPU time of "Others"
    !
    clocks(clk_proc_num + 1) = clocks(1)
    do i = 2, clk_proc_num
      clocks(clk_proc_num + 1) = clocks(clk_proc_num + 1) - clocks(i)
    end do
    call DCClockSetName( clocks(clk_proc_num + 1), 'others' )

    ! CPU �������è¨���è¡�¤º
    ! Print total CPU time
    !
    call DCClockResult( clocks(2:clk_proc_num + 1), total_auto = .true. ) ! (in)

  end subroutine TimesetClose
Subroutine :

è¨�ç®����������������¤ã���¼æ�������������, ä¸������� �t �����������¾ã��. TimesetProgress ���¼ã�°ã����段é���� �t �������»ã���¾ã��.

Delta t is reduced to half temporarily in order to use Euler method at initial step. Delta t is returned to default, when "TimesetProgress" is called.

[Source]

  subroutine TimesetDelTimeHalf
    ! 
    ! è¨�ç®����������������¤ã���¼æ�������������, 
    ! ä¸������� �t �����������¾ã��. 
    ! TimesetProgress ���¼ã�°ã����段é���� �t �������»ã���¾ã��. 
    ! 
    ! Delta t is reduced to half temporarily 
    ! in order to use Euler method at initial step. 
    ! Delta t is returned to default, when "TimesetProgress" is called. 
    !

    ! 宣�� ; Declaration statements
    !

    ! �業��
    ! Work variables
    !

    ! ���� ; Executable statement
    !
    if ( flag_half ) return
    DelTime = DelTime / 2.0_DP
    flag_half = .true.

  end subroutine TimesetDelTimeHalf
Subroutine :

timeset �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. NAMELIST#timeset_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��.

"timeset" module is initialized. NAMELIST#timeset_nml is loaded in this procedure.

This procedure input/output NAMELIST#timeset_nml .

[Source]

  subroutine TimesetInit
    !
    ! timeset �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. 
    ! NAMELIST#timeset_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��. 
    !
    ! "timeset" module is initialized. 
    ! NAMELIST#timeset_nml is loaded in this procedure. 
    !

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

    ! 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

    ! �����¥æ��������±ã��
    ! Calendar and Date handler
    !
    use dc_calendar, only: DCCalCreate, DCCalConvertByUnit, DCCalToChar, DCCalInquire, DCCalDateCreate, DCCalDateDifference, DCCalDateToChar, DCCalDateInquire, DCCalDefault

    ! CPU ������
    ! CPU time monitor
    !
    use dc_clock, only: DCClockCreate, DCClockStart

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


    ! 宣�� ; Declaration statements
    !

    integer:: InitialYear, InitialMonth, InitialDay, InitialHour, InitialMin
                              ! è¨�ç®���å§��¥æ�� (å¹´æ���¥æ����)
                              ! Start date of calculation (year, month, day, hour, minute)
    real(DP):: InitialSec
                              ! è¨�ç®���å§��¥æ�� (ç§�)
                              ! Start date of calculation (second)
    real(DP):: IntegPeriodValue
                              ! �������. 
                              ! Integral time. 
    character(TOKEN):: IntegPeriodUnit
                              ! "IntegPeriodValue" �����. 
                              ! Unit of "IntegPeriodValue". 
    integer:: EndYear, EndMonth, EndDay, EndHour, EndMin
                              ! è¨�ç®�çµ�äº��¥æ�� (å¹´æ���¥æ����). 
                              ! "IntegPeriodValue" ��è²����´å�������¡ã����使ç��������. 
                              ! 
                              ! End date of calculation (year, month, day, hour, minute)
                              ! These are used when "IntegPeriodValue" is negative
    real(DP):: EndSec
                              ! è¨�ç®�çµ�äº��¥æ�� (ç§�). 
                              ! "IntegPeriodValue" ��è²����´å�������¡ã����使ç��������. 
                              ! 
                              ! End date of calculation (second)
                              ! These are used when "IntegPeriodValue" is negative

    ! �°å����業å���
    ! Work variables for print
    !
    type(DC_CAL):: cal_print
    real(DP):: EndTimeValue_print
    character(TOKEN):: date_print

    ! �業��
    ! 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 /timeset_nml/ cal_type, month_in_year, day_in_month, hour_in_day, min_in_hour, sec_in_min, DelTimeValue,    DelTimeUnit, RestartTimeValue,  RestartTimeUnit, InitialYear, InitialMonth, InitialDay, InitialHour, InitialMin, InitialSec, EndYear, EndMonth, EndDay, EndHour, EndMin, EndSec, IntegPeriodValue, IntegPeriodUnit, PredictIntValue,  PredictIntUnit, CpuTimeMoniter
          !
          ! �����������¤ã���¤ã��������������ç¶� "timeset#TimesetInit" 
          ! ���½ã�¼ã�¹ã�³ã�¼ã�������§ã������. 
          !
          ! Refer to source codes in the initialization procedure
          ! "timeset#TimesetInit" for the default values. 
          !

    ! ���� ; Executable statement
    !

    if ( timeset_inited ) return
    call InitCheck


    ! �����������¤ã��¨­å®�
    ! Default values settings
    !
    cal_type                      = 'noleap'
    month_in_year                 =   -1
    day_in_month(1:MaxNmlArySize) =   -1
    hour_in_day                   =   -1
    min_in_hour                   =   -1
    sec_in_min                    =   -1.0_DP

    ! Sample value for the Earth
    !
!!$    cal_type                      = 'gregorian'
!!$    month_in_year                 =   -1
!!$    day_in_month(1:MaxNmlArySize) =   -1
!!$    hour_in_day                   =   -1
!!$    min_in_hour                   =   -1
!!$    sec_in_min                    =   -1.0_DP

    ! Sample value for the Mars
    !   Number of days in a year and Mars solar day in second are obtained from 
    !   Allison (1997). 
    !   Allison, M, Geophys. Res. Lett., 24, 1967-1970, 1997.
    !
!!$    cal_type                      = 'user_defined'
!!$    month_in_year                 =    1
!!$    day_in_month(1:MaxNmlArySize) =  669
!!$    hour_in_day                   =   24
!!$    min_in_hour                   =    1
!!$    sec_in_min                    = 3700.0_DP    ! 3699.0_DP


    DelTimeValue                  =   30.0_DP
    DelTimeUnit                   = 'min'
    flag_half                     = .false.

    RestartTimeValue              =    0.0_DP
    RestartTimeUnit               = 'sec'

    InitialYear                   = 2000
    InitialMonth                  =    1
    InitialDay                    =    1
    InitialHour                   =    0
    InitialMin                    =    0
    InitialSec                    =    0.0

    IntegPeriodValue              =   -1.0
                                   ! If IntegPeriodValue is negative, EndXXX are used.
    IntegPeriodUnit               = 'sec'

    EndYear                       = 2000
    EndMonth                      =    1
    EndDay                        =    2
    EndHour                       =    0
    EndMin                        =    0
    EndSec                        =    0.0

    PredictIntValue               =    1.0_DP
    PredictIntUnit                = 'day'

    CpuTimeMoniter                 = .true.


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

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


    ! �������±ã��設å�
    ! Set calendar
    !
    if ( cal_type == "user_defined" ) then
      call DCCalCreate( month_in_year = month_in_year                , day_in_month  = day_in_month(1:month_in_year), hour_in_day   = hour_in_day                  , min_in_hour   = min_in_hour                  , sec_in_min    = sec_in_min )
    else
      call DCCalCreate( cal_type = cal_type ) ! (in)
    end if


    ! Lines below will be deleted. (yot, 2010/08/12)
    !

    ! �������±ã��設å� (�µã�³ã��������������¤ã���� case ��è¨�è¼�)
    !
    ! case 1:
    ! dc_calendar �§ç����������¸å������������������������������¨­å®�
    !
!!$    call DCCalCreate( cal_type = 'gregorian' ) ! (in)  ! �°ã���´ã������
!!$    call DCCalCreate( cal_type = 'julian'    ) ! (in)  ! �������¹æ��
!!$    call DCCalCreate( cal_type = 'noleap'    ) ! (in)  ! �鎶´ç�¡ã������
!!$    call DCCalCreate( cal_type = '360day'    ) ! (in)  ! 1�¶æ���� 30 �¥ã����
!!$    call DCCalCreate( cal_type = 'cyclic'    ) ! (in)  ! ���������¥æ�°ã�� ��30.6 � ���� �� �����¾ã�§ã����¥æ�°ã������°ç�¹ä»¥ä¸������������� 

!!$    ! case 2:
!!$    ! 決ã�¾ã�����£ã���� (以ä����������¹æ��) ��設å�
!!$    !
!!$    call DCCalCreate( cal_type = 'Julian' ) ! (in)
!!$
!!$    ! case 3:
!!$    ! �°ç���£ã�½ã����������������¤º������å®�
!!$    !
!!$    call DCCalCreate( month_in_year = 12 , &   ! (in)
!!$      &               day_in_month  = (/31, 28, 31, 30, 31, 30,   &
!!$      &                                 31, 31, 30, 31, 30, 31/), & ! (in) 
!!$      &               hour_in_day = 24,     &  ! (in) 
!!$      &               min_in_hour = 60 ,    &  ! (in) 
!!$      &               sec_in_min  = 60.0d0 )   ! (in) 
!!$
!!$    ! case 3:
!!$    ! �����£ã�½ã����������������¤º������å®�. 
!!$    ! �� �����������������´å������, month_in_year = 1 ������. 
!!$    !
!!$    call DCCalCreate( month_in_year = 1 , &      ! (in)
!!$      &               day_in_month  = (/669/), & ! (in)
!!$      &               hour_in_day = 24, &        ! (in)
!!$      &               min_in_hour = 1 , &        ! (in)
!!$      &               sec_in_min  = 3694.0d0  )  ! (in)


    ! ����å¤��� (ç§�) ��¨­å®�
    ! Calculate time variable (sec)
    !
    DelTime        = DCCalConvertByUnit( DelTimeValue,     DelTimeUnit,     'sec' ) !(in)
    RestartTime    = DCCalConvertByUnit( RestartTimeValue, RestartTimeUnit, 'sec' ) !(in)


    ! ��å§��¥æ�������±ã��設å�
    !
    ! ��è¨�ç®������� restart_file_io �¢ã�¸ã�¥ã�¼ã�������� TimesetSetInitialDate 
    ! �¼ã�³å�ºã�������£ã����¸ã���������������³å�. 
    !
    if ( ( .not. ( InitialMonth < 0      ) ) .and. ( .not. ( InitialDay   < 0      ) ) .and. ( .not. ( InitialHour  < 0      ) ) .and. ( .not. ( InitialMin   < 0      ) ) .and. ( .not. ( InitialSec   < 0.0_DP ) ) ) then

      call DCCalDateCreate( year  = InitialYear, month = InitialMonth, day   = InitialDay, hour  = InitialHour, min   = InitialMin, sec   = InitialSec, date  = InitialDate )  ! (out) optional
    else
      call MessageNotify('W', module_name, 'InitialMonth/Day/Hour/Min/Sec is negative.' )
    end if


    ! çµ�äº��¥æ�� (��å§��¥æ����������������§è¡¨��) ��設å�
    !
    if ( IntegPeriodValue < 0.0 ) then

      IntegPeriod = IntegPeriodValue

      ! case 1
      ! çµ�äº��¥æ����使ã���´å��
      !
      call DCCalDateCreate( year  = EndYear, month = EndMonth, day   = EndDay, hour  = EndHour, min   = EndMin, sec   = EndSec, date  = EndDate )    ! (out) optional

      EndTime = DCCalDateDifference( start_date = InitialDate, end_date   = EndDate )       ! (in)

      if ( .not. EndTime > 0.0 ) then
        call DCCalDateInquire( date_print, date = InitialDate )
        call MessageNotify('W', module_name, 'InitialDate=<%c>', c1 = trim(date_print) )
        call DCCalDateInquire( date_print, date = EndDate )
        call MessageNotify('W', module_name, 'EndDate=<%c>', c1 = trim(date_print) )
        call MessageNotify('E', module_name, '"EndTime" must be positive.')
      end if

    else
      ! case 2
      ! ç©���������使ã���´å��
      !
      IntegPeriod = DCCalConvertByUnit( IntegPeriodValue, IntegPeriodUnit, 'sec' ) !(in)

      EndTime = RestartTime + IntegPeriod
    end if


    ! çµ�äº�äº�æ¸��¥æ��è¡�¤º����������設å�
    ! Initialize Time when predicted end time is output
    !
    PredictIntTime  = DCCalConvertByUnit( PredictIntValue, PredictIntUnit, 'sec' ) !(in)
    PredictPrevTime = RestartTime - DelTime


    ! ���»ã��­£å½��§ã�����§ã����
    ! Check validation of time
    !
    call TimeValidCheck( RestartTime, EndTime, DelTime, PredictIntTime ) ! (in)


    ! ���¿ã�¤ã���¹ã�����������»ã��¨­å®�
    ! Configure time on each time step
    !
    ! ��è¨�ç®������� restart_file_io �¢ã�¸ã�¥ã�¼ã�������� TimesetSetTimeN
    ! �¼ã�³å�ºã�������£ã����¸ã���������������³å�. 
    ! 
    TimeN = RestartTime
    TimeB = TimeN - DelTime
    TimeA = TimeN + DelTime


    ! $ \Delta t $ [s] ����
    ! Save $ \Delta t $ [s]
    !
    DelTimeSave = DelTime


    ! CPU ����è¨�æ¸���å§� (�¢ã�������)
    ! Start CPU time monitoring (for entire model)
    !
    if ( CpuTimeMoniter ) then
      call DCClockCreate( clocks(clk_proc_num + 1), 'total' ) ! (in)
      call DCClockStart( clocks(clk_proc_num + 1) ) ! (in)
      clocks_name(clk_proc_num + 1) = 'total'
      clk_proc_num = clk_proc_num + 1
    end if

    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, '  RestartTime  = %f [%c]', d = (/ RestartTimeValue /), c1 = trim(RestartTimeUnit) )
    call DCCalDateInquire( date_print, date = InitialDate )
    call MessageNotify( 'M', module_name, '  InitialDate  = %c', c1 = trim(date_print) )
    if ( IntegPeriodValue < 0.0 ) then
      call DCCalDateInquire( date_print, date = EndDate )
      call MessageNotify( 'M', module_name, '  EndDate      = %c', c1 = trim(date_print) )
    end if
    EndTimeValue_print = DCCalConvertByUnit( EndTime, 'sec', RestartTimeUnit ) ! (in)
    call MessageNotify( 'M', module_name, '  EndTime      = %f [%c]', d = (/ EndTimeValue_print /), c1 = trim(RestartTimeUnit) )
    call MessageNotify( 'M', module_name, '  DelTime      = %f [%c]', d = (/ DelTimeValue /), c1 = trim(DelTimeUnit) )
    call MessageNotify( 'M', module_name, '               = %f [%c]', d = (/ DelTime /), c1 = 'sec' )
    if ( cal_type /= 'user_defined' ) then
      call MessageNotify( 'M', module_name, '  Calendar     = %c', c1 = trim(cal_type) )
    else
      call DCCalDefault( cal_print ) ! (out) 
      call MessageNotify( 'M', module_name, '  Calendar     = %c', c1 = trim(DCCalToChar(cal_print)) )
    end if
    call MessageNotify( 'M', module_name, '  PredictInt = %f [%c]', d = (/ PredictIntValue /), c1 = trim(PredictIntUnit) )
    call MessageNotify( 'M', module_name, '  CpuTimeMoniter = %b', l = (/ CpuTimeMoniter /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    timeset_inited = .true.
  end subroutine TimesetInit
Subroutine :

timeset �¢ã�¸ã�¥ã�¼ã���������»ã���²ã���¾ã��. �¾ã��, TimesetProgress#PredictIntStep �§è¨­å®��������¤ã�������, �¾å���¾ã�§ã���ç®��������ç®�çµ�äº�äº�æ¸����»ã��è¡�¤º���¾ã��.

Progress time configured in "timeset" module. And, computation time until now and predicted end of computation time are printed according to configured "TimesetProgress#PredictIntStep"

[Source]

  subroutine TimesetProgress
    !
    ! timeset �¢ã�¸ã�¥ã�¼ã���������»ã���²ã���¾ã��. 
    ! �¾ã��, TimesetProgress#PredictIntStep �§è¨­å®��������¤ã�������, 
    ! �¾å���¾ã�§ã���ç®��������ç®�çµ�äº�äº�æ¸����»ã��è¡�¤º���¾ã��. 
    !
    ! Progress time configured in "timeset" module. 
    ! And, computation time until now and 
    ! predicted end of computation time are printed 
    ! according to configured "TimesetProgress#PredictIntStep"
    !

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

    ! CPU ������
    ! CPU time monitor
    !
    use dc_clock, only: DCClockPredict, DCClockStop, DCClockClose, operator(+), operator(-)

    ! 宣�� ; Declaration statements
    !

    ! �業��
    ! Work variables
    !
    type(CLOCK):: clock_tmp

    ! ���� ; Executable statement
    !

    ! �t �������»ã��. 
    ! Delta t is returned to default
    !
    if ( flag_half ) then
      DelTime = DelTimeSave
      flag_half = .false.
    end if

    ! çµ�äº�äº�æ¸��¥æ��è¡�¤º
    ! Print predicted end time
    !
    if ( .not. TimeA - PredictPrevTime < PredictIntTime ) then
      PredictPrevTime = PredictPrevTime + PredictIntTime
      if ( CpuTimeMoniter ) then
        clock_tmp = clocks(1)
        call DCClockStop( clock_tmp ) ! (in)
        call DCClockPredict( clock_tmp, real( ( TimeA - RestartTime ) / ( ( EndTime + DelTimeSave ) - RestartTime ) ) ) ! (in)
        call DCClockClose( clock_tmp ) ! (in)
      end if
    end if

    ! ���»ã���²è�
    ! Progress time
    !
    TimeB = TimeB + DelTime
    TimeN = TimeN + DelTime
    TimeA = TimeA + DelTime
  end subroutine TimesetProgress
Subroutine :
cal_type :character(*), intent(in)
: �����¿ã�¤ã��.
month_in_year :integer, intent(in)
day_in_month(:) :integer, intent(in)
hour_in_day :integer, intent(in)
min_in_hour :integer, intent(in)
sec_in_min :real(DP), intent(in)
: ������. Information of Calendar.

(in)

������設å���è¡����¾ã��.

TimesetInit ���¢ã���¼ã�°ã���������������§ã��. TimesetInit ���¼ã�°ã�������������µã�����¼ã���³ã���¼ã�°ã�����´å��, ä½��������������µã�����¼ã���³ã���äº����¾ã��.

Calendar is reconfigured.

"TimesetInit" must be called before this subroutine is called. If "TimesetInit" is not called previously, this subroutine is finished with no changes.

[Source]

  subroutine TimesetSetCalendar( cal_type, month_in_year, day_in_month, hour_in_day, min_in_hour, sec_in_min )       ! (in)
    !
    ! ������設å���è¡����¾ã��. 
    !
    ! TimesetInit ���¢ã���¼ã�°ã���������������§ã��. 
    ! TimesetInit ���¼ã�°ã�������������µã�����¼ã���³ã���¼ã�°ã�����´å��,
    ! ä½��������������µã�����¼ã���³ã���äº����¾ã��. 
    !
    ! Calendar is reconfigured. 
    !
    ! "TimesetInit" must be called before this subroutine is called. 
    ! If "TimesetInit" is not called previously, this subroutine 
    ! is finished with no changes. 
    !

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

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

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

    ! 宣�� ; Declaration statements
    !

    character(*), intent(in):: cal_type
                              ! �����¿ã�¤ã��. 
    integer, intent(in):: month_in_year, day_in_month(:), hour_in_day, min_in_hour
    real(DP), intent(in):: sec_in_min
                              ! ������. 
                              ! Information of Calendar. 

    ! �業��
    ! Work variables
    !
    character(TOKEN):: cal_type_print
    type(DC_CAL):: cal_print

    ! ���� ; Executable statement
    !

    if ( .not. timeset_inited ) return

    ! ��å§��¥æ�������±ã��設å�
    !
    if ( cal_type /= 'user_defined' ) then
      call DCCalCreate( cal_type = cal_type )  ! (in)
    else
      call DCCalCreate( month_in_year, day_in_month , hour_in_day, min_in_hour , sec_in_min )     ! (in) 
    end if

    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Reconfigure Calendar Messages -----' )
    call DCCalInquire( cal_type = cal_type_print ) ! (out) optional
    if ( cal_type_print /= 'user_defined' ) then
      call MessageNotify( 'M', module_name, '  Calendar   = %c', c1 = trim(cal_type_print) )
    else
      call DCCalDefault( cal_print ) ! (out) 
      call MessageNotify( 'M', module_name, '  Calendar   = %c', c1 = trim(DCCalToChar(cal_print)) )
    end if

  end subroutine TimesetSetCalendar
Subroutine :
InitialYear :integer, intent(in)
: è¨�ç®���å§���¹´���¥æ����
InitialMonth :integer, intent(in)
: è¨�ç®���å§���¹´���¥æ����
InitialDay :integer, intent(in)
: è¨�ç®���å§���¹´���¥æ����
InitialHour :integer, intent(in)
: è¨�ç®���å§���¹´���¥æ����
InitialMin :integer, intent(in)
: è¨�ç®���å§���¹´���¥æ����
InitialSec :real(DP), intent(in)
: ��������

��å§��¥æ������設å���è¡����¾ã��.

TimesetInit ���¢ã���¼ã�°ã���������������§ã��. TimesetInit ���¼ã�°ã�������������µã�����¼ã���³ã���¼ã�°ã�����´å��, ä½��������������µã�����¼ã���³ã���äº����¾ã��.

Start date is reconfigured.

"TimesetInit" must be called before this subroutine is called. If "TimesetInit" is not called previously, this subroutine is finished with no changes.

[Source]

  subroutine TimesetSetInitialDate( InitialYear, InitialMonth, InitialDay, InitialHour, InitialMin, InitialSec )
    !
    ! ��å§��¥æ������設å���è¡����¾ã��. 
    !
    ! TimesetInit ���¢ã���¼ã�°ã���������������§ã��. 
    ! TimesetInit ���¼ã�°ã�������������µã�����¼ã���³ã���¼ã�°ã�����´å��,
    ! ä½��������������µã�����¼ã���³ã���äº����¾ã��. 
    !
    ! Start date is reconfigured. 
    !
    ! "TimesetInit" must be called before this subroutine is called. 
    ! If "TimesetInit" is not called previously, this subroutine 
    ! is finished with no changes. 
    !

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

    ! �����¥æ��������±ã��
    ! Calendar and Date handler
    !
    use dc_calendar, only: DCCalCreate, DCCalConvertByUnit, DCCalToChar, DCCalInquire, DCCalDateCreate, DCCalDateDifference, DCCalDateToChar, DCCalDateInquire

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

    ! 宣�� ; Declaration statements
    !

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

    ! �業��
    ! Work variables
    !
    real(DP):: EndTimeValue_print
    character(TOKEN):: date_print

    ! ���� ; Executable statement
    !

    if ( .not. timeset_inited ) return

    ! "InitialDate" ����設å�
    ! Reconfigure "InitialDate"
    !
    call DCCalDateCreate( year  = InitialYear, month = InitialMonth, day   = InitialDay, hour  = InitialHour, min   = InitialMin, sec   = InitialSec, date  = InitialDate )  ! (out) optional

    ! "EndTime" ����設å�
    ! Reconfigure "EndTime"
    !
    if ( IntegPeriod < 0.0 ) then
      EndTime = DCCalDateDifference( start_date = InitialDate, end_date = EndDate )         ! (in)

      if ( .not. EndTime > 0.0 ) then
        call DCCalDateInquire( date_print, date = InitialDate )
        call MessageNotify('W', module_name, 'InitialDate=<%c>', c1 = trim(date_print) )
        call DCCalDateInquire( date_print, date = EndDate )
        call MessageNotify('W', module_name, 'EndDate=<%c>', c1 = trim(date_print) )
        call MessageNotify('E', module_name, '"EndTime" must be positive.')
      end if

    end if

    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Reconfigure InitialDate Messages -----' )
    call DCCalDateInquire( date_print, date = InitialDate )
    call MessageNotify( 'M', module_name, '  InitialDate  = %c', c1 = trim(date_print) )
    if ( IntegPeriod < 0.0 ) then
      call DCCalDateInquire( date_print, date = EndDate )
      call MessageNotify( 'M', module_name, '  EndDate    = %c', c1 = trim(date_print) )

      EndTimeValue_print = DCCalConvertByUnit( EndTime, 'sec', RestartTimeUnit ) ! (in)
      call MessageNotify( 'M', module_name, '  EndTime    = %f [%c]', d = (/ EndTimeValue_print /), c1 = trim(RestartTimeUnit) )
    end if

  end subroutine TimesetSetInitialDate
Subroutine :
TimeNSet :real(DP), intent(in)
: �¹ã������ $ t $ ������. Time of step $ t $.

TimeN ����設å���è¡����¾ã��. �������� TimeB, TimeA, EndTime ���¤ã������ ��設å���è¡����¾ã��.

TimesetInit ���¢ã���¼ã�°ã���������������§ã��. TimesetInit ���¼ã�°ã�������������µã�����¼ã���³ã���¼ã�°ã�����´å��, ä½��������������µã�����¼ã���³ã���äº����¾ã��.

"TimeN" is reconfigured. "TimeB", "TimeA", "EndTime" are reconfigured automatically.

"TimesetInit" must be called before this subroutine is called. If "TimesetInit" is not called previously, this subroutine is finished with no changes.

[Source]

  subroutine TimesetSetTimeN(TimeNSet)
    !
    ! TimeN ����設å���è¡����¾ã��. 
    ! �������� TimeB, TimeA, EndTime ���¤ã������
    ! ��設å���è¡����¾ã��. 
    !
    ! TimesetInit ���¢ã���¼ã�°ã���������������§ã��. 
    ! TimesetInit ���¼ã�°ã�������������µã�����¼ã���³ã���¼ã�°ã�����´å��,
    ! ä½��������������µã�����¼ã���³ã���äº����¾ã��. 
    !
    ! "TimeN" is reconfigured. 
    ! "TimeB", "TimeA", "EndTime" are reconfigured automatically. 
    !
    ! "TimesetInit" must be called before this subroutine is called. 
    ! If "TimesetInit" is not called previously, this subroutine 
    ! is finished with no changes. 
    !

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

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

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

    ! 宣�� ; Declaration statements
    !

    real(DP), intent(in):: TimeNSet
                              ! �¹ã������ $ t $ ������. 
                              ! Time of step $ t $. 
    
    ! �業��
    ! Work variables
    !
    real(DP):: EndTimeValue_print

    ! ���� ; Executable statement
    !

    if ( .not. timeset_inited ) return

    ! TimeN ��è²����´å���������¼ã���ºç��
    ! Cause an error, if TimeN is negative
    !
    if ( TimeN < 0.0 ) then
      call MessageNotify( 'E', module_name, 'TimeN=<%f [sec]> must be positive', d = (/ TimeNSet /) )
    end if

    ! ���¿ã�¤ã���¹ã�����������»ã��¨­å®�
    ! Reconfigure time on each time step
    !
    TimeN = TimeNSet
    TimeB = TimeN - DelTime
    TimeA = TimeN + DelTime

    ! �������äº�äº�æ¸��¥æ��è¡�¤º��������設å�
    ! Reconfigure Time when predicted end time is output previously
    !
    PredictPrevTime = TimeN - DelTime

    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Reconfigure Time Messages -----' )
    call MessageNotify( 'M', module_name, '  TimeB  = %f [sec]', d = (/ TimeB /) )
    call MessageNotify( 'M', module_name, '  TimeN  = %f [sec]', d = (/ TimeN /) )
    call MessageNotify( 'M', module_name, '  TimeA  = %f [sec]', d = (/ TimeA /) )
    if ( IntegPeriod > 0.0 ) then
      EndTimeValue_print = DCCalConvertByUnit( EndTime, 'sec', RestartTimeUnit ) ! (in)
      call MessageNotify( 'M', module_name, '  EndTime    = %f [%c]', d = (/ EndTimeValue_print /), c1 = trim(RestartTimeUnit) )
    end if

  end subroutine TimesetSetTimeN
timeset_inited
Variable :
timeset_inited = .false. :logical, save, public
: ����設������. Initialization flag

Private Instance methods

CpuTimeMoniter
Variable :
CpuTimeMoniter :logical , save
: CPU ����è¨�æ¸������³ã���� On/off of CPU time monitoring
DelTimeSave
Variable :
DelTimeSave :real(DP) , save
: $ Delta t $ [s] ��������������. ("TimesetDelTimeHalf" �§ä½¿��������)

Default value of $ Delta t $ [s]. (for "TimesetDelTimeHalf")

DelTimeUnit
Variable :
DelTimeUnit :character(TOKEN), save
: $ Delta t $ �����. Unit of $ Delta t $
DelTimeValue
Variable :
DelTimeValue :real(DP) , save
: $ Delta t $ . ����� DelTimeUnit �������. Unit is specified by "DelTimeUnit".
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

    ! ���� ; Executable statement
    !

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

  end subroutine InitCheck
IntegPeriod
Variable :
IntegPeriod :real(DP), save
: �������. ������. Unit is second.
PredictIntTime
Variable :
PredictIntTime :real(DP) , save
: çµ�äº�äº�æ¸��¥æ��è¡�¤º��������. Interval time of predicted end time output
PredictIntUnit
Variable :
PredictIntUnit :character(TOKEN), save
: çµ�äº�äº�æ¸��¥æ��è¡�¤º���� (��ä½�). Unit for interval of predicted end time output
PredictIntValue
Variable :
PredictIntValue :real(DP) , save
: çµ�äº�äº�æ¸��¥æ��è¡�¤º����. Interval of predicted end time output
PredictPrevTime
Variable :
PredictPrevTime :real(DP) , save
: �������äº�äº�æ¸��¥æ��è¡�¤º����. Time when predicted end time is output previously
RestartTimeUnit
Variable :
RestartTimeUnit :character(TOKEN), save
: ���¹ã�¿ã�¼ã����å§����»ã����ä½�. Unit of restart time of calculation
RestartTimeValue
Variable :
RestartTimeValue :real(DP) , save
: ���¹ã�¿ã�¼ã����å§�����. Restart time of calculation
Subroutine :
RestartTimeChk :real(DP), intent(in)
: ���¹ã�¿ã�¼ã����å§�����. Restart time of calculation
EndTimeChk :real(DP), intent(in)
: ��������. End time of calculation
DelTimeChk :real(DP), intent(in)
: $ Delta t $ [s]
PredictIntTimeChk :real(DP), intent(in)
: çµ�äº�äº�æ¸��¥æ��è¡�¤º����. Interval of predicted end time output

���»æ���±ã���¤ã���������¹æ�§ã�����§ã�������¾ã��.

Check validation about infomation time

[Source]

  subroutine TimeValidCheck( RestartTimeChk, EndTimeChk, DelTimeChk, PredictIntTimeChk )
    !
    ! ���»æ���±ã���¤ã���������¹æ�§ã�����§ã�������¾ã��. 
    !
    ! Check validation about infomation time
    !

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

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

    real(DP), intent(in):: RestartTimeChk
                              ! ���¹ã�¿ã�¼ã����å§�����. 
                              ! Restart time of calculation
    real(DP), intent(in):: EndTimeChk
                              ! ��������. 
                              ! End time of calculation
    real(DP), intent(in):: DelTimeChk
                              ! $ \Delta t $ [s]
    real(DP), intent(in):: PredictIntTimeChk
                              ! çµ�äº�äº�æ¸��¥æ��è¡�¤º����. 
                              ! Interval of predicted end time output

    ! �°å����業å���
    ! Work variables for print
    !
    real(DP):: RestartTimeValue_print
    real(DP):: EndTimeValue_print
    real(DP):: DelTimeValue_print
    real(DP):: PredictIntValue_print

    ! �業��
    ! Work variables
    !

    ! ���� ; Executable statement
    !

    if ( .not. 0.0_DP < ( EndTimeChk - RestartTimeChk ) ) then
      RestartTimeValue_print = DCCalConvertByUnit( RestartTimeChk, 'sec', RestartTimeUnit ) ! (in)
      EndTimeValue_print = DCCalConvertByUnit( EndTimeChk, 'sec', RestartTimeUnit ) ! (in)
      
      call MessageNotify( 'E', module_name, 'RestartTime=<%f[%c]> is later than EndTime=<%f[%c]>', d = (/ RestartTimeValue_print, EndTimeValue_print /), c1 = trim(RestartTimeUnit), c2 = trim(RestartTimeUnit) )
    end if

    if ( DelTimeChk > ( EndTimeChk - RestartTimeChk ) ) then
      RestartTimeValue_print = DCCalConvertByUnit( RestartTimeChk, 'sec', RestartTimeUnit ) ! (in)
      EndTimeValue_print = DCCalConvertByUnit( EndTimeChk, 'sec', RestartTimeUnit ) ! (in)
      DelTimeValue_print = DCCalConvertByUnit( DelTimeChk, 'sec', DelTimeUnit ) ! (in)
      call MessageNotify( 'E', module_name, 'DelTime=<%f[%c]> is larger than ' // 'EndTime=<%f[%c]> - RestartTime=<%f[%c]>.', d = (/ DelTimeValue_print, EndTimeValue_print, RestartTimeValue_print /), c1 = trim(DelTimeUnit), c2 = trim(RestartTimeUnit), c3 = trim(RestartTimeUnit) )
    end if

    if ( .not. DelTimeChk > 0.0_DP ) then
      DelTimeValue_print = DCCalConvertByUnit( DelTimeChk, 'sec', DelTimeUnit ) ! (in)
      call MessageNotify( 'E', module_name, 'DelTime=<%f[%c]> must be more than 0.', d = (/ DelTimeValue_print /), c1 = trim(DelTimeUnit) )
    end if

    if ( .not. PredictIntTimeChk > 0.0_DP ) then
      PredictIntValue_print = DCCalConvertByUnit( PredictIntTimeChk, 'sec', PredictIntUnit ) ! (in)
      call MessageNotify( 'E', module_name, 'PredictInt=<%f[%c]> must be more than 0.', d = (/ PredictIntValue_print /), c1 = trim(PredictIntUnit) )
    end if

  end subroutine TimeValidCheck
cal_type
Variable :
cal_type :character(TOKEN), save
: ������. Type of calendar used for an experiment
clk_proc_num
Variable :
clk_proc_num = 0 :integer , save
: CPU ����è¨�æ¸���è¡��£ã���������­ã�»ã�¹ã����. Number of processes monitored CPU time
clkmax
Constant :
clkmax = 64 :integer , parameter
: CPU ����è¨�æ¸���è¡������­ã�»ã�¹ã����大æ��. Maximum number of processes monitored CPU time
clocks
Variable :
clocks(1:clkmax) :type(CLOCK) , save
: CPU ������������ Derived type for monitoring CPU time
clocks_name
Variable :
clocks_name(1:clkmax) = ’’ :character(TOKEN), save
: CPU ����è¨�æ¸���è¡��£ã���������­ã�»ã�¹ã����ç§� Names of processes monitored CPU time
day_in_month
Variable :
day_in_month(1:MaxNmlArySize) :integer , save
: Number of days in a month which is used when cal_type = "user_defined"
flag_half
Variable :
flag_half :logical , save
: TimesetDelTimeHalf �����£ã�� $ Delta t $ �� ���������£ã������������示ã��������.

Flag that shows $ Delta t $ is reduced to half by "TimesetDelTimeHalf"

hour_in_day
Variable :
hour_in_day :integer , save
: Number of hours in a day which is used when cal_type = "user_defined"
min_in_hour
Variable :
min_in_hour :integer , save
: Number of minutes in a hour which is used when cal_type = "user_defined"
module_name
Constant :
module_name = ‘timeset :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã������ç§�. Module name
month_in_year
Variable :
month_in_year :integer , save
: Number of months in a year which is used when cal_type = "user_defined"
sec_in_min
Variable :
sec_in_min :real(DP) , save
: Number of seconds in a minute which is used when cal_type = "user_defined"
version
Constant :
version = ’$Name: $’ // ’$Id: timeset.f90,v 1.24 2012/01/20 00:17:14 yot Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version