SFEMaNS  version 5.3
Reference documentation for SFEMaNS
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)
33 #include "petsc/finclude/petsc.h"
34  USE petsc
35  IMPLICIT NONE
36  REAL(KIND=8), OPTIONAL, INTENT(IN) :: opt_tps, opt_tploc_max
37  petscerrorcode :: code
38  petscmpiint :: rank
39  IF (inputs%verbose_timing) THEN
40  IF (present(opt_tps).AND.present(opt_tploc_max)) THEN
41  CALL mpi_allreduce(opt_tps,talk_to_me%total_cpu_time,1,mpi_double_precision,&
42  mpi_max, petsc_comm_world, code)
43  IF(inputs%nb_iteration>1) THEN
44  CALL mpi_allreduce(opt_tploc_max,talk_to_me%total_cpu_time_minus_init,1,&
45  mpi_double_precision, mpi_max, petsc_comm_world, code)
46  END IF
47  IF (rank==0) WRITE(*,'(A,F12.5)') ' Total elapse time ', talk_to_me%total_cpu_time
48  IF(inputs%nb_iteration>1) THEN
49  IF (rank==0) WRITE(*,'(A,F12.5)') 'Average time in loop (minus initialization) ', &
50  talk_to_me%total_cpu_time_minus_init/(inputs%nb_iteration-1)
51  END IF
52  RETURN
53  END IF
54  END IF
55 
56  IF (inputs%verbose_CFL) THEN
57  IF (rank==0) WRITE(*,'(2(A,e10.3))') ' Time = ', talk_to_me%time, ', CFL = ', talk_to_me%CFL
58  END IF
59  IF (inputs%verbose_divergence) THEN
60  IF (inputs%type_pb=='nst' .OR. inputs%type_pb=='mhd' .OR. inputs%type_pb=='fhd') THEN
61  IF (rank==0) WRITE(*,'(2(A,e10.3))') ' Time = ', talk_to_me%time, &
62  ', ||div(un)||_L2/||un||_H1 = ', talk_to_me%div_L2
63  IF (rank==0) WRITE(*,'(2(A,e10.3))') ' Time = ', talk_to_me%time, &
64  ', ||weak_div(un)||_L2/||un||_H1 = ', talk_to_me%weak_div_L2
65  END IF
66  IF (inputs%type_pb/='nst') THEN
67  IF (rank==0) WRITE(*,'(2(A,e10.3))') ' Time = ', talk_to_me%time, &
68  ', ||div(Bn)||_L2/||Bn||_L2 = ', talk_to_me%div_B_L2
69  END IF
70  END IF
71 
72  END SUBROUTINE write_verbose
73 END MODULE verbose
type(my_data), public inputs
subroutine, public write_verbose(rank, opt_tps, opt_tploc_max)
Definition: verbose.f90:32
type(my_verbose), public talk_to_me
Definition: verbose.f90:27