File: N:\mfix\model\run_mod.f

1     ! -*- f90 -*-
2     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
3     !                                                                      C
4     !  Module name: run                                                    C
5     !  Purpose: Common block containing run control data                   C
6     !                                                                      C
7     !  Author: M. Syamlal                                 Date: dd-mmm-yy  C
8     !  Reviewer:                                          Date: dd-mmm-yy  C
9     !                                                                      C
10     !                                                                      C
11     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
12     
13           MODULE run
14     
15     ! Modules
16     !---------------------------------------------------------------------//
17           use param, only: dim_M, dim_eqs
18           use param1, only: UNDEFINED_I
19           use derived_types
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           DOUBLE PRECISION :: DT
52     
53     ! 1./Time step.
54           DOUBLE PRECISION :: oDT
55     
56     ! Indicates whether simulation is steady-state
57           LOGICAL :: STEADY_STATE
58     
59     ! Number of times steps completed.
60           INTEGER :: NSTEP
61     
62     ! Declare a new variable to use on CN with RESTART cases
63     ! Number of time steps when restart file was read
64           INTEGER :: NSTEPRST
65     
66     ! Discretization scheme for different equations
67           INTEGER :: DISCRETIZE(DIM_EQS)
68     
69     ! Use Chi scheme for discretizing certain equation sets
70     !  (species mass fractions)
71           LOGICAL :: Chi_scheme
72     
73     ! If .TRUE. solve X momentum equations
74           LOGICAL :: MOMENTUM_X_EQ(0:DIM_M)
75     
76     ! If .TRUE. solve Y momentum equations
77           LOGICAL :: MOMENTUM_Y_EQ(0:DIM_M)
78     
79     ! If .TRUE. solve Z momentum equations
80           LOGICAL :: MOMENTUM_Z_EQ(0:DIM_M)
81     
82     ! IF .TRUE. use Jackson form momentum equations
83           LOGICAL :: JACKSON
84     ! IF .TRUE. use Ishii form momentum equations
85           LOGICAL :: ISHII
86     
87     ! If .TRUE. use Model-B momentum equations
88           LOGICAL :: Model_B
89     
90     ! If .TRUE. include added (virtual) mass in momentum eq.
91           LOGICAL :: Added_Mass
92     
93     ! phase number where added mass is applied.
94           INTEGER :: M_AM
95     
96     ! If .TRUE. solve K_Epsilon turbulence eq.
97           LOGICAL :: K_Epsilon
98     
99     ! If .TRUE. solve energy equations
100           LOGICAL :: ENERGY_EQ
101     
102     ! If .TRUE. use the deferred correction method
103           LOGICAL :: DEF_COR
104     
105     ! If .TRUE. use the fourth order interpolation
106           LOGICAL :: FPFOI
107     
108     ! If .TRUE. activate 2nd order accurate time implementation
109           LOGICAL :: CN_ON
110     
111     ! If .TRUE. solve granular energy equations
112           LOGICAL :: GRANULAR_ENERGY
113     
114     ! If .TRUE. solve species balance equations
115           LOGICAL :: SPECIES_EQ(0:DIM_M)
116     
117     ! If .TRUE. one of the species equations is being solved
118           LOGICAL :: ANY_SPECIES_EQ
119     
120     ! If .TRUE. call user-defined subroutines
121           LOGICAL :: CALL_USR
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     ! If .TRUE. incorporate the wall effects upon the calculation of the
130     ! subgrid solids viscosity, solids pressure, and gas-solids drag
131           LOGICAL :: SUBGRID_Wall
132     ! the ratio of the FilterSize to the GridSize
133           DOUBLE PRECISION :: filter_size_ratio
134     
135     ! Single particle drag correlation
136           CHARACTER(64) :: CD_FUNCTION
137     
138     ! Parameter used to calculate lubrication interactions between
139     ! different particles in HYS drag model
140           DOUBLE PRECISION :: LAM_HYS
141     
142     ! If .TRUE. use Simonin model (k_epsilon must also be true)
143           LOGICAL :: SIMONIN
144     
145     ! If .TRUE. use Ahmadi model (k_epsilon must also be true)
146           LOGICAL :: AHMADI
147     
148     ! If .TRUE. calculate frictional stress terms
149           LOGICAL :: FRICTION
150     ! Form of friction model:
151     !             If 0: use S:S
152     !             If 1: use the form of Savage to compute S:S
153     !             If 2: use combination of both for frictional stress terms
154           INTEGER :: SAVAGE
155     
156     ! If .TRUE. use Scheffer frictional stress (default set to .TRUE.)
157           LOGICAL :: SCHAEFFER
158     
159     ! If .TRUE. use blending frictional/kinetic stresses
160     ! (default set to .FALSE. do not blend)
161           LOGICAL :: BLENDING_STRESS
162           LOGICAL :: TANH_BLEND ! default set to true
163           LOGICAL :: SIGM_BLEND ! default set to false
164     
165     ! If .TRUE. use Jenkins small friction BC
166           LOGICAL :: JENKINS
167     ! If .TRUE. use revised phip for JJ BC
168           LOGICAL :: BC_JJ_M
169     ! If .TRUE. output PHIP to JJ_PHIP.dat
170           LOGICAL :: PHIP_OUT_JJ
171     ! to write specularity
172           INTEGER :: PHIP_OUT_ITER
173     
174     ! If .TRUE. treat system as if shearing
175           LOGICAL :: SHEAR
176     ! Shear Vel
177           DOUBLE PRECISION :: V_sh
178     
179     ! If .TRUE. use Yu and Standish correlation to compute ep_star
180           LOGICAL :: YU_STANDISH
181     
182     ! If .TRUE. use Fedors and Landel correlation to compute ep_star
183           LOGICAL :: FEDORS_LANDEL
184     
185     ! STOP Trigger mechanism to terminate MFIX normally before batch
186     ! queue terminates flag variable to check for end of batch queue when
187     ! set to TRUE check performed at the beginning of each time step and
188     ! termination of mfix triggered after saving all files if condition
189     ! is met
190           LOGICAL :: CHK_BATCHQ_END
191     ! variable to store the total wall clock duration of the batch queue
192     ! session wall clock time specified in seconds
193     ! for jaguarcnl@NCCS max wall clock limit is 2.5 hr limit up to 512
194     ! processors
195           DOUBLE PRECISION :: BATCH_WALLCLOCK
196     ! variable to set a buffer time before the batch queue session ends to
197     ! make sure once MFIX is triggered to shutdown, there is sufficient
198     ! time to save files, make copies to HPSS storage before batch queue
199     ! time runs out. Current logic in MFIX checks for:
200     !    if CPU_TIME > (BATCH_WALLCLOCK - TERM_BUFFER) then
201     !    save all .RES .SP files and trigger shutdown
202           DOUBLE PRECISION :: TERM_BUFFER
203     
204     ! If .TRUE. code will automatically restart for DT < DT_MIN
205           LOGICAL :: AUTO_RESTART
206     
207     ! If .TRUE. code will automatically restart for DT < DT_MIN
208           LOGICAL :: REINITIALIZING = .FALSE.
209     
210     ! Time-step failure rate:
211     ! 1) Number of failed time steps
212     ! 2) Observation window
213           INTEGER :: TIMESTEP_FAIL_RATE(2)
214     
215     ! parameters for dynamically adjusting time step
216     ! +1 -> increase dt; -1 decrease dt
217           INTEGER :: DT_dir = -1
218     
219     ! Maximum Time step.
220           DOUBLE PRECISION :: DT_MAX
221     
222     ! Minimum Time step.
223           DOUBLE PRECISION :: DT_MIN
224     
225     ! Time step adjustment factor (<1.0)
226           DOUBLE PRECISION :: DT_FAC
227     
228     ! The previous time step used in iterate (before it is
229     ! changed by adjust_dt)
230           DOUBLE PRECISION :: DT_prev
231     
232     ! in case iterations converged and DT modified, use old dt
233     ! to advance time in time_march.
234           LOGICAL :: use_DT_prev
235     
236     ! Slope limiter parameter (0 < C _FAC <= 1.0)
237           DOUBLE PRECISION :: C_FAC
238     
239     ! If .TRUE. reduce time step when residuals do not decrease
240           LOGICAL :: DETECT_STALL
241     
242     ! String which controls reduction of global sums for residual
243     ! calculations
244           LOGICAL :: DEBUG_RESID
245     
246            common /run_dp/ time      !for Linux
247     
248     
249     ! Flags indicating variable solids density.
250           LOGICAL :: SOLVE_ROs(DIM_M), ANY_SOLVE_ROs
251     
252     ! Specifies the type of solids: TFM, DEM, MPPIC
253           CHARACTER(len=3), DIMENSION(DIM_M) :: SOLIDS_MODEL
254     
255     ! Flags for various solids phase models.
256           LOGICAL :: TFM_SOLIDS
257           LOGICAL :: DEM_SOLIDS
258           LOGICAL :: PIC_SOLIDS
259     ! The number of the various solids phases.
260           INTEGER :: TFM_COUNT = 0
261           INTEGER :: DEM_COUNT = 0
262           INTEGER :: PIC_COUNT = 0
263     
264           ! Error index
265           INTEGER :: IER
266     
267           ! CPU time unit.
268           CHARACTER(LEN=4) :: TUNIT
269     
270           CONTAINS
271     
272              !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
273              !  Purpose:  Given time in seconds, calculate time in days/hours/seconds
274              !
275              !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
276              SUBROUTINE GET_TUNIT(TLEFT, TUNIT)
277     
278                 !-----------------------------------------------
279                 ! Modules
280                 !-----------------------------------------------
281                 IMPLICIT NONE
282                 !-----------------------------------------------
283                 ! Dummy arguments
284                 !-----------------------------------------------
285                 DOUBLE PRECISION, INTENT(INOUT) :: TLEFT
286                 CHARACTER(LEN=4) :: TUNIT
287                 !-----------------------------------------------
288     
289                 IF (TLEFT < 3600.0d0) THEN
290                    TUNIT = 's'
291                 ELSE
292                    TLEFT = TLEFT/3600.0d0
293                    TUNIT = 'h'
294                    IF (TLEFT >= 24.) THEN
295                       TLEFT = TLEFT/24.0d0
296                       TUNIT = 'days'
297                    ENDIF
298                 ENDIF
299     
300                 RETURN
301              END SUBROUTINE GET_TUNIT
302     
303           END MODULE RUN
304