MFIX  2016-1
check_boundary_conditions.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: CHECK_BOUNDARY_CONDITIONS !
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 check_boundary_conditions
16 
17 ! Global Variables:
18 !---------------------------------------------------------------------//
19 ! Total number of (actual) continuum solids.
20  use physprop, only: smax, mmax
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 specified 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 ! Run-time flag for DEM solids
33  use run, only: dem_solids
34 ! Run-time flag for PIC solids
35  use run, only: pic_solids
36 
37 ! Global Parameters:
38 !---------------------------------------------------------------------//
39 ! Parameter constants
40  use param1, only: zero, one, undefined
41 ! Maximum number of BCs
42  use param, only: dimension_bc
43 ! Maximum number of disperse phases
44  use param, only: dim_m
45 
46 ! Use the error manager for posting error messages.
47 !---------------------------------------------------------------------//
48  use error_manager
49 
50 
51  IMPLICIT NONE
52 
53 
54 ! Local Variables:
55 !---------------------------------------------------------------------//
56 ! Loop counter for BCs
57  INTEGER :: BCV
58 ! Total number of solids phases (continuum + discrete)
59  INTEGER :: MMAX_TOT
60 ! Flag to skip checks on indexed solid phase.
61  LOGICAL :: SKIP(1:dim_m)
62 !......................................................................!
63 
64 
65 ! Initialize the error manager.
66  CALL init_err_msg("CHECK_BOUNDARY_CONDITIONS")
67 
68 ! Determine which BCs are DEFINED
70 
71 ! Total number of solids. (this won't work for GHD/hybrid)
72  mmax_tot = smax + des_mmax
73 
74 ! Loop over each defined BC and check the user data.
75  DO bcv = 1, dimension_bc
76 
77  IF (bc_defined(bcv)) THEN
78 
79 ! Determine which solids phases are present.
80  skip=(bc_rop_s(bcv,:)==undefined.OR.bc_rop_s(bcv,:)==zero) &
81  .AND.(bc_ep_s(bcv,:)==undefined.OR.bc_ep_s(bcv,:)==zero)
82 
83  IF(mmax_tot == 1 .AND. bc_ep_g(bcv)/=one) skip(1) = .false.
84 
85  SELECT CASE (bc_type_enum(bcv))
86 
87  CASE (mass_inflow)
88  CALL check_bc_geometry_flow(bcv)
89  CALL check_bc_mass_inflow(mmax_tot, skip, bcv)
90  CALL check_bc_inflow(mmax_tot,skip,bcv)
91 
92  CASE (p_inflow)
93  CALL check_bc_geometry_flow(bcv)
94  CALL check_bc_p_inflow(mmax_tot, skip, bcv)
95  CALL check_bc_inflow(mmax_tot, skip, bcv)
96  CALL check_bc_outflow(mmax_tot, bcv)
97 
98  CASE (outflow)
99  CALL check_bc_geometry_flow(bcv)
100  CALL check_bc_outflow(mmax_tot, bcv)
101 
102  CASE (mass_outflow)
103  CALL check_bc_geometry_flow(bcv)
104  CALL check_bc_mass_outflow(mmax_tot, bcv)
105  CALL check_bc_outflow(mmax_tot, bcv)
106 
107  CASE (p_outflow)
108  CALL check_bc_geometry_flow(bcv)
109  CALL check_bc_p_outflow(mmax_tot, bcv)
110  CALL check_bc_outflow(mmax_tot, bcv)
111 
112  CASE (free_slip_wall)
113  CALL check_bc_geometry_wall(bcv)
114  CALL check_bc_walls(mmax_tot, skip, bcv)
115 
116  CASE (no_slip_wall)
117  CALL check_bc_geometry_wall(bcv)
118  CALL check_bc_walls(mmax_tot, skip, bcv)
119 
120  CASE (par_slip_wall)
121  CALL check_bc_geometry_wall(bcv)
122  CALL check_bc_walls(mmax_tot, skip, bcv)
123 
124  END SELECT
125 
126 ! Check whether BC values are specified for undefined BC locations
127  ELSEIF(bc_type_enum(bcv) /= dummy .AND. &
128  .NOT.is_cg(bc_type_enum(bcv))) THEN
129 
130  CALL check_bc_range(bcv)
131 
132  ENDIF
133  ENDDO
134 
135  mmax_tot = mmax+des_mmax
136 ! Additional checks needed for DEM boundaries
137  IF(dem_solids) CALL check_bc_dem(mmax_tot)
138 ! Additional checks needed for PIC inflow/outflow boundaries
139  IF(pic_solids) CALL check_bc_pic(mmax_tot)
140 
141 ! Cleanup and exit.
142  CALL finl_err_msg
143 
144  RETURN
145 
146  END SUBROUTINE check_boundary_conditions
147 
148 
149 
150 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
151 ! !
152 ! Subroutine: CHECK_BC_RANGE !
153 ! Author: P. Nicoletti Date: 10-DEC-91 !
154 ! !
155 ! Purpose: Verify that data was not given for undefined BC regions. !
156 ! !
157 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
158  SUBROUTINE check_bc_range(BCV)
160 ! Global Variables:
161 !---------------------------------------------------------------------//
162 ! Gas phase BC varaibles
163  use bc, only: bc_ep_g, bc_t_g, bc_x_g, bc_p_g
164  use bc, only: bc_u_g, bc_v_g, bc_w_g
165 ! Solids phase BC variables.
166  USE bc, only: bc_ep_s, bc_rop_s, bc_t_s, bc_x_s
167  use bc, only: bc_u_s, bc_v_s, bc_w_s
168 ! Scalar equation BC variables.
169  USE bc, only: bc_scalar
170 
171 
172 ! Global Parameters:
173 !---------------------------------------------------------------------//
174 ! Parameter constant for unspecified values.
175  use param1, only: undefined
176 ! Maximum number of disperse phases.
177  use param, only: dim_m
178 ! Maximum number of species gas/solids
179  use param, only: dimension_n_g, dimension_n_s
180 ! Maximum number of scalar equations.
181  use param, only: dim_scalar
182 
183 
184 ! Use the error manager for posting error messages.
185 !---------------------------------------------------------------------//
186  use error_manager
187 
188 
189  IMPLICIT NONE
190 
191 
192 ! Dummy Arguments:
193 !---------------------------------------------------------------------/
194 ! Boundary condition index.
195  INTEGER, INTENT(in) :: BCV
196 
197 ! Local Variables:
198 !---------------------------------------------------------------------//
199 ! Generic loop varaibles.
200  INTEGER :: M, N
201 !......................................................................!
202 
203 
204 ! Initialize the error manager.
205  CALL init_err_msg("CHECK_BC_RANGE")
206 
207 
208 ! Check gas phase variables.
209  IF(bc_u_g(bcv) /= undefined) THEN
210  WRITE(err_msg,1100) trim(ivar('BC_U_g',bcv))
211  CALL flush_err_msg(abort=.true.)
212  ENDIF
213  IF(bc_v_g(bcv) /= undefined) THEN
214  WRITE(err_msg,1100) trim(ivar('BC_V_g',bcv))
215  CALL flush_err_msg(abort=.true.)
216  ENDIF
217  IF (bc_w_g(bcv) /= undefined) THEN
218  WRITE(err_msg,1100) trim(ivar('BC_W_g',bcv))
219  CALL flush_err_msg(abort=.true.)
220  ENDIF
221  IF (bc_ep_g(bcv) /= undefined) THEN
222  WRITE(err_msg,1100) trim(ivar('BC_EP_g',bcv))
223  CALL flush_err_msg(abort=.true.)
224  ENDIF
225  IF (bc_p_g(bcv) /= undefined) THEN
226  WRITE(err_msg,1100) trim(ivar('BC_P_g',bcv))
227  CALL flush_err_msg(abort=.true.)
228  ENDIF
229  IF (bc_t_g(bcv) /= undefined) THEN
230  WRITE(err_msg,1100) trim(ivar('BC_T_g',bcv))
231  CALL flush_err_msg(abort=.true.)
232  ENDIF
233 
234  DO n = 1, dimension_n_g
235  IF(bc_x_g(bcv,n) /= undefined) THEN
236  WRITE(err_msg,1100) trim(ivar('BC_X_g',bcv,n))
237  CALL flush_err_msg(abort=.true.)
238  ENDIF
239  ENDDO
240 
241 ! Check solids phase variables.
242  DO m = 1, dim_m
243  IF(bc_rop_s(bcv,m) /= undefined) THEN
244  WRITE(err_msg,1100) trim(ivar('BC_ROP_s',bcv,m))
245  CALL flush_err_msg(abort=.true.)
246  ENDIF
247  IF(bc_ep_s(bcv,m) /= undefined) THEN
248  WRITE(err_msg,1100) trim(ivar('BC_EP_s',bcv,m))
249  CALL flush_err_msg(abort=.true.)
250  ENDIF
251  IF(bc_u_s(bcv,m) /= undefined) THEN
252  WRITE(err_msg,1100) trim(ivar('BC_U_s',bcv,m))
253  CALL flush_err_msg(abort=.true.)
254  ENDIF
255  IF(bc_v_s(bcv,m) /= undefined) THEN
256  WRITE(err_msg,1100) trim(ivar('BC_V_s',bcv,m))
257  CALL flush_err_msg(abort=.true.)
258  ENDIF
259 
260  IF(bc_w_s(bcv,m) /= undefined) THEN
261  WRITE(err_msg,1100) trim(ivar('BC_W_s',bcv,m))
262  CALL flush_err_msg(abort=.true.)
263  ENDIF
264  IF(bc_t_s(bcv,m) /= undefined) THEN
265  WRITE(err_msg,1100) trim(ivar('BC_T_s',bcv,m))
266  CALL flush_err_msg(abort=.true.)
267  ENDIF
268 
269  DO n = 1, dimension_n_s
270  IF(bc_x_s(bcv,m,n) /= undefined) THEN
271  WRITE(err_msg,1100) trim(ivar('BC_X_s',bcv,m,n))
272  CALL flush_err_msg(abort=.true.)
273  ENDIF
274  ENDDO
275 
276  ENDDO
277 
278 ! Check scalar equation variables.
279  DO n = 1, dim_scalar
280  IF(bc_scalar(bcv,n) /= undefined) THEN
281  WRITE(err_msg,1100) trim(ivar('BC_Scalar',bcv))
282  CALL flush_err_msg(abort=.true.)
283  ENDIF
284  ENDDO
285 
286 
287  CALL finl_err_msg
288 
289 
290  RETURN
291 
292  1100 FORMAT('Error 1100:',a,' specified for an undefined BC location')
293 
294  END SUBROUTINE check_bc_range
logical dem_solids
Definition: run_mod.f:257
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
double precision, parameter one
Definition: param1_mod.f:29
subroutine check_bc_geometry
integer dimension_n_g
Definition: param_mod.f:20
double precision, dimension(dimension_bc, dim_m) bc_w_s
Definition: bc_mod.f:129
double precision, dimension(dimension_bc, dim_m, dim_n_s) bc_x_s
Definition: bc_mod.f:254
integer, parameter dim_scalar
Definition: param_mod.f:85
subroutine check_bc_range(BCV)
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(dimension_bc) bc_v_g
Definition: bc_mod.f:117
subroutine check_boundary_conditions
subroutine init_err_msg(CALLER)
subroutine check_bc_pic(M_TOT)
Definition: check_bc_pic.f:12
integer mmax
Definition: physprop_mod.f:19
double precision, dimension(dimension_bc, dim_m) bc_t_s
Definition: bc_mod.f:101
subroutine check_bc_mass_inflow(M_TOT, SKIP, BCV)
double precision, dimension(dimension_bc, dim_scalar) bc_scalar
Definition: bc_mod.f:384
subroutine check_bc_inflow(M_TOT, SKIP, BCV)
subroutine check_bc_dem(M_TOT)
Definition: check_bc_dem.f:12
subroutine check_bc_mass_outflow(M_TOT, BCV)
logical, dimension(dimension_bc) bc_defined
Definition: bc_mod.f:207
double precision, dimension(dimension_bc) bc_p_g
Definition: bc_mod.f:80
subroutine check_bc_p_inflow(M_TOT, SKIP, BCV)
Definition: run_mod.f:13
subroutine check_bc_geometry_flow(BCV)
Definition: param_mod.f:2
double precision, dimension(dimension_bc, dim_m) bc_v_s
Definition: bc_mod.f:121
subroutine check_bc_geometry_wall(BCV)
double precision, dimension(dimension_bc) bc_u_g
Definition: bc_mod.f:109
subroutine check_bc_walls(M_TOT, SKIP, BCV)
double precision, dimension(dimension_bc, dim_m) bc_u_s
Definition: bc_mod.f:113
character(len=line_length), dimension(line_count) err_msg
double precision, dimension(dimension_bc, dim_n_g) bc_x_g
Definition: bc_mod.f:251
double precision, dimension(dimension_bc) bc_ep_g
Definition: bc_mod.f:77
integer smax
Definition: physprop_mod.f:22
integer dimension_n_s
Definition: param_mod.f:21
double precision, dimension(dimension_bc) bc_w_g
Definition: bc_mod.f:125
logical pic_solids
Definition: run_mod.f:258
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