MFIX  2016-1
check_bc_walls.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: CHECK_BC_WALLS !
4 ! Author: J.Musser Date: 01-Mar-14 !
5 ! !
6 ! Purpose: Driver routine to call checks for WALL BCs. !
7 ! !
8 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
9  SUBROUTINE check_bc_walls(M_TOT, SKIP, BCV)
10 
11 
12 ! Global Variables:
13 !---------------------------------------------------------------------//
14 ! Flag: Identifies solids model (TFM,DEM,PIC)
15  use run, only: solids_model
16 ! User-input: solids kinetic-theory model.
17  use run, only: kt_type_enum, ghd_2007
18 
19 ! Global Parameters:
20 !---------------------------------------------------------------------//
21 ! Maximum number of solids phases
22  use param, only: dim_m
23 
24 ! Use the error manager for posting error messages.
25 !---------------------------------------------------------------------//
26  use error_manager
27 
28  IMPLICIT NONE
29 
30 ! Dummy Arguments.
31 !---------------------------------------------------------------------//
32 ! Index of BC being checked.
33  INTEGER, INTENT(in) :: BCV
34 ! Total number of solids phases.
35  INTEGER, INTENT(in) :: M_TOT
36 ! Flag. Solids not present at this BC (used for flow BCs).
37  LOGICAL, INTENT(in) :: SKIP(dim_m)
38 
39 ! Local Variables:
40 !---------------------------------------------------------------------//
41 ! Loop/counter variable.
42  INTEGER :: M
43 ! Local total number of solids phases
44  INTEGER :: MTOT_L
45 !......................................................................!
46 
47 
48 ! Initialize the error manager.
49  CALL init_err_msg("CHECK_BC_WALLS")
50 
51 ! Input checks for gas phase.
52  CALL check_bc_walls_gas(bcv)
53 
54  mtot_l = merge( m_tot+1, m_tot, kt_type_enum == ghd_2007)
55 
56 ! Input checks for solid phases.
57  DO m=1, mtot_l
58  SELECT CASE(solids_model(m))
59  CASE ('TFM'); CALL check_bc_walls_tfm(bcv, m)
60  CASE ('DEM'); CALL check_bc_walls_discrete(bcv, m)
61  CASE ('PIC'); CALL check_bc_walls_discrete(bcv, m)
62  END SELECT
63  ENDDO
64 
65 ! Input checks for user-defined scalar equations.
66  CALL check_bc_walls_scalar_eq(bcv)
67 
68  CALL finl_err_msg
69 
70  RETURN
71  END SUBROUTINE check_bc_walls
72 
73 
74 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
75 ! !
76 ! Subroutine: CHECK_BC_WALLS_GAS !
77 ! Author: J.Musser Date: 01-Mar-14 !
78 ! !
79 ! Purpose: Check user-input for gas phase WALL BC parameters. !
80 ! !
81 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
82  SUBROUTINE check_bc_walls_gas(BCV)
83 
84 ! Global Variables:
85 !---------------------------------------------------------------------//
86 ! User-input: type of BC
87  use bc
88 ! User-Input: gas velocity at wall BCs.
89  use bc, only: bc_uw_g, bc_vw_g, bc_ww_g
90 ! User-Input: gas energy eq BCs.
91  use bc, only: bc_hw_t_g, bc_tw_g, bc_c_t_g
92 ! User-Input: gas species eq BCs.
93  use bc, only: bc_hw_x_g, bc_xw_g, bc_c_x_g
94 ! Total number of speices in each phase.
95  use physprop, only: nmax
96 ! Flag: Solve energy equations.
97  use run, only: energy_eq
98 ! Flag: Solve species equations.
99  use run, only: species_eq
100 ! Flag: Solve K-th direction (3D)
101  use geometry, only: do_k
102 
103 ! Global Parameters:
104 !---------------------------------------------------------------------//
105 ! Parameter constants.
106  use param1, only: zero, undefined
107 
108 ! Use the error manager for posting error messages.
109 !---------------------------------------------------------------------//
110  use error_manager
111 
112  IMPLICIT NONE
113 
114 ! Dummy Arguments.
115 !---------------------------------------------------------------------//
116  INTEGER, INTENT(in) :: BCV
117 
118  INTEGER :: N
119 !......................................................................!
120 
121 
122 ! Initialize the error manger.
123  CALL init_err_msg("CHECK_BC_WALLS_GAS")
124 
125 ! The wall velocities are not needed for no-slip or free-slip
126  IF(bc_type_enum(bcv) == par_slip_wall) THEN
127  IF(bc_uw_g(bcv) == undefined) THEN
128  WRITE(err_msg,1000) trim(ivar('BC_Uw_g',bcv))
129  CALL flush_err_msg(abort=.true.)
130  ELSEIF(bc_vw_g(bcv) == undefined) THEN
131  WRITE(err_msg,1000) trim(ivar('BC_Vw_g',bcv))
132  CALL flush_err_msg(abort=.true.)
133  ELSEIF(bc_ww_g(bcv) == undefined) THEN
134  IF(do_k)THEN
135  WRITE(err_msg,1000) trim(ivar('BC_Ww_g',bcv))
136  CALL flush_err_msg(abort=.true.)
137  ELSE
138  bc_ww_g(bcv) = zero
139  ENDIF
140  ENDIF
141  ENDIF
142 
143 ! Check energy equation input.
144  IF(energy_eq) THEN
145  IF(bc_hw_t_g(bcv) < zero) THEN
146  WRITE(err_msg,1001) trim(ivar('BC_HW_T_g',bcv)), &
147  trim(ival(bc_hw_t_g(bcv)))
148  CALL flush_err_msg(abort=.true.)
149  ENDIF
150  IF(bc_hw_t_g(bcv)/=zero .AND. &
151  bc_tw_g(bcv)==undefined) THEN
152  WRITE(err_msg,1000) trim(ivar('BC_Tw_g',bcv))
153  CALL flush_err_msg(abort=.true.)
154  ENDIF
155  IF(bc_hw_t_g(bcv)/=undefined .AND. &
156  bc_c_t_g(bcv)==undefined) THEN
157  WRITE(err_msg,1000) trim(ivar('BC_C_T_g',bcv))
158  CALL flush_err_msg(abort=.true.)
159  ENDIF
160  ENDIF
161 
162 
163 ! Check species equation input.
164  IF(species_eq(0)) THEN
165  DO n=1, nmax(0)
166  IF(bc_hw_x_g(bcv,n) < zero) THEN
167  WRITE(err_msg,1001) trim(ivar('BC_HW_X_g',bcv,n)), &
168  trim(ival(bc_hw_x_g(bcv,n)))
169  CALL flush_err_msg(abort=.true.)
170  ENDIF
171  IF(bc_hw_x_g(bcv,n)/=zero .AND. &
172  bc_xw_g(bcv,n)==undefined) THEN
173  WRITE(err_msg,1000) trim(ivar('BC_Xw_g',bcv,n))
174  CALL flush_err_msg(abort=.true.)
175  ENDIF
176  IF(bc_hw_x_g(bcv,n)/=undefined .AND. &
177  bc_c_x_g(bcv,n)==undefined) THEN
178  WRITE(err_msg,1000) trim(ivar('BC_C_X_g',bcv,n))
179  CALL flush_err_msg(abort=.true.)
180  ENDIF
181  ENDDO
182  ENDIF
183 
184 
185 ! Clear the error manager.
186  CALL finl_err_msg
187 
188  RETURN
189 
190  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
191  'correct the mfix.dat file.')
192 
193  1001 FORMAT('Error 1001: Illegal or unphysical input: ',a,' = ',a,/ &
194  'Please correct the mfix.dat file.')
195 
196  END SUBROUTINE check_bc_walls_gas
197 
198 
199 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
200 ! !
201 ! Subroutine: CHECK_BC_WALLS_TFM !
202 ! Author: J.Musser Date: 01-Mar-14 !
203 ! !
204 ! Purpose: Check user-input for TFM solids WALL BC parameters. !
205 ! !
206 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
207  SUBROUTINE check_bc_walls_tfm(BCV,M)
209 
210 ! Global Variables:
211 !---------------------------------------------------------------------//
212 ! User-input: type of BC
213  use bc
214 ! User-Input: solids velocity at wall BCs.
215  use bc, only: bc_uw_s, bc_vw_s, bc_ww_s
216 ! User-Input: solids energy eq BCs.
217  use bc, only: bc_hw_t_s, bc_tw_s, bc_c_t_s
218 ! User-Input: solids species eq BCs.
219  use bc, only: bc_hw_x_s, bc_xw_s, bc_c_x_s
220 ! User-Input: granular energy eq BCs.
222 ! Total number of solids phases
223  use physprop, only: mmax
224 ! Total number of speices in each phase.
225  use physprop, only: nmax
226 ! Flag: Solve energy equations.
227  use run, only: energy_eq
228 ! Flag: Solve species equations.
229  use run, only: species_eq
230 ! Flag: Solve Granular energy PDE
231  use run, only: granular_energy
232 ! User-input: solids kinetic-theory model.
233  use run, only: kt_type_enum, ghd_2007
234 ! Flag: Use johnson and jackson bc
235  use bc, only: bc_jj_ps
236 ! Flag: use revised phip for JJ BC.
237  use run, only: bc_jj_m, phip_out_jj
238 ! Flag: use jenkins small friction bc
239  use run, only: jenkins
240 ! User input: particle wall restitution coefficient and
241 ! angle of internal friction at walls (degrees)
242  use constant, only: e_w, phi_w
243 ! Used by jenkins or revised phip bcs
244  use constant, only: tan_phi_w
245 ! Used by revised phip for jj bc
246  use constant, only: k4phi, phip0
247 ! User-Input: number of reactionrates
248 ! use rxns, only: nrr
249 ! Flag: Solve K-th direction (3D)
250  use geometry, only: do_k
251 ! Flag: use cartesian grid
252  use cutcell, only: cartesian_grid
253 
254 ! Global Parameters:
255 !---------------------------------------------------------------------//
256 ! Parameter constants.
257  use param1, only: one, zero, undefined, undefined_i
258 ! parameter values
259  use constant, only: pi
260 
261  use rxns
262 ! Use the error manager for posting error messages.
263 !---------------------------------------------------------------------//
264  use error_manager
265  use funits, only: unit_log
266  IMPLICIT NONE
267 
268 ! Dummy Arguments.
269 !---------------------------------------------------------------------//
270 ! Index of BC being checked.
271  INTEGER, INTENT(in) :: BCV
272 ! Index of solids phase.
273  INTEGER, INTENT(in) :: M
274 
275 ! Local Variables:
276 !---------------------------------------------------------------------//
277 ! Loop/variable counter.
278  INTEGER :: NN
279 ! Flag to check momentum eq input.
280  LOGICAL :: CHECK_MOMENTUM
281 ! Flag to check scalar eq input.
282  LOGICAL :: CHECK_SCALARS
283 !......................................................................!
284 
285 
286 ! Initialize the error manager.
287  CALL init_err_msg("CHECK_BC_WALLS_TFM")
288 
289 ! Toggle the momentum and scalar input variable checks.
290  SELECT CASE(kt_type_enum)
291  CASE (ghd_2007)
292  check_momentum = (m == mmax)
293  check_scalars = (m /= mmax)
294  CASE DEFAULT
295  check_momentum = .true.
296  check_scalars = .true.
297  END SELECT
298 
299 ! Set the default specification of Johnson-Jackson BC
300  IF(bc_jj_ps(bcv) == undefined_i) &
301  bc_jj_ps(bcv) = merge(1,0,granular_energy)
302 
303 ! specifying bc_jj_ps=1 without granular_energy would cause problem in
304 ! the momentum bc routines
305  IF(.NOT.granular_energy .AND. bc_jj_ps(bcv) == 1) THEN
306  WRITE(err_msg, 1101)
307  CALL flush_err_msg(abort=.true.)
308  ENDIF
309  1101 FORMAT('Error 1101: Invoking BC_JJ_PS requires GRANULAR_ENERGY', &
310  '=.TRUE.',/ 'Please correct the mfix.dat file.')
311 
312 ! The wall velocities are not needed for no-slip or free-slip
313 ! Wall velocities are needed if johnson-jackson bc model is used
314  IF(check_momentum) THEN
315  IF(bc_type_enum(bcv) == par_slip_wall .OR. &
316  bc_jj_ps(bcv) /= zero) THEN
317  IF(bc_uw_s(bcv,m) == undefined) THEN
318  WRITE(err_msg,1000) trim(ivar('BC_Uw_s',bcv,m))
319  CALL flush_err_msg(abort=.true.)
320  ELSEIF(bc_vw_s(bcv,m) == undefined) THEN
321  WRITE(err_msg,1000) trim(ivar('BC_Vw_s',bcv,m))
322  CALL flush_err_msg(abort=.true.)
323  ELSEIF(bc_ww_s(bcv,m) == undefined) THEN
324  IF(do_k)THEN
325  WRITE(err_msg,1000) trim(ivar('BC_Ww_s',bcv,m))
326  CALL flush_err_msg(abort=.true.)
327  ELSE
328  bc_ww_s(bcv,m) = zero
329  ENDIF
330  ENDIF
331  ENDIF
332 
333  IF(granular_energy .AND. bc_jj_ps(bcv)==0) THEN
334  IF(bc_hw_theta_m(bcv,m) < zero) THEN
335  WRITE(err_msg,1001) trim(ivar('BC_HW_Theta_M',bcv,m)), &
336  trim(ival(bc_hw_theta_m(bcv,m)))
337  CALL flush_err_msg(abort=.true.)
338  ENDIF
339  IF(bc_hw_theta_m(bcv,m)/=zero .AND. &
340  bc_thetaw_m(bcv,m)==undefined) THEN
341  WRITE(err_msg,1000) trim(ivar('BC_ThetaW_M',bcv,m))
342  CALL flush_err_msg(abort=.true.)
343  ENDIF
344  IF(bc_hw_theta_m(bcv,m)/=undefined .AND. &
345  bc_c_theta_m(bcv,m)==undefined) THEN
346  WRITE(err_msg,1000) trim(ivar('BC_C_THETA_M',bcv,m))
347  CALL flush_err_msg(abort=.true.)
348  ENDIF
349  ENDIF
350  ELSE
351  ENDIF
352 
353  IF(check_scalars)THEN
354  IF(energy_eq) THEN
355  IF(bc_hw_t_s(bcv,m) < zero) THEN
356  WRITE(err_msg,1001) trim(ivar('BC_HW_T_s',bcv,m)), &
357  trim(ival(bc_hw_t_s(bcv,m)))
358  CALL flush_err_msg(abort=.true.)
359  ENDIF
360  IF(bc_hw_t_s(bcv,m)/=zero .AND. &
361  bc_tw_s(bcv,m)==undefined) THEN
362  WRITE(err_msg,1000) trim(ivar('BC_Tw_s',bcv,m))
363  CALL flush_err_msg(abort=.true.)
364  ENDIF
365  IF(bc_hw_t_s(bcv,m)/=undefined .AND. &
366  bc_c_t_s(bcv,m)==undefined) THEN
367  WRITE(err_msg,1000) trim(ivar('BC_C_T_s',bcv,m))
368  CALL flush_err_msg(abort=.true.)
369  ENDIF
370  ENDIF
371 
372  IF(species_eq(m)) THEN
373  DO nn=1, nmax(m)
374  IF(bc_hw_x_s(bcv,m,nn) < zero) THEN
375  WRITE(err_msg,1001) trim(ivar('BC_HW_X_s',bcv,m,nn)), &
376  trim(ival(bc_hw_x_s(bcv,m,nn)))
377  CALL flush_err_msg(abort=.true.)
378  ENDIF
379  IF(bc_hw_x_s(bcv,m,nn)/=zero .AND. &
380  bc_xw_s(bcv,m,nn)==undefined) THEN
381  WRITE(err_msg,1000) trim(ivar('BC_Xw_s',bcv,m,nn))
382  CALL flush_err_msg(abort=.true.)
383  ENDIF
384  IF(bc_hw_x_s(bcv,m,nn)/=undefined .AND. &
385  bc_c_x_s(bcv,m,nn)==undefined) THEN
386  WRITE(err_msg,1000) trim(ivar('BC_C_X_s',bcv,m,nn))
387  CALL flush_err_msg(abort=.true.)
388  ENDIF
389  ENDDO
390  ENDIF ! Species Equation
391  ELSE
392  ENDIF ! Check Scalars
393 
394 
395 ! might make sense to move these checks out of this routine
396 ! but placed here for now
397  IF(granular_energy .AND. bc_jj_ps(bcv) == 1) THEN
398 
399  IF(kt_type_enum == ghd_2007) THEN
400  WRITE(err_msg, 1201)
401  CALL flush_err_msg(abort=.true.)
402  ENDIF
403 
404  IF(cartesian_grid) THEN
405 ! the user should really be warned this is not implemented as
406 ! opposed to running with it
407  WRITE(err_msg, 1202)
408  CALL flush_err_msg(abort=.true.)
409  ENDIF
410 
411 ! small frictional boundary condition model
412  IF(jenkins) THEN
413  IF (bc_jj_m) THEN
414  WRITE(err_msg, 1203)
415  CALL flush_err_msg(abort=.true.)
416  ELSEIF (phi_w == undefined) THEN
417  WRITE(err_msg, 1204)
418  CALL flush_err_msg(abort=.true.)
419  ELSEIF (e_w > one .OR. e_w < zero) THEN
420  WRITE(err_msg, 1001) 'E_W', e_w
421  CALL flush_err_msg(abort=.true.)
422  ENDIF
423 ! PHI_W is given in degrees but calculated in radian within
424 ! the fortran codes
425  tan_phi_w = tan(phi_w*pi/180.d0)
426  ENDIF
427 
428 ! k4phi, phip0 for variable specularity coefficient
429  k4phi = undefined
430  IF(bc_jj_m) THEN
431  IF (jenkins) THEN
432  WRITE(err_msg, 1203)
433  CALL flush_err_msg(abort=.true.)
434  ELSEIF (phi_w == undefined) THEN
435  WRITE(err_msg, 1204)
436  CALL flush_err_msg(abort=.true.)
437  ELSEIF (e_w > one .OR. e_w < zero) THEN
438  WRITE(err_msg, 1001) 'E_W', e_w
439  CALL flush_err_msg(abort=.true.)
440  ENDIF
441 ! PHI_W is given in degrees but calculated in radian within
442 ! the fortran codes
443  tan_phi_w = tan(phi_w*pi/180.d0)
444 
445  k4phi = 7.d0/2.d0*tan_phi_w*(1.d0+e_w)
446  IF (phip0 .eq. undefined) THEN
447  phip0 = -0.0012596340709032689 + &
448  0.10645510095633175*k4phi - &
449  0.04281476447854031*k4phi**2 + &
450  0.009759402181229842*k4phi**3 - &
451  0.0012508257938705263*k4phi**4 + &
452  0.00008369829630479206*k4phi**5 - &
453  0.000002269550565981776*k4phi**6
454 ! if k4phi is less than 0.2, the analytical expression for phi is used
455 ! to estimate the phi at r->0
456  IF (k4phi .le. 0.2d0) THEN
457  phip0=0.09094568176225006*k4phi
458  ENDIF
459  WRITE (unit_log, 1207) phip0
460  ENDIF
461  IF (phip0 < 0) THEN
462  WRITE(err_msg, 1208)
463  CALL flush_err_msg(abort=.true.)
464  ENDIF
465 
466  IF (phip_out_jj) THEN
467  IF(nrr < 1) THEN
468  WRITE(err_msg, 1209)
469  CALL flush_err_msg(abort=.true.)
470  ENDIF
471  WRITE (unit_log, 1210) phip0
472  ENDIF
473  ENDIF
474  ENDIF ! if granular_energy and bc_jj_ps = 1
475 
476 
477  CALL finl_err_msg
478 
479  RETURN
480 
481  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
482  'correct the mfix.dat file.')
483 
484  1001 FORMAT('Error 1001: Illegal or unphysical input: ',a,' = ',a,/ &
485  'Please correct the mfix.dat file.')
486 
487  1201 FORMAT('Error 1201: KT_TYPE = "GHD" cannot be used with ',&
488  ' BC_JJ_PS',/'Please correct the mfix.dat file.')
489 
490  1202 FORMAT('Error 1202: CARTESIAN_GRID cannot be used with ',&
491  ' BC_JJ_PS',/'Please correct the mfix.dat file.')
492 
493  1203 FORMAT('Error 1203: JENKINS and BC_JJ_M cannot be used at the',&
494  ' same time',/'Please correct the mfix.dat file.')
495  1204 FORMAT('Error 1204: Angle of particle-wall friction (PHI_W) not',&
496  ' specified.',/'Please correct the mfix.dat file.')
497 
498  1208 FORMAT('Error 1208: phip0 less than zero.')
499  1209 FORMAT('Error 1209: nRR should be at least 1 for storing ',&
500  'specularity.')
501 
502  1207 FORMAT(/1x,70('*')//' From: CHECK_BC_WALLS_TFM',/' Message: ',&
503  'No input for phip0 available, working expression is used.',/ &
504  'phip0=',g12.5,/1x,70('*')/)
505  1210 FORMAT(/1x,70('*')//' From: CHECK_BC_WALLS_TFM',/' Message: ',&
506  'Specularity will be stored as the first element of ', &
507  'ReactionRates',/1x,'array in WALL CELLS. Please avoid ', &
508  'overwriting it when reacting flow',/1x,' is simulated.', &
509  /1x,70('*')/)
510 
511  END SUBROUTINE check_bc_walls_tfm
512 
513 
514 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
515 ! !
516 ! Subroutine: CHECK_BC_WALLS_DISCRETE !
517 ! Author: J.Musser Date: 01-Mar-14 !
518 ! !
519 ! Purpose: Check user-input for DEM/PIC solids WALL BC parameters. !
520 ! !
521 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
522  SUBROUTINE check_bc_walls_discrete(BCV,M)
524 
525 ! Global Variables:
526 !---------------------------------------------------------------------//
527 ! User-Input: solids velocity at wall BCs.
528  use bc, only: bc_uw_s, bc_vw_s, bc_ww_s
529 ! User-Input: solids energy eq BCs.
530  use bc, only: bc_hw_t_s, bc_tw_s, bc_c_t_s
531 ! User-Input: solids species eq BCs.
532  use bc, only: bc_hw_x_s, bc_xw_s, bc_c_x_s
533 
534 ! Global Parameters:
535 !---------------------------------------------------------------------//
536 ! Maximum number of possible species.
537  use param, only: dim_n_s
538 ! Parameter constants.
539  use param1, only: undefined, zero
540 
541 ! Use the error manager for posting error messages.
542 !---------------------------------------------------------------------//
543  use error_manager
544 
545  IMPLICIT NONE
546 
547 ! Dummy Arguments.
548 !---------------------------------------------------------------------//
549 ! Index of BC getting checked.
550  INTEGER, INTENT(in) :: BCV
551 ! Index of solid phase getting checked.
552  INTEGER, INTENT(in) :: M
553 
554 ! Local Variables:
555 !---------------------------------------------------------------------//
556 ! Loop/variable counter.
557  INTEGER :: NN
558 !......................................................................!
559 
560 
561 ! Initialize the error manager.
562  CALL init_err_msg("CHECK_BC_WALLS_DISCRETE")
563 
564 ! DEM and PIC are restricted to adiabatic walls.
565  IF((bc_hw_t_s(bcv,m) /= undefined) .and. &
566  & (bc_hw_t_s(bcv,m) /= zero)) THEN
567  WRITE(err_msg,1100) trim(ivar('BC_HW_T_s',bcv,m))
568  CALL flush_err_msg(abort=.true.)
569  ELSEIF((bc_c_t_s(bcv,m) /= undefined) .and. &
570  & (bc_c_t_s(bcv,m) /= zero))THEN
571  WRITE(err_msg,1100) trim(ivar('BC_C_T_s',bcv,m))
572  CALL flush_err_msg(abort=.true.)
573  ENDIF
574 
575  1100 FORMAT('Error 1100: ',a,' should not specified for DEM/PIC',/ &
576  'to be non-zero as they are currently limited to constant',/ &
577  'constant temperature BCs.',&
578  /'Please correct the mfix.dat file.')
579 
580 
581 ! The following checks verify that TFM solids parameters are not
582 ! specified for discrete solids.
583 
584 
585 ! The wall velocities are not needed DEM/PIC solids
586  IF(bc_uw_s(bcv,m) /= undefined) THEN
587  WRITE(err_msg,1101) bcv, trim(ivar('BC_Uw_s',bcv,m))
588  CALL flush_err_msg(abort=.true.)
589  ELSEIF(bc_vw_s(bcv,m) /= undefined) THEN
590  WRITE(err_msg,1101) bcv, trim(ivar('BC_Vw_s',bcv,m))
591  CALL flush_err_msg(abort=.true.)
592  ELSEIF(bc_ww_s(bcv,m) /= undefined) THEN
593  WRITE(err_msg,1101) bcv, trim(ivar('BC_Ww_s',bcv,m))
594  CALL flush_err_msg(abort=.true.)
595  ENDIF
596 
597 ! DEM cannot have a species flux at the walls.
598  DO nn=1, dim_n_s
599  IF(bc_hw_x_s(bcv,m,nn) /= undefined) THEN
600  WRITE(err_msg,1101) bcv, trim(ivar('BC_HW_X_s',bcv,m,nn))
601  CALL flush_err_msg(abort=.true.)
602  ELSEIF(bc_xw_s(bcv,m,nn) /= undefined) THEN
603  WRITE(err_msg,1101) bcv, trim(ivar('BC_Xw_s',bcv,m,nn))
604  CALL flush_err_msg(abort=.true.)
605  ELSEIF(bc_c_x_s(bcv,m,nn) /= undefined) THEN
606  WRITE(err_msg,1101) bcv, trim(ivar('BC_C_X_s',bcv,m,nn))
607  CALL flush_err_msg(abort=.true.)
608  ENDIF
609  ENDDO
610 
611  1101 FORMAT('Error 1101: Illegal input for boundary condition: ',i3,/ &
612  a,' should not be specified for DEM/PIC simulations.',/ &
613  'Please correct the mfix.dat file.')
614 
615  CALL finl_err_msg
616 
617  RETURN
618 
619  END SUBROUTINE check_bc_walls_discrete
620 
621 
622 
623 
624 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
625 ! !
626 ! Subroutine: CHECK_BC_WALLS_SCALAR_EQ !
627 ! Author: J.Musser Date: 01-Mar-14 !
628 ! !
629 ! Purpose: Check user-input for generic scalar eq WALL BC parameters. !
630 ! !
631 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
632  SUBROUTINE check_bc_walls_scalar_eq(BCV)
634 
635 ! Global Variables:
636 !---------------------------------------------------------------------//
637 ! User-input: number of generic scalar equations to solve.
638  use scalars, only: nscalar
639 ! User-Input: generic scalar eq at wall BCs.
641 
642 ! Global Parameters:
643 !---------------------------------------------------------------------//
644 ! Parameter constants
645  use param1, only: zero, undefined
646 
647 ! Use the error manager for posting error messages.
648 !---------------------------------------------------------------------//
649  use error_manager
650 
651  IMPLICIT NONE
652 
653 ! Dummy Arguments.
654 !---------------------------------------------------------------------//
655 ! Index of BC getting checked.
656  INTEGER, INTENT(in) :: BCV
657 
658 ! Local Variables:
659 !---------------------------------------------------------------------//
660 ! Loop/counter variable.
661  INTEGER :: NN
662 !......................................................................!
663 
664 
665 ! Initialize the error manager.
666  CALL init_err_msg("CHECK_BC_WALLS_SCALAR_EQ")
667 
668  DO nn=1, nscalar
669  IF(bc_hw_scalar(bcv,nn) < zero) THEN
670  WRITE(err_msg,1001) trim(ivar('BC_HW_SCALAR',bcv,nn)), &
671  trim(ival(bc_hw_scalar(bcv,nn)))
672  CALL flush_err_msg(abort=.true.)
673  ENDIF
674  IF(bc_hw_scalar(bcv,nn) /= zero .AND. &
675  bc_scalarw(bcv,nn) == undefined) THEN
676  WRITE(err_msg,1000) trim(ivar('BC_SCALARw',bcv,nn))
677  CALL flush_err_msg(abort=.true.)
678  ENDIF
679  IF(bc_hw_scalar(bcv,nn) /= undefined .AND. &
680  bc_c_scalar(bcv,nn) == undefined) THEN
681  WRITE(err_msg,1000) trim(ivar('BC_C_SCALAR',bcv,nn))
682  ENDIF
683  ENDDO
684 
685  CALL finl_err_msg
686 
687  RETURN
688 
689  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
690  'correct the mfix.dat file.')
691 
692  1001 FORMAT('Error 1001: Illegal or unphysical input: ',a,' = ',a,/ &
693  'Please correct the mfix.dat file.')
694 
695  END SUBROUTINE check_bc_walls_scalar_eq
double precision, dimension(dimension_bc, dim_m) bc_ww_s
Definition: bc_mod.f:328
double precision e_w
Definition: constant_mod.f:85
double precision, dimension(dimension_bc, dim_scalar) bc_scalarw
Definition: bc_mod.f:396
double precision, dimension(dimension_bc) bc_uw_g
Definition: bc_mod.f:313
double precision, dimension(dimension_bc, dim_m) bc_uw_s
Definition: bc_mod.f:322
character(len=32) function ivar(VAR, i1, i2, i3)
double precision, dimension(dimension_bc, dim_m, dim_n_s) bc_hw_x_s
Definition: bc_mod.f:365
subroutine finl_err_msg
double precision, dimension(dimension_bc, dim_scalar) bc_c_scalar
Definition: bc_mod.f:392
double precision, parameter one
Definition: param1_mod.f:29
double precision, dimension(dimension_bc, dim_n_g) bc_c_x_g
Definition: bc_mod.f:374
double precision, dimension(dimension_bc) bc_hw_t_g
Definition: bc_mod.f:332
Definition: rxns_mod.f:1
logical, dimension(0:dim_m) species_eq
Definition: run_mod.f:115
double precision, dimension(dimension_bc, dim_m) bc_tw_s
Definition: bc_mod.f:341
integer, parameter dim_m
Definition: param_mod.f:67
character(len=3), dimension(dim_m) solids_model
Definition: run_mod.f:253
double precision, parameter undefined
Definition: param1_mod.f:18
subroutine check_bc_walls_scalar_eq(BCV)
double precision phi_w
Definition: constant_mod.f:120
subroutine init_err_msg(CALLER)
logical jenkins
Definition: run_mod.f:166
double precision, dimension(dimension_bc, dim_m) bc_thetaw_m
Definition: bc_mod.f:355
double precision, dimension(dimension_bc, dim_m) bc_c_theta_m
Definition: bc_mod.f:358
double precision k4phi
Definition: constant_mod.f:83
integer mmax
Definition: physprop_mod.f:19
double precision, dimension(dimension_bc, dim_m, dim_n_s) bc_c_x_s
Definition: bc_mod.f:377
logical bc_jj_m
Definition: run_mod.f:168
double precision, dimension(dimension_bc) bc_tw_g
Definition: bc_mod.f:338
double precision, dimension(dimension_bc, dim_m, dim_n_s) bc_xw_s
Definition: bc_mod.f:371
integer, parameter unit_log
Definition: funits_mod.f:21
Definition: run_mod.f:13
integer nrr
Definition: rxns_mod.f:10
double precision, dimension(dimension_bc, dim_n_g) bc_xw_g
Definition: bc_mod.f:368
Definition: param_mod.f:2
logical cartesian_grid
Definition: cutcell_mod.f:13
double precision, dimension(dimension_bc) bc_c_t_g
Definition: bc_mod.f:344
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
logical do_k
Definition: geometry_mod.f:30
double precision, dimension(dimension_bc) bc_vw_g
Definition: bc_mod.f:316
logical energy_eq
Definition: run_mod.f:100
double precision, dimension(dimension_bc, dim_m) bc_c_t_s
Definition: bc_mod.f:347
subroutine check_bc_walls_discrete(BCV, M)
integer, parameter undefined_i
Definition: param1_mod.f:19
subroutine check_bc_walls_tfm(BCV, M)
subroutine check_bc_walls(M_TOT, SKIP, BCV)
character(len=line_length), dimension(line_count) err_msg
logical phip_out_jj
Definition: run_mod.f:170
integer, parameter dim_n_s
Definition: param_mod.f:71
integer nscalar
Definition: scalars_mod.f:7
double precision, dimension(dimension_bc, dim_m) bc_hw_theta_m
Definition: bc_mod.f:352
double precision tan_phi_w
Definition: constant_mod.f:132
integer, dimension(dimension_bc) bc_jj_ps
Definition: bc_mod.f:212
double precision, parameter pi
Definition: constant_mod.f:158
double precision phip0
Definition: constant_mod.f:81
logical granular_energy
Definition: run_mod.f:112
double precision, dimension(dimension_bc, dim_m) bc_vw_s
Definition: bc_mod.f:325
double precision, dimension(dimension_bc) bc_ww_g
Definition: bc_mod.f:319
subroutine check_bc_walls_gas(BCV)
double precision, dimension(dimension_bc, dim_m) bc_hw_t_s
Definition: bc_mod.f:335
double precision, dimension(dimension_bc, dim_scalar) bc_hw_scalar
Definition: bc_mod.f:388
double precision, dimension(dimension_bc, dim_n_g) bc_hw_x_g
Definition: bc_mod.f:362
double precision, parameter zero
Definition: param1_mod.f:27
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
Definition: bc_mod.f:23