source: codes/icosagcm/devel/src/base/profiling.f90 @ 714

Last change on this file since 714 was 714, checked in by dubos, 6 years ago

devel : backported from trunk commits r607,r648,r649,r667,r668,r669,r706

File size: 2.4 KB
Line 
1MODULE profiling_mod
2  IMPLICIT NONE
3  SAVE
4  PRIVATE
5
6  INTEGER, PARAMETER :: max_id=20, max_depth=10
7  INTEGER :: nb_id=-10, depth=-10, current_id(max_depth)
8  CHARACTER(10), DIMENSION(max_id) :: name
9  REAL :: chrono(max_depth), elapsed(max_id)
10
11  PUBLIC :: init_profiling, register_id, enter_profile, exit_profile, print_profile
12
13CONTAINS
14
15  SUBROUTINE init_profiling
16    !$OMP MASTER
17    nb_id=0
18    depth=0
19    elapsed(:)=0
20    !$OMP END MASTER
21  END SUBROUTINE init_profiling
22
23  SUBROUTINE register_id(thename, id)
24    CHARACTER(*), INTENT(IN) :: thename
25    INTEGER, INTENT(OUT) :: id
26    !$OMP MASTER
27    nb_id = nb_id+1
28    id = nb_id
29    name(id)=thename
30    !$OMP END MASTER
31  END SUBROUTINE register_id
32
33  FUNCTION get_elapsed(start)
34    INTEGER(kind=8) :: count, count_rate
35    REAL :: start,get_elapsed
36    CALL SYSTEM_CLOCK(count,count_rate)
37    get_elapsed = (1.*count)/(1.*count_rate) - start
38    IF(get_elapsed<0.) get_elapsed=0.
39  END FUNCTION get_elapsed
40
41  SUBROUTINE enter_profile(id)
42    INTEGER, INTENT(IN) :: id
43    REAL :: my_chrono
44    !$OMP MASTER
45    depth = depth+1
46    chrono(depth) = get_elapsed(0.)
47    current_id(depth) = id
48    !$OMP END MASTER
49  END SUBROUTINE enter_profile
50   
51  SUBROUTINE exit_profile(id)
52    INTEGER, INTENT(IN) :: id
53    INTEGER :: parent_id
54    REAL :: my_elapsed
55    !$OMP MASTER
56    IF(depth<=0) THEN
57       PRINT *, 'exit_profile called at depth=0 !!'
58       STOP
59    END IF
60    IF(id /= current_id(depth)) THEN
61       PRINT *,' exit_profile : at depth ', depth, ' exiting ', TRIM(name(id)), ' after entering ', TRIM(name(current_id(depth)))
62       STOP
63    END IF
64    my_elapsed = get_elapsed(chrono(depth))
65    ! add elapsed to current profile
66    elapsed(id) = elapsed(id) + my_elapsed
67    depth = depth-1
68    ! and substract from parent profile
69    IF(depth>0) THEN
70       parent_id = current_id(depth)
71       elapsed(parent_id) = elapsed(parent_id) - my_elapsed
72    END IF
73    !$OMP END MASTER
74  END SUBROUTINE exit_profile
75
76  SUBROUTINE print_profile
77    INTEGER :: i
78    REAL :: total
79    !$OMP MASTER
80    PRINT *, '---------------------- Profiling -----------------------'
81    total = SUM(elapsed(1:nb_id))
82    PRINT *, 'Total (s) : ', total
83    DO i=1,nb_id
84       PRINT *, name(i), INT(elapsed(i)), INT(1000.*elapsed(i)/total)
85    END DO
86    PRINT *, '---------------------- Profiling -----------------------'
87    !$OMP END MASTER
88  END SUBROUTINE print_profile
89   
90END MODULE profiling_mod
Note: See TracBrowser for help on using the repository browser.