File: RELATIVE:/../../../mfix.git/model/check_data/check_bc_outflow.f
1
2
3
4
5
6
7
8
9
10 SUBROUTINE CHECK_BC_OUTFLOW(M_TOT, BCV)
11
12
13
14 use bc, only: bc_ep_g, bc_rop_s
15 use param1, only: one, undefined, zero
16 use physprop, only: ro_s0
17 use run, only: solids_model
18 use toleranc, only: compare
19 use error_manager
20
21 IMPLICIT NONE
22
23
24
25
26 INTEGER, INTENT(in) :: BCV
27 INTEGER, INTENT(in) :: M_TOT
28
29
30
31 INTEGER :: M
32 DOUBLE PRECISION :: SUM_EP
33 LOGICAL :: FLAG_WARNING
34
35 FLAG_WARNING = .TRUE.
36 CALL INIT_ERR_MSG("CHECK_BC_OUTFLOW")
37
38
39
40
41
42
43
44
45 IF (BC_EP_G(BCV) /= UNDEFINED) THEN
46
47 SUM_EP = BC_EP_G(BCV)
48 DO M = 1, M_TOT
49
50 IF(SOLIDS_MODEL(M) /= 'TFM' .AND. FLAG_WARNING) THEN
51 WRITE(ERR_MSG, 1101) trim(iVar('BC_EP_g',BCV))
52 CALL FLUSH_ERR_MSG
53 FLAG_WARNING = .FALSE.
54 ENDIF
55
56 IF(BC_ROP_S(BCV,M) == UNDEFINED) THEN
57
58 IF(BC_EP_G(BCV) == ONE) THEN
59
60
61 (BCV,M) = ZERO
62 ELSEIF(M_TOT == 1 ) THEN
63 BC_ROP_S(BCV,M) = (ONE - BC_EP_G(BCV))*RO_S0(M)
64 ELSE
65
66
67
68
69
70 WRITE(ERR_MSG, 1102) trim(iVar('BC_EP_g',BCV))
71 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
72 1102 FORMAT('Warning 1102: Volume fraction may not sum to one when ',/&
73 A,' is defined.')
74 ENDIF
75 ENDIF
76
77
78
79
80 = SUM_EP + BC_ROP_S(BCV,M)/RO_S0(M)
81 ENDDO
82
83
84 IF(.NOT.COMPARE(SUM_EP,ONE)) THEN
85 WRITE(ERR_MSG,1103) BCV, trim(iVal(SUM_EP))
86 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
87 ENDIF
88
89
90 ELSE
91
92 SUM_EP = ZERO
93 DO M = 1, M_TOT
94 IF(BC_ROP_S(BCV,M) /= UNDEFINED) THEN
95 IF(SOLIDS_MODEL(M) /= 'TFM') THEN
96 WRITE(ERR_MSG, 1101) trim(iVar('BC_ROP_s',BCV,M))
97 CALL FLUSH_ERR_MSG
98 ENDIF
99 SUM_EP = SUM_EP + BC_ROP_S(BCV,M)/RO_S0(M)
100 ENDIF
101 ENDDO
102
103
104
105 IF(SUM_EP > ONE) THEN
106 WRITE(ERR_MSG,1103) BCV, trim(iVal(SUM_EP))
107 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
108 ENDIF
109
110 ENDIF
111
112 CALL FINL_ERR_MSG
113
114 RETURN
115
116 1101 FORMAT('Warning 1101: ',A,' should not be specified for ', &
117 'outflow BCs',/'with DEM/PIC runs except for a mass outflow ',&
118 'boundary with specified ',/ 'flow rate(s). In this case ',&
119 'volume fraction data is used for ',/ 'conversion to ',&
120 'velocity(s). However, the solids volume fraction data ',/&
121 'is effectively disregarded and it is the solids velocity ',&
122 'that is ',/'used to direct any solids at the boundary.')
123
124 1103 FORMAT('Error 1103: Illegal boundary condition region: ',I3,'. ',&
125 'Sum of volume',/'fractions does NOT equal ONE. (SUM = ',A, &
126 ')',/'Please correct the mfix.dat file.')
127
128 END SUBROUTINE CHECK_BC_OUTFLOW
129
130
131
132
133
134
135
136
137
138
139 SUBROUTINE CHECK_BC_P_OUTFLOW(M_TOT, BCV)
140
141
142
143 USE param1, only: UNDEFINED
144 USE param1, only: ZERO
145 use physprop, only: RO_g0
146 use bc, only: BC_P_g
147 use error_manager
148 IMPLICIT NONE
149
150
151
152
153 INTEGER, INTENT(in) :: BCV
154 INTEGER, INTENT(in) :: M_TOT
155
156
157 CALL INIT_ERR_MSG("CHECK_BC_P_OUTFLOW")
158
159 IF (BC_P_G(BCV) == UNDEFINED) THEN
160 WRITE(ERR_MSG,1000) trim(iVar('BC_P_g',BCV))
161 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
162
163 ELSEIF (BC_P_G(BCV)<=ZERO .AND. RO_G0==UNDEFINED) THEN
164 WRITE(ERR_MSG, 1100) BCV, trim(iVal(BC_P_G(BCV)))
165 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
166 ENDIF
167
168 1100 FORMAT('Error 1100: Pressure must be greater than zero for ', &
169 'compressible flow',/3x,'BC_P_g(',I3,') = ',A,/'Please ', &
170 'correct the mfix.dat file.')
171
172
173 CALL FINL_ERR_MSG
174
175 RETURN
176
177 1000 FORMAT('Error 1000: Required input not specified: ',A,/'Please ',&
178 'correct the mfix.dat file.')
179
180 END SUBROUTINE CHECK_BC_P_OUTFLOW
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199 SUBROUTINE CHECK_BC_MASS_OUTFLOW(M_TOT, BCV)
200
201
202
203 use bc, only: bc_plane
204 use bc, only: bc_dt_0, bc_massflow_g, bc_volflow_g
205 use bc, only: bc_massflow_s, bc_volflow_s
206 use bc, only: bc_ep_g, bc_rop_s
207 use bc, only: bc_p_g, bc_t_g
208 use bc, only: bc_u_g, bc_v_g, bc_w_g
209 use physprop, only: ro_g0
210 use param1, only: undefined, zero
211 use error_manager
212 IMPLICIT NONE
213
214
215
216
217 INTEGER, intent(in) :: BCV
218 INTEGER, intent(in) :: M_TOT
219
220
221 INTEGER :: M
222
223
224 CALL INIT_ERR_MSG("CHECK_BC_MASS_OUTFLOW")
225
226 IF(BC_DT_0(BCV) == UNDEFINED) THEN
227 WRITE(ERR_MSG, 1000) trim(iVar('BC_DT_0',BCV))
228 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
229 ENDIF
230
231 IF(BC_MASSFLOW_G(BCV) /= UNDEFINED .OR. &
232 BC_VOLFLOW_G(BCV) /= UNDEFINED) THEN
233 IF (BC_EP_G(BCV) == UNDEFINED) THEN
234 WRITE(ERR_MSG,1101) trim(iVar('BC_EP_G',BCV))
235 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
236 ENDIF
237 1101 FORMAT('Error 1101: Invalid mass outflow boundary condition: ', /&
238 'BC_MASSFLOW_G and/or BC_VOLFLOW_G are DEFINED but ',&
239 A,' is not ',/'Please correct the mfix.dat file.')
240 ENDIF
241
242 DO M = 1, M_TOT
243 IF(BC_MASSFLOW_S(BCV,M) /= UNDEFINED .OR. &
244 BC_VOLFLOW_S(BCV,M) /= UNDEFINED) THEN
245 WRITE(ERR_MSG,1102) trim(iVar('BC_MASSFLOW_S',BCV,M)), &
246 trim(iVar('BC_VOLFLOW_S',BCV,M))
247 1102 FORMAT('Warning 1102: ', A,' and/or ', A,' have been defined',/&
248 'at a mass outflow boundary. A specified solids flow ',&
249 'rate may not be ',/'physically achievable depending on the ',&
250 'system and simulation ',/'setup.')
251
252 IF (BC_ROP_S(BCV,M) == UNDEFINED) THEN
253 WRITE(ERR_MSG,1103) trim(iVar('BC_ROP_S',BCV,M))
254 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
255 ENDIF
256 1103 FORMAT('Error 1103: Invalid mass outflow boundary condition: ', /&
257 'BC_MASSFLOW_S and/or BC_VOLFLOW_S are DEFINED but ',&
258 A,' is not ',/'Please correct the mfix.dat file.')
259
260 ENDIF
261 ENDDO
262
263
264 IF(RO_G0 == UNDEFINED .AND. (BC_P_G(BCV) == UNDEFINED .OR. &
265 BC_T_G(BCV) == UNDEFINED) .AND.BC_MASSFLOW_G(BCV) /= ZERO) THEN
266
267 IF(BC_PLANE(BCV)=='W' .OR. BC_PLANE(BCV)=='E') THEN
268 IF(BC_U_G(BCV) /= ZERO) THEN
269 WRITE(ERR_MSG, 1100) BCV, 'BC_U_g'
270 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
271 ENDIF
272 ELSEIF(BC_PLANE(BCV)=='N' .OR. BC_PLANE(BCV)=='S') THEN
273 IF(BC_V_G(BCV) /= ZERO) THEN
274 WRITE(ERR_MSG, 1100) BCV, 'BC_V_g'
275 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
276 ENDIF
277 ELSEIF (BC_PLANE(BCV)=='T' .OR. BC_PLANE(BCV)=='B') THEN
278 IF(BC_W_G(BCV) /= ZERO) THEN
279 WRITE(ERR_MSG, 1100) BCV, 'BC_W_g'
280 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
281 ENDIF
282 ENDIF
283 ENDIF
284
285 FORMAT('Error 1100: Invalid mass outflow boundary condition: ', &
286 I3,/'RO_g0, BC_P_g, and BC_T_g are UNDEFINED and ',A,' is ', &
287 'non-zero',/'Please correct the mfix.dat file.')
288
289
290 CALL FINL_ERR_MSG
291
292 RETURN
293
294 1000 FORMAT('Error 1000: Required input not specified: ',A,/'Please ',&
295 'correct the mfix.dat file.')
296
297 END SUBROUTINE CHECK_BC_MASS_OUTFLOW
298