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