CPU time counting

Dc_clock module of gtool5 provides subroutines for CPU time counting. By using dc_clock module, CPU time it takes to execute arbitrary part of user's program can be estimated.

For example, a sample program using the dc_clock module (diffusion_5.f90) is shown here, which are modified from diffusion_3.f90 in Fortran 90/95 general-purpose modules: Type parameter specification. Statements with colored font (or bold font) are associated with the dc_clock module.

!= Sample program for gtool_history/gtool5
!
! * 2007/06/25 M.Odaka
! * 2006/10/25 Y.Morikawa
! * 2003/08/21 M.Odaka
! * 2001/02/27 S.Takehiro
!
! Solving diffusion equation
! \[
!     du/dt = \kappa d^2 u/dx^2
! \]
! for giving values of $u$ at $x=[0,1]$.
!
program diffusion_5

  use gtool_history                                   ! Access module (モジュール指定)
  use dc_types, only : DP                           ! Access module (モジュール指定)
  use dc_clock, only : CLOCK, DCClockCreate, &
    & DCClockClose, DCClockStart, DCClockStop, &
    & DCClockResult, DCClockPredict, &
    & operator(+)                             ! Access module (モジュール指定)

  integer, parameter     :: nx=30                   ! Grid number (グリッド数)
  integer, parameter     :: nt=200                  ! Time step number (時間ステップ数)
  integer, parameter     :: ndisp=10                ! Output interval (出力間隔)
  real(DP), parameter    :: dx=1.0/(nx-1)           ! Grid interval (グリッド間隔)
  real(DP), parameter    :: dt=0.0005               ! Time step (時間間隔)
  real(DP), dimension(nx):: x=(/(dx*(i-1),i=1,nx)/) ! X coordinate (座標変数)
  real(DP), dimension(nx):: temp                    ! Temperature (温度)
  real(DP), parameter    :: kappa=1.0               ! Diffusion coefficient (熱拡散係数)
  type(CLOCK)            :: clock_init, clock_loop  ! Variables for CPU time counting 
                                                    ! CPU 時間計測用変数

  call DCClockCreate( &           ! Initialize (初期化)
    & clk = clock_init, &         ! (out)
    & name = 'initialization' )   ! (in)
  call DCClockCreate( &           ! Initialize (初期化)
    & clk = clock_loop, &         ! (out)
    & name = 'time-integration' ) ! (in)

  call DCClockStart( clk = clock_init ) ! (inout)   ! Start CPU time counting 
                                                    ! (CPU 時間計測開始)

  tinit = 0.0                                       ! Set initial time 
                                                    ! (初期時刻設定)

  temp = exp(-((x-0.5)/0.1)**2)                     ! Set initial value 
                                                    ! (初期値設定)

  call HistoryCreate( &                             ! Create output file 
    & file='diffusion_5.nc', &                      ! (ヒストリー作成) 
    & title='Diffusion equation',                        &
    & source='Sample program of gtool_history/gtool5',   &
    & institution='GFD_Dennou Club davis project',       &
    & dims=(/'x','t'/), dimsizes=(/nx,0/),               &
    & longnames=(/'X-coordinate','time        '/),       &
    & units=(/'m','s'/),                                 &
    & origin=real(tinit), interval=real(ndisp*dt) )

  call HistoryPut('x',x)                            ! Output 'x' (次元変数出力)

  call HistoryAddVariable( &                        ! Set output variable
    & varname='temp', dims=(/'x','t'/), &           ! (変数定義)
    & longname='temperature', units='K', xtype='double')

  call HistoryAddAttr('temp','gt_graph_tick_all',1)
  call HistoryAddAttr('temp','gt_graph_contour_spacing',(/0.0,1.0,0.01/))
  call HistoryAddAttr('temp','+gt_user_davis_kappa',kappa)

  call HistoryPut('temp',temp)                      ! Output 'temp' (変数出力)

  call DCClockStop( clk = clock_init ) ! (inout)    ! Stop CPU time counting 
                                                    ! (CPU 時間計測終了)

  do it=1,nt
    call DCClockStart ( clk = clock_loop ) ! (inout) ! Start CPU time counting 
                                                     ! (CPU 時間計測開始)

    temp(2:nx-1) = temp(2:nx-1) &                   ! Time integration (時間積分)
      & + kappa*(temp(3:nx)-2*temp(2:nx-1)+temp(1:nx-2))/dx**2*dt

    if ( mod(it,ndisp) == 0 ) then
      call HistoryPut('temp',temp)                  ! Output 'temp' (変数出力)
    endif

    call DCClockStop( clk = clock_loop ) ! (inout)  ! Stop CPU time counting 
                                                    ! (CPU 時間計測終了)

    call DCClockPredict( &               ! Estimate remaining time (残り時間の予測)
      & clk = clock_init + clock_loop, & ! (in)
      & progress = real(it)/real(nt) )   ! (in) 
  end do

  call HistoryClose

  call DCClockResult( &                    ! Display total CPU time (全 CPU 時間の表示)
    & clks = (/clock_init, clock_loop/), & ! (in)
    & total_auto = .true. )                ! (in)
  call DCClockClose( clk = clock_init )    ! (inout)       ! Finalize (後処理)
  call DCClockClose( clk = clock_loop )    ! (inout)       ! Finalize (後処理)

  stop
