MFIX  2016-1
check_gas_phase.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Module name: CHECK_GAS_PHASE !
4 ! Purpose: Check the gas phase input section !
5 ! !
6 ! Author: P.Nicoletti Date: 02-DEC-91 !
7 ! J.Musser Date: 01-FEB-14 !
8 ! !
9 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
10  SUBROUTINE check_gas_phase
11 
12 
13 ! Global Variables:
14 !---------------------------------------------------------------------//
15 ! Flag: Solve species equations.
16  use run, only: species_eq, energy_eq
17 ! Flag: Use legacy reaction rates implementation
18  use rxns, only: use_rrates
19 ! User specified: Constant gas viscosity
20  use physprop, only: mu_g0
21 ! User specified: Constant gas thermal conductivity
22  use physprop, only: k_g0
23 ! User specified: Constant gas mixture diffusion coefficient
24  use physprop, only: dif_g0
25 ! User specified: Constant gas specific heat
26  use physprop, only: c_pg0
27 ! User specified: Constant gas density
28  use physprop, only: ro_g0
29 ! User specified: Constant gas mixture molecular weight
30  use physprop, only: mw_avg
31 
32  use mms, only: use_mms
33 ! Global Parameters:
34 !---------------------------------------------------------------------//
35 ! Parameter constants
36  use param1, only: undefined, zero
37 
38 ! Use the error manager for posting error messages.
39 !---------------------------------------------------------------------//
40  use error_manager
41 
42 
43  IMPLICIT NONE
44 
45 
46 ! Local Variables:
47 !---------------------------------------------------------------------//
48 ! NONE
49 
50 !......................................................................!
51 
52 
53 ! Initialize the error manager.
54  CALL init_err_msg("CHECK_GAS_PHASE")
55 
56 
57 ! CHECK MU_g0
58  IF (mu_g0 <= zero) THEN
59  WRITE(err_msg,1001) 'MU_G0', ival(mu_g0)
60  CALL flush_err_msg(abort=.true.)
61  ENDIF
62 
63 ! CHECK K_g0
64  IF (k_g0 < zero) THEN
65  WRITE(err_msg,1001) 'K_G0', ival(k_g0)
66  CALL flush_err_msg(abort=.true.)
67  ENDIF
68 
69 ! CHECK C_pg0
70  IF (c_pg0 < zero) THEN
71  WRITE(err_msg,1001) 'C_PG0', ival(c_pg0)
72  CALL flush_err_msg(abort=.true.)
73  ENDIF
74 
75 ! CHECK DIF_g0
76  IF (dif_g0 < zero) THEN
77  WRITE(err_msg,1001) 'DIF_g0', ival(dif_g0)
78  CALL flush_err_msg(abort=.true.)
79  ENDIF
80 
81 ! Check the input specifications for gas species.
82  IF(use_rrates)THEN
84  ELSE
86  ENDIF
87 
88 ! Currently MMS uses constant properties. These are in place simply
89 ! to give the developer a heads-up that the code/setup may not fully
90 ! encompass the use of non-constant properties
91  IF (use_mms) THEN
92  IF (mu_g0 == undefined) THEN
93  WRITE(err_msg, 1200) 'MU_G0'
94  CALL flush_err_msg(abort=.true.)
95  ENDIF
96  IF (k_g0 == undefined .AND. energy_eq) THEN
97  WRITE(err_msg, 1200) 'K_G0'
98  CALL flush_err_msg(abort=.true.)
99  ENDIF
100  IF (dif_g0 == undefined .AND. species_eq(0)) THEN
101  WRITE(err_msg, 1200) 'DIF_G0'
102  CALL flush_err_msg(abort=.true.)
103  ENDIF
104 
105  1200 FORMAT('Error 1200: ',a,' must be defined when USE_MMS is T.',/,&
106  'Please correct the mfix.dat file.')
107  ENDIF
108 
109 ! CHECK MW_AVG
110  IF (species_eq(0)) THEN
111 ! MW_AVG is defined and the gas phase species equations are solved, then
112 ! the user specified average molecular weight is ignored. The gas phase
113 ! mixture molecular weight (MW_MIX_g) is used instead.
114  IF (mw_avg /= undefined) THEN
115  WRITE (err_msg, 1100) 'solving species equations'
116  CALL flush_err_msg
117  mw_avg = undefined
118  ENDIF
119  ELSE
120 ! When the species equations are not solved and the gas phase is
121 ! compressible, verify that the user provided average molecular weight
122 ! has a physical value. (This does not include the case where MW_AVG
123 ! is UNDEFINED.)
124  IF (ro_g0 == undefined) THEN
125  IF (mw_avg <= zero) THEN
126  WRITE(err_msg, 1001) 'MW_AVG', ival(mw_avg)
127  CALL flush_err_msg(abort=.true.)
128  ENDIF
129  ELSE
130 ! Gas density for incompressible flows must be positive.
131  IF (ro_g0 < zero) THEN
132  WRITE(err_msg, 1001) 'RO_G0', ival(ro_g0)
133  CALL flush_err_msg(abort=.true.)
134  ENDIF
135 ! Incompressible simulations do not need MW_AVG. Notify the user that
136 ! the provided data is ignored.
137  IF (mw_avg /= undefined)THEN
138  WRITE(err_msg, 1100) 'RO_g0 is specified'
139  CALL flush_err_msg
140  ENDIF
141 
142  ENDIF
143  ENDIF
144 
145 
146 ! Finalize the error manager
147  CALL finl_err_msg
148 
149 
150  RETURN
151 
152  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
153  'correct the mfix.dat file.')
154 
155  1001 FORMAT('Error 1001: Illegal or unknown input: ',a,' = ',a,/ &
156  'Please correct the mfix.dat file.')
157 
158 
159  1100 FORMAT('Message 2000: MW_AVG is not needed when ',a,'.')
160 
161  END SUBROUTINE check_gas_phase
162 
163 
164 
165 !----------------------------------------------------------------------!
166 ! Subroutine: CHECK_GAS_SPECIES !
167 ! Purpose: Gas phase species checks. !
168 ! !
169 ! Author: J. Musser Date: 07-FEB-14 !
170 !----------------------------------------------------------------------!
171  SUBROUTINE check_gas_species
173 
174 ! Global Variables:
175 !---------------------------------------------------------------------//
176 ! Flag: Solve energy equations
177  use run, only: energy_eq
178 ! Flag: Solve species equations
179  use run, only: species_eq
180 ! Flag: Database for phase X was read for species Y
181  use rxns, only: rdatabase
182 ! Flag: Code is reinitializing
183  use run, only: reinitializing
184 ! Gas phase species database names.
185  use rxns, only: species_g
186 ! Gas phase molecular weights.
187  use physprop, only: mw_g
188 ! Number of gas phase species.
189  use physprop, only: nmax, nmax_g
190 ! User specified: Constant gas phase specific heat
191  use physprop, only: c_pg0
192 ! User specified: Constant gas density
193  use physprop, only: ro_g0
194 ! User specified: Constant gas phase mixture molecular weight
195  use physprop, only: mw_avg
196 
197 
198 ! Global Parameters:
199 !---------------------------------------------------------------------//
200 ! Maximum number of gas phase species.
201  USE param, only: dim_n_g
202 ! Constants.
204  USE param1, only: zero
205 
206 
207 ! Use the error manager for posting error messages.
208 !---------------------------------------------------------------------//
209  use error_manager
210 
211 
212  implicit none
213 
214 
215 ! Local Variables:
216 !---------------------------------------------------------------------//
217 ! Loop counter.
218  INTEGER :: N
219 
220 ! Flag that the energy equations are solved and constant gas phase
221 ! specific heat is undefined.
222 ! If true, a call to the thermochemical database is made.
223  LOGICAL EEQ_CPG
224 
225 ! Flag that the average molecular weight (MW_AVG) and constant gas
226 ! phase density are undefined.
227 ! If true, a call to the thermochemical database is made.
228  LOGICAL MWg_ROg
229 
230 ! Flag that the gas phase species equations are solved and the
231 ! molecular weight for a species is not given in the data file.
232 ! If true, a call to the thermochemical database is made.
233  LOGICAL SEQ_MWg
234 
235 
236 !......................................................................!
237 
238 
239 ! Initialize the error manager.
240  CALL init_err_msg("CHECK_GAS_SPECIES")
241 
242 
243 ! Reconcile the new species input method with the legacy input method.
244  IF(species_eq(0)) THEN
245 
246  IF(nmax_g == undefined_i) THEN
247  WRITE(err_msg,1000) 'NMAX_g'
248  CALL flush_err_msg(abort=.true.)
249  ELSEIF(nmax_g > dim_n_g) THEN
250  WRITE(err_msg,1001) 'NMAX_g', ival(nmax_g)
251  CALL flush_err_msg(abort=.true.)
252  ELSE
253  nmax(0) = nmax_g
254  ENDIF
255 ! Set the number of species to one if the species equations are not solved and
256 ! the number of species is not specified.
257  ELSE
258  nmax(0) = merge(1, nmax_g, nmax_g == undefined_i)
259  ENDIF
260 
261 ! Flag that the energy equations are solved and specified solids phase
262 ! specific heat is undefined.
263  eeq_cpg = (energy_eq .AND. c_pg0 == undefined)
264  IF(eeq_cpg .AND. .NOT.reinitializing) THEN
265  WRITE(err_msg,2000)
266  CALL flush_err_msg
267  ENDIF
268 
269  2000 FORMAT('Message: 2000 The energy equations are being solved ', &
270  '(ENERGY_EQ) and',/'the constant gas specific heat is ', &
271  'undefined (C_PG0). Thus, the thermo-',/'chemical database ', &
272  'will be used to gather specific heat data on the',/ &
273  'individual gas phase species.')
274 
275  mwg_rog = .false.
276  seq_mwg = .false.
277  IF(mw_avg == undefined) THEN
278  DO n=1,nmax(0)
279  IF(mw_g(n) == undefined) THEN
280  IF(ro_g0 == undefined) mwg_rog = .true.
281  IF(species_eq(0)) seq_mwg = .true.
282  ENDIF
283  ENDDO
284  ENDIF
285 
286  IF(mwg_rog .AND. reinitializing) THEN
287  WRITE(err_msg, 2001)
288  CALL flush_err_msg
289  ENDIF
290 
291  2001 FORMAT('Message 2001: MW_AVG and RO_G0 are undefined and one or',&
292  ' more species',/'molecular weights are undefined. The therm',&
293  'ochemical database will be',/'used in an attempt to gather ',&
294  'missing molecular weight data.')
295 
296  IF(seq_mwg .AND. reinitializing) THEN
297  WRITE(err_msg, 2002)
298  CALL flush_err_msg
299  ENDIF
300 
301  2002 FORMAT('Message 2002: One or more species molecular weights are',&
302  ' undefined and',/'the gas phase species equations are being',&
303  ' solved (SOLVE_EQ(0)). The',/'thermochemical database will ',&
304  'be used in an attempt to gather missing',/'molecular weight',&
305  ' data.')
306 
307 ! Initialize flag indicating the database was read for a species.
308  rdatabase(0,:) = .false.
309 
310  IF(eeq_cpg .OR. seq_mwg .OR. mwg_rog) THEN
311 
312  IF(.NOT.reinitializing) THEN
313  WRITE(err_msg, 3000)
314  CALL flush_err_msg(footer=.false.)
315  ENDIF
316 
317  3000 FORMAT('Message 3000: Searching thermochemical databases for ', &
318  'gas phase',/'species data.',/' ')
319 
320  DO n = 1, nmax(0)
321  IF(eeq_cpg .OR. mw_g(n) == undefined) THEN
322 ! Notify the user of the reason the thermochemical database is used.
323 ! Flag that the species name is not provided.
324  IF(species_g(n) == undefined_c) THEN
325  WRITE(err_msg,1000) trim(ivar('SPECIES_g',n))
326  CALL flush_err_msg(abort=.true.)
327  ENDIF
328 ! Update the log files.
329  IF(.NOT.reinitializing) THEN
330  WRITE(err_msg, 3001) n, trim(species_g(n))
331  CALL flush_err_msg(header=.false., footer=.false.)
332  ENDIF
333  3001 FORMAT(/2x,'>',i3,': Species: ',a)
334 ! Read the database.
335  CALL read_database(0, n, species_g(n), mw_g(n))
336 ! Flag variable to stating that the database was read.
337  rdatabase(0,n) = .true.
338  ENDIF
339 
340  ENDDO ! Loop over species
341  IF(.NOT.reinitializing) CALL flush_err_msg(header=.false.)
342  ENDIF
343 
344 ! Verify that no additional species information was given.
345  DO n = nmax(0) + 1, dim_n_g
346  IF(mw_g(n) /= undefined) THEN
347  WRITE(err_msg, 1002) trim(ivar('MW_g',n))
348  CALL flush_err_msg(abort=.true.)
349  ENDIF
350  ENDDO
351 
352  CALL finl_err_msg
353 
354  RETURN
355 
356  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
357  'correct the mfix.dat file.')
358 
359  1001 FORMAT('Error 1001: Illegal or unphysical input: ',a,' = ',a,/ &
360  'Please correct the mfix.dat file.')
361 
362  1002 FORMAT('Error 1002: Illegal input: ',a,' specified out of range.',&
363  'Please correct the mfix.dat file.')
364 
365  END SUBROUTINE check_gas_species
366 
367 
368 !----------------------------------------------------------------------!
369 ! Subroutine: CHECK_GAS_SPECIES_LEGACY !
370 ! Purpose: These are legacy checks for using rrates.f to specify !
371 ! chemical reactions. !
372 ! !
373 ! Author: J. Musser Date: 03-FEB-14 !
374 !----------------------------------------------------------------------!
375  SUBROUTINE check_gas_species_legacy
377 
378 ! Global Variables:
379 !---------------------------------------------------------------------//
380 ! Flag: Solve species equations
381  use run, only: species_eq
382 ! Gas phase molecular weights.
383  use physprop, only: mw_g
384 ! Number of gas phase species.
385  use physprop, only: nmax, nmax_g
386 ! Flag: Database was read. (legacy)
387  use physprop, only: database_read
388 
389 
390 ! Global Parameters:
391 !---------------------------------------------------------------------//
392 ! Maximum number of gas phase species.
393  USE param, only: dim_n_g
394 ! Constants.
395  USE param1, only: undefined_i, undefined, zero
396 
397 
398 ! Use the error manager for posting error messages.
399 !---------------------------------------------------------------------//
400  use error_manager
401 
402 
403  implicit none
404 
405 
406 ! Local Variables:
407 !---------------------------------------------------------------------//
408 ! Loop counter.
409  INTEGER :: N
410 
411 
412 !......................................................................!
413 
414 
415 ! Initialize the error manager.
416  CALL init_err_msg("CHECK_GAS_SPECIES_LEGACY")
417 
418 
419 ! Reconcile the new species input method with the legacy input method.
420  IF(species_eq(0)) THEN
421 ! Legacy checks for species equations.
422  IF(nmax_g /= undefined_i) THEN
423  WRITE(err_msg,2000) 'NMAX_g', 'undefined'
424  CALL flush_err_msg(abort=.true.)
425  ELSEIF(nmax(0) == undefined_i) THEN
426  WRITE(err_msg,2000) trim(ivar('NMAX',0)), 'specified'
427  CALL flush_err_msg(abort=.true.)
428  ELSEIF(nmax(0) > dim_n_g) THEN
429  WRITE(err_msg,1001) trim(ivar('NMAX',0)), ival(nmax(0))
430  CALL flush_err_msg(abort=.true.)
431  ENDIF
432 ! Set the number of species to one if the species equations are not
433 ! solved and the number of species is not specified.
434  ELSE
435  IF(nmax(0) == undefined_i) nmax(0) = 1
436  ENDIF
437 
438 ! Check MW_g if solids species are present
439  DO n = 1, nmax(0)
440  IF(mw_g(n) == undefined) THEN
441  WRITE(err_msg,2000)trim(ivar('MW_g',n)), 'specified'
442  CALL flush_err_msg(abort=.true.)
443  ELSEIF(mw_g(n) <= zero) THEN
444  WRITE(err_msg,1001)trim(ivar('MW_g',n)), ival(mw_g(n))
445  CALL flush_err_msg(abort=.true.)
446  ENDIF
447  ENDDO ! Loop over species
448  DO n = nmax(0) + 1, dim_n_g
449  IF(mw_g(n) /= undefined) THEN
450  WRITE(err_msg,1001)trim(ivar('MW_g',n)), ival(mw_g(n))
451  CALL flush_err_msg(abort=.true.)
452  ENDIF
453  ENDDO
454 
455  CALL finl_err_msg
456 
457 ! Set the legacy database flag. (Also in check_solids_common_all)
458  database_read = .false.
459 
460  RETURN
461 
462  1001 FORMAT('Error 1001: Illegal or unphysical input: ',a,' = ',a,/ &
463  'Please correct the mfix.dat file.')
464 
465  2000 FORMAT('Error 2000: Invalid input. ',a,' must be ',a,/'when ', &
466  'USE_RRATES is .TRUE.'/,'Please correct the mfix.dat file')
467 
468  END SUBROUTINE check_gas_species_legacy
469 
integer, parameter dim_n_g
Definition: param_mod.f:69
character(len=32) function ivar(VAR, i1, i2, i3)
subroutine finl_err_msg
double precision c_pg0
Definition: physprop_mod.f:74
Definition: rxns_mod.f:1
logical, dimension(0:dim_m) species_eq
Definition: run_mod.f:115
double precision mu_g0
Definition: physprop_mod.f:62
double precision, parameter undefined
Definition: param1_mod.f:18
subroutine check_gas_species
double precision, dimension(dim_n_g) mw_g
Definition: physprop_mod.f:124
subroutine init_err_msg(CALLER)
logical use_rrates
Definition: rxns_mod.f:21
double precision ro_g0
Definition: physprop_mod.f:59
Definition: mms_mod.f:12
Definition: run_mod.f:13
double precision k_g0
Definition: physprop_mod.f:89
logical, dimension(0:dim_m, dim_n_g) rdatabase
Definition: rxns_mod.f:14
Definition: param_mod.f:2
logical database_read
Definition: physprop_mod.f:133
integer nmax_g
Definition: physprop_mod.f:120
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
logical reinitializing
Definition: run_mod.f:208
double precision mw_avg
Definition: physprop_mod.f:71
logical energy_eq
Definition: run_mod.f:100
logical use_mms
Definition: mms_mod.f:15
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
subroutine read_database(lM, lN, lName, lMW)
Definition: read_database.f:22
character(len=18), dimension(dim_n_g) species_g
Definition: rxns_mod.f:47
double precision dif_g0
Definition: physprop_mod.f:107
subroutine check_gas_phase
double precision, parameter zero
Definition: param1_mod.f:27
subroutine check_gas_species_legacy
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
character, parameter undefined_c
Definition: param1_mod.f:20