File: /nfs/home/0/users/jenkins/mfix.git/model/init_namelist.f

1     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2     !                                                                      !
3     !  Subroutine: INIT_NAMELIST                                           !
4     !  Purpose: initialize the NAMELIST variables                          !
5     !                                                                      !
6     !  Author: P. Nicoletti                               Date: 26-NOV-91  !
7     !                                                                      !
8     !  Keyword Documentation Format:                                       !
9     !                                                                      !
10     !<keyword category="category name" required="true"/FALSE               !
11     !                                    legacy=TRUE/FALSE>                !
12     !  <description></description>                                         !
13     !  <arg index="" id="" max="" min=""/>                                 !
14     !  <dependent keyword="" value="DEFINED"/>                             !
15     !  <conflict keyword="" value="DEFINED"/>                              !
16     !  <valid value="" note="" alias=""/>                                  !
17     !  <range min="" max="" />                                             !
18     !  MFIX_KEYWORD=INIT_VALUE                                             !
19     !</keyword>                                                            !
20     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
21     
22           SUBROUTINE INIT_NAMELIST
23     
24     !-----------------------------------------------
25     ! Modules
26     !-----------------------------------------------
27           USE param
28           USE param1
29           USE run
30           USE output
31           USE physprop
32           USE geometry
33           USE ic
34           USE bc
35           USE ps
36           USE fldvar
37           USE constant
38           USE indices
39           USE is
40           USE toleranc
41           USE scales
42           USE ur_facs
43           USE leqsol
44           USE residual
45           USE rxns
46           USE scalars
47           USE compar
48           USE parallel
49           USE cdist
50           USE stiff_chem
51           IMPLICIT NONE
52     !-----------------------------------------------
53     ! Local variables
54     !-----------------------------------------------
55     ! loop counters
56           INTEGER :: LC, LCM, M, N
57     ! Coefficient of restitution (old symbol)
58           DOUBLE PRECISION :: E
59     !-----------------------------------------------
60     ! Include statement functions
61     !-----------------------------------------------
62           INCLUDE 'namelist.inc'
63     
64     
65     
66     
67     !#####################################################################!
68     !                             Run Control                             !
69     !#####################################################################!
70     
71     
72     
73     !<keyword category="Run Control" required="true">
74     !  <description> Name used to create output files. The name should
75     !    generate legal file names after appending extensions.
76     !    Ex: Given the input, RUN_NAME = "bub01", MFIX will generate
77     !    the output files: BUB01.LOG, BUB01.OUT, BUB01.RES, etc.
78     !  </description>
79           RUN_NAME = UNDEFINED_C
80     !</keyword>
81     
82     !<keyword category="Run Control" required="false">
83     !  <description>Problem description. Limited to 60 characters.</description>
84           DESCRIPTION = UNDEFINED_C
85     !</keyword>
86     
87     !<keyword category="Run Control" required="true">
88     !  <description> Simulation input/output units.</description>
89     !  <valid value="cgs" note="All input and output in CGS units (g, cm, s, cal)."/>
90     !  <valid value="si" note="All input and output in SI units (kg, m, s, J)."/>
91           UNITS = UNDEFINED_C
92     !</keyword>
93     
94     !<keyword category="Run Control" required="true">
95     !  <description>Type of run.</description>
96     !  <valid value="new" note="A new run. There should be no .RES, .SPx,
97     !    .OUT, or .LOG files in the run directory."/>
98     !  <valid value="RESTART_1" note="Traditional restart. The run continues
99     !    from the last time the .RES file was updated and new data is added
100     !    to the SPx files."/>
101     !  <valid value="RESTART_2"
102     !    note="Start a new run with initial conditions from a .RES file
103     !      created from another run. No other data files (SPx) should be
104     !      in the run directory."/>
105           RUN_TYPE = UNDEFINED_C
106     !</keyword>
107     
108     !<keyword category="Run Control" required="false">
109     !  <description>
110     !    Simulation start time. This is typically zero.
111     !  </description>
112     !  <range min="0.0" max="+Inf" />
113           TIME = UNDEFINED
114     !</keyword>
115     
116     !<keyword category="Run Control" required="false">
117     !  <description>
118     !    Simulation stop time.
119     !  </description>
120     !  <range min="0.0" max="+Inf" />
121           TSTOP = UNDEFINED
122     !</keyword>
123     
124     !<keyword category="Run Control" required="false">
125     !  <description>
126     !    Initial time step size. If left undefined, a steady-state
127     !    calculation is performed.
128     !  </description>
129     !  <dependent keyword="TIME" value="DEFINED"/>
130     !  <dependent keyword="TSTOP" value="DEFINED"/>
131     !  <range min="0.0" max="+Inf" />
132           DT = UNDEFINED
133     !</keyword>
134     
135     !<keyword category="Run Control" required="false">
136     !  <description>Maximum time step size.</description>
137     !  <dependent keyword="TIME" value="DEFINED"/>
138     !  <dependent keyword="TSTOP" value="DEFINED"/>
139     !  <range min="0.0" max="+Inf" />
140           DT_MAX = ONE
141     !</keyword>
142     
143     !<keyword category="Run Control" required="false">
144     !  <description>Minimum time step size.</description>
145     !  <dependent keyword="TIME" value="DEFINED"/>
146     !  <dependent keyword="TSTOP" value="DEFINED"/>
147     !  <range min="0.0" max="+Inf" />
148           DT_MIN = 1.0D-6
149     !</keyword>
150     
151     !<keyword category="Run Control" required="false">
152     !  <description>
153     !    Factor for adjusting time step.
154     !    * The value must be less than or equal to 1.0.
155     !    * A value of 1.0 keeps the time step constant which may help overcome
156     !      initial non-convergence.
157     !  </description>
158     !  <dependent keyword="TIME" value="DEFINED"/>
159     !  <dependent keyword="TSTOP" value="DEFINED"/>
160     !  <range min="0.0" max="1" />
161           DT_FAC = 0.9D0
162     !</keyword>
163     
164     !<keyword category="Run Control" required="false">
165     !  <description>
166     !    Flag to restart the code when DT < DT_MIN.
167     !  </description>
168           AUTO_RESTART = .FALSE.
169     !</keyword>
170     
171     !<keyword category="Run Control" required="false">
172     !  <description>
173     !    Flag to enable/disable solving the X-momentum equations.
174     !  </description>
175     !  <arg index="1" id="Phase" min="0" max="DIM_M"/>
176     !  <valid value=".TRUE." note="Solve X-momentum equations."/>
177     !  <valid value=".FALSE." note="The X velocity initial conditions
178     !   persist throughout the simulation."/>
179           MOMENTUM_X_EQ(:DIM_M) = .TRUE.
180     !</keyword>
181     
182     !<keyword category="Run Control" required="false">
183     !  <description>
184     !    Flag to enable/disable solving the Y-momentum equations.
185     ! </description>
186     !  <arg index="1" id="Phase" min="0" max="DIM_M"/>
187     !  <valid value=".TRUE." note="Solve Y-momentum equations."/>
188     !  <valid value=".FALSE." note="The Y velocity initial conditions
189     !   persist throughout the simulation."/>
190           MOMENTUM_Y_EQ(:DIM_M) = .TRUE.
191     !</keyword>
192     
193     !<keyword category="Run Control" required="false">
194     !  <description>
195     !    Flag to enable/disable solving the Z-momentum equations.
196     !  </description>
197     !  <arg index="1" id="Phase" min="0" max="DIM_M"/>
198     !  <valid value=".TRUE." note="Solve Z-momentum equations."/>
199     !  <valid value=".FALSE." note="The Z velocity initial conditions
200     !   persist throughout the simulation."/>
201           MOMENTUM_Z_EQ(:DIM_M) = .TRUE.
202     !</keyword>
203     
204     !<keyword category="Run Control" required="false">
205     !  <description>Solve energy equations.</description>
206     !  <valid value=".TRUE." note="Solve energy equations."/>
207     !  <valid value=".FALSE." note="Do not solve energy equations."/>
208           ENERGY_EQ = .TRUE.
209     !</keyword>
210     
211     !<keyword category="Run Control" required="false">
212     !  <description>Solve species transport equations.</description>
213     !  <arg index="1" id="Phase" min="0" max="DIM_M"/>
214     !  <valid value=".TRUE." note="Solve species equations."/>
215     !  <valid value=".FALSE." note="Do not solve species equations."/>
216           SPECIES_EQ(:DIM_M) = .TRUE.
217     !</keyword>
218     
219     !<keyword category="Run Control" required="false" tfm="true">
220     !  <description>Granular energy formulation selection.</description>
221     !  <valid value=".FALSE."
222     !    note="Use algebraic granular energy equation formulation."/>
223     !  <valid value=".TRUE."
224     !    note="Use granular energy transport equation (PDE) formulation."/>
225           GRANULAR_ENERGY = .FALSE.
226     !</keyword>
227     
228     !<keyword category="Run Control" required="false">
229     !  <description>
230     !    The K-Epsilon turbulence model (for single-phase flow).
231     !    o Numerical parameters (like under-relaxation) are the same as the
232     !      ones for SCALAR (index = 9).
233     !    o All walls must be defined (NSW, FSW or PSW) in order to use
234     !      standard wall functions. If a user does not specify a wall type,
235     !      the simulation will not contain the typical turbulent profile in
236     !      wall-bounded flows.
237     !  </description>
238     !  <dependent keyword="MU_GMAX" value="DEFINED"/>
239     !  <conflict keyword="L_SCALE0" value="DEFINED"/>
240     !  <valid value=".TRUE."  note="Enable the K-epsilon turbulent model
241     !    (for single-phase flow) using standard wall functions."/>
242     !  <valid value=".FALSE." note="Do not use K-epsilon turbulent model"/>
243           K_EPSILON = .FALSE.
244     !</keyword>
245     
246     !<keyword category="Run Control" required="false">
247     !  <description>
248     !    Value of turbulent length initialized. This may be overwritten
249     !    in specific regions with the keyword IC_L_SCALE.
250     !</description>
251     !  <dependent keyword="MU_GMAX" value="DEFINED"/>
252     !  <conflict keyword="K_EPSILON" value=".TRUE."/>
253           L_SCALE0 = ZERO
254     !</keyword>
255     
256     !<keyword category="Run Control" required="false">
257     !  <description>
258     !    Maximum value of the turbulent viscosity of the fluid, which
259     !    must be defined if any turbulence model is used.
260     !    A value MU_GMAX =1.E+03 is recommended. (see calc_mu_g.f)
261     !  </description>
262           MU_GMAX = UNDEFINED
263     !</keyword>
264     
265     !<keyword category="Run Control" required="false">
266     !  <description>
267     !     Available gas-solids drag models.
268     !     Note: The extension _PCF following the specified drag model
269     !     indicates that the polydisperse correction factor is available.
270     !     For PCF details see:
271     !     o Van der Hoef MA, Beetstra R, Kuipers JAM. (2005)
272     !       Journal of Fluid Mechanics.528:233-254.
273     !     o Beetstra, R., van der Hoef, M. A., Kuipers, J.A.M. (2007).
274     !       AIChE Journal, 53:489-501.
275     !     o Erratum (2007), AIChE Journal, Volume 53:3020
276     !  </description>
277     !
278     !  <valid value="SYAM_OBRIEN" note="Syamlal M, OBrien TJ (1988).
279     !   International Journal of Multiphase Flow 14:473-481.
280     !   Two additional parameters may be specified: DRAG_C1, DRAG_D1"/>
281     !
282     !  <valid value="GIDASPOW" note="Ding J, Gidaspow D (1990).
283     !   AIChE Journal 36:523-538"/>
284     !
285     !  <valid value="GIDASPOW_BLEND" note="Lathouwers D, Bellan J (2000).
286     !    Proceedings of the 2000 U.S. DOE
287     !        Hydrogen Program Review NREL/CP-570-28890."/>
288     !
289     !  <valid value="WEN_YU" note="Wen CY, Yu YH (1966).
290     !   Chemical Engineering Progress Symposium Series 62:100-111."/>
291     !
292     !  <valid value="KOCH_HILL" note="Hill RJ, Koch DL, Ladd JC (2001).
293     !   Journal of Fluid Mechanics, 448: 213-241. and 448:243-278."/>
294     !
295     !  <valid value="BVK" note="Beetstra, van der Hoef, Kuipers (2007).
296     !   Chemical Engineering Science 62:246-255"/>
297     !
298     !  <valid value="HYS" note="Yin, X, Sundaresan, S. (2009).
299     !   AIChE Journal 55:1352-1368
300     !   This model has a lubrication cutoff distance, LAM_HYS, that can be
301     !   specified."/>
302     !
303     !  <valid value="USER_DRAG" note="Invoke user-defined drag law. (usr_drag.f)"/>
304     !
305     !  <valid value="GIDASPOW_PCF" note="see GIDASPOW"/>
306     !  <valid value="GIDASPOW_BLEND_PCF" note="see GIDASPOW_BLEND"/>
307     !  <valid value="WEN_YU_PCF" note="see WEN_YU"/>
308     !  <valid value="KOCH_HILL_PCF" note="see KOCH_HILL"/>
309     !
310           DRAG_TYPE = 'SYAM_OBRIEN'
311     !</keyword>
312     
313     !<keyword category="Run Control" required="false">
314     !  <description>
315     !    Quantity for calibrating Syamlal-O'Brien drag correlation using Umf
316     !    data.  This is determined using the Umf spreadsheet.
317     !  </description>
318           DRAG_C1 = 0.8d0
319     !</keyword>
320     
321     !<keyword category="Run Control" required="false">
322     !  <description>
323     !    Quantity for calibrating Syamlal-O'Brien drag correlation using Umf
324     !    data.  This is determined using the Umf spreadsheet.
325     !  </description>
326           DRAG_D1 = 2.65d0
327     !</keyword>
328     
329     !<keyword category="Run Control" required="false">
330     !  <description>
331     !    The lubrication cutoff distance for HYS drag model.  In practice
332     !    this number should be on the order of the mean free path of the
333     !    gas for smooth particles, or the RMS roughness of a particle if
334     !    they are rough (if particle roughness is larger than the mean
335     !   free path).
336     !  </description>
337     !  <dependent keyword="DRAG_TYPE" value="HYS"/>
338           LAM_HYS = UNDEFINED
339     !</keyword>
340     
341     !<keyword category="Run Control" required="false" tfm="true">
342     !  <description>
343     !    Subgrid models.
344     !  </description>
345     !
346     !  <valid value="Igci" note="
347     !   Igci, Y., Pannala, S., Benyahia, S., and Sundaresan S. (2012).
348     !   Industrial & Engineering Chemistry Research, 2012, 51(4):2094-2103"/>
349     !
350     !  <valid value="Milioli" note="
351     !   Milioli, C.C., Milioli, F. E., Holloway, W., Agrawal, K. and
352     !   Sundaresan, S. (2013). AIChE Journal, 59:3265-3275."/>
353     !
354           SUBGRID_TYPE = UNDEFINED_C
355     !</keyword>
356     
357     !<keyword category="Run Control" required="false" tfm="true">
358     !  <description>
359     !    Ratio of filter size to computational cell size.
360     !  </description>
361           FILTER_SIZE_RATIO = 2.0D0
362     !</keyword>
363     
364     !<keyword category="Run Control" required="false" tfm="true">
365     !  <description>Flag for subgrid wall correction.</description>
366     !  <valid value=".FALSE." note="Do not include wall correction."/>
367     !  <valid value=".TRUE." note="Include subgrid wall correction."/>
368           SUBGRID_Wall = .FALSE.
369     !</keyword>
370     
371     !<keyword category="Run Control" required="false">
372     !  <description>
373     !    Shared gas-pressure formulation. See Syamlal, M. and Pannala, S.
374     !    "Multiphase continuum formulation for gas-solids reacting flows,"
375     !    chapter in Computational Gas-Solids Flows and Reacting Systems:
376     !    Theory, Methods and Practice, S. Pannala, M. Syamlal and T.J.
377     !    O'Brien (editors), IGI Global, Hershey, PA, 2011.
378     !  </description>
379     !  <valid value=".FALSE." note="Use Model A"/>
380     !  <valid value=".TRUE."  note="Use Model B. Bouillard, J.X.,
381     !    Lyczkowski, R.W., Folga, S., Gidaspow, D., Berry, G.F. (1989).
382     !    Canadian Journal of Chemical Engineering 67:218-229."/>
383           MODEL_B = .FALSE.
384     !</keyword>
385     
386     !<keyword category="Run Control" required="false">
387     !  <description> The number of user-defined scalar transport equations
388     !    to solve.
389     !  </description>
390     !  <range min="0" max="DIM_SCALAR" />
391           NScalar = 0
392     !</keyword>
393     
394     !<keyword category="Run Control" required="false">
395     !  <description>
396     !    The phase convecting the indexed scalar transport equation.
397     !  </description>
398     !  <arg index="1" id="Scalar Equation" min="0" max="DIM_SCALAR"/>
399     !  <range min="0" max="DIM_M" />
400           Phase4Scalar(:DIM_SCALAR) = UNDEFINED_I
401     !</keyword>
402     
403     
404     !#####################################################################!
405     !                           Physical Parameters                       !
406     !#####################################################################!
407     
408     
409     !<keyword category="Physical Parameters" required="false">
410     !  <description>Reference pressure. [0.0]</description>
411           P_REF = ZERO
412     !</keyword>
413     
414     !<keyword category="Physical Parameters" required="false">
415     !  <description>Scale factor for pressure. [1.0]</description>
416           P_SCALE = ONE
417     !</keyword>
418     
419     !<keyword category="Physical Parameters" required="false">
420     !  <description>Gravitational acceleration. [980.7 in CGS]</description>
421           GRAVITY = UNDEFINED
422     !</keyword>
423     
424     !<keyword category="Physical Parameters" required="false">
425     !  <description>
426     !    X-component of gravitational acceleration vector. By default, the
427     !    gravity force acts in the negative y-direction.
428     !  </description>
429           GRAVITY_X = ZERO
430     !</keyword>
431     
432     !<keyword category="Physical Parameters" required="false">
433     !  <description>
434     !    Y-component of gravitational acceleration vector. By default, the
435     !    gravity force acts in the negative y-direction.
436     !  </description>
437           GRAVITY_Y = ZERO
438     !</keyword>
439     
440     !<keyword category="Physical Parameters" required="false">
441     !  <description>
442     !    Z-component of gravitational acceleration vector. By default, the
443     !    gravity force acts in the negative y-direction.
444     !  </description>
445           GRAVITY_Z = ZERO
446     !</keyword>
447     
448     
449     
450     
451     
452     !#####################################################################!
453     !                          Numerical Parameters                       !
454     !#####################################################################!
455     
456     
457     
458     !<keyword category="Numerical Parameters" required="false">
459     !  <description>
460     !    Maximum number of iterations [500].
461     !  </description>
462           MAX_NIT = 500
463     !</keyword>
464     
465     !<keyword category="Numerical Parameters" required="false">
466     !  <description>
467     !    Factor to normalize the gas continuity equation residual. The
468     !    residual from the first iteration is used if NORM_G is left
469     !    undefined. NORM_G=0 invokes a normalization method based on the
470     !    dominant term in the continuity equation. This setting may speed up
471     !    calculations, especially near a steady state and incompressible
472     !    fluids. But, the number of iterations for the gas phase pressure
473     !    should be increased, LEQ_IT(1), to ensure mass balance
474     !  </description>
475           NORM_G = UNDEFINED
476     !</keyword>
477     
478     !<keyword category="Numerical Parameters" required="false">
479     !  <description>
480     !    Factor to normalize the solids continuity equation residual. The
481     !    residual from the first iteration is used if NORM_S is left
482     !    undefined. NORM_S = 0 invokes a normalization method based on the
483     !    dominant term in the continuity equation. This setting may speed up
484     !    calculations, especially near a steady state and incompressible
485     !    fluids. But, the number of iterations for the solids volume
486     !    fraction should be increased, LEQ_IT(2), to ensure mass balance.
487     !  </description>
488           NORM_S = UNDEFINED
489     !</keyword>
490     
491     !<keyword category="Numerical Parameters" required="false">
492     !  <description>
493     !    Maximum residual at convergence (Continuity + Momentum) [1.0d-3].
494     !  </description>
495           TOL_RESID = 1.0D-3
496     !</keyword>
497     
498     
499     !<keyword category="Numerical Parameters" required="false">
500     !  <description>
501     !    Maximum residual at convergence (Energy) [1.0d-4].
502     !  </description>
503           TOL_RESID_T = 1.0D-4
504     !</keyword>
505     
506     !<keyword category="Numerical Parameters" required="false">
507     !  <description>
508     !    Maximum residual at convergence (Species Balance) [1.0d-4].
509     !  </description>
510           TOL_RESID_X = 1.0D-4
511     !</keyword>
512     
513     !<keyword category="Numerical Parameters" required="false">
514     !  <description>
515     !    Maximum residual at convergence (Granular Energy) [1.0d-4].
516     !  </description>
517           TOL_RESID_Th = 1.0D-4
518     !</keyword>
519     
520     !<keyword category="Numerical Parameters" required="false">
521     !  <description>
522     !    Maximum residual at convergence (Scalar Equations) [1.0d-4].
523     !  </description>
524           TOL_RESID_Scalar = 1.0D-4
525     !</keyword>
526     
527     !<keyword category="Numerical Parameters" required="false">
528     !  <description>
529     !    Maximum residual at convergence (K_Epsilon Model) [1.0d-4].
530     !  </description>
531           TOL_RESID_K_Epsilon = 1.0D-4
532     !</keyword>
533     
534     !<keyword category="Numerical Parameters" required="false">
535     !  <description>
536     !    Minimum residual for declaring divergence [1.0d+4].
537     !    This parameter is useful for incompressible fluid simulations
538     !    because velocity residuals can take large values for the second
539     !    iteration (e.g., 1e+8) before dropping down to smaller values for
540     !    the third iteration.
541     !  </description>
542           TOL_DIVERGE = 1.0D+4
543     !</keyword>
544     
545     !<keyword category="Numerical Parameters" required="false">
546     !  <description>
547     !    Reduce the time step if the residuals stop decreasing. Disabling this
548     !    feature may help overcome initial non-convergence.
549     !  </description>
550     !  <valid value=".FALSE." note="Continue iterating if residuals stall."/>
551     !  <valid value=".TRUE."  note="Reduce time step if residuals stall."/>
552           DETECT_STALL = .TRUE.
553     !</keyword>
554     
555     
556     !<keyword category="Numerical Parameters" required="false">
557     !  <description>
558     !    LEQ Solver selection. BiCGSTAB is the default method for all
559     !    equation types.
560     !  </description>
561     !  <arg index="1" id="Equation ID Number" min="1" max="DIM_EQS"/>
562     !  <valid value="1" note="SOR - Successive over-relaxation"/>
563     !  <valid value="2" note="BiCGSTAB - Biconjugate gradient stabilized."/>
564     !  <valid value="3" note="GMRES - Generalized minimal residual method"/>
565     !  <valid value="5" note="CG - Conjugate gradient"/>
566           LEQ_METHOD(:) = 2
567     !</keyword>
568     
569     !<keyword category="Numerical Parameters" required="false">
570     !  <description>
571     !    Linear Equation tolerance [1.0d-4].
572     !  </description>
573     !  <arg index="1" id="Equation ID Number" min="1" max="DIM_EQS"/>
574     !  <dependent keyword="LEQ_METHOD" value="2"/>
575     !  <dependent keyword="LEQ_METHOD" value="3"/>
576           LEQ_TOL(:) = 1.0D-4
577     !</keyword>
578     
579     !<keyword category="Numerical Parameters" required="false">
580     !  <description>
581     !    Number of iterations in the linear equation solver.
582     !    o 20 iterations for equation types 1-2
583     !    o  5 iterations for equation types 3-5,10
584     !    o 15 iterations for equation types 6-9
585     !  </description>
586     !  <arg index="1" id="Equation ID Number" min="1" max="DIM_EQS"/>
587           LEQ_IT(1) =  20
588           LEQ_IT(2) =  20
589           LEQ_IT(3) =   5
590           LEQ_IT(4) =   5
591           LEQ_IT(5) =   5
592           LEQ_IT(6) =  15
593           LEQ_IT(7) =  15
594           LEQ_IT(8) =  15
595           LEQ_IT(9) =  15
596           LEQ_IT(10) =  5
597     !</keyword>
598     
599     !<keyword category="Numerical Parameters" required="false">
600     !  <description>
601     !    Linear equation sweep direction. This applies when using GMRES or
602     !    when using the LINE preconditioner with BiCGSTAB or CG methods.
603     !    'RSRS' is the default for all equation types.
604     !  </description>
605     !  <arg index="1" id="Equation ID Number" min="1" max="DIM_EQS"/>
606     !  <valid value="RSRS" note="(Red/Black Sweep, Send Receive) repeated twice"/>
607     !  <valid value="ISIS" note="(Sweep in I, Send Receive) repeated twice"/>
608     !  <valid value="JSJS" note="(Sweep in J, Send Receive) repeated twice"/>
609     !  <valid value="KSKS" note="(Sweep in K, Send Receive) repeated twice"/>
610     !  <valid value="ASAS" note="(All Sweep, Send Receive) repeated twice"/>
611           LEQ_SWEEP(:) = 'RSRS'
612     !</keyword>
613     
614     !<keyword category="Numerical Parameters" required="false">
615     !  <description>
616     !    Linear precondition used by the BiCGSTAB and CG LEQ solvers. 'LINE'
617     !    is the default for all equation types.
618     !  </description>
619     !  <arg index="1" id="Equation ID Number" min="1" max="DIM_EQS"/>
620     !  <valid value="NONE" note="No preconditioner"/>
621     !  <valid value="LINE" note="Line relaxation"/>
622     !  <valid value="DIAG" note="Diagonal Scaling"/>
623           LEQ_PC(:) = 'LINE'
624     !</keyword>
625     
626     
627     !<keyword category="Numerical Parameters" required="false">
628     !  <description>
629     !    Under relaxation factors.
630     !    o 0.8 for equation types 1,6,9
631     !    o 0.5 for equation types 2,3,4,5,8
632     !    o 1.0 for equation types 7
633     !  </description>
634     !  <arg index="1" id="Equation ID Number" min="1" max="DIM_EQS"/>
635           UR_FAC(1)  = 0.8D0     ! pressure
636           UR_FAC(2)  = 0.5D0     ! rho, ep
637           UR_FAC(3)  = 0.5D0     ! U
638           UR_FAC(4)  = 0.5D0     ! V
639           UR_FAC(5)  = 0.5D0     ! W
640           UR_FAC(6)  = 1.0D0     ! T
641           UR_FAC(7)  = 1.0D0     ! X
642           UR_FAC(8)  = 0.5D0     ! Th
643           UR_FAC(9)  = 0.8D0     ! Scalar
644           UR_FAC(10) = 1.0D0     ! DES Diffusion
645     !</keyword>
646     
647     !<keyword category="Numerical Parameters" required="false">
648     !  <description>
649     !    The implicitness calculation of the gas-solids drag coefficient
650     !    may be underrelaxed by changing ur_f_gs, which takes values
651     !    between 0 to 1.
652     !    o  0 updates F_GS every time step
653     !    o  1 updates F_GS every iteration
654     !  </description>
655     !  <range min="0" max="1" />
656           UR_F_gs = 1.0D0
657     !</keyword>
658     
659     !<keyword category="Numerical Parameters" required="false">
660     !  <description>
661     !    Under relaxation factor for conductivity coefficient associated
662     !    with other solids phases for IA Theory [1.0].
663     !  </description>
664           UR_Kth_sml = 1.0D0
665     !</keyword>
666     
667     !<keyword category="Numerical Parameters" required="false">
668     !  <description>Discretization scheme of equations.</description>
669     !  <arg index="1" id="Equation ID Number" min="1" max="DIM_EQS"/>
670     !  <valid value="0" note="First-order upwinding."/>
671     !  <valid value="1" note="First-order upwinding (using down-wind factors)."/>
672     !  <valid value="3" note="Smart."/>
673     !  <valid value="2" note="Superbee (recommended method)."/>
674     !  <valid value="5" note="QUICKEST (does not work)."/>
675     !  <valid value="4" note="ULTRA-QUICK."/>
676     !  <valid value="7" note="van Leer."/>
677     !  <valid value="6" note="MUSCL."/>
678     !  <valid value="8" note="minmod."/>
679           DISCRETIZE(:) = 0
680     !</keyword>
681     
682     !<keyword category="Numerical Parameters" required="false">
683     !  <description>
684     !    Use deferred correction method for implementing higher order
685     !    discretization.
686     !  </description>
687     !  <valid value=".FALSE." note="Use down-wind factor method (default)."/>
688     !  <valid value=".TRUE."  note="Use deferred correction method."/>
689           DEF_COR  =  .FALSE.
690     !</keyword>
691     
692     !<keyword category="Numerical Parameters" required="false">
693     !  <description>
694     !    This scheme guarantees that the set of differenced species mass
695     !    balance equations maintain the property that the sum of species
696     !    mass fractions sum to one. This property is not guaranteed when
697     !    a flux limiter is used with higher order spatial discretization
698     !    schemes. Note: The chi-scheme is implemented for SMART and MUSCL
699     !    discretization schemes.
700     !    Darwish, M.S., Moukalled, F. (2003). Computer Methods in Applied
701     !    Mech. Eng., 192(13):1711-1730.
702     !  </description>
703     !  <valid value=".FALSE." note="Do not use the chi-scheme."/>
704     !  <valid value=".TRUE."  note="Use the chi-scheme correction."/>
705           Chi_scheme = .FALSE.
706     !</keyword>
707     
708     !<keyword category="Numerical Parameters" required="false">
709     !  <description>
710     !    Four point fourth order interpolation and is upstream biased.
711     !    Notes:
712     !    o DISCRETIZE(*) defaults to Superbee if this scheme is chosen
713     !      and DISCRETIZE(*) < 2.
714     !    o Set C_FAC between 0 and 1 when using this scheme.
715     !  </description>
716     !  <dependent keyword="C_FAC" value="DEFINED"/>
717           FPFOI = .FALSE.
718     !</keyword>
719     
720     !<keyword category="Numerical Parameters" required="false">
721     !  <description>
722     !    Factor between zero and one used in the universal limiter when
723     !    using four point, fourth order interpolation (FPFOI).
724     !    o Choosing one gives (diffusive) first order upwinding.
725     !    o The scheme becomes more compressive as values near zero.
726     !  </description>
727     !  <range min="0.0" max="1.0" />
728     !  <dependent keyword="fpfoi" value=".TRUE."/>
729           C_FAC = UNDEFINED
730     !</keyword>
731     
732     !<keyword category="Numerical Parameters" required="false">
733     !  <description>Temporal discretization scheme.</description>
734     !  <valid value=".FALSE."
735     !    note="Implicit Euler based temporal discretization scheme employed
736     !      (first order accurate in time)."/>
737     !  <valid value=".TRUE."
738     !    note="Two-step implicit Runge-Kutta method based temporal
739     !      discretization scheme employed (second order accurate in time
740     !      excluding the pressure terms and restart time step which are
741     !      first order accurate)."/>
742           CN_ON = .FALSE.
743     !</keyword>
744     
745     !<keyword category="Numerical Parameters" required="false">
746     !  <description>
747     !    The code declares divergence if the velocity anywhere in the domain
748     !    exceeds a maximum value.  This maximum value is automatically
749     !    determined from the boundary values. The user may scale the maximum
750     !    value by adjusting this scale factor [1.0d0].
751     !  </description>
752           MAX_INLET_VEL_FAC = ONE
753     !</keyword>
754     
755     !<keyword category="Numerical Parameters" required="false">
756     !  <description>
757     !    Solve transpose of linear system. (BICGSTAB ONLY).
758     !  </description>
759     !  <dependent keyword="LEQ_METHOD" value="2"/>
760           DO_TRANSPOSE = .FALSE.
761     !</keyword>
762     
763     !<keyword category="Numerical Parameters" required="false">
764     !  <description>
765     !    Frequency to check for convergence. (BICGSTAB ONLY)
766     !  </description>
767     !  <dependent keyword="LEQ_METHOD" value="2"/>
768           icheck_bicgs = 1
769     !</keyword>
770     
771     !<keyword category="Numerical Parameters" required="false">
772     !  <description>
773     !    Sets optimal LEQ flags for parallel runs.
774     !  </description>
775           OPT_PARALLEL = .FALSE.
776     !</keyword>
777     
778     !<keyword category="Numerical Parameters" required="false">
779     !  <description>
780     !    Use do-loop assignment over direct vector assignment.
781     !  </description>
782           USE_DOLOOP = .FALSE.
783     !</keyword>
784     
785     !<keyword category="Numerical Parameters" required="false">
786     !  <description>
787     !    Calculate dot-products more efficiently (Serial runs only.)
788     !  </description>
789           IS_SERIAL = .TRUE.
790     !</keyword>
791     
792     
793     !#####################################################################!
794     !                      Geometry and Discretization                    !
795     !#####################################################################!
796     
797     
798     !<keyword category="Geometry and Discretization" required="false">
799     !  <description>Coordinates used in the simulation.</description>
800     !  <valid value="cartesian" note="Cartesian coordinates."/>
801     !  <valid value="cylindrical" note="Cylindrical coordinates."/>
802           COORDINATES = UNDEFINED_C
803     !</keyword>
804     
805     !<keyword category="Geometry and Discretization" required="false">
806     !  <description>(Do not use.)</description>
807     !  <valid value=".FALSE." note="x (r) direction is considered."/>
808     !  <valid value=".TRUE." note="x (r) direction is not considered."/>
809     !     NO_I = .FALSE.
810     !</keyword>
811     
812     !<keyword category="Geometry and Discretization" required="false">
813     !  <description>Number of cells in the x (r) direction.</description>
814           IMAX = UNDEFINED_I
815     !</keyword>
816     
817     !<keyword category="Geometry and Discretization" required="false">
818     !  <description>
819     !    Cell sizes in the x (r) direction. Enter values from DX(0) to
820     !    DX(IMAX-1). 
821     !    o Use uniform mesh size with higher-order discretization methods.
822     !    o DX should be kept uniform in cylindrical coordinates
823     !      for strict momentum conservation.
824     !  </description>
825     !  <arg index="1" id="Cell" min="0" max="DIM_I"/>
826           DX(:DIM_I) = UNDEFINED
827     !</keyword>
828     
829     !<keyword category="Geometry and Discretization" required="false">
830     !  <description>
831     !    The inner radius in the simulation of an annular cylindrical region.
832     !  </description>
833           XMIN = ZERO
834     !</keyword>
835     
836     !<keyword category="Geometry and Discretization" required="false">
837     !  <description>Reactor length in the x (r) direction.</description>
838           XLENGTH = UNDEFINED
839     !</keyword>
840     
841     !<keyword category="Geometry and Discretization" required="false">
842     !  <description>(Do not use.)</description>
843     !  <valid value=".FALSE. note="y-direction is considered."/>
844     !  <valid value=".TRUE." note="y-direction is not considered."/>
845     !     NO_J = .FALSE.
846     !</keyword>
847     
848     
849     !<keyword category="Geometry and Discretization" required="false">
850     !  <description>Number of cells in the y-direction.</description>
851           JMAX = UNDEFINED_I
852     !</keyword>
853     
854     !<keyword category="Geometry and Discretization" required="false">
855     !  <description>
856     !    Cell sizes in the y-direction. Enter values from DY(0) to
857     !    DY(IMAX-1). Use uniform mesh size with second-order
858     !    discretization methods.
859     !  </description>
860     !  <arg index="1" id="Cell" min="0" max="DIM_J"/>
861           DY(:DIM_J) = UNDEFINED
862     !</keyword>
863     
864     !<keyword category="Geometry and Discretization" required="false">
865     !  <description>Reactor length in the y-direction.</description>
866           YLENGTH = UNDEFINED
867     !</keyword>
868     
869     !<keyword category="Geometry and Discretization" required="false">
870     !  <description>
871     !    Flag to disable the third dimension (i.e., 2D simulation).
872     !      o Z axis in Cartesian coordinate system
873     !      o Theta in Cylindrical coordinate system
874     !  </description>
875     !  <valid value=".FALSE." note="3D simulation."/>
876     !  <valid value=".TRUE."  note="2D simulation."/>
877           NO_K = .FALSE.
878     !</keyword>
879     
880     !<keyword category="Geometry and Discretization" required="false">
881     !  <description>Number of cells in the z-direction.</description>
882           KMAX = UNDEFINED_I
883     !</keyword>
884     
885     !<keyword category="Geometry and Discretization" required="false">
886     !  <description>
887     !    Cell sizes in the z (theta) direction. Enter values from DZ(0) to
888     !    DZ(IMAX-1). Use uniform mesh size with second-order discretization
889     !    methods.
890     !  </description>
891     !  <arg index="1" id="Cell" min="0" max="DIM_K"/>
892           DZ(:DIM_K) = UNDEFINED
893     !</keyword>
894     
895     !<keyword category="Geometry and Discretization" required="false">
896     !  <description>Reactor length in the z (theta) direction.</description>
897           ZLENGTH = UNDEFINED
898     !</keyword>
899     
900     
901     !<keyword category="Geometry and Discretization" required="false">
902     !  <description>
903     !    Flag for making the x-direction cyclic without pressure drop. No other
904     !    boundary conditions for the x-direction should be specified.
905     !</description>
906     !  <valid value=".FALSE." note="No cyclic condition at x-boundary."/>
907     !  <valid value=".TRUE." note="Cyclic condition at x-boundary."/>
908           CYCLIC_X = .FALSE.
909     !</keyword>
910     
911     !<keyword category="Geometry and Discretization" required="false">
912     !  <description>
913     !    Flag for making the x-direction cyclic with pressure drop. If the
914     !    keyword FLUX_G is given a value this becomes a cyclic boundary
915     !    condition with specified mass flux. No other boundary conditions
916     !    for the x-direction should be specified.
917     !  </description>
918     !  <valid value=".FALSE." note="No cyclic condition at x-boundary."/>
919     !  <valid value=".TRUE." note="Cyclic condition with pressure drop at x-boundary."/>
920           CYCLIC_X_PD = .FALSE.
921     !</keyword>
922     
923     !<keyword category="Geometry and Discretization" required="false">
924     !  <description>
925     !    Fluid pressure drop across XLENGTH when a cyclic boundary condition
926     !    with pressure drop is imposed in the x-direction.
927     !  </description>
928           DELP_X = UNDEFINED
929     !</keyword>
930     
931     !<keyword category="Geometry and Discretization" required="false">
932     !  <description>
933     !    Flag for making the y-direction cyclic without pressure drop. No
934     !    other boundary conditions for the y-direction should be specified.
935     !  </description>
936     !  <valid value=".FALSE." note="No cyclic condition at y-boundary."/>
937     !  <valid value=".TRUE." note="Cyclic condition at x-boundary."/>
938           CYCLIC_Y = .FALSE.
939     !</keyword>
940     
941     !<keyword category="Geometry and Discretization" required="false">
942     !  <description>
943     !    Flag for making the y-direction cyclic with pressure drop. If the
944     !    keyword FLUX_G is given a value this becomes a cyclic boundary
945     !    condition with specified mass flux. No other boundary conditions
946     !    for the y-direction should be specified.
947     !  </description>
948     !  <valid value=".FALSE." note="No cyclic condition at y-boundary."/>
949     !  <valid value=".TRUE." note="Cyclic condition with pressure drop at y-boundary."/>
950           CYCLIC_Y_PD = .FALSE.
951     !</keyword>
952     
953     !<keyword category="Geometry and Discretization" required="false">
954     !  <description>
955     !    Fluid pressure drop across YLENGTH when a cyclic boundary condition
956     !    with pressure drop is imposed in the y-direction.
957     !  </description>
958           DELP_Y = UNDEFINED
959     !</keyword>
960     
961     !<keyword category="Geometry and Discretization" required="false">
962     !  <description>
963     !    Flag for making the z-direction cyclic without pressure drop. No
964     !    other boundary conditions for the z-direction should be specified.
965     !  </description>
966     !  <valid value=".FALSE." note="No cyclic condition at z-boundary."/>
967     !  <valid value=".TRUE." note="Cyclic condition at z-boundary."/>
968           CYCLIC_Z = .FALSE.
969     !</keyword>
970     
971     !<keyword category="Geometry and Discretization" required="false">
972     !  <description>
973     !    Flag for making the z-direction cyclic with pressure drop. If the
974     !    keyword FLUX_G is given a value this becomes a cyclic boundary
975     !    condition with specified mass flux. No other boundary conditions
976     !    for the z-direction should be specified.
977     !  </description>
978     !  <valid value=".FALSE." note="No cyclic condition at z-boundary."/>
979     !  <valid value=".TRUE." note="Cyclic condition with pressure drop at
980     !    z-boundary."/>
981           CYCLIC_Z_PD = .FALSE.
982     !</keyword>
983     
984     !<keyword category="Geometry and Discretization" required="false">
985     !  <description>
986     !    Fluid pressure drop across ZLENGTH when a cyclic boundary condition
987     !    with pressure drop is imposed in the z-direction.
988     !  </description>
989           DELP_Z = UNDEFINED
990     !</keyword>
991     
992     !<keyword category="Geometry and Discretization" required="false">
993     !  <description>
994     !    Imposes a mean shear on the flow field as a linear function of the
995     !    x coordinate. This feature should only be used when CYCLIC_X is
996     !    .TRUE. and the keyword V_SH is set.
997     !  </description>
998     !  <dependent keyword="CYCLIC_X" value=".TRUE."/>
999     !  <dependent keyword="V_SH" value="DEFINED"/>
1000           SHEAR = .FALSE.
1001     !</keyword>
1002     
1003     
1004     !<keyword category="Geometry and Discretization" required="false">
1005     !  <description>
1006     !    Specifies the mean y velocity component at the eastern boundary
1007     !    of the domain (V_SH), and the mean Y velocity (-V_SH) at the
1008     !    western boundary of the domain.
1009     !  </description>
1010           V_sh = 0.0d0
1011     !</keyword>
1012     
1013     
1014     !<keyword category="Geometry and Discretization" required="false">
1015     !  <description>
1016     !    If a value is specified (in units of g/cm^2.s), the domain-averaged gas
1017     !    flux is held constant at that value in simulations over a periodic
1018     !    domain.  A pair of boundaries specified as periodic with fixed
1019     !    pressure drop is then treated as periodic with fixed mass flux.
1020     !    Even for this case a pressure drop must also be specified, which
1021     !    is used as the initial guess in the simulations.
1022     !  </description>
1023           Flux_g = UNDEFINED
1024     !</keyword>
1025     
1026     !<keyword category="Geometry and Discretization" required="false">
1027     !  <description>
1028     !    Applies the 2.5D model for cylindrical column by combining 2D assumption
1029     !    and axi-symmetric assumption.
1030     !    Li et al. (2015). A 2.5D computational method to simulate 
1031     !    cylindrical fluidized beds, Chemical Engineering Science,
1032     !    123:236-246.
1033     !  </description>
1034           CYLINDRICAL_2D = .FALSE.
1035     !</keyword>
1036     
1037     !<keyword category="Geometry and Discretization" required="false">
1038     !  <description>
1039     !    Parameter to control the plate half width and the wedge radius
1040     !    in the 2.5D cylindrical model. This value should be less than
1041     !    half the grid cells in the radial direction (IMAX/2).  [1]
1042     !  </description>
1043     !  <dependent keyword="CYLINDRICAL_2D" value=".TRUE."/>
1044           I_CYL_NUM = 1
1045     !</keyword>
1046     
1047     !<keyword category="Geometry and Discretization" required="false">
1048     !  <description>
1049     !    Parameter to smooth the transition from cylindrical to 2D in
1050     !    the 2.5D cylindrical model. [2]
1051     !  </description>
1052     !  <valid value="2" note="Two cell smoothing transition."/>
1053     !  <valid value="1" note="One cell smoothing transition."/>
1054     !  <valid value="0" note="No smoothing."/>
1055     !  <dependent keyword="CYLINDRICAL_2D" value=".TRUE."/>
1056           I_CYL_TRANSITION = 2
1057     !</keyword>
1058     
1059     !#####################################################################!
1060     !                               Gas Phase                             !
1061     !#####################################################################!
1062     
1063     !<keyword category="Gas Phase" required="false">
1064     !  <description>
1065     !    Specified constant gas density [g/cm^3 in CGS]. An equation of
1066     !    state -the ideal gas law by default- is used to calculate the gas
1067     !    density if this parameter is undefined. The value may be set to
1068     !    zero to make the drag zero and to simulate granular flow in a
1069     !    vacuum. For this case, users may turn off solving for gas momentum
1070     !    equations to accelerate convergence.
1071     !  </description>
1072           RO_G0 = UNDEFINED
1073     !</keyword>
1074     
1075     !<keyword category="Gas Phase" required="false">
1076     !  <description>
1077     !    Specified constant gas viscosity [g/(cm.s) in CGS].
1078     !  </description>
1079           MU_G0 = UNDEFINED
1080     !</keyword>
1081     
1082     !<keyword category="Gas Phase" required="false">
1083     !  <description>
1084     !    Specified constant gas conductivity [cal/(s.cm.K) in CGS].
1085     !  </description>
1086           K_G0 = UNDEFINED
1087     !</keyword>
1088     
1089     !<keyword category="Gas Phase" required="false">
1090     !  <description>
1091     !    Specified constant gas specific heat [cal/(g.s.K) in CGS].
1092     !  </description>
1093           C_PG0 = UNDEFINED
1094     !</keyword>
1095     
1096     !<keyword category="Gas Phase" required="false">
1097     !  <description>
1098     !    Specified constant gas diffusivity [(cm^2/s) in CGS].
1099     !  </description>
1100           DIF_G0 = UNDEFINED
1101     !</keyword>
1102     
1103     !<keyword category="Gas Phase" required="false">
1104     !  <description>
1105     !    Average molecular weight of gas [(g/mol) in CGS]. Used in 
1106     !    calculating the gas density for non-reacting flows when the gas
1107     !    composition is not defined.
1108     !  </description>
1109           MW_AVG = UNDEFINED
1110     !</keyword>
1111     
1112     !<keyword category="Gas Phase" required="false">
1113     !  <description>
1114     !    Molecular weight of gas species [(g/mol) in GCS].
1115     !  </description>
1116     !  <arg index="1" id="Species" min="1" max="DIM_N_G"/>
1117           MW_G(:DIM_N_G) = UNDEFINED
1118     !</keyword>
1119     
1120     !<keyword category="Gas Phase" required="false">
1121     !  <description>Number of species comprising the gas phase.</description>
1122           NMAX_g = UNDEFINED_I
1123     !</keyword>
1124     
1125     !<keyword category="Gas Phase" required="false">
1126     !  <description>
1127     !    Name of gas phase species as it appears in the materials database.
1128     !  </description>
1129     !  <arg index="1" id="Species" min="1" max="DIM_N_G"/>
1130           SPECIES_g = UNDEFINED_C
1131     !</keyword>
1132     
1133     !<keyword category="Gas Phase" required="false">
1134     !  <description>
1135     !    User defined name for gas phase species. Aliases are used in
1136     !    specifying chemical equations and must be unique.
1137     !  </description>
1138     !  <arg index="1" id="Species" min="1" max="DIM_N_G"/>
1139           SPECIES_ALIAS_g = UNDEFINED_C
1140     !</keyword>
1141     
1142     
1143     
1144     !#####################################################################!
1145     !                            Solids Phase                             !
1146     !#####################################################################!
1147     
1148     !<keyword category="Solids Phase" required="false">
1149     !  <description>
1150     !    Defines the model used for the solids phase. For TFM/DEM
1151     !    hybrid simulations, first define all TFM solids, then
1152     !    define the DEM solids phases.
1153     !  </description>
1154     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1155     !  <valid value='TFM' note='Two-fluid Model (continuum)' />
1156     !  <valid value='DEM' note='Discrete Element Model' />
1157     !  <valid value='PIC' note='Multiphase-Particle in Cell' />
1158           SOLIDS_MODEL(:DIM_M) = 'TFM'
1159     !</keyword>
1160     
1161     !<keyword category="Solids Phase" required="false"
1162     !  tfm="true" dem="true" pic="true">
1163     !  <description>Number of solids phases.</description>
1164           MMAX = 1
1165     !</keyword>
1166     
1167     !<keyword category="Solids Phase" required="false"
1168     !  tfm="true" dem="true" pic="true">
1169     !  <description>
1170     !    Initial particle diameters [cm in CGS].
1171     !  </description>
1172     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1173           D_P0(:DIM_M) = UNDEFINED
1174     !</keyword>
1175     
1176     !<keyword category="Solids Phase" required="false"
1177     !  tfm="true" dem="true" pic="true">
1178     !  <description>
1179     !    Specified constant solids density [g/cm^3 in CGS]. Reacting flows
1180     !    may use variable solids density by leaving this parameter
1181     !    undefined and specifying X_S0 and RO_XS0 as well as the index
1182     !    of the inert species.
1183     !  </description>
1184     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1185           RO_S0(:DIM_M) = UNDEFINED
1186     !</keyword>
1187     
1188     !<keyword category="Solids Phase" required="false" tfm="true" dem="true">
1189     !  <description>
1190     !    Baseline species mass fraction. Specifically, the mass fraction
1191     !    of an unreacted sample (e.g., proximate analysis).
1192     !  </description>
1193     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1194     !  <arg index="2" id="Species" min="1" max="DIM_N_s"/>
1195     !  <dependent keyword="SPECIES_EQ" value=".TRUE."/>
1196     !  <dependent keyword="RO_Xs0" value="DEFINED"/>
1197     !  <dependent keyword="INERT_SPECIES" value="DEFINED"/>
1198     !  <conflict keyword="RO_s0" value="DEFINED"/>
1199           X_s0(:DIM_M,:DIM_N_s) = UNDEFINED
1200     !</keyword>
1201     
1202     !<keyword category="Solids Phase" required="false" tfm="true" dem="true">
1203     !  <description>
1204     !    Specified constant solids species density [g/cm^3 in CGS].
1205     !  </description>
1206     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1207     !  <arg index="2" id="Species" min="1" max="DIM_N_s"/>
1208     !  <dependent keyword="SPECIES_EQ" value=".TRUE."/>
1209     !  <dependent keyword="X_s0" value="DEFINED"/>
1210     !  <dependent keyword="INERT_SPECIES" value="DEFINED"/>
1211     !  <conflict keyword="RO_s0" value="DEFINED"/>
1212           RO_Xs0(:DIM_M,:DIM_N_s) = UNDEFINED
1213     !</keyword>
1214     
1215     !<keyword category="Solids Phase" required="false" tfm="true" dem="true">
1216     !  <description>
1217     !    Index of inert solids phase species. This species should not be a
1218     !    product or reactant of any chemical reaction.
1219     !  </description>
1220     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1221     !  <arg index="2" id="Species" min="1" max="DIM_N_s"/>
1222     !  <dependent keyword="SPECIES_EQ" value=".TRUE."/>
1223     !  <dependent keyword="X_s0" value="DEFINED"/>
1224     !  <dependent keyword="RO_Xs0" value="DEFINED"/>
1225     !  <conflict keyword="RO_s0" value="DEFINED"/>
1226           INERT_SPECIES(:DIM_M) = UNDEFINED_I
1227     !</keyword>
1228     
1229     
1230     !<keyword category="Solids Phase" required="false" tfm="true" dem="true">
1231     !  <description>
1232     !    Specified constant solids conductivity [cal/(s.cm.K) in CGS].
1233     !  </description>
1234     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1235           K_S0(:DIM_M) = UNDEFINED
1236     !</keyword>
1237     
1238     !<keyword category="Solids Phase" required="false" tfm="true" dem="true">
1239     !  <description>
1240     !    Specified constant solids specific heat [cal/(g.s.K) in CGS].
1241     !  </description>
1242     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1243           C_PS0(:DIM_M) = UNDEFINED
1244     !</keyword>
1245     
1246     
1247     !<keyword category="Solids Phase" required="false" tfm="true" dem="true">
1248     !  <description>
1249     !    Molecular weight of solids phase species [(g/mol) in CGS].
1250     !  </description>
1251     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1252     !  <arg index="2" id="Species" min="1" max="DIM_N_s"/>
1253           MW_S(:DIM_M,:DIM_N_s) = UNDEFINED
1254     !</keyword>
1255     
1256     !<keyword category="Solids Phase" required="false" tfm="true" dem="true">
1257     !  <description>
1258     !    Number of species comprising the solids phase.
1259     !  </description>
1260     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1261           NMAX_s(:DIM_M) = UNDEFINED_I
1262     !</keyword>
1263     
1264     !<keyword category="Solids Phase" required="false" tfm="true" dem="true">
1265     !  <description>
1266     !    Name of solids phase M, species N as it appears in the materials
1267     !    database.
1268     !</description>
1269     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1270     !  <arg index="2" id="Species" min="1" max="DIM_N_s"/>
1271           SPECIES_s(:DIM_M,:DIM_N_s) = UNDEFINED_C
1272     !</keyword>
1273     
1274     !<keyword category="Solids Phase" required="false" tfm="true" dem="true">
1275     !  <description>
1276     !    User defined name for solids phase species. Aliases are used in
1277     !    specifying chemical equations and must be unique.
1278     !  </description>
1279     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1280     !  <arg index="2" id="Species" min="1" max="DIM_N_s"/>
1281           SPECIES_ALIAS_s(:DIM_M,:DIM_N_s) = UNDEFINED_C
1282     !</keyword>
1283     
1284     !#####################################################################!
1285     !                           Two Fluid Model                           !
1286     !#####################################################################!
1287     
1288     
1289     !<keyword category="Two Fluid Model" required="false" tfm="true">
1290     !  <description>
1291     !    Solids phase stress model [LUN_1984]. This is only needed when 
1292     !    solving the granular energy PDE (GRANULAR_ENERGY = .TRUE.).
1293     !  </description>
1294     !  <dependent keyword="GRANULAR_ENERGY" value=".TRUE."/>
1295     !  <valid value="AHMADI"
1296     !    note="Cao and Ahmadi (1995). Int. J. Multiphase Flow 21(6), 1203."/>
1297     !  <valid value="GD_99"
1298     !     note="Garzo and Dufty (1999). Phys. Rev. E 59(5), 5895."/>
1299     !  <valid value="GHD"
1300     !    note="Garzo, Hrenya and Dufty (2007). Phys. Rev. E 76(3), 31304"/>
1301     !  <valid value="GTSH"
1302     !    note="Garzo, Tenneti, Subramaniam, Hrenya (2012). J.Fluid Mech. 712, 129."/>
1303     !  <valid value="IA_NONEP"
1304     !     note="Iddir & Arastoopour (2005). AIChE J. 51(6), 1620"/>
1305     !  <valid value="LUN_1984"
1306     !    note="Lun et al (1984). J. Fluid Mech., 140, 223."/>
1307     !  <valid value="SIMONIN"
1308     !    note="Simonin (1996). VKI Lecture Series, 1996-2"/>
1309           KT_TYPE = "LUN_1984"
1310     !</keyword>
1311     
1312     ! Retired keyword for specifying Ahmadi KT Theory.
1313     ! Use: KT_TYPE = "AHMADI"
1314           AHMADI = .FALSE.
1315     
1316     ! Retired keyword for specifying Simonin KT Theory.
1317     ! Use: KT_TYPE = "SIMONIN"
1318           SIMONIN = .FALSE.
1319     
1320     !<keyword category="Two Fluid Model" required="false" tfm="true">
1321     !  <description>
1322     !    Solids stress model selection.
1323     !  </description>
1324     !  <valid value=".FALSE." note="Do not use the Princeton solids stress model."/>
1325     !  <valid value=".TRUE."  note="Use the Princeton solids stress model"/>
1326     !  <dependent keyword="GRANULAR_ENERGY" value=".TRUE."/>
1327     !  <dependent keyword="PHI" value="DEFINED"/>
1328     !  <dependent keyword="PHI_W" value="DEFINED"/>
1329           FRICTION = .FALSE.
1330     !</keyword>
1331     
1332     !<keyword category="Two Fluid Model" required="false" tfm="true">
1333     !  <description>
1334     !    For a term appearing in the frictional stress model
1335     !    invoked with FRICTION keyword.
1336     !  </description>
1337     !  <valid value="0" note="Use S:S in the frictional stress model."/>
1338     !  <valid value="1" note="Use an alternate form suggested by Savage."/>
1339     !  <valid value="2" note="An appropriate combination of above."/>
1340     !  <dependent keyword="friction" value=".TRUE."/>
1341           SAVAGE = 1
1342     !</keyword>
1343     
1344     !<keyword category="Two Fluid Model" required="false" tfm="true">
1345     !  <description>Schaeffer frictional stress tensor formulation. </description>
1346     !  <dependent keyword="PHI" value="DEFINED"/>
1347     !  <valid value=".TRUE." note="Use the Schaeffer model."/>
1348     !  <valid value=".FALSE." note="Do not use the Schaeffer model."/>
1349           SCHAEFFER = .TRUE.
1350     !</keyword>
1351     
1352     !<keyword category="Two Fluid Model" required="false" tfm="true">
1353     !  <description>
1354     !    Blend the Schaeffer stresses with that of algebraic kinetic theory
1355     !    around EP_STAR.
1356     !  </description>
1357           BLENDING_STRESS = .FALSE.
1358     !</keyword>
1359     
1360     !<keyword category="Two Fluid Model" required="false" tfm="ture">
1361     !  <description>
1362     !    Hyperbolic tangent function for blending frictional stress models.
1363     !  </description>
1364     !  <dependent keyword="BLENDING_STRESS" value=".TRUE."/>
1365     !  <conflict keyword="SIGM_BLEND" value=".TRUE."/>
1366           TANH_BLEND = .TRUE.
1367     !</keyword>
1368     
1369     !<keyword category="Two Fluid Model" required="false" tfm="true">
1370     !  <description>
1371     !    A scaled and truncated sigmoidal function for blending
1372     !    frictional stress models.
1373     !  </description>
1374     !  <dependent keyword="BLENDING_STRESS" value=".TRUE."/>
1375     !  <conflict keyword="TANH_BLEND" value=".TRUE."/>
1376           SIGM_BLEND = .FALSE.
1377     !</keyword>
1378     
1379     !<keyword category="Two Fluid Model" required="false" tfm="true">
1380     !  <description>
1381     !    Correlation to compute maximum packing for polydisperse systems.
1382     !  </description>
1383     !  <valid value=".TRUE."
1384     !    note="Use the Yu and Standish correlation."/>
1385     !  <valid value=".FALSE."
1386     !    note="Do not use the Yu and Standish correlation."/>
1387           YU_STANDISH = .FALSE.
1388     !</keyword>
1389     
1390     !<keyword category="Two Fluid Model" required="false" tfm="true">
1391     !  <description>
1392     !    Correlation to compute maximum packing for binary (only)
1393     !    mixtures of powders.
1394     !  </description>
1395     !  <valid value=".TRUE."
1396     !    note="Use the Fedors and Landel correlation."/>
1397     !  <valid value=".FALSE."
1398     !    note="Do not use the Fedors and Landel correlation."/>
1399           FEDORS_LANDEL = .FALSE.
1400     !</keyword>
1401     
1402     !<keyword category="Two Fluid Model" required="false" tfm="true">
1403     !  <description>
1404     !    Radial distribution function at contact for polydisperse systems.
1405     !    Do not specify any RDF for monodisperse systems because Carnahan-
1406     !    Starling is the model only available.
1407     !
1408     !    Carnahan, N.F. and Starling K.E., (1969).
1409     !    The Journal of Chemical Physics, Vol. 51(2):635-636.
1410     !  </description>
1411     !
1412     !  <valid value="LEBOWITZ" note="Lebowitz, J.L. (1964)
1413     !   The Physical Review, A133, 895-899"/>
1414     !
1415     !  <valid value="MODIFIED_LEBOWITZ" note="
1416     !    Iddir, H. Y., Modeling of the multiphase mixture of particles
1417     !    using the kinetic theory approach. Doctoral Dissertation,
1418     !    Illinois Institute of Technology, Chicago, Illinois, 2004,
1419     !    (chapter 2, equations 2-49 through 2-52.)"/>
1420     !
1421     !  <valid value="MANSOORI" note="
1422     !   Mansoori, GA, Carnahan N.F., Starling, K.E. Leland, T.W. (1971).
1423     !    The Journal of Chemical Physics, Vol. 54:1523-1525."/>
1424     !
1425     !  <valid value="MODIFIED_MANSOORI" note="van Wachem, B.G.M., Schouten, J.C.,
1426     !    van den Bleek, C.M., Krishna, R. and Sinclair, J. L. (2001)
1427     !    AIChE Journal 47:10351051."/>
1428           RDF_TYPE = 'LEBOWITZ'
1429     !</keyword>
1430     
1431     !<keyword category="Two Fluid Model" required="false" tfm="true">
1432     !  <description>
1433     !    Flag to include the added (or virtual) mass force. This force
1434     !    acts to increase the inertia of the dispersed phase, which
1435     !    tends to stabilize simulations of bubbly gas-liquid flows.
1436     !  </description>
1437     !  <dependent keyword="M_AM" value="DEFINED"/>
1438           Added_Mass = .FALSE.
1439     !</keyword>
1440     
1441     !<keyword category="Two Fluid Model" required="false" tfm="true">
1442     !  <description>
1443     !    The disperse phase number to which the added mass is applied.
1444     !  </description>
1445           M_AM = UNDEFINED_I
1446     !</keyword>
1447     
1448     !<keyword category="Two Fluid Model" required="false" tfm="true">
1449     !  <description>
1450     !    Coefficient of restitution for particle-particle collisions.
1451     !  </description>
1452     !  <range min="0.0" max="1.0" />
1453           C_E = UNDEFINED
1454     !</keyword>
1455     
1456     !<keyword category="Two Fluid Model" required="false">
1457     !  <description>
1458     !    Coefficient of restitution for particle-particle collisions specific
1459     !    to GHD theory implementation.
1460     !  </description>
1461     !  <arg index="1" id="Phase" min="0" max="DIM_M"/>
1462     !  <arg index="2" id="Phase" min="0" max="DIM_M"/>
1463           r_p(:DIM_M, :DIM_M) = UNDEFINED
1464     !</keyword>
1465     
1466     !<keyword category="Two Fluid Model" required="false">
1467     !  <description>
1468     !    Coefficient of restitution for particle-wall collisions when using
1469     !    Johnson and Jackson partial slip BC (BC_JJ_PS).</description>
1470     !  <range min="0.0" max="1.0" />
1471           E_W = 1.D0
1472     !</keyword>
1473     
1474     !<keyword category="Two Fluid Model" required="false" tfm="true">
1475     !  <description>
1476     !    Specularity coefficient associated with particle-wall collisions
1477     !    when using Johnson and Jackson partial slip BC (BC_JJ_PS). If
1478     !    Jenkins small frictional BC are invoked (JENKINS) then phip is
1479     !    not used.
1480     !  </description>
1481     !  <range min="0.0" max="1.0" />
1482           PHIP = 0.6D0
1483     !</keyword>
1484     
1485     !<keyword category="Two Fluid Model" required="false" tfm="true">
1486     !  <description>
1487     !    Specify the value of specularity coefficient when the normalized
1488     !    slip velocity goes to zero when BC_JJ_M is .TRUE.. This variable
1489     !    is calculated internally in the code. Do not modify unless an
1490     !    accurate number is known.
1491     !  </description>
1492     !  <dependent keyword="BC_JJ_M" value=".TRUE."/>
1493           phip0 = undefined
1494     !</keyword>
1495     
1496     !<keyword category="Two Fluid Model" required="false" tfm="true">
1497     !  <description>
1498     !    Coefficient of friction between the particles of two solids phases.
1499     !  </description>
1500           C_F = UNDEFINED
1501     !</keyword>
1502     
1503     !<keyword category="Two Fluid Model" required="false" tfm="true">
1504     !  <description>
1505     !     Angle of internal friction (in degrees). Set this value
1506     !     to zero to turn off plastic regime stress calculations.
1507     !  </description>
1508           PHI = UNDEFINED
1509     !</keyword>
1510     
1511     !<keyword category="Two Fluid Model" required="false" tfm="true">
1512     !  <description>
1513     !    Angle of internal friction (in degrees) at walls. Set this
1514     !    value to non-zero (PHI_W = 11.31 means TAN_PHI_W = MU = 0.2)
1515     !    when using Johnson and Jackson partial slip BC (BC_JJ_PS) with
1516     !    Friction model or Jenkins small frictional boundary condition.
1517     !  </description>
1518           PHI_W = UNDEFINED
1519     !</keyword>
1520     
1521     !<keyword category="Two Fluid Model" required="false" tfm="true">
1522     !  <description>
1523     !    Minimum solids fraction above which friction sets in. [0.5] (when
1524     !    FRICTION = .TRUE.)
1525     !  </description>
1526     !  <dependent keyword="FRICTION" value=".TRUE."/>
1527           EPS_F_MIN = 0.5D0
1528     !</keyword>
1529     
1530     !<keyword category="Two Fluid Model" required="false" tfm="true">
1531     !  <description>
1532     !    Maximum solids volume fraction at packing for polydisperse
1533     !    systems (more than one solids phase used). The value of
1534     !    EP_STAR may change during the computation if solids phases
1535     !    with different particle diameters are specified and
1536     !    Yu_Standish or Fedors_Landel correlations are used.
1537     !  </description>
1538     !  <arg index="1" id="Phase" min="0" max="DIM_M"/>
1539     !  <range min="0" max="1-EP_STAR" />
1540           EP_S_MAX(:DIM_M) = UNDEFINED
1541     !</keyword>
1542     
1543     !<keyword category="Two Fluid Model" required="false" tfm="true">
1544     !  <description>
1545     !    Used in calculating the initial slope of segregation: see
1546     !    Gera et al. (2004) - recommended value 0.3. Increasing this
1547     !    coefficient results in decrease in segregation of particles
1548     !    in binary mixtures.
1549     !  </description>
1550           SEGREGATION_SLOPE_COEFFICIENT=0.D0
1551     !</keyword>
1552     
1553     
1554     !<keyword category="Two Fluid Model" required="false" tfm="true">
1555     !  <description>Excluded volume in Boyle-Massoudi stress.</description>
1556     !  <valid value="0.0" note="b-m stress is turned off."/>
1557           V_EX = ZERO
1558     !</keyword>
1559     
1560     !<keyword category="Two Fluid Model" required="false" tfm="true">
1561     !  <description>
1562     !    Specified constant granular viscosity [g/(cm.s) in CGS]. If this
1563     !    value is specified, then the kinetic theory calculation is turned
1564     !    off and P_S = 0 and LAMBDA_S = -2/3 MU_S0.
1565     !  </description>
1566           MU_S0 = UNDEFINED
1567     !</keyword>
1568     
1569     !<keyword category="Two Fluid Model" required="false" tfm="true">
1570     !  <description>
1571     !    Specified constant solids diffusivity [(cm^2)/s in CGS].
1572     !  </description>
1573           DIF_S0 = UNDEFINED
1574     !</keyword>
1575     
1576     !<keyword category="Two Fluid Model" required="false" tfm="true">
1577     !  <description>
1578     !    Packed bed void fraction. Used to calculate plastic stresses (for
1579     !    contribution to viscosity) and when to implement plastic pressure,
1580     !    P_STAR. Specifically, if EP_G < EP_STAR, then plastic pressure is
1581     !    employed in the momentum equations.
1582     !  </description>
1583     !  <range min="0.0" max="1.0" />
1584           EP_STAR = UNDEFINED
1585     !</keyword>
1586     
1587     !<keyword category="Two Fluid Model" required="false" tfm="true">
1588     !  <description>
1589     !    Flag to enable/disable a phase from forming a packed bed.
1590     !    Effectively removes plastic pressure term from the solids phase
1591     !    momentum equation.
1592     !  </description>
1593     !  <arg index="1" id="Phase" min="1" max="DIM_M"/>
1594     !  <valid value=".TRUE." note="The phase forms a packed bed with void
1595     !    fraction EP_STAR."/>
1596     !  <valid value=".FALSE." note="The phase can exceed close pack conditions
1597     !    so that it maybe behave like a liquid."/>
1598           CLOSE_PACKED(:DIM_M) = .TRUE.
1599     !</keyword>
1600     
1601     
1602     !#####################################################################!
1603     !                   Initial Conditions Section                        !
1604     !#####################################################################!
1605     
1606     
1607           DO LC = 1, DIMENSION_IC
1608     
1609     !<keyword category="Initial Condition" required="false">
1610     !  <description>X coordinate of the west face.</description>
1611     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1612              IC_X_W(LC) = UNDEFINED
1613     !</keyword>
1614     
1615     !<keyword category="Initial Condition" required="false">
1616     !  <description>X coordinate of the east face.</description>
1617     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1618              IC_X_E(LC) = UNDEFINED
1619     !</keyword>
1620     
1621     !<keyword category="Initial Condition" required="false">
1622     !  <description>Y coordinate of the south face.</description>
1623     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1624              IC_Y_S(LC) = UNDEFINED
1625     !</keyword>
1626     
1627     !<keyword category="Initial Condition" required="false">
1628     !  <description>Y coordinate of the north face.</description>
1629     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1630              IC_Y_N(LC) = UNDEFINED
1631     !</keyword>
1632     
1633     !<keyword category="Initial Condition" required="false">
1634     !  <description>Z coordinate of the bottom face.</description>
1635     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1636              IC_Z_B(LC) = UNDEFINED
1637     !</keyword>
1638     
1639     !<keyword category="Initial Condition" required="false">
1640     !  <description>Z coordinate of the top face.</description>
1641     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1642              IC_Z_T(LC) = UNDEFINED
1643     !</keyword>
1644     
1645     !<keyword category="Initial Condition" required="false">
1646     !  <description>I index of the west-most wall.</description>
1647     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1648              IC_I_W(LC) = UNDEFINED_I
1649     !</keyword>
1650     
1651     !<keyword category="Initial Condition" required="false">
1652     !  <description>I index of the east-most wall.</description>
1653     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1654              IC_I_E(LC) = UNDEFINED_I
1655     !</keyword>
1656     
1657     !<keyword category="Initial Condition" required="false">
1658     !  <description>J index of the south-most wall.</description>
1659     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1660              IC_J_S(LC) = UNDEFINED_I
1661     !</keyword>
1662     
1663     !<keyword category="Initial Condition" required="false">
1664     !  <description>J index of the north-most wall.</description>
1665     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1666              IC_J_N(LC) = UNDEFINED_I
1667     !</keyword>
1668     
1669     !<keyword category="Initial Condition" required="false">
1670     !  <description>K index of the bottom-most wall.</description>
1671     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1672              IC_K_B(LC) = UNDEFINED_I
1673     !</keyword>
1674     
1675     !<keyword category="Initial Condition" required="false">
1676     !  <description>K index of the top-most wall.</description>
1677     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1678              IC_K_T(LC) = UNDEFINED_I
1679     !</keyword>
1680     
1681     !<keyword category="Initial Condition" required="false">
1682     !  <description>
1683     !    Type of initial condition. Mainly used in restart runs to overwrite
1684     !    values read from the .RES file by specifying it as _PATCH_. The
1685     !    user needs to be careful when using the _PATCH_ option, since the
1686     !    values from the .RES file are overwritten and no error checking is
1687     !    done for the patched values.
1688     !  </description>
1689     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1690              IC_TYPE(LC) = UNDEFINED_C
1691     !</keyword>
1692     
1693     !<keyword category="Initial Condition" required="false">
1694     !  <description>Initial void fraction in the IC region.</description>
1695     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1696              IC_EP_G(LC) = UNDEFINED
1697     !</keyword>
1698     
1699     !<keyword category="Initial Condition" required="false">
1700     !  <description>
1701     !    Initial gas pressure in the IC region. If this quantity is not
1702     !    specified, MFIX will set up a hydrostatic pressure profile,
1703     !    which varies only in the y-direction.
1704     !  </description>
1705     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1706              IC_P_G(LC) = UNDEFINED
1707     !</keyword>
1708     
1709     !<keyword category="Initial Condition" required="false">
1710     !  <description>
1711     !    Initial solids pressure in the IC region. Usually, this value is
1712     !    specified as zero.
1713     !  </description>
1714     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1715              IC_P_STAR(LC) = UNDEFINED
1716     !</keyword>
1717     
1718     !<keyword category="Initial Condition" required="false">
1719     !  <description>Turbulence length scale in the IC region.</description>
1720     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1721              IC_L_SCALE(LC) = UNDEFINED
1722     !</keyword>
1723     
1724     !<keyword category="Initial Condition" required="false">
1725     !  <description>
1726     !    Initial bulk density (rop_s = ro_s x ep_s) of solids phase-m in the
1727     !    IC region. Users need to specify this IC only for polydisperse flow
1728     !    (MMAX > 1). Users must make sure that summation of ( IC_ROP_s(ic,m)
1729     !    / RO_s(m) ) over all solids phases is equal to ( 1.0 - IC_EP_g(ic)).
1730     !  </description>
1731     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1732     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1733              IC_ROP_S(LC,:DIM_M) = UNDEFINED
1734     !</keyword>
1735     
1736     !<keyword category="Initial Condition" required="false">
1737     !  <description>
1738     !    Initial solids volume fraction of solids phase-m in the IC region.
1739     !    This may be specified in place of IC_ROP_s.
1740     !  </description>
1741     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1742     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1743              IC_EP_S(LC,:DIM_M) = UNDEFINED
1744     !</keyword>
1745     
1746     !<keyword category="Initial Condition" required="false">
1747     !  <description>Initial gas phase temperature in the IC region.</description>
1748     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1749              IC_T_G(LC) = UNDEFINED
1750     !</keyword>
1751     
1752     !<keyword category="Initial Condition" required="false">
1753     !  <description>Initial solids phase-m temperature in the IC region.</description>
1754     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1755     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1756              IC_T_S(LC,:DIM_M) = UNDEFINED
1757     !</keyword>
1758     
1759     !<keyword category="Initial Condition" required="false">
1760     !  <description>Initial solids phase-m granular temperature in the IC region.</description>
1761     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1762     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1763              IC_THETA_M(LC,:DIM_M) = UNDEFINED
1764     !</keyword>
1765     
1766     !<keyword category="Initial Condition" required="false">
1767     !  <description>
1768     !    Gas phase radiation coefficient in the IC region. Modify file
1769     !    rdtn2.inc to change the source term.
1770     !  </description>
1771     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1772     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1773              IC_GAMA_RG(LC) = ZERO
1774     !</keyword>
1775     
1776     !<keyword category="Initial Condition" required="false">
1777     !  <description>Gas phase radiation temperature in the IC region.</description>
1778     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1779     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1780              IC_T_RG(LC) = UNDEFINED
1781     !</keyword>
1782     
1783     !<keyword category="Initial Condition" required="false">
1784     !  <description>
1785     !    Solids phase-m radiation coefficient in the IC region. Modify file
1786     !    energy_mod.f to change the source term.
1787     !  </description>
1788     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1789     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1790              IC_GAMA_RS(LC,:DIM_M) = ZERO
1791     !</keyword>
1792     
1793     !<keyword category="Initial Condition" required="false">
1794     !  <description>Solids phase-m radiation temperature in the IC region.</description>
1795     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1796     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1797              IC_T_RS(LC,:DIM_M) = UNDEFINED
1798     !</keyword>
1799     
1800     !<keyword category="Initial Condition" required="false">
1801     !  <description>Initial x-component of gas velocity in the IC region.</description>
1802     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1803              IC_U_G(LC) = UNDEFINED
1804     !</keyword>
1805     
1806     !<keyword category="Initial Condition" required="false">
1807     !  <description>Initial x-component of solids-phase velocity in the IC region.</description>
1808     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1809     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1810              IC_U_S(LC,:DIM_M) = UNDEFINED
1811     !</keyword>
1812     
1813     !<keyword category="Initial Condition" required="false">
1814     !  <description>Initial y-component of gas velocity in the IC region.</description>
1815     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1816              IC_V_G(LC) = UNDEFINED
1817     !</keyword>
1818     
1819     !<keyword category="Initial Condition" required="false">
1820     !  <description>Initial y-component of solids-phase velocity in the IC region.</description>
1821     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1822     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1823              IC_V_S(LC,:DIM_M) = UNDEFINED
1824     !</keyword>
1825     
1826     !<keyword category="Initial Condition" required="false">
1827     !  <description>Initial z-component of gas velocity in the IC region.</description>
1828     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1829              IC_W_G(LC) = UNDEFINED
1830     !</keyword>
1831     
1832     !<keyword category="Initial Condition" required="false">
1833     !  <description>Initial z-component of solids-phase velocity in the IC region.</description>
1834     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1835     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1836              IC_W_S(LC,:DIM_M) = UNDEFINED
1837     !</keyword>
1838     
1839     !<keyword category="Initial Condition" required="false">
1840     !  <description>Initial mass fraction of gas species.</description>
1841     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1842     !  <arg index="2" id="Species" min="1" max="DIM_N_G"/>
1843              IC_X_G(LC,:DIM_N_G) = UNDEFINED
1844     !</keyword>
1845     
1846     !<keyword category="Initial Condition" required="false">
1847     !  <description>Initial mass fraction of solids species.</description>
1848     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1849     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1850     !  <arg index="3" id="Species" min="1" max="DIM_N_S"/>
1851              IC_X_S(LC,:DIM_M,:DIM_N_S) = UNDEFINED
1852     !</keyword>
1853     
1854     !<keyword category="Initial Condition" required="false">
1855     !  <description>Initial value of Scalar n.</description>
1856     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1857     !  <arg index="2" id="Scalar Eq." min="1" max="DIM_SCALAR"/>
1858             IC_SCALAR(LC,:DIM_SCALAR) = UNDEFINED
1859     !</keyword>
1860     
1861     !<keyword category="Initial Condition" required="false">
1862     !  <description>Initial value of K in K-Epsilon.</description>
1863     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1864              IC_K_Turb_G(LC) = UNDEFINED
1865     !</keyword>
1866     
1867     !<keyword category="Initial Condition" required="false">
1868     !  <description>Initial value of Epsilon in K-Epsilon.</description>
1869     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1870              IC_E_Turb_G(LC) = UNDEFINED
1871     !</keyword>
1872     
1873     !<keyword category="Initial Condition" required="false">
1874     !  <description>Flag for inflating initial lattice distribution
1875     ! to the entire IC region. </description>
1876     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1877               IC_DES_FIT_TO_REGION(LC) = .FALSE.
1878     !</keyword>
1879     
1880     
1881     !<keyword category="Initial Condition" required="false">
1882     !  <description>Flag to specify the initial constant number
1883     ! of particles per cell for the PIC method initialization.
1884     !Statistical weight of parcels will be calculated by the code.</description>
1885     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1886     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1887     !  <dependent keyword="SOLIDS_MODEL" value="PIC"/>
1888     !  <conflict keyword="IC_PIC_CONST_STATWT" value="DEFINED"/>
1889               IC_PIC_CONST_NPC(LC, :DIM_M) = 0
1890     !</keyword>
1891     
1892     
1893     !<keyword category="Initial Condition" required="false">
1894     !  <description>Flag to specify the initial constant statistical
1895     ! weight for computational particles/parcels. Actual number of
1896     ! parcels will be automatically computed. </description>
1897     !  <arg index="1" id="IC" min="1" max="DIMENSION_IC"/>
1898     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
1899     !  <dependent keyword="SOLIDS_MODEL" value="PIC"/>
1900     !  <conflict keyword="IC_PIC_CONST_NPC" value="DEFINED"/>
1901               IC_PIC_CONST_STATWT(LC, :DIM_M) = ZERO
1902     !</keyword>
1903           ENDDO
1904     
1905     
1906     
1907     
1908     !#####################################################################!
1909     !                        Boundary Conditions                          !
1910     !#####################################################################!
1911           DO LC = 1, DIMENSION_BC
1912     
1913     
1914     !<keyword category="Boundary Condition" required="false">
1915     !  <description>X coordinate of the west face or edge.</description>
1916     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1917              BC_X_W(LC) = UNDEFINED
1918     !</keyword>
1919     
1920     !<keyword category="Boundary Condition" required="false">
1921     !  <description>X coordinate of the east face or edge.</description>
1922     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1923              BC_X_E(LC) = UNDEFINED
1924     !</keyword>
1925     
1926     !<keyword category="Boundary Condition" required="false">
1927     !  <description>Y coordinate of the south face or edge.</description>
1928     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1929              BC_Y_S(LC) = UNDEFINED
1930     !</keyword>
1931     
1932     !<keyword category="Boundary Condition" required="false">
1933     !  <description>Y coordinate of the north face or edge.</description>
1934     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1935              BC_Y_N(LC) = UNDEFINED
1936     !</keyword>
1937     
1938     !<keyword category="Boundary Condition" required="false">
1939     !  <description>Z coordinate of the bottom face or edge.</description>
1940     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1941              BC_Z_B(LC) = UNDEFINED
1942     !</keyword>
1943     
1944     !<keyword category="Boundary Condition" required="false">
1945     !  <description>Z coordinate of the top face or edge.</description>
1946     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1947              BC_Z_T(LC) = UNDEFINED
1948     !</keyword>
1949     
1950     !<keyword category="Boundary Condition" required="false">
1951     !  <description>I index of the west-most cell.</description>
1952     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1953              BC_I_W(LC) = UNDEFINED_I
1954     !</keyword>
1955     
1956     !<keyword category="Boundary Condition" required="false">
1957     !  <description>I index of the east-most cell.</description>
1958     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1959              BC_I_E(LC) = UNDEFINED_I
1960     !</keyword>
1961     
1962     !<keyword category="Boundary Condition" required="false">
1963     !  <description>J index of the south-most cell.</description>
1964     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1965              BC_J_S(LC) = UNDEFINED_I
1966     !</keyword>
1967     
1968     !<keyword category="Boundary Condition" required="false">
1969     !  <description>J index of the north-most cell.</description>
1970     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1971              BC_J_N(LC) = UNDEFINED_I
1972     !</keyword>
1973     
1974     !<keyword category="Boundary Condition" required="false">
1975     !  <description>K index of the bottom-most cell.</description>
1976     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1977              BC_K_B(LC) = UNDEFINED_I
1978     !</keyword>
1979     
1980     !<keyword category="Boundary Condition" required="false">
1981     !  <description>K index of the top-most cell.</description>
1982     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1983              BC_K_T(LC) = UNDEFINED_I
1984     !</keyword>
1985     
1986     !<keyword category="Boundary Condition" required="false">
1987     !  <description>Type of boundary.</description>
1988     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
1989     !
1990     !  <valid value='DUMMY'
1991     !    note='The specified boundary condition is ignored. This is
1992     !      useful for turning off some boundary conditions without having
1993     !      to delete them from the file.' />
1994     !
1995     !  <valid value='MASS_INFLOW' alias='MI'
1996     !    note='Mass inflow rates for gas and solids phases are
1997     !      specified at the boundary.'/>
1998     !
1999     !  <valid value='MASS_OUTFLOW' alias='MO'
2000     !    note='The specified values of gas and solids mass outflow
2001     !      rates at the boundary are maintained, approximately. This
2002     !      condition should be used sparingly for minor outflows, when
2003     !      the bulk of the outflow is occurring through other constant
2004     !      pressure outflow boundaries.' />
2005     !
2006     !  <valid value='P_INFLOW' alias='PI'
2007     !    note='Inflow from a boundary at a specified constant
2008     !      pressure. To specify as the west, south, or bottom end of
2009     !      the computational region, add a layer of wall cells to the
2010     !      west, south, or bottom of the PI cells. Users need to specify
2011     !      all scalar quantities and velocity components. The specified
2012     !      values of fluid and solids velocities are only used initially
2013     !      as MFIX computes these values at this inlet boundary.' />
2014     !
2015     !  <valid value='P_OUTFLOW' alias='PO'
2016     !    note='Outflow to a boundary at a specified constant pressure.
2017     !      To specify as the west, south, or bottom end of the computational
2018     !      region, add a layer of wall cells to the west, south, or bottom of
2019     !      the PO cells.' />
2020     !
2021     !  <valid value='FREE_SLIP_WALL' alias='FSW'
2022     !    note='Velocity gradients at the wall vanish. If BC_JJ_PS is
2023     !      equal to 1, the Johnson-Jackson boundary condition is used for
2024     !      solids.  A FSW is equivalent to using a PSW with hw=0.' />
2025     !
2026     !  <valid value='NO_SLIP_WALL' alias='NSW'
2027     !    note='All components of the velocity vanish at the wall. If
2028     !      BC_JJ_PS is equal to 1, the Johnson-Jackson boundary condition is
2029     !      used for solids.  A NSW is equivalent to using a PSW with vw=0
2030     !      and hw undefined.' />
2031     !
2032     !  <valid value='PAR_SLIP_WALL' alias='PSW'
2033     !    note='Partial slip at the wall implemented as
2034     !      dv/dn + hw (v - vw) = 0, where n is the normal pointing from the
2035     !      fluid into the wall. The coefficients hw and vw should be
2036     !      specified. For free slip set hw = 0. For no slip leave hw
2037     !      undefined (hw=+inf) and set vw = 0. To set hw = +inf, leave it
2038     !      unspecified. If BC_JJ_PS is equal to 1, the Johnson-Jackson
2039     !      boundary condition is used for solids.' />
2040              BC_TYPE(LC) = UNDEFINED_C
2041     !</keyword>
2042     
2043     !<keyword category="Boundary Condition" required="false">
2044     !  <description>Gas phase hw for partial slip boundary.</description>
2045     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2046              BC_HW_G(LC) = UNDEFINED
2047     !</keyword>
2048     
2049     !<keyword category="Boundary Condition" required="false">
2050     !  <description>Solids phase hw for partial slip boundary.</description>
2051     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2052     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2053              BC_HW_S(LC,:DIM_M) = UNDEFINED
2054     !</keyword>
2055     
2056     !<keyword category="Boundary Condition" required="false">
2057     !  <description>Gas phase Uw for partial slip boundary.</description>
2058     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2059              BC_UW_G(LC) = UNDEFINED
2060     !</keyword>
2061     
2062     !<keyword category="Boundary Condition" required="false">
2063     !  <description>Solids phase Uw for partial slip boundary.</description>
2064     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2065     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2066              BC_UW_S(LC,:DIM_M) = UNDEFINED
2067     !</keyword>
2068     
2069     !<keyword category="Boundary Condition" required="false">
2070     !  <description>Gas phase Vw for partial slip boundary.</description>
2071     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2072              BC_VW_G(LC) = UNDEFINED
2073     !</keyword>
2074     
2075     !<keyword category="Boundary Condition" required="false">
2076     !  <description>Solids phase Vw for partial slip boundary.</description>
2077     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2078     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2079              BC_VW_S(LC,:DIM_M) = UNDEFINED
2080     !</keyword>
2081     
2082     !<keyword category="Boundary Condition" required="false">
2083     !  <description>Gas phase Ww for partial slip boundary.</description>
2084     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2085              BC_WW_G(LC) = UNDEFINED
2086     !</keyword>
2087     
2088     !<keyword category="Boundary Condition" required="false">
2089     !  <description>Solids phase Ww for partial slip boundary.</description>
2090     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2091     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2092              BC_WW_S(LC,:DIM_M) = UNDEFINED
2093     !</keyword>
2094     
2095     !<keyword category="Boundary Condition" required="false">
2096     !  <description>
2097     !   Johnson and Jackson partial slip BC.
2098     !  </description>
2099     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2100     !  <valid value='0'
2101     !    note='Do not use Johnson and Jackson partial slip bc. Default
2102     !      if granular energy transport equation is not solved.'/>
2103     !  <valid value='1'
2104     !    note='Use Johnson and Jackson partial slip bc. Default if
2105     !      granular energy transport equation is solved.'/>
2106     !  <dependent keyword="GRANULAR_ENERGY" value=".TRUE."/>
2107              BC_JJ_PS(LC) = UNDEFINED_I
2108     !</keyword>
2109     
2110     !<keyword category="Boundary Condition" required="false">
2111     !  <description>Use a modified version of Johnson and Jackson
2112     !   partial slip BC (BC_JJ_PS BC) with a variable specularity
2113     !   coefficient.
2114     !  </description>
2115     !  <dependent keyword="E_w" value="DEFINED"/>
2116     !  <dependent keyword="PHI_w" value="DEFINED"/>
2117     !  <conflict keyword="JENKINS" value=".TRUE."/>
2118              BC_JJ_M = .FALSE.
2119     !</keyword>
2120     
2121     !<keyword category="Two Fluid Model" required="false">
2122     !  <description>
2123     !    This flag effects how the momentum and granular energy boundary
2124     !    conditions are implemented when using BC_JJ_PS BC.
2125     !  </description>
2126     !  <dependent keyword="PHI_w" value="DEFINED"/>
2127     !  <dependent keyword="E_w" value="DEFINED"/>
2128     !  <conflict keyword="BC_JJ_M" value=".TRUE."/>
2129     !  <valid value=".FALSE." note="Use standard boundary conditions."/>
2130     !  <valid value=".TRUE."
2131     !    note="Use Jenkins small frictional boundary condition."/>
2132              JENKINS = .FALSE.
2133     !</keyword>
2134     
2135     !<keyword category="Boundary Condition" required="false">
2136     !  <description>
2137     !    Specified wall value, THETAw_M, in diffusion boundary condition:
2138     !    d(Theta_M)/dn + Hw (THETA_M - THETAw_M) = C, where n is the fluid-to-wall normal.
2139     !  </description>
2140     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2141     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2142              BC_THETAW_M(LC,:DIM_M) = UNDEFINED
2143     !</keyword>
2144     
2145     !<keyword category="Boundary Condition" required="false">
2146     !  <description>
2147     !    Transfer coefficient, Hw, in diffusion boundary condition:
2148     !    d(Theta_M)/dn + Hw (THETA_M - THETAw_M) = C, where n is the fluid-to-wall normal.
2149     !  </description>
2150     !  <description>Hw for granular energy bc.</description>
2151     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2152     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2153              BC_HW_THETA_M(LC,:DIM_M) = UNDEFINED
2154     !</keyword>
2155     
2156     !<keyword category="Boundary Condition" required="false">
2157     !  <description>
2158     !    Specified constant flux, C, in diffusion boundary condition:
2159     !    d(Theta_M)/dn + Hw (THETA_M - THETAw_M) = C, where n is the fluid-to-wall normal.
2160     !  </description>
2161     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2162     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2163              BC_C_THETA_M(LC,:DIM_M) = UNDEFINED
2164     !</keyword>
2165     
2166     !<keyword category="Boundary Condition" required="false">
2167     !  <description>
2168     !    Gas phase heat transfer coefficient, Hw, in diffusion boundary condition:
2169     !    d(T_g)/dn + Hw (T_g - Tw_g) = C, where n is the fluid-to-wall normal.
2170     !  </description>
2171     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2172              BC_HW_T_G(LC) = UNDEFINED
2173     !</keyword>
2174     
2175     !<keyword category="Boundary Condition" required="false">
2176     !  <description>
2177     !    Specified gas phase wall temperature, Tw_g, in diffusion boundary condition:
2178     !    d(T_g)/dn + Hw (T_g - Tw_g) = C, where n is the fluid-to-wall normal.
2179     !  </description>
2180     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2181              BC_TW_G(LC) = UNDEFINED
2182     !</keyword>
2183     
2184     !<keyword category="Boundary Condition" required="false">
2185     !  <description>
2186     !    Specified constant gas phase heat flux, C, in diffusion boundary condition:
2187     !    d(T_g)/dn + Hw (T_g - Tw_g) = C, where n is the fluid-to-wall normal.
2188     !  </description>
2189     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2190              BC_C_T_G(LC) = UNDEFINED
2191     !</keyword>
2192     
2193     !<keyword category="Boundary Condition" required="false">
2194     !  <description>
2195     !    Solids phase heat transfer coefficient, Hw, in diffusion boundary condition:
2196     !    d(T_s)/dn + Hw (T_s - Tw_s) = C, where n is the fluid-to-wall normal.
2197     !  </description>
2198     !  <description>Solids phase hw for heat transfer.</description>
2199     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2200     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2201              BC_HW_T_S(LC,:DIM_M) = UNDEFINED
2202     !</keyword>
2203     
2204     !<keyword category="Boundary Condition" required="false">
2205     !  <description>
2206     !    Specified solids phase wall temperature, Tw_s, in diffusion boundary condition:
2207     !    d(T_s)/dn + Hw (T_s - Tw_s) = C, where n is the fluid-to-wall normal.
2208     !  </description>
2209     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2210     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2211              BC_TW_S(LC,:DIM_M) = UNDEFINED
2212     !</keyword>
2213     
2214     !<keyword category="Boundary Condition" required="false">
2215     !  <description>
2216     !    Specified constant solids phase heat flux, C, in diffusion boundary condition:
2217     !    d(T_s)/dn + Hw (T_s - Tw_s) = C, where n is the fluid-to-wall normal.
2218     !  </description>
2219     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2220     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2221              BC_C_T_S(LC,:DIM_M) = UNDEFINED
2222     !</keyword>
2223     
2224     !<keyword category="Boundary Condition" required="false">
2225     !  <description>
2226     !    Gas phase species mass transfer coefficient, Hw, in diffusion boundary condition:
2227     !    d(X_g)/dn + Hw (X_g - Xw_g) = C, where n is the fluid-to-wall normal.
2228     !  </description>
2229     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2230     !  <arg index="2" id="Species" min="1" max="DIM_N_G"/>
2231              BC_HW_X_G(LC,:DIM_N_G) = UNDEFINED
2232     !</keyword>
2233     
2234     !<keyword category="Boundary Condition" required="false">
2235     !  <description>
2236     !    Specified wall gas species mass fraction, Xw, in diffusion boundary condition:
2237     !    d(X_g)/dn + Hw (X_g - Xw_g) = C, where n is the fluid-to-wall normal.
2238     !  </description>
2239     !  <description>Gas phase Xw for mass transfer.</description>
2240     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2241     !  <arg index="2" id="Species" min="1" max="DIM_N_G"/>
2242              BC_XW_G(LC,:DIM_N_G) = UNDEFINED
2243     !</keyword>
2244     
2245     !<keyword category="Boundary Condition" required="false">
2246     !  <description>
2247     !    Specified constant gas species mass flux, C, in diffusion boundary condition:
2248     !    d(X_g)/dn + Hw (X_g - Xw_g) = C, where n is the fluid-to-wall normal.
2249     !  </description>
2250     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2251     !  <arg index="2" id="Species" min="1" max="DIM_N_G"/>
2252              BC_C_X_G(LC,:DIM_N_G) = UNDEFINED
2253     !</keyword>
2254     
2255     !<keyword category="Boundary Condition" required="false">
2256     !  <description>
2257     !    Solid phase species mass transfer coefficient, Hw, in diffusion boundary condition:
2258     !    d(X_s)/dn + Hw (X_s - Xw_s) = C, where n is the fluid-to-wall normal.
2259     !  </description>
2260     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2261     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2262     !  <arg index="3" id="Species" min="1" max="DIM_N_S"/>
2263              BC_HW_X_S(LC,:DIM_M,:DIM_N_S) = UNDEFINED
2264     !</keyword>
2265     
2266     !<keyword category="Boundary Condition" required="false">
2267     !  <description>
2268     !    Specified solids species mass fraction at the wall, Xw, in diffusion boundary condition:
2269     !    d(X_g)/dn + Hw (X_g - Xw_g) = C, where n is the fluid-to-wall normal.
2270     !  </description>
2271     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2272     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2273     !  <arg index="3" id="Species" min="1" max="DIM_N_S"/>
2274              BC_XW_S(LC,:DIM_M,:DIM_N_S) = UNDEFINED
2275     !</keyword>
2276     
2277     !<keyword category="Boundary Condition" required="false">
2278     !  <description>
2279     !    Specified constant solids species mass flux, C, in diffusion boundary condition:
2280     !    d(X_s)/dn + Hw (X_s - Xw_s) = C, where n is the fluid-to-wall normal.
2281     !  </description>
2282     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2283     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2284     !  <arg index="3" id="Species" min="1" max="DIM_N_S"/>
2285              BC_C_X_S(LC,:DIM_M,:DIM_N_S) = UNDEFINED
2286     !</keyword>
2287     
2288     !<keyword category="Boundary Condition" required="false">
2289     !  <description>
2290     !    Scalar transfer coefficient, Hw, in diffusion boundary condition:
2291     !    d(Scalar)/dn + Hw (Scalar - ScalarW) = C, where n is the fluid-to-wall normal.
2292     !  </description>
2293     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2294     !  <arg index="2" id="Scalar Eq." min="1" max="DIM_SCALAR"/>
2295              BC_HW_Scalar(LC,:DIM_SCALAR) = UNDEFINED
2296     !</keyword>
2297     
2298     !<keyword category="Boundary Condition" required="false">
2299     !  <description>
2300     !    Specified scalar value at the wall, ScalarW, in diffusion boundary condition:
2301     !    d(Scalar)/dn + Hw (Scalar - ScalarW) = C, where n is the fluid-to-wall normal.
2302     !  </description>
2303     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2304     !  <arg index="2" id="Scalar Eq." min="1" max="DIM_SCALAR"/>
2305              BC_ScalarW(LC,:DIM_SCALAR) = UNDEFINED
2306     !</keyword>
2307     
2308     !<keyword category="Boundary Condition" required="false">
2309     !  <description>
2310     !    Specified constant scalar flux, C, in diffusion boundary condition:
2311     !    d(Scalar)/dn + Hw (Scalar - ScalarW) = C, where n is the fluid-to-wall normal.
2312     !  </description>
2313     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2314     !  <arg index="2" id="Scalar Eq." min="1" max="DIM_SCALAR"/>
2315              BC_C_Scalar(LC,:DIM_SCALAR) = UNDEFINED
2316     !</keyword>
2317     
2318     !<keyword category="Boundary Condition" required="false">
2319     !  <description>Void fraction at the BC plane.</description>
2320     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2321              BC_EP_G(LC) = UNDEFINED
2322     !</keyword>
2323     
2324     !<keyword category="Boundary Condition" required="false">
2325     !  <description>Gas pressure at the BC plane.</description>
2326     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2327              BC_P_G(LC) = UNDEFINED
2328     !</keyword>
2329     
2330     !<keyword category="Boundary Condition" required="false">
2331     !  <description>Bulk density of solids phase at the BC plane.</description>
2332     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2333     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2334              BC_ROP_S(LC,:DIM_M) = UNDEFINED
2335     !</keyword>
2336     
2337     !<keyword category="Boundary Condition" required="false">
2338     !  <description>Solids volume fraction at the BC plane.</description>
2339     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2340     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2341              BC_EP_S(LC,:DIM_M) = UNDEFINED
2342     !</keyword>
2343     
2344     !<keyword category="Boundary Condition" required="false">
2345     !  <description>Gas phase temperature at the BC plane.</description>
2346     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2347              BC_T_G(LC) = UNDEFINED
2348     !</keyword>
2349     
2350     !<keyword category="Boundary Condition" required="false">
2351     !  <description>Solids phase-m temperature at the BC plane.</description>
2352     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2353     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2354              BC_T_S(LC,:DIM_M) = UNDEFINED
2355     !</keyword>
2356     
2357     !<keyword category="Boundary Condition" required="false">
2358     !  <description>Solids phase-m granular temperature at the BC plane.</description>
2359     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2360     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2361              BC_THETA_M(LC,:DIM_M) = UNDEFINED
2362     !</keyword>
2363     
2364     !<keyword category="Boundary Condition" required="false">
2365     !  <description>Mass fraction of gas species at the BC plane.</description>
2366     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2367     !  <arg index="2" id="Species" min="1" max="DIM_N_G"/>
2368              BC_X_G(LC,:DIM_N_G) = UNDEFINED
2369     !</keyword>
2370     
2371     !<keyword category="Boundary Condition" required="false">
2372     !  <description>Mass fraction of solids species at the BC plane.</description>
2373     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2374     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2375     !  <arg index="3" id="Species" min="1" max="DIM_N_S"/>
2376              BC_X_S(LC,:DIM_M,:DIM_N_S) = UNDEFINED
2377     !</keyword>
2378     
2379     !<keyword category="Boundary Condition" required="false">
2380     !  <description>X-component of gas velocity at the BC plane.</description>
2381     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2382              BC_U_G(LC) = UNDEFINED
2383     !</keyword>
2384     
2385     !<keyword category="Boundary Condition" required="false">
2386     !  <description>X-component of solids-phase velocity at the BC plane.</description>
2387     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2388     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2389              BC_U_S(LC,:DIM_M) = UNDEFINED
2390     !</keyword>
2391     
2392     !<keyword category="Boundary Condition" required="false">
2393     !  <description>Y-component of gas velocity at the BC plane.</description>
2394     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2395              BC_V_G(LC) = UNDEFINED
2396     !</keyword>
2397     
2398     !<keyword category="Boundary Condition" required="false">
2399     !  <description>Y-component of solids-phase velocity at the BC plane.</description>
2400     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2401     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2402              BC_V_S(LC,:DIM_M) = UNDEFINED
2403     !</keyword>
2404     
2405     !<keyword category="Boundary Condition" required="false">
2406     !  <description>Z-component of gas velocity at the BC plane.</description>
2407     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2408              BC_W_G(LC) = UNDEFINED
2409     !</keyword>
2410     
2411     !<keyword category="Boundary Condition" required="false">
2412     !  <description>Z-component of solids-phase velocity at the BC plane.</description>
2413     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2414     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2415              BC_W_S(LC,:DIM_M) = UNDEFINED
2416     !</keyword>
2417     
2418     !<keyword category="Boundary Condition" required="false">
2419     !  <description>Gas volumetric flow rate through the boundary.</description>
2420     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2421              BC_VOLFLOW_G(LC) = UNDEFINED
2422     !</keyword>
2423     
2424     !<keyword category="Boundary Condition" required="false">
2425     !  <description>Solids volumetric flow rate through the boundary.</description>
2426     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2427     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2428              BC_VOLFLOW_S(LC,:DIM_M) = UNDEFINED
2429     !</keyword>
2430     
2431     !<keyword category="Boundary Condition" required="false">
2432     !  <description>Gas mass flow rate through the boundary.</description>
2433     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2434              BC_MASSFLOW_G(LC) = UNDEFINED
2435     !</keyword>
2436     
2437     !<keyword category="Boundary Condition" required="false">
2438     !  <description>Solids mass flow rate through the boundary.</description>
2439     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2440     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2441              BC_MASSFLOW_S(LC,:DIM_M) = UNDEFINED
2442     !</keyword>
2443     
2444     !<keyword category="Boundary Condition" required="false">
2445     !  <description>The interval at the beginning when the normal
2446     !    velocity at the boundary is equal to BC_Jet_g0. When restarting,
2447     !    run this value and BC_Jet_g0 should be specified such that the
2448     !    transient jet continues correctly. MFIX does not store the jet
2449     !    conditions. For MASS_OUTFLOW boundary conditions, BC_DT_0 is
2450     !    the time period to average and print the outflow rates. The
2451     !    adjustment of velocities to get a specified mass or volumetric
2452     !    flow rate is based on the average outflow rate.
2453     !  </description>
2454     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2455              BC_DT_0(LC) = UNDEFINED
2456     !</keyword>
2457     
2458     !<keyword category="Boundary Condition" required="false">
2459     !  <description>Value of normal velocity during the initial interval BC_DT_0.</description>
2460     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2461              BC_JET_G0(LC) = UNDEFINED
2462     !</keyword>
2463     
2464     !<keyword category="Boundary Condition" required="false">
2465     !  <description>The interval when normal velocity is equal to BC_Jet_gh.</description>
2466     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2467              BC_DT_H(LC) = UNDEFINED
2468     !</keyword>
2469     
2470     !<keyword category="Boundary Condition" required="false">
2471     !  <description>Value of normal velocity during the interval BC_DT_h.</description>
2472     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2473              BC_JET_GH(LC) = UNDEFINED
2474     !</keyword>
2475     
2476     !<keyword category="Boundary Condition" required="false">
2477     !  <description>The interval when normal velocity is equal to BC_JET_gL.</description>
2478     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2479              BC_DT_L(LC) = UNDEFINED
2480     !</keyword>
2481     
2482     !<keyword category="Boundary Condition" required="false">
2483     !  <description>Value of normal velocity during the interval BC_DT_L.</description>
2484     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2485              BC_JET_GL(LC) = UNDEFINED
2486     !</keyword>
2487     
2488     !<keyword category="Boundary Condition" required="false">
2489     !  <description>Boundary value for user-defined scalar equation.</description>
2490     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2491     !  <arg index="2" id="Scalar Eq." min="1" max="DIM_SCALAR"/>
2492              BC_Scalar(LC,:DIM_SCALAR) = UNDEFINED
2493     !</keyword>
2494     
2495     !<keyword category="Boundary Condition" required="false">
2496     !  <description>Boundary value of K for K-Epsilon Equation.</description>
2497     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2498              BC_K_Turb_G(LC) = UNDEFINED
2499     !</keyword>
2500     
2501     !<keyword category="Boundary Condition" required="false">
2502     !  <description>Boundary value of Epsilon for K-Epsilon Equation.</description>
2503     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2504              BC_E_Turb_G(LC) = UNDEFINED
2505     !</keyword>
2506     
2507     !<keyword category="Boundary Condition" required="false">
2508     !  <description>Magnitude of gas velocity in a specified boundary region.</description>
2509     !  <dependent keyword="CARTESIAN_GRID" value=".TRUE."/>
2510     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2511              BC_VELMAG_G(LC) = UNDEFINED
2512     !</keyword>
2513     
2514     !<keyword category="Boundary Condition" required="false">
2515     !  <description>Magnitude of gas velocity in a specified boundary region.</description>
2516     !  <dependent keyword="CARTESIAN_GRID" value=".TRUE."/>
2517     !  <arg index="1" id="BC" min="1" max="DIMENSION_BC"/>
2518     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2519              BC_VELMAG_S(LC,:DIM_M) = UNDEFINED
2520     !</keyword>
2521     
2522     !<keyword category="Boundary Condition" required="false">
2523     !  <description>Flag to specify the constant number
2524     ! of computational particles per cell for the PIC solids inflow BC.
2525     !Statistical weight of parcels will be calculated by the code.</description>
2526     !  <arg index="1" id="BC" min="1" max="DIMENSION_IC"/>
2527     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2528     !  <conflict keyword="BC_PIC_CONST_STATWT" value="DEFINED"/>
2529     !  <dependent keyword="SOLIDS_MODEL" value="PIC"/>
2530               BC_PIC_MI_CONST_NPC(LC, :DIM_M) = 0
2531     !</keyword>
2532     
2533     
2534     !<keyword category="Boundary Condition" required="false">
2535     !  <description>Flag to specify the constant statistical
2536     ! weight for inflowing computational particles/parcels. Actual number of
2537     ! parcels will be automatically computed. </description>
2538     !  <arg index="1" id="BC" min="1" max="DIMENSION_IC"/>
2539     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2540     !  <conflict keyword="IC_PIC_CONST_NPC" value="DEFINED"/>
2541               BC_PIC_MI_CONST_STATWT(LC, :DIM_M) = ZERO
2542     !</keyword>
2543     
2544     !<keyword category="Boundary Condition" required="false">
2545     !  <description>Flag to make the PO BC invisible to discrete solids.
2546     ! Set this flag to.FALSE.to remove this BC for discrete solids. </description>
2547     !  <arg index="1" id="BC" min="1" max="DIMENSION_IC"/>
2548              BC_PO_APPLY_TO_DES(LC) = .TRUE.
2549     !</keyword>
2550     
2551     
2552     !<keyword category="Boundary Condition" required="false">
2553     !  <description>Flag to make the inflow plane invisible to discrete solids.
2554     ! Set this flag to.FALSE.to remove to inflow plane. </description>
2555     !  <arg index="1" id="BC" min="1" max="DIMENSION_IC"/>
2556              BC_MI_AS_WALL_FOR_DES(LC)  = .TRUE.
2557     !</keyword>
2558     
2559              BC_ROP_G(LC) = UNDEFINED
2560           ENDDO
2561     
2562     
2563     
2564     
2565     !#####################################################################!
2566     !                         Internal Surfaces                           !
2567     !#####################################################################!
2568           DO LC = 1, DIMENSION_IS
2569     
2570     
2571     !<keyword category="Internal Surface" required="false">
2572     !  <description>X coordinate of the west face or edge.</description>
2573     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2574              IS_X_W(LC) = UNDEFINED
2575     !</keyword>
2576     
2577     !<keyword category="Internal Surface" required="false">
2578     !  <description>X coordinate of the east face or edge.</description>
2579     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2580              IS_X_E(LC) = UNDEFINED
2581     !</keyword>
2582     
2583     !<keyword category="Internal Surface" required="false">
2584     !  <description>Y coordinate of the south face or edge</description>
2585     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2586              IS_Y_S(LC) = UNDEFINED
2587     !</keyword>
2588     
2589     !<keyword category="Internal Surface" required="false">
2590     !  <description>Y coordinate of the north face or edge</description>
2591     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2592              IS_Y_N(LC) = UNDEFINED
2593     !</keyword>
2594     
2595     !<keyword category="Internal Surface" required="false">
2596     !  <description>Z coordinate of the bottom face or edge</description>
2597     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2598              IS_Z_B(LC) = UNDEFINED
2599     !</keyword>
2600     
2601     !<keyword category="Internal Surface" required="false">
2602     !  <description>Z coordinate of the top face or edge</description>
2603     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2604              IS_Z_T(LC) = UNDEFINED
2605     !</keyword>
2606     
2607     !<keyword category="Internal Surface" required="false">
2608     !  <description>I index of the west-most cell.</description>
2609     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2610              IS_I_W(LC) = UNDEFINED_I
2611     !</keyword>
2612     
2613     !<keyword category="Internal Surface" required="false">
2614     !  <description>I index of the east-most cell</description>
2615     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2616              IS_I_E(LC) = UNDEFINED_I
2617     !</keyword>
2618     
2619     !<keyword category="Internal Surface" required="false">
2620     !  <description>J index of the south-most cell</description>
2621     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2622              IS_J_S(LC) = UNDEFINED_I
2623     !</keyword>
2624     
2625     !<keyword category="Internal Surface" required="false">
2626     !  <description>J index of the north-most cell</description>
2627     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2628              IS_J_N(LC) = UNDEFINED_I
2629     !</keyword>
2630     
2631     !<keyword category="Internal Surface" required="false">
2632     !  <description>K index of the bottom-most cell</description>
2633     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2634              IS_K_B(LC) = UNDEFINED_I
2635     !</keyword>
2636     
2637     !<keyword category="Internal Surface" required="false">
2638     !  <description>K index of the top-most cell</description>
2639     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2640              IS_K_T(LC) = UNDEFINED_I
2641     !</keyword>
2642     
2643     !<keyword category="Internal Surface" required="false">
2644     !  <description>Type of internal surface</description>
2645     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2646     !  <valid value="IMPERMEABLE"
2647     !    note="No gas or solids flow through the surface." alias="IP"/>
2648     !  <valid value="SEMIPERMEABLE" alias='SP'
2649     !    note="Gas flows through the surface with an additional resistance.
2650     !      Solids velocity through the surface is set to zero or to a user-
2651     !      specified fixed value (i.e., solids momentum equation for this
2652     !      direction is not solved)." />
2653              IS_TYPE(LC) = UNDEFINED_C
2654     !</keyword>
2655     
2656     !<keyword category="Internal Surface" required="false">
2657     !  <description>
2658     !    Parameters defining the internal surface. These values need to be
2659     !    specified for semipermeable surfaces only. The thickness used for
2660     !    pressure drop computation is that of the momentum cell (DX_e,
2661     !    DY_n, or DZ_t). To turn off the resistance, use a large value
2662     !    for permeability. 
2663     !    o IDX=1: Permeability [1.0E32]
2664     !    o IDX=2: Inertial resistance coefficient [0.0]
2665     !  </description>
2666     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2667     !  <arg index="2" id="IDX" min="1" max="2"/>
2668              IS_PC(LC,1) = UNDEFINED
2669              IS_PC(LC,2) = ZERO
2670     !</keyword>
2671     
2672     !<keyword category="Internal Surface" required="false">
2673     !  <description>Value of fixed solids velocity through semipermeable surfaces.</description>
2674     !  <arg index="1" id="IS" min="1" max="DIMENSION_IS"/>
2675     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2676              IS_VEL_S(LC,:DIM_M) = ZERO
2677     !</keyword>
2678           ENDDO
2679     
2680     
2681     !#####################################################################!
2682     !                     Point Source Mass Inlets                        !
2683     !#####################################################################!
2684           DO LC = 1, DIMENSION_PS
2685     
2686     !<keyword category="Point Source" required="false">
2687     !  <description>X coordinate of the west face or edge.</description>
2688     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2689              PS_X_W(LC) = UNDEFINED
2690     !</keyword>
2691     
2692     !<keyword category="Point Source" required="false">
2693     !  <description>X coordinate of the east face or edge.</description>
2694     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2695              PS_X_E(LC) = UNDEFINED
2696     !</keyword>
2697     
2698     !<keyword category="Point Source" required="false">
2699     !  <description>Y coordinate of the south face or edge.</description>
2700     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2701              PS_Y_S(LC) = UNDEFINED
2702     !</keyword>
2703     
2704     !<keyword category="Point Source" required="false">
2705     !  <description>Y coordinate of the north face or edge.</description>
2706     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2707              PS_Y_N(LC) = UNDEFINED
2708     !</keyword>
2709     
2710     !<keyword category="Point Source" required="false">
2711     !  <description>Z coordinate of the bottom face or edge.</description>
2712     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2713              PS_Z_B(LC) = UNDEFINED
2714     !</keyword>
2715     
2716     !<keyword category="Point Source" required="false">
2717     !  <description>Z coordinate of the top face or edge.</description>
2718     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2719              PS_Z_T(LC) = UNDEFINED
2720     !</keyword>
2721     
2722     !<keyword category="Point Source" required="false">
2723     !  <description>I index of the west-most cell.</description>
2724     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2725              PS_I_W(LC) = UNDEFINED_I
2726     !</keyword>
2727     
2728     !<keyword category="Point Source" required="false">
2729     !  <description>I index of the east-most cell.</description>
2730     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2731              PS_I_E(LC) = UNDEFINED_I
2732     !</keyword>
2733     
2734     !<keyword category="Point Source" required="false">
2735     !  <description>J index of the south-most cell.</description>
2736     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2737              PS_J_S(LC) = UNDEFINED_I
2738     !</keyword>
2739     
2740     !<keyword category="Point Source" required="false">
2741     !  <description>J index of the north-most cell.</description>
2742     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2743              PS_J_N(LC) = UNDEFINED_I
2744     !</keyword>
2745     
2746     !<keyword category="Point Source" required="false">
2747     !  <description>K index of the bottom-most cell.</description>
2748     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2749              PS_K_B(LC) = UNDEFINED_I
2750     !</keyword>
2751     
2752     !<keyword category="Point Source" required="false">
2753     !  <description>K index of the top-most cell.</description>
2754     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2755              PS_K_T(LC) = UNDEFINED_I
2756     !</keyword>
2757     
2758     
2759     !<keyword category="Point Source" required="false">
2760     !  <description>X-component of incoming gas velocity.</description>
2761     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2762              PS_U_G(LC) = UNDEFINED
2763     !</keyword>
2764     
2765     !<keyword category="Point Source" required="false">
2766     !  <description>Y-component of incoming gas velocity.</description>
2767     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2768              PS_V_G(LC) = UNDEFINED
2769     !</keyword>
2770     
2771     !<keyword category="Point Source" required="false">
2772     !  <description>Z-component of incoming gas velocity.</description>
2773     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2774              PS_W_G(LC) = UNDEFINED
2775     !</keyword>
2776     
2777     !<keyword category="Point Source" required="false">
2778     !  <description>Gas mass flow rate through the point source.</description>
2779     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2780              PS_MASSFLOW_G(LC) = UNDEFINED
2781     !</keyword>
2782     
2783     !<keyword category="Point Source" required="false">
2784     !  <description>Temperature of incoming gas.</description>
2785     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2786              PS_T_G(LC) = UNDEFINED
2787     !</keyword>
2788     
2789     !<keyword category="Point Source" required="false">
2790     !  <description>Gas phase incoming species n mass fraction.</description>
2791     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2792              PS_X_G(LC,:DIM_N_g) = UNDEFINED
2793     !</keyword>
2794     
2795     !<keyword category="Point Source" required="false">
2796     !  <description>X-component of incoming solids velocity.</description>
2797     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2798     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2799              PS_U_S(LC,:DIM_M) = UNDEFINED
2800     !</keyword>
2801     
2802     !<keyword category="Point Source" required="false">
2803     !  <description>Y-component of incoming solids velocity.</description>
2804     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2805     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2806              PS_V_S(LC,:DIM_M) = UNDEFINED
2807     !</keyword>
2808     
2809     !<keyword category="Point Source" required="false">
2810     !  <description>Z-component of incoming solids velocity.</description>
2811     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2812     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2813              PS_W_S(LC,:DIM_M) = UNDEFINED
2814     !</keyword>
2815     
2816     !<keyword category="Point Source" required="false">
2817     !  <description>Solids mass flow rate through the point source.</description>
2818     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2819     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2820              PS_MASSFLOW_S(LC,:DIM_M) = UNDEFINED
2821     !</keyword>
2822     
2823     !<keyword category="Point Source" required="false">
2824     !  <description>Temperature of incoming solids.</description>
2825     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2826     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2827              PS_T_S(LC,:DIM_M) = UNDEFINED
2828     !</keyword>
2829     
2830     !<keyword category="Point Source" required="false">
2831     !  <description>Solids phase incoming species n mass fraction.</description>
2832     !  <arg index="1" id="PS" min="1" max="DIMENSION_PS"/>
2833     !  <arg index="2" id="Phase" min="1" max="DIM_M"/>
2834     !  <arg index="3" id="Species" min="1" max="DIM_N_S"/>
2835              PS_X_S(LC,:DIM_M,:DIM_N_S) = UNDEFINED
2836     !</keyword>
2837     
2838           ENDDO
2839     
2840     
2841     !#####################################################################!
2842     !                          Output Control                             !
2843     !#####################################################################!
2844     
2845     !<keyword category="Output Control" required="false">
2846     !  <description>Interval at which restart (.res) file is updated.</description>
2847           RES_DT = UNDEFINED
2848     !</keyword>
2849     
2850     !<keyword category="Output Control" required="false">
2851     !  <description>
2852     !    Interval at which .SPX files are updated.
2853     !    o SP1: void fraction (EP_G)
2854     !    o SP2: Gas pressure (P_G) and Solids pressure (P_star)
2855     !    o SP3: Gas velocity (U_G, V_G, W_G)
2856     !    o SP4: Solids velocity (U_S, V_S, W_S)
2857     !    o SP5: Solids bulk density (ROP_s)
2858     !    o SP6: Gas and solids temperature (T_G, T_S)
2859     !    o SP7: Gas and solids mass fractions (X_G, X_S)
2860     !    o SP8: Granular temperature (THETA_M)
2861     !    o SP9: User defined scalars. (SCALAR)
2862     !    o SPA: Reaction Rates (ReactionRates)
2863     !    o SPB: Turbulence quantities (K_TURB_G, E_TURB_G)
2864     !  </description>
2865     !  <arg index="1" id="SP Value" min="1" max="N_SPX"/>
2866           SPX_DT(:N_SPX) = UNDEFINED
2867     !</keyword>
2868     
2869     !<keyword category="Output Control" required="false">
2870     !  <description>
2871     !    The number of user defined chemical reactions stored
2872     !    in the *.SPA file.
2873     !  </description>
2874           nRR = 0
2875     !</keyword>
2876     
2877     !<keyword category="Output Control" required="false">
2878     !  <description> Interval at which standard output (.OUT) file is updated.
2879     !    Only run configuration information is written if left undefined. Otherwise
2880     !    all field variables for the entire domain are written in ASCII
2881     !    format to the .OUT file at OUT_DT intervals.
2882     !  </description>
2883           OUT_DT = UNDEFINED
2884     !</keyword>
2885     
2886     !<keyword category="Output Control" required="false">
2887     !  <description>Number of time steps between .LOG file updates.</description>
2888           NLOG = 25
2889     !</keyword>
2890     
2891     !<keyword category="Output Control" required="false">
2892     !  <description> Display the residuals on the screen and provide
2893     !    messages about convergence on the screen and in the .LOG file.
2894     !  </description>
2895           FULL_LOG = .FALSE.
2896     !</keyword>
2897     
2898     !<keyword category="Output Control" required="false">
2899     !  <description>Specifies the residuals to display. </description>
2900     !  <arg index="1" id="Residual Index" max="8" min="1"/>
2901     !  <valid value="P0" note="Gas pressure"/>
2902     !  <valid value="PM" note="Solids phase M pressure"/>
2903     !  <valid value="R0" note="Gas density"/>
2904     !  <valid value="RM" note="Solids phase M density"/>
2905     !  <valid value="U0" note="Gas phase U-velocity"/>
2906     !  <valid value="V0" note="Gas phase V-velocity"/>
2907     !  <valid value="W0" note="Gas phase W-velocity"/>
2908     !  <valid value="UM" note="Solids phase M U-velocity"/>
2909     !  <valid value="VM" note="Solids phase M V-velocity"/>
2910     !  <valid value="WM" note="Solids phase M W-velocity"/>
2911     !  <valid value="T0" note="Gas temperature"/>
2912     !  <valid value="TM" note="Solids phase M temperature"/>
2913     !  <valid value="X0NN" note="Gas phase species NN mass fraction"/>
2914     !  <valid value="XMNN" note="Solids phase M species NN mass fraction"/>
2915     !  <valid value="K0" note="K-Epsilon model residuals"/>
2916           RESID_STRING(:8) = UNDEFINED_C
2917     !</keyword>
2918     
2919     !<keyword category="Output Control" required="false">
2920     !  <description>Display residuals by equation.  </description>
2921           GROUP_RESID = .FALSE.
2922     !</keyword>
2923     
2924     
2925     !<keyword category="Output Control" required="false">
2926     !  <description>
2927     !    Provide detailed logging of negative density errors.
2928     !  </description>
2929     !  <valid value=".FALSE." note="Do not log negative density errors."/>
2930     !  <valid value=".TRUE." note="Log negative density errors."/>
2931           REPORT_NEG_DENSITY = .FALSE.
2932     !</keyword>
2933     
2934     !<keyword category="Output Control" required="false">
2935     !  <description>
2936     !    Frequency to perform an overall species mass balance. Leaving
2937     !    undefined suppresses the mass balance calculations which can
2938     !    slightly extend run time.
2939     !  </description>
2940           REPORT_MASS_BALANCE_DT = UNDEFINED
2941     !</keyword>
2942     
2943     !<keyword category="Output Control" required="false">
2944     !  <description>
2945     !    Output the variable specularity coefficient when BC_JJ_M is
2946     !    .TRUE.. The specularity coefficient will be stored in ReactionRates
2947     !    array for post-processing by post-mfix. User needs to set NRR to 1
2948     !    for this purpose. Be careful with this setting when reacting flow
2949     !    is simulated.
2950     !  </description>
2951           PHIP_OUT_JJ=.FALSE.
2952     !</keyword>
2953     
2954     !<keyword category="Output Control" required="false">
2955     !  <description>
2956     !    Use distributed IO :: Each MPI process generates RES/SPx files.
2957     !  </description>
2958           bDist_IO = .FALSE.
2959     !</keyword>
2960     
2961     !<keyword category="Output Control" required="false">
2962     !  <description>
2963     !    Restart a serial IO run (only one RES file was created) with
2964     !    distributed IO.
2965     !  </description>
2966     !  <dependent keyword="RUN_TYPE" value="RESTART_2"/>
2967     !  <dependent keyword="bDist_IO" value=".TRUE."/>
2968           bStart_with_one_RES = .FALSE.
2969     !</keyword>
2970     
2971     !<keyword category="Output Control" required="false">
2972     !  <description>
2973     !    Flag to write variable in NetCDF output file. NetCDF support is not
2974     !    included in MFIX by default. The executable must be compiled and
2975     !    linked with an appropriate NetCDF library to use this functionality.
2976     !
2977     !    Variable Index List:
2978     !     1: void fraction (EP_G)
2979     !     2: Gas pressure (P_G)
2980     !     3: Solids pressure (P_star)
2981     !     4: Gas velocity (U_G, V_G, W_G)
2982     !     5: Solids velocity (U_S, V_S, W_S)
2983     !     6: Solids bulk density (ROP_s)
2984     !     7: Gas temperature (T_G)
2985     !     8: Gas and solids temperature (T_S)
2986     !     9: Gas mass fractions (X_G)
2987     !    10: Solids mass fractions (X_S)
2988     !    11: Granular temperature (THETA_M)
2989     !    12: User defined scalars. (SCALAR)
2990     !    13: Reaction Rates (ReactionRates)
2991     !    14: Turbulence quantities (K_TURB_G, E_TURB_G)
2992     !  </description>
2993     !  <arg index="1" id="NetCDF Variable Reference" max="20" min="1"/>
2994     !  <valid value=".TRUE." note="Write variable in NetCDF output."/>
2995     !  <valid value=".FALSE." note="Do not include variable in NetCDF output."/>
2996           bWrite_netCDF(:20) = .FALSE.
2997     !</keyword>
2998     
2999     
3000     !#####################################################################!
3001     !                           UDF  Control                              !
3002     !#####################################################################!
3003     
3004     !<keyword category="UDF Control" required="false">
3005     !  <description>
3006     !    Flag to enable user-defined subroutines: USR0, USR1, USR2, USR3,
3007     !    USR0_DES, USR1_DES, USR2_DES, USR3_DES, USR4_DES.
3008     !  </description>
3009     !  <valid value=".TRUE." note="Call user-defined subroutines."/>
3010     !  <valid value=".FALSE." note="Do NOT call user-defined subroutines."/>
3011           CALL_USR = .FALSE.
3012     !</keyword>
3013     
3014     !<keyword category="UDF Control" required="false">
3015     !  <description>User defined constants.</description>
3016           C(:DIMENSION_C) = UNDEFINED
3017     !</keyword>
3018     
3019     !<keyword category="UDF Control" required="false">
3020     !  <description>Name of user-defined constant. (20 character max)</description>
3021           C_NAME(:DIMENSION_C) = '....................'
3022     !</keyword>
3023     
3024           DO LC=1, DIMENSION_USR
3025     !<keyword category="UDF Control" required="false">
3026     !  <description>
3027     !    Intervals at which subroutine write_usr1 is called.
3028     !  </description>
3029     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3030              USR_DT(LC) = UNDEFINED
3031     !</keyword>
3032     
3033     !<keyword category="UDF Control" required="false">
3034     !  <description>Udf Hook: x coordinate of the west face or edge.</description>
3035     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3036              USR_X_W(LC) = UNDEFINED
3037     !</keyword>
3038     
3039     !<keyword category="UDF Control" required="false">
3040     !  <description>Udf Hook: x coordinate of the east face or edge.</description>
3041     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3042              USR_X_E(LC) = UNDEFINED
3043     !</keyword>
3044     
3045     !<keyword category="UDF Control" required="false">
3046     !  <description>Udf Hook: y coordinate of the south face or edge.</description>
3047     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3048              USR_Y_S(LC) = UNDEFINED
3049     !</keyword>
3050     
3051     !<keyword category="UDF Control" required="false">
3052     !  <description>Udf Hook: y coordinate of the north face or edge.</description>
3053     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3054              USR_Y_N(LC) = UNDEFINED
3055     !</keyword>
3056     
3057     !<keyword category="UDF Control" required="false">
3058     !  <description>Udf Hook: z coordinate of the bottom face or edge.</description>
3059     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3060              USR_Z_B(LC) = UNDEFINED
3061     !</keyword>
3062     
3063     !<keyword category="UDF Control" required="false">
3064     !  <description>Udf Hook: z coordinate of the top face or edge.</description>
3065     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3066              USR_Z_T(LC) = UNDEFINED
3067     !</keyword>
3068     
3069     !<keyword category="UDF Control" required="false">
3070     !  <description>Udf Hook: i index of the west-most cell.</description>
3071     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3072              USR_I_W(LC) = UNDEFINED_I
3073     !</keyword>
3074     
3075     !<keyword category="UDF Control" required="false">
3076     !  <description>Udf Hook: i index of the east-most cell.</description>
3077     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3078              USR_I_E(LC) = UNDEFINED_I
3079     !</keyword>
3080     
3081     !<keyword category="UDF Control" required="false">
3082     !  <description>Udf Hook: j index of the south-most cell.</description>
3083     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3084              USR_J_S(LC) = UNDEFINED_I
3085     !</keyword>
3086     
3087     !<keyword category="UDF Control" required="false">
3088     !  <description>Udf Hook: j index of the north-most cell.</description>
3089     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3090              USR_J_N(LC) = UNDEFINED_I
3091     !</keyword>
3092     
3093     !<keyword category="UDF Control" required="false">
3094     !  <description>Udf Hook: k index of the bottom-most cell.</description>
3095     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3096              USR_K_B(LC) = UNDEFINED_I
3097     !</keyword>
3098     
3099     !<keyword category="UDF Control" required="false">
3100     !  <description>Udf Hook: k index of the top-most cell.</description>
3101     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3102              USR_K_T(LC) = UNDEFINED_I
3103     !</keyword>
3104     
3105     !<keyword category="UDF Control" required="false">
3106     !  <description>Udf Hook: Type of user-defined output: Binary of ASCII.</description>
3107     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3108              USR_TYPE(LC) = UNDEFINED_C
3109     !</keyword>
3110     
3111     !<keyword category="UDF Control" required="false">
3112     !  <description>Udf Hook:
3113     !    Variables to be written in the user-defined output files.
3114     !  </description>
3115     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3116              USR_VAR(LC) = UNDEFINED_C
3117     !</keyword>
3118     
3119     !<keyword category="UDF Control" required="false">
3120     !  <description>Udf Hook:
3121     !    Format for writing user-defined (ASCII) output file.
3122     !  </description>
3123     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3124              USR_FORMAT(LC) = UNDEFINED_C
3125     !</keyword>
3126     
3127     !<keyword category="UDF Control" required="false">
3128     !  <description>Udf Hook: File extension for the user-defined output.</description>
3129     !  <arg index="1" id="USR" max="DIMENSION_USR" min="1"/>
3130              USR_EXT(LC) = UNDEFINED_C
3131     !</keyword>
3132           ENDDO
3133     
3134     
3135     !#####################################################################!
3136     !                        Chemical Reactions                           !
3137     !#####################################################################!
3138     
3139     
3140     !<keyword category="Chemical Reactions" required="false">
3141     !  <description>Flag to use stiff chemistry solver (Direct Integration).</description>
3142     !  <conflict keyword="USE_RRATES" value=".TRUE."/>
3143           STIFF_CHEMISTRY = .FALSE.
3144     !</keyword>
3145     
3146     !<keyword category="Chemical Reactions" required="false">
3147     !  <description>
3148     !    Maximum number of internal steps ODEPACK may use to integrate
3149     !    over the time interval. Leaving this value unspecified permits
3150     !    an unlimited number of steps. The stiff solver reports the
3151     !    number of cells that exceed the number of steps as 'incomplete'.
3152     !  </description>
3153     !  <dependent keyword="STIFF_CHEMISTRY" value=".TRUE."/>
3154     !  <conflict keyword="USE_RRATES" value=".TRUE."/>
3155           STIFF_CHEM_MAX_STEPS = UNDEFINED_I
3156     !</keyword>
3157     
3158     !<keyword category="Chemical Reactions" required="false">
3159     !  <description>Flag to use legacy chemical reaction UDFs.</description>
3160           USE_RRATES = .FALSE.
3161     !</keyword>
3162     
3163     !<keyword category="Chemical Reactions" required="false" legacy=.TRUE.>
3164     !  <description>
3165     !    Names of gas and solids phase species as it appears in the
3166     !    materials database. The first NMAX(0) are the names of gas
3167     !    species. The next NMAX(1) are the names of solids phase-1
3168     !    species, etc.
3169     !  </description>
3170     !  <dependent keyword="USE_RRATES" value=".TRUE."/>
3171           SPECIES_NAME(:DIM_N_ALL) = UNDEFINED_C
3172     !</keyword>
3173     
3174     !<keyword category="Chemical Reactions" required="false">
3175     !  <description>
3176     !    Number of species in phase m. Note that the gas phase is indicated
3177     !    as m=0.
3178     !  </description>
3179     !  <dependent keyword="USE_RRATES" value=".TRUE."/>
3180           NMAX = UNDEFINED_I
3181     !</keyword>
3182     
3183     
3184     !#####################################################################!
3185     !                    Parallelization Control                          !
3186     !#####################################################################!
3187     
3188     
3189     !<keyword category="Parallelization Control" required="false">
3190     !  <description>Number of grid blocks in x-direction.</description>
3191           NODESI = UNDEFINED_I
3192     !</keyword>
3193     
3194     !<keyword category="Parallelization Control" required="false">
3195     !  <description>Number of grid blocks in y-direction.</description>
3196           NODESJ = UNDEFINED_I
3197     !</keyword>
3198     
3199     !<keyword category="Parallelization Control" required="false">
3200     !  <description>Number of grid blocks in z-direction.</description>
3201           NODESK = UNDEFINED_I
3202     !</keyword>
3203     
3204     !<keyword category="Parallelization Control" required="false">
3205     !  <description>Print out additional statistics for parallel runs</description>
3206           solver_statistics = .FALSE.
3207     !</keyword>
3208     
3209     !<keyword category="Parallelization Control" required="false">
3210     !  <description>Group residuals to reduce global collectives.</description>
3211           DEBUG_RESID = .TRUE.
3212     !</keyword>
3213     
3214     !<keyword category="Parallelization Control" required="false">
3215     !  <description>All ranks write error messages.</description>
3216           ENABLE_DMP_LOG = .FALSE.
3217     !</keyword>
3218     
3219     !<keyword category="Parallelization Control" required="false">
3220     !  <description>Print the index layout for debugging.</description>
3221           DBGPRN_LAYOUT = .FALSE.
3222     !</keyword>
3223     
3224     
3225     !#####################################################################!
3226     !                       Batch Queue Environment                       !
3227     !#####################################################################!
3228     
3229     
3230     !<keyword category="Batch Queue Environment" required="false">
3231     !  <description>
3232     !    Enables controlled termination feature when running under batch
3233     !    queue system to force MFIX to cleanly terminate before the end
3234     !    of wall clock allocated in the batch session.
3235     !  </description>
3236           CHK_BATCHQ_END = .FALSE.
3237     !</keyword>
3238     
3239     !<keyword category="Batch Queue Environment" required="false">
3240     !  <description>Total wall-clock duration of the job, in seconds.</description>
3241           BATCH_WALLCLOCK = 9000.0    ! set to 2.5 hrs for jaguarcnl w/ nproc<=512
3242     !</keyword>
3243     
3244     !<keyword category="Batch Queue Environment" required="false">
3245     !  <description>
3246     !    Buffer time specified to allow MFIX to write out the files and
3247     !    cleanly terminate before queue wall clock time limit is reached
3248     !    such that (BATCH_WALLCLOCK-TERM_BUFFER) is less than then batch
3249     !    queue wall clock time limit, in seconds.
3250     !  </description>
3251           TERM_BUFFER = 180.0         ! set to 3 minutes prior to end of job
3252     !</keyword>
3253     
3254     
3255     
3256     !#####################################################################!
3257     !          Direct Quadrature Method of Moments (DQMOM)                !
3258     !#####################################################################!
3259     
3260     
3261     !<keyword category="Direct Quadrature Method of Moments (DQMOM)" required="false">
3262     !  <description>Variable to decide if the population balance equations are solved.</description>
3263           Call_DQMOM = .FALSE.
3264     !</keyword>
3265     
3266     !<keyword category="Direct Quadrature Method of Moments (DQMOM)" required="false">
3267     !  <description>Success-factor for aggregation.</description>
3268           AGGREGATION_EFF=0.D0
3269     !</keyword>
3270     
3271     !<keyword category="Direct Quadrature Method of Moments (DQMOM)" required="false">
3272     !  <description>Success-factor for breakage.</description>
3273           BREAKAGE_EFF=0.D0
3274     !</keyword>
3275     
3276     
3277     
3278     
3279     
3280     
3281     
3282     
3283     ! ---------------------------------- questionable namelist entries below
3284     
3285     
3286     
3287     
3288     
3289     
3290     
3291     
3292     !<keyword category="category name" required="false">
3293     !  <description>Variable which triggers an automatic restart.</description>
3294           AUTOMATIC_RESTART = .FALSE.
3295     !</keyword>
3296     
3297     !<keyword category="category name" required="false">
3298     !  <description>AUTO_RESTART counter.</description>
3299           ITER_RESTART = 1
3300     !</keyword>
3301     
3302     
3303     
3304     ! NO_OF_RXNS is not a keyword. However, it is initialized here so that
3305     ! if there are no reactions, this value is assigned.
3306           NO_OF_RXNS = UNDEFINED_I
3307     
3308     
3309           U_G0 = UNDEFINED
3310           V_G0 = UNDEFINED
3311           W_G0 = UNDEFINED
3312           U_S0(:DIM_M) = UNDEFINED
3313           V_S0(:DIM_M) = UNDEFINED
3314           W_S0(:DIM_M) = UNDEFINED
3315     
3316     
3317           PHIP_OUT_ITER=0
3318     
3319     
3320     
3321     
3322     
3323           CALL DES_INIT_NAMELIST
3324     
3325           CALL QMOMK_INIT_NAMELIST
3326     
3327           CALL USR_INIT_NAMELIST
3328     
3329           CALL CARTESIAN_GRID_INIT_NAMELIST
3330     
3331           RETURN
3332           END SUBROUTINE INIT_NAMELIST
3333