MODULE profiling_mod IMPLICIT NONE SAVE PRIVATE INTEGER, PARAMETER :: max_id=20, max_depth=10 INTEGER :: nb_id=-10, depth=-10, current_id(max_depth) CHARACTER(10), DIMENSION(max_id) :: name REAL :: chrono(max_depth), elapsed(max_id) PUBLIC :: init_profiling, register_id, enter_profile, exit_profile, print_profile CONTAINS SUBROUTINE init_profiling !$OMP MASTER nb_id=0 depth=0 elapsed(:)=0 !$OMP END MASTER END SUBROUTINE init_profiling SUBROUTINE register_id(thename, id) CHARACTER(*), INTENT(IN) :: thename INTEGER, INTENT(OUT) :: id !$OMP MASTER nb_id = nb_id+1 id = nb_id name(id)=thename !$OMP END MASTER END SUBROUTINE register_id FUNCTION get_elapsed(start) INTEGER(kind=8) :: count, count_rate REAL :: start,get_elapsed CALL SYSTEM_CLOCK(count,count_rate) get_elapsed = (1.*count)/(1.*count_rate) - start IF(get_elapsed<0.) get_elapsed=0. END FUNCTION get_elapsed SUBROUTINE enter_profile(id) INTEGER, INTENT(IN) :: id REAL :: my_chrono !$OMP MASTER depth = depth+1 chrono(depth) = get_elapsed(0.) current_id(depth) = id !$OMP END MASTER END SUBROUTINE enter_profile SUBROUTINE exit_profile(id) INTEGER, INTENT(IN) :: id INTEGER :: parent_id REAL :: my_elapsed !$OMP MASTER IF(depth<=0) THEN PRINT *, 'exit_profile called at depth=0 !!' STOP END IF IF(id /= current_id(depth)) THEN PRINT *,' exit_profile : at depth ', depth, ' exiting ', TRIM(name(id)), ' after entering ', TRIM(name(current_id(depth))) STOP END IF my_elapsed = get_elapsed(chrono(depth)) ! add elapsed to current profile elapsed(id) = elapsed(id) + my_elapsed depth = depth-1 ! and substract from parent profile IF(depth>0) THEN parent_id = current_id(depth) elapsed(parent_id) = elapsed(parent_id) - my_elapsed END IF !$OMP END MASTER END SUBROUTINE exit_profile SUBROUTINE print_profile INTEGER :: i REAL :: total !$OMP MASTER PRINT *, '---------------------- Profiling -----------------------' total = SUM(elapsed(1:nb_id)) PRINT *, 'Total (s) : ', total DO i=1,nb_id PRINT *, name(i), INT(elapsed(i)), INT(1000.*elapsed(i)/total) END DO PRINT *, '---------------------- Profiling -----------------------' !$OMP END MASTER END SUBROUTINE print_profile END MODULE profiling_mod