MFIX  2016-1
calc_dif_g.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Subroutine: CALC_DIF_g C
4 ! Purpose: Calculate the effective diffusivity of fluid phase C
5 ! C
6 ! C
7 ! Comments: C
8 ! This routine will not be called if dif_g is defined C
9 ! C
10 ! C
11 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
12  SUBROUTINE calc_dif_g()
13 
14 ! Modules
15 !---------------------------------------------------------------------//
16  USE param1, only: undefined
17  USE physprop, only: dif_g0, dif_g
18  USE sendrecv, only: send_recv
19 ! invoke user defined quantity
20  USE usr_prop, only: usr_difg, calc_usr_prop
21  USE usr_prop, only: gas_diffusivity
22  IMPLICIT NONE
23 !---------------------------------------------------------------------//
24 
25  IF (usr_difg) THEN
26  CALL calc_usr_prop(gas_diffusivity,lm=0)
27  ELSEIF (dif_g0 == undefined) THEN
28 ! unncessary check but included for clarity
30  ENDIF
31 
32  CALL send_recv(dif_g, 2)
33 
34  RETURN
35  END SUBROUTINE calc_dif_g
36 
37 
38 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
39 ! C
40 ! Subroutine: CALC_DEFAULT_DIF_GAS C
41 ! Purpose: Compute the default value for diffusivity of each gas C
42 ! species; each species is assigned the same value with the base C
43 ! value corresponding to CO2 in N2 at T=298K and P~=1atm. C
44 ! C
45 ! Author:M. Syamlal Date: 13-FEB-98 C
46 ! C
47 ! Revision: Include dilute mixture approximation for calculation of C
48 ! multicomponent diffusion coefficients C
49 ! Author:N. Reuge Date: 11-APR-07 C
50 ! C
51 ! C
52 ! Literature/Document References: C
53 ! Fuller relation - to account for influence of gas temperature C
54 ! and pressure C
55 ! Curtiss-Hirschfelder, Wilke & Blanc - dilute mixture approximation C
56 ! for multicomponent diffusion. Valid if the mass fraction of the C
57 ! carrier species > 0.9 C
58 ! C
59 ! C
60 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
61  SUBROUTINE calc_default_dif_gas
62 
63 ! Modules
64 !---------------------------------------------------------------------//
65  use compar, only: ijkstart3, ijkend3
66  use fldvar, only: rop_g, t_g, p_g, x_g
67  use functions, only: fluid_at
68  use param1, only: zero, one
69  use physprop, only: nmax, dif_g
70  use scales, only: unscale_pressure
71  use toleranc, only: zero_x_gs
72  IMPLICIT NONE
73 
74 ! Local Variables
75 !---------------------------------------------------------------------//
76 ! Indices
77  INTEGER :: IJK
78 ! Species index
79  INTEGER :: N, L
80 ! Binary diffusion coefficient
81  DOUBLE PRECISION :: Dab(nmax(0),nmax(0))
82 ! Reference temperature and pressure for each species diffusion
83 ! coefficient
84  DOUBLE PRECISION :: Tg_ref(nmax(0))
85  DOUBLE PRECISION :: Pg_ref(nmax(0))
86 ! Intermediate calculation to determine weighted average diffusion
87 ! coefficient
88  DOUBLE PRECISION :: lDab, Sum_XgLoDab, Sum_XgL, lXgN
89 !---------------------------------------------------------------------//
90 
91  CALL set_binary_dab_gas(dab, tg_ref, pg_ref)
92 
93 !!$omp parallel do private(ijk) &
94 !!$omp& schedule(dynamic,chunk_size)
95  DO n = 1, nmax(0)
96  DO ijk = ijkstart3, ijkend3
97  IF (fluid_at(ijk)) THEN
98 
99  IF (nmax(0) == 1) THEN
100 ! Only 1 species present in gas phase
101  ldab = dab(n,n)
102 
103  ELSE
104 ! Dilute mixture approximation for multi-component diffusion
105 
106  sum_xglodab = zero
107  sum_xgl = zero
108  DO l = 1, nmax(0)
109  IF (l /= n) THEN
110  sum_xglodab = sum_xglodab+&
111  x_g(ijk,l)/dab(n,l)
112 ! Sum_XgL = 1-XgN
113  sum_xgl = sum_xgl + x_g(ijk,l)
114  ENDIF
115  ENDDO
116 ! it is possible for lXgN to evaluate <0
117  lxgn = one-sum_xgl
118 
119  IF (lxgn > zero_x_gs .AND. &
120  sum_xgl > zero_x_gs) THEN
121 ! i.e. when cell is not only species N
122 ! If this criteria is too strict (i.e. when XgN->1), then this section
123 ! may be evaluated when the other XgN do not carry significant value
124 ! (i.e. are effectively zero). As a result, lDab may be evaluated and
125 ! become unrealistically large. This may happen when happen when
126 ! 1-XgN != sum_XgL. Generally, sum_XgL should equal 1-XgN but they may
127 ! differ due to the numerical evaluation of each Xg. If XgN->1, then
128 ! use both sum_XgL and 1-XgN to determine whether calculations should
129 ! proceed. Given the noted limitation of this approximation then an
130 ! additional criteria should probably be added to only evaluate when
131 ! sum_xgL <0.1.
132  IF (sum_xglodab > zero) THEN
133 ! for numerical reasons use Sum_XgL rather than ONE-X_g(IJK,N)
134  ldab = sum_xgl/sum_xglodab
135  ELSE
136 ! this should not occur...
137  ldab = dab(n,n)
138  ENDIF
139  ELSE
140 ! Address case when the mass fraction of the Nth species is nearly 1.
141  ldab = dab(n,n)
142  ENDIF
143  ENDIF
144 
145 ! Influence of gas temperature and gas pressure from Fuller relation
146  dif_g(ijk,n) = rop_g(ijk)*ldab* &
147  (t_g(ijk)/tg_ref(n))**1.75* &
148  pg_ref(n)/unscale_pressure(p_g(ijk))
149  ELSE
150  dif_g(ijk,n) = zero
151  ENDIF
152  ENDDO
153  ENDDO
154 
155  RETURN
156  END SUBROUTINE calc_default_dif_gas
157 
158 
159 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
160 ! C
161 ! Subroutine: SET_BINARY_DAB_GAS C
162 ! Purpose: Set binary diffusion coefficients for all cross species C
163 ! C
164 ! C
165 ! Literature/Document References: C
166 ! Bird, Stewart and lightfoot (1960) C
167 ! Reid, Prausnitz and Poling (1987) C
168 ! C
169 ! C
170 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
171  SUBROUTINE set_binary_dab_gas(lDab, lTg_ref, lPg_ref)
173 ! Modules
174 !---------------------------------------------------------------------//
175  use physprop, only: nmax
176  use run, only: units
177  IMPLICIT NONE
178 
179 ! Dummy arguments
180 !---------------------------------------------------------------------//
181 ! Binary diffusion coefficient
182  DOUBLE PRECISION, INTENT(OUT) :: lDab(nmax(0),nmax(0))
183  DOUBLE PRECISION, INTENT(OUT) :: lTg_ref(nmax(0))
184  DOUBLE PRECISION, INTENT(OUT) :: lPg_ref(nmax(0))
185 
186 ! Local Variables
187 !---------------------------------------------------------------------//
188 ! Species index
189  INTEGER :: N, L
190 !---------------------------------------------------------------------//
191 
192 
193 ! Default gas diffusion coefficient
194 ! Bird, Stewart, and Lightfoot (1960) -- CO2--N2 at 298.2 K
195  DO n = 1,nmax(0)
196  DO l = n,nmax(0)
197 ! DO L = N+1, NMAX(0)
198 ! IF (N /= L) THEN
199 ! assign the diaganol case for when nmax = 1 or when only species N present
200 ! in given cell.
201  ldab(n,l) = 0.165d0 !cm^2/s
202  ldab(l,n) = ldab(n,l)
203 ! ENDIF
204  ENDDO
205  ltg_ref(n) = 298.2d0
206  lpg_ref(n) = 1.01d6 !dyne
207  ENDDO
208 
209 ! Gas diffusion coefficients for 3 species system: SiH4, H2 & N2
210 ! Calculated using relation derived from Chapman and Enskog's theory
211 ! of gases - Reid, Prausnitz and Poling (1987)
212 ! Binary diffusion coefficient SiH4/H2 at 873 K
213 ! lDab(1,2) = 3.78 ! cm^2/s
214 ! lDab(2,1) = lDab(1,2)
215 ! Binary diffusion coefficient SiH4/N2 at 873 K
216 ! lDab(1,3) = 1.02 ! cm^2/s
217 ! lDab(3,1) = lDab(1,3)
218 ! Binary diffusion coefficient H2/N2 at 873 K
219 ! lDab(2,3) = 4.52 ! cm^2/s
220 ! lDab(3,2) = lDab(2,3)
221 ! DO N = 1,NMAX(0)
222 ! lTg_ref(N) = 873.0
223 ! lPg_ref(N) = 1.01e6 ! dyne
224 ! ENDDO
225 
226  IF(units == 'SI') THEN
227  DO n = 1,nmax(0)
228  DO l = n,nmax(0)
229 ! IF (N /= L) THEN
230 ! assign the diaganol case nmax = 1 or when only species N present
231 ! in given cell.
232  ldab(n,l) = ldab(n,l)*0.0001d0 !m^2/s
233  ldab(l,n) = ldab(n,l)
234 ! ENDIF
235  ENDDO
236  lpg_ref(n) = lpg_ref(n)/10.d0 !Pa
237  ENDDO
238  ENDIF
239 
240  RETURN
241  END SUBROUTINE set_binary_dab_gas
integer ijkend3
Definition: compar_mod.f:80
double precision, dimension(:,:), allocatable dif_g
Definition: physprop_mod.f:110
double precision, parameter one
Definition: param1_mod.f:29
double precision, dimension(:), allocatable t_g
Definition: fldvar_mod.f:63
subroutine calc_dif_g()
Definition: calc_dif_g.f:13
double precision, dimension(:), allocatable p_g
Definition: fldvar_mod.f:26
double precision, parameter undefined
Definition: param1_mod.f:18
subroutine calc_usr_prop(lprop, lM, lL, lerr)
Definition: usr_prop_mod.f:49
logical usr_difg
Definition: usr_prop_mod.f:15
double precision, dimension(:,:), allocatable x_g
Definition: fldvar_mod.f:75
subroutine set_binary_dab_gas(lDab, lTg_ref, lPg_ref)
Definition: calc_dif_g.f:172
double precision function unscale_pressure(XXX)
Definition: scales_mod.f:24
Definition: run_mod.f:13
character(len=16) units
Definition: run_mod.f:30
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
integer ijkstart3
Definition: compar_mod.f:80
subroutine calc_default_dif_gas
Definition: calc_dif_g.f:62
double precision, parameter zero_x_gs
Definition: toleranc_mod.f:19
double precision dif_g0
Definition: physprop_mod.f:107
double precision, dimension(:), allocatable rop_g
Definition: fldvar_mod.f:38
double precision, parameter zero
Definition: param1_mod.f:27