MFIX  2016-1
check_bc_pic.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! minimum amount of geometry data. !
3 ! !
4 ! Subroutine: CHECK_BC_PIC !
5 ! Author: R. Garg Date: 11-Jun-14 !
6 ! !
7 ! Purpose: Determine if BCs are "DEFINED" and that they contain the !
8 ! minimum amount of geometry data. !
9 ! !
10 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
11  SUBROUTINE check_bc_pic(M_TOT)
12 
13 ! Global Variables:
14 !---------------------------------------------------------------------//
15 
16 ! Simulation dimension (2D/3D)
17  USE discretelement, only: dimn
18 ! User specified BC
19  use bc
20 ! User specified: BC geometry
21  use bc, only: bc_ep_s
22 ! Use specified flag for ignoring PO BC for discrete solids
23  USE bc, only: bc_po_apply_to_des
24 ! PIC model specific BC region specification.
26  USE bc, only: bc_x_w, bc_x_e, bc_y_s, bc_y_n, bc_z_b, bc_z_t
27 
28 ! Solids phase identifier
29  use run, only: solids_model
30 ! Number of PIC inlet/outlet BCs detected.
31  use pic_bc, only: pic_bcmi, pic_bcmo
32 !
33  use pic_bc, only: pic_bcmi_map
34  use pic_bc, only: pic_bcmo_map
35 ! Global Parameters:
36 !---------------------------------------------------------------------//
37 ! The max number of BCs.
38  use param, only: dimension_bc
39 ! Parameter constants
40  use param1, only: zero, undefined
41 
42 
43 ! Use the error manager for posting error messages.
44 !---------------------------------------------------------------------//
45  use error_manager
46 
47 
48  IMPLICIT NONE
49 
50 
51 ! Passed Arguments:
52 !---------------------------------------------------------------------//
53 ! Total number of solids phases.
54  INTEGER, INTENT(in) :: M_TOT
55 
56 ! Local Variables:
57 !---------------------------------------------------------------------//
58 ! loop/variable indices
59  INTEGER :: BCV, M, BCV_I, IDIM
60  INTEGER :: BCV2, BCV2_I
61 
62 ! Temp logical variables for checking constant npc and statwt specification
63  LOGICAL :: CONST_NPC, CONST_STATWT
64 
65  DOUBLE PRECISION :: BC_ORIG(3), BC_END(3), BC2_ORIG(3) , BC2_END(3)
66  DOUBLE PRECISION :: BC_MIN, BC_MAX, BC2_MIN, BC2_MAX
67 
68  LOGICAL :: SEP_AXIS
69 
70 !......................................................................!
71 
72 
73 ! Initialize the error manager.
74  CALL init_err_msg("CHECK_BC_PIC")
75 
76 ! Initialize
77  pic_bcmi = 0
78  pic_bcmo = 0
79 
80 ! Loop over all BCs looking for PIC solids inlets/outlets
81  DO bcv = 1, dimension_bc
82 
83  SELECT CASE (bc_type_enum(bcv))
84 
85 ! Determine the number of mass inlets that contain PIC solids.
86  CASE (mass_inflow)
87  m_lp: DO m=1,m_tot
88  IF(solids_model(m)=='PIC' .AND. &
89  bc_ep_s(bcv,m) > zero) THEN
90  pic_bcmi = pic_bcmi + 1
91  pic_bcmi_map(pic_bcmi) = bcv
92  EXIT m_lp
93  ENDIF
94  ENDDO m_lp
95 
96 ! Count the number of pressure outflows.
97  CASE (p_outflow)
98  IF(bc_po_apply_to_des(bcv)) then
99  pic_bcmo = pic_bcmo + 1
100  pic_bcmo_map(pic_bcmo) = bcv
101  ENDIF
102 
103 ! Flag CG_MI as an error if PIC solids are present.
104  CASE (cg_mi)
105  DO m=1,m_tot
106  IF(solids_model(m)=='PIC') THEN
107  IF(bc_ep_s(bcv,m) /= undefined .AND. &
108  bc_ep_s(bcv,m) > zero) THEN
109  WRITE(err_msg,1000) trim(ivar('BC_TYPE',bcv)), &
110  'GC_MI'
111  CALL flush_err_msg(abort=.true.)
112  ENDIF
113  ENDIF
114  ENDDO
115 
116  CASE (cg_po)
117  WRITE(err_msg,1000) trim(ivar('BC_TYPE',bcv)), 'GC_PO'
118  CALL flush_err_msg(abort=.true.)
119 
120  CASE (mass_outflow, outflow, p_inflow)
121  WRITE(err_msg,1000) trim(ivar('BC_TYPE',bcv)), &
122  bc_type_enum(bcv)
123  CALL flush_err_msg(abort=.true.)
124 
125  END SELECT
126 
127  ENDDO
128 
129 
130  CALL finl_err_msg
131 
132 
133 1000 FORMAT('Error 1000: Unsupported boundary condition specified ', &
134  'with',/'PIC simulation: ',a,' = ',a,/'Please correct the ',&
135  'mfix.dat file.')
136 
137 
138 ! Loop over all MI BC's for data consistency checks
139  DO bcv_i = 1, pic_bcmi
140 
141 ! Get the user defined BC ID.
142  bcv = pic_bcmi_map(bcv_i)
143 
144  DO m=1,m_tot
145  IF(solids_model(m)=='PIC' .AND. &
146  bc_ep_s(bcv,m) > zero) THEN
147  const_npc = (bc_pic_mi_const_npc (bcv, m) .ne. 0)
148  const_statwt = (bc_pic_mi_const_statwt(bcv, m) .ne. zero )
149  IF(const_npc.and.const_statwt) then
150  WRITE(err_msg, 1100) bcv, m
151  CALL flush_err_msg(abort=.true.)
152  ENDIF
153 
154  IF(.not.const_npc.and.(.not.const_statwt)) then
155  WRITE(err_msg, 1101) bcv, m
156  CALL flush_err_msg(abort=.true.)
157  ENDIF
158 
159 
160  ENDIF
161  ENDDO
162 
163 1100 FORMAT('Error 1100: In PIC model for BC # ',i5, &
164  ' and solid phase # ', i5, /, &
165  'Non zero Values specified for both ', &
166  'BC_PIC_MI_CONST_NPC and BC_PIC_MI_CONST_STATWT.', /, &
167  'Choose between constant number of parcels per cell or ', &
168  'constant statistical weight', /, &
169  'See MFIX readme',/'Please correct the data file.')
170 
171 
172 1101 FORMAT('Error 1101: In PIC model for BC # ',i5, &
173  ' and solid phase # ', i5, /, &
174  'A non-zero value not specified for ', &
175  'BC_PIC_MI_CONST_NPC or BC_PIC_MI_CONST_STATWT. ', /, &
176  'Choose between constant number of parcels per cell or ', &
177  'constant statistical weight', /, &
178  'See MFIX readme',/'Please correct the data file.')
179 
180 
181  bc_orig(1) = bc_x_w(bcv)
182  bc_orig(2) = bc_y_s(bcv)
183  bc_orig(3) = bc_z_b(bcv)
184  bc_end(1) = bc_x_e(bcv)
185  bc_end(2) = bc_y_n(bcv)
186  bc_end(3) = bc_z_t(bcv)
187  bcvtwoloop: DO bcv2_i = bcv_i+1, pic_bcmi
188 
189  ! Get the user defined BC ID.
190  bcv2 = pic_bcmi_map(bcv2_i)
191 
192 
193  bc2_orig(1) = bc_x_w(bcv2)
194  bc2_orig(2) = bc_y_s(bcv2)
195  bc2_orig(3) = bc_z_b(bcv2)
196  bc2_end(1) = bc_x_e(bcv2)
197  bc2_end(2) = bc_y_n(bcv2)
198  bc2_end(3) = bc_z_t(bcv2)
199 
200  sep_axis = .false.
201  DO idim = 1, dimn
202 
203  bc_min = bc_orig(idim)
204  bc_max = bc_end(idim)
205  bc2_min = bc2_orig(idim)
206  bc2_max = bc2_end(idim)
207 
208 
209  if(bc_min.eq.bc_max.and.bc_min.eq.bc2_min.and.bc_min.eq.bc2_max) cycle
210  !if above is true, then the sep_axis will be true (see below) and
211  !overlapping bc regions will also be deemed as non-overlapping
212 
213  !Check for separating axis. If the separating axis exists, then
214  !the BC regions can't overlap.
215  !generally equality implies lack of sep_axis, and thus, overlapping
216  !However, doing so will flag all BC's as overlapping since
217  !BC's have to share common edges. So here the equality is considered
218  !as existence of a separating axis, and hence, no overlap
219  !equality is also considered as separating axis which is
220  if ((bc_min .ge. bc2_max) .or. (bc_max .le. bc2_min) ) then
221  sep_axis = .true.
222  exit
223  endif
224 
225  end DO
226 
227  if(.not.sep_axis) then
228  !implies the BC regions could not find a separating axis and are therefore
229  !overlapping
230 
231  write(err_msg, 1004) bcv, bcv2
232  CALL flush_err_msg(footer = .false.)
233 
234  DO idim = 1, dimn
235 
236  write(err_msg, 1005) 'BC1', idim, bc_orig(idim), bc_end(idim)
237  CALL flush_err_msg(header = .false., footer = .false.)
238 
239  write(err_msg, 1005) 'BC2', idim, bc2_orig(idim), bc2_end(idim)
240  CALL flush_err_msg(header = .false., footer = .false.)
241 
242  ENDDO
243  write(err_msg, 1006)
244 
245  CALL flush_err_msg(header=.false., abort=.true.)
246 
247  endif
248  end DO bcvtwoloop
249 
250 
251  ENDDO
252 
253 1004 FORMAT('Error # 1004 for PIC Solids MI BC:',/5x, &
254  'Overlapping MI BC regions with non zero', /, &
255  'solids volume fraction not allowed.', /, &
256  'Overlapping BCs are', 2(2x, i4))
257 
258 1005 FORMAT('Spans of ', a, ' in dir ', i2, /5x, 2(2x, g17.8))
259 
260 
261 1006 Format('Please correct the data file. Exiting.')
262 
263 
264  END SUBROUTINE check_bc_pic
double precision, dimension(dimension_bc) bc_y_n
Definition: bc_mod.f:42
integer pic_bcmi
Definition: pic_bc_mod.f:18
character(len=32) function ivar(VAR, i1, i2, i3)
subroutine finl_err_msg
integer, parameter dimension_bc
Definition: param_mod.f:61
double precision, dimension(dimension_bc) bc_x_e
Definition: bc_mod.f:34
character(len=3), dimension(dim_m) solids_model
Definition: run_mod.f:253
double precision, parameter undefined
Definition: param1_mod.f:18
integer, dimension(dimension_bc, dim_m) bc_pic_mi_const_npc
Definition: bc_mod.f:412
double precision, dimension(dimension_bc) bc_y_s
Definition: bc_mod.f:38
subroutine init_err_msg(CALLER)
subroutine check_bc_pic(M_TOT)
Definition: check_bc_pic.f:12
Definition: run_mod.f:13
integer, dimension(dimension_bc) pic_bcmo_map
Definition: pic_bc_mod.f:25
Definition: param_mod.f:2
double precision, dimension(dimension_bc) bc_z_b
Definition: bc_mod.f:46
double precision, dimension(dimension_bc, dim_m) bc_pic_mi_const_statwt
Definition: bc_mod.f:417
character(len=line_length), dimension(line_count) err_msg
double precision, dimension(dimension_bc) bc_z_t
Definition: bc_mod.f:50
logical, dimension(dimension_bc) bc_po_apply_to_des
Definition: bc_mod.f:192
integer pic_bcmo
Definition: pic_bc_mod.f:19
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)
Definition: bc_mod.f:23
double precision, dimension(dimension_bc) bc_x_w
Definition: bc_mod.f:30
integer, dimension(dimension_bc) pic_bcmi_map
Definition: pic_bc_mod.f:24