MFIX  2016-1
stiff_chem_maps_mod.f
Go to the documentation of this file.
2 
3  PRIVATE
4 
5 ! Variable Access:
6 !---------------------------------------------------------------------//
7 
8 ! Subroutine Access:
9 !---------------------------------------------------------------------//
10  PUBLIC :: mapmfixtoode, &
12 
13  contains
14 
15 
16 
17 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
18 ! !
19 ! Module name: mapMFIXtoODE !
20 ! !
21 ! Purpose: This routine maps MFIX variables into the ODE array. !
22 ! !
23 ! Author: J.Musser Date: 07-Feb-13 !
24 ! !
25 ! Comments: !
26 ! !
27 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
28  SUBROUTINE mapmfixtoode(lnD, lNEQ, loD, lVars)
29 
30 ! Global Variables:
31 !---------------------------------------------------------------------//
32  use fldvar, only: rop_g
33  use fldvar, only: rop_s
34  use fldvar, only: t_g
35  use fldvar, only: t_s
36  use fldvar, only: x_g
37  use fldvar, only: x_s
38 
39  use physprop, only: nmax
40  use physprop, only: mmax
41 
42 
43  implicit none
44 
45 
46 ! Passed Variables:
47 !---------------------------------------------------------------------//
48 ! Passed array dimensions
49  INTEGER, intent(in) :: lnD ! lNEQ
50  INTEGER, intent(in) :: loD ! lVars
51 
52 ! (1) Number of ODEs to be solve
53 ! (2) Fluid cell index
54  INTEGER, intent(in) :: lNEQ(lnd)
55 ! Array of dependent variable initial values.
56  DOUBLE PRECISION, intent(out) :: lVars(lod)
57 
58 
59 ! Local Variables:
60 !---------------------------------------------------------------------//
61 ! Fluid cell index
62  INTEGER :: IJK
63 ! Loop indicies:
64  INTEGER :: M ! phase
65  INTEGER :: N ! species
66 ! ODE Equation Counter
67  INTEGER :: Node
68 
69 
70 ! Initialize.
71  ijk = lneq(2)
72  lvars = 0.0d0
73  node = 1
74 
75 ! Gas phase density.
76  lvars(node) = rop_g(ijk); node = node + 1
77 ! Gas phase temperature.
78  lvars(node) = t_g(ijk); node = node + 1
79 ! Gas phase species mass fractions.
80  DO n=1,nmax(0)
81  lvars(node) = x_g(ijk,n); node = node + 1
82  ENDDO
83 
84 ! Solids temperature.
85  DO m = 1, mmax
86  lvars(node) = t_s(ijk,m); node = node + 1
87  ENDDO
88 
89  DO m = 1, mmax
90  IF(lneq(2+m) == 1) THEN
91 ! Solids volume fraction.
92  lvars(node) = rop_s(ijk,m); node = node + 1
93 ! Solids phase species mass fractions.
94  DO n=1,nmax(m)
95  lvars(node) = x_s(ijk,m,n); node = node + 1
96  ENDDO
97  ENDIF
98  ENDDO
99 
100  RETURN
101  END SUBROUTINE mapmfixtoode
102 
103 
104 
105 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
106 ! !
107 ! Module name: mapODEtoMFIX !
108 ! !
109 ! Purpose: This is a driver routine for mapping variables stored in !
110 ! the ODE array back to MFIX field variables. !
111 ! !
112 ! Author: J.Musser Date: 07-Feb-13 !
113 ! !
114 ! Comments: !
115 ! !
116 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
117  SUBROUTINE mapodetomfix(lnD, lNEQ, loD, lVars)
119 ! Global Variables:
120 !---------------------------------------------------------------------//
121 ! Material density.
122  use fldvar, only : ro_g, ro_s
123 ! Bulk density.
124  use fldvar, only : rop_g, rop_s
125 ! Gas temperature. (K)
126  use fldvar, only : t_g, t_s
127 ! Species Mass frcations.
128  use fldvar, only : x_g, x_s
129 ! Number of solids phases.
130  use physprop, only : mmax
131 ! Number of species comprising each phase.
132  use physprop, only : nmax
133 ! Gas constant (cal/g.K)
134  use constant, only : gas_const
135 ! Gas pressure
136  use fldvar, only : p_g
137 ! Gas phase volume fraction.
138  use fldvar, only : ep_g
139 ! Species molecular weights
140  use physprop, only : mw_g
141 ! Gas phase mixture molecular weight.
142  use physprop, only : mw_mix_g
143 ! Baseline/Unreaced solids density.
144  use physprop, only: ro_s0
145 ! Initial mass fraction of inert solids species.
146  use physprop, only: x_s0
147 ! Index of inert solids phase species.
148  use physprop, only: inert_species
149 ! Rank ID and Rank of IO process.
150  use compar, only : mype
151 ! Runtime flag for variable solids density.
152  use run, only: solve_ros
153 
154 ! Variable solids density calculation.
155  USE eos, ONLY: eoss
156 
157 ! Global Parameters:
158 !---------------------------------------------------------------------//
159  use param1, only : one
160  use param1, only : large_number
161  use param1, only : small_number
162 
163 
164  implicit none
165 
166 
167 ! Passed Variables:
168 !---------------------------------------------------------------------//
169 ! (1) Number of ODEs to be solve
170 ! (2) Fluid cell index
171  INTEGER, intent(in) :: lnD
172  INTEGER, intent(in) :: lNEQ(lnd)
173 
174 ! Array of dependent variable initial values.
175  INTEGER, intent(in) :: loD
176  DOUBLE PRECISION, intent(in) :: lVars(lod)
177 
178 
179 ! Local Variables:
180 !---------------------------------------------------------------------//
181 ! Fluid Cell index.
182  INTEGER :: IJK
183  INTEGER :: L
184 
185 ! Loop indicies:
186  INTEGER :: M ! phase
187  INTEGER :: N ! species
188  INTEGER :: Node ! ODE Equation Counter
189 
190 ! Error flags/counters.
191  INTEGER :: countNaN
192  LOGICAL :: writeMsg
193 
194  ijk = lneq(2)
195 
196 ! Check if any NaNs were returned from ODEPACK. This shouldn't happend
197 ! but errors in the usr_rates file can cause this to occur.
198 !-----------------------------------------------------------------------
199  countnan = 0
200  writemsg = .false.
201  nan_lp: do l=1, lod
202  if(lvars(l).NE.lvars(l)) then
203  countnan = countnan + 1
204  writemsg = .true.
205  endif
206  enddo nan_lp
207 
208  if(writemsg) then
209  write(*,"(3x,'From MapODEtoMFIX: NaNs Found! :: ',3(3x,I4))") &
210  mype, ijk, countnan
211 
212  if(countnan < lod) then
213  do l=1, lod
214  if(lvars(l).NE.lvars(l)) &
215  write(*,"(5x,' NaN in Var ',I2)") l
216  enddo
217  endif
218  endif
219 
220 ! Directly map the ODE values into the field variable names.
221 !-----------------------------------------------------------------------
222 ! Initialize the loop counter for ODEs.
223  node = 1
224 
225 ! Gas phase density.
226  rop_g(ijk) = lvars(node); node = node + 1
227 ! Gas phase temperature.
228  t_g(ijk) = lvars(node); node = node + 1
229 ! Gas phase species mass fractions.
230  DO n=1,nmax(0)
231  x_g(ijk,n) = lvars(node); node = node + 1
232  ENDDO
233 
234 ! Solids temperature.
235  DO m = 1, mmax
236  IF(rop_s(ijk,m) > 1.0d-8) &
237  t_s(ijk,m) = lvars(node); node = node + 1
238  ENDDO
239 
240 ! Only map back what was calculated.
241  DO m = 1, mmax
242  IF(lneq(2+m) == 1) THEN
243 ! Solids bulk density.
244  rop_s(ijk,m) = lvars(node); node = node + 1
245 ! Solids phase species mass fractions.
246  DO n=1,nmax(m)
247  x_s(ijk,m,n) = lvars(node); node = node + 1
248  ENDDO
249 ! Update the solids density from speices composition. This update must
250 ! come after the species data is mapped back into the MFIX variables.
251  IF(solve_ros(m)) ro_s(ijk,m) = eoss(ro_s0(m), &
252  x_s0(m,inert_species(m)), x_s(ijk,m,inert_species(m)))
253  ENDIF
254  ENDDO
255 
256 ! Calculate the gas volume fraction from solids volume fractions. Only
257 ! update it's value if the solids equations are being solved.
258  IF(sum(lneq(3:)) > 0) ep_g(ijk) = &
259  one - sum(rop_s(ijk,1:mmax)/ro_s(ijk,1:mmax))
260 
261 ! Gas phase bulk density is updated within the stiff solver (lVar(1)).
262 ! Now that the gas phase volume fraction is updated, the gas phase
263 ! density can be backed out. RO_g * EP_g = ROP_g
264  IF(ep_g(ijk) > small_number) THEN
265  ro_g(ijk) = rop_g(ijk) / ep_g(ijk)
266  ELSE
267 ! This case shouldn't happen, however 'LARGE_NUMBER' is used to aid
268 ! in tracking errors should this somehow become and issue.
269  ro_g(ijk) = large_number
270  ENDIF
271 
272 ! Calculate the mixture molecular weight.
273  mw_mix_g(ijk) = sum(x_g(ijk,1:nmax(0))/mw_g(1:nmax(0)))
274  mw_mix_g(ijk) = one/mw_mix_g(ijk)
275 
276 ! Calculate the gas phase pressure.
277  p_g(ijk) = (ro_g(ijk)*gas_const*t_g(ijk))/mw_mix_g(ijk)
278 
279  RETURN
280  END SUBROUTINE mapodetomfix
281 
282  END MODULE stiff_chem_maps
double precision, dimension(:), allocatable ep_g
Definition: fldvar_mod.f:15
double precision, parameter one
Definition: param1_mod.f:29
double precision, dimension(:), allocatable t_g
Definition: fldvar_mod.f:63
double precision gas_const
Definition: constant_mod.f:152
logical, dimension(dim_m) solve_ros
Definition: run_mod.f:250
subroutine, public mapodetomfix(lnD, lNEQ, loD, lVars)
double precision, dimension(:), allocatable p_g
Definition: fldvar_mod.f:26
double precision, dimension(dim_m, dim_n_s) x_s0
Definition: physprop_mod.f:32
double precision, dimension(dim_n_g) mw_g
Definition: physprop_mod.f:124
subroutine, public mapmfixtoode(lnD, lNEQ, loD, lVars)
integer mmax
Definition: physprop_mod.f:19
double precision, dimension(:,:,:), allocatable x_s
Definition: fldvar_mod.f:78
double precision function eoss(pBase, Xs0_INERT, Xs_INERT)
Definition: eos_mod.f:155
double precision, parameter small_number
Definition: param1_mod.f:24
double precision, dimension(:,:), allocatable t_s
Definition: fldvar_mod.f:66
double precision, dimension(:,:), allocatable x_g
Definition: fldvar_mod.f:75
integer, dimension(dim_m) inert_species
Definition: physprop_mod.f:39
Definition: eos_mod.f:10
Definition: run_mod.f:13
double precision, parameter large_number
Definition: param1_mod.f:23
double precision, dimension(:,:), allocatable ro_s
Definition: fldvar_mod.f:45
double precision, dimension(:), allocatable mw_mix_g
Definition: physprop_mod.f:130
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
integer mype
Definition: compar_mod.f:24
double precision, dimension(:,:), allocatable rop_s
Definition: fldvar_mod.f:51
double precision, dimension(dim_m) ro_s0
Definition: physprop_mod.f:28
double precision, dimension(:), allocatable ro_g
Definition: fldvar_mod.f:32
double precision, dimension(:), allocatable rop_g
Definition: fldvar_mod.f:38