end program diffusion_5

In this program, CPU time for initialization part and time integration part are counted and summation of then is estimated at the end of program. At the time integration loop, following messages are dumped.

########## PREDICTION OF CALCULATION ###########
Start Date             2007-06-26T13:53:18+09:00
Current Date           2007-06-26T13:53:19+09:00
Progress     52.50%  [*************            ]
Remaining CPU TIME      0.000000E+00
Completion Date        2007-06-26T13:53:19+09:00

When the program is terminated, following messages are dumped.

############## CPU TIME SUMMARY ################
initialization         0.129980E-01
time-integration       0.179959E-01
------------------------------------------------
       TOTAL TIME =    0.309939E-01

Summary of dc_clock module and its subroutines used in the sample program are as follows. In detail, please see gtool5 reference manual.

use dc_clock
Access dc_message module. This statement is located at the beginning of main program. In this case, ONLY option is used. If addition of CLOCK derived type variables, is necessary, defined operator + must be accessed.
tupe(CLOCK)
Definition of CLOCK derived data type variable. Counted CPU time is stored this variables
DCClockCreate(clk, name)
Initialize CLOCK derived data type variable. Descriptions of each argument are as follows.
  • clk specifies initialized CLOCK derived data type variable.
  • name specifies label.
DCClockStart(clk, [err])
Start CPU time counting. Counted CPU time is stored 1'st argument clk.
DCClockStop(clk, [err])
Stop CPU time counting. Value of clk is saved unless subroutine Close is called. If CPU time counting is started again with same CLOCK derived data type variable, new counted CPU time is added to saved value.
DCClockPredict ( clk, progress, [unit], [err] )
Estimate remaining CPU time by using elapsed CPU time and ratio of already executed part of program to remaining part. volume of program. Descriptions of each argument are as follows.
  • clk specifies CLOCK derived data type variable where elapsed CPU time is stored.
  • progress specifies ratio of already executed part of program to remaining part where the subroutine is called. progress should be given as float value between 0 and 1, 0 means at the start point of program and 1 means at the end of program. In this case, progress is given by using loop variable and total time step number.
  • unit specifies unit number for output. Its default value is standard out.
  • err is argument to execute if the 1'st argument clks is not initialized.
DCClockResults( clks, [unit] [total_auto], [clk_total], [total_name], [err] )
Display total CPU time. Descriptions of each argument are as follows.
  • clks specifies allay of CLOCK derived data type variable for estimation total CPU time.
  • unit specifies unit number for output. Its default value is standard out.
  • total_auto is logical argument whether total CPU time is displayed or not. If total_auto is ".true.", total value of CLOCK derived data type variable specified as clks argument is dis-plied. If optional argument clk_total is specified, the value of clk_total is given priority.
  • clk_total specifies CLOCK derived data type variable for estimation total CPU time.
  • total_name specifies dump message when total CPU time is displayed.
  • err is argument to execute if the 1'st argument clks is not initialized.
DCClockClose( clk )
Finalize CLOCK derived data type variable specified as 1'st argument.

$Id: dc_clock.rd,v 1.4 2009-02-28 16:07:56 morikawa Exp $