MFIX  2016-1
check_solids_common_all.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: CHECK_SOLIDS_COMMON_ALL !
4 ! Purpose: Check the solid phase input that is common to all solids !
5 ! phase models. !
6 ! !
7 ! ****** DO NOT PUT MODEL SPECIFIC CHECKS IN THIS ROUTINE ****** !
8 ! !
9 ! Use the companion routines for checks specific to a particular !
10 ! solids phase model: !
11 ! !
12 ! > CHECK_SOLIDS_CONTINUUM :: TFM solids phase model !
13 ! > CHECK_SOLIDS_DEM :: DEM solids phase model !
14 ! > CHECK_SOLIDS_MPPIC :: MPPIC solids phase model !
15 ! !
16 ! Author: J.Musser Date: 03-FEB-14 !
17 ! !
18 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
19  SUBROUTINE check_solids_common_all
20 
21 
22 ! Global Variables:
23 !---------------------------------------------------------------------//
24  use run, only: energy_eq, species_eq
25 ! Flag: Use legacy rrates implementation.
26  use rxns, only: use_rrates
27 ! Number of continuum solids phases.
28  use physprop, only: smax, mmax
29 ! Number of discrete (DEM/MPPIC) solids.
30  use discretelement, only: des_mmax
31 ! User specified: Constant solids specific heat.
32  use physprop, only: c_ps0
33 ! User specified: Constant solids thermal conductivity.
34  use physprop, only: k_s0
35 ! User specified: Initial solids diameter.
36  use physprop, only: d_p0
37  use physprop, only: mu_s0, dif_s0
38  use mms, only: use_mms
39 
40 ! Global Parameters:
41 !---------------------------------------------------------------------//
42 ! Maximum number of solids phases.
43  use param, only: dim_m
44 ! Parameter constants
45  use param1, only: undefined, zero
46 
47 
48 ! Global Module procedures:
49 !---------------------------------------------------------------------//
50  use error_manager
51 
52 
53  implicit none
54 
55 
56 ! Local Variables:
57 !---------------------------------------------------------------------//
58 ! Loop counters.
59  INTEGER :: M
60 ! Total number of all solids
61  INTEGER :: MMAX_L
62 
63 !......................................................................!
64 
65 ! Initialize the error manager.
66  CALL init_err_msg("CHECK_SOLIDS_COMMON_ALL")
67 
68 ! Set the number of solids phases to be checked.
69  mmax_l = smax + des_mmax
70 
71 ! Check D_p0
72  DO m = 1, mmax_l
73  IF(d_p0(m) == undefined) THEN
74  WRITE(err_msg, 1000) trim(ivar('D_p0',m))
75  CALL flush_err_msg(abort=.true.)
76  ELSEIF(d_p0(m) <= zero)THEN
77  WRITE(err_msg, 1001) trim(ivar('D_p0',m)), ival(d_p0(m))
78  CALL flush_err_msg(abort=.true.)
79  ENDIF
80  ENDDO
81 
82  DO m = mmax_l+1, dim_m
83  IF(d_p0(m) /= undefined)THEN
84  WRITE(err_msg,1002) trim(ivar('D_p0',m))
85  CALL flush_err_msg(abort=.true.)
86  ENDIF
87  ENDDO
88 
89 ! Check K_s0
90  DO m=1, mmax_l
91  IF (k_s0(m) < zero) THEN
92  WRITE(err_msg, 1001) trim(ivar('K_s0',m)), ival(k_s0(m))
93  CALL flush_err_msg(abort=.true.)
94  ENDIF
95  ENDDO
96 
97  DO m = mmax_l+1, dim_m
98  IF(k_s0(m) /= undefined)THEN
99  WRITE(err_msg,1002) trim(ivar('K_s0',m))
100  CALL flush_err_msg(abort=.true.)
101  ENDIF
102  ENDDO
103 
104 ! Check C_ps0
105  DO m=1, mmax_l
106  IF (c_ps0(m) < zero) THEN
107  WRITE(err_msg, 1001) trim(ivar('C_ps0',m)), ival(c_ps0(m))
108  CALL flush_err_msg(abort=.true.)
109  ENDIF
110  ENDDO
111 
112  DO m = mmax_l+1, dim_m
113  IF(c_ps0(m) /= undefined)THEN
114  WRITE(err_msg,1002) trim(ivar('C_ps0',m))
115  CALL flush_err_msg(abort=.true.)
116  ENDIF
117  ENDDO
118 
119 ! Check the input specifications for solids species.
120  IF(use_rrates)THEN
121  CALL check_solids_species_legacy(mmax_l)
122  ELSE
123  CALL check_solids_species(mmax_l)
124  ENDIF
125 
126 ! Currently MMS uses constant properties. These are in place simply
127 ! to give the developer a heads-up that the code/setup may not fully
128 ! encompass the use of non-constant properties
129  IF (use_mms) THEN
130  DO m = 1, mmax_l
131  IF (mu_s0(m) == undefined) THEN
132  WRITE(err_msg, 1200) trim(ivar('MU_s0',m))
133  CALL flush_err_msg(abort=.true.)
134  ENDIF
135  IF (k_s0(m) == undefined .AND. energy_eq) THEN
136  WRITE(err_msg, 1200) trim(ivar('K_s0',m))
137  CALL flush_err_msg(abort=.true.)
138  ENDIF
139  IF (dif_s0(m) == undefined .AND. species_eq(m)) THEN
140  WRITE(err_msg, 1200) trim(ivar('DIF_S0',m))
141  CALL flush_err_msg(abort=.true.)
142  ENDIF
143  ENDDO
144  1200 FORMAT('Error 1200: ',a,' must be defined when USE_MMS is T.',/,&
145  'Please correct the mfix.dat file.')
146  ENDIF
147 
148 
149 ! Check solids drag model selection.
150  CALL check_solids_drag
151 
152 ! Checks required for the subgrid drag models.
154 
155 ! Check the solids density input parameters.
156  CALL check_solids_density(mmax_l)
157 
158 ! Finalize the error messges
159  CALL finl_err_msg
160 
161  RETURN
162 
163  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
164  'correct the mfix.dat file.')
165 
166  1001 FORMAT('Error 1001: Illegal or unphysical input: ',a,' = ',a,/ &
167  'Please correct the mfix.dat file.')
168 
169  1002 FORMAT('Error 1002: Illegal input: ',a,' specified out of range.', &
170  'Please correct the mfix.dat file.')
171 
172  END SUBROUTINE check_solids_common_all
173 
174 
175 !----------------------------------------------------------------------!
176 ! Subroutine: CHECK_SOLIDS_DRAG !
177 ! Purpose: Check solids species input. !
178 ! !
179 ! Author: J. Musser Date: 07-FEB-14 !
180 !----------------------------------------------------------------------!
181  SUBROUTINE check_solids_drag
183 ! Global Variables:
184 !---------------------------------------------------------------------//
185 ! User specifed drag type, as string and enum
186  use run, only: drag_type
187  use run, only: drag_type_enum
188 ! Possible DRAG_TYPE_ENUM values:
189  use run, only: syam_obrien
190  use run, only: gidaspow
191  use run, only: gidaspow_pcf
192  use run, only: gidaspow_blend
193  use run, only: gidaspow_blend_pcf
194  use run, only: wen_yu
195  use run, only: wen_yu_pcf
196  use run, only: koch_hill
197  use run, only: koch_hill_pcf
198  use run, only: bvk
199  use run, only: hys
200  use run, only: user_drag
201 
202 ! Global Parameters:
203 !---------------------------------------------------------------------//
204 
205 ! Global Module procedures:
206 !---------------------------------------------------------------------//
207  use error_manager
208 
209  implicit none
210 
211 
212 ! Local Variables:
213 !---------------------------------------------------------------------//
214 ! NONE
215 
216 !......................................................................!
217 
218 
219 ! Initialize the error manager.
220  CALL init_err_msg("CHECK_SOLIDS_DRAG")
221 
222  SELECT CASE(trim(adjustl(drag_type)))
223 
224  CASE ('SYAM_OBRIEN'); drag_type_enum = syam_obrien
225  CASE ('GIDASPOW'); drag_type_enum = gidaspow
226  CASE ('GIDASPOW_PCF'); drag_type_enum = gidaspow_pcf
227  CASE ('GIDASPOW_BLEND'); drag_type_enum = gidaspow_blend
228  CASE ('GIDASPOW_BLEND_PCF'); drag_type_enum = gidaspow_blend_pcf
229  CASE ('WEN_YU'); drag_type_enum = wen_yu
230  CASE ('WEN_YU_PCF'); drag_type_enum = wen_yu_pcf
231  CASE ('KOCH_HILL'); drag_type_enum = koch_hill
232  CASE ('KOCH_HILL_PCF'); drag_type_enum = koch_hill_pcf
233  CASE ('BVK'); drag_type_enum = bvk
234  CASE ('HYS'); drag_type_enum = hys
235  CASE ('USER_DRAG','USR_DRAG'); drag_type_enum = user_drag
236 
237  CASE DEFAULT
238  WRITE(err_msg,1001)'DRAG_TYPE', trim(adjustl(drag_type))
239  CALL flush_err_msg(abort=.true.)
240  END SELECT
241 
242  CALL finl_err_msg
243 
244  RETURN
245 
246  1001 FORMAT('Error 1001: Illegal or unknown input: ',a,' = ',a,/ &
247  'Please correct the mfix.dat file.')
248 
249  END SUBROUTINE check_solids_drag
250 
251 
252 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
253 ! !
254 ! Subroutine: CHECK_SUBGRID_MODEL !
255 ! Purpose: Check the subgrid drag model interactions. !
256 ! !
257 ! Author: J.Musser Date: 31-JAN-14 !
258 ! !
259 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
260  SUBROUTINE check_subgrid_model
262 ! Global Variables:
263 !---------------------------------------------------------------------//
264 ! Flag: Specify friction model (Schaeffer model/Princeton model)
265  USE run, only: friction
266 ! Flag: Solve granular energy eq
267  USE run, only: granular_energy
268 ! Flag: Solve K-Epsilon Eq.
269  USE run, only: k_epsilon
270 ! Flag: Impose a mean shear on flow field.
271  USE run, only: shear
272 ! Flag: Invoke Schaeffer and KT-Theory blending
273  USE run, only: blending_stress
274 ! User specifed drag model
275  USE run, only: drag_type
276 ! Ratio of filter size to computational cell size
277  USE run, only: filter_size_ratio
278 ! User specifed subgrid model: IGCI or MILIOLI
279  USE run, only: subgrid_type, subgrid_type_enum
280  USE run, only: undefined_subgrid_type, igci, milioli
281 ! Flag: Include wall effect term
282  USE run, only: subgrid_wall
283 ! Specularity coefficient for particle-wall collisions
284  use constant, only: phip
285 ! Flag: Use cartesian grid model
286  USE cutcell, only : cartesian_grid
287 ! Flag: Use discrete element solids model
288  use discretelement, only: discrete_element
289 ! Flag: Use MP-PIC solids model
290  use mfix_pic, only: mppic
291 
292 ! Global Parameters:
293 !---------------------------------------------------------------------//
294  USE param1, only: zero, undefined_c
295 
296 
297 ! Global Module procedures:
298 !---------------------------------------------------------------------//
299  USE error_manager
300 
301  IMPLICIT NONE
302 
303 ! Local Variables:
304 !---------------------------------------------------------------------//
305 ! NONE
306 
307 ! If the models are not being used, return.
308  IF(subgrid_type == undefined_c .AND. .NOT.subgrid_wall) RETURN
309 
310 
311 ! Initialize the error manager.
312  CALL init_err_msg("CHECK_SUBGRID_MODEL")
313 
314 
315  IF(subgrid_type == undefined_c .AND. subgrid_wall) THEN
316  WRITE(err_msg,2011)
317  CALL flush_err_msg(abort=.true.)
318  ENDIF
319 
320  2011 FORMAT('Error 2011: Invalid input. SUBGRID_WALL cannot be used ',&
321  'without',/'specifying a SUBGRID_TYPE.',/'Please correct ', &
322  'the mfix.dat file.')
323 
324 
325  SELECT CASE(trim(adjustl(subgrid_type)))
326 
327  CASE ('IGCI'); subgrid_type_enum = igci
328  CASE ('MILIOLI'); subgrid_type_enum = milioli
329  CASE DEFAULT
330  subgrid_type_enum = undefined_subgrid_type
331  END SELECT
332 
333  IF(subgrid_type_enum .ne. igci .AND. subgrid_type_enum .ne. milioli) THEN
334  WRITE(err_msg,1001) 'SUBGRID_TYPE', subgrid_type
335  CALL flush_err_msg(abort=.true.)
336  ENDIF
337 
338  IF(drag_type /= 'WEN_YU')THEN
339  WRITE(err_msg, 2012)
340  CALL flush_err_msg(abort=.true.)
341  ENDIF
342 
343  2012 FORMAT('Error 2012: Invalid input. WEN_YU is the only DRAG_TYPE',&
344  ' available',/'when using the SUBGRID model.',/'Please ', &
345  'correct the mfix.dat file.')
346 
347  IF(discrete_element .OR. mppic) THEN
348  WRITE(err_msg, 2013)
349  CALL flush_err_msg(abort=.true.)
350  ENDIF
351 
352  2013 FORMAT('Error 2013: Invalid input. The SUBGRID model is not ', &
353  'available',/'with discrete solids phases.',/'Please ', &
354  'correct the mfix.dat file.')
355 
356 ! Impose the subgrid limitations.
357  IF(filter_size_ratio <= zero) THEN
358  WRITE(err_msg, 1002)'FILTER_SIZE_RATIO', filter_size_ratio
359  CALL flush_err_msg(abort=.true.)
360 
361  ELSEIF(granular_energy) THEN
362  WRITE(err_msg, 2010) 'GRANULAR_ENERGY', 'FALSE'
363  CALL flush_err_msg(abort=.true.)
364 
365  ELSEIF(k_epsilon) THEN
366  WRITE(err_msg, 2010) 'K_EPSILON', 'FALSE'
367  CALL flush_err_msg(abort=.true.)
368 
369  ELSEIF(blending_stress) THEN
370  WRITE(err_msg, 2010) 'BLENDING_STRESS', 'FALSE'
371  CALL flush_err_msg(abort=.true.)
372 
373  ELSEIF(friction) THEN
374  WRITE(err_msg, 2010) 'FRICTION', 'FALSE'
375  CALL flush_err_msg(abort=.true.)
376 
377  ELSEIF(shear) THEN
378  WRITE(err_msg, 2010) 'SHEAR', 'FALSE'
379  CALL flush_err_msg(abort=.true.)
380 
381  ELSEIF(phip /= zero) THEN
382  WRITE(err_msg, 2010) 'PHIP', 'ZERO'
383  CALL flush_err_msg(abort=.true.)
384 
385  ENDIF
386 
387  IF(subgrid_wall .AND. .NOT.cartesian_grid) THEN
388  WRITE(err_msg, 2010) 'CARTESIAN_GRID', 'TRUE'
389  CALL flush_err_msg(abort=.true.)
390  ENDIF
391 
392  2010 FORMAT('Error 2010: Invalid input. ',a,' must be ',a,/'when ', &
393  'using the SUBGRID model.'/,'Please correct the mfix.dat', &
394  ' file.')
395 
396  CALL finl_err_msg
397 
398  RETURN
399 
400 
401  1001 FORMAT('Error 1001: Illegal or unknown input: ',a,' = ',a,/ &
402  'Please correct the mfix.dat file.')
403 
404  1002 FORMAT('Error 1002: Illegal or unknown input: ',a,' = ',g14.4,/ &
405  'Please correct the mfix.dat file.')
406 
407  1003 FORMAT('Error 1003: Illegal or unknown input: ',a,' = ',i4,/ &
408  'Please correct the mfix.dat file.')
409 
410  END SUBROUTINE check_subgrid_model
411 
412 
413 
414 !----------------------------------------------------------------------!
415 ! Subroutine: CHECK_SOLIDS_SPECIES !
416 ! Purpose: Check solids species input. !
417 ! !
418 ! Author: J. Musser Date: 07-FEB-14 !
419 !----------------------------------------------------------------------!
420  SUBROUTINE check_solids_species(MMAX_LL)
422 
423 ! Global Variables:
424 !---------------------------------------------------------------------//
425 ! Flag: Solve energy equations
426  use run, only: energy_eq
427 ! Flag: Solve species equations
428  use run, only: species_eq
429 ! FLag: Reinitializing the code
430  use run, only: reinitializing
431 ! Flag: Database for phase X was read for species Y
432  use rxns, only: rdatabase
433 ! Solids phase species database names.
434  use rxns, only: species_s
435 ! Solids phase molecular weights.
436  use physprop, only: mw_s
437 ! Number of solids phase species.
438  use physprop, only: nmax, nmax_s
439 ! User specified: Constant solids specific heat
440  use physprop, only: c_ps0
441 
442 ! Global Parameters:
443 !---------------------------------------------------------------------//
444 ! Maximum number of solids phase species.
445  USE param, only: dim_n_s
446 ! Parameter constants.
448 
449 ! Global Module procedures:
450 !---------------------------------------------------------------------//
451  use error_manager
452 
453 
454  implicit none
455 
456 
457 ! Subroutine Arguments:
458 !---------------------------------------------------------------------//
459 ! Total number of solids phases
460  INTEGER, intent(in) :: MMAX_LL
461 
462 ! Local Variables:
463 !---------------------------------------------------------------------//
464 
465 ! Flag that the energy equations are solved and specified solids phase
466 ! specific heat is undefined.
467 ! If true, a call to the thermochemical database is made.
468  LOGICAL EEQ_CPS
469 
470 ! Flag that the solids phase species equations are solved and the
471 ! molecular weight for a species are not given in the data file.
472 ! If true, a call to the thermochemical database is made.
473  LOGICAL SEQ_MWs
474 
475 ! Loop counters.
476  INTEGER :: M, N
477 
478 
479 !......................................................................!
480 
481 
482 ! Initialize the error manager.
483  CALL init_err_msg("CHECK_SOLIDS_SPECIES")
484 
485 
486 ! Reconcile the new species input method with the legacy input method.
487  DO m=1, mmax_ll
488  IF(species_eq(m)) THEN
489  IF(nmax_s(m) == undefined_i) THEN
490  WRITE(err_msg,1000) ivar('NMAX_s',m)
491  CALL flush_err_msg(abort=.true.)
492  ELSEIF(nmax_s(m) > dim_n_s) THEN
493  WRITE(err_msg,1001) trim(ivar('NMAX_s',m)), &
494  trim(ival(nmax_s(m)))
495  CALL flush_err_msg(abort=.true.)
496  ELSE
497  nmax(m) = nmax_s(m)
498  ENDIF
499 
500 ! Set the number of species to one if the species equations are not solved and
501 ! the number of species is not specified.
502  ELSE
503  nmax(m) = merge(1, nmax_s(m), nmax_s(m) == undefined_i)
504  ENDIF
505 
506 ! Flag that the energy equations are solved and specified solids phase
507 ! specific heat is undefined.
508  eeq_cps = (energy_eq .AND. c_ps0(m) == undefined)
509  IF(eeq_cps .AND. .NOT.reinitializing)THEN
510  WRITE(err_msg,2000)
511  CALL flush_err_msg
512  ENDIF
513 
514  2000 FORMAT('Message: 2000 The energy equations are being solved ', &
515  '(ENERGY_EQ) and',/'the constant solids specific heat is ', &
516  'undefined (C_PS0). Thus, the',/'thermochemical database ', &
517  'will be used to gather specific heat data on',/'the ', &
518  'individual gas phase species.')
519 
520  seq_mws = .false.
521  DO n=1,nmax(m)
522  IF(mw_s(m,n) == undefined) THEN
523  IF(species_eq(m)) seq_mws = .true.
524  ENDIF
525  ENDDO
526 
527  IF(seq_mws .AND. .NOT.reinitializing) THEN
528  WRITE(err_msg, 2001) m
529  CALL flush_err_msg
530  ENDIF
531 
532  2001 FORMAT('Message 2001: One or more species molecular weights are',&
533  ' undefined and',/'the solids phase species equations are ', &
534  'solved (SOLVE_EQ(',i2,')). The',/'thermochemical database ', &
535  'will be used in an attempt to gather missing',/'molecular ', &
536  'weight data.')
537 
538 ! Initialize flag indicating the database was read for a species.
539  rdatabase(m,:) = .false.
540 
541  IF(eeq_cps .OR. seq_mws)THEN
542 
543  IF(.NOT.reinitializing) THEN
544  WRITE(err_msg, 3000) m
545  CALL flush_err_msg(footer=.false.)
546  ENDIF
547 
548  3000 FORMAT('Message 3000: Searching thermochemical databases for ', &
549  'solids phase',i3,/'species data.',/' ')
550 
551  DO n = 1, nmax(m)
552 
553 ! Notify the user of the reason the thermochemical database is used.
554  IF(eeq_cps .OR. mw_s(m,n) == undefined) THEN
555 
556 ! Flag that the species name is not provided.
557  IF(species_s(m,n) == undefined_c) THEN
558  WRITE(err_msg,1000) trim(ivar('SPECIES_s',m,n))
559  CALL flush_err_msg(abort=.true.)
560  ENDIF
561 ! Update the log files.
562  IF(.NOT.reinitializing) THEN
563  WRITE(err_msg, 3001) n, trim(species_s(m,n))
564  CALL flush_err_msg(header=.false., footer=.false.)
565  ENDIF
566  3001 FORMAT(/2x,'>',i3,': Species: ',a)
567 
568  CALL read_database(m, n, species_s(m,n), mw_s(m,n))
569 ! Flag variable to stating that the database was read.
570  rdatabase(m,n) = .true.
571  ENDIF
572  ENDDO ! Loop over species
573  IF(.NOT.reinitializing) CALL flush_err_msg(header=.false.)
574  ENDIF
575 
576 ! Verify that no additional species information was given.
577  DO n = nmax(m) + 1, dim_n_s
578  IF(mw_s(m,n) /= undefined) THEN
579  WRITE(err_msg, 1002) trim(ivar('MW_s',m,n))
580  CALL flush_err_msg(abort=.true.)
581  ENDIF
582  ENDDO
583  ENDDO ! Loop over solids phases
584 
585  CALL finl_err_msg
586 
587  RETURN
588 
589  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
590  'correct the mfix.dat file.')
591 
592  1001 FORMAT('Error 1001: Illegal or unphysical input: ',a,' = ',a,/ &
593  'Please correct the mfix.dat file.')
594 
595  1002 FORMAT('Error 1002: Illegal input: ',a,' specified out of range.',&
596  'Please correct the mfix.dat file.')
597 
598  END SUBROUTINE check_solids_species
599 
600 
601 !----------------------------------------------------------------------!
602 ! Subroutine: CHECK_SOLIDS_SPECIES_LEGACY !
603 ! Purpose: These are legacy checks for using rrates.f to specify !
604 ! chemical reactions. !
605 ! !
606 ! Author: J. Musser Date: 03-FEB-14 !
607 !----------------------------------------------------------------------!
608  SUBROUTINE check_solids_species_legacy(MMAX_LL)
610 
611 ! Global Variables:
612 !---------------------------------------------------------------------//
613 ! Flag: Solve species equations
614  use run, only: species_eq
615 ! Solids phase molecular weights.
616  use physprop, only: mw_s
617 ! Number of solids phase species.
618  use physprop, only: nmax, nmax_s
619 ! Flag: Database was read. (legacy)
620  use physprop, only: database_read
621 
622 ! Global Parameters:
623 !---------------------------------------------------------------------//
624 ! Maximum number of gas phase species.
625  USE param, only: dim_n_s
626 ! Constants.
627  USE param1, only: undefined_i, undefined
628 
629 ! Global Module procedures:
630 !---------------------------------------------------------------------//
631  use error_manager
632 
633 
634  implicit none
635 
636 
637 ! Arguments:
638 !---------------------------------------------------------------------//
639 ! Total number of solids phases
640  INTEGER, intent(in) :: MMAX_LL
641 
642 ! Local Variables:
643 !---------------------------------------------------------------------//
644 ! Loop counters.
645  INTEGER :: M, N
646 
647 
648 !......................................................................!
649 
650 
651 ! Initialize the error manager.
652  CALL init_err_msg("CHECK_SOLIDS_SPECIES_LEGACY")
653 
654 ! Reconcile the new species input method with the legacy input method.
655  DO m=1, mmax_ll
656  IF(species_eq(m)) THEN
657 
658 ! Legacy checks for species equations.
659  IF(nmax_s(m) /= undefined_i) THEN
660  WRITE(err_msg,2000) trim(ivar('NMAX_s',m)), 'undefined'
661  CALL flush_err_msg(abort=.true.)
662  ELSEIF(nmax(m) == undefined_i) THEN
663  WRITE(err_msg,2000) trim(ivar('NMAX',m)), 'specified'
664  CALL flush_err_msg(abort=.true.)
665  ELSEIF(nmax(m) > dim_n_s) THEN
666  WRITE(err_msg,1002) trim(ivar('NMAX',m))
667  CALL flush_err_msg(abort=.true.)
668  ENDIF
669 
670 ! Set the number of species to one if the species equations are not solved and
671 ! the number of species is not specified.
672  ELSE
673  IF(nmax(m) == undefined) nmax(m) = 1
674  ENDIF
675  ENDDO
676 
677 ! Check MW_s if solids species are present
678  DO m = 1, mmax_ll
679 ! Initialize flag indicating the database was read for a species.
680  DO n = 1, nmax(m)
681  IF(mw_s(m,n) == undefined) THEN
682  WRITE(err_msg, 2000) trim(ivar('MW_s',m,n)), 'specified'
683  CALL flush_err_msg(abort=.true.)
684  ENDIF
685  ENDDO ! Loop over species
686  DO n = nmax(m) + 1, dim_n_s
687  IF(mw_s(m,n) /= undefined) THEN
688  WRITE(err_msg,1002) trim(ivar('MW_s',m,n))
689  ENDIF
690  ENDDO
691  ENDDO ! Loop over solids phases
692 
693 ! Set the legacy database flag. (Also in check_gas_phase.f)
694  database_read = .false.
695 
696  CALL finl_err_msg
697 
698  RETURN
699 
700  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
701  'correct the mfix.dat file.')
702 
703  1001 FORMAT('Error 1001: Illegal or unphysical input: ',a,' = ',a,/ &
704  'Please correct the mfix.dat file.')
705 
706  1002 FORMAT('Error 1002: Illegal input: ',a,' specified out of range.',&
707  'Please correct the mfix.dat file.')
708 
709  2000 FORMAT('Error 2000: Invalid input. ',a,' must be ',a,/'when ', &
710  'USE_RRATES is .TRUE.'/,'Please correct the mfix.dat file')
711 
712  END SUBROUTINE check_solids_species_legacy
713 
714 
715 
716 !----------------------------------------------------------------------!
717 ! Subroutine: CHECK_SOLIDS_DENSITY !
718 ! Purpose: check the solid phase density input !
719 ! !
720 ! Author: J.Musser Date: 03-FEB-14 !
721 !----------------------------------------------------------------------!
722  SUBROUTINE check_solids_density(MMAX_LL)
724 
725 ! Global Variables:
726 !---------------------------------------------------------------------//
727 ! Flag: Solve variable solids density.
728  use run, only: solve_ros
729 ! User specified: constant solids density
730  use physprop, only: ro_s0
731 ! Baseline species densities
732  use physprop, only: ro_xs0
733 ! Baseline species mass fractions.
734  use physprop, only: x_s0
735 ! Index of inert solids species
736  use physprop, only: inert_species
737 ! Inert species mass fraction in dilute region
738  use physprop, only: dil_inert_x_vsd
739 ! Number of solids phase species.
740  use physprop, only: nmax
741 
742 ! Global Parameters:
743 !---------------------------------------------------------------------//
744 ! Parameter constants
745  use param1, only: zero, one
746  use param1, only: undefined, undefined_i
747 ! Maximum number of solids phases.
748  use param, only: dim_m
749 ! Maximum number of solids species.
750  use param, only: dim_n_s
751 
752 ! Solids phase density caMulation
753  use eos, ONLY: eoss0
754 
755 ! Global Module procedures:
756 !---------------------------------------------------------------------//
757  use error_manager
758 
759 
760  implicit none
761 
762 
763 ! Arguments:
764 !---------------------------------------------------------------------//
765 ! Total number of solids phases
766  INTEGER, intent(in) :: MMAX_LL
767 
768 ! Local Variables:
769 !---------------------------------------------------------------------//
770  INTEGER :: M, N
771 
772 
773 !......................................................................!
774 
775 
776 ! Initialize the error manager.
777  CALL init_err_msg("CHECK_SOLIDS_DENSITY")
778 
779 ! Initialize the flag for variable solids density.
780  solve_ros = .false.
781 
782 ! Check each solids phase.
783  DO m = 1, mmax_ll
784 
785 ! Set the flag for variable solids density if any of the input parameters
786 ! are specified.
787  IF(inert_species(m) /= undefined_i) solve_ros(m) = .true.
788  DO n=1, dim_n_s
789  IF(ro_xs0(m,n) /= undefined) solve_ros(m) = .true.
790  IF(x_s0(m,n) /= undefined) solve_ros(m) = .true.
791  ENDDO
792 
793 
794 ! Verify that one -and only one- solids density model is in use.
795  IF(ro_s0(m) == undefined .AND. .NOT.solve_ros(m)) THEN
796  WRITE(err_msg, 1100) m
797  CALL flush_err_msg(abort=.true.)
798 
799  1100 FORMAT('Error 1101: No solids density information for phase ', &
800  i2,'.',/'Please correct the mfix.dat file.')
801 
802 ! Check if the constant solids phase density is physical.
803  ELSEIF(ro_s0(m) /= undefined .AND. solve_ros(m)) THEN
804  WRITE(err_msg, 1101) m
805  CALL flush_err_msg(abort=.true.)
806 
807  1101 FORMAT('Error 1101: Conflicting solids density input specified ',&
808  'for solids',/'phase ',i2,'. Constant solids density ', &
809  'specified (RO_s0) along with one',/'or more of the variable',&
810  ' solids density parameters:',/'RO_Xs0, X_s0, INERT_SPECIES.',&
811  /'Please correct the mfix.dat file.')
812 
813  ENDIF
814 
815 ! Check physical restrictions on variable solids density input.
816  IF(solve_ros(m)) THEN
817 ! Check INERT_SPECIES
818  IF(inert_species(m) == undefined_i) THEN
819  WRITE(err_msg,1000) trim(ivar('INERT_SPECIES',m))
820  CALL flush_err_msg(abort=.true.)
821  ELSEIF(inert_species(m) < 1 .OR. &
822  inert_species(m) > nmax(m)) THEN
823  WRITE(err_msg, 1001) trim(ivar('INERT_SPECIES',m)), &
824  trim(ival(inert_species(m)))
825  CALL flush_err_msg(abort=.true.)
826  ENDIF
827  IF(dil_inert_x_vsd(m)<=zero) THEN
828  WRITE(err_msg,1103) m, dil_inert_x_vsd(m)
829  CALL flush_err_msg(abort=.true.)
830  ELSEIF(dil_inert_x_vsd(m)>one) THEN
831  WRITE(err_msg,1104) m, dil_inert_x_vsd(m)
832  print*,'M,DIL_INERT_X_VSD(M)=',m,dil_inert_x_vsd(m)
833  CALL flush_err_msg(abort=.true.)
834  ENDIF
835  DO n=1, nmax(m)
836 ! Check RO_Xs0
837  IF(ro_xs0(m,n) == undefined) THEN
838  WRITE(err_msg,1000) trim(ivar('RO_Xs0',m,n))
839  CALL flush_err_msg(abort=.true.)
840  ELSEIF(ro_xs0(m,n) < zero) THEN
841  WRITE(err_msg,1001) trim(ivar('RO_Xs0',m,n)), &
842  trim(ival(ro_xs0(m,n)))
843  CALL flush_err_msg(abort=.true.)
844  ENDIF
845 ! Check X_s0
846  IF(x_s0(m,n) == undefined) THEN
847  WRITE(err_msg,1000) trim(ivar('X_s0',m,n))
848  CALL flush_err_msg(abort=.true.)
849  ELSEIF(x_s0(m,n) < zero .OR. x_s0(m,n) >= one) THEN
850  WRITE(err_msg,1001) trim(ivar('X_s0',m,n)), &
851  trim(ival(x_s0(m,n)))
852  CALL flush_err_msg(abort=.true.)
853  ENDIF
854  ENDDO
855 
856 ! Check for input overflow.
857  DO n=nmax(m)+1, dim_n_s
858  IF(ro_xs0(m,n) /= undefined) THEN
859  WRITE(err_msg,1002) trim(ivar('RO_Xs0',m,n))
860  CALL flush_err_msg(abort=.true.)
861  ENDIF
862  IF(x_s0(m,n) /= undefined) THEN
863  WRITE(err_msg,1002) trim(ivar('X_s0',m,n))
864  CALL flush_err_msg(abort=.true.)
865  ENDIF
866  ENDDO
867 
868 ! Check X_s0(Inert)
869  IF(x_s0(m,inert_species(m)) == zero) THEN
870  WRITE(err_msg,1102) m, inert_species(m)
871  CALL flush_err_msg(abort=.true.)
872  ENDIF
873 
874  1102 FORMAT('Error 1102: Invalid baseline inert species mass',/ &
875  'fraction. The inert species mass fraction must be greater ', &
876  'than zero.',/' Phase ',i2,' Inert Species: ',i3,' X_s0 = 0.0')
877 
878  1103 FORMAT('Error 1103: Invalid dilute region inert species mass',/ &
879  'fraction. The inert species mass fraction must be greater ', &
880  'than zero.',/' Phase ',i2,/ &
881  ' Please check the value of DIL_INERT_X_VSD:',g14.4)
882 
883  1104 FORMAT('Error 1104: Invalid dilute region inert species mass',/ &
884  'fraction. The inert species mass fraction must be less ', &
885  'than or equal to one.',/' Phase ',i2,/ &
886  ' Please check the value of DIL_INERT_X_VSD:',g14.4)
887 
888 ! All of the information for variable solids density has been verified
889 ! as of this point. Calculate and store the baseline density.
890  ro_s0(m) = eoss0(m)
891 
892 ! Check physical restrictions on constant solids density input.
893  ELSEIF(ro_s0(m) <= zero) THEN
894  WRITE(err_msg,1101) ivar('RO_s0',m), ival(ro_s0(m))
895  CALL flush_err_msg(abort=.true.)
896  ENDIF
897 
898  ENDDO
899 
900 ! Check for input overflow.
901  DO m = mmax_ll+1, dim_m
902  IF(ro_s0(m) /= undefined) THEN
903  WRITE(err_msg,1002) trim(ivar('RO_s0',m))
904  CALL flush_err_msg(abort=.true.)
905  ENDIF
906  IF(inert_species(m) /= undefined_i) THEN
907  WRITE(err_msg,1002) trim(ivar('INERT_SPECIES',m))
908  CALL flush_err_msg(abort=.true.)
909  ENDIF
910  DO n=1, dim_n_s
911  IF(ro_xs0(m,n) /= undefined) THEN
912  WRITE(err_msg,1002) trim(ivar('RO_Xs0',m,n))
913  CALL flush_err_msg(abort=.true.)
914  ENDIF
915  IF(x_s0(m,n) /= undefined) THEN
916  WRITE(err_msg,1002) trim(ivar('X_s0',m,n))
917  CALL flush_err_msg(abort=.true.)
918  ENDIF
919  ENDDO
920  ENDDO
921 
922 ! Finalize the error messges
923  CALL finl_err_msg
924 
925  RETURN
926 
927  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
928  'correct the mfix.dat file.')
929 
930  1001 FORMAT('Error 1001: Illegal or unphysical input: ',a,' = ',a,/ &
931  'Please correct the mfix.dat file.')
932 
933  1002 FORMAT('Error 1002: Illegal input: ',a,' specified out of range.',&
934  'Please correct the mfix.dat file.')
935 
936  END SUBROUTINE check_solids_density
double precision, dimension(dim_m) c_ps0
Definition: physprop_mod.f:83
character(len=18), dimension(dim_m, dim_n_s) species_s
Definition: rxns_mod.f:51
double precision, dimension(dim_m) d_p0
Definition: physprop_mod.f:25
character(len=32) function ivar(VAR, i1, i2, i3)
subroutine finl_err_msg
logical shear
Definition: run_mod.f:175
double precision, parameter one
Definition: param1_mod.f:29
double precision, dimension(dim_m) dif_s0
Definition: physprop_mod.f:113
Definition: rxns_mod.f:1
logical, dimension(0:dim_m) species_eq
Definition: run_mod.f:115
logical subgrid_wall
Definition: run_mod.f:131
logical friction
Definition: run_mod.f:149
integer, parameter dim_m
Definition: param_mod.f:67
logical, dimension(dim_m) solve_ros
Definition: run_mod.f:250
double precision, dimension(dim_m, dim_n_s) x_s0
Definition: physprop_mod.f:32
double precision, parameter undefined
Definition: param1_mod.f:18
double precision, dimension(dim_m, dim_n_s) ro_xs0
Definition: physprop_mod.f:35
double precision function eoss0(M)
Definition: eos_mod.f:74
subroutine init_err_msg(CALLER)
subroutine check_solids_common_all
logical use_rrates
Definition: rxns_mod.f:21
subroutine check_solids_species(MMAX_LL)
integer mmax
Definition: physprop_mod.f:19
integer, dimension(dim_m) inert_species
Definition: physprop_mod.f:39
Definition: eos_mod.f:10
subroutine check_solids_species_legacy(MMAX_LL)
double precision, dimension(dim_m) k_s0
Definition: physprop_mod.f:95
Definition: mms_mod.f:12
double precision filter_size_ratio
Definition: run_mod.f:133
double precision, dimension(dim_m) dil_inert_x_vsd
Definition: physprop_mod.f:43
double precision phip
Definition: constant_mod.f:79
Definition: run_mod.f:13
logical, dimension(0:dim_m, dim_n_g) rdatabase
Definition: rxns_mod.f:14
Definition: param_mod.f:2
logical cartesian_grid
Definition: cutcell_mod.f:13
logical database_read
Definition: physprop_mod.f:133
logical blending_stress
Definition: run_mod.f:161
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
logical k_epsilon
Definition: run_mod.f:97
logical reinitializing
Definition: run_mod.f:208
logical energy_eq
Definition: run_mod.f:100
logical use_mms
Definition: mms_mod.f:15
double precision, dimension(dim_m, dim_n_s) mw_s
Definition: physprop_mod.f:127
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
integer, parameter dim_n_s
Definition: param_mod.f:71
integer smax
Definition: physprop_mod.f:22
logical mppic
Definition: mfix_pic_mod.f:14
double precision, dimension(dim_m) ro_s0
Definition: physprop_mod.f:28
subroutine read_database(lM, lN, lName, lMW)
Definition: read_database.f:22
double precision, dimension(dim_m) mu_s0
Definition: physprop_mod.f:53
logical granular_energy
Definition: run_mod.f:112
subroutine check_solids_density(MMAX_LL)
integer, dimension(dim_m) nmax_s
Definition: physprop_mod.f:121
double precision, parameter zero
Definition: param1_mod.f:27
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
subroutine check_solids_drag
character, parameter undefined_c
Definition: param1_mod.f:20
subroutine check_subgrid_model