File: N:\mfix\model\des\des_init_namelist.f

1     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2     !                                                                         C
3     !     Module name: DES_INIT_NAMELIST                                      C
4     !     Purpose: DES - initialize the des-namelist                          C
5     !                                                                         C
6     !     Reviewer: Rahul Garg                               Date: 01-Aug-07  C
7     !     Comments: Added some interpolation based inputs                     C
8     !                                                                         C
9     !  Keyword Documentation Format:                                          C
10     !<keyword category="category name" required="true/false"                  C
11     !                                    legacy="true/false">                 C
12     !  <description></description>                                            C
13     !  <arg index="" id="" max="" min=""/>                                    C
14     !  <dependent keyword="" value="DEFINED"/>                                C
15     !  <conflict keyword="" value="DEFINED"/>                                 C
16     !  <valid value="" note="" alias=""/>                                     C
17     !  <range min="" max="" />                                                C
18     !  MFIX_KEYWORD=INIT_VALUE                                                C
19     !</keyword>                                                               C
20     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
21     
22           SUBROUTINE DES_INIT_NAMELIST
23     
24           USE param1
25           USE discretelement
26           USE mfix_pic
27           USE des_bc
28           USE des_thermo
29           USE des_rxns
30           USE pic_bc
31           USE particle_filter
32     
33           IMPLICIT NONE
34     !-----------------------------------------------
35     ! Local variables
36     !-----------------------------------------------
37     
38     !-----------------------------------------------
39     
40           INCLUDE 'desnamelist.inc'
41     
42     
43     
44     !#####################################################################!
45     !                             Run Control                             !
46     !#####################################################################!
47     
48     
49     
50     
51     !#####################################################################!
52     !                           Physical Parameters                       !
53     !#####################################################################!
54     
55     
56     
57     !#####################################################################!
58     !                          Numerical Parameters                       !
59     !#####################################################################!
60     
61     
62     
63     !#####################################################################!
64     !                          Output Control                             !
65     !#####################################################################!
66     
67     !<keyword category="Output Control" required="false"
68     !  dem="true" pic="true">
69     !  <description>
70     !    Reports mass based on Lagrangian particles and continuum
71     !    representation. Useful to ensure mass conservation between
72     !    Lagrangian and continuum representations. Recommended use for
73     !    debugging purposes.
74     !  </description>
75     !  <dependent keyword="DES_INTERP_MEAN_FIELDS" value=".TRUE."/>
76           DES_REPORT_MASS_INTERP = .FALSE.
77     !</keyword>
78     
79     !<keyword category="Output Control" required="false"
80     !  dem="true" pic="true">
81     !  <description>
82     !    Allows writing of discrete particle data to output files. Relevant
83     !    to both granular and coupled simulations.
84     !  </description>
85           PRINT_DES_DATA = .FALSE.
86     !</keyword>
87     
88     !<keyword category="Output Control" required="false">
89     !  <description>
90     !    Directory where particle vtp files are stored. The files are
91     !    written in the run directory by default.
92     !  </description>
93     !  <dependent keyword="CARTESIAN_GRID" value=".TRUE."/>
94           VTP_DIR = '.'
95     !</keyword>
96     
97     !<keyword category="Output Control" required="false"
98     !   dem="true" pic="true">
99     !  <description> The output file format for DES data.</description>
100     !  <valid value="PARAVIEW" note="ParaView formatted files (.vtp)"/>
101     !  <valid value="TECPLOT" note="Tecplot formatted files (.dat)"/>
102           DES_OUTPUT_TYPE = "PARAVIEW"
103     !</keyword>
104     
105     !<keyword category="Output Control" required="false"
106     !  dem="true" pic="true">
107     !  <description>
108     !    Runtime flag to generate debugging information. Additional data for
109     !    FOCUS_PARTICLE is saved.
110     !  </description>
111           DEBUG_DES = .FALSE.
112     !</keyword>
113     
114     !<keyword category="Output Control" required="false" dem="true" pic="true">
115     !  <description>
116     !    Specify particle number for particle level debugging details.
117     !  </description>
118     !  <dependent keyword="DEBUG_DES" value=".TRUE."/>
119           FOCUS_PARTICLE = 0
120     !</keyword>
121     
122     !<keyword category="Output Control" required="false" pic="true">
123     !  <description>
124     !    Flag to print processor level parcel seeding statistics for inflow
125     !    BC with PIC model.
126     !  </description>
127     !  <dependent keyword="MPPIC" value=".TRUE."/>
128           PIC_REPORT_SEEDING_STATS = .false.
129     !</keyword>
130     
131     !<keyword category="Output Control" required="false" pic="true">
132     !  <description>
133     !     Flag to print processor level parcel deletion statistics for
134     !     outflow BC with PIC model. Not recommended for production runs.
135     !  </description>
136     !  <dependent keyword="MPPIC" value=".TRUE."/>
137           PIC_REPORT_DELETION_STATS = .false.
138     !</keyword>
139     
140     
141     
142     
143     !#####################################################################!
144     ! DEM/PIC COMMON:      Discrete Element Simulation                    !
145     !#####################################################################!
146     
147     
148     !<keyword category="Discrete Element Simulation" required="false"
149     !  dem="true" pic="true">
150     !  <description>
151     !    Number of particles to be read in from the particle_input.dat file.
152     !    This value is overwritten when using automatic particle generation.
153     !    A simulation with a mass inflow BC can start without solids by
154     !    setting PARTICLES = 0.
155     !  </description>
156     !  <range min="0" max="+Inf" />
157           PARTICLES = UNDEFINED_I
158     !</keyword>
159     
160     !<keyword category="Discrete Element Simulation" required="false"
161     !  dem="true" pic="true">
162     !  <description>
163     !    Automatically generate the initial particle position and velocity
164     !    data based on the parameters specified for each initial condition
165     !    (IC) region.
166     !  </description>
167     !  <valid value=".TRUE." note="Generate particle configuration based
168     !    on the initial condition parameters. Data provided in the
169     !    particle_input.dat file, if present, is ignored. "/>
170     !  <valid value=".FALSE." note="Particle position and velocity data are
171     !    provided in the particle_input.dat file. A runtime error occurs if
172     !    this file is not provided."/>
173           GENER_PART_CONFIG = .FALSE.
174     !</keyword>
175     
176     !<keyword category="Discrete Element Simulation" required="false"
177     !  dem="true" pic="true">
178     !  <description>
179     !    To switch between pure granular or coupled simulations of carried
180     !    and dispersed phase flows.
181     !  </description>
182     !  <valid value=".true." note="Performs coupled simulations. "/>
183           DES_CONTINUUM_COUPLED = .FALSE.
184     !</keyword>
185     
186     !<keyword category="Discrete Element Simulation" required="false"
187     !  dem="true" pic="true">
188     !  <description>Run one-way coupled simulations. The fluid does not
189     ! see the particles in terms of drag force. The effect of particle volume
190     ! is still felt by the fluid through non-unity voidage values.
191     ! </description>
192           DES_ONEWAY_COUPLED = .FALSE.
193     !</keyword>
194     
195     !<keyword category="Discrete Element Simulation" required="false" dem="true">
196     !  <description>
197     !    Time stepping scheme.
198     !  </description>
199     !  <valid value="EULER"
200     !    note="First-Order Euler Scheme."/>
201     !  <valid value="ADAMS BASHFORTH"
202     !    note="Second order ADAMS BASHFORTH scheme (DEM only)"/>
203           DES_INTG_METHOD = 'EULER'
204     !</keyword>
205     
206     !<keyword category="Discrete Element Simulation" required="false" dem="true">
207     !  <description>
208     !    Defines the size of the particle-based user variable:
209     !    DES_USR_VAR(SIZE, PARTICLES). Information in this array follows
210     !    the particle throughout a simulation.
211     !  </description>
212           DES_USR_VAR_SIZE = 0
213     !</keyword>
214     
215     !<keyword category="Discrete Element Simulation" required="false"
216     !  dem="true" pic="true">
217     !  <description>
218     !    Number of des grid cells in the I-direction. If left undefined,
219     !    then it is set by MFIX such that its size equals three times the
220     !    maximum particle diameter with a minimum of 1 cell.
221     !  </description>
222           DESGRIDSEARCH_IMAX = UNDEFINED_I
223     !</keyword>
224     
225     !<keyword category="Discrete Element Simulation" required="false"
226     !  dem="true" pic="true">
227     !  <description>
228     !    Number of des grid cells in the J-direction. If left undefined,
229     !    then it is set by MFIX such that its size equals three times
230     !    the maximum particle diameter with a minimum of 1 cell.
231     !  </description>
232           DESGRIDSEARCH_JMAX = UNDEFINED_I
233     !</keyword>
234     
235     !<keyword category="Discrete Element Simulation" required="false"
236     !  dem="true" pic="true">
237     !  <description>
238     !    Number of des grid cells in the K-direction. If left undefined,
239     !    then it is set by MFIX such that its size equals three times
240     !    the maximum particle diameter with a minimum of 1 cell.
241     !  </description>
242           DESGRIDSEARCH_KMAX = UNDEFINED_I
243     !</keyword>
244     
245     !<keyword category="Discrete Element Simulation" required="false"
246     !  dem="true" pic="true">
247     !  <description>
248     !    Specify the scheme used to map data to/from a particle's position
249     !    and the Eulerian grid. This keyword is required when
250     !    DES_INTERP_MEAN_FIELDS and/or DES_INTERP_ON are specified. A
251     !    graphical representation of the schemes is shown below.
252     !  </description>
253     !  <valid value="NONE" note="Do not use interpolation."/>
254     !  <valid value="GARG_2012" note="Interpolate to/from a particle's
255     !    position using the corners (nodes) of the fluid cells. This was
256     !    the default behavior prior to the 2015-1 Release.
257     !    See Garg et al. (2012) Documentation of the open-souce MFIX-DEM
258     !    software for gas-solids flows."/>
259     !  <valid value="SQUARE_DPVM" note="Divided Particle Volume Method:
260     !    Information is interpolated to/from a particles position using
261     !    a square filter of size DES_INTERP_WIDTH."/>
262     !  <valid value="LINEAR_HAT" note="Linear interpolation: Hat funtions
263     !    are used to distribute particle information."/>
264           DES_INTERP_SCHEME = 'NONE'
265     !</keyword>
266     
267     !<keyword category="Discrete Element Simulation" required="false" dem="true">
268     !  <description>
269     !    The length used in interpolating data to/from a particle's position
270     !    and the Eulerian grid. The interpolation width is only applicable
271     !    to the DPVM_SQUARE and DPVM_GAUSS interpolation schemes as the
272     !    GARG_2012 scheme's interpolation width is determined by the
273     !    Eulerian grid dimensions.
274     !    o The interpolation half-width cannot exceed the minimum cell
275     !      dimension because interpolation is restricted to the 27-cell
276     !      neighborhood surrounding a particle (9-cell neighborhood in 2D).
277     !    o It is recommend that the DES_INTERP_WIDTH be set equal to the
278     !      maximum particle diameter when using STL defined boundaries.
279     !      Field data can be smooth by specifying DES_DIFFUSE_WIDTH.
280     !  </description>
281           DES_INTERP_WIDTH = UNDEFINED
282     !</keyword>
283     
284     
285     !<keyword category="Discrete Element Simulation" required="false"
286     !  dem="true" pic="true">
287     !  <description>
288     !    Enables/Disables interpolation of field quantities to a particle's
289     !    position. This is used in calculating gas-particle interactions,
290     !    such as the drag force.
291     !  </description>
292     !  <valid value=".FALSE." note="Use fluid values from the cell containing
293     !    the particle's center."/>
294     !  <valid value=".TRUE." note="Interpolate fluid values from the 27-cell
295     !    neighborhood to a particle's position."/>
296           DES_INTERP_ON = .FALSE.
297     !</keyword>
298     
299     !<keyword category="Discrete Element Simulation" required="false"
300     !  dem="true" pic="true">
301     !  <description>
302     !    Enables/Disables interpolation of particle data (e.g., solids
303     !    volume and drag force) from a particle's position to the
304     !    Eulerian grid.
305     !  </description>
306     !  <valid value=".FALSE." note="Assign particle data to the fluid
307     !    grid cell containing the particle's center."/>
308     !  <valid value=".TRUE." note="Interpolate particle data from the
309     !    particle's position to the 27-cell neighborhood surrounding
310     !    the particle."/>
311           DES_INTERP_MEAN_FIELDS = .FALSE.
312     !</keyword>
313     
314     
315     !<keyword category="Discrete Element Simulation" required="false" dem="true">
316     !  <description>
317     !    The length scale used to smooth dispersed phase averaged fields by
318     !    solving a diffusion equation. This approach is typically used when
319     !    particle sizes near or exceed the size of the Eulerian grid cell sizes.
320     !    o  Mean filed diffusion is disabled if DES_DIFFUSE_WIDTH is not specified.
321     !    o  Mean filed diffusion cannot be used with the GARG_2012
322     !       interpolation scheme.
323     !    o  It is recommend that mean field diffusion be used in conjunction
324     !       with DES_EXPLICITLY_COUPLED to minimize the computational cost of
325     !       diffusing field data.
326     !    o  The DES diffusion equation is listed as equation type 10 in the
327     !       Numerical Parameters section.
328     !  </description>
329           DES_DIFFUSE_WIDTH = UNDEFINED
330     !</keyword>
331     
332     
333     !<keyword category="Discrete Element Simulation" required="false" dem="true">
334     !  <description>
335     !    Enable/Disable explicit coupling of DEM solids and the fluid. This
336     !    algorithm is presently limited to hydrodynamic simulations.
337     !  </description>
338     !  <valid value=".FALSE." note="The fluid and particles calculate
339     !    interphase forces at their respective time scales. The fluid phase
340     !    calculates the interphase coupling forces once per fluid time step.
341     !    Similarly, DEM particles calculate the interface coupling forces at
342     !    each solids time-step. The DEM must also bin particles to the fluid
343     !    grid and recalculate the fluid volume fraction every time-step."/>
344     !  <valid value=".TRUE." note="Interphase forces are calculated during
345     !    the fluid time step and stored for each particle. The interphase
346     !    forces are then distributed among the solids time-steps. This
347     !    approach can substantially reduce the computational overhead for
348     !    coupled simulations."/>
349           DES_EXPLICITLY_COUPLED = .FALSE.
350     !</keyword>
351     
352     
353     !#####################################################################!
354     ! DEM ONLY:            Discrete Element Model                         !
355     !#####################################################################!
356     
357     !<keyword category="Discrete Element Model" required="false">
358     !  <description>
359     !    The number of iterations of a pure granular simulation to let
360     !    the initial particle configuration settle before a coupled
361     !    gas-solid is started.
362     !  </description>
363     !  <range min="0" max="+Inf" />
364           NFACTOR = 0
365     !</keyword>
366     
367     !<keyword category="Discrete Element Model" required="false">
368     !  <description>
369     !    Maximum number of steps through a DEM loop before a neighbor
370     !    search will be performed. The search may be called earlier
371     !    based on other logic.
372     !  </description>
373     !  <range min="0.0" max="+Inf" />
374           NEIGHBOR_SEARCH_N = 25
375     !</keyword>
376     
377     !<keyword category="Discrete Element Model" required="false">
378     !  <description>
379     !    Flag to set the neighbor search algorithm.
380     !  </description>
381     !  <valid value="1" note="N-Square search algorithm (most expensive)"/>
382     !  <valid value="4" note="Grid-Based Neighbor Search (Recommended)"/>
383           DES_NEIGHBOR_SEARCH = 4
384     !</keyword>
385     
386     
387     !<keyword category="Discrete Element Model" required="false">
388     !  <description>
389     !    Ratio of the distance (imaginary sphere radius) to particle radius
390     !    that is allowed before a neighbor search is performed. This works
391     !    in conjunction with the logic imposed by NEIGHBOR_SEARCH_N in
392     !    deciding calls to the neighbor search algorithm.
393     !  </description>
394           NEIGHBOR_SEARCH_RAD_RATIO = 1.0D0
395     !</keyword>
396     
397     
398     !<keyword category="Discrete Element Model" required="false">
399     !  <description>
400     !    Effectively increase the radius of a particle (multiple of the sum
401     !    of particle radii) during the building of particle neighbor list.
402     !  </description>
403           FACTOR_RLM = 1.2
404     !</keyword>
405     
406     !<keyword category="Discrete Element Model" required="false">
407     !  <description>
408     !    Flag to use van der Hoef et al. (2006) model for adjusting the
409     !    rotation of the contact plane. See the MFIX-DEM documentation.
410     !  </description>
411           USE_VDH_DEM_MODEL = .FALSE.
412     !</keyword>
413     
414     
415     !<keyword category="Discrete Element Model" required="false">
416     !  <description>
417     !    Collision model for the soft-sphere approach used in DEM model.
418     !    All models require specifying the following parameters: DES_EN_INPUT,
419     !    DES_EN_WALL_INPUT, MEW, and MEW_W.
420     !  </description>
421     !  <valid value="LSD" note="The linear spring-dashpot model.
422     !    Requires: KN, KN_W, KT_FAC, KT_W_FAC, DES_ETAT_FAC, DES_ETAT_W_FAC."/>
423     !  <valid value="HERTZIAN" note="The Hertzian model.
424     !    Requires: DES_ET_INPUT, DES_ET_WALL_INPUT, E_YOUNG, EW_YOUNG
425     !    V_POISSON, VW_POISSON."/>
426           DES_COLL_MODEL = 'LSD'
427     !</keyword>
428     
429     
430     !<keyword category="Discrete Element Model" required="false" dem="true">
431     !  <description>
432     !    Normal spring constant [dyne/cm in CGS] for inter-particle collisions.
433     !    Required when using the linear spring-dashpot collision model.
434     !  </description>
435           KN = UNDEFINED
436     !</keyword>
437     
438     
439     !<keyword category="Discrete Element Model" required="false" dem="true">
440     !  <description>
441     !    Ratio of the tangential spring constant to normal spring constant
442     !    for inter-particle collisions. Use it to specify the tangential
443     !    spring constant for particle-particle collisions as KT_FAC*KN.
444     !    Required when using the linear spring-dashpot collision model.
445     !  </description>
446     !  <dependent keyword="DES_COLL_MODEL" value="LSD"/>
447     !  <range min="0.0" max="1.0" />
448           KT_FAC = 2.d0/7.d0
449     !</keyword>
450     
451     
452     !<keyword category="Discrete Element Model" required="false" dem=.true.>
453     !  <description>
454     !    Normal spring constant [dyne/cm in CGS] for particle-wall collisions.
455     !    Required when using the linear spring-dashpot collision model.
456     !  </description>
457           KN_W = UNDEFINED
458     !</keyword>
459     
460     
461     !<keyword category="Discrete Element Model" required="false" dem="true">
462     !  <description>
463     !    Ratio of the tangential spring constant to normal spring constant
464     !    for particle-wall collisions. Use it to specify the tangential
465     !    spring constant for particle-wall collisions as KT_W_FAC*KN_W.
466     !    Required when using the linear spring-dashpot collision model.
467     !  </description>
468     !  <dependent keyword="DES_COLL_MODEL" value="LSD"/>
469     !  <range min="0.0" max="1.0" />
470           KT_W_FAC = 2.d0/7.d0
471     !</keyword>
472     
473     !<keyword category="Discrete Element Model" required="false" dem="true"
474     !  <description>
475     !    Inter-particle Coulomb friction coefficient.
476     !  </description>
477     ! <range min="0.0" max="1.0" />
478           MEW = UNDEFINED
479     !</keyword>
480     
481     !<keyword category="Discrete Element Model" required="false">
482     !  <description>
483     !    Particle-wall Coulomb friction coefficient.
484     !  </description>
485     ! <range min="0.0" max="1.0" />
486           MEW_W = UNDEFINED
487     !</keyword>
488     
489     
490     !<keyword category="Discrete Element Model" required="false" dem="true">
491     !  <description>
492     !    The normal restitution coefficient for inter-particle collisions
493     !    used to determine the inter-particle normal damping factor.
494     !
495     !    Values should be defined for a single dimensional array. For
496     !    example, a simulation with three solids phases (MMAX=3) needs
497     !    six values: en11, en12, en13; en22 en 23; en33.
498     !  </description>
499     !  <range min="0.0" max="1.0" />
500           DES_EN_INPUT(:) = UNDEFINED
501     !</keyword>
502     
503     
504     !<keyword category="Discrete Element Model" required="false" dem="true">
505     !  <description>
506     !    The normal restitution coefficient for particle-wall collisions
507     !    used to determine the particle-wall normal damping factor.
508     !
509     !    Values should be defined in a single dimensional array. For
510     !    example, a simulation with three solids phases (MMAX=3) needs
511     !    three values: enw1, enw2, enw3.
512     !  </description>
513     !  <range min="0.0" max="1.0" />
514           DES_EN_WALL_INPUT(:) = UNDEFINED
515     !</keyword>
516     
517     
518     !<keyword category="Discrete Element Model" required="false" dem="true">
519     !  <description>
520     !    Tangential restitution coefficient for inter-particle collisions.
521     !    Values are defined in a one dimensional array. This is required
522     !    input when using the Hertzian collision model.
523     ! </description>
524     ! <dependent keyword="DES_COLL_MODEL" value="HERTZIAN"/>
525     ! <range min="0.0" max="1.0" />
526           DES_ET_INPUT(:) = UNDEFINED
527     !</keyword>
528     
529     
530     !<keyword category="Discrete Element Model" required="false" dem="true">
531     !  <description>
532     !    Tangential restitution coefficient for particle wall collisions.
533     !    Values are defined in a one dimensional array. This is required
534     !    input when using the Hertzian collision model.
535     !  </description>
536     ! <range min="0.0" max="1.0" />
537     ! <dependent keyword="DES_COLL_MODEL" value="HERTZIAN"/>
538           DES_ET_WALL_INPUT(:) = UNDEFINED
539     !</keyword>
540     
541     
542     !<keyword category="Discrete Element Model" required="false" dem="true">
543     !  <description>
544     !    Ratio of the tangential damping factor to the normal damping factor
545     !    for inter-particle collisions.  Required for the linear spring-
546     !    dashpot model collision model
547     !  </description>
548     !  <dependent keyword="DES_COLL_MODEL" value="LSD"/>
549     !  <range min="0.0" max="1.0" />
550     !  <valid value="UNDEFINED" note="For LSD model, if left undefined, MFIX
551     !   reverts to default value of 0.5" />
552           DES_ETAT_FAC = UNDEFINED
553     !</keyword>
554     
555     
556     !<keyword category="Discrete Element Model" required="false">
557     ! <description>
558     !    Ratio of the tangential damping factor to the normal damping
559     !    factor for particle-wall collisions. Required for the linear
560     !    spring-dashpot model for soft-spring collision modelling under
561     !    DEM. For the Hertzian model, the tangential damping coefficients
562     !    have to be explicitly specified and specification of this
563     !    variable is not required.
564     ! </description>
565     ! <dependent keyword="DES_COLL_MODEL" value="LSD"/>
566     ! <range min="0.0" max="1.0" />
567     ! <valid value="UNDEFINED" note="For LSD model, if left undefined, MFIX
568     ! will revert to default value of 0.5" />
569           DES_ETAT_W_FAC = UNDEFINED
570     !</keyword>
571     
572     
573     !<keyword category="Discrete Element Model" required="false">
574     !  <description>
575     !    Youngs modulus for the wall [barye in CGS]. Required when using the
576     !    Hertzian spring-dashpot model.
577     !  </description>
578     !  <dependent keyword="DES_COLL_MODEL" value="HERTZIAN"/>
579           EW_YOUNG = UNDEFINED
580     !</keyword>
581     
582     !<keyword category="Discrete Element Model" required="false">
583     !  <description>
584     !    Poisson ratio for the wall. Required when using the Hertzian
585     !    spring-dashpot model.
586     !  </description>
587     !  <dependent keyword="DES_COLL_MODEL" value="HERTZIAN"/>
588           VW_POISSON = UNDEFINED
589     !</keyword>
590     
591     
592     !<keyword category="Discrete Element Model" required="false">
593     !  <description>
594     !    Youngs modulus for the particle [barye in CGS]. Required when using
595     !    the Hertzian spring-dashpot model.
596     !  </description>
597     !  <arg index="1" id="Phase" min="1" max="DES_MMAX"/>
598     !  <dependent keyword="DES_COLL_MODEL" value="HERTZIAN"/>
599           E_YOUNG(:DIM_M) = UNDEFINED
600     !</keyword>
601     
602     
603     !<keyword category="Discrete Element Model" required="false">
604     !  <description>
605     !    Poissons ratio for the particle. Required when using the Hertzian
606     !    spring-dashpot model.
607     !  </description>
608     !  <arg index="1" id="Phase" min="1" max="DES_MMAX"/>
609     !  <dependent keyword="DES_COLL_MODEL" value="HERTZIAN"/>
610           V_POISSON(:DIM_M) = UNDEFINED
611     !</keyword>
612     
613     
614     !<keyword category="Discrete Element Model" required="false">
615     !  <description>
616     !    Actual Youngs modulus for the particle [barye in CGS]. Used for
617     !    computing correction terms for DEM conduction.
618     !  </description>
619     !  <arg index="1" id="Phase" min="1" max="DES_MMAX"/>
620           E_YOUNG_ACTUAL(:DIM_M) = UNDEFINED
621     !</keyword>
622     
623     !<keyword category="Discrete Element Model" required="false">
624     !  <description>
625     !    Actual Youngs modulus for the walls [barye in CGS]. Used for
626     !    computing correction terms for DEM conduction.
627     !  </description>
628     !  <arg index="1" id="Phase" min="1" max="DES_MMAX"/>
629     !  <dependent keyword="DES_COLL_MODEL" value="HERTZIAN"/>
630           EW_YOUNG_ACTUAL = UNDEFINED
631     !</keyword>
632     
633     !<keyword category="Discrete Element Model" required="false">
634     !  <description>
635     !    Poissons ratio for the particle. Required when using the Hertzian
636     !    spring-dashpot model.
637     !  </description>
638     !  <arg index="1" id="Phase" min="1" max="DES_MMAX"/>
639           V_POISSON_ACTUAL(:DIM_M) = UNDEFINED
640     !</keyword>
641     
642     !<keyword category="Discrete Element Model" required="false">
643     !  <description>
644     !    Poisson ratio for the wall. Required when using the Hertzian
645     !    spring-dashpot model.
646     !  </description>
647           VW_POISSON_ACTUAL = UNDEFINED
648     !</keyword>
649     
650     
651     !<keyword category="Discrete Element Model" required="false">
652     !  <description>
653     !    Flag to enable/disable cohesion model.
654     !  </description>
655           USE_COHESION = .FALSE.
656     !</keyword>
657     
658     
659     !<keyword category="Discrete Element Model" required="false">
660     !  <description>
661     !    Flag to turn on the use Hamaker van der Waals forces.
662     !  </description>
663     !  <dependent keyword="USE_COHESION" value=".TRUE."/>
664           VAN_DER_WAALS = .FALSE.
665     !</keyword>
666     
667     
668     ! for cohesion: van der waals
669     !<keyword category="Discrete Element Model" required="false">
670     !  <description>
671     !    Hamaker constant used in particle-particle cohesive interactions.
672     !  </description>
673     !  <dependent keyword="USE_COHESION" value=".TRUE."/>
674           HAMAKER_CONSTANT = UNDEFINED
675     !</keyword>
676     
677     
678     !<keyword category="Discrete Element Model" required="false">
679     !  <description>
680     !    Hamaker constant used in particle-wall cohesive interactions.
681     !  </description>
682     !  <dependent keyword="USE_COHESION" value=".TRUE."/>
683           WALL_HAMAKER_CONSTANT = UNDEFINED
684     !</keyword>
685     
686     
687     !<keyword category="Discrete Element Model" required="false">
688     !  <description>
689     !    Maximum separation distance above which van der Waals forces are
690     !    not implemented.
691     !  </description>
692     !  <dependent keyword="USE_COHESION" value=".TRUE."/>
693           VDW_OUTER_CUTOFF = UNDEFINED
694     !</keyword>
695     
696     
697     !<keyword category="Discrete Element Model" required="false">
698     !  <description>
699     !    Minimum separation distance below which van der Waals forces are
700     !    calculated using a surface adhesion model.
701     !  </description>
702     !  <dependent keyword="USE_COHESION" value=".TRUE."/>
703           VDW_INNER_CUTOFF = UNDEFINED
704     !</keyword>
705     
706     
707     !<keyword category="Discrete Element Model" required="false">
708     !  <description>
709     !    Maximum separation distance above which van der Waals forces are
710     !    not implemented (particle-wall interactions).
711     !  </description>
712     !  <dependent keyword="USE_COHESION" value=".TRUE."/>
713           WALL_VDW_OUTER_CUTOFF = ZERO
714     !</keyword>
715     
716     
717     !<keyword category="Discrete Element Model" required="false">
718     !  <description>
719     !    Minimum separation distance below which van der Waals forces are
720     !    calculated using a surface adhesion model (particle-wall
721     !    interactions).
722     !  </description>
723     !  <dependent keyword="USE_COHESION" value=".TRUE."/>
724           WALL_VDW_INNER_CUTOFF = UNDEFINED
725     !</keyword>
726     
727     
728     !<keyword category="Discrete Element Model" required="false">
729     !  <description>
730     !    Mean radius of surface asperities that influence the cohesive force
731     !    following a model. See H. Rumpf, Particle Technology, Chapman & Hall,
732     !    London/New York, 1990.
733     !  </description>
734     !  <dependent keyword="USE_COHESION" value=".TRUE."/>
735           Asperities = ZERO
736     !</keyword>
737     
738     !<keyword category="Discrete Element Model" required="false">
739     !  <description>
740     !    Specify the Nusselt number correlation used for particle-gas
741     !    convection.
742     !  </description>
743     !  <valid value="RANZ_1952" note="Ranz, W.E. and Marshall, W.R. (1952).
744     !    Chemical Engineering Progress, 48: 141-146 and 173-180"/>
745           DES_CONV_CORR = 'RANZ_1952'
746     !</keyword>
747     
748     !<keyword category="Discrete Element Model" required="false">
749     !  <description>
750     !    Minimum separation distance between the surfaces of two contacting
751     !    particles.
752     !  </description>
753           DES_MIN_COND_DIST = UNDEFINED
754     !</keyword>
755     
756     !<keyword category="Discrete Element Model" required="false">
757     !  <description>
758     !    Fluid lens proportion constant used to calculate the radius of
759     !    the fluid lens that surrounds a particle. This parameter is used
760     !    in the particle-fluid-particle conduction model.
761     !  </description>
762           FLPC = 1.0d0/5.0d0
763     !</keyword>
764     
765     !<keyword category="Discrete Element Model" required="false">
766     !  <description>Emissivity of solids phase M.</description>
767     !  <arg index="1" id="Phase" min="1" max="DES_MMAX"/>
768           DES_Em(:DIM_M) = UNDEFINED
769     !</keyword>
770     
771     
772     !<keyword category="Discrete Element Model" required="false">
773     !  <description>
774     !    Flag to turn on/off optimizing the list of facets at each des grid cell
775     !  </description>
776     !  <dependent keyword="USE_STL" value=".TRUE."/>
777           MINIMIZE_DES_FACET_LIST =.TRUE.
778     !</keyword>
779     
780     !#####################################################################!
781     !                          Particle In Cell                           !
782     !#####################################################################!
783     
784     
785     !<keyword category="Particle In Cell" required="false">
786     !  <description>
787     !    Turn on snider's version of frictional model.
788     !    Does not run very stably.
789     !  </description>
790           MPPIC_SOLID_STRESS_SNIDER = .false.
791     !</keyword>
792     
793     
794     !<keyword category="Particle In Cell" required="false">
795     !  <description>
796     !    First coefficient of restitution for the frictional stress model
797     !    in the MPPIC model. See the MPPIC documentation for more details.
798     !  </description>
799     !  <dependent keyword="MPPIC" value=".TRUE."/>
800           MPPIC_COEFF_EN1 = UNDEFINED
801     !</keyword>
802     
803     
804     !<keyword category="Particle In Cell" required="false">
805     !  <description>
806     !    Second coefficient of restitution for the frictional stress model
807     !    in the MPPIC model. See the MPPIC documentation for more details.
808     !</description>
809     !  <dependent keyword="MPPIC" value=".TRUE."/>
810           MPPIC_COEFF_EN2 = UNDEFINED
811     !</keyword>
812     
813     
814     !<keyword category="Particle In Cell" required="false">
815     !  <description>
816     !    Normal coefficient of restitution for parcel-wall collisions
817     !    in the MPPIC model.
818     !</description>
819     !  <dependent keyword="MPPIC" value=".TRUE."/>
820           MPPIC_COEFF_EN_WALL = UNDEFINED
821     !</keyword>
822     
823     
824     !<keyword category="Particle In Cell" required="false">
825     !  <description> Tangential coefficient of restitution for
826     ! parcel-wall collisions in the MPPIC model.
827     ! Currently not implemented in the code.
828     !</description>
829     !  <dependent keyword="MPPIC" value=".TRUE."/>
830           MPPIC_COEFF_ET_WALL = 1.0
831     !</keyword>
832     
833     
834     !<keyword category="Particle In Cell" required="false">
835     !  <description> Turn on the implicit treatment for interphase drag force.
836     ! Valid only for MPPIC model.
837     !</description>
838     !  <dependent keyword="MPPIC" value=".TRUE."/>
839           MPPIC_PDRAG_IMPLICIT = .false.
840     !</keyword>
841     
842     !<keyword category="Particle In Cell" required="false">
843     !  <description>
844     !     Variable to decide if special treatment is needed or not in the
845     !     direction of gravity in the frictional stress tensor. See the
846     !     MPPIC documentation for details.
847     !  </description>
848     !  <dependent keyword="MPPIC" value=".TRUE."/>
849           MPPIC_GRAV_TREATMENT = .true.
850     !</keyword>
851     
852     !<keyword category="Particle In Cell" required="false">
853     !  <description>
854     !    A run time flag to report minimum value and location of gas
855     !    voidage. This is useful only for debugging and is not
856     !    recommended for production runs.
857     !  </description>
858     !  <dependent keyword="MPPIC" value=".TRUE."/>
859           PIC_REPORT_MIN_EPG = .FALSE.
860     !</keyword>
861     
862     !<keyword category="Particle In Cell" required="false">
863     !  <description>
864     !    P_s term in the frictional stress model of Snider.
865     !  </description>
866     !  <dependent keyword="MPPIC" value=".TRUE."/>
867           PSFAC_FRIC_PIC = 100
868     !</keyword>
869     
870     !<keyword category="Particle In Cell" required="false">
871     !  <description>
872     !    Beta term in the frictional stress model of Snider.
873     !  </description>
874     !  <dependent keyword="MPPIC" value=".TRUE."/>
875           FRIC_EXP_PIC = 2.5
876     !</keyword>
877     
878     !<keyword category="Particle In Cell" required="false">
879     !  <description>
880     !    Non-singularity term (epsilon) in the frictional stress model of
881     !    Snider.
882     !  </description>
883     !  <dependent keyword="MPPIC" value=".TRUE."/>
884           FRIC_NON_SING_FAC = 1E-07
885     !</keyword>
886     
887     !<keyword category="Particle In Cell" required="false">
888     !  <description>CFL number used to decide maximum time
889     ! step size for parcels evolution equations.
890     ! Relevant to MPPIC model only.
891     !</description>
892     !  <dependent keyword="MPPIC" value=".TRUE."/>
893           CFL_PIC = 0.1
894     !</keyword>
895     
896     
897     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
898     !                            UNSUPPORTED KEYWORDS                      !
899     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
900     
901     ! Logical to force the inlet to operate with an ordered boundary
902     ! condition. This may be useful during long simulations or if the
903     ! inlet appears to be taking a long time to randomly place particles.
904           FORCE_ORD_BC = .FALSE.
905     
906     ! Lees-Edwards boundary condition to simulate homogeneous shear
907     ! problem with periodic boundary conditions. Not supported in this
908     ! version.
909           DES_LE_BC = .FALSE.
910     
911     ! Relative velocity needed for Lees-Edwards BC.
912     ! Not supported in this version.
913           DES_LE_REL_VEL = UNDEFINED
914     
915     ! Direction of shear for Lees-Edwards BC.
916     ! Not supported in this version. </description>
917           DES_LE_SHEAR_DIR = UNDEFINED_C
918     
919     ! des wall boundaries: wall velocities. I think they probably
920     ! defined for the Lees-Edwards BC's
921           DES_BC_Uw_s(:,:) = ZERO
922           DES_BC_Vw_s(:,:) = ZERO
923           DES_BC_Ww_s(:,:) = ZERO
924     
925     
926     ! These need to be inialized to 0, but they are not part of the namelist
927           VTP_FINDEX = 0
928           TECPLOT_FINDEX = 0
929     
930     ! not a well supported feature and not generic either. So removing
931     ! from namelists
932           DES_CALC_BEDHEIGHT = .FALSE.
933           RETURN
934           END SUBROUTINE DES_INIT_NAMELIST
935