-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathnormal.f90
executable file
·132 lines (107 loc) · 4.23 KB
/
normal.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
!
! The following times are measured:
!
! o each phase each time through the loop
! o total time for each phase
! o the total time
!
! There will be printed output that should not be included in the measured time.
!
module M_stopwatch__globals_3
use M_stopwatch
implicit none
private
public :: watchgroup
public :: setup_watches
type (watchgroup), public :: ALL_GROUPS ! the group with all the watches; global var
type (watchtype), public, dimension(5) :: w
! The watches are: w(1) time for phase 1 this time through the loop
! w(2) time for phase 2 this time through the loop
! w(3) total time for phase 1
! w(4) total time for phase 2
! w(5) total time
! The watch groups are: GROUPS_FOR_ONE phase 1 times w(1) and w(3)
! GROUPS_FOR_TWO phase 2 times w(2) and w(4)
! ALL_GROUPS all of them (declared in module M_stopwatch__globals_3)
type (watchgroup), public :: GROUPS_FOR_ONE, GROUPS_FOR_TWO
contains
subroutine setup_watches
call option_stopwatch(default_clock=(/"cpu ","wall"/)) ! Measure only cpu and wall time
call create_watch(w,name=(/ "phase 1 ", & ! create the watches
"phase 2 ", &
"total phase 1", &
"total phase 2", &
"Total " /) )
call create_watchgroup(w(1),GROUPS_FOR_ONE) ! create the groups
call join_watchgroup(w(3),GROUPS_FOR_ONE)
call create_watchgroup(w(2:4:2),GROUPS_FOR_TWO) ! a shorter way
call create_watchgroup(w,ALL_GROUPS)
call start_watch(w(5)) ! start the total time
end subroutine setup_watches
end module M_stopwatch__globals_3
module M_stopwatch__workers_normal
implicit none
! The routines being measured
public :: subone
contains
subroutine subone(n,c) ! just to give us something to time.
use M_stopwatch
use M_stopwatch__globals_3
integer, intent(in) :: n
real, intent(out) :: c
integer :: i
real :: a=2.0,b
b=real(n)
do i=1,n
c=a*b
end do
call pause_watch(ALL_GROUPS)
write(unit=*,fmt=*) "Performed ",n," multiplications"
call end_pause_watch(ALL_GROUPS)
end subroutine subone
end module M_stopwatch__workers_normal
program advanced
use M_stopwatch
use M_stopwatch__globals_3
use M_stopwatch__workers_normal
implicit none
integer :: i, nmult ! loop counter, number of multiplies to do
logical :: cpu_is_there ! flag for cpu clock
real :: zz
call setup_watches()
nmult = 200000
do i=1,3
write(*,'(a)')repeat('=',80)
write(*,*)'LOOP',i,':'
call reset_watch(w(1:2)) ! reset the watches that measure the time for this loop
call start_watch(GROUPS_FOR_ONE) ! start the phase 1 watches, do phase 1, and stop the phase 1 watches
nmult = 5*nmult
call subone(nmult,zz)
call stop_watch(GROUPS_FOR_ONE)
call start_watch(GROUPS_FOR_TWO) ! same for phase 2
nmult = 2*nmult
call subone(nmult,zz)
call stop_watch(GROUPS_FOR_TWO)
! pause the cpu clock of the total time watch while printing the current times,
! if the cpu clock is available on this implementation, but leave the wall
! clock running. The call to inquiry_stopwatch should be outside the loop, but
! this should make a clearer illustration.
call inquiry_stopwatch(cpu_avail=cpu_is_there)
if (cpu_is_there) then
call pause_watch(w(5),"cpu")
end if
write(*,'(a)')repeat('-',80)
call print_watch(w(1:2),title="Times for this loop")
write(*,'(a)')repeat('-',80)
call print_watch(w(3:4),title="Total times so far")
if (cpu_is_there) then
call end_pause_watch(w(5),"cpu")
end if
end do
write(*,'(a)')repeat('=',80)
call print_watch([w(3),w(4),w(5)],title="Final total times") ! print the total times
write(unit=*,fmt=*)"Note: the difference between the sum of the first two wall clocks"
write(unit=*,fmt=*)" and the Total wall clock is due to not pausing the wall clock"
write(unit=*,fmt=*)" on the Total watch while printing."
call destroy_watch(w) ! destroy the watches
end program advanced