CAMP 1.0.0
Chemistry Across Multiple Phases
solver_stats.F90
Go to the documentation of this file.
1! Copyright (C) 2021 Barcelona Supercomputing Center and University of
2! Illinois at Urbana-Champaign
3! SPDX-License-Identifier: MIT
4
5!> \file
6!> The camp_solver_stats module
7
8!> The solver_stats_t type and associated subroutines
10
11 use camp_constants, only : i_kind, dp
12
13 implicit none
14 private
15
16 public :: solver_stats_t
17
18 !> Solver statistics
19 !!
20 !! Holds information related to a solver run
22 !> Status code
23 integer(kind=i_kind) :: status_code
24 !> Integration start time [s]
25 real(kind=dp) :: start_time__s
26 !> Integration end time [s]
27 real(kind=dp) :: end_time__s
28 !> Last flag returned by the solver
29 integer(kind=i_kind) :: solver_flag
30 !> Number of steps
31 integer(kind=i_kind) :: num_steps
32 !> Right-hand side evaluations
33 integer(kind=i_kind) :: rhs_evals
34 !> Linear solver setups
35 integer(kind=i_kind) :: ls_setups
36 !> Error test failures
37 integer(kind=i_kind) :: error_test_fails
38 !> Non-Linear solver iterations
39 integer(kind=i_kind) :: nls_iters
40 !> Non-Linear solver convergence failures
41 integer(kind=i_kind) :: nls_convergence_fails
42 !> Direct Linear Solver Jacobian evaluations
43 integer(kind=i_kind) :: dls_jac_evals
44 !> Direct Linear Solver right-hand size evaluations
45 integer(kind=i_kind) :: dls_rhs_evals
46 !> Last time step [s]
47 real(kind=dp) :: last_time_step__s
48 !> Next time step [s]
49 real(kind=dp) :: next_time_step__s
50 !> Jacobian evaluation failures
51 integer(kind=i_kind) :: jac_eval_fails
52 !> Total calls to `f()`
53 integer(kind=i_kind) :: rhs_evals_total
54 !> Total calls to `Jac()`
55 integer(kind=i_kind) :: jac_evals_total
56 !> Compute time for calls to `f()` [s]
57 real(kind=dp) :: rhs_time__s
58 !> Compute time for calls to `Jac()` [s]
59 real(kind=dp) :: jac_time__s
60 !> Maximum loss of precision on last deriv call
61 real(kind=dp) :: max_loss_precision
62#ifdef CAMP_DEBUG
63 !> Flag to output debugging info during solving
64 !! THIS PRINTS A LOT OF TEXT TO THE STANDARD OUTPUT
65 logical :: debug_out = .false.
66 !> Evalute the Jacobian during solving
67 logical :: eval_jac = .false.
68#endif
69 contains
70 !> Print the solver statistics
71 procedure :: print => do_print
72 !> Assignment
73 procedure :: assignvalue
74 generic :: assignment(=) => assignvalue
75 end type solver_stats_t
76
77contains
78
79!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
80
81 !> Print the solver statistics
82 subroutine do_print( this, file_unit )
83
84 !> Solver statistics
85 class(solver_stats_t), intent(in) :: this
86 !> File unit to output to
87 integer(kind=i_kind), optional :: file_unit
88
89 integer(kind=i_kind) :: f_unit
90
91 f_unit = 6
92
93 if( present( file_unit ) ) f_unit = file_unit
94
95 write(f_unit,*) "Status code: ", this%status_code
96 write(f_unit,*) "Integration start time [s]: ", this%start_time__s
97 write(f_unit,*) "Integration end time [s]: ", this%end_time__s
98 write(f_unit,*) "Last solver flag: ", this%solver_flag
99 write(f_unit,*) "Number of steps: ", this%num_steps
100 write(f_unit,*) "Right-hand side evals: ", this%RHS_evals
101 write(f_unit,*) "Linear solver setups: ", this%LS_setups
102 write(f_unit,*) "Error test failures: ", this%error_test_fails
103 write(f_unit,*) "Non-Linear solver iterations:", this%NLS_iters
104 write(f_unit,*) "Non-Linear convergence fails:", this%NLS_convergence_fails
105 write(f_unit,*) "DLS Jacobian evals: ", this%DLS_Jac_evals
106 write(f_unit,*) "DLS Right-hand side evals: ", this%DLS_RHS_evals
107 write(f_unit,*) "Last time step [s]: ", this%last_time_step__s
108 write(f_unit,*) "Next time step [s]: ", this%next_time_step__s
109 write(f_unit,*) "Maximum loss of precision ", this%max_loss_precision
110#ifdef CAMP_DEBUG
111 write(f_unit,*) "Output debugging info: ", this%debug_out
112 write(f_unit,*) "Evaluate Jacobian: ", this%eval_Jac
113 if (this%eval_Jac) then
114 write(f_unit,*) "Jacobian evaluation failures:", this%Jac_eval_fails
115 end if
116#endif
117
118 end subroutine do_print
119
120!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
121
122 !> Assign a value to all members of solver stats
123 subroutine assignvalue( this, new_value )
124
125 !> Solver statistics
126 class(solver_stats_t), intent(inout) :: this
127 !> Value to assign
128 integer(kind=i_kind), intent(in) :: new_value
129
130 this%status_code = new_value
131 this%start_time__s = real( new_value, kind=dp )
132 this%end_time__s = real( new_value, kind=dp )
133 this%solver_flag = new_value
134 this%num_steps = new_value
135 this%RHS_evals = new_value
136 this%LS_setups = new_value
137 this%error_test_fails = new_value
138 this%NLS_iters = new_value
139 this%NLS_convergence_fails = new_value
140 this%DLS_Jac_evals = new_value
141 this%DLS_RHS_evals = new_value
142 this%last_time_step__s = real( new_value, kind=dp )
143 this%next_time_step__s = real( new_value, kind=dp )
144 this%Jac_eval_fails = new_value
145 this%max_loss_precision = new_value
146
147 end subroutine assignvalue
148
149!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
150
151end module camp_solver_stats
Physical constants.
Definition constants.F90:9
integer, parameter dp
Kind of a double precision real number.
Definition constants.F90:16
integer, parameter i_kind
Kind of an integer.
Definition constants.F90:21
The solver_stats_t type and associated subroutines.
subroutine do_print(this, file_unit)
Print the solver statistics.
subroutine assignvalue(this, new_value)
Assign a value to all members of solver stats.