File: N:\mfix\model\des\des_bc_mod.f

1     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2     !                                                                      !
3     !  Module name: DES_INLET                                              !
4     !                                                                      !
5     !  Purpose: Common elements needed for the des mass inflow boundary    !
6     !  condition.                                                          !
7     !                                                                      !
8     !  Author: J.Musser                                   Date: 13-Jul-09  !
9     !                                                                      !
10     !  Comments:                                                           !
11     !                                                                      !
12     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
13     
14           MODULE DES_BC
15     
16           USE param, only: dimension_bc, dim_m
17     
18           INTEGER :: DEM_BCMI
19           INTEGER :: DEM_BCMO
20     
21           LOGICAL DEM_MIO  ! either inlet or outlet exists
22     
23     ! Map between DEM MI/MO IDs and the user input BC index.
24           INTEGER :: DEM_BCMI_MAP(DIMENSION_BC)
25           INTEGER :: DEM_BCMO_MAP(DIMENSION_BC)
26     
27     ! This array contains integers representing the mass/solid phase indices
28     ! present at a specific boundary condtion in proportion to their
29     ! respective number fraction at the inlet (i.e., it represents the
30     ! particle number distribution of incoming solids at the inlet).  The
31     ! array is scaled in size according to the parameter NUMFRAC_LIMIT.
32           INTEGER, DIMENSION(:,:), ALLOCATABLE :: DEM_BC_POLY_LAYOUT
33     
34     ! Particle injection time scale; used when pi_factor > 1 to keep track
35     ! of time needed for next injection
36           DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: DEM_MI_TIME
37     
38     ! Logical that can be flagged in the mfix.dat file to force the inlet
39     ! to operate with an ordered boundary condition.  This may be useful
40     ! during long simulations or if the inlet appears to be taking a long
41     ! time to randomly place particles.
42           LOGICAL :: FORCE_ORD_BC
43     
44     ! Particle injection factor; how many solid time steps (dtsolid) pass
45     ! before the next injection of a particle. if pi_count is greater than
46     ! 1, then pi_factor is set to 1 (i.e. multiple particles enter every
47     ! solids time step).
48           INTEGER, DIMENSION(:), ALLOCATABLE :: PI_FACTOR   !(DES_BCMI)
49     
50     ! Particle injection count (injection number); how many particles are
51     ! injected in one solids time step. pi_count is set to one if
52     ! less than 1 particle enters per solids time step.
53           INTEGER, DIMENSION(:), ALLOCATABLE :: PI_COUNT   !(DES_BCMI)
54     
55     
56     ! Limit on the total number of divisions (fineness) used to represent
57     ! the particle number distribution at an inlet.
58           INTEGER, PARAMETER :: NUMFRAC_LIMIT = 10000
59     
60     
61     ! the dimension of this variable is equal to the number of grid
62     ! cells in the inlet edge/face
63           TYPE DEM_MI_
64     ! Array position of next seed location.
65              INTEGER :: VACANCY
66     ! Number of positions in the layout grid.
67              INTEGER :: OCCUPANTS
68     ! Flag for polydisperse inlets.
69              LOGICAL :: POLYDISPERSE
70     ! Uniform grid dimension (width and height).
71              DOUBLE PRECISION :: WINDOW
72     ! Offset for placing particles in ghost cell.
73              DOUBLE PRECISION :: OFFSET
74     ! Fluid cell index associated with each grid. (I/J/K like)
75              INTEGER :: L
76              INTEGER, ALLOCATABLE :: W(:)
77              INTEGER, ALLOCATABLE :: H(:)
78     ! Spatial location of each grid cell's lower, bottom corder.
79              DOUBLE PRECISION, ALLOCATABLE :: P(:)
80              DOUBLE PRECISION, ALLOCATABLE :: Q(:)
81     ! The rank of the owning process owning the indexed grid cell.
82              INTEGER, ALLOCATABLE :: OWNER(:)
83           END TYPE DEM_MI_
84     
85     ! Construct an array of integers in values from 1 to a calculated factor
86     ! in a random order, which is used when placing new particles.
87     !      TYPE(DEM_MI_DATA), DIMENSION(:), ALLOCATABLE :: MI_ORDER
88     
89     ! Array linking all of the reaction data.
90           TYPE(DEM_MI_), DIMENSION(:), TARGET, ALLOCATABLE :: DEM_MI
91     
92           INTEGER, ALLOCATABLE :: DEM_BCMO_IJKSTART(:)
93           INTEGER, ALLOCATABLE :: DEM_BCMO_IJKEND(:)
94     
95           INTEGER, ALLOCATABLE :: DEM_BCMO_IJK(:)
96     
97     
98           INTEGER, ALLOCATABLE :: DEM_BCMI_IJKSTART(:)
99           INTEGER, ALLOCATABLE :: DEM_BCMI_IJKEND(:)
100     
101           INTEGER, ALLOCATABLE :: DEM_BCMI_IJK(:)
102     
103     
104     !----------------------------------------------------------------------!
105     
106     
107     ! DES specification for solids phase velocity for WALL boundary
108     ! conditions. The current setup is fairly limited. The specified
109     ! boundary velocities are assigned to the indicated wall where a wall
110     ! corresponds to one of the six planes in a cubic domain. Each wall
111     ! corresponds to a number as follows west=1, east=2, bottom=3, top=4,
112     ! south=5, north=6. See cfwallposvel for details. To specify a y or z
113     ! velocity to the west wall set des_bc_vw_s(1,M) or des_bc_ww_s(1,M),
114     ! respectively (note an x velocity is not valid for a west or east wall).
115     ! Since these are user input, they are allocated here with a constant
116     ! preset size, but their actual size is represented by &
117     ! (nwalls, des_mmax)
118           DOUBLE PRECISION DES_BC_Uw_s(DIMENSION_BC, DIM_M)
119           DOUBLE PRECISION DES_BC_Vw_s(DIMENSION_BC, DIM_M)
120           DOUBLE PRECISION DES_BC_Ww_s(DIMENSION_BC, DIM_M)
121     
122           CONTAINS
123     !----------------------------------------------------------------------!
124     !  Function to exclude cells from DEM mass inlet.                      !
125     !----------------------------------------------------------------------!
126           LOGICAL FUNCTION EXCLUDE_DEM_MI_CELL(lI, lJ, lK)
127     
128           use functions, only: FUNIJK
129           use functions, only: FLUID_AT
130           use functions, only: IS_ON_myPE_plus2layers
131     
132           use compar, only: DEAD_CELL_AT
133     
134     ! Indicies of cell to check
135           INTEGER, INTENT(IN) :: lI, lJ, lK
136     ! Local value for IJK
137           INTEGER :: IJK
138     
139           EXCLUDE_DEM_MI_CELL = .TRUE.
140     
141           IF(.NOT.IS_ON_myPE_plus2layers(lI,lJ,lK)) RETURN
142           IF(DEAD_CELL_AT(lI,lJ,lK)) RETURN
143           IJK = FUNIJK(lI,lJ,lK)
144           IF(.NOT.FLUID_AT(IJK)) RETURN
145     
146           EXCLUDE_DEM_MI_CELL = .FALSE.
147           RETURN
148           END FUNCTION EXCLUDE_DEM_MI_CELL
149     
150           END MODULE DES_BC
151     
152