MFIX  2016-1
check_geometry.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! SUBROUTINE: CHECK_GEOMETRY !
4 ! Purpose: Check the distributed parallel namelist variables. !
5 ! !
6 ! Author: P. Nicoletti Date: 14-DEC-99 !
7 ! Reviewer: J.Musser Date: 16-Jan-14 !
8 ! !
9 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
10  SUBROUTINE check_geometry(SHIFT)
11 
13 
14 ! Global Variables:
15 !---------------------------------------------------------------------//
16 ! Domain partitions in various directions.
17  use geometry, only: dx, xlength
18  use geometry, only: dy, ylength
19  use geometry, only: dz, zlength
20 
21  use geometry, only: no_i, imin1, imax, imax1, imax3
22  use geometry, only: no_j, jmin1, jmax, jmax1, jmax3
23  use geometry, only: no_k, kmin1, kmax, kmax1, kmax3
24 
25 ! Runtime flag specifying 2D simulations
26 ! use geometry, only: NO_K
27 
28  use geometry, only: cylindrical
29  use geometry, only: cyclic_x, cyclic_x_pd
30  use geometry, only: cyclic_y, cyclic_y_pd
31  use geometry, only: cyclic_z, cyclic_z_pd
32 ! use geometry, only: COORDINATES
33 
34 ! Use the error manager for posting error messages.
35 !---------------------------------------------------------------------//
36  use error_manager
37 
38  implicit none
39 
40 
41  LOGICAL, intent(IN) :: SHIFT
42  LOGICAL, external :: COMPARE
43 
44 ! Local Variables:
45 !---------------------------------------------------------------------//
46 
47 
48 ! Initialize the error manager.
49  CALL init_err_msg("CHECK_GEOMETRY")
50 
52 
53  CALL check_axis(imax, imax3, xlength, dx, 'X', 'I', no_i, shift)
54  CALL check_axis(jmax, jmax3, ylength, dy, 'Y', 'J', no_j, shift)
55  CALL check_axis(kmax, kmax3, zlength, dz, 'Z', 'K', no_k, shift)
56 
57  IF(shift) CALL shift_dxyz
58 
59 ! Ensure that the cell sizes across cyclic boundaries are comparable
60  IF(cyclic_x .OR. cyclic_x_pd) THEN
61  IF(dx(imin1) /= dx(imax1)) THEN
62  WRITE(err_msg,1100) 'DX(IMIN1)',dx(imin1),'DX(IMAX1)',dx(imax1)
63  CALL flush_err_msg(abort=.true.)
64  ENDIF
65  ENDIF
66 
67  IF(cyclic_y .OR. cyclic_y_pd) THEN
68  IF(dy(jmin1) /= dy(jmax1)) THEN
69  WRITE(err_msg,1100) 'DY(JMIN1)',dy(jmin1),'DY(JMAX1)',dy(jmax1)
70  CALL flush_err_msg(abort=.true.)
71  ENDIF
72  ENDIF
73 
74  IF(cyclic_z .OR. cyclic_z_pd .OR. cylindrical) THEN
75  IF (dz(kmin1) /= dz(kmax1)) THEN
76  WRITE(err_msg,1100) 'DZ(KMIN1)',dz(kmin1),'DZ(KMAX1)',dz(kmax1)
77  CALL flush_err_msg(abort=.true.)
78  ENDIF
79  ENDIF
80 
81  1100 FORMAT('Error 1100: Cells adjacent to cyclic boundaries must ', &
82  'be of same size:',/2x,a,' = ',g12.5,/2x,a,' = ',g12.5,/ &
83  'Please correct the mfix.dat file.')
84 
85 
86  CALL finl_err_msg
87 
88  RETURN
89 
90  END SUBROUTINE check_geometry
91 
92 
93 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
94 ! !
95 ! SUBROUTINE: CHECK_GEOMETRY_DES !
96 ! Author: Pradeep Gopalakrishnan Date: Nov-11 !
97 ! !
98 ! Purpose: Checks the des grid input parameters. !
99 ! !
100 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
101  SUBROUTINE check_geometry_des
103 ! Global Variables:
104 !---------------------------------------------------------------------//
105 ! Domain partition for DEM background mesh.
106  use discretelement, only: desgridsearch_imax
107  use discretelement, only: desgridsearch_jmax
108  use discretelement, only: desgridsearch_kmax
109 ! Domain size specified by the user.
110  use geometry, only: xlength, ylength, zlength, no_k
111 ! Maximum particle size.
112  use discretelement, only: max_radius
113 
114 
115 ! Global Parameters:
116 !---------------------------------------------------------------------//
117  use param1, only: undefined_i
118 
119 ! Use the error manager for posting error messages.
120 !---------------------------------------------------------------------//
121  use error_manager
122 
123 
124  implicit none
125 
126 
127 ! Local Variables:
128 !---------------------------------------------------------------------//
129 ! Maximum particle diameter.
130  DOUBLE PRECISION :: MAX_DIAM
131 ! Calculated cell dimension based on particle size
132  DOUBLE PRECISION :: WIDTH
133 !......................................................................!
134 
135 ! Initialize the error manager.
136  CALL init_err_msg("CHECK_GEOMETRY_DES")
137 
138 ! Calculate the max particle diameter and cell width.
139  max_diam = 2.0d0*max_radius
140  width = 3.0d0*(max_diam)
141 
142 ! Calculate and/or verify the grid in the X-axial direction.
143  IF(desgridsearch_imax == undefined_i) THEN
144  desgridsearch_imax = max(int(xlength/width), 1)
145  ELSEIF((xlength/dble(desgridsearch_imax)) < max_diam) THEN
146  WRITE(err_msg, 1100) 'X', max_diam, &
147  xlength/dble(desgridsearch_imax)
148  CALL flush_err_msg(abort=.true.)
149  ENDIF
150 
151 ! Calculate and/or verify the grid in the Y-axial direction.
152  IF(desgridsearch_jmax == undefined_i) THEN
153  desgridsearch_jmax = max(int(ylength/width), 1)
154  ELSEIF((ylength/dble(desgridsearch_jmax)) < max_diam) THEN
155  WRITE(err_msg, 1100) 'Y', max_diam, &
156  ylength/dble(desgridsearch_jmax)
157  CALL flush_err_msg(abort=.true.)
158  ENDIF
159 
160 ! Calculate and/or verify the grid in the Z-axial direction.
161  IF(no_k) THEN
162  desgridsearch_kmax = 1
163  ELSEIF(desgridsearch_kmax == undefined_i) THEN
164  desgridsearch_kmax = max(int(zlength/width), 1)
165  ELSEIF((zlength/dble(desgridsearch_kmax)) < max_diam) THEN
166  WRITE(err_msg, 1100) 'Z', max_diam, &
167  zlength/dble(desgridsearch_kmax)
168  CALL flush_err_msg(abort=.true.)
169  ENDIF
170 
171  CALL finl_err_msg
172 
173  1100 FORMAT('Error 1100: The des search grid is too fine in the ',a1, &
174  '-direction. The',/'maximum particle diameter is larger than',&
175  ' the cell width:',/2x,'MAX DIAM: ',g12.5,/2x,'CELL ', &
176  'WIDTH: ',g12.5,/'Decrease the values for DESGRIDSEARCH in ', &
177  'the mfix.dat file.')
178 
179  RETURN
180  END SUBROUTINE check_geometry_des
subroutine finl_err_msg
logical no_i
Definition: geometry_mod.f:20
integer imax3
Definition: geometry_mod.f:91
subroutine check_axis(NA, DIMEN, ALENGTH, DA, AXIS, AXIS_INDEX, NO_IJK, SHIFT)
Definition: check_axis.f:11
double precision, dimension(0:dim_j) dy
Definition: geometry_mod.f:70
logical cyclic_z
Definition: geometry_mod.f:153
double precision, dimension(0:dim_k) dz
Definition: geometry_mod.f:72
logical cyclic_z_pd
Definition: geometry_mod.f:159
integer imax
Definition: geometry_mod.f:47
subroutine init_err_msg(CALLER)
integer kmax1
Definition: geometry_mod.f:58
subroutine get_dxyz_from_control_points
logical cyclic_y_pd
Definition: geometry_mod.f:157
integer imax1
Definition: geometry_mod.f:54
logical cyclic_y
Definition: geometry_mod.f:151
integer jmax3
Definition: geometry_mod.f:91
double precision, dimension(0:dim_i) dx
Definition: geometry_mod.f:68
double precision xlength
Definition: geometry_mod.f:33
integer jmax1
Definition: geometry_mod.f:56
logical cyclic_x
Definition: geometry_mod.f:149
integer kmax
Definition: geometry_mod.f:51
logical no_k
Definition: geometry_mod.f:28
integer jmin1
Definition: geometry_mod.f:42
integer kmax3
Definition: geometry_mod.f:91
logical cyclic_x_pd
Definition: geometry_mod.f:155
logical no_j
Definition: geometry_mod.f:24
logical cylindrical
Definition: geometry_mod.f:168
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
integer jmax
Definition: geometry_mod.f:49
subroutine check_geometry(SHIFT)
double precision ylength
Definition: geometry_mod.f:35
subroutine check_geometry_des
subroutine shift_dxyz
Definition: shift_dxyz.f:29
integer imin1
Definition: geometry_mod.f:40
integer kmin1
Definition: geometry_mod.f:44
double precision zlength
Definition: geometry_mod.f:37
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)