MFIX  2016-1
check_ic_common_discrete.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: CHECK_IC_COMMON_DISCRETE !
4 ! Author: R.Garg Date: 11-Mar-14 !
5 ! !
6 ! Purpose: check the initial conditions input section common to both !
7 ! DEM and MPPIC models !
8 ! - ensure the first IC is defined over the entire domain with !
9 ! ep_g = 1 when more than one IC has solids !
10 ! - ensure the ICs are non-overlapping !
11 ! !
12 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
13  SUBROUTINE check_ic_common_discrete
14 
15 ! Modules
16 !---------------------------------------------------------------------//
17 ! Runtime Flag: Generate initial particle configuration.
18  USE discretelement, only : gener_part_config
19 ! Simulation dimension (2D/3D)
20  USE discretelement, only: dimn
21 ! Number of DEM solids phases.
22  USE discretelement, only: des_mmax
23 ! direction wise spans of the domain and grid spacing in each direction
24  Use geometry, only: xlength, ylength, zlength
25 ! Flag indicating that the IC region is defined.
26  USE ic, only: ic_defined
27 ! IC Region gas volume fraction.
28  USE ic, only: ic_ep_g
29 ! IC Region solid volume fraction.
30  USE ic, only: ic_ep_s
31 ! IC Region gas volume fraction.
32  USE ic, only: ic_theta_m
33 !
34  USE ic, only: ic_x_w, ic_x_e, ic_y_s, ic_y_n, ic_z_b, ic_z_t
35 ! Maximum number of IC regions
36  USE param, only: dimension_ic
37 !
38  USE param1, only: undefined, undefined_i, zero, one
39 !
40  use physprop, only: mmax
41 
42 ! Use the error manager for posting error messages.
43  use error_manager
44  implicit none
45 
46 ! Local variables
47 !---------------------------------------------------------------------//
48  INTEGER :: ICV, ICV2, M, IDIM
49  INTEGER :: COUNT_IC, COUNT_IC_WITH_SOLS
50  INTEGER :: FIRST_DEF_IC
51  DOUBLE PRECISION :: IC_ORIG(3), IC_END(3), IC2_ORIG(3) , IC2_END(3)
52  DOUBLE PRECISION :: IC_MIN, IC_MAX, IC2_MIN, IC2_MAX , TOL_IC_REG
53  LOGICAL :: SEP_AXIS, first_ic_ok
54 !---------------------------------------------------------------------//
55 
56  IF (.NOT.gener_part_config) RETURN
57 
58 ! Initialize the error manager.
59  CALL init_err_msg("CHECK_IC_COMMON_DISCRETE")
60 
61 ! First check if multiple IC regions are defined for non-zero solids volume
62 ! fraction, then check if the first IC is specified over the whole domain with IC_EP_g = 1
63 
64  !total count of defined ICs
65  count_ic = 0
66  !total count of defined IC's with solids
67  count_ic_with_sols = 0
68  first_def_ic = undefined_i
69  DO icv = 1, dimension_ic
70 
71  IF (ic_defined(icv)) THEN
72  count_ic = count_ic + 1
73  first_def_ic = min(first_def_ic, icv)
74 
75  IF(ic_ep_g(icv).LT.one) count_ic_with_sols &
76  = count_ic_with_sols + 1
77 
78  ENDIF ! if(ic_defined(icv))
79  end DO
80 
81  IF(count_ic_with_sols >= 1 .AND. &
82  count_ic > count_ic_with_sols+1) THEN
83 
84 ! If the number of IC's with solids is greater than one, make sure the
85 ! first IC spans the entire domain with voidage of one. This ensures
86 ! that the entire domain has valid ICs defined.
87  icv = first_def_ic
88  first_ic_ok = .false.
89  IF(ic_ep_g(icv).EQ.one &
90  .AND.ic_x_w(icv).LE.zero.AND.ic_x_e(icv).GE.xlength &
91  .AND.ic_y_s(icv).LE.zero.AND.ic_y_n(icv).GE.ylength) &
92  first_ic_ok = .true.
93 
94  IF (first_ic_ok .AND. ic_z_b(icv) <= zero .AND. &
95  ic_z_t(icv) >= zlength) first_ic_ok = .true.
96 
97  IF(.NOT.first_ic_ok) THEN
98  WRITE(err_msg, 1003)
99  CALL flush_err_msg(abort=.true.)
100  ENDIF
101 
102  1003 FORMAT(' Error 1003: Particle seeding with more than one IC ', &
103  'region requires',/'that IC 1 span the entire domain and ', &
104  'have IC_EP_g(1) = 1.0.',/'Please correct the mfix.dat file.')
105 
106  ENDIF
107 
108 ! Check if the ICs are non-overlapping.
109  tol_ic_reg = 1e-04
110  icvloop : DO icv = 1, dimension_ic
111 
112  IF(.NOT.ic_defined(icv)) cycle icvloop
113  IF(ic_ep_g(icv) == 1.d0) cycle icvloop
114  ic_orig(1) = ic_x_w(icv)
115  ic_orig(2) = ic_y_s(icv)
116  ic_orig(3) = ic_z_b(icv)
117  ic_end(1) = ic_x_e(icv)
118  ic_end(2) = ic_y_n(icv)
119  ic_end(3) = ic_z_t(icv)
120  icvtwoloop : DO icv2 = icv+1, dimension_ic
121 
122  IF(.NOT.ic_defined(icv2)) cycle icvtwoloop
123  IF(ic_ep_g(icv2) == 1.0d0) cycle icvtwoloop
124 
125  ic2_orig(1) = ic_x_w(icv2)
126  ic2_orig(2) = ic_y_s(icv2)
127  ic2_orig(3) = ic_z_b(icv2)
128  ic2_end(1) = ic_x_e(icv2)
129  ic2_end(2) = ic_y_n(icv2)
130  ic2_end(3) = ic_z_t(icv2)
131 
132  sep_axis = .false.
133  DO idim = 1, dimn
134 
135  ic_min = ic_orig(idim)
136  ic_max = ic_end(idim)
137  ic2_min = ic2_orig(idim)
138  ic2_max = ic2_end(idim)
139 
140 ! Check for separating axis. If the separating axis exists, then the IC
141 ! regions can't overlap generally equality implies lack of sep_axis,
142 ! and thus, overlapping. However, doing so will flag all IC's as
143 ! overlapping since IC's have to share common edges. So here the
144 ! equality is considered as existence of a separating axis, and hence,
145 ! no overlap equality is also considered as separating axis which is
146  if ((ic_min .ge. ic2_max) .or. (ic_max .le. ic2_min) ) then
147  sep_axis = .true.
148  exit
149  endif
150  end DO
151 
152 ! Implies the IC regions could not find a separating axis and are
153 ! therefore overlapping.
154  IF(.NOT.sep_axis) THEN
155  WRITE(err_msg, 1004) icv, icv2
156  CALL flush_err_msg(abort=.true.)
157  ENDIF
158 
159  1004 FORMAT('Error 1004: Overlapping IC regions with nonzero solids ',&
160  'volume',/'fraction detected. This is not supported for ', &
161  'discrete solids.',2/'Overlapping ICs: ',2(2x,i4),2/, &
162  'Please correct the mfix.dat file.')
163 
164  end DO icvtwoloop
165  end DO icvloop
166 
167 
168 
169 ! Check if IC_theta_M is specified for solids phases wherever IC_EP_g lt 1
170  DO icv = 1, dimension_ic
171 
172  IF (ic_defined(icv).and.ic_ep_g(icv).LT.one) THEN
173  DO m = mmax+1, des_mmax+mmax
174  IF(ic_theta_m(icv,m)==undefined) THEN
175  IF(ic_ep_s(icv,m).gt.zero) THEN
176  WRITE(err_msg, 1000) trim(ivar('IC_THETA_M',icv,m))
177  CALL flush_err_msg(abort=.true.)
178  ELSE
179  ic_theta_m(icv,m) = zero
180  ENDIF
181  ENDIF
182  ENDDO
183  ENDIF
184  ENDDO
185 
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  END SUBROUTINE check_ic_common_discrete
integer, parameter dimension_ic
Definition: param_mod.f:59
character(len=32) function ivar(VAR, i1, i2, i3)
subroutine finl_err_msg
double precision, dimension(dimension_ic, dim_m) ic_theta_m
Definition: ic_mod.f:86
double precision, parameter one
Definition: param1_mod.f:29
subroutine check_ic_common_discrete
logical, dimension(dimension_ic) ic_defined
Definition: ic_mod.f:107
double precision, dimension(dimension_ic) ic_z_b
Definition: ic_mod.f:35
double precision, dimension(dimension_ic) ic_x_w
Definition: ic_mod.f:23
double precision, parameter undefined
Definition: param1_mod.f:18
subroutine init_err_msg(CALLER)
Definition: ic_mod.f:9
double precision, dimension(dimension_ic) ic_z_t
Definition: ic_mod.f:38
integer mmax
Definition: physprop_mod.f:19
double precision, dimension(dimension_ic) ic_y_n
Definition: ic_mod.f:32
double precision xlength
Definition: geometry_mod.f:33
Definition: param_mod.f:2
double precision, dimension(dimension_ic) ic_x_e
Definition: ic_mod.f:26
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
double precision, dimension(dimension_ic) ic_ep_g
Definition: ic_mod.f:62
double precision ylength
Definition: geometry_mod.f:35
double precision, dimension(dimension_ic) ic_y_s
Definition: ic_mod.f:29
double precision, dimension(dimension_ic, dim_m) ic_ep_s
Definition: ic_mod.f:77
double precision, parameter zero
Definition: param1_mod.f:27
double precision zlength
Definition: geometry_mod.f:37
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)