File: RELATIVE:/../../../mfix.git/model/run_mod.f

1     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2     !                                                                      C
3     !  Module name: run                                                    C
4     !  Purpose: Common block containing run control data                   C
5     !                                                                      C
6     !  Author: M. Syamlal                                 Date: dd-mmm-yy  C
7     !  Reviewer:                                          Date: dd-mmm-yy  C
8     !                                                                      C
9     !                                                                      C
10     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
11     
12           MODULE run
13     
14     ! Modules
15     !---------------------------------------------------------------------//
16           use param, only: dim_M, dim_eqs
17           use param1, only: UNDEFINED_I
18           USE, INTRINSIC :: ISO_C_BINDING
19     !---------------------------------------------------------------------//
20     
21     
22     ! Main filename to be used for output files  Name must
23     ! still be legal after extensions are added to it.
24           CHARACTER(LEN=60) :: RUN_NAME
25     
26     ! Brief description of the problem.
27           CHARACTER(LEN=60) :: DESCRIPTION
28     
29     ! Units for data input and output: CGS.
30           CHARACTER(LEN=16) :: UNITS
31     
32     ! Type of run: NEW, RESTART
33           CHARACTER(LEN=16) :: RUN_TYPE
34     
35     ! Variable which triggers automatic restart
36           LOGICAL :: AUTOMATIC_RESTART
37     
38     ! counter to keep track of how many auto_retart were performed
39           INTEGER :: ITER_RESTART
40     
41     ! version.release of software
42           CHARACTER(LEN=10) :: ID_VERSION
43     
44     ! Start-time of the run.
45           DOUBLE PRECISION :: TIME
46     
47     ! Stop-time of the run.
48           DOUBLE PRECISION :: TSTOP
49     
50     ! Time step.
51           REAL(C_DOUBLE), bind(C, name="simulation_time") :: DT
52     
53     ! 1./Time step.
54           DOUBLE PRECISION :: oDT
55     
56     ! Number of times steps completed.
57           INTEGER :: NSTEP
58     
59     ! Declare a new variable to use on CN with RESTART cases
60     ! Number of time steps when restart file was read
61           INTEGER :: NSTEPRST
62     
63     ! Discretization scheme for different equations
64           INTEGER :: DISCRETIZE(DIM_EQS)
65     
66     ! Use Chi scheme for discretizing certain equation sets
67     !  (species mass fractions)
68           LOGICAL :: Chi_scheme
69     
70     ! If .TRUE. solve X momentum equations
71           LOGICAL :: MOMENTUM_X_EQ(0:DIM_M)
72     
73     ! If .TRUE. solve Y momentum equations
74           LOGICAL :: MOMENTUM_Y_EQ(0:DIM_M)
75     
76     ! If .TRUE. solve Z momentum equations
77           LOGICAL :: MOMENTUM_Z_EQ(0:DIM_M)
78     
79     ! IF .TRUE. use Jackson form momentum equations
80           LOGICAL :: JACKSON
81     ! IF .TRUE. use Ishii form momentum equations
82           LOGICAL :: ISHII
83     
84     ! If .TRUE. use Model-B momentum equations
85           LOGICAL :: Model_B
86     
87     ! If .TRUE. include added (virtual) mass in momentum eq.
88           LOGICAL :: Added_Mass
89     
90     ! phase number where added mass is applied.
91           INTEGER :: M_AM
92     
93     ! If .TRUE. solve K_Epsilon turbulence eq.
94           LOGICAL :: K_Epsilon
95     
96     ! If .TRUE. solve energy equations
97           LOGICAL :: ENERGY_EQ
98     
99     ! If .TRUE. use the deferred correction method
100           LOGICAL :: DEF_COR
101     
102     ! If .TRUE. use the fourth order interpolation
103           LOGICAL :: FPFOI
104     
105     ! If .TRUE. activate 2nd order accurate time implementation
106           LOGICAL :: CN_ON
107     
108     ! If .TRUE. solve granular energy equations
109           LOGICAL :: GRANULAR_ENERGY
110     
111     ! If .TRUE. solve species balance equations
112           LOGICAL :: SPECIES_EQ(0:DIM_M)
113     
114     ! If .TRUE. one of the species equations is being solved
115           LOGICAL :: ANY_SPECIES_EQ
116     
117     ! If .TRUE. call user-defined subroutines
118           LOGICAL :: CALL_USR
119     
120     ! If .TRUE. call user-defined physical properties routines
121           LOGICAL :: USR_ROg, USR_ROs, USR_CPg, USR_CPs
122     
123     ! If .TRUE. force time-step when NIT=MAX_NIT and DT=DT_MIN
124           LOGICAL :: PERSISTENT_MODE
125     
126     ! If .TRUE. solve population balance  equations
127           LOGICAL :: Call_DQMOM
128     
129     ! Drag model options (see drag_gs for full details)
130     ! default is syam_obrien (may enforce a corrected Umf by defining
131     ! drag_c1 and drag_d1 accordingly)
132           CHARACTER(64) :: DRAG_TYPE
133           INTEGER :: DRAG_TYPE_ENUM
134           INTEGER,PARAMETER :: SYAM_OBRIEN=0
135           INTEGER,PARAMETER :: GIDASPOW=1
136           INTEGER,PARAMETER :: GIDASPOW_PCF=2
137           INTEGER,PARAMETER :: GIDASPOW_BLEND=3
138           INTEGER,PARAMETER :: GIDASPOW_BLEND_PCF=4
139           INTEGER,PARAMETER :: WEN_YU=5
140           INTEGER,PARAMETER :: WEN_YU_PCF=6
141           INTEGER,PARAMETER :: KOCH_HILL=7
142           INTEGER,PARAMETER :: KOCH_HILL_PCF=8
143           INTEGER,PARAMETER :: BVK=9
144           INTEGER,PARAMETER :: HYS=10
145           INTEGER,PARAMETER :: USER_DRAG=11
146     
147     ! filtered/subgrid corrections to the drag coefficient & granular
148     ! stress terms including granular viscosity and solids pressure
149     ! current options are 'igci' and 'milioli'
150           CHARACTER(64) :: SUBGRID_TYPE
151     
152           INTEGER :: SUBGRID_TYPE_ENUM
153           INTEGER,PARAMETER :: UNDEFINED_SUBGRID_TYPE=0
154           INTEGER,PARAMETER :: IGCI=1
155           INTEGER,PARAMETER :: MILIOLI=2
156     
157     ! If .TRUE. incorporate the wall effects upon the calculation of the
158     ! subgrid solids viscosity, solids pressure, and gas-solids drag
159           LOGICAL :: SUBGRID_Wall
160     ! the ratio of the FilterSize to the GridSize
161           DOUBLE PRECISION :: filter_size_ratio
162     
163     ! Single particle drag correlation
164           CHARACTER(64) :: CD_FUNCTION
165     
166     ! Parameter used to calculate lubrication interactions between
167     ! different particles in HYS drag model
168           DOUBLE PRECISION :: LAM_HYS
169     
170     ! Kinetic theory model options (see calc_mu_s for details)
171     ! for m > 1 : IA_nonep, GHD, LUN_1984
172     ! for m = 1 : LUN_1984, simonin, ahmadi, or
173     !             GD_99 for granular flow or GTSH for gas-solids flow
174           CHARACTER(64) :: KT_TYPE
175           INTEGER :: KT_TYPE_ENUM
176           INTEGER,PARAMETER :: LUN_1984=0
177           INTEGER,PARAMETER :: SIMONIN_1996=1
178           INTEGER,PARAMETER :: AHMADI_1995=2
179           INTEGER,PARAMETER :: GD_1999=3
180           INTEGER,PARAMETER :: GTSH_2012=4
181           INTEGER,PARAMETER :: IA_2005=5
182           INTEGER,PARAMETER :: GHD_2007=6
183     
184     ! If .TRUE. use Simonin model (k_epsilon must also be true)
185           LOGICAL :: SIMONIN
186     
187     ! If .TRUE. use Ahmadi model (k_epsilon must also be true)
188           LOGICAL :: AHMADI
189     
190     ! If .TRUE. calculate frictional stress terms
191           LOGICAL :: FRICTION
192     ! Form of friction model:
193     !             If 0: use S:S
194     !             If 1: use the form of Savage to compute S:S
195     !             If 2: use combination of both for frictional stress terms
196           INTEGER :: SAVAGE
197     
198     ! If .TRUE. use Scheffer frictional stress (default set to .TRUE.)
199           LOGICAL :: SCHAEFFER
200     
201     ! If .TRUE. use blending frictional/kinetic stresses
202     ! (default set to .FALSE. do not blend)
203           LOGICAL :: BLENDING_STRESS
204           LOGICAL :: TANH_BLEND ! default set to true
205           LOGICAL :: SIGM_BLEND ! default set to false
206     
207     ! If .TRUE. use Jenkins small friction BC
208           LOGICAL :: JENKINS
209     ! If .TRUE. use revised phip for JJ BC
210           LOGICAL :: BC_JJ_M
211     ! If .TRUE. output PHIP to JJ_PHIP.dat
212           LOGICAL :: PHIP_OUT_JJ
213     ! to write specularity
214           INTEGER :: PHIP_OUT_ITER
215     
216     ! If .TRUE. treat system as if shearing
217           LOGICAL :: SHEAR
218     ! Shear Vel
219           DOUBLE PRECISION :: V_sh
220     
221     ! Radial distribution function options (see g_0 for details)
222     ! for m > 1 options are lebowitz, modified_lebowitz,
223     ! mansoori, modified_mansoori.  default = lebowitz
224     ! for m = 1 then carnahan and starling rdf used
225           CHARACTER(64) :: RDF_TYPE
226           INTEGER :: RDF_TYPE_ENUM
227           INTEGER, PARAMETER :: LEBOWITZ=0
228           INTEGER, PARAMETER :: MODIFIED_LEBOWITZ=1
229           INTEGER, PARAMETER :: MANSOORI=2
230           INTEGER, PARAMETER :: MODIFIED_MANSOORI=3
231           INTEGER, PARAMETER :: CARNAHAN_STARLING=4
232     
233     ! If .TRUE. use Yu and Standish correlation to compute ep_star
234           LOGICAL :: YU_STANDISH
235     
236     ! If .TRUE. use Fedors and Landel correlation to compute ep_star
237           LOGICAL :: FEDORS_LANDEL
238     
239     ! STOP Trigger mechanism to terminate MFIX normally before batch
240     ! queue terminates flag variable to check for end of batch queue when
241     ! set to TRUE check performed at the beginning of each time step and
242     ! termination of mfix triggered after saving all files if condition
243     ! is met
244           LOGICAL :: CHK_BATCHQ_END
245     ! variable to store the total wall clock duration of the batch queue
246     ! session wall clock time specified in seconds
247     ! for jaguarcnl@NCCS max wall clock limit is 2.5 hr limit up to 512
248     ! processors
249           DOUBLE PRECISION :: BATCH_WALLCLOCK
250     ! variable to set a buffer time before the batch queue session ends to
251     ! make sure once MFIX is triggered to shutdown, there is sufficient
252     ! time to save files, make copies to HPSS storage before batch queue
253     ! time runs out. Current logic in MFIX checks for:
254     !    if CPU_TIME > (BATCH_WALLCLOCK - TERM_BUFFER) then
255     !    save all .RES .SP files and trigger shutdown
256           DOUBLE PRECISION :: TERM_BUFFER
257     
258     ! If .TRUE. code will automatically restart for DT < DT_MIN
259           LOGICAL :: AUTO_RESTART
260     
261     ! If. .TRUE. code will respond during runtime
262           LOGICAL :: INTERACTIVE_MODE
263     
264     ! Number of interactive iterations.
265           INTEGER :: INTERACTIVE_NITS=UNDEFINED_I
266     
267     ! If .TRUE. code will halt at call to interact
268           LOGICAL :: INTERUPT = .FALSE.
269     
270     ! If .TRUE. code will automatically restart for DT < DT_MIN
271           LOGICAL :: REINITIALIZING = .FALSE.
272     
273     ! Time-step failure rate:
274     ! 1) Number of failed time steps
275     ! 2) Observation window
276           INTEGER :: TIMESTEP_FAIL_RATE(2)
277     
278     ! parameters for dynamically adjusting time step
279     ! +1 -> increase dt; -1 decrease dt
280           INTEGER :: DT_dir = -1
281     
282     ! Maximum Time step.
283           DOUBLE PRECISION :: DT_MAX
284     
285     ! Minimum Time step.
286           DOUBLE PRECISION :: DT_MIN
287     
288     ! Time step adjustment factor (<1.0)
289           DOUBLE PRECISION :: DT_FAC
290     
291     ! The previous time step used in iterate (before it is
292     ! changed by adjust_dt)
293           DOUBLE PRECISION :: DT_prev
294     
295     ! in case iterations converged and DT modified, use old dt
296     ! to advance time in time_march.
297           LOGICAL :: use_DT_prev
298     
299     ! Slope limiter parameter (0 < C _FAC <= 1.0)
300           DOUBLE PRECISION :: C_FAC
301     
302     ! If .TRUE. reduce time step when residuals do not decrease
303           LOGICAL :: DETECT_STALL
304     
305     ! String which controls reduction of global sums for residual
306     ! calculations
307           LOGICAL :: DEBUG_RESID
308     
309     ! Generate log files when negative gas density is detected.
310           LOGICAL :: REPORT_NEG_DENSITY
311     
312            common /run_dp/ time      !for Linux
313     
314     
315     ! Flags indicating variable solids density.
316           LOGICAL :: SOLVE_ROs(DIM_M), ANY_SOLVE_ROs
317     
318     ! Specifies the type of solids: TFM, DEM, MPPIC
319           CHARACTER(len=3), DIMENSION(DIM_M) :: SOLIDS_MODEL
320     
321     ! Flags for various solids phase models.
322           LOGICAL :: TFM_SOLIDS
323           LOGICAL :: DEM_SOLIDS
324           LOGICAL :: PIC_SOLIDS
325     ! The number of the various solids phases.
326           INTEGER :: TFM_COUNT = 0
327           INTEGER :: DEM_COUNT = 0
328           INTEGER :: PIC_COUNT = 0
329     
330           END MODULE RUN
331