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