SFEMaNS  version 4.1 (work in progress)
Reference documentation for SFEMaNS
 All Classes Files Functions Variables Groups Pages
verbose.f90
Go to the documentation of this file.
2  TYPE my_verbose
3  REAL(KIND=8) :: CFL
4  REAL(KIND=8) :: time
5  REAL(KIND=8) :: div_L2
6  REAL(KIND=8) :: weak_div_L2
7  REAL(KIND=8) :: div_B_L2
8  REAL(KIND=8) :: total_cpu_time
9  REAL(KIND=8) :: total_cpu_time_minus_init
10  !CONTAINS
11  !PROCEDURE, PUBLIC :: write_verbose
12  END type my_verbose
13  !CONTAINS
14  ! SUBROUTINE write_verbose(a)
15  ! USE input_data
16  ! CLASS(my_verbose), INTENT(INOUT) :: a
17  ! IF (inputs%verbose_CFL) THEN
18  ! WRITE(*,'(2(A,e10.3))') ' Time = ', time, ', CFL = ', a%CFL
19  ! END IF
20  ! END SUBROUTINE write_verbose
21 END module type_verbose
22 
23 MODULE verbose
24  USE type_verbose
25  IMPLICIT NONE
26  PUBLIC :: write_verbose
27  TYPE(my_verbose), PUBLIC :: talk_to_me
28  PRIVATE
29 
30 CONTAINS
31  SUBROUTINE write_verbose(rank,opt_tps,opt_tploc_max)
32  USE input_data
33  IMPLICIT NONE
34  REAL(KIND=8), OPTIONAL, INTENT(IN) :: opt_tps, opt_tploc_max
35 #include "petsc/finclude/petsc.h"
36  petscerrorcode :: code
37  petscmpiint :: rank
38  IF (inputs%verbose_timing) THEN
39  IF (present(opt_tps).AND.present(opt_tploc_max)) THEN
40  CALL mpi_allreduce(opt_tps,talk_to_me%total_cpu_time,1,mpi_double_precision,&
41  mpi_max, petsc_comm_world, code)
42  IF(inputs%nb_iteration>1) THEN
43  CALL mpi_allreduce(opt_tploc_max,talk_to_me%total_cpu_time_minus_init,1,&
44  mpi_double_precision, mpi_max, petsc_comm_world, code)
45  END IF
46  IF (rank==0) WRITE(*,'(A,F12.5)') ' Total elapse time ', talk_to_me%total_cpu_time
47  IF(inputs%nb_iteration>1) THEN
48  IF (rank==0) WRITE(*,'(A,F12.5)') 'Average time in loop (minus initialization) ', &
49  talk_to_me%total_cpu_time_minus_init/(inputs%nb_iteration-1)
50  END IF
51  RETURN
52  END IF
53  END IF
54 
55  IF (inputs%verbose_CFL) THEN
56  IF (rank==0) WRITE(*,'(2(A,e10.3))') ' Time = ', talk_to_me%time, ', CFL = ', talk_to_me%CFL
57  END IF
58  IF (inputs%verbose_divergence) THEN
59  IF (inputs%type_pb=='nst' .OR. inputs%type_pb=='mhd' .OR. inputs%type_pb=='fhd') THEN
60  IF (rank==0) WRITE(*,'(2(A,e10.3))') ' Time = ', talk_to_me%time, &
61  ', ||div(un)||_L2/||un||_H1 = ', talk_to_me%div_L2
62  IF (rank==0) WRITE(*,'(2(A,e10.3))') ' Time = ', talk_to_me%time, &
63  ', ||weak_div(un)||_L2/||un||_H1 = ', talk_to_me%weak_div_L2
64  END IF
65  IF (inputs%type_pb/='nst') THEN
66  IF (rank==0) WRITE(*,'(2(A,e10.3))') ' Time = ', talk_to_me%time, &
67  ', ||div(Bn)||_L2/||Bn||_L2 = ', talk_to_me%div_B_L2
68  END IF
69  END IF
70 
71  END SUBROUTINE write_verbose
72 END MODULE verbose
subroutine, public write_verbose(rank, opt_tps, opt_tploc_max)
Definition: verbose.f90:31