MFIX  2016-1
set_geometry_des.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: SET_GEOMETRY_DES !
4 ! Author: R.Garg Date: 19-Mar-14 !
5 ! !
6 ! Purpose: Allocate des arrays that are based on Eulerian grid. !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  SUBROUTINE set_geometry_des
10 
11 
12 ! Global Variables:
13 !---------------------------------------------------------------------//
14 ! Arrays for DEM simulations delineating cell edges.
15  use discretelement, only: xe, yn, zt, dimn
16 ! Domain bounds (max/min).
17  use discretelement, only: ex2, ty2, nz2, wx1, by1, sz1
18 ! Fluid grid cell dimensions and mesh size
19  USE geometry, only: dx, imin2, imax2
20  USE geometry, only: dy, jmin2, jmax2
21  USE geometry, only: dz, kmin2, kmax2
22 ! Number of particles in the I/J/K direction
24 
25 ! Global Parameters:
26 !---------------------------------------------------------------------//
27  use param1, only: zero
28 
29 ! Module proceedures.
30 !---------------------------------------------------------------------//
31  use mpi_utility
32  use error_manager
33 
34  IMPLICIT NONE
35 
36 ! Local Variables:
37 !---------------------------------------------------------------------//
38 ! Generic loop indices
39  INTEGER :: I, J, K
40 ! Error Flag
41  INTEGER :: IER
42 !......................................................................!
43 
44 ! Initialize the error manager.
45  CALL init_err_msg("SET_GEOMETRY_DES")
46 
47  Allocate( xe(0:dimension_i), stat=ier )
48  Allocate( yn(0:dimension_j), stat=ier )
49  Allocate( zt(0:dimension_k), stat=ier )
50 
51 ! Collect the error flags from all ranks. If all allocaitons were
52 ! successfull, do nothing. Otherwise, flag the error and abort.
53  CALL global_all_sum(ier)
54 
55 
56 ! Set boundary edges.
57 ! In some instances wx1,ex2, etc have been used and in others
58 ! xlength,zero, etc are used. the code should be modified for
59 ! consistency throughout
60  ex2 = xlength; wx1 = zero ! East/West
61  ty2 = ylength; by1 = zero ! North/South
62  nz2 = zlength; sz1 = zero ! Top/Bottom
63 
64 ! Initialize arrays.
65  xe(:) = zero
66  yn(:) = zero
67  zt(:) = zero
68 
69 ! Each loop starts at 2 and goes to max+2 (i.e., imin1=2, imax2=imax+2)
70 ! However, the indices range to include ghost cells (0-imax2) to avoid
71 ! multiple if statements in particles_in_cell
72  xe(imin2-1) = zero-dx(imin2)
73  DO i = imin2, imax2
74  xe(i) = xe(i-1) + dx(i)
75  ENDDO
76 
77  yn(jmin2-1) = zero-dy(jmin2)
78  DO j = jmin2, jmax2
79  yn(j) = yn(j-1) + dy(j)
80  ENDDO
81 
82  IF(dimn.EQ.3) THEN
83  zt(kmin2-1) = zero-dz(kmin2)
84  DO k = kmin2, kmax2
85  zt(k) = zt(k-1) + dz(k)
86  ENDDO
87  ENDIF
88 
89  CALL finl_err_msg
90 
91  RETURN
92  END SUBROUTINE set_geometry_des
integer dimension_i
Definition: param_mod.f:7
integer imax2
Definition: geometry_mod.f:61
subroutine finl_err_msg
integer dimension_k
Definition: param_mod.f:9
double precision, dimension(0:dim_j) dy
Definition: geometry_mod.f:70
double precision, dimension(0:dim_k) dz
Definition: geometry_mod.f:72
integer jmin2
Definition: geometry_mod.f:89
subroutine init_err_msg(CALLER)
subroutine set_geometry_des
integer jmax2
Definition: geometry_mod.f:63
double precision, dimension(0:dim_i) dx
Definition: geometry_mod.f:68
integer kmax2
Definition: geometry_mod.f:65
Definition: param_mod.f:2
integer imin2
Definition: geometry_mod.f:89
double precision, parameter zero
Definition: param1_mod.f:27
integer kmin2
Definition: geometry_mod.f:89
integer dimension_j
Definition: param_mod.f:8