15 SUBROUTINE get_connectivity(IJK,TYPE_OF_CELL,N_NEW_POINTS,N_NODES,CONNECT,X_NP,Y_NP,Z_NP,TOTAL_NUMBER_OF_INTERSECTIONS,&
16 x_intersect,y_intersect,z_intersect)
29 INTEGER :: I,J,K,IM,JM,KM
30 INTEGER :: IJK,IMJK,IJMK,IJKM,IMJMK,IMJKM,IJMKM,IMJMKM
32 LOGICAL,
DIMENSION(8) :: CORNER_INTERSECTION
33 INTEGER :: TOTAL_NUMBER_OF_INTERSECTIONS,NUMBER_OF_EDGE_INTERSECTIONS
34 INTEGER :: NUMBER_OF_CORNER_INTERSECTIONS,MAX_CORNER_INTERSECTIONS
35 INTEGER :: N_NODES,N_NEW_POINTS
36 INTEGER :: NODE,N_N1,N_N2,Q_ID,BCID
37 INTEGER,
DIMENSION(DIMENSION_3,15) :: CONNECT
38 DOUBLE PRECISION,
DIMENSION(DIMENSION_MAX_CUT_CELL) :: X_NP,Y_NP,Z_NP
39 DOUBLE PRECISION,
DIMENSION(DIMENSION_3) :: X_intersect,Y_intersect,Z_intersect
40 CHARACTER (LEN=*) :: TYPE_OF_CELL
60 imjmk = funijk(im,jm,k)
61 imjkm = funijk(im,j,km)
62 ijmkm = funijk(i,jm,km)
64 imjmkm = funijk(im,jm,km)
73 corner_intersection = .false.
74 number_of_corner_intersections = 0
75 number_of_edge_intersections = 0
97 corner_intersection(node) = .true.
98 number_of_corner_intersections = number_of_corner_intersections + 1
105 corner_intersection(node) = .true.
106 number_of_corner_intersections = number_of_corner_intersections + 1
107 n_nodes = n_nodes + 1
123 IF((.NOT.corner_intersection(1)).AND.(.NOT.corner_intersection(2)))
THEN 124 number_of_edge_intersections = number_of_edge_intersections + 1
125 n_new_points = n_new_points + 1
126 x_np(n_new_points) = x_intersect(ijmkm)
127 y_np(n_new_points) =
y_node(1)
128 z_np(n_new_points) =
z_node(1)
129 n_nodes = n_nodes + 1
130 connect(ijk,n_nodes) = n_new_points +
ijkend3 135 IF((.NOT.corner_intersection(2)).AND.(.NOT.corner_intersection(4)))
THEN 136 number_of_edge_intersections = number_of_edge_intersections + 1
137 n_new_points = n_new_points + 1
138 x_np(n_new_points) =
x_node(2)
139 y_np(n_new_points) = y_intersect(ijkm)
140 z_np(n_new_points) =
z_node(2)
141 n_nodes = n_nodes + 1
142 connect(ijk,n_nodes) = n_new_points +
ijkend3 147 IF((.NOT.corner_intersection(3)).AND.(.NOT.corner_intersection(4)))
THEN 148 number_of_edge_intersections = number_of_edge_intersections + 1
149 n_new_points = n_new_points + 1
150 x_np(n_new_points) = x_intersect(ijkm)
151 y_np(n_new_points) =
y_node(3)
152 z_np(n_new_points) =
z_node(3)
153 n_nodes = n_nodes + 1
154 connect(ijk,n_nodes) = n_new_points +
ijkend3 159 IF((.NOT.corner_intersection(1)).AND.(.NOT.corner_intersection(3)))
THEN 160 number_of_edge_intersections = number_of_edge_intersections + 1
161 n_new_points = n_new_points + 1
162 x_np(n_new_points) =
x_node(1)
163 y_np(n_new_points) = y_intersect(imjkm)
164 z_np(n_new_points) =
z_node(1)
165 n_nodes = n_nodes + 1
166 connect(ijk,n_nodes) = n_new_points +
ijkend3 174 IF((.NOT.corner_intersection(5)).AND.(.NOT.corner_intersection(6)))
THEN 175 number_of_edge_intersections = number_of_edge_intersections + 1
176 n_new_points = n_new_points + 1
177 x_np(n_new_points) = x_intersect(ijmk)
178 y_np(n_new_points) =
y_node(5)
179 z_np(n_new_points) =
z_node(5)
180 n_nodes = n_nodes + 1
181 connect(ijk,n_nodes) = n_new_points +
ijkend3 186 IF((.NOT.corner_intersection(6)).AND.(.NOT.corner_intersection(8)))
THEN 187 number_of_edge_intersections = number_of_edge_intersections + 1
188 n_new_points = n_new_points + 1
189 x_np(n_new_points) =
x_node(6)
190 y_np(n_new_points) = y_intersect(ijk)
191 z_np(n_new_points) =
z_node(6)
192 n_nodes = n_nodes + 1
193 connect(ijk,n_nodes) = n_new_points +
ijkend3 198 IF((.NOT.corner_intersection(7)).AND.(.NOT.corner_intersection(8)))
THEN 199 number_of_edge_intersections = number_of_edge_intersections + 1
200 n_new_points = n_new_points + 1
201 x_np(n_new_points) = x_intersect(ijk)
202 y_np(n_new_points) =
y_node(7)
203 z_np(n_new_points) =
z_node(7)
204 n_nodes = n_nodes + 1
205 connect(ijk,n_nodes) = n_new_points +
ijkend3 210 IF((.NOT.corner_intersection(5)).AND.(.NOT.corner_intersection(7)))
THEN 211 number_of_edge_intersections = number_of_edge_intersections + 1
212 n_new_points = n_new_points + 1
213 x_np(n_new_points) =
x_node(5)
214 y_np(n_new_points) = y_intersect(imjk)
215 z_np(n_new_points) =
z_node(5)
216 n_nodes = n_nodes + 1
217 connect(ijk,n_nodes) = n_new_points +
ijkend3 225 IF((.NOT.corner_intersection(1)).AND.(.NOT.corner_intersection(5)))
THEN 226 number_of_edge_intersections = number_of_edge_intersections + 1
227 n_new_points = n_new_points + 1
228 x_np(n_new_points) =
x_node(1)
229 y_np(n_new_points) =
y_node(1)
230 z_np(n_new_points) = z_intersect(imjmk)
231 n_nodes = n_nodes + 1
232 connect(ijk,n_nodes) = n_new_points +
ijkend3 237 IF((.NOT.corner_intersection(2)).AND.(.NOT.corner_intersection(6)))
THEN 238 number_of_edge_intersections = number_of_edge_intersections + 1
239 n_new_points = n_new_points + 1
240 x_np(n_new_points) =
x_node(2)
241 y_np(n_new_points) =
y_node(2)
242 z_np(n_new_points) = z_intersect(ijmk)
243 n_nodes = n_nodes + 1
244 connect(ijk,n_nodes) = n_new_points +
ijkend3 249 IF((.NOT.corner_intersection(4)).AND.(.NOT.corner_intersection(8)))
THEN 250 number_of_edge_intersections = number_of_edge_intersections + 1
251 n_new_points = n_new_points + 1
252 x_np(n_new_points) =
x_node(4)
253 y_np(n_new_points) =
y_node(4)
254 z_np(n_new_points) = z_intersect(ijk)
255 n_nodes = n_nodes + 1
256 connect(ijk,n_nodes) = n_new_points +
ijkend3 261 IF((.NOT.corner_intersection(3)).AND.(.NOT.corner_intersection(7)))
THEN 262 number_of_edge_intersections = number_of_edge_intersections + 1
263 n_new_points = n_new_points + 1
264 x_np(n_new_points) =
x_node(3)
265 y_np(n_new_points) =
y_node(3)
266 z_np(n_new_points) = z_intersect(imjk)
267 n_nodes = n_nodes + 1
268 connect(ijk,n_nodes) = n_new_points +
ijkend3 279 max_corner_intersections = 2
281 max_corner_intersections = 4
285 IF(number_of_corner_intersections > max_corner_intersections)
THEN 287 WRITE(*,*)
'WARNING:',number_of_corner_intersections,&
288 ' CORNER INTERSECTIONS DETECTED IN CELL IJK=',ijk
289 WRITE(*,*)
'THIS USUALLY INDICATE A FALSE CUT-CELL (CORNER CELL)' 291 WRITE(*,*)
'REMOVING CUT CELL' 299 number_of_corner_intersections = -number_of_edge_intersections -1
304 total_number_of_intersections = number_of_edge_intersections + number_of_corner_intersections
334 CHARACTER (LEN=*) :: TYPE_OF_CELL
335 DOUBLE PRECISION:: Xw,Xe,Yn,Ys,Zb,Zt
336 INTEGER :: I,J,K,IP,JP,KP,IM,JM,KM
337 INTEGER :: IJK,IMJK,IJMK,IJKM,IMJMK,IMJKM,IJMKM,IMJMKM
351 imjk = funijk(im,j,k)
352 ijmk = funijk(i,jm,k)
353 ijkm = funijk(i,j,km)
355 imjmk = funijk(im,jm,k)
356 imjkm = funijk(im,j,km)
357 ijmkm = funijk(i,jm,km)
359 imjmkm = funijk(im,jm,km)
373 SELECT CASE (type_of_cell)
431 WRITE(*,*)
'SUBROUTINE: GET_CELL_NODE_COORDINATES' 432 WRITE(*,*)
'UNKNOWN TYPE OF CELL:',type_of_cell
433 WRITE(*,*)
'ACCEPTABLE TYPES ARE:' 435 WRITE(*,*)
'U_MOMENTUM' 436 WRITE(*,*)
'V_MOMENTUM' 437 WRITE(*,*)
'W_MOMENTUM' 514 CHARACTER (LEN=*) :: TYPE_OF_CELL
515 DOUBLE PRECISION:: Xw,Xe,Yn,Ys,Zb,Zt
516 INTEGER :: I,J,K,IP,JP,KP,IM,JM,KM
517 INTEGER :: IJK,IMJK,IJMK,IJKM,IMJMK,IMJKM,IJMKM,IMJMKM
531 imjk = funijk_gl(im,j,k)
532 ijmk = funijk_gl(i,jm,k)
533 ijkm = funijk_gl(i,j,km)
535 imjmk = funijk_gl(im,jm,k)
536 imjkm = funijk_gl(im,j,km)
537 ijmkm = funijk_gl(i,jm,km)
539 imjmkm = funijk_gl(im,jm,km)
550 SELECT CASE (type_of_cell)
608 WRITE(*,*)
'SUBROUTINE: GET_CELL_NODE_COORDINATES' 609 WRITE(*,*)
'UNKNOWN TYPE OF CELL:',type_of_cell
610 WRITE(*,*)
'ACCEPTABLE TYPES ARE:' 612 WRITE(*,*)
'U_MOMENTUM' 613 WRITE(*,*)
'V_MOMENTUM' 614 WRITE(*,*)
'W_MOMENTUM'
integer, dimension(:), allocatable i_of
subroutine eval_stl_fct_at(TYPE_OF_CELL, IJK, NODE, f_stl, CLIP_FLAG, B
double precision, dimension(:), allocatable yg_n
double precision, dimension(:), allocatable xg_e
double precision, dimension(0:15) z_node
subroutine get_connectivity(IJK, TYPE_OF_CELL, N_NEW_POINTS, N_NODES, CONNECT, X_NP, Y_NP, Z_NP, TOTAL_NUMBER_OF_INTERSECTIONS, X_intersect, Y_intersect, Z_intersect)
double precision, dimension(0:15) y_node
integer, dimension(:), allocatable global_j_of
double precision, dimension(0:dim_j) dy
double precision, dimension(0:dim_k) dz
integer, dimension(:), allocatable k_of
subroutine get_global_cell_node_coordinates(IJK, TYPE_OF_CELL)
integer, dimension(:), allocatable global_i_of
subroutine mfix_exit(myID, normal_termination)
integer, dimension(:), allocatable j_of
subroutine get_cell_node_coordinates(IJK, TYPE_OF_CELL)
double precision, dimension(0:dim_i) dx
logical, dimension(:), allocatable intersect_z
double precision, parameter half
logical, dimension(:), allocatable intersect_x
integer, dimension(:), allocatable global_k_of
logical, dimension(:), allocatable intersect_y
subroutine eval_f(METHOD, x1, x2, x3, Q, f, CLIP_FLAG)
double precision, dimension(:), allocatable zg_t
double precision, dimension(0:15) f_node
integer, dimension(0:15) ijk_of_node
double precision, parameter zero
double precision, dimension(0:15) x_node
logical, dimension(:), allocatable snap