Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion profiler/AbstractMeterNode.F90
Original file line number Diff line number Diff line change
Expand Up @@ -153,7 +153,7 @@ function i_get_inclusive(this) result(inclusive)
use, intrinsic :: iso_fortran_env, only: REAL64
import AbstractMeterNode
real(kind=REAL64) :: inclusive
class(AbstractMeterNode), intent(in) :: this
class(AbstractMeterNode), target, intent(in) :: this
end function i_get_inclusive

subroutine i_reset(this)
Expand Down
7 changes: 4 additions & 3 deletions profiler/BaseProfiler.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ module mapl_BaseProfiler
private
type(MeterNode) :: root_node
type(MeterNodeStack) :: stack
integer :: status = 0
integer :: status
integer :: comm_world
contains
procedure :: start_name
Expand All @@ -53,8 +53,8 @@ module mapl_BaseProfiler
procedure :: get_root_node
procedure :: get_status
procedure :: copy_profiler
procedure(copy_profiler), deferred :: copy
generic :: assignment(=) => copy
!# procedure(copy_profiler), deferred :: copy
!# generic :: assignment(=) => copy

procedure :: reset
procedure :: accumulate
Expand Down Expand Up @@ -102,6 +102,7 @@ subroutine start_self(this, unusable, rc)

logical :: empty_stack

this%status = 0
empty_stack = .true.
!$omp master
if (this%stack%size()/= 0) this%status = INCORRECTLY_NESTED_METERS
Expand Down
3 changes: 2 additions & 1 deletion profiler/DistributedProfiler.F90
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
#include "MAPL.h"
module MAPL_DistributedProfiler
use MAPL_AbstractMeter
use MAPL_AbstractGauge
Expand All @@ -20,7 +21,7 @@ module MAPL_DistributedProfiler
contains
procedure :: make_meter
procedure :: reduce
procedure :: copy
!# procedure :: copy
end type DistributedProfiler

interface DistributedProfiler
Expand Down
5 changes: 3 additions & 2 deletions profiler/MemoryProfiler.F90
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
#include "MAPL_ErrLog.h"
#include "MAPL.h"
module MAPL_MemoryProfiler_private
use MAPL_BaseProfiler, only: BaseProfiler
use MAPL_BaseProfiler, only: MemoryProfilerIterator => BaseProfilerIterator
Expand Down Expand Up @@ -53,7 +53,8 @@ subroutine copy(new, old)
class(MemoryProfiler), target, intent(inout) :: new
class(BaseProfiler), target, intent(in) :: old

call new%copy_profiler(old)
_HERE
!# call new%copy_profiler(old)

end subroutine copy

Expand Down
32 changes: 16 additions & 16 deletions profiler/MeterNode.F90
Original file line number Diff line number Diff line change
Expand Up @@ -37,8 +37,8 @@ module MAPL_MeterNode
procedure :: accumulate
procedure :: reset

procedure :: begin
procedure :: end
procedure :: begin => node_begin
procedure :: end => node_end
end type MeterNode


Expand All @@ -56,7 +56,7 @@ module MAPL_MeterNode
procedure :: get_meter => get_meter_iter
procedure :: equals
procedure :: not_equals
procedure :: next
procedure :: next => node_next
end type MeterNodeIterator


Expand Down Expand Up @@ -110,14 +110,14 @@ end function get_name

function get_inclusive(this) result(inclusive)
real(kind=REAL64) :: inclusive
class (MeterNode), intent(in) :: this
class (MeterNode), target, intent(in) :: this
inclusive = this%meter%get_total()
end function get_inclusive


function get_exclusive(this) result(exclusive)
real(kind=REAL64) :: exclusive
class (MeterNode), intent(in) :: this
class (MeterNode), target, intent(in) :: this

type (MeterNodevectorIterator) :: iter
class (AbstractMeterNode), pointer :: child
Expand All @@ -133,7 +133,7 @@ function get_exclusive(this) result(exclusive)

iter = this%children%begin()
do while (iter /= this%children%end())
child => iter%get()
child => iter%of()
tmp = tmp - child%get_inclusive()
call iter%next()
end do
Expand Down Expand Up @@ -239,7 +239,7 @@ recursive integer function get_num_nodes(this) result(num_nodes)
num_nodes = 1
iter = this%children%begin()
do while (iter /= this%children%end())
child => iter%get()
child => iter%of()
num_nodes = num_nodes + child%get_num_nodes()
call iter%next()
end do
Expand All @@ -266,18 +266,18 @@ function new_MeterNodeIterator(meter_node) result(iterator)
end function new_MeterNodeIterator


