MFIX  2016-1
display_resid.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Module name: DISPLAY_RESID(NIT, IER) !
4 ! Author: M. Syamlal Date: 8-JUL-96 !
5 ! !
6 ! Purpose: Display residuals !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  SUBROUTINE display_resid(NIT)
10 
11  USE residual, only: group_resid
12 
13  IMPLICIT NONE
14 
15 ! iteration number
16  INTEGER, INTENT(IN) :: NIT
17 
18 ! Print Location of Max_Resid
19 ! LOGICAL,PARAMETER:: Print_ijk=.FALSE.
20 
21 
22  IF(group_resid) THEN
24  ELSE
26  ENDIF
27 
28 ! IF(PRINT_IJK)
29 
30 
31 
32 
33 
34 !
35 !
36 ! Display maximum values of residuals
37 ! IF(PRINT_IJK) WRITE(*,'(A, G12.3, 3I6, A, G12.3, 3I6, A, G12.3)') &
38 ! & " Max Res/IJK: P_g: ", MAX_RESID(RESID_P, 0), &
39 ! & I_OF_G(IJK_RESID(RESID_P, 0)), &
40 ! & J_OF_G(IJK_RESID(RESID_P, 0)), &
41 ! & K_OF_G(IJK_RESID(RESID_P, 0)), &
42 ! & " P_s: ", MAX_RESID(RESID_p, 1), &
43 ! & I_OF_G(IJK_RESID(RESID_p, 1)), &
44 ! & J_OF_G(IJK_RESID(RESID_p, 1)), &
45 ! & K_OF_G(IJK_RESID(RESID_p, 1)), &
46 ! & " P_star=", P_star(IJK_RESID(RESID_p, 1))
47 !
48  RETURN
49 
50  contains
51 
52 
53 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
54 ! !
55 ! Module name: DISPLAY_FIELD_RESID(NIT, IER) !
56 ! Author: M. Syamlal Date: 8-JUL-96 !
57 ! !
58 ! Purpose: Display residuals for each field variable. !
59 ! !
60 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
61  SUBROUTINE display_field_resid
62 
63  use param1, only: undefined_i
65 
66  use error_manager
67 
68  IMPLICIT NONE
69 
70  INTEGER :: LL, LC, LS, LE
71 
72  IF(nit == 1) THEN
73  WRITE(err_msg(1)(1:5),'(" Nit")')
74  lc=1
75  DO ll = 1, 8
76  IF (resid_index(ll,1) /= undefined_i) THEN
77  ls= 6+10*(lc-1)
78  le= 5+10*(lc)
79  WRITE(err_msg(1)(ls:le),'(5X,A4)') resid_string(ll)
80  lc=lc+1
81  ENDIF
82  END DO
83  IF(resid_index(8,1) == undefined_i) THEN
84  ls= 6+10*(lc-1)
85  le= 5+10*(lc)
86  WRITE(err_msg(1)(ls:le),'(2X,A7)') 'Max res'
87  ENDIF
88  CALL flush_err_msg(header=.false., footer=.false., log=.false.)
89  ENDIF
90 
91 
92  WRITE(err_msg(1)(1:5),'(I5)') nit
93  lc=1
94  DO ll = 1, 8
95  IF(resid_index(ll,1) /= undefined_i) THEN
96  ls= 6+10*(lc-1)
97  le= 5+10*(lc)
98  WRITE(err_msg(1)(ls:le),'(2X,1PG8.1)') &
99  resid(resid_index(ll,1),resid_index(ll,2))
100  lc=lc+1
101  ENDIF
102  ENDDO
103  IF(resid_index(8,1) == undefined_i) THEN
104  ls= 6+10*(lc-1)
105  le= 3+10*(lc)
106  WRITE(err_msg(1)(ls:le),'(4X,A4)') resid_string(8)
107  ENDIF
108  CALL flush_err_msg(header=.false., footer=.false., log=.false.)
109 
110  RETURN
111 
112  END SUBROUTINE display_field_resid
113 
114 
115 
116 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
117 ! !
118 ! Module name: DISPLAY_GROUP_RESID(NIT, IER) !
119 ! Author: M. Syamlal Date: 8-JUL-96 !
120 ! !
121 ! Purpose: Display residuals grouped by equation type. !
122 ! !
123 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
124  SUBROUTINE display_group_resid
126  use residual, only: resid_string
130  use run, only: granular_energy, energy_eq
131  use run, only: any_species_eq, k_epsilon
132  use scalars, only : nscalar
133 
134  use error_manager
135 
136  IMPLICIT NONE
137 
138 
139  INTEGER :: LC, LS, LE
140 
141  IF (nit == 1) THEN
142  WRITE(err_msg(1)(1:5),'(" Nit")')
143  lc=1
144 
145  ls= 6+10*(lc-1)
146  le= 5+10*(lc)
147  WRITE(err_msg(1)(ls:le),1000) resid_grp_string(hydro_grp)
148  lc=lc+1
149 
150  IF(granular_energy) THEN
151  ls= 6+10*(lc-1)
152  le= 5+10*(lc)
153  WRITE(err_msg(1)(ls:le),1000) resid_grp_string(theta_grp)
154  lc=lc+1
155  ENDIF
156 
157  IF(energy_eq) THEN
158  ls= 6+10*(lc-1)
159  le= 5+10*(lc)
160  WRITE(err_msg(1)(ls:le),1000) resid_grp_string(energy_grp)
161  lc=lc+1
162  ENDIF
163 
164  IF(any_species_eq) THEN
165  ls= 6+10*(lc-1)
166  le= 5+10*(lc)
167  WRITE(err_msg(1)(ls:le),1000) resid_grp_string(species_grp)
168  lc=lc+1
169  ENDIF
170 
171  IF(nscalar > 0) THEN
172  ls= 6+10*(lc-1)
173  le= 5+10*(lc)
174  WRITE(err_msg(1)(ls:le),1000) resid_grp_string(scalar_grp)
175  lc=lc+1
176  ENDIF
177 
178  IF(k_epsilon) THEN
179  ls= 6+10*(lc-1)
180  le= 5+10*(lc)
181  WRITE(err_msg(1)(ls:le),1000) resid_grp_string(ke_grp)
182  lc=lc+1
183  ENDIF
184 
185  ls= 6+10*(lc-1)
186  le= 5+10*(lc)
187  WRITE(err_msg(1)(ls:le),1000) 'Max res '
188 
189  CALL flush_err_msg(header=.false., footer=.false., log=.false.)
190  ENDIF
191 
192  1000 FORMAT(3x,a7)
193 
194 
195 
196  WRITE(err_msg(1)(1:5),'(I5)') nit
197  lc=1
198 
199  ls= 6+10*(lc-1)
200  le= 5+10*(lc)
201  WRITE(err_msg(1)(ls:le),1100) resid_grp(hydro_grp)
202  lc=lc+1
203 
204  IF(granular_energy) THEN
205  ls= 6+10*(lc-1)
206  le= 5+10*(lc)
207  WRITE(err_msg(1)(ls:le),1100) resid_grp(theta_grp)
208  lc=lc+1
209  ENDIF
210 
211  IF(energy_eq) THEN
212  ls= 6+10*(lc-1)
213  le= 5+10*(lc)
214  WRITE(err_msg(1)(ls:le),1100) resid_grp(energy_grp)
215  lc=lc+1
216  ENDIF
217 
218  IF(any_species_eq) THEN
219  ls= 6+10*(lc-1)
220  le= 5+10*(lc)
221  WRITE(err_msg(1)(ls:le),1100) resid_grp(species_grp)
222  lc=lc+1
223  ENDIF
224 
225  IF(nscalar > 0) THEN
226  ls= 6+10*(lc-1)
227  le= 5+10*(lc)
228  WRITE(err_msg(1)(ls:le),1100) resid_grp(scalar_grp)
229  lc=lc+1
230  ENDIF
231 
232  IF(k_epsilon) THEN
233  ls= 6+10*(lc-1)
234  le= 5+10*(lc)
235  WRITE(err_msg(1)(ls:le),1100) resid_grp(ke_grp)
236  lc=lc+1
237  ENDIF
238 
239  ls= 6+10*(lc-1)
240  le= 3+10*(lc)
241  WRITE(err_msg(1)(ls:le),'(4X,A4)') resid_string(8)
242 
243  1100 FORMAT(2x,1pg8.1)
244 
245  CALL flush_err_msg(header=.false., footer=.false., log=.false.)
246 
247  RETURN
248  END SUBROUTINE display_group_resid
249 
250  END SUBROUTINE display_resid
integer, parameter hydro_grp
Definition: residual_mod.f:24
double precision, dimension(6) resid_grp
Definition: residual_mod.f:59
integer, parameter scalar_grp
Definition: residual_mod.f:28
logical group_resid
Definition: residual_mod.f:58
integer, parameter species_grp
Definition: residual_mod.f:27
integer, dimension(max_resid_index, 2) resid_index
Definition: residual_mod.f:66
subroutine display_field_resid
Definition: display_resid.f:62
logical any_species_eq
Definition: run_mod.f:118
Definition: run_mod.f:13
subroutine display_resid(NIT)
Definition: display_resid.f:10
integer, parameter energy_grp
Definition: residual_mod.f:26
integer, parameter theta_grp
Definition: residual_mod.f:25
subroutine display_group_resid
logical k_epsilon
Definition: run_mod.f:97
character(len=4), dimension(max_resid_index) resid_string
Definition: residual_mod.f:62
logical energy_eq
Definition: run_mod.f:100
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
integer nscalar
Definition: scalars_mod.f:7
character(len=8), dimension(6) resid_grp_string
Definition: residual_mod.f:63
double precision, dimension(:,:), allocatable resid
Definition: residual_mod.f:37
logical granular_energy
Definition: run_mod.f:112
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
integer, parameter ke_grp
Definition: residual_mod.f:29