MFIX  2016-1
check_ic_dem.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: CHECK_IC_DEM !
4 ! Author: R.Garg Date: 11-Mar-14 !
5 ! !
6 ! Purpose: check the initial conditions input section for DEM model !
7 ! - calculate the number of particles needed to initialize the !
8 ! DEM model !
9 ! !
10 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
11  SUBROUTINE check_ic_dem
12 
13 ! Global variables
14 !---------------------------------------------------------------------//
15 ! Runtime Flag: Generate initial particle configuration.
16  USE discretelement, only : gener_part_config
17 ! Simulation dimension (2D/3D)
18  USE discretelement, only: dimn
19 ! Number of DEM solids phases.
20  USE discretelement, only: des_mmax
21 ! runtime flag to specify if the simulation uses both discrete/continuum
22 ! solids
23  USE discretelement, only: des_continuum_hybrid
24 
25 ! direction wise spans of the domain and grid spacing in each direction
26  Use geometry, only: zlength
27 ! Use the error manager for posting error messages.
28  use error_manager
29 
30  use physprop, only: mmax, d_p0
31  use toleranc
32 
33  implicit none
34 ! Local variables
35 !---------------------------------------------------------------------//
36  integer :: dm
37 !......................................................................!
38 
39 ! Initialize the error manager.
40  CALL init_err_msg("CHECK_IC_DEM")
41 
42 ! Determine the domain volume which is used to calculate the total
43 ! number of particles and the number of particles in each phase.
44 ! Values of DZ(1) or zlength are guaranteed at this point due to
45 ! check_geometry_prereqs. If the user left both undefined and
46 ! NO_K = .T., then they are set to ONE. If dz(1) is undefined but
47 ! zlength is defined, then dz(1) is set to zlength (and vice versa).
48 ! If both are defined they must be equal.
49  IF(dimn.EQ.2) THEN
50  IF (des_mmax.EQ.1) THEN
51 ! account for a possible offset index when using d_p0 and ro_s.
52  dm = mmax+1
53 ! Warn the user if the domain depth is not equal to the particle
54 ! diameter as it may cause problems for coupled simulations.
55 ! The user should also be aware of this when interpreting
56 ! volume/void fraction calculations (including bulk density).
57  IF(.NOT.compare(zlength,d_p0(dm))) THEN
58  WRITE(err_msg, 1000) ival(d_p0(dm))
59  CALL flush_err_msg
60  ENDIF
61  ELSE
62 ! Let the user know basis of depth dimension for calculating number of
63 ! particles. this will also be important when considering volume/void
64 ! fraction calculations.
65  WRITE(err_msg, 1001)
66  CALL flush_err_msg
67  ENDIF
68  ENDIF
69 
70 
71  1000 FORMAT(' Message: ',&
72  'WARNING: zlength or dz(1) is used to calculate the ',&
73  'number of particles in the 2D simulation when ',&
74  'GENER_PART_CONFIG is T and DIMN = 2.',/10x,'This depth ',&
75  'does not equal D_P0 = ', a, '.')
76 
77  1001 FORMAT(' Message: ',&
78  'WARNING: zlength or dz(1) is used to calculate the ',&
79  'number of particles in the 2D simulation when ',&
80  'GENER_PART_CONFIG is T and DIMN = 2.')
81 
82 
83  IF (gener_part_config.and.des_continuum_hybrid) THEN
84  WRITE(err_msg, 999)
85  CALL flush_err_msg(abort=.true.)
86  ENDIF
87 
88  999 format('Error # 999: Gener_part_config set to', &
89  ' true for DES_continuum hybrid', /, &
90  ' This is not allowed, specify the initial particle', &
91  ' configuration explicitly', /, &
92  ' See MFIX readme', /, &
93  ' Please correct the data file.')
94 
95  CALL finl_err_msg
96 
97  END SUBROUTINE check_ic_dem
double precision, dimension(dim_m) d_p0
Definition: physprop_mod.f:25
subroutine finl_err_msg
logical function compare(V1, V2)
Definition: toleranc_mod.f:94
subroutine check_ic_dem
Definition: check_ic_dem.f:12
subroutine init_err_msg(CALLER)
integer mmax
Definition: physprop_mod.f:19
character(len=line_length), dimension(line_count) err_msg
double precision zlength
Definition: geometry_mod.f:37
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)