function begin(this) result(iterator)
function node_begin(this) result(iterator)
class (AbstractMeterNodeIterator), allocatable :: iterator
class (MeterNode), target, intent(in) :: this

!!$ iterator = MeterNodeIterator(this)
allocate(iterator, source=MeterNodeIterator(this))

end function begin
end function node_begin



function end(this) result(iterator)
function node_end(this) result(iterator)
class (AbstractMeterNodeIterator), allocatable :: iterator
class (MeterNode), target, intent(in) :: this

Expand All @@ -294,10 +294,10 @@ function end(this) result(iterator)
print*,'uh oh'
end select

end function end
end function node_end


recursive subroutine next(this)
recursive subroutine node_next(this)
class (MeterNodeIterator), intent(inout) :: this
class (AbstractMeterNode), pointer :: current_child

Expand All @@ -307,7 +307,7 @@ recursive subroutine next(this)
if (.not. allocated(this%iterator_over_children)) then
this%iterator_over_children = this%reference%children%begin()
if (this%iterator_over_children /= this%reference%children%end()) then
current_child => this%iterator_over_children%get()
current_child => this%iterator_over_children%of()
this%iterator_of_current_child = current_child%begin()
this%current => this%iterator_of_current_child%get()
else
Expand All @@ -323,14 +323,14 @@ recursive subroutine next(this)
if (this%iterator_over_children == this%reference%children%end()) then ! done
deallocate(this%iterator_over_children)
else
current_child => this%iterator_over_children%get()
current_child => this%iterator_over_children%of()
this%iterator_of_current_child = current_child%begin() ! always at least one node
this%current => this%iterator_of_current_child%get()
end if
end if
end if

end subroutine next
end subroutine node_next


function get(this) result(tree)
Expand Down Expand Up @@ -395,7 +395,7 @@ recursive subroutine reset(this)

iter = this%children%begin()
do while (iter /= this%children%end())
child => iter%get()
child => iter%of()
call child%reset()
call iter%next()
end do
Expand Down
19 changes: 10 additions & 9 deletions profiler/MeterNodeVector.F90
Original file line number Diff line number Diff line change
@@ -1,15 +1,16 @@
module MAPL_MeterNodeVector
use MAPL_AbstractMeterNode

#define _type class (AbstractMeterNode)
#define _allocatable
#define _vector MeterNodeVector
#define _iterator MeterNodeVectorIterator
#include "templates/vector.inc"
#define T AbstractMeterNode
#define T_polymorphic
#define Vector MeterNodeVector
#define VectorIterator MeterNodeVectorIterator

#undef _iterator
#undef _vector
#undef _pointer
#undef _type
#include "vector/template.inc"

#undef VectorIterator
#undef Vector
#undef T_polymorphic
#undef T

end module MAPL_MeterNodeVector
5 changes: 3 additions & 2 deletions profiler/StubProfiler.F90
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
#include "MAPL_ErrLog.h"
#include "MAPL.h"
module MAPL_StubProfiler
use MAPL_BaseProfiler, only: BaseProfiler
use MAPL_DistributedProfiler
Expand Down Expand Up @@ -62,7 +62,8 @@ subroutine copy(new, old)
class(StubProfiler), target, intent(inout) :: new
class(BaseProfiler), target, intent(in) :: old

call new%copy_profiler(old)
_HERE
!# call new%copy_profiler(old)

end subroutine copy

Expand Down
6 changes: 3 additions & 3 deletions profiler/TimeProfiler.F90
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
#include "unused_dummy.H"
#include "MAPL_ErrLog.h"
#include "MAPL.h"

module mapl_TimeProfiler_private
use mapl_BaseProfiler, only: BaseProfiler
Expand Down Expand Up @@ -49,7 +48,8 @@ subroutine copy(new, old)
class(TimeProfiler), target, intent(inout) :: new
class(BaseProfiler), target, intent(in) :: old

call new%copy_profiler(old)
_HERE
!# call new%copy_profiler(old)

end subroutine copy

Expand Down
Loading