MFIX  2016-1
set_bc_flow.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: SET_BC_FLOW !
4 ! Author: P. Nicoletti Date: 10-DEC-91 !
5 ! !
6 ! Purpose: Check boundary condition specifications !
7 ! - convert physical locations to i, j, k's (GET_FLOW_BC) !
8 ! - compute area of boundary surfaces (GET_BC_AREA) !
9 ! - convert mass and volumetric flows to velocities (FLOW_TO_VEL) !
10 ! - check specification of physical quantities !
11 ! !
12 ! Comments: !
13 ! !
14 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
15  SUBROUTINE set_bc_flow
16 
17 ! Global Variables:
18 !---------------------------------------------------------------------//
19 ! Total number of (actual) continuum solids.
20  use physprop, only: smax
21 ! Total number of discrete solids.
22  use discretelement, only: des_mmax
23 ! Flag: BC dimensions or Type is specified
24  use bc, only: bc_defined
25 ! Use specified BC type
26  use bc
27 ! User specifed BC solids bulk density
28  use bc, only: bc_rop_s
29 ! Solids volume fraction at BC
30  use bc, only: bc_ep_s
31  use bc, only: bc_ep_g
32 
33 ! Global Parameters:
34 !---------------------------------------------------------------------//
35 ! Parameter constants
36  use param1, only: zero, one, undefined
37 ! Maximum number of BCs
38  use param, only: dimension_bc
39 ! Maximum number of disperse phases
40  use param, only: dim_m
41 
42 ! Use the error manager for posting error messages.
43 !---------------------------------------------------------------------//
44  use error_manager
45 
46 
47  IMPLICIT NONE
48 
49 
50 ! Local Variables:
51 !---------------------------------------------------------------------//
52 ! Loop counter for BCs
53  INTEGER :: BCV
54 ! Total number of solids phases (continuum + discrete)
55  INTEGER :: MMAX_TOT
56 ! Flag to skip checks on indexed solid phase.
57  LOGICAL :: SKIP(1:dim_m)
58 !......................................................................!
59 
60 
61 ! Initialize the error manager.
62  CALL init_err_msg("SET_BC_FLOW")
63 
64 ! Total number of solids.
65  mmax_tot = smax + des_mmax
66 
67 ! Loop over each defined BC and check the user data.
68  DO bcv = 1, dimension_bc
69 
70  IF(.NOT.bc_defined(bcv)) cycle
71 
72 ! Determine which solids phases are present.
73  skip=(bc_rop_s(bcv,:)==undefined.OR.bc_rop_s(bcv,:)==zero) &
74  .AND.(bc_ep_s(bcv,:)==undefined.OR.bc_ep_s(bcv,:)==zero)
75 
76  IF(mmax_tot == 1 .AND. bc_ep_g(bcv)/=one) skip(1) = .false.
77 
78  SELECT CASE (bc_type_enum(bcv))
79 
80  CASE (mass_inflow)
81  CALL flow_to_vel_new(.true., mmax_tot, skip, bcv)
82  CALL check_bc_vel_inflow(mmax_tot, skip, bcv)
83 
84  CASE (mass_outflow)
85  CALL flow_to_vel_new(.true., mmax_tot, skip, bcv)
86  CALL check_bc_vel_outflow(mmax_tot, skip, bcv)
87  END SELECT
88  ENDDO
89 
90 ! Cleanup and exit.
91  CALL finl_err_msg
92 
93  RETURN
94 
95  END SUBROUTINE set_bc_flow
96 
97 
98 
99 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
100 ! !
101 ! Subroutine: CHECK_BC_VEL_INFLOW !
102 ! Author: J.Musser Date: 01-Mar-14 !
103 ! !
104 ! Purpose: Provided a detailed error message when the sum of volume !
105 ! !
106 ! Comments: !
107 ! The velocities at the inflow face are fixed and the momentum !
108 ! equations are not solved in the inflow cells. Since the flow is !
109 ! into the domain all other scalars that are used need to be !
110 ! specified (e.g., mass fractions, void fraction, etc.,) !
111 ! !
112 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
113  SUBROUTINE check_bc_vel_inflow(M_TOT, SKIP, BCV)
115  USE param, only: dim_m
116  USE param1, only: zero
117  USE param1, only: undefined
118 
119  use geometry, only: no_i
120  use geometry, only: no_j
121  use geometry, only: no_k
122 
123  use bc
124 
125  use error_manager
126 
127  IMPLICIT NONE
128 
129 
130  INTEGER, INTENT(in) :: BCV
131  INTEGER, INTENT(in) :: M_TOT
132 
133  LOGICAL, INTENT(in) :: SKIP(dim_m)
134 
135 ! loop/variable indices
136  INTEGER :: M
137 
138  CALL init_err_msg("CHECK_BC_VEL_INFLOW")
139 
140 
141 ! Check that gas phase velocities are defined.
142  IF(bc_u_g(bcv) == undefined) THEN
143  IF(no_i) THEN
144  bc_u_g(bcv) = zero
145  ELSE
146  WRITE(err_msg,1000) trim(ivar('BC_U_g',bcv))
147  CALL flush_err_msg(abort=.true.)
148  ENDIF
149  ENDIF
150 
151  IF (bc_v_g(bcv) == undefined) THEN
152  IF (no_j) THEN
153  bc_v_g(bcv) = zero
154  ELSE
155  WRITE(err_msg,1000) trim(ivar('BC_V_g',bcv))
156  CALL flush_err_msg(abort=.true.)
157  ENDIF
158  ENDIF
159 
160  IF(bc_w_g(bcv) == undefined) THEN
161  IF (no_k) THEN
162  bc_w_g(bcv) = zero
163  ELSE
164  WRITE(err_msg,1000) trim(ivar('BC_W_g',bcv))
165  CALL flush_err_msg(abort=.true.)
166  ENDIF
167  ENDIF
168 
169 ! Check that solids phase velocities are defined.
170  DO m = 1, m_tot
171  IF(bc_u_s(bcv,m) == undefined) THEN
172  IF(skip(m) .OR. no_i) THEN
173  bc_u_s(bcv,m) = zero
174  ELSE
175  WRITE(err_msg,1000) trim(ivar('BC_U_s',bcv,m))
176  CALL flush_err_msg(abort=.true.)
177  ENDIF
178  ENDIF
179 
180  IF(bc_v_s(bcv,m) == undefined) THEN
181  IF(skip(m) .OR. no_j) THEN
182  bc_v_s(bcv,m) = zero
183  ELSE
184  WRITE(err_msg,1000) trim(ivar('BC_V_s',bcv,m))
185  CALL flush_err_msg(abort=.true.)
186  ENDIF
187  ENDIF
188 
189  IF(bc_w_s(bcv,m) == undefined) THEN
190  IF(skip(m) .OR. no_k) THEN
191  bc_w_s(bcv,m) = zero
192  ELSE
193  WRITE(err_msg,1000) trim(ivar('BC_W_s',bcv,m))
194  CALL flush_err_msg(abort=.true.)
195  ENDIF
196  ENDIF
197  ENDDO
198 
199 ! Check that gas phase velocities are consistent.
200  SELECT CASE (bc_plane(bcv))
201 
202  CASE ('W')
203  IF(bc_u_g(bcv) > zero) THEN
204  WRITE(err_msg,1300) trim(ivar('BC_U_g',bcv)), '<'
205  CALL flush_err_msg
206  ENDIF
207  DO m = 1, m_tot
208  IF(bc_u_s(bcv,m) > zero) THEN
209  WRITE(err_msg, 1300) trim(ivar('BC_U_s',bcv,m)), '<'
210  CALL flush_err_msg(abort=.true.)
211  ENDIF
212  ENDDO
213 
214  CASE('E')
215  IF(bc_u_g(bcv) < zero) THEN
216  WRITE(err_msg,1300) trim(ivar('BC_U_g',bcv)), '>'
217  CALL flush_err_msg
218  ENDIF
219  DO m = 1, m_tot
220  IF(bc_u_s(bcv,m) < zero) THEN
221  WRITE(err_msg, 1300) trim(ivar('BC_U_s',bcv,m)), '>'
222  CALL flush_err_msg(abort=.true.)
223  ENDIF
224  ENDDO
225 
226  CASE('S')
227  IF(bc_v_g(bcv) > zero) THEN
228  WRITE(err_msg,1300) trim(ivar('BC_V_g',bcv)), '<'
229  CALL flush_err_msg
230  ENDIF
231  DO m = 1, m_tot
232  IF(bc_v_s(bcv,m) > zero) THEN
233  WRITE(err_msg, 1300) trim(ivar('BC_V_s',bcv,m)), '<'
234  CALL flush_err_msg(abort=.true.)
235  ENDIF
236  ENDDO
237 
238  CASE('N')
239  IF(bc_v_g(bcv) < zero) THEN
240  WRITE(err_msg,1300) trim(ivar('BC_V_g',bcv)), '>'
241  CALL flush_err_msg
242  ENDIF
243  DO m = 1, m_tot
244  IF(bc_v_s(bcv,m) < zero) THEN
245  WRITE(err_msg, 1300) trim(ivar('BC_V_s',bcv,m)), '>'
246  CALL flush_err_msg(abort=.true.)
247  ENDIF
248  ENDDO
249 
250  CASE('B')
251  IF(bc_w_g(bcv) > zero) THEN
252  WRITE(err_msg,1300) trim(ivar('BC_W_g',bcv)), '<'
253  CALL flush_err_msg
254  ENDIF
255  DO m = 1, m_tot
256  IF(bc_w_s(bcv,m) > zero) THEN
257  WRITE(err_msg, 1300) trim(ivar('BC_W_s',bcv,m)), '<'
258  CALL flush_err_msg(abort=.true.)
259  ENDIF
260  ENDDO
261 
262  CASE('T')
263  IF(bc_w_g(bcv) < zero) THEN
264  WRITE(err_msg,1300) trim(ivar('BC_W_g',bcv)), '>'
265  CALL flush_err_msg
266  ENDIF
267  DO m = 1, m_tot
268  IF(bc_w_s(bcv,m) < zero) THEN
269  WRITE(err_msg, 1300) trim(ivar('BC_W_s',bcv,m)), '>'
270  CALL flush_err_msg(abort=.true.)
271  ENDIF
272  ENDDO
273 
274  END SELECT
275 
276  1300 FORMAT('Error 1300: Invalid flow direction. ',a,' should be ', &
277  a,' zero. ',/'Please correct the mfix.dat file.')
278 
279  CALL finl_err_msg
280 
281  RETURN
282 
283  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
284  'correct the mfix.dat file.')
285 
286  END SUBROUTINE check_bc_vel_inflow
287 
288 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
289 ! !
290 ! Subroutine: CHECK_BC_VEL_OUTFLOW !
291 ! Author: J.Musser Date: 01-Mar-14 !
292 ! !
293 ! Purpose: Provided a detailed error message when the sum of volume !
294 ! !
295 ! Comments: !
296 ! The velocities at the outflow face are fixed and the momentum !
297 ! equations are not solved in the outflow cells. Since the flow !
298 ! is out of the domain none of the other scalars should need to !
299 ! be specified (e.g., mass fractions, void fraction, etc.,). !
300 ! Such values will become defined according to their adjacent !
301 ! fluid cell !
302 ! !
303 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
304  SUBROUTINE check_bc_vel_outflow(M_TOT, SKIP, BCV)
306  USE param
307  USE param1
308  USE geometry
309  USE fldvar
310  USE physprop
311  USE run
312  USE bc
313  USE indices
314  USE funits
315  USE scalars
316  USE compar
317  USE sendrecv
318  USE discretelement
319  USE mfix_pic
320  USE cutcell
321 
322  use error_manager
323 
324  IMPLICIT NONE
325 
326 ! loop/variable indices
327  INTEGER, intent(in) :: BCV
328  INTEGER, intent(in) :: M_TOT
329  LOGICAL, intent(in) :: SKIP(dim_m)
330 
331 ! Loop variable
332  INTEGER :: M
333 
334  CALL init_err_msg("CHECK_BC_VEL_OUTFLOW")
335 
336 ! Check that gas phase velocities are defined.
337  IF(bc_u_g(bcv) == undefined) THEN
338  IF(no_i) THEN
339  bc_u_g(bcv) = zero
340  ELSE
341  WRITE(err_msg,1000) trim(ivar('BC_U_g',bcv))
342  CALL flush_err_msg(abort=.true.)
343  ENDIF
344  ENDIF
345 
346  IF (bc_v_g(bcv) == undefined) THEN
347  IF (no_j) THEN
348  bc_v_g(bcv) = zero
349  ELSE
350  WRITE(err_msg,1000) trim(ivar('BC_V_g',bcv))
351  CALL flush_err_msg(abort=.true.)
352  ENDIF
353  ENDIF
354 
355  IF(bc_w_g(bcv) == undefined) THEN
356  IF (no_k) THEN
357  bc_w_g(bcv) = zero
358  ELSE
359  WRITE(err_msg,1000) trim(ivar('BC_W_g',bcv))
360  CALL flush_err_msg(abort=.true.)
361  ENDIF
362  ENDIF
363 
364 ! Check that solids phase velocities are defined.
365  DO m = 1, m_tot
366  IF(bc_u_s(bcv,m) == undefined) THEN
367  IF(skip(m) .OR. no_i) THEN
368  bc_u_s(bcv,m) = zero
369  ELSE
370  WRITE(err_msg,1000) trim(ivar('BC_U_s',bcv,m))
371  CALL flush_err_msg(abort=.true.)
372  ENDIF
373  ENDIF
374 
375  IF(bc_v_s(bcv,m) == undefined) THEN
376  IF(skip(m) .OR. no_j) THEN
377  bc_v_s(bcv,m) = zero
378  ELSE
379  WRITE(err_msg,1000) trim(ivar('BC_V_s',bcv,m))
380  CALL flush_err_msg(abort=.true.)
381  ENDIF
382  ENDIF
383 
384  IF(bc_w_s(bcv,m) == undefined) THEN
385  IF(skip(m) .OR. no_k) THEN
386  bc_w_s(bcv,m) = zero
387  ELSE
388  WRITE(err_msg,1000) trim(ivar('BC_W_s',bcv,m))
389  CALL flush_err_msg(abort=.true.)
390  ENDIF
391  ENDIF
392  ENDDO
393 
394 
395 ! Check that gas phase velocities are consistent.
396  SELECT CASE (bc_plane(bcv))
397 
398  CASE ('W')
399  IF(bc_u_g(bcv) < zero) THEN
400  WRITE(err_msg,1300) trim(ivar('BC_U_g',bcv)), '>'
401  CALL flush_err_msg
402  ENDIF
403  DO m = 1, m_tot
404  IF(bc_u_s(bcv,m) < zero) THEN
405  WRITE(err_msg, 1300) trim(ivar('BC_U_s',bcv,m)), '>'
406  CALL flush_err_msg(abort=.true.)
407  ENDIF
408  ENDDO
409 
410  CASE('E')
411  IF(bc_u_g(bcv) > zero) THEN
412  WRITE(err_msg,1300) trim(ivar('BC_U_g',bcv)), '<'
413  CALL flush_err_msg
414  ENDIF
415  DO m = 1, m_tot
416  IF(bc_u_s(bcv,m) > zero) THEN
417  WRITE(err_msg, 1300) trim(ivar('BC_U_s',bcv,m)), '<'
418  CALL flush_err_msg(abort=.true.)
419  ENDIF
420  ENDDO
421 
422  CASE('S')
423  IF(bc_v_g(bcv) < zero) THEN
424  WRITE(err_msg,1300) trim(ivar('BC_V_g',bcv)), '>'
425  CALL flush_err_msg
426  ENDIF
427  DO m = 1, m_tot
428  IF(bc_v_s(bcv,m) < zero) THEN
429  WRITE(err_msg, 1300) trim(ivar('BC_V_s',bcv,m)), '>'
430  CALL flush_err_msg(abort=.true.)
431  ENDIF
432  ENDDO
433 
434  CASE('N')
435  IF(bc_v_g(bcv) > zero) THEN
436  WRITE(err_msg,1300) trim(ivar('BC_V_g',bcv)), '<'
437  CALL flush_err_msg
438  ENDIF
439  DO m = 1, m_tot
440  IF(bc_v_s(bcv,m) > zero) THEN
441  WRITE(err_msg, 1300) trim(ivar('BC_V_s',bcv,m)), '<'
442  CALL flush_err_msg(abort=.true.)
443  ENDIF
444  ENDDO
445 
446  CASE('B')
447  IF(bc_w_g(bcv) < zero) THEN
448  WRITE(err_msg,1300) trim(ivar('BC_W_g',bcv)), '>'
449  CALL flush_err_msg
450  ENDIF
451  DO m = 1, m_tot
452  IF(bc_w_s(bcv,m) < zero) THEN
453  WRITE(err_msg, 1300) trim(ivar('BC_W_s',bcv,m)), '>'
454  CALL flush_err_msg(abort=.true.)
455  ENDIF
456  ENDDO
457 
458  CASE('T')
459  IF(bc_w_g(bcv) > zero) THEN
460  WRITE(err_msg,1300) trim(ivar('BC_W_g',bcv)), '<'
461  CALL flush_err_msg
462  ENDIF
463  DO m = 1, m_tot
464  IF(bc_w_s(bcv,m) > zero) THEN
465  WRITE(err_msg, 1300) trim(ivar('BC_W_s',bcv,m)), '<'
466  CALL flush_err_msg(abort=.true.)
467  ENDIF
468  ENDDO
469 
470  END SELECT
471 
472  1300 FORMAT('Error 1300: Invalid flow direction. ',a,' should be ', &
473  a,' zero. ',/'Please correct the mfix.dat file.')
474  CALL finl_err_msg
475 
476 
477  RETURN
478 
479 
480  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
481  'correct the mfix.dat file.')
482 
483  END SUBROUTINE check_bc_vel_outflow
subroutine flow_to_vel_new(DO_VEL_CHECK, M_TOT, SKIP, BCV)
Definition: flow_to_vel.f:23
subroutine set_bc_flow
Definition: set_bc_flow.f:16
character(len=32) function ivar(VAR, i1, i2, i3)
subroutine finl_err_msg
logical no_i
Definition: geometry_mod.f:20
double precision, parameter one
Definition: param1_mod.f:29
double precision, dimension(dimension_bc, dim_m) bc_w_s
Definition: bc_mod.f:129
integer, parameter dim_m
Definition: param_mod.f:67
integer, parameter dimension_bc
Definition: param_mod.f:61
double precision, parameter undefined
Definition: param1_mod.f:18
double precision, dimension(:), allocatable a
Definition: scalars_mod.f:29
double precision, dimension(dimension_bc) bc_v_g
Definition: bc_mod.f:117
character, dimension(dimension_bc) bc_plane
Definition: bc_mod.f:217
subroutine init_err_msg(CALLER)
logical, dimension(dimension_bc) bc_defined
Definition: bc_mod.f:207
Definition: run_mod.f:13
Definition: param_mod.f:2
logical no_k
Definition: geometry_mod.f:28
double precision, dimension(dimension_bc, dim_m) bc_v_s
Definition: bc_mod.f:121
double precision, dimension(dimension_bc) bc_u_g
Definition: bc_mod.f:109
logical no_j
Definition: geometry_mod.f:24
subroutine check_bc_vel_inflow(M_TOT, SKIP, BCV)
Definition: set_bc_flow.f:114
double precision, dimension(dimension_bc, dim_m) bc_u_s
Definition: bc_mod.f:113
character(len=line_length), dimension(line_count) err_msg
subroutine check_bc_vel_outflow(M_TOT, SKIP, BCV)
Definition: set_bc_flow.f:305
double precision, dimension(dimension_bc) bc_ep_g
Definition: bc_mod.f:77
integer smax
Definition: physprop_mod.f:22
double precision, dimension(dimension_bc) bc_w_g
Definition: bc_mod.f:125
double precision, dimension(dimension_bc, dim_m) bc_ep_s
Definition: bc_mod.f:93
double precision, parameter zero
Definition: param1_mod.f:27
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
double precision, dimension(dimension_bc, dim_m) bc_rop_s
Definition: bc_mod.f:92
Definition: bc_mod.f:23