MFIX  2016-1
check_bc_geometry.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: CHECK_BC_GEOMETRY !
4 ! Author: J.Musser Date: 01-Mar-14 !
5 ! !
6 ! Purpose: Determine if BCs are "DEFINED" and that they contain the !
7 ! minimum amount of geometry data. !
8 ! !
9 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
10  SUBROUTINE check_bc_geometry
11 
12 ! Global Variables:
13 !---------------------------------------------------------------------//
14 ! Flag: BC contains geometric data and/or specified type
15  use bc, only: bc_defined
16 ! User specified BC
17  use bc
18 ! User specified: BC geometry
19  use bc, only: bc_x_e, bc_x_w, bc_i_e, bc_i_w
20  use bc, only: bc_y_n, bc_y_s, bc_j_n, bc_j_s
21  use bc, only: bc_z_t, bc_z_b, bc_k_t, bc_k_b
22 ! User specified: System geometry
23  use geometry, only: no_i, xlength
24  use geometry, only: no_j, ylength
25  use geometry, only: no_k, zlength
26 ! Flag: Reinitializing field conditions.
27  use run, only: reinitializing
28 
29 ! Global Parameters:
30 !---------------------------------------------------------------------//
31 ! The max number of BCs.
32  use param, only: dimension_bc
33 ! Parameter constants
35 
36 ! Use the error manager for posting error messages.
37 !---------------------------------------------------------------------//
38  use error_manager
39 
40 
41  IMPLICIT NONE
42 
43 
44 ! Local Variables:
45 !---------------------------------------------------------------------//
46 ! loop/variable indices
47  INTEGER :: BCV, I
48 ! Error flag
49  LOGICAL :: RECOGNIZED_BC_TYPE
50 !......................................................................!
51 
52 ! Skip this routine if reinitializing as BC locations cannot be changed.
53  IF(reinitializing) RETURN
54 
55  CALL init_err_msg("CHECK_BC_GEOMETRY")
56 
57  bc_type_enum = blank
58 
59  l50: DO bcv = 1, dimension_bc
60 
61  bc_defined(bcv) = .false.
62  IF(bc_x_w(bcv) /= undefined) bc_defined(bcv) = .true.
63  IF(bc_x_e(bcv) /= undefined) bc_defined(bcv) = .true.
64  IF(bc_y_s(bcv) /= undefined) bc_defined(bcv) = .true.
65  IF(bc_y_n(bcv) /= undefined) bc_defined(bcv) = .true.
66  IF(bc_z_b(bcv) /= undefined) bc_defined(bcv) = .true.
67  IF(bc_z_t(bcv) /= undefined) bc_defined(bcv) = .true.
68  IF(bc_i_w(bcv) /= undefined_i) bc_defined(bcv) = .true.
69  IF(bc_i_e(bcv) /= undefined_i) bc_defined(bcv) = .true.
70  IF(bc_j_s(bcv) /= undefined_i) bc_defined(bcv) = .true.
71  IF(bc_j_n(bcv) /= undefined_i) bc_defined(bcv) = .true.
72  IF(bc_k_b(bcv) /= undefined_i) bc_defined(bcv) = .true.
73  IF(bc_k_t(bcv) /= undefined_i) bc_defined(bcv) = .true.
74  IF(bc_type(bcv) == 'CG_NSW') bc_defined(bcv) = .true.
75  IF(bc_type(bcv) == 'CG_FSW') bc_defined(bcv) = .true.
76  IF(bc_type(bcv) == 'CG_PSW') bc_defined(bcv) = .true.
77  IF(bc_type(bcv) == 'CG_MI') bc_defined(bcv) = .true.
78  IF(bc_type(bcv) == 'CG_PO') bc_defined(bcv) = .true.
79 
80  IF (bc_type(bcv) == 'DUMMY') bc_defined(bcv) = .false.
81 
82  IF(bc_type(bcv)/=undefined_c .AND. bc_type(bcv)/='DUMMY')THEN
83 
84  recognized_bc_type = .false.
85  DO i = 1, dim_bctype
86  valid_bc_type(i) = trim(valid_bc_type(i))
87  IF(valid_bc_type(i) == trim(bc_type(bcv))) THEN
88  bc_type_enum(bcv) = valid_bc_type_enum(i)
89  recognized_bc_type = .true.
90  EXIT
91  ENDIF
92  ENDDO
93 
94  IF(.NOT.recognized_bc_type) THEN
95  WRITE(err_msg, 1100) trim(ivar('BC_TYPE',bcv)), &
96  bc_type_enum(bcv), valid_bc_type
97  CALL flush_err_msg(abort=.true.)
98  ENDIF
99  ENDIF
100 
101  IF(.NOT.bc_defined(bcv)) cycle
102  IF(is_cg(bc_type_enum(bcv))) cycle
103 
104  IF(bc_x_w(bcv)==undefined .AND. bc_i_w(bcv)==undefined_i) THEN
105  IF(no_i) THEN
106  bc_x_w(bcv) = zero
107  ELSE
108  WRITE(err_msg,1101) bcv, 'BC_X_w and BC_I_w'
109  CALL flush_err_msg(abort=.true.)
110  ENDIF
111  ENDIF
112 
113  IF(bc_x_e(bcv)==undefined .AND. bc_i_e(bcv)==undefined_i) THEN
114  IF(no_i) THEN
115  bc_x_e(bcv) = xlength
116  ELSE
117  WRITE(err_msg, 1101) bcv, 'BC_X_e and BC_I_e'
118  CALL flush_err_msg(abort=.true.)
119  ENDIF
120  ENDIF
121 
122  IF(bc_y_s(bcv)==undefined .AND. bc_j_s(bcv)==undefined_i) THEN
123  IF(no_j) THEN
124  bc_y_s(bcv) = zero
125  ELSE
126  WRITE(err_msg, 1101) bcv, 'BC_Y_s and BC_J_s'
127  CALL flush_err_msg(abort=.true.)
128  ENDIF
129  ENDIF
130 
131  IF(bc_y_n(bcv)==undefined .AND. bc_j_n(bcv)==undefined_i) THEN
132  IF(no_j) THEN
133  bc_y_n(bcv) = ylength
134  ELSE
135  WRITE(err_msg, 1101) bcv, 'BC_Y_n and BC_J_n'
136  CALL flush_err_msg(abort=.true.)
137  ENDIF
138  ENDIF
139 
140  IF(bc_z_b(bcv)==undefined .AND. bc_k_b(bcv)==undefined_i) THEN
141  IF(no_k) THEN
142  bc_z_b(bcv) = zero
143  ELSE
144  WRITE(err_msg, 1101) bcv, 'BC_Z_b and BC_K_b'
145  CALL flush_err_msg(abort=.true.)
146  ENDIF
147  ENDIF
148 
149  IF(bc_z_t(bcv)==undefined .AND. bc_k_t(bcv)==undefined_i) THEN
150  IF(no_k) THEN
151  bc_z_t(bcv) = zlength
152  ELSE
153  WRITE(err_msg, 1101) bcv, 'BC_Z_t and BC_K_t'
154  CALL flush_err_msg(abort=.true.)
155  ENDIF
156  ENDIF
157 
158  1101 FORMAT('Error 1101: Boundary condition ',i3,' is ill-defined.',/ &
159  a,' are not specified.',/'Please correct the mfix.dat file.')
160 
161 ! Swap BC aliases for the "full name" complement.
162  DO i = 1, dim_bctype
163  valid_bc_type(i) = trim(valid_bc_type(i))
164  IF(valid_bc_type(i) == bc_type(bcv)) THEN
165  IF(mod(i,2) == 0) THEN
166  bc_type_enum(bcv) = valid_bc_type_enum(i-1)
167  ELSE
168  bc_type_enum(bcv) = valid_bc_type_enum(i)
169  ENDIF
170  cycle l50
171  ENDIF
172  ENDDO
173 
174  WRITE(err_msg, 1100) trim(ivar('BC_TYPE',bcv)), &
175  bc_type_enum(bcv), valid_bc_type
176  CALL flush_err_msg(abort=.true.)
177 
178  ENDDO l50 ! end loop over (bcv=1,dimension_bc)
179 
180  CALL finl_err_msg
181 
182  RETURN
183 
184 
185  1100 FORMAT('Error 1100: Illegal entry: ',a,' = ',a,/'Valid entries:',&
186  ' ',10(/5x,a,2x,a),/5x,a)
187 
188  END SUBROUTINE check_bc_geometry
189 
190 
191 
192 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
193 ! !
194 ! Subroutine: CHECK_BC_GEOMETRY_WALL !
195 ! Author: P. Nicoletti Date: 10-DEC-91 !
196 ! !
197 ! Purpose: Find and validate i, j, k locations for walls BC's !
198 ! !
199 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
200  SUBROUTINE check_bc_geometry_wall(BCV)
202 ! Global Variables:
203 !---------------------------------------------------------------------//
204 ! Boundary condition locations and corresponding grid index
205  use bc, only: bc_x_w, bc_x_e, bc_i_w, bc_i_e
206  use bc, only: bc_y_s, bc_y_n, bc_j_s, bc_j_n
207  use bc, only: bc_z_b, bc_z_t, bc_k_b, bc_k_t
208 ! Basic grid information
209  use geometry, only: no_i, xlength, dx, imax, imax2, xmin
210  use geometry, only: no_j, ylength, dy, jmax, jmax2
211  use geometry, only: no_k, zlength, dz, kmax, kmax2
212 ! Flag: Reinitializing field conditions.
213  use run, only: reinitializing
214 ! Function to compare two values
215  use toleranc, only: compare
216 
217 ! Global Parameters:
218 !---------------------------------------------------------------------//
219  use param1, only: zero, undefined_i, undefined
220 
221 ! Use the error manager for posting error messages.
222 !---------------------------------------------------------------------//
223  use error_manager
224 
225 
226  IMPLICIT NONE
227 
228 
229 ! Dummy Arguments:
230 !---------------------------------------------------------------------//
231 ! Index of boundary condition.
232  INTEGER, INTENT(in) :: BCV
233 
234 ! Local Variables:
235 !---------------------------------------------------------------------//
236 ! Calculated indices of the wall boundary
237  INTEGER :: I_w , I_e , J_s , J_n , K_b , K_t
238 ! Integer error flag
239  INTEGER :: IER
240 !......................................................................!
241 
242 
243 ! Skip this routine if reinitializing as BC locations cannot be changed.
244  IF(reinitializing) RETURN
245 
246  CALL init_err_msg("CHECK_BC_GEOMETRY_WALL")
247 
248  IF(bc_x_w(bcv)/=undefined .AND. bc_x_e(bcv)/=undefined) THEN
249 
250 ! setting indices to 1 if there is no variation in the i (x) direction
251  IF (no_i) THEN
252  i_w = 1
253  i_e = 1
254  ELSE
255  CALL calc_cell (xmin, bc_x_w(bcv), dx, imax, i_w)
256  i_w = i_w + 1
257  CALL calc_cell (xmin, bc_x_e(bcv), dx, imax, i_e)
258 ! BC along zy plane, checking if far west or far east of domain
259  IF(bc_x_w(bcv) == bc_x_e(bcv)) THEN
260  IF(compare(bc_x_w(bcv),xmin)) THEN
261  i_w = 1
262  i_e = 1
263  ELSEIF(compare(bc_x_w(bcv),xmin+xlength)) THEN
264  i_w = imax2
265  i_e = imax2
266  ENDIF
267  ENDIF
268  ENDIF
269 
270 ! checking/setting corresponding i indices according to specified x
271 ! coordinates
272  IF(bc_i_w(bcv)/=undefined_i .OR. bc_i_e(bcv)/=undefined_i) THEN
273  CALL location_check (bc_i_w(bcv), i_w, bcv, 'BC - west')
274  CALL location_check (bc_i_e(bcv), i_e, bcv, 'BC - east')
275  ELSE
276  bc_i_w(bcv) = i_w
277  bc_i_e(bcv) = i_e
278  ENDIF
279  ENDIF
280 
281 
282  IF(bc_y_s(bcv)/=undefined .AND. bc_y_n(bcv)/=undefined) THEN
283 ! setting indices to 1 if there is no variation in the j (y) direction
284  IF(no_j) THEN
285  j_s = 1
286  j_n = 1
287  ELSE
288  CALL calc_cell (zero, bc_y_s(bcv), dy, jmax, j_s)
289  j_s = j_s + 1
290  CALL calc_cell (zero, bc_y_n(bcv), dy, jmax, j_n)
291 ! BC along xz plane, checking if far south or far north of domain
292  IF(bc_y_s(bcv) == bc_y_n(bcv)) THEN
293  IF(compare(bc_y_s(bcv),zero)) THEN
294  j_s = 1
295  j_n = 1
296  ELSE IF (compare(bc_y_s(bcv),ylength)) THEN
297  j_s = jmax2
298  j_n = jmax2
299  ENDIF
300  ENDIF
301  ENDIF
302 ! checking/setting corresponding j indices according to specified y
303 ! coordinates
304  IF(bc_j_s(bcv)/=undefined_i .OR. bc_j_n(bcv)/=undefined_i) THEN
305  CALL location_check (bc_j_s(bcv), j_s, bcv, 'BC - south')
306  CALL location_check (bc_j_n(bcv), j_n, bcv, 'BC - north')
307  ELSE
308  bc_j_s(bcv) = j_s
309  bc_j_n(bcv) = j_n
310  ENDIF
311  ENDIF
312 
313  IF(bc_z_b(bcv)/=undefined .AND. bc_z_t(bcv)/=undefined) THEN
314 ! setting indices to 1 if there is no variation in the k (z) direction
315  IF(no_k)THEN
316  k_b = 1
317  k_t = 1
318  ELSE
319  CALL calc_cell (zero, bc_z_b(bcv), dz, kmax, k_b)
320  k_b = k_b + 1
321  CALL calc_cell (zero, bc_z_t(bcv), dz, kmax, k_t)
322 ! BC along xy plane, checking if far bottom or far top of domain
323  IF(bc_z_b(bcv) == bc_z_t(bcv)) THEN
324  IF(compare(bc_z_b(bcv),zero)) THEN
325  k_b = 1
326  k_t = 1
327  ELSEIF(compare(bc_z_b(bcv),zlength)) THEN
328  k_b = kmax2
329  k_t = kmax2
330  ENDIF
331  ENDIF
332  ENDIF
333 ! checking/setting corresponding j indices according to specified y
334 ! coordinates
335  IF(bc_k_b(bcv)/=undefined_i .OR.bc_k_t(bcv)/=undefined_i) THEN
336  CALL location_check (bc_k_b(bcv), k_b, bcv, 'BC - bottom')
337  CALL location_check (bc_k_t(bcv), k_t, bcv, 'BC - top')
338  ELSE
339  bc_k_b(bcv) = k_b
340  bc_k_t(bcv) = k_t
341  ENDIF
342  ENDIF
343 
344 
345 ! CHECK FOR VALID VALUES
346  ier = 0
347  IF (bc_k_b(bcv)<1 .OR. bc_k_b(bcv)>kmax2) ier = 1
348  IF (bc_j_s(bcv)<1 .OR. bc_j_s(bcv)>jmax2) ier = 1
349  IF (bc_i_w(bcv)<1 .OR. bc_i_w(bcv)>imax2) ier = 1
350  IF (bc_k_t(bcv)<1 .OR. bc_k_t(bcv)>kmax2) ier = 1
351  IF (bc_j_n(bcv)<1 .OR. bc_j_n(bcv)>jmax2) ier = 1
352  IF (bc_i_e(bcv)<1 .OR. bc_i_e(bcv)>imax2) ier = 1
353  IF (bc_k_b(bcv) > bc_k_t(bcv)) ier = 1
354  IF (bc_j_s(bcv) > bc_j_n(bcv)) ier = 1
355  IF (bc_i_w(bcv) > bc_i_e(bcv)) ier = 1
356 
357  IF(ier /= 0)THEN
358  WRITE(err_msg,1100) bcv, &
359  'X', bc_x_w(bcv), bc_x_e(bcv),'I',bc_i_w(bcv),bc_i_e(bcv), &
360  'Y', bc_y_s(bcv), bc_y_n(bcv),'J',bc_j_s(bcv),bc_j_n(bcv), &
361  'Z', bc_z_b(bcv), bc_z_t(bcv),'K',bc_k_b(bcv),bc_k_t(bcv)
362  CALL flush_err_msg(abort=.true.)
363  ENDIF
364 
365  1100 FORMAT('Error 1100: Invalid location specified for BC ',i3,'.', &
366  3(/3x,a1,': ',g12.5,',',g12.5,8x,a1,': ',i8,',',i8),/ &
367  'Please correct the mfix.dat file.')
368 
369  CALL finl_err_msg
370 
371  RETURN
372 
373  END SUBROUTINE check_bc_geometry_wall
374 
375 
376 
377 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
378 ! !
379 ! Subroutine: CHECK_BC_GEOMETRY_FLOW !
380 ! Author: P. Nicoletti Date: 10-DEC-91 !
381 ! !
382 ! Purpose: Find and validate i, j, k locations for flow BC's. Also !
383 ! set value of bc_plane for flow BC's. !
384 ! !
385 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
386  SUBROUTINE check_bc_geometry_flow(BCV)
388 ! Global Variables:
389 !---------------------------------------------------------------------//
390 ! Boundary condition locations and corresponding grid index
391  use bc, only: bc_x_w, bc_x_e, bc_i_w, bc_i_e
392  use bc, only: bc_y_s, bc_y_n, bc_j_s, bc_j_n
393  use bc, only: bc_z_b, bc_z_t, bc_k_b, bc_k_t
394 ! Basic grid information
395  use geometry, only: no_i, dx, imax, imax2, xmin
396  use geometry, only: no_j, dy, jmax, jmax2
397  use geometry, only: no_k, dz, kmax, kmax2
398 ! Flag: Reinitializing field conditions.
399  use run, only: reinitializing
400 
401 ! Global Parameters:
402 !---------------------------------------------------------------------//
403  use param1, only: zero, undefined_i, undefined
404 
405 ! Use the error manager for posting error messages.
406 !---------------------------------------------------------------------//
407  use error_manager
408 
409  IMPLICIT NONE
410 
411 
412 ! Dummy Arguments:
413 !---------------------------------------------------------------------//
414 ! Index of boundary condition.
415  INTEGER, INTENT(in) :: BCV
416 
417 ! Local Variables:
418 !---------------------------------------------------------------------//
419 ! Calculated indices of the wall boundary
420  INTEGER :: I_w, I_e, J_s, J_n, K_b, K_t
421 ! Indices for error checking
422  INTEGER :: IER
423 
424 ! surface indictors:
425 ! a value of T indicates that the defined boundary region does not
426 ! vary in indicated coordinate direction. that is, if bc_x_w is
427 ! equal to bc_x_e then the boundary region must be in the yz plane
428  LOGICAL :: X_CONSTANT, Y_CONSTANT, Z_CONSTANT
429 !......................................................................!
430 
431 ! Skip this routine if reinitializing as BC locations cannot be changed.
432  IF(reinitializing) RETURN
433 
434  CALL init_err_msg("CHECK_BC_GEOMETRY_FLOW")
435 
436  x_constant = .true.
437  y_constant = .true.
438  z_constant = .true.
439 
440  IF (bc_x_w(bcv)/=undefined .AND. bc_x_e(bcv)/=undefined) THEN
441  CALL calc_cell (xmin, bc_x_w(bcv), dx, imax, i_w)
442  CALL calc_cell (xmin, bc_x_e(bcv), dx, imax, i_e)
443  IF (bc_x_w(bcv) /= bc_x_e(bcv)) THEN
444  x_constant = .false.
445  i_w = i_w + 1
446  IF(bc_i_w(bcv)/=undefined_i.OR.bc_i_e(bcv)/=undefined_i)THEN
447  CALL location_check (bc_i_w(bcv), i_w, bcv, 'BC - west')
448  CALL location_check (bc_i_e(bcv), i_e, bcv, 'BC - east')
449  ENDIF
450  ENDIF
451  bc_i_w(bcv) = i_w
452  bc_i_e(bcv) = i_e
453  ELSE
454  IF(bc_i_w(bcv) /= undefined_i) &
455  CALL calc_loc (xmin,dx,bc_i_w(bcv),bc_x_w(bcv))
456  IF(bc_i_e(bcv) /= undefined_i) &
457  CALL calc_loc (xmin,dx,bc_i_e(bcv),bc_x_e(bcv))
458  IF(bc_x_w(bcv) /= bc_x_e(bcv)) x_constant = .false.
459  ENDIF
460 
461 ! If there is no variation in the I direction set indices to 1
462  IF(no_i) THEN
463  bc_i_w(bcv) = 1
464  bc_i_e(bcv) = 1
465  ENDIF
466 
467  IF (bc_y_s(bcv)/=undefined .AND. bc_y_n(bcv)/=undefined) THEN
468  CALL calc_cell (zero, bc_y_s(bcv), dy, jmax, j_s)
469  CALL calc_cell (zero, bc_y_n(bcv), dy, jmax, j_n)
470  IF(bc_y_s(bcv) /= bc_y_n(bcv)) THEN
471  y_constant = .false.
472  j_s = j_s + 1
473  IF(bc_j_s(bcv)/=undefined_i.OR.bc_j_n(bcv)/=undefined_i)THEN
474  CALL location_check (bc_j_s(bcv), j_s, bcv, 'BC - south')
475  CALL location_check (bc_j_n(bcv), j_n, bcv, 'BC - north')
476  ENDIF
477  ENDIF
478  bc_j_s(bcv) = j_s
479  bc_j_n(bcv) = j_n
480  ELSE
481  IF(bc_j_s(bcv) /= undefined_i) &
482  CALL calc_loc (zero,dy,bc_j_s(bcv),bc_y_s(bcv))
483  IF(bc_j_n(bcv) /= undefined_i) &
484  CALL calc_loc (zero,dy,bc_j_n(bcv),bc_y_n(bcv))
485  IF (bc_y_s(bcv) /= bc_y_n(bcv)) y_constant = .false.
486  ENDIF
487 
488 ! If there is no variation in the J direction set indices to 1
489  IF(no_j) THEN
490  bc_j_s(bcv) = 1
491  bc_j_n(bcv) = 1
492  ENDIF
493 
494  IF(bc_z_b(bcv)/=undefined .AND. bc_z_t(bcv)/=undefined) THEN
495  CALL calc_cell (zero, bc_z_b(bcv), dz, kmax, k_b)
496  CALL calc_cell (zero, bc_z_t(bcv), dz, kmax, k_t)
497  IF(bc_z_b(bcv) /= bc_z_t(bcv)) THEN
498  z_constant = .false.
499  k_b = k_b + 1
500  IF(bc_k_b(bcv)/=undefined_i.OR.bc_k_t(bcv)/=undefined_i)THEN
501  CALL location_check (bc_k_b(bcv), k_b, bcv, 'BC - bottom')
502  CALL location_check (bc_k_t(bcv), k_t, bcv, 'BC - top')
503  ENDIF
504  ENDIF
505  bc_k_b(bcv) = k_b
506  bc_k_t(bcv) = k_t
507  ELSE
508  IF(bc_k_b(bcv) /= undefined_i) &
509  CALL calc_loc (zero,dz,bc_k_b(bcv),bc_z_b(bcv))
510  IF(bc_k_t(bcv) /= undefined_i) &
511  CALL calc_loc (zero,dz,bc_k_t(bcv),bc_z_t(bcv))
512  IF(bc_z_b(bcv) /= bc_z_t(bcv)) z_constant = .false.
513  ENDIF
514 
515 ! If there is no variation in the K direction set indices to 1
516  IF(no_k) THEN
517  bc_k_b(bcv) = 1
518  bc_k_t(bcv) = 1
519  ENDIF
520 
521 ! Check whether the boundary is a plane parallel to one of the three
522 ! coordinate planes
523  IF(bc_x_w(bcv)/=undefined .AND. bc_y_s(bcv)/=undefined .AND. &
524  bc_z_b(bcv)/=undefined) CALL check_plane (x_constant, &
525  y_constant, z_constant, bcv, 'BC')
526 
527 
528 ! CHECK FOR VALID VALUES
529  ier = 0
530  IF(bc_i_w(bcv)<1 .OR. bc_i_w(bcv)>imax2) ier = 1
531  IF(bc_i_e(bcv)<1 .OR. bc_i_e(bcv)>imax2) ier = 1
532  IF(bc_j_s(bcv)<1 .OR. bc_j_s(bcv)>jmax2) ier = 1
533  IF(bc_j_n(bcv)<1 .OR. bc_j_n(bcv)>jmax2) ier = 1
534  IF(bc_k_b(bcv)<1 .OR. bc_k_b(bcv)>kmax2) ier = 1
535  IF(bc_k_t(bcv)<1 .OR. bc_k_t(bcv)>kmax2) ier = 1
536  IF(bc_k_b(bcv) > bc_k_t(bcv)) ier = 1
537  IF(bc_j_s(bcv) > bc_j_n(bcv)) ier = 1
538  IF(bc_i_w(bcv) > bc_i_e(bcv)) ier = 1
539 
540  IF(ier /= 0)THEN
541  WRITE(err_msg,1100) bcv, &
542  'X', bc_x_w(bcv), bc_x_e(bcv),'I',bc_i_w(bcv),bc_i_e(bcv), &
543  'Y', bc_y_s(bcv), bc_y_n(bcv),'J',bc_j_s(bcv),bc_j_n(bcv), &
544  'Z', bc_z_b(bcv), bc_z_t(bcv),'K',bc_k_b(bcv),bc_k_t(bcv)
545  CALL flush_err_msg(abort=.true.)
546  ENDIF
547 
548  1100 FORMAT('Error 1100: Invalid location specified for BC ',i3,'.', &
549  3(/3x,a1,': ',g12.5,',',g12.5,8x,a1,': ',i8,',',i8),/ &
550  'Please correct the mfix.dat file.')
551 
552  CALL finl_err_msg
553 
554  RETURN
555 
556  END SUBROUTINE check_bc_geometry_flow
integer, dimension(dimension_bc) bc_k_b
Definition: bc_mod.f:70
double precision, dimension(dimension_bc) bc_y_n
Definition: bc_mod.f:42
subroutine calc_cell(RMIN, REACTOR_LOC, D_DIR, N_DIR, CELL_LOC)
Definition: calc_cell.f:14
integer imax2
Definition: geometry_mod.f:61
character(len=32) function ivar(VAR, i1, i2, i3)
subroutine finl_err_msg
logical function compare(V1, V2)
Definition: toleranc_mod.f:94
logical no_i
Definition: geometry_mod.f:20
subroutine check_bc_geometry
subroutine check_plane(X_CONSTANT, Y_CONSTANT, Z_CONSTANT, BC, NAM
Definition: check_plane.f:21
integer, dimension(dimension_bc) bc_i_w
Definition: bc_mod.f:54
integer, dimension(dimension_bc) bc_j_n
Definition: bc_mod.f:66
double precision, dimension(0:dim_j) dy
Definition: geometry_mod.f:70
integer, parameter dimension_bc
Definition: param_mod.f:61
double precision, dimension(dimension_bc) bc_x_e
Definition: bc_mod.f:34
double precision, parameter undefined
Definition: param1_mod.f:18
double precision, dimension(0:dim_k) dz
Definition: geometry_mod.f:72
integer imax
Definition: geometry_mod.f:47
double precision, dimension(dimension_bc) bc_y_s
Definition: bc_mod.f:38
subroutine init_err_msg(CALLER)
integer, dimension(dimension_bc) bc_k_t
Definition: bc_mod.f:74
integer jmax2
Definition: geometry_mod.f:63
integer, dimension(dimension_bc) bc_j_s
Definition: bc_mod.f:62
logical, dimension(dimension_bc) bc_defined
Definition: bc_mod.f:207
double precision, dimension(0:dim_i) dx
Definition: geometry_mod.f:68
integer kmax2
Definition: geometry_mod.f:65
double precision xlength
Definition: geometry_mod.f:33
Definition: run_mod.f:13
subroutine check_bc_geometry_flow(BCV)
Definition: param_mod.f:2
integer kmax
Definition: geometry_mod.f:51
subroutine location_check(CELL_SPECIFIED, CELL_CALCULATED, COUNTER, MESSAGE)
logical no_k
Definition: geometry_mod.f:28
subroutine check_bc_geometry_wall(BCV)
double precision, dimension(dimension_bc) bc_z_b
Definition: bc_mod.f:46
logical reinitializing
Definition: run_mod.f:208
logical no_j
Definition: geometry_mod.f:24
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
double precision xmin
Definition: geometry_mod.f:75
integer jmax
Definition: geometry_mod.f:49
double precision, dimension(dimension_bc) bc_z_t
Definition: bc_mod.f:50
double precision ylength
Definition: geometry_mod.f:35
integer, dimension(dimension_bc) bc_i_e
Definition: bc_mod.f:58
double precision, parameter zero
Definition: param1_mod.f:27
double precision zlength
Definition: geometry_mod.f:37
subroutine calc_loc(RMIN, D_DIR, CELL_LOC, REACTOR_LOC)
Definition: calc_cell.f:76
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
Definition: bc_mod.f:23
double precision, dimension(dimension_bc) bc_x_w
Definition: bc_mod.f:30
character, parameter undefined_c
Definition: param1_mod.f:20