From f4f43072a0a76fbb4adbd32eb075eee165f695ca Mon Sep 17 00:00:00 2001 From: Simon KERN Date: Wed, 27 Nov 2024 11:32:40 +0100 Subject: [PATCH 1/6] clean after testing --- example/roessler/main.f90 | 1 - 1 file changed, 1 deletion(-) diff --git a/example/roessler/main.f90 b/example/roessler/main.f90 index 120db72..09bda8b 100644 --- a/example/roessler/main.f90 +++ b/example/roessler/main.f90 @@ -42,7 +42,6 @@ program demo real(wp), dimension(r, r) :: Lr ! IO character(len=20) :: data_fmt, header_fmt - !integer, allocatable :: logunits(:) write (header_fmt, *) '(22X,*(A,2X))' write (data_fmt, *) '(A22,*(1X,F15.6))' From b08a02442884c69a5fff8e230856ad32c34d5c6d Mon Sep 17 00:00:00 2001 From: Simon KERN Date: Wed, 27 Nov 2024 11:35:55 +0100 Subject: [PATCH 2/6] Fixed problems that occurred when integrating with LightROM --- src/Timer.f90 | 53 +++++--- src/Timer_Utils.f90 | 318 ++++++++++++++++++++++++-------------------- 2 files changed, 208 insertions(+), 163 deletions(-) diff --git a/src/Timer.f90 b/src/Timer.f90 index f924adc..2cb7d88 100644 --- a/src/Timer.f90 +++ b/src/Timer.f90 @@ -8,23 +8,41 @@ module LightKrylov_Timing private character(len=*), parameter :: this_module = 'LK_Timer' character(len=*), parameter :: this_module_long = 'LightKrylov_Timer' - logical :: if_time = .false. + logical :: if_time = .false. + public :: time_lightkrylov public :: global_lightkrylov_timer ! LightKrylov_watch type type, extends(abstract_watch), public :: lightkrylov_watch !! Global timing structure to contain all timers within Lightkrylov - character(len=128) :: name = 'lightkrylov_timer' contains private - procedure, pass(self), public :: set_private_timers => set_lightkrylov_timers + procedure, pass(self), public :: set_private_timers_and_name => set_lightkrylov_timers end type lightkrylov_watch type(lightkrylov_watch) :: global_lightkrylov_timer contains + logical function time_lightkrylov() result(if_time_lightkrylov) + if_time_lightkrylov = if_time + end function time_lightkrylov + + subroutine set_lightkrylov_timer_switch(value) + logical, intent(in) :: value + if (if_time .neqv. value) then + if_time = value + if (if_time) then + call logger%log_message('LightKrylov timing enabled.', module=this_module) + else + call logger%log_message('LightKrylov timing disabled.', module=this_module) + end if + else + call logger%log_debug('LightKrylov timing switched unchanged.', module=this_module) + end if + end subroutine set_lightkrylov_timer_switch + !-------------------------------------------------------------- ! Concrete implementations for the lightkrylov_watch type !-------------------------------------------------------------- @@ -33,11 +51,11 @@ subroutine set_lightkrylov_timers(self) !! Initialize global watch within LightKrylov and define private system timers. class(lightkrylov_watch), intent(inout) :: self ! internal - integer :: count_old + integer :: istart, iend + call self%set_watch_name('LightKrylov_timer') ! timers for LightKrylov_BaseKrylov - count_old = self%get_timer_count() ! rsp - call self%add_timer('qr_with_pivoting_rsp') + call self%add_timer('qr_with_pivoting_rsp', istart) call self%add_timer('qr_no_pivoting_rsp') call self%add_timer('orthonormalize_basis_rsp') call self%add_timer('orthonormalize_vector_against_basis_rsp') @@ -79,12 +97,12 @@ subroutine set_lightkrylov_timers(self) call self%add_timer('dgs_basis_against_basis_cdp') call self%add_timer('arnoldi_cdp') call self%add_timer('lanczos_bidiagonalization_cdp') - call self%add_timer('lanczos_tridiagonalization_cdp') - call self%add_group('BaseKrylov', istart=count_old+1, iend=self%get_timer_count()) + call self%add_timer('lanczos_tridiagonalization_cdp', iend) + ! define BaseKrylov group + call self%add_group('BaseKrylov', istart=istart, iend=iend) ! timers for LightKrylov_IterativeSolvers - count_old = self%get_timer_count() ! rsp - call self%add_timer('eigs_rsp') + call self%add_timer('eigs_rsp', istart) call self%add_timer('eighs_rsp') call self%add_timer('svds_rsp') call self%add_timer('gmres_rsp') @@ -110,19 +128,22 @@ subroutine set_lightkrylov_timers(self) call self%add_timer('svds_cdp') call self%add_timer('gmres_cdp') call self%add_timer('fgmres_cdp') - call self%add_timer('cg_cdp') - call self%add_group('IterativeSolvers', istart=count_old+1, iend=self%get_timer_count()) + call self%add_timer('cg_cdp', iend) + ! define IterativeSolvers group + call self%add_group('IterativeSolvers', istart=istart, iend=iend) ! timers for LightKrylov_NewtonKrylov - count_old = self%get_timer_count() ! rsp - call self%add_timer('newton_rsp') + call self%add_timer('newton_rsp', istart) ! rdp call self%add_timer('newton_rdp') ! csp call self%add_timer('newton_csp') ! cdp - call self%add_timer('newton_cdp') - call self%add_group('NewtonKrylov', istart=count_old+1, iend=self%get_timer_count()) + call self%add_timer('newton_cdp', iend) + ! define NewtonKrylov group + call self%add_group('NewtonKrylov', istart=istart, iend=iend) + ! Enable timing + call set_lightkrylov_timer_switch(.true.) end subroutine set_lightkrylov_timers end module LightKrylov_Timing \ No newline at end of file diff --git a/src/Timer_Utils.f90 b/src/Timer_Utils.f90 index 52ba4e9..ae048eb 100644 --- a/src/Timer_Utils.f90 +++ b/src/Timer_Utils.f90 @@ -7,10 +7,6 @@ module LightKrylov_Timer_Utils private character(len=*), parameter :: this_module = 'LK_TmrUtils' character(len=*), parameter :: this_module_long = 'LightKrylov_Timer_Utils' - logical :: if_time = .false. - - public :: time_lightkrylov - public :: set_timer_switch ! Timer type type, public :: lightkrylov_timer @@ -76,6 +72,7 @@ module LightKrylov_Timer_Utils type, abstract, public :: abstract_watch !! Base type to define a global timer. private + character(len=128) :: name = 'default_watch' type(lightkrylov_timer), dimension(:), allocatable :: timers !! Array of timers contained in the watch integer :: timer_count = 0 @@ -99,12 +96,10 @@ module LightKrylov_Timer_Utils !! Remove existing timer from the watch procedure, pass(self), public :: add_group !! Add new timer group to the watch - procedure, pass(self), public :: enumerate - !! Print summary of registered timers and their current status ! Getter/Setter and helper routines procedure, pass(self), public :: get_timer_id - procedure, pass(self), public :: get_timer_count procedure, pass(self), public :: get_group_id + procedure, pass(self), public :: set_watch_name procedure, pass(self), public :: reset_all ! Wrappers for the basic timing routines procedure, pass(self), public :: start => start_timer_by_name @@ -112,11 +107,14 @@ module LightKrylov_Timer_Utils procedure, pass(self), public :: pause => pause_timer_by_name procedure, pass(self), public :: reset => reset_timer_by_name procedure, pass(self), public :: print_info => print_timer_info_by_name + ! Global manipulation routines + procedure, pass(self), public :: enumerate + !! Print summary of registered timers and their current status procedure, pass(self), public :: initialize !! Set up private timers, flags and counters. Switch on timing. procedure, pass(self), public :: finalize !! Gather timing information and print it to screen/logfile - procedure(abstract_set_timers), pass(self), deferred, public :: set_private_timers + procedure(abstract_set_timers), pass(self), deferred, public :: set_private_timers_and_name !! Define private timers that cannot be removed by the user end type abstract_watch @@ -136,24 +134,6 @@ end subroutine abstract_set_timers contains - logical function time_lightkrylov() result(if_time_lightkrylov) - if_time_lightkrylov = if_time - end function time_lightkrylov - - subroutine set_timer_switch(value) - logical, intent(in) :: value - if (if_time .neqv. value) then - if_time = value - if (if_time) then - call logger%log_message('LightKrylov timing enabled.', module=this_module) - else - call logger%log_message('LightKrylov timing disabled.', module=this_module) - end if - else - call logger%log_debug('LightKrylov timing switched unchanged.', module=this_module) - end if - end subroutine set_timer_switch - !-------------------------------------------------------------- ! Type-bound procedures for lightkrylov_timer type !-------------------------------------------------------------- @@ -254,6 +234,11 @@ subroutine reset_timer(self, soft, clean, verbose) save_data = optval(soft, .true.) flush_timer = optval(clean, .false.) print_info = optval(verbose, .false.) + if (self%running) then + call self%stop() + call logger%log_message('Timer "'//trim(self%name)//'" is curently running. Stopping timer before reset.', & + & module=this_module, procedure='reset_timer') + end if if (save_data) then write(msg,'(A,A)') trim(self%name), ': soft reset.' if (print_info) then @@ -356,7 +341,7 @@ subroutine print_timer_info(self, full) end if end if else ! is_finalized - call print_summary_header('Timer summary') + call print_summary_header('Summary', self%name) if (self%reset_count == 0) then call stop_error(trim(self%name)//': reset_count inconsistent!', module=this_module, procedure='finalize_timer') end if @@ -390,74 +375,51 @@ end subroutine finalize_timer ! Type-bound procedures for abstract_watch type !-------------------------------------------------------------- - integer function get_timer_id(self, name) result(id) - !! Type-bound to abstract_watch: Getter routine to return the timer id based on name - class(abstract_watch) :: self - character(len=*) :: name - !! Timer name - ! internal - integer :: i - id = 0 - do i = 1, self%timer_count - if (self%timers(i)%name == to_lower(name)) id = i - end do - end function get_timer_id - - integer function get_timer_count(self) result(count) - !! Type-bound to abstract_watch: Getter routine to return the timer count - class(abstract_watch) :: self - count = self%timer_count - end function get_timer_count - - integer function get_group_id(self, name) result(id) - !! Type-bound to abstract_watch: Getter routine to return the group id based on name - class(abstract_watch) :: self - character(len=*) :: name - !! Timer name - ! internal - integer :: i - id = 0 - do i = 1, self%group_count - if (self%groups(i)%name == to_lower(name)) id = i - end do - end function get_group_id - - subroutine add_timer(self, name) + subroutine add_timer(self, name, count) !! Type-bound to abstract_watch: Add timer to watch !! Note: The new timer name must be unique class(abstract_watch), intent(inout) :: self character(len=*), intent(in) :: name + integer, optional, intent(out) :: count + ! internal + character(len=128) :: msg, tname + tname = to_lower(name) if (self%timer_count == 0) then allocate(self%timers(1)) - self%timers(1) = lightkrylov_timer(to_lower(name)) + self%timers(1) = lightkrylov_timer(tname) self%timer_count = 1 else if (self%get_timer_id(name) > 0) then - call stop_error('Timer "'//to_lower(trim(name))//'" already defined!', & + call stop_error('Timer "'//trim(tname)//'" already defined!', & & module=this_module, procedure='add_timer') end if - self%timers = [ self%timers, lightkrylov_timer(name) ] + self%timers = [ self%timers, lightkrylov_timer(tname) ] self%timer_count = self%timer_count + 1 if (self%user_mode) self%user_count = self%user_count + 1 end if - call logger%log_debug('Timer "'//to_lower(trim(name))//'" added.', module=this_module) + write(msg,'(A,I0)') 'Timer "'//trim(tname)//'" added: timer_count: ', self%timer_count + call logger%log_debug(msg, module=this_module) + if (present(count)) count = self%timer_count end subroutine add_timer - subroutine remove_timer(self, name) + subroutine remove_timer(self, name, count) !! Type-bound to abstract_watch: Remove timer from watch !! Note: Timers considered private (defined during initialisation) cannot be removed. class(abstract_watch), intent(inout) :: self character(len=*), intent(in) :: name + integer, optional, intent(out) :: count ! internal type(lightkrylov_timer), dimension(:), allocatable :: new_timers + character(len=128) :: msg, tname integer :: id - id = self%get_timer_id(name) + tname = to_lower(name) + id = self%get_timer_id(tname) if (id == 0) then - call stop_error('Timer "'//to_lower(trim(name))//'" not defined!', & + call stop_error('Timer "'//trim(tname)//'" not defined!', & & module=this_module, procedure='remove_timer') else if (id <= self%private_count) then - call logger%log_message('Cannot remove private timer "'//to_lower(trim(name))//'".', & + call logger%log_message('Cannot remove private timer "'//trim(tname)//'".', & & module=this_module, procedure='remove_timer') else self%timer_count = self%timer_count - 1 @@ -468,30 +430,104 @@ subroutine remove_timer(self, name) self%timers = new_timers end if end if - call logger%log_debug('Timer "'//to_lower(trim(name))//'" removed.', module=this_module) + write(msg,'(A,I0)') 'Timer "'//trim(tname)//'" removed: timer_count: ', self%timer_count + call logger%log_debug(msg, module=this_module) + if (present(count)) count = self%timer_count end subroutine remove_timer - subroutine add_group(self, name, istart, iend) + subroutine add_group(self, name, istart, iend, count) !! Type-bound to abstract_watch: Add timer group to watch - !! Note: The new group name must be unique + !! Note: The new group name must be unique. This is a quick hack and should be done better. class(abstract_watch), intent(inout) :: self character(len=*), intent(in) :: name integer, intent(in) :: istart integer, intent(in) :: iend + integer, optional, intent(out) :: count + ! internal + character(len=128) :: msg, gname + ! Sanity checks + if (istart < 1 .or. iend < 1) then + call stop_error('Inconsistent input for istart, iend.', module=this_module, procedure='add_group') + else if (istart > iend) then + call stop_error('istart > iend.', module=this_module, procedure='add_group') + else if (iend > self%timer_count) then + call stop_error('iend > timer_count.', module=this_module, procedure='add_group') + end if + gname = to_lower(name) if (self%group_count == 0) then allocate(self%groups(1)) - self%groups(1) = lightkrylov_timer_group(name=to_lower(name), istart=istart, iend=iend) + self%groups(1) = lightkrylov_timer_group(name=gname, istart=istart, iend=iend) self%group_count = 1 else if (self%get_group_id(name) > 0) then - call stop_error('Timer group "'//to_lower(trim(name))//'" already defined!', & + call stop_error('Timer group "'//trim(gname)//'" already defined!', & & module=this_module, procedure='add_group') end if - self%groups = [ self%groups, lightkrylov_timer_group(name=to_lower(name), istart=istart, iend=iend) ] + self%groups = [ self%groups, lightkrylov_timer_group(name=gname, istart=istart, iend=iend) ] self%group_count = self%group_count + 1 end if - call logger%log_debug('Timer group "'//to_lower(trim(name))//'" added.', module=this_module) + write(msg,'(A,I0)') 'Timer group "'//trim(gname)//'" added: group_count: ', self%group_count + call logger%log_debug(msg, module=this_module) + if (present(count)) count = self%group_count end subroutine add_group + + integer function get_timer_id(self, name) result(id) + !! Type-bound to abstract_watch: Getter routine to return the timer id based on name + class(abstract_watch) :: self + character(len=*) :: name + !! Timer name + ! internal + integer :: i + id = 0 + do i = 1, self%timer_count + if (self%timers(i)%name == to_lower(name)) id = i + end do + end function get_timer_id + + integer function get_group_id(self, name) result(id) + !! Type-bound to abstract_watch: Getter routine to return the group id based on name + class(abstract_watch) :: self + character(len=*) :: name + !! Timer name + ! internal + integer :: i + id = 0 + do i = 1, self%group_count + if (self%groups(i)%name == to_lower(name)) id = i + end do + end function get_group_id + + subroutine set_watch_name(self, name) + !! Type-bound to abstract_watch: Set name of watch + class(abstract_watch), intent(inout) :: self + character(len=*), intent(in) :: name + !! Watch name + self%name = name + end subroutine set_watch_name + + subroutine reset_all(self, soft, clean) + !! Type-bound to abstract_watch: Utility function to reset all timers at once + !! Note: Wrapper of the corresponding routine from lightkrylov_timer + class(abstract_watch), intent(inout) :: self + logical, optional, intent(in) :: soft + logical, optional, intent(in) :: clean + ! internal + integer :: i + logical :: soft_ + logical :: clean_ + character(len=128) :: msg + soft_ = optval(soft, .true.) + clean_ = optval(clean, .false.) + do i = 1, self%timer_count + call self%timers(i)%reset(soft, clean, verbose=.false.) + end do + write(msg,'(A,2(A,I0))') 'All timers reset: ', 'private: ', self%private_count, ', user: ', self%user_count + call logger%log_message(msg, module=this_module) + write(msg,'(2X,A,L)') 'soft reset: ', soft_ + call logger%log_message(msg, module=this_module) + write(msg,'(2X,A,L)') 'flush timers: ', clean_ + call logger%log_message(msg, module=this_module) + end subroutine reset_all subroutine start_timer_by_name(self, name) !! Type-bound to abstract_watch: Start timer referenced by name @@ -500,14 +536,16 @@ subroutine start_timer_by_name(self, name) character(len=*), intent(in) :: name ! internal integer :: id - id = self%get_timer_id(name) + character(len=128) :: tname + tname = to_lower(name) + id = self%get_timer_id(tname) if (id == 0) then - call stop_error('Timer "'//to_lower(trim(name))//'" not found!', & + call stop_error('Timer "'//trim(tname)//'" not found!', & & module=this_module, procedure='start_timer_by_name') else call self%timers(id)%start() end if - call logger%log_debug('Timer "'//to_lower(trim(name))//'" started.', module=this_module) + call logger%log_debug('Timer "'//trim(tname)//'" started.', module=this_module) end subroutine start_timer_by_name subroutine stop_timer_by_name(self, name) @@ -517,14 +555,16 @@ subroutine stop_timer_by_name(self, name) character(len=*), intent(in) :: name ! internal integer :: id - id = self%get_timer_id(name) + character(len=128) :: tname + tname = to_lower(name) + id = self%get_timer_id(tname) if (id == 0) then - call stop_error('Timer "'//to_lower(trim(name))//'" not found!', & + call stop_error('Timer "'//trim(tname)//'" not found!', & & module=this_module, procedure='stop_timer_by_name') else call self%timers(id)%stop() end if - call logger%log_debug('Timer "'//to_lower(trim(name))//'" stopped.', module=this_module) + call logger%log_debug('Timer "'//trim(tname)//'" stopped.', module=this_module) end subroutine stop_timer_by_name subroutine pause_timer_by_name(self, name) @@ -534,14 +574,16 @@ subroutine pause_timer_by_name(self, name) character(len=*), intent(in) :: name ! internal integer :: id - id = self%get_timer_id(name) + character(len=128) :: tname + tname = to_lower(name) + id = self%get_timer_id(tname) if (id == 0) then - call stop_error('Timer "'//to_lower(trim(name))//'" not found!', & + call stop_error('Timer "'//trim(tname)//'" not found!', & & module=this_module, procedure='pause_timer_by_name') else call self%timers(id)%pause() end if - call logger%log_debug('Timer "'//to_lower(trim(name))//'" paused.', module=this_module) + call logger%log_debug('Timer "'//trim(tname)//'" paused.', module=this_module) end subroutine subroutine reset_timer_by_name(self, name, soft, clean) @@ -553,9 +595,11 @@ subroutine reset_timer_by_name(self, name, soft, clean) logical, optional, intent(in) :: clean ! internal integer :: id - id = self%get_timer_id(name) + character(len=128) :: tname + tname = to_lower(name) + id = self%get_timer_id(tname) if (id == 0) then - call stop_error('Timer "'//to_lower(trim(name))//'" not found!', & + call stop_error('Timer "'//trim(tname)//'" not found!', & & module=this_module, procedure='reset_timer_by_name') else call self%timers(id)%reset(soft, clean) @@ -570,9 +614,11 @@ subroutine print_timer_info_by_name(self, name, full) logical, optional, intent(in) :: full ! internal integer :: id - id = self%get_timer_id(name) + character(len=128) :: tname + tname = to_lower(name) + id = self%get_timer_id(tname) if (id == 0) then - call stop_error('Timer "'//to_lower(trim(name))//'" not found!', & + call stop_error('Timer "'//trim(tname)//'" not found!', & & module=this_module, procedure='print_timer_info_by_name') else call self%timers(id)%print_info(full) @@ -583,57 +629,36 @@ subroutine enumerate(self, only_user) !! Type-bound to abstract_watch: Summarize registered timers and their status class(abstract_watch), intent(in) :: self logical, optional, intent(in) :: only_user - !! Summarize only user defined timers? default: .true. + !! Summarize only user defined timers? default: .false. ! internal - integer :: i + integer :: i, j logical :: only_user_ - character(len=128) :: msg, fmt - fmt = '(4X,I4," :",3(1X,I0))' - only_user_ = optval(only_user, .true.) + character(len=128) :: msg, fmt_e + fmt_e = '(2X,I3,A50," :",3(1X,I0))' + only_user_ = optval(only_user, .false.) if (.not. only_user_) then call logger%log_message('Registered timers: all', module=this_module) - do i = 1, self%private_count - associate (t => self%timers(i)) - write(msg,fmt) i, trim(t%name), t%count, t%local_count, t%reset_count - call logger%log_message(msg, module=this_module) - end associate + do i = 1, self%group_count + call logger%log_message(trim(self%groups(i)%name)//":", module=this_module) + do j = self%groups(i)%istart, self%groups(i)%iend + associate (t => self%timers(j)) + write(msg,fmt_e) j, trim(t%name), t%count, t%local_count, t%reset_count + call logger%log_message(msg, module=this_module) + end associate + end do end do end if if (self%user_count > 0) then call logger%log_message('Registered timers: user', module=this_module) do i = self%private_count+1, self%timer_count associate (t => self%timers(i)) - write(msg,fmt) i, trim(t%name), t%count, t%local_count, t%reset_count + write(msg,fmt_e) i, trim(t%name), t%count, t%local_count, t%reset_count call logger%log_message(msg, module=this_module) end associate end do end if end subroutine enumerate - subroutine reset_all(self, soft, clean) - !! Type-bound to abstract_watch: Utility function to reset all timers at once - !! Note: Wrapper of the corresponding routine from lightkrylov_timer - class(abstract_watch), intent(inout) :: self - logical, optional, intent(in) :: soft - logical, optional, intent(in) :: clean - ! internal - integer :: i - logical :: soft_ - logical :: clean_ - character(len=128) :: msg - soft_ = optval(soft, .true.) - clean_ = optval(clean, .false.) - do i = 1, self%timer_count - call self%timers(i)%reset(soft, clean, verbose=.false.) - end do - write(msg,'(A,2(A,I0))') 'All timers reset: ', 'system: ', self%private_count, ', user: ', self%user_count - call logger%log_message(msg, module=this_module) - write(msg,'(2X,A,L)') 'soft reset: ', soft_ - call logger%log_message(msg, module=this_module) - write(msg,'(2X,A,L)') 'flush timers: ', clean_ - call logger%log_message(msg, module=this_module) - end subroutine reset_all - subroutine initialize(self) !! Initialize global watch within LightKrylov and define private system timers. class(abstract_watch), intent(inout) :: self @@ -641,32 +666,29 @@ subroutine initialize(self) integer :: i, count character(len=128) :: msg if (.not. self%is_initialized) then - call logger%log_information('Set private timers.', module=this_module) - call self%set_private_timers() + call self%set_private_timers_and_name() self%private_count = self%timer_count write(msg,'(2(I0,A))') self%private_count, ' private timers registered in ', self%group_count, ' groups:' - call logger%log_information(msg, module=this_module) + call logger%log_information(msg, module=this_module, procedure=self%name) do i = 1, self%group_count count = self%groups(i)%iend - self%groups(i)%istart + 1 write(msg,'(3X,A20," : ",I3," timers.")') self%groups(i)%name, count - call logger%log_information(msg, module=this_module) + call logger%log_information(msg, module=this_module, procedure=self%name) end do self%is_initialized = .true. else ! If the system timers have already been defined, we want to flush the data call self%reset_all(soft = .false.) write(msg,'(3X,I4,A)') self%private_count, ' private timers registered and fully reset.' - call logger%log_information(msg, module=this_module) + call logger%log_information(msg, module=this_module, procedure=self%name) if (self%user_count > 0) then write(msg,'(3X,I4,A)') self%user_count, ' user defined timers registered and fully reset.' - call logger%log_information(msg, module=this_module) + call logger%log_information(msg, module=this_module, procedure=self%name) end if end if ! All subsequent timers that are added are user defined self%user_mode = .true. - ! We want to ensable timing - call set_timer_switch(.true.) - call logger%log_message('LightKrylov system timer initialization complete.', module=this_module) + call logger%log_message('Private timer initialization complete.', module=this_module, procedure=self%name) end subroutine initialize subroutine finalize(self) @@ -689,26 +711,27 @@ subroutine finalize(self) end do end do ic_user = icalled - if_time = .false. - call logger%log_message('LightKrylov timer finalization complete.', module=this_module) + call logger%log_message('Timer finalization complete.', module=this_module, procedure=self%name) call logger%log_message('######### Global timer summary #########', module=this_module) - call logger%log_message('Overview:', module=this_module) - write(msg, '(2X,A40,I5)') 'Total active timers:', self%timer_count + call logger%log_message('Overview:', module=this_module, procedure=self%name) + write(msg, '(2X,A60,I5)') 'Total active timers:', self%timer_count call logger%log_message(msg, module=this_module) - write(msg, '(2X,A40,I5)') 'User defined:', self%user_count + write(msg, '(2X,A60,I5)') 'User defined:', self%user_count call logger%log_message(msg, module=this_module) - write(msg, '(2X,A40,I5)') 'Called timers:', sum(ic) + ic_user + write(msg, '(2X,A60,I5)') 'Called timers:', sum(ic) + ic_user call logger%log_message(msg, module=this_module) do i = 1, self%group_count - associate(g => self%groups(i)) - call print_summary_header(g%name) - do j = g%istart, g%iend - call print_summary(self%timers(j)) - end do - end associate + if (ic(i) > 0) then + associate(g => self%groups(i)) + call print_summary_header(g%name, self%name) + do j = g%istart, g%iend + call print_summary(self%timers(j)) + end do + end associate + end if end do if (self%user_count > 0 .and. ic_user > 0) then - call print_summary_header('User-defined') + call print_summary_header('User-defined', self%name) do i = self%private_count + 1, self%timer_count call print_summary(self%timers(i)) end do @@ -720,12 +743,13 @@ end subroutine finalize ! Helper subroutines for pretty output !-------------------------------------------------------------- - subroutine print_summary_header(section_name) + subroutine print_summary_header(section_name, watch_name) !! Print section headers for the private and user defined timers character(len=*), intent(in) :: section_name + character(len=*), intent(in) :: watch_name ! internal character(len=128) :: msg - call logger%log_message(trim(section_name)//':', module=this_module) + call logger%log_message(trim(section_name)//':', module=this_module, procedure=watch_name) write(msg, fmt_h) 'name', 'calls', 'total (s)', 'avg (s)', 'min (s)', 'max (s)' call logger%log_message(msg, module=this_module) call logger%log_message('____________________________________________', module=this_module) From 77982f0d07640bef42df145512ee949b5b024969 Mon Sep 17 00:00:00 2001 From: Simon KERN Date: Wed, 27 Nov 2024 11:36:20 +0100 Subject: [PATCH 3/6] Updated use statements to reflect updates --- src/AbstractLinops.f90 | 3 ++- src/AbstractLinops.fypp | 3 ++- src/AbstractSystems.f90 | 3 ++- src/AbstractSystems.fypp | 3 ++- src/BaseKrylov.f90 | 3 +-- src/BaseKrylov.fypp | 3 +-- src/IterativeSolvers.f90 | 3 +-- src/IterativeSolvers.fypp | 3 +-- src/NewtonKrylov.f90 | 3 +-- src/NewtonKrylov.fypp | 3 +-- 10 files changed, 14 insertions(+), 16 deletions(-) diff --git a/src/AbstractLinops.f90 b/src/AbstractLinops.f90 index bbbae3b..5395579 100644 --- a/src/AbstractLinops.f90 +++ b/src/AbstractLinops.f90 @@ -12,7 +12,8 @@ module LightKrylov_AbstractLinops use stdlib_optval, only: optval use LightKrylov_Logger use LightKrylov_Constants - use LightKrylov_Timer_Utils + use LightKrylov_Timer_Utils, only: lightkrylov_timer + use LightKrylov_Timing, only: time_lightkrylov use LightKrylov_Utils use LightKrylov_AbstractVectors implicit none diff --git a/src/AbstractLinops.fypp b/src/AbstractLinops.fypp index d3e19e2..cd5ecc3 100644 --- a/src/AbstractLinops.fypp +++ b/src/AbstractLinops.fypp @@ -14,7 +14,8 @@ module LightKrylov_AbstractLinops use stdlib_optval, only: optval use LightKrylov_Logger use LightKrylov_Constants - use LightKrylov_Timer_Utils + use LightKrylov_Timer_Utils, only: lightkrylov_timer + use LightKrylov_Timing, only: time_lightkrylov use LightKrylov_Utils use LightKrylov_AbstractVectors implicit none diff --git a/src/AbstractSystems.f90 b/src/AbstractSystems.f90 index 9c26282..dddf73c 100644 --- a/src/AbstractSystems.f90 +++ b/src/AbstractSystems.f90 @@ -4,7 +4,8 @@ module LightKrylov_AbstractSystems use stdlib_optval, only: optval use LightKrylov_Logger use LightKrylov_Constants - use LightKrylov_Timer_Utils + use LightKrylov_Timer_Utils, only: lightkrylov_timer + use LightKrylov_Timing, only: time_lightkrylov use LightKrylov_AbstractVectors use LightKrylov_AbstractLinops implicit none diff --git a/src/AbstractSystems.fypp b/src/AbstractSystems.fypp index ed2e764..e33f0ba 100644 --- a/src/AbstractSystems.fypp +++ b/src/AbstractSystems.fypp @@ -6,7 +6,8 @@ module LightKrylov_AbstractSystems use stdlib_optval, only: optval use LightKrylov_Logger use LightKrylov_Constants - use LightKrylov_Timer_Utils + use LightKrylov_Timer_Utils, only: lightkrylov_timer + use LightKrylov_Timing, only: time_lightkrylov use LightKrylov_AbstractVectors use LightKrylov_AbstractLinops implicit none diff --git a/src/BaseKrylov.f90 b/src/BaseKrylov.f90 index d6f3097..5b3e434 100644 --- a/src/BaseKrylov.f90 +++ b/src/BaseKrylov.f90 @@ -21,8 +21,7 @@ module lightkrylov_BaseKrylov !------------------------------- use LightKrylov_Constants use LightKrylov_Logger - use LightKrylov_Timing, only: timer => global_lightkrylov_timer - use LightKrylov_Timer_Utils, only: time_lightkrylov + use LightKrylov_Timing, only: timer => global_lightkrylov_timer, time_lightkrylov use LightKrylov_Utils use LightKrylov_AbstractVectors use LightKrylov_AbstractLinops diff --git a/src/BaseKrylov.fypp b/src/BaseKrylov.fypp index 901a107..4ea999b 100644 --- a/src/BaseKrylov.fypp +++ b/src/BaseKrylov.fypp @@ -23,8 +23,7 @@ module lightkrylov_BaseKrylov !------------------------------- use LightKrylov_Constants use LightKrylov_Logger - use LightKrylov_Timing, only: timer => global_lightkrylov_timer - use LightKrylov_Timer_Utils, only: time_lightkrylov + use LightKrylov_Timing, only: timer => global_lightkrylov_timer, time_lightkrylov use LightKrylov_Utils use LightKrylov_AbstractVectors use LightKrylov_AbstractLinops diff --git a/src/IterativeSolvers.f90 b/src/IterativeSolvers.f90 index 0302ecb..ef8877f 100644 --- a/src/IterativeSolvers.f90 +++ b/src/IterativeSolvers.f90 @@ -31,8 +31,7 @@ module lightkrylov_IterativeSolvers use LightKrylov_Constants Use LightKrylov_Logger use LightKrylov_Utils - use LightKrylov_Timing, only: timer => global_lightkrylov_timer - use LightKrylov_Timer_Utils, only: time_lightkrylov + use LightKrylov_Timing, only: timer => global_lightkrylov_timer, time_lightkrylov use LightKrylov_AbstractVectors use LightKrylov_AbstractLinops use LightKrylov_BaseKrylov diff --git a/src/IterativeSolvers.fypp b/src/IterativeSolvers.fypp index f7eff80..2c37a43 100644 --- a/src/IterativeSolvers.fypp +++ b/src/IterativeSolvers.fypp @@ -33,8 +33,7 @@ module lightkrylov_IterativeSolvers use LightKrylov_Constants Use LightKrylov_Logger use LightKrylov_Utils - use LightKrylov_Timing, only: timer => global_lightkrylov_timer - use LightKrylov_Timer_Utils, only: time_lightkrylov + use LightKrylov_Timing, only: timer => global_lightkrylov_timer, time_lightkrylov use LightKrylov_AbstractVectors use LightKrylov_AbstractLinops use LightKrylov_BaseKrylov diff --git a/src/NewtonKrylov.f90 b/src/NewtonKrylov.f90 index ec494a1..3b75866 100644 --- a/src/NewtonKrylov.f90 +++ b/src/NewtonKrylov.f90 @@ -2,8 +2,7 @@ module LightKrylov_NewtonKrylov use stdlib_optval, only: optval use LightKrylov_Constants use LightKrylov_Logger - use LightKrylov_Timing, only: timer => global_lightkrylov_timer - use LightKrylov_Timer_Utils, only: time_lightkrylov + use LightKrylov_Timing, only: timer => global_lightkrylov_timer, time_lightkrylov use LightKrylov_AbstractVectors use LightKrylov_AbstractLinops use LightKrylov_AbstractSystems diff --git a/src/NewtonKrylov.fypp b/src/NewtonKrylov.fypp index 87fad3b..dbbc74b 100644 --- a/src/NewtonKrylov.fypp +++ b/src/NewtonKrylov.fypp @@ -4,8 +4,7 @@ module LightKrylov_NewtonKrylov use stdlib_optval, only: optval use LightKrylov_Constants use LightKrylov_Logger - use LightKrylov_Timing, only: timer => global_lightkrylov_timer - use LightKrylov_Timer_Utils, only: time_lightkrylov + use LightKrylov_Timing, only: timer => global_lightkrylov_timer, time_lightkrylov use LightKrylov_AbstractVectors use LightKrylov_AbstractLinops use LightKrylov_AbstractSystems From d35d08a8e989aa8cc91da37fa3301a54d8fcf784 Mon Sep 17 00:00:00 2001 From: Simon KERN Date: Wed, 27 Nov 2024 12:51:45 +0100 Subject: [PATCH 4/6] Increased width of counter format --- src/Timer_Utils.f90 | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Timer_Utils.f90 b/src/Timer_Utils.f90 index ae048eb..6b85ad6 100644 --- a/src/Timer_Utils.f90 +++ b/src/Timer_Utils.f90 @@ -127,10 +127,10 @@ end subroutine abstract_set_timers end interface ! format strings for uniform printing - character(len=128), parameter :: fmt_h = '(2X,A30," : ", 9X,A7,4(A15))' ! headers - character(len=128), parameter :: fmt_t = '(2X,A30," : ",A6,3X,I7,4(1X,F14.6))' ! data total - character(len=128), parameter :: fmt_r = '(2X,30X,3X, A6,I3,I7,4(1X,F14.6))' ! data reset - character(len=128), parameter :: fmt_n = '(2X,30X,3X, A6,I3,I7,A60)' ! not called + character(len=128), parameter :: fmt_h = '(2X,A30," : ", 9X,A9,4(A15))' ! headers + character(len=128), parameter :: fmt_t = '(2X,A30," : ",A6,3X,I9,4(1X,F14.6))' ! data total + character(len=128), parameter :: fmt_r = '(2X,30X,3X, A6,I3,I9,4(1X,F14.6))' ! data reset + character(len=128), parameter :: fmt_n = '(2X,30X,3X, A6,I3,I9,A60)' ! not called contains From 5af8b80d4aee5321418eb089e0aaeb3ae6c397da Mon Sep 17 00:00:00 2001 From: Simon KERN Date: Wed, 27 Nov 2024 13:15:30 +0100 Subject: [PATCH 5/6] cleanup --- src/Timer_Utils.f90 | 44 +++++++++++++++----------------------------- 1 file changed, 15 insertions(+), 29 deletions(-) diff --git a/src/Timer_Utils.f90 b/src/Timer_Utils.f90 index 6b85ad6..2f040b3 100644 --- a/src/Timer_Utils.f90 +++ b/src/Timer_Utils.f90 @@ -239,13 +239,13 @@ subroutine reset_timer(self, soft, clean, verbose) call logger%log_message('Timer "'//trim(self%name)//'" is curently running. Stopping timer before reset.', & & module=this_module, procedure='reset_timer') end if - if (save_data) then - write(msg,'(A,A)') trim(self%name), ': soft reset.' - if (print_info) then - call logger%log_message(msg, module=this_module) - else - call logger%log_debug(msg, module=this_module) - end if + write(msg,'(A,L,3X,A,L)') 'soft reset: ', save_data, 'flush timers: ', flush_timer + if (print_info) then + call logger%log_message(msg, module=this_module, procedure=self%name) + else + call logger%log_debug(msg, module=this_module, procedure=self%name) + end if + if (save_data .and. .not. flush_timer) then if (self%local_count > 0) then call self%save_timer_data() self%etime = 0.0_dp @@ -258,12 +258,6 @@ subroutine reset_timer(self, soft, clean, verbose) end if else ! hard reset - write(msg,'(A,A)') trim(self%name), ': hard reset.' - if (print_info) then - call logger%log_message(msg, module=this_module) - else - call logger%log_debug(msg, module=this_module) - end if self%etime = 0.0_dp self%etime_pause = 0.0_dp self%etime_min = huge(1.0_dp) @@ -279,12 +273,6 @@ subroutine reset_timer(self, soft, clean, verbose) if(allocated(self%count_data)) deallocate(self%count_data) end if if (flush_timer) then - write(msg,'(A,A)') trim(self%name), ': data flushed.' - if (print_info) then - call logger%log_message(msg, module=this_module) - else - call logger%log_debug(msg, module=this_module) - end if self%count = 0 self%is_finalized = .false. end if @@ -522,11 +510,9 @@ subroutine reset_all(self, soft, clean) call self%timers(i)%reset(soft, clean, verbose=.false.) end do write(msg,'(A,2(A,I0))') 'All timers reset: ', 'private: ', self%private_count, ', user: ', self%user_count - call logger%log_message(msg, module=this_module) - write(msg,'(2X,A,L)') 'soft reset: ', soft_ - call logger%log_message(msg, module=this_module) - write(msg,'(2X,A,L)') 'flush timers: ', clean_ - call logger%log_message(msg, module=this_module) + call logger%log_message(msg, module=this_module, procedure=self%name) + write(msg,'(A,L,3X,A,L)') 'soft reset: ', soft_, 'flush timers: ', clean_ + call logger%log_message(msg, module=this_module, procedure=self%name) end subroutine reset_all subroutine start_timer_by_name(self, name) @@ -545,7 +531,7 @@ subroutine start_timer_by_name(self, name) else call self%timers(id)%start() end if - call logger%log_debug('Timer "'//trim(tname)//'" started.', module=this_module) + call logger%log_debug('Timer "'//trim(tname)//'" started.', module=this_module, procedure=self%name) end subroutine start_timer_by_name subroutine stop_timer_by_name(self, name) @@ -564,7 +550,7 @@ subroutine stop_timer_by_name(self, name) else call self%timers(id)%stop() end if - call logger%log_debug('Timer "'//trim(tname)//'" stopped.', module=this_module) + call logger%log_debug('Timer "'//trim(tname)//'" stopped.', module=this_module, procedure=self%name) end subroutine stop_timer_by_name subroutine pause_timer_by_name(self, name) @@ -583,7 +569,7 @@ subroutine pause_timer_by_name(self, name) else call self%timers(id)%pause() end if - call logger%log_debug('Timer "'//trim(tname)//'" paused.', module=this_module) + call logger%log_debug('Timer "'//trim(tname)//'" paused.', module=this_module, procedure=self%name) end subroutine subroutine reset_timer_by_name(self, name, soft, clean) @@ -637,7 +623,7 @@ subroutine enumerate(self, only_user) fmt_e = '(2X,I3,A50," :",3(1X,I0))' only_user_ = optval(only_user, .false.) if (.not. only_user_) then - call logger%log_message('Registered timers: all', module=this_module) + call logger%log_message('Registered timers: all', module=this_module, procedure=self%name) do i = 1, self%group_count call logger%log_message(trim(self%groups(i)%name)//":", module=this_module) do j = self%groups(i)%istart, self%groups(i)%iend @@ -649,7 +635,7 @@ subroutine enumerate(self, only_user) end do end if if (self%user_count > 0) then - call logger%log_message('Registered timers: user', module=this_module) + call logger%log_message('Registered timers: user', module=this_module, procedure=self%name) do i = self%private_count+1, self%timer_count associate (t => self%timers(i)) write(msg,fmt_e) i, trim(t%name), t%count, t%local_count, t%reset_count From 887afb9e9a84dcc8e9cad5abd48758acb3dfac2f Mon Sep 17 00:00:00 2001 From: Simon KERN Date: Wed, 27 Nov 2024 14:45:21 +0100 Subject: [PATCH 6/6] Added user-defined timers to examples --- example/ginzburg_landau/main.f90 | 1 + example/roessler/main.f90 | 46 +++++++++++++++----- src/Timer.f90 | 12 ++--- src/Timer_Utils.f90 | 75 +++++++++++++++++--------------- 4 files changed, 84 insertions(+), 50 deletions(-) diff --git a/example/ginzburg_landau/main.f90 b/example/ginzburg_landau/main.f90 index 94e1112..7822169 100644 --- a/example/ginzburg_landau/main.f90 +++ b/example/ginzburg_landau/main.f90 @@ -48,6 +48,7 @@ program demo !> Set up timing call timer%initialize() + call timer%add_timer('Ginzburg-Landau example', start=.true.) !> Initialize physical parameters. call initialize_parameters() diff --git a/example/roessler/main.f90 b/example/roessler/main.f90 index 09bda8b..778fdcb 100644 --- a/example/roessler/main.f90 +++ b/example/roessler/main.f90 @@ -52,6 +52,8 @@ program demo ! Set up timing call timer%initialize() + call timer%add_timer('Roessler example (total)', start=.true.) + call timer%add_timer('Chaotic attractor', start=.true.) ! Initialize baseflow and perturbation state vectors call bf%zero(); call dx%zero(); call residual%zero() @@ -74,6 +76,9 @@ program demo print data_fmt, 'Final position :', eval(1), eval(2), eval(3), Tend print *, '' + call timer%stop('Chaotic attractor') + call timer%add_timer('Newton iteration (const. tol)', start=.true.) + print *, '########################################################################################' print '(A,E9.2,A)', ' # Newton iteration with constant tolerance (tol=', tol, ') #' print *, '########################################################################################' @@ -91,11 +96,6 @@ program demo sys%jacobian = jacobian() sys%jacobian%X = bf - ! Reset eval timer - call sys%reset_timer() - ! Reset system timers - call timer%reset_all() - ! Set tolerance tol = 1e-12_wp @@ -109,6 +109,12 @@ program demo print data_fmt, 'Solution residual:', residual%x, residual%y, residual%z, residual%T print *, '' + ! Reset timers + call timer%stop('Newton iteration (const. tol)') + call sys%reset_timer() + call timer%reset_all() + call timer%add_timer('Newton iteration (dyn. tol)', start=.true.) + print *, '########################################################################################' print '(A,E9.2,A)', ' # Newton iteration with dynamic tolerances (target=', tol, ') #' print *, '########################################################################################' @@ -130,6 +136,12 @@ program demo print data_fmt, 'Solution residual:', residual%x, residual%y, residual%z, residual%T print *, '' + ! Reset timers + call timer%stop('Newton iteration (dyn. tol)') + call sys%reset_timer() + call timer%reset_all() + call timer%add_timer('Monodromy matrix & Floquet exp.', start=.true.) + print *, '########################################################################################' print *, '# Monodromy matrix and floquet exponents #' print *, '########################################################################################' @@ -138,11 +150,6 @@ program demo ! Compute the stability of the orbit sys%jacobian = floquet_operator() sys%jacobian%X = bf ! <- periodic orbit - - ! Reset eval timer - call sys%reset_timer() - ! Reset system timers - call timer%reset_all() M = 0.0_wp Id = eye(npts) @@ -160,6 +167,12 @@ program demo end do print *, '' + ! Reset timers + call timer%stop('Monodromy matrix & Floquet exp.') + call sys%reset_timer() + call timer%reset_all() + call timer%add_timer('OTD modes - fixed-point', start=.true.) + print *, '########################################################################################' print *, '# Optimally Time-Dependent (OTD) modes on fixed point #' print *, '########################################################################################' @@ -207,6 +220,13 @@ program demo print '(A16,1X,*(F16.9,1X))', 'Reference ', EV_ref print *, '' print '(A10,F6.3,1X,*(F16.9,1X))', 'OTD: t=', Tend, eval(1:r) + + ! Reset timers + call timer%stop('OTD modes - fixed-point') + call sys%reset_timer() + call timer%reset_all() + call timer%add_timer('OTD modes - periodic orbit', start=.true.) + print *, '' print *, '########################################################################################' print *, '# Optimally Time-Dependent (OTD) modes on periodic orbit #' @@ -231,6 +251,12 @@ program demo call rename(report_file_OTD_LE, 'example/roessler/PO_LE.txt') print *, '' + ! Reset timers + call timer%stop('OTD modes - periodic orbit') + call sys%reset_timer() + call timer%reset_all() + call timer%add_timer('OTD modes - route to chaos', start=.true.) + print *, '' print *, '########################################################################################' print *, '# Optimally Time-Dependent (OTD) modes on Route to Chaos #' diff --git a/src/Timer.f90 b/src/Timer.f90 index 2cb7d88..ac183f8 100644 --- a/src/Timer.f90 +++ b/src/Timer.f90 @@ -55,7 +55,7 @@ subroutine set_lightkrylov_timers(self) call self%set_watch_name('LightKrylov_timer') ! timers for LightKrylov_BaseKrylov ! rsp - call self%add_timer('qr_with_pivoting_rsp', istart) + call self%add_timer('qr_with_pivoting_rsp', count=istart) call self%add_timer('qr_no_pivoting_rsp') call self%add_timer('orthonormalize_basis_rsp') call self%add_timer('orthonormalize_vector_against_basis_rsp') @@ -97,12 +97,12 @@ subroutine set_lightkrylov_timers(self) call self%add_timer('dgs_basis_against_basis_cdp') call self%add_timer('arnoldi_cdp') call self%add_timer('lanczos_bidiagonalization_cdp') - call self%add_timer('lanczos_tridiagonalization_cdp', iend) + call self%add_timer('lanczos_tridiagonalization_cdp', count=iend) ! define BaseKrylov group call self%add_group('BaseKrylov', istart=istart, iend=iend) ! timers for LightKrylov_IterativeSolvers ! rsp - call self%add_timer('eigs_rsp', istart) + call self%add_timer('eigs_rsp', count=istart) call self%add_timer('eighs_rsp') call self%add_timer('svds_rsp') call self%add_timer('gmres_rsp') @@ -128,18 +128,18 @@ subroutine set_lightkrylov_timers(self) call self%add_timer('svds_cdp') call self%add_timer('gmres_cdp') call self%add_timer('fgmres_cdp') - call self%add_timer('cg_cdp', iend) + call self%add_timer('cg_cdp', count=iend) ! define IterativeSolvers group call self%add_group('IterativeSolvers', istart=istart, iend=iend) ! timers for LightKrylov_NewtonKrylov ! rsp - call self%add_timer('newton_rsp', istart) + call self%add_timer('newton_rsp', count=istart) ! rdp call self%add_timer('newton_rdp') ! csp call self%add_timer('newton_csp') ! cdp - call self%add_timer('newton_cdp', iend) + call self%add_timer('newton_cdp', count=iend) ! define NewtonKrylov group call self%add_group('NewtonKrylov', istart=istart, iend=iend) ! Enable timing diff --git a/src/Timer_Utils.f90 b/src/Timer_Utils.f90 index 2f040b3..170e072 100644 --- a/src/Timer_Utils.f90 +++ b/src/Timer_Utils.f90 @@ -235,46 +235,46 @@ subroutine reset_timer(self, soft, clean, verbose) flush_timer = optval(clean, .false.) print_info = optval(verbose, .false.) if (self%running) then - call self%stop() - call logger%log_message('Timer "'//trim(self%name)//'" is curently running. Stopping timer before reset.', & + call logger%log_message('Timer "'//trim(self%name)//'" is curently running. Timer not reset.', & & module=this_module, procedure='reset_timer') - end if - write(msg,'(A,L,3X,A,L)') 'soft reset: ', save_data, 'flush timers: ', flush_timer - if (print_info) then - call logger%log_message(msg, module=this_module, procedure=self%name) else - call logger%log_debug(msg, module=this_module, procedure=self%name) - end if - if (save_data .and. .not. flush_timer) then - if (self%local_count > 0) then - call self%save_timer_data() + write(msg,'(A,L,3X,A,L)') 'soft reset: ', save_data, 'flush timers: ', flush_timer + if (print_info) then + call logger%log_message(msg, module=this_module, procedure=self%name) + else + call logger%log_debug(msg, module=this_module, procedure=self%name) + end if + if (save_data .and. .not. flush_timer) then + if (self%local_count > 0) then + call self%save_timer_data() + self%etime = 0.0_dp + self%etime_pause = 0.0_dp + self%start_time = 0.0_dp + self%etime_min = huge(1.0_dp) + self%etime_max = 0.0_dp + self%running = .false. + self%local_count = 0 + end if + else + ! hard reset self%etime = 0.0_dp self%etime_pause = 0.0_dp - self%start_time = 0.0_dp self%etime_min = huge(1.0_dp) self%etime_max = 0.0_dp + self%start_time = 0.0_dp self%running = .false. self%local_count = 0 + self%reset_count = 0 + if(allocated(self%etime_data)) deallocate(self%etime_data) + if(allocated(self%etmin_data)) deallocate(self%etmin_data) + if(allocated(self%etmax_data)) deallocate(self%etmax_data) + if(allocated(self%etavg_data)) deallocate(self%etavg_data) + if(allocated(self%count_data)) deallocate(self%count_data) + end if + if (flush_timer) then + self%count = 0 + self%is_finalized = .false. end if - else - ! hard reset - self%etime = 0.0_dp - self%etime_pause = 0.0_dp - self%etime_min = huge(1.0_dp) - self%etime_max = 0.0_dp - self%start_time = 0.0_dp - self%running = .false. - self%local_count = 0 - self%reset_count = 0 - if(allocated(self%etime_data)) deallocate(self%etime_data) - if(allocated(self%etmin_data)) deallocate(self%etmin_data) - if(allocated(self%etmax_data)) deallocate(self%etmax_data) - if(allocated(self%etavg_data)) deallocate(self%etavg_data) - if(allocated(self%count_data)) deallocate(self%count_data) - end if - if (flush_timer) then - self%count = 0 - self%is_finalized = .false. end if end subroutine reset_timer @@ -363,14 +363,17 @@ end subroutine finalize_timer ! Type-bound procedures for abstract_watch type !-------------------------------------------------------------- - subroutine add_timer(self, name, count) - !! Type-bound to abstract_watch: Add timer to watch + subroutine add_timer(self, name, start, count) + !! Type-bound to abstract_watch: Add timer to watch and optionally start it immediately !! Note: The new timer name must be unique class(abstract_watch), intent(inout) :: self character(len=*), intent(in) :: name + logical, optional, intent(in) :: start integer, optional, intent(out) :: count ! internal + logical :: start_ character(len=128) :: msg, tname + start_ = optval(start, .false.) tname = to_lower(name) if (self%timer_count == 0) then allocate(self%timers(1)) @@ -388,6 +391,7 @@ subroutine add_timer(self, name, count) write(msg,'(A,I0)') 'Timer "'//trim(tname)//'" added: timer_count: ', self%timer_count call logger%log_debug(msg, module=this_module) if (present(count)) count = self%timer_count + if (start_) call self%start(tname) end subroutine add_timer subroutine remove_timer(self, name, count) @@ -759,7 +763,10 @@ subroutine print_summary(t) etmax = max(etmax, t%etmax_data(i)) end if end do - if (count > 0) then + if (count == 1) then + write(msg,'(2X,A30," : ",A6,3X,I9,1X,F14.6,3(A15))') trim(t%name), 'total', count, t%etime_data(1), '-', '-', '-' + call logger%log_message(msg, module=this_module) + else if (count > 1) then etime = sum(t%etime_data) etavg = sum(t%etavg_data)/count2 write(msg,fmt_t) trim(t%name), 'total', count, etime, etavg, etmin, etmax