MFIX  2016-1
check_solids_continuum.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: CHECK_CONTINUUM_SOLIDS !
4 ! Purpose: Check kinetic the run control namelist section !
5 ! !
6 ! Author: P. Nicoletti Date: 27-NOV-91 !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  SUBROUTINE check_solids_continuum
10 
11 ! Global Variables:
12 !---------------------------------------------------------------------//
13  USE constant
14  USE run
15  USE physprop
16 
17 ! Global Parameters:
18 !---------------------------------------------------------------------//
19  USE param1, only: zero, one, undefined, undefined_i
20 
21 ! Global Module procedures:
22 !---------------------------------------------------------------------//
23  use error_manager
24 
25  IMPLICIT NONE
26 
27 ! Local Variables:
28 !---------------------------------------------------------------------//
29  INTEGER :: LC, M
30  DOUBLE PRECISION :: lsin_phi
31 ! counters for number of phases with defined/undefined mu_s0
32  INTEGER :: def_mus0, undef_mus0
33 !......................................................................!
34 
35 
36 ! initialization of various dependent constants
37  sin_phi = undefined ! friction
38  sin2_phi = undefined ! schaeffer
39  f_phi = undefined ! commented schaeffer section
40  tan_phi_w = undefined ! friction or jenkins
41 
42 ! Initialize the error manager.
43  CALL init_err_msg("CHECK_SOLIDS_CONTINUUM")
44 
45 ! Check EP_star. This is used to populate ep_star_array which is what
46 ! should be used elsewhere in the code. (see set_constprop)
47  IF(ep_star == undefined) THEN
48  WRITE(err_msg,1000) 'EP_STAR'
49  CALL flush_err_msg(abort=.true.)
50  ELSEIF(ep_star < zero .OR. ep_star > one) THEN
51  WRITE(err_msg, 1001)'EP_STAR', ival(ep_star)
52  CALL flush_err_msg(abort=.true.)
53  ENDIF
54 
55 ! CHECK DIF_s0
56  DO m = 1, smax
57  IF (dif_s0(m) < zero) THEN
58  WRITE(err_msg, 1001) trim(ivar('Dif_s0',m)), &
59  ival(dif_s0(m))
60  CALL flush_err_msg(abort=.true.)
61  ENDIF
62  ENDDO
63  DO m = smax+1, dim_m
64  IF(dif_s0(m) /= undefined)THEN
65  WRITE(err_msg,1002) trim(ivar('Dif_s0',m))
66  CALL flush_err_msg(abort=.true.)
67  ENDIF
68  ENDDO
69 
70 ! CHECK MU_s0
71  def_mus0 = 0
72  DO m = 1, smax
73  IF (mu_s0(m) /= undefined) THEN
74  def_mus0 = def_mus0 + 1
75  IF(mu_s0(m) < zero) THEN
76  WRITE(err_msg, 1001) trim(ivar('Mu_s0',m)), &
77  ival(mu_s0(m))
78  CALL flush_err_msg(abort=.true.)
79  ENDIF
80  ENDIF
81  ENDDO
82  undef_mus0 = smax - def_mus0
83 
84  DO m = smax+1, dim_m
85  IF(mu_s0(m) /= undefined)THEN
86  WRITE(err_msg,1002) trim(ivar('Mu_s0',m))
87  CALL flush_err_msg(abort=.true.)
88  ENDIF
89  ENDDO
90 
91 ! Solids phase with constant solids viscosity is employed
92 !---------------------------------------------------------------------//
93  IF (def_mus0 > 0) THEN
94  IF(granular_energy) THEN
95 ! calculation of many of the solids phase transport coefficients
96 ! needed by the granular energy equation will be skipped in the
97 ! calc_mu_s if mu_s0 is defined. so make sure that the granular
98 ! energy eqn is not evaluated when the solids viscosity is set to
99 ! a constant.
100 ! Also do not allow a mixed case of constant viscosity and pde
101 ! granular energy. To permit such would require going through the
102 ! KT sections of the code and ensuring that the solids phase with
103 ! granular energy doesn't interact or depend on a phase with a
104 ! constant viscosity.
105  WRITE(err_msg,1100)
106  CALL flush_err_msg(abort=.true.)
107  ENDIF
108 
109 ! needed by default solids-solids drag model
110  IF (smax >=2) THEN
111  IF (c_e == undefined) THEN
112  WRITE(err_msg,1101)
113  CALL flush_err_msg(abort=.true.)
114  ELSEIF (c_f == undefined) THEN
115  WRITE(err_msg,1102)
116  CALL flush_err_msg(abort=.true.)
117  ENDIF
118  ENDIF
119  ENDIF
120 
121 
122 ! PDE granular energy. Check kinetic theory specifications.
123 !---------------------------------------------------------------------//
124  IF (granular_energy) THEN
125  IF(def_mus0 >0) THEN
126  WRITE(err_msg,1100)
127  CALL flush_err_msg(abort=.true.)
128  ENDIF
129  CALL check_kt_type
130  ENDIF
131 
132 ! Algebraic granular energy equation
133 !---------------------------------------------------------------------//
134  IF (.NOT.granular_energy .AND. undef_mus0 > 0) THEN
135  IF (c_e == undefined) THEN
136  WRITE(err_msg,1101)
137  CALL flush_err_msg(abort=.true.)
138  ENDIF
139 ! needed by default solids-solids drag model. SMAX may be 1 for
140 ! hybrid simulations and C_F is still needed.
141  IF (smax >=2 .OR. dem_solids) THEN
142  IF (c_f == undefined) THEN
143  WRITE(err_msg,1102)
144  CALL flush_err_msg(abort=.true.)
145  ENDIF
146  ENDIF
147  ENDIF
148  1100 FORMAT('Error 1100: Constant viscosity is specified but', /&
149  'GRANULAR_ENERGY=.TRUE. Please correct the mfix.dat file')
150  1101 FORMAT('Error 1101: Coefficient of restitution (C_E) not ', &
151  'specified.',/'Please correct the mfix.dat file.')
152  1102 FORMAT('Error 1102: Coefficient of friction (C_F) not ', &
153  'specified.',/'Please correct the mfix.dat file.')
154 
155 
156 
157 ! If frictional stress modeling check various dependent/conflicting
158 ! settings
159 
160 ! plastic/frictional stress model
161  IF (friction) THEN
162  IF(schaeffer) THEN
163  WRITE(err_msg, 1200)
164  CALL flush_err_msg(abort=.true.)
165 ! Check that the granular energy PDE is solved.
166  ELSEIF (.NOT.granular_energy) THEN
167  WRITE(err_msg,1201)
168  CALL flush_err_msg(abort=.true.)
169 ! Check the value specified for SAVAGE.
170  ELSEIF(savage>2 .OR. savage<0) THEN
171  WRITE(err_msg, 1001)'SAVAGE', ival(savage)
172  CALL flush_err_msg(abort=.true.)
173 ! Verify that stress blending is not turned on.
174  ELSEIF(blending_stress) THEN
175  WRITE(err_msg, 1202)
176  CALL flush_err_msg(abort=.true.)
177  ELSEIF(phi == undefined) THEN
178  WRITE(err_msg, 1203)
179  CALL flush_err_msg(abort=.true.)
180 ! used by friction bc
181  ELSEIF(phi_w == undefined) THEN
182  WRITE(err_msg, 1204)
183  CALL flush_err_msg(abort=.true.)
184  ENDIF
185 ! PHI & PHI_W are given in degrees but calculated in radian within
186 ! the fortran codes
187  sin_phi = sin(phi*pi/180.d0)
188  tan_phi_w = tan(phi_w*pi/180.d0)
189  ENDIF
190  1201 FORMAT('Error 1201: The FRICTION solids stress model requires ', &
191  /,'GRANULAR_ENERGY=.TRUE. Please correct the mfix.dat file.')
192  1202 FORMAT('Error 1202: Cannot use BLENDING_STRESS with FRICTION ',&
193  /,'Please correct the mfix.dat file.')
194  1204 FORMAT('Error 1204: Angle of particle-wall friction (PHI_W) not',&
195  ' specified.',/'Please correct the mfix.dat file.')
196 
197 
198 ! plastic/frictional stress model
199  IF(schaeffer) THEN
200  IF(friction) THEN
201  WRITE(err_msg, 1200)
202  CALL flush_err_msg(abort=.true.)
203  ELSEIF (phi == undefined) THEN
204  WRITE(err_msg, 1203)
205  CALL flush_err_msg(abort=.true.)
206  ENDIF
207 ! PHI is given in degrees but calculated in radian within
208 ! the fortran codes
209  lsin_phi = sin(phi*pi/180.d0)
210  sin2_phi = lsin_phi*lsin_phi
211  f_phi = (3.0d0 - 2.0d0*sin2_phi)/3.0d0 ! employed in commented
212  ENDIF
213  1200 FORMAT('Error 1200: FRICTION and SCHAEFFER models cannot be ',&
214  'used',/'together. Please correct the mfix.dat file')
215  1203 FORMAT('Error 1203: Angle of internal friction (PHI) not ', &
216  'specified.',/'Please correct the mfix.dat file.')
217 
218 
219  IF(yu_standish .AND. fedors_landel) THEN
220  WRITE(err_msg, 1300)
221  CALL flush_err_msg(abort=.true.)
222  ELSEIF(yu_standish) THEN
223 ! Yu_Standish correlation checks
224  IF(smax < 2) THEN
225  WRITE(err_msg, 1301)
226  CALL flush_err_msg(abort=.true.)
227  ENDIF
228  ELSEIF(fedors_landel) THEN
229 ! Fedors_Landel correlation checks.
230  IF(smax /= 2) THEN
231  WRITE(err_msg, 1302)
232  CALL flush_err_msg(abort=.true.)
233  ENDIF
234  ENDIF
235  1300 FORMAT('Error 1300: FEDORS_LANDEL and YU_STANDISH correlations ',&
236  'cannot be',/'used at the same time. Please correct the ', &
237  'mfix.dat file.')
238  1301 FORMAT('Error 1301: YU_STANDISH correlation is for polydisperse',&
239  ' mixtures',/'(MMAX >= 2). Please correct the mfix.dat file.')
240  1302 FORMAT('Error 1302: FEDORS_LANDEL correlation is for binary ', &
241  'mixtures (MMAX=2).',/'Please correct the mfix.dat file.')
242 
243 
244 ! Set the flags for blending stresses.
245  IF(blending_stress) THEN
246 ! Turn off the default if SIGM_BLEND is set.
247  IF(sigm_blend) tanh_blend = .false.
248  ELSE
249  tanh_blend = .false.
250  sigm_blend = .false.
251  ENDIF
252 
253 
254  IF(model_b) THEN
255  DO lc = 1, mmax
256  IF(.NOT.close_packed(lc)) THEN
257  WRITE(err_msg, 1400) lc
258  CALL flush_err_msg(abort=.true.)
259  ENDIF
260  ENDDO
261  ENDIF
262  1400 FORMAT('Error 1400: Solids phase ',i2,' is not CLOSE_PACKED.',/, &
263  'All solids phases must be CLOSE_PACKED with MODEL_B=.TURE.',/ &
264  'Please correct the mfix.dat file.')
265 
266 
267 ! Check that phase number where added mass applies is properly defined.
268  IF (added_mass) THEN
269  IF(m_am == undefined_i)THEN
270  WRITE(err_msg, 1500)
271  CALL flush_err_msg(abort=.true.)
272  ELSEIF(m_am == 0 .OR. m_am > mmax) THEN
273  WRITE(err_msg,1501)
274  CALL flush_err_msg(abort=.true.)
275  1500 FORMAT('Error 1500: Must specify a disperse phase, M_AM, where ',&
276  'the',/'virtual mass applies (ADDED_MASS).',/'Please correct',&
277  ' the mfix.dat file.')
278  1501 FORMAT('Error 1501: M_AM is out of range. [1,MMAX]',/'Please ', &
279  'correct the mfix.dat file.')
280  ENDIF
281  ENDIF
282 
283 
284 ! Check name of radial distribution function
285  SELECT CASE(trim(adjustl(rdf_type)))
286 
287  CASE ('LEBOWITZ')
288  rdf_type_enum = lebowitz
289 
290  CASE ('MODIFIED_LEBOWITZ')
291  rdf_type_enum = modified_lebowitz
292 
293  CASE ('MANSOORI')
294  rdf_type_enum = mansoori
295 
296  CASE ('MODIFIED_MANSOORI')
297  rdf_type_enum = modified_mansoori
298 
299  CASE DEFAULT
300  WRITE(err_msg, 1600)
301  CALL flush_err_msg(abort=.true.)
302  END SELECT
303 
304  1600 FORMAT('Error 1600: Unknown RDF_TYPE',/'Please ', &
305  'correct the mfix.dat file.')
306 
307 ! If the default (LEBOWITZ) is not set for a monodisperse case, then
308 ! flag the error and exit. Otherwise, change it to CARNAHAN-STARLING.
309  IF(mmax == 1) THEN
310  IF(rdf_type_enum /= lebowitz) THEN
311  WRITE(err_msg, 1601) trim(adjustl(rdf_type))
312  CALL flush_err_msg(abort=.true.)
313 
314  1601 FORMAT('Error 1601: The RDF_TYPE should NOT be specified when ',&
315  'MMAX = 1',/'because Carnahan-Starling is the only available',&
316  ' radial distribution',/'function for monodisperse systems. ',&
317  'Please correct the mfix.dat file.')
318 
319  ELSE
320  rdf_type_enum = carnahan_starling
321  ENDIF
322  ENDIF
323 
324  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
325  'correct the mfix.dat file.')
326  1001 FORMAT('Error 1001: Illegal or unphysical input: ',a,' = ',a,/ &
327  'Please correct the mfix.dat file.')
328  1002 FORMAT('Error 1002: Illegal input: ',a,' specified out of ',&
329  'range.', /,'Please correct the mfix.dat file.')
330 
331 
332  CALL finl_err_msg
333 
334 
335  RETURN
336  END SUBROUTINE check_solids_continuum
337 
338 
339 
340 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
341 ! !
342 ! Subroutine: CHECK_KT_TYPE !
343 ! Purpose: Check kinetic theory input specifications. These checks !
344 ! are almost all related to the KT_TYPE keyword. !
345 ! Notes: To enter this routine granular_energy must be true !
346 ! !
347 ! Author: J.Musser Date: 04-FEB-14 !
348 ! !
349 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
350  SUBROUTINE check_kt_type
352 
353 ! Global Variables:
354 !---------------------------------------------------------------------//
355  USE constant
356  USE run
357  USE physprop
358 
359 ! Global Parameters:
360 !---------------------------------------------------------------------//
361  USE param1, only: half, one, undefined
362 
363 ! Global Module procedures:
364 !---------------------------------------------------------------------//
365  use error_manager
366 
367  IMPLICIT NONE
368 
369 ! Local Variables:
370 !---------------------------------------------------------------------//
371 ! loop counters
372  INTEGER :: I, J
373 
374 !......................................................................!
375 
376 
377 ! Initialize the error manager.
378  CALL init_err_msg("CHECK_KT_TYPE")
379 
380 ! These are some checks to satisfy legacy input:
381  IF (ahmadi .AND. simonin) THEN
382  WRITE(err_msg, 9001)
383  CALL flush_err_msg(abort=.true.)
384  ELSEIF(ahmadi) THEN
385  IF(kt_type(1:6) /= 'AHMADI' .AND. &
386  kt_type(1:8) /= 'LUN_1984')THEN
387  WRITE(err_msg,9002)trim(kt_type)
388  CALL flush_err_msg(abort = .true.)
389  ELSE
390  kt_type='AHMADI'
391  ENDIF
392  ELSEIF(simonin) THEN
393  IF(kt_type(1:7) /= 'SIMONIN' .AND. &
394  kt_type(1:8) /= 'LUN_1984')THEN
395  WRITE(err_msg,9003)trim(kt_type)
396  CALL flush_err_msg(abort = .true.)
397  ELSE
398  kt_type='SIMONIN'
399  ENDIF
400  ENDIF
401  9001 FORMAT('Error 9001: Cannot specify AHMADI and SIMONIN together.',&
402  /'Please correct the mfix.dat file.')
403  9002 FORMAT('Error 9002: Cannot specify AHMADI and KT_TYPE = ',a,'.', &
404  /'Please correct the mfix.dat file.')
405  9003 FORMAT('Error 9003: Cannot specify SIMONIN and KT_TYPE = ',a,'.',&
406  /'Please correct the mfix.dat file.')
407 
408 
409 
410 ! Check for valid options for kinetic theory models (KT_TYPE)
411  SELECT CASE(trim(adjustl(kt_type)))
412 
413 !``````````````````````````````````````````````````````````````````````
414  CASE ('IA_NONEP')
415  kt_type_enum = ia_2005
416  IF (c_e == undefined) THEN
417  WRITE(err_msg,1003)
418  CALL flush_err_msg(abort=.true.)
419  ENDIF
420 
421 
422 !``````````````````````````````````````````````````````````````````````
423  CASE ('GD_99')
424  kt_type_enum = gd_1999
425  IF (c_e == undefined) THEN
426  WRITE(err_msg,1003)
427  CALL flush_err_msg(abort=.true.)
428  ELSEIF(smax > 1) THEN
429  WRITE(err_msg,1002) trim(kt_type)
430  CALL flush_err_msg(abort=.true.)
431  ENDIF
432 
433 
434 !``````````````````````````````````````````````````````````````````````
435  CASE ('GTSH')
436  kt_type_enum = gtsh_2012
437  IF (c_e == undefined) THEN
438  WRITE(err_msg,1002)
439  CALL flush_err_msg(abort=.true.)
440  ELSEIF(smax > 1) THEN
441  WRITE(err_msg,1002) trim(kt_type)
442  CALL flush_err_msg(abort=.true.)
443  ENDIF
444 
445 
446 !``````````````````````````````````````````````````````````````````````
447  CASE ('GHD')
448  kt_type_enum = ghd_2007
449 ! This variable is only used for GHD at this point...
450 ! Define restitution coefficient matrix
451  DO i = 1, smax
452  DO j = 1, smax
453  IF(r_p(i,j) == undefined) THEN
454  IF(c_e == undefined) THEN
455  WRITE(err_msg,1003)
456  CALL flush_err_msg(abort=.true.)
457  ELSE
458  r_p(i,j) = c_e
459  ENDIF
460  ENDIF
461 ! just need to define r_p(1,2) and r_p(2,1) will be set.
462  r_p(j,i) = r_p(i,j)
463  ENDDO
464  ENDDO
465 
466  IF(drag_type_enum /= wen_yu .AND. drag_type_enum /= hys) THEN
467  WRITE(err_msg, 1030)
468  CALL flush_err_msg(abort=.true.)
469  ELSEIF(added_mass) THEN
470  WRITE(err_msg,1031)
471  CALL flush_err_msg(abort=.true.)
472  ELSEIF(smax > 2) THEN ! not sure this is still true!
473  WRITE(err_msg, 1032)
474  CALL flush_err_msg
475  ENDIF
476 
477 ! Automatically set SPECIES_EQ(MMAX) = .FALSE. to avoid potential
478 ! checks/loops over the mmax species type eqn which has no meaning
479  species_eq(mmax) = .false.
480  nmax_s(mmax) = 1
481 
482 ! currently set to avoid an overflow error in write_res0
483 ! legacy variable?
484  nmax(mmax) = 1
485 
486  1030 FORMAT('Error 1030: KT_TYPE = "GHD" is restricted to DRAG_TYPE', &
487  'values of WEN_YU and HYS.',/'Please correct the mfix.dat ', &
488  'file.')
489  1031 FORMAT('Error 1031: ADDED_MASS force cannot be applied with ', &
490  'GHD theory that',/'solves for mixture equations.',/'Please', &
491  'correct the mifx.dat file.')
492  1032 FORMAT('Warning 1032: GHD theory may not be valid for more ', &
493  'than two solids phases',/'it requires further development.')
494 
495 
496 !``````````````````````````````````````````````````````````````````````
497  CASE ('AHMADI')
498  kt_type_enum = ahmadi_1995
499  ahmadi = .true.
500  IF(.NOT.k_epsilon) THEN
501  WRITE(err_msg,1040) 'K_EPSILON = .TRUE.'
502  CALL flush_err_msg(abort=.true.)
503  ELSEIF (c_e == undefined) THEN
504  WRITE(err_msg,1003)
505  CALL flush_err_msg(abort=.true.)
506  ELSEIF(c_f == undefined .AND. smax>=2) THEN
507  WRITE(err_msg, 1004)
508  CALL flush_err_msg(abort=.true.)
509  ENDIF
510  1040 FORMAT('Error 1040: KT_TYPE = "AHMADI" requires ',a,/ &
511  'Please correct the mfix.dat file.')
512 
513 
514 !``````````````````````````````````````````````````````````````````````
515  CASE ('SIMONIN')
516  kt_type_enum = simonin_1996
517  simonin = .true.
518  IF(.NOT.k_epsilon) THEN
519  WRITE(err_msg,1050) 'K_EPSILON = .TRUE.'
520  CALL flush_err_msg(abort=.true.)
521  ELSEIF (c_e == undefined) THEN
522  WRITE(err_msg,1003)
523  CALL flush_err_msg(abort=.true.)
524  ELSEIF(c_f == undefined .AND. smax>=2) THEN
525  WRITE(err_msg, 1004)
526  CALL flush_err_msg(abort=.true.)
527  ENDIF
528  1050 FORMAT('Error 1050: KT_TYPE = "SIMONIN" requires ',a,/ &
529  'Please correct the mfix.dat file.')
530 
531 
532 ! Lun is the default implementation.
533 !``````````````````````````````````````````````````````````````````````
534  CASE ('LUN_1984')
535  kt_type_enum = lun_1984
536 ! this version of the restitution coefficient is needed by most KT_TYPE
537 ! models. it is also needed in default solids-solids drag model
538  IF (c_e == undefined) THEN
539  WRITE(err_msg,1003)
540  CALL flush_err_msg(abort=.true.)
541  ELSEIF(c_f == undefined .AND. smax>=2) THEN
542  WRITE(err_msg, 1004)
543  CALL flush_err_msg(abort=.true.)
544  ENDIF
545 
546 
547  CASE DEFAULT
548  WRITE(err_msg,1001) trim(adjustl(kt_type))
549  CALL flush_err_msg(abort=.true.)
550  1001 FORMAT('Error 1001: Invalid or unknown KT_TYPE: ',a,/ &
551  'Please correct the mfix.dat file.')
552 
553  END SELECT
554 
555 ! eventually this should be made specific to lun/ahmadi/simonin
556 ! but because calc_gw_hw_cw in calc_u_friction is not consistent
557 ! it currently must be defined for all kt_types whenever friction
558 ! is invoked...
559  eta = (one + c_e)*half
560 
561 
562  1002 FORMAT('Error 1002: KT_TYPE = ',a,' is for monodisperse',&
563  ' solids',/'(MMAX = 1). Please correct the mfix.dat file.')
564 
565  1003 FORMAT('Error 1003: Coefficient of restitution (C_E) not ', &
566  'specified.',/'Please correct the mfix.dat file.')
567 
568  1004 FORMAT('Error 1004: Coefficient of friction (C_F) not ', &
569  'specified.',/'Please correct the mfix.dat file.')
570 
571 
572  RETURN
573  END SUBROUTINE check_kt_type
double precision c_e
Definition: constant_mod.f:105
logical dem_solids
Definition: run_mod.f:257
character(len=32) function ivar(VAR, i1, i2, i3)
subroutine finl_err_msg
double precision, parameter one
Definition: param1_mod.f:29
double precision phi
Definition: constant_mod.f:117
logical sigm_blend
Definition: run_mod.f:163
logical added_mass
Definition: run_mod.f:91
double precision, dimension(dim_m) dif_s0
Definition: physprop_mod.f:113
logical, dimension(0:dim_m) species_eq
Definition: run_mod.f:115
logical friction
Definition: run_mod.f:149
subroutine check_solids_continuum
double precision, parameter undefined
Definition: param1_mod.f:18
logical, dimension(dim_m) close_packed
Definition: physprop_mod.f:56
double precision sin_phi
Definition: constant_mod.f:123
double precision c_f
Definition: constant_mod.f:114
double precision phi_w
Definition: constant_mod.f:120
subroutine init_err_msg(CALLER)
integer mmax
Definition: physprop_mod.f:19
logical simonin
Definition: run_mod.f:143
subroutine check_kt_type
integer m_am
Definition: run_mod.f:94
double precision eta
Definition: constant_mod.f:108
logical schaeffer
Definition: run_mod.f:157
integer savage
Definition: run_mod.f:154
double precision, parameter half
Definition: param1_mod.f:28
Definition: run_mod.f:13
logical yu_standish
Definition: run_mod.f:180
double precision ep_star
Definition: constant_mod.f:29
double precision sin2_phi
Definition: constant_mod.f:126
logical blending_stress
Definition: run_mod.f:161
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
logical ahmadi
Definition: run_mod.f:146
logical k_epsilon
Definition: run_mod.f:97
logical fedors_landel
Definition: run_mod.f:183
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
double precision tan_phi_w
Definition: constant_mod.f:132
logical model_b
Definition: run_mod.f:88
integer smax
Definition: physprop_mod.f:22
logical tanh_blend
Definition: run_mod.f:162
double precision, dimension(dim_m) mu_s0
Definition: physprop_mod.f:53
double precision, dimension(dim_m, dim_m) r_p
Definition: constant_mod.f:111
double precision, parameter pi
Definition: constant_mod.f:158
logical granular_energy
Definition: run_mod.f:112
double precision f_phi
Definition: constant_mod.f:129
integer, dimension(dim_m) nmax_s
Definition: physprop_mod.f:121
double precision, parameter zero
Definition: param1_mod.f:27
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)