source: codes/icosagcm/trunk/src/base/profiling.f90 @ 953

Last change on this file since 953 was 899, checked in by adurocher, 5 years ago

trunk : Fixed GCC warnings

Fixed iso c bindings
fixed warnings with -Wall -Wno-aliasing -Wno-unused -Wno-unused-dummy-argument -Wno-maybe-uninitialized -Wno-tabs warnings
Removed all unused variables (-Wunused-variable)
vector%dot_product is now dot_product_3d to avoid compilation warning "dot_product shadows intrinsic" with GCC

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    !$OMP MASTER
44    depth = depth+1
45    chrono(depth) = get_elapsed(0.)
46    current_id(depth) = id
47    !$OMP END MASTER
48  END SUBROUTINE enter_profile
49   
50  SUBROUTINE exit_profile(id)
51    INTEGER, INTENT(IN) :: id
52    INTEGER :: parent_id
53    REAL :: my_elapsed
54    !$OMP MASTER
55    IF(depth<=0) THEN
56       PRINT *, 'exit_profile called at depth=0 !!'
57       STOP
58    END IF
59    IF(id /= current_id(depth)) THEN
60       PRINT *,' exit_profile : at depth ', depth, ' exiting ', TRIM(name(id)), ' after entering ', TRIM(name(current_id(depth)))
61       STOP
62    END IF
63    my_elapsed = get_elapsed(chrono(depth))
64    ! add elapsed to current profile
65    elapsed(id) = elapsed(id) + my_elapsed
66    depth = depth-1
67    ! and substract from parent profile
68    IF(depth>0) THEN
69       parent_id = current_id(depth)
70       elapsed(parent_id) = elapsed(parent_id) - my_elapsed
71    END IF
72    !$OMP END MASTER
73  END SUBROUTINE exit_profile
74
75  SUBROUTINE print_profile
76    INTEGER :: i
77    REAL :: total
78    !$OMP MASTER
79    PRINT *, '---------------------- Profiling -----------------------'
80    total = SUM(elapsed(1:nb_id))
81    PRINT *, 'Total (s) : ', total
82    DO i=1,nb_id
83       PRINT *, name(i), INT(elapsed(i)), INT(1000.*elapsed(i)/total)
84    END DO
85    PRINT *, '---------------------- Profiling -----------------------'
86    !$OMP END MASTER
87  END SUBROUTINE print_profile
88   
89END MODULE profiling_mod
Note: See TracBrowser for help on using the repository browser.