MFIX  2016-1
check_bc_outflow.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: CHECK_BC_OUTFLOW !
4 ! Author: J.Musser Date: 01-Mar-14 !
5 ! !
6 ! Purpose: Provided a detailed error message concerning specification !
7 ! of bc_ep_g + bc_rop_s at a outflow boundary (and pressure inflow) !
8 ! !
9 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
10  SUBROUTINE check_bc_outflow(M_TOT, BCV)
11 
12 ! Modules
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 ! Dummy arguments
24 ! --------------------------------------------------------------------//
25 ! loop/variable indices
26  INTEGER, INTENT(in) :: BCV
27  INTEGER, INTENT(in) :: M_TOT
28 
29 ! Local variables
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 ! if bc_ep_g is defined at the outflow boundary, then the sum of ep_g
39 ! and ep_s at the boundary may not equal one given the code in the
40 ! subroutine set_outflow (see code for details).
41 ! therefore if bc_ep_g and/or bc_rop_s are defined, perform possible
42 ! data consistency checks and, when appropriate, provide the user with
43 ! a warning about their chosen settings.
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 ! what does it mean to force the bulk density to zero at the
60 ! boundary? (does this value matter anyway?)
61  bc_rop_s(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 ! bc_ep_g is defined but some bc_rop_s(m) are undefined.
66 ! in this case, ep_p in the outflow boundary will be based on the user
67 ! defined value of bc_ep_g, while rop_s would become based on the
68 ! value in the adjacent fluid cell. consequently, no check ensures
69 ! the result is consistent with a requirement for ep_g+ep_s=1.
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 ! end if(bc_rop_s(bcv,m) == undefined)
76 
77 ! by this point bc_rop_s should either be defined or mfix exited
78 ! therefore we can check that sum of void fraction and solids volume
79 ! fractions
80  sum_ep = sum_ep + bc_rop_s(bcv,m)/ro_s0(m)
81  ENDDO
82 
83 ! now verify that the volume fractions sum to one.
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 ! bc_ep_g is not defined but check if any bc_rop_s are defined
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 ! verify that the sum of any specified volume fractions is not greater
104 ! than one
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 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
132 ! !
133 ! Subroutine: CHECK_BC_P_OUTFLOW !
134 ! Author: J.Musser Date: 01-Mar-14 !
135 ! !
136 ! Purpose: Provided a detailed error message on bc !
137 ! !
138 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
139  SUBROUTINE check_bc_p_outflow(M_TOT, BCV)
141 ! Modules
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 ! Dummy arguments
151 ! --------------------------------------------------------------------//
152 ! loop/variable indices
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 ! Clean up and return.
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 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
184 ! !
185 ! Subroutine: CHECK_BC_MASS_OUTFLOW !
186 ! Author: J.Musser Date: 01-Mar-14 !
187 ! !
188 ! Purpose: Provided a detailed error message when the sum of volume !
189 ! !
190 ! Comments: !
191 ! The velocities at the outflow face are fixed and the momentum !
192 ! equations are not solved in the outflow cells. Since the flow !
193 ! is out of the domain none of the other scalars should need to !
194 ! be specified (e.g., mass fractions, void fraction, etc.,). !
195 ! Such values will become defined according to their adjacent !
196 ! fluid cell !
197 ! !
198 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
199  SUBROUTINE check_bc_mass_outflow(M_TOT, BCV)
201 ! Modules
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 ! Dummy arguments
215 ! --------------------------------------------------------------------//
216 ! loop/variable indices
217  INTEGER, intent(in) :: BCV
218  INTEGER, intent(in) :: M_TOT
219 ! Local variables
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 ! This check probably needs changed.
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 ! end if/else (ro_g0 /=undefined)
284 
285  1100 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
double precision, dimension(dimension_bc) bc_dt_0
Definition: bc_mod.f:221
double precision, dimension(dimension_bc) bc_volflow_g
Definition: bc_mod.f:195
subroutine check_bc_outflow(M_TOT, BCV)
character(len=32) function ivar(VAR, i1, i2, i3)
subroutine check_bc_p_outflow(M_TOT, BCV)
double precision, dimension(dimension_bc) bc_t_g
Definition: bc_mod.f:97
subroutine finl_err_msg
logical function compare(V1, V2)
Definition: toleranc_mod.f:94
double precision, parameter one
Definition: param1_mod.f:29
character(len=3), dimension(dim_m) solids_model
Definition: run_mod.f:253
double precision, parameter undefined
Definition: param1_mod.f:18
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)
double precision, dimension(dimension_bc, dim_m) bc_volflow_s
Definition: bc_mod.f:198
double precision ro_g0
Definition: physprop_mod.f:59
subroutine check_bc_mass_outflow(M_TOT, BCV)
double precision, dimension(dimension_bc) bc_p_g
Definition: bc_mod.f:80
Definition: run_mod.f:13
double precision, dimension(dimension_bc) bc_massflow_g
Definition: bc_mod.f:201
double precision, dimension(dimension_bc, dim_m) bc_massflow_s
Definition: bc_mod.f:204
double precision, dimension(dimension_bc) bc_u_g
Definition: bc_mod.f:109
character(len=line_length), dimension(line_count) err_msg
double precision, dimension(dimension_bc) bc_ep_g
Definition: bc_mod.f:77
double precision, dimension(dim_m) ro_s0
Definition: physprop_mod.f:28
double precision, dimension(dimension_bc) bc_w_g
Definition: bc_mod.f:125
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