MFIX  2016-1
get_connectivity.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Module name: GET_CONNECTIVITY C
4 ! Purpose: Set flags for saclar cut cells, based on intersection C
5 ! of the grid with the quadric(s) C
6 ! C
7 ! Author: Jeff Dietiker Date: 21-Feb-08 C
8 ! Reviewer: Date: C
9 ! C
10 ! Revision Number # Date: ##-###-## C
11 ! Author: # C
12 ! Purpose: # C
13 ! C
14 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
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)
17 
18  USE compar, ONLY: ijkend3
19  USE cutcell
20  USE cut_cell_preproc, ONLY: eval_f
21  USE functions, ONLY: funijk
22  USE geometry, ONLY: do_k, no_k
23  USE indices, ONLY: i_of, j_of, k_of
24  USE polygon, ONLY: n_polygon
25  USE quadric, ONLY: tol_f
26  USE param, ONLY: dimension_3
27 
28  IMPLICIT NONE
29  INTEGER :: I,J,K,IM,JM,KM
30  INTEGER :: IJK,IMJK,IJMK,IJKM,IMJMK,IMJKM,IJMKM,IMJMKM
31  LOGICAL :: CLIP_FLAG
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
41 
42 !======================================================================
43 ! Get coordinates of eight nodes
44 !======================================================================
45 
46  CALL get_cell_node_coordinates(ijk,type_of_cell)
47 
48  i = i_of(ijk)
49  j = j_of(ijk)
50  k = k_of(ijk)
51 
52  im = i - 1
53  jm = j - 1
54  km = k - 1
55 
56  imjk = funijk(im,j,k)
57  ijmk = funijk(i,jm,k)
58  ijkm = funijk(i,j,km)
59 
60  imjmk = funijk(im,jm,k)
61  imjkm = funijk(im,j,km)
62  ijmkm = funijk(i,jm,km)
63 
64  imjmkm = funijk(im,jm,km)
65 
66 
67 !======================================================================
68 ! Evaluate Quadric at all corners
69 !======================================================================
70 
71  n_nodes = 0
72 
73  corner_intersection = .false.
74  number_of_corner_intersections = 0
75  number_of_edge_intersections = 0
76 
77  IF(no_k) THEN
78  n_n1 = 5
79  n_n2 = 8
80  ELSE
81  n_n1 = 1
82  n_n2 = 8
83  ENDIF
84 
85  DO node = n_n1,n_n2
86 
87  q_id = 1
88  CALL eval_f('QUADRIC',x_node(node),y_node(node),z_node(node),q_id,f_node(node),clip_flag)
89 
90  CALL eval_f('POLYGON',x_node(node),y_node(node),z_node(node),n_polygon,f_node(node),clip_flag)
91 
92  CALL eval_f('USR_DEF',x_node(node),y_node(node),z_node(node),n_usr_def,f_node(node),clip_flag)
93 
94  CALL eval_stl_fct_at(type_of_cell,ijk,node,f_node(node),clip_flag,bcid)
95 
96  IF (abs(f_node(node)) < tol_f ) THEN
97  corner_intersection(node) = .true.
98  number_of_corner_intersections = number_of_corner_intersections + 1
99  n_nodes = n_nodes + 1
100  connect(ijk,n_nodes) = ijk_of_node(node)
101  ENDIF
102 
103 
104  IF(snap(ijk_of_node(node))) THEN
105  corner_intersection(node) = .true.
106  number_of_corner_intersections = number_of_corner_intersections + 1
107  n_nodes = n_nodes + 1
108  connect(ijk,n_nodes) = ijk_of_node(node)
109  ENDIF
110 
111  END DO
112 
113 !======================================================================
114 ! Count the number of edge intersections (excluding corner intersections)
115 ! For each new edge intersection found:
116 ! - Increment the total number of points
117 ! - Store the location of the additional point
118 !======================================================================
119 
120  IF(do_k) THEN
121 
122  IF(intersect_x(ijmkm)) THEN ! Edge 1 = Nodes 1-2
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
131  ENDIF
132  ENDIF
133 
134  IF(intersect_y(ijkm)) THEN ! Edge 2 = Nodes 2-4
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
143  ENDIF
144  ENDIF
145 
146  IF(intersect_x(ijkm)) THEN ! Edge 3 = Nodes 3-4
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
155  ENDIF
156  ENDIF
157 
158  IF(intersect_y(imjkm)) THEN ! Edge 4 = Nodes 1-3
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
167  ENDIF
168  ENDIF
169 
170  ENDIF
171 
172 
173  IF(intersect_x(ijmk)) THEN ! Edge 5 = Nodes 5-6
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
182  ENDIF
183  ENDIF
184 
185  IF(intersect_y(ijk)) THEN ! Edge 6 = Nodes 6-8
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
194  ENDIF
195  ENDIF
196 
197  IF(intersect_x(ijk)) THEN ! Edge 7 = Nodes 7-8
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
206  ENDIF
207  ENDIF
208 
209  IF(intersect_y(imjk)) THEN ! Edge 8 = Nodes 5-7
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
218  ENDIF
219  ENDIF
220 
221 
222  IF(do_k) THEN
223 
224  IF(intersect_z(imjmk)) THEN ! Edge 9 = Nodes 1-5
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
233  ENDIF
234  ENDIF
235 
236  IF(intersect_z(ijmk)) THEN ! Edge 10 = Nodes 2-6
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
245  ENDIF
246  ENDIF
247 
248  IF(intersect_z(ijk)) THEN ! Edge 11 = Nodes 4-8
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
257  ENDIF
258  ENDIF
259 
260  IF(intersect_z(imjk)) THEN ! Edge 12 = Nodes 3-7
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
269  ENDIF
270  ENDIF
271 
272  ENDIF
273 
274 !======================================================================
275 ! Count the total number of intersections (corner and edge intersections)
276 !======================================================================
277 
278  IF(no_k) THEN
279  max_corner_intersections = 2
280  ELSE
281  max_corner_intersections = 4
282  ENDIF
283 
284 
285  IF(number_of_corner_intersections > max_corner_intersections) THEN
286  IF(print_warnings) 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)'
290 ! WRITE(*,*)'RESETTING NUMBER_OF_CORNER_INTERSECTIONS TO', MAX_CORNER_INTERSECTIONS
291  WRITE(*,*)'REMOVING CUT CELL'
292  ENDIF
293 ! NUMBER_OF_CORNER_INTERSECTIONS = MAX_CORNER_INTERSECTIONS
294 
295  ! Force the total number of intersections to be zero, and therefore, the cell will be considered as a non-cut cell
296 ! NUMBER_OF_CORNER_INTERSECTIONS = -NUMBER_OF_EDGE_INTERSECTIONS
297 
298  ! Force the total number of intersections to be -one, and therefore, the cell will be considered as a non-cut cell
299  number_of_corner_intersections = -number_of_edge_intersections -1
300 
301 
302  ENDIF
303 
304  total_number_of_intersections = number_of_edge_intersections + number_of_corner_intersections
305 
306  RETURN
307 
308  END SUBROUTINE get_connectivity
309 
310 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
311 ! C
312 ! Module name: GET_CELL_NODE_COORDINATES C
313 ! Purpose: Get the cell corners (x,y,z) coordinates C
314 ! C
315 ! Author: Jeff Dietiker Date: 21-Feb-08 C
316 ! Reviewer: Date: C
317 ! C
318 ! Revision Number # Date: ##-###-## C
319 ! Author: # C
320 ! Purpose: # C
321 ! C
322 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
323  SUBROUTINE get_cell_node_coordinates(IJK,TYPE_OF_CELL)
325  USE compar, ONLY: mype
326  USE cutcell
327  USE exit, only: mfix_exit
328  USE functions, ONLY: funijk
329  USE geometry, ONLY: no_k, dx, dy, dz
330  USE indices, ONLY: i_of, j_of, k_of
331  USE param1, ONLY: half, zero
332 
333  IMPLICIT NONE
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
338 
339  i = i_of(ijk)
340  j = j_of(ijk)
341  k = k_of(ijk)
342 
343  ip = i + 1
344  jp = j + 1
345  kp = k + 1
346 
347  im = i - 1
348  jm = j - 1
349  km = k - 1
350 
351  imjk = funijk(im,j,k)
352  ijmk = funijk(i,jm,k)
353  ijkm = funijk(i,j,km)
354 
355  imjmk = funijk(im,jm,k)
356  imjkm = funijk(im,j,km)
357  ijmkm = funijk(i,jm,km)
358 
359  imjmkm = funijk(im,jm,km)
360 
361  ijk_of_node(0) = ijk
362  ijk_of_node(1) = imjmkm
363  ijk_of_node(2) = ijmkm
364  ijk_of_node(3) = imjkm
365  ijk_of_node(4) = ijkm
366  ijk_of_node(5) = imjmk
367  ijk_of_node(6) = ijmk
368  ijk_of_node(7) = imjk
369  ijk_of_node(8) = ijk
370  ijk_of_node(15) = ijk
371 
372 
373  SELECT CASE (type_of_cell)
374  CASE('SCALAR')
375  xw = xg_e(i) - dx(i) ! west face location
376  xe = xg_e(i) ! east face location
377 
378  ys = yg_n(j) - dy(j) ! south face location
379  yn = yg_n(j) ! north face location
380 
381  IF(no_k) THEN
382  zb = zero ! bottom face location
383  zt = zero ! top face location
384  ELSE
385  zb = zg_t(k) - dz(k) ! bottom face location
386  zt = zg_t(k) ! top face location
387  ENDIF
388 
389  CASE('U_MOMENTUM')
390  xw = xg_e(i) - half * dx(i) ! west face location
391  xe = xg_e(i) + half * dx(ip) ! east face location
392 
393  ys = yg_n(j) - dy(j) ! south face location
394  yn = yg_n(j) ! north face location
395 
396  IF(no_k) THEN
397  zb = zero ! bottom face location
398  zt = zero ! top face location
399  ELSE
400  zb = zg_t(k) - dz(k) ! bottom face location
401  zt = zg_t(k) ! top face location
402  ENDIF
403 
404  CASE('V_MOMENTUM')
405  xw = xg_e(i) - dx(i) ! west face location
406  xe = xg_e(i) ! east face location
407 
408  ys = yg_n(j) - half * dy(j) ! south face location
409  yn = yg_n(j) + half * dy(jp) ! north face location
410 
411  IF(no_k) THEN
412  zb = zero ! bottom face location
413  zt = zero ! top face location
414  ELSE
415  zb = zg_t(k) - dz(k) ! bottom face location
416  zt = zg_t(k) ! top face location
417  ENDIF
418 
419  CASE('W_MOMENTUM')
420  xw = xg_e(i) - dx(i) ! west face location
421  xe = xg_e(i) ! east face location
422 
423  ys = yg_n(j) - dy(j) ! south face location
424  yn = yg_n(j) ! north face location
425 
426  zb = zg_t(k) - half * dz(k) ! bottom face location
427  zt = zg_t(k) + half * dz(kp) ! top face location
428 
429 
430  CASE DEFAULT
431  WRITE(*,*)'SUBROUTINE: GET_CELL_NODE_COORDINATES'
432  WRITE(*,*)'UNKNOWN TYPE OF CELL:',type_of_cell
433  WRITE(*,*)'ACCEPTABLE TYPES ARE:'
434  WRITE(*,*)'SCALAR'
435  WRITE(*,*)'U_MOMENTUM'
436  WRITE(*,*)'V_MOMENTUM'
437  WRITE(*,*)'W_MOMENTUM'
438  CALL mfix_exit(mype)
439  END SELECT
440 
441 ! CELL CENTER :
442  x_node(0) = half * ( xw + xe )
443  y_node(0) = half * ( ys + yn )
444  z_node(0) = half * ( zb + zt )
445 
446 ! NODE 1 : IM,JM,KM
447  x_node(1) = xw
448  y_node(1) = ys
449  z_node(1) = zb
450 
451 ! NODE 2 : I,JM,KM
452  x_node(2) = xe
453  y_node(2) = ys
454  z_node(2) = zb
455 
456 ! NODE 3 : IM,J,KM
457  x_node(3) = xw
458  y_node(3) = yn
459  z_node(3) = zb
460 
461 ! NODE 4 : I,J,KM
462  x_node(4) = xe
463  y_node(4) = yn
464  z_node(4) = zb
465 
466 ! NODE 5 : IM,JM,K
467  x_node(5) = xw
468  y_node(5) = ys
469  z_node(5) = zt
470 
471 ! NODE 6 : I,JM,K
472  x_node(6) = xe
473  y_node(6) = ys
474  z_node(6) = zt
475 
476 ! NODE 7 : IM,J,K
477  x_node(7) = xw
478  y_node(7) = yn
479  z_node(7) = zt
480 
481 ! NODE 8 : I,J,K
482  x_node(8) = xe
483  y_node(8) = yn
484  z_node(8) = zt
485 
486  RETURN
487 
488  END SUBROUTINE get_cell_node_coordinates
489 
490 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
491 ! C
492 ! Module name: GET_GLOBAL_CELL_NODE_COORDINATES C
493 ! Purpose: Get the cell corners (x,y,z) coordinates C
494 ! C
495 ! Author: Jeff Dietiker Date: 21-Feb-08 C
496 ! Reviewer: Date: C
497 ! C
498 ! Revision Number # Date: ##-###-## C
499 ! Author: # C
500 ! Purpose: # C
501 ! C
502 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
503  SUBROUTINE get_global_cell_node_coordinates(IJK,TYPE_OF_CELL)
505  USE compar, ONLY: mype
506  USE cutcell
507  USE exit, only: mfix_exit
508  USE functions, ONLY: funijk_gl
509  USE geometry, ONLY: no_k, dx, dy, dz
510  USE param1, only: half, zero
512 
513  IMPLICIT NONE
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
518 
519  i = global_i_of(ijk)
520  j = global_j_of(ijk)
521  k = global_k_of(ijk)
522 
523  ip = i + 1
524  jp = j + 1
525  kp = k + 1
526 
527  im = i - 1
528  jm = j - 1
529  km = k - 1
530 
531  imjk = funijk_gl(im,j,k)
532  ijmk = funijk_gl(i,jm,k)
533  ijkm = funijk_gl(i,j,km)
534 
535  imjmk = funijk_gl(im,jm,k)
536  imjkm = funijk_gl(im,j,km)
537  ijmkm = funijk_gl(i,jm,km)
538 
539  imjmkm = funijk_gl(im,jm,km)
540 
541  ijk_of_node(1) = imjmkm
542  ijk_of_node(2) = ijmkm
543  ijk_of_node(3) = imjkm
544  ijk_of_node(4) = ijkm
545  ijk_of_node(5) = imjmk
546  ijk_of_node(6) = ijmk
547  ijk_of_node(7) = imjk
548  ijk_of_node(8) = ijk
549 
550  SELECT CASE (type_of_cell)
551  CASE('SCALAR')
552  xw = xg_e(i) - dx(i) ! west face location
553  xe = xg_e(i) ! east face location
554 
555  ys = yg_n(j) - dy(j) ! south face location
556  yn = yg_n(j) ! north face location
557 
558  IF(no_k) THEN
559  zb = zero ! bottom face location
560  zt = zero ! top face location
561  ELSE
562  zb = zg_t(k) - dz(k) ! bottom face location
563  zt = zg_t(k) ! top face location
564  ENDIF
565 
566  CASE('U_MOMENTUM')
567  xw = xg_e(i) - half * dx(i) ! west face location
568  xe = xg_e(i) + half * dx(ip) ! east face location
569 
570  ys = yg_n(j) - dy(j) ! south face location
571  yn = yg_n(j) ! north face location
572 
573  IF(no_k) THEN
574  zb = zero ! bottom face location
575  zt = zero ! top face location
576  ELSE
577  zb = zg_t(k) - dz(k) ! bottom face location
578  zt = zg_t(k) ! top face location
579  ENDIF
580 
581  CASE('V_MOMENTUM')
582  xw = xg_e(i) - dx(i) ! west face location
583  xe = xg_e(i) ! east face location
584 
585  ys = yg_n(j) - half * dy(j) ! south face location
586  yn = yg_n(j) + half * dy(jp) ! north face location
587 
588  IF(no_k) THEN
589  zb = zero ! bottom face location
590  zt = zero ! top face location
591  ELSE
592  zb = zg_t(k) - dz(k) ! bottom face location
593  zt = zg_t(k) ! top face location
594  ENDIF
595 
596  CASE('W_MOMENTUM')
597  xw = xg_e(i) - dx(i) ! west face location
598  xe = xg_e(i) ! east face location
599 
600  ys = yg_n(j) - dy(j) ! south face location
601  yn = yg_n(j) ! north face location
602 
603  zb = zg_t(k) - half * dz(k) ! bottom face location
604  zt = zg_t(k) + half * dz(kp) ! top face location
605 
606 
607  CASE DEFAULT
608  WRITE(*,*)'SUBROUTINE: GET_CELL_NODE_COORDINATES'
609  WRITE(*,*)'UNKNOWN TYPE OF CELL:',type_of_cell
610  WRITE(*,*)'ACCEPTABLE TYPES ARE:'
611  WRITE(*,*)'SCALAR'
612  WRITE(*,*)'U_MOMENTUM'
613  WRITE(*,*)'V_MOMENTUM'
614  WRITE(*,*)'W_MOMENTUM'
615  CALL mfix_exit(mype)
616  END SELECT
617 
618 ! CELL CENTER :
619  x_node(0) = half * ( xw + xe )
620  y_node(0) = half * ( ys + yn )
621  z_node(0) = half * ( zb + zt )
622 
623 ! NODE 1 : IM,JM,KM
624  x_node(1) = xw
625  y_node(1) = ys
626  z_node(1) = zb
627 
628 ! NODE 2 : I,JM,KM
629  x_node(2) = xe
630  y_node(2) = ys
631  z_node(2) = zb
632 
633 ! NODE 3 : IM,J,KM
634  x_node(3) = xw
635  y_node(3) = yn
636  z_node(3) = zb
637 
638 ! NODE 4 : I,J,KM
639  x_node(4) = xe
640  y_node(4) = yn
641  z_node(4) = zb
642 
643 ! NODE 5 : IM,JM,K
644  x_node(5) = xw
645  y_node(5) = ys
646  z_node(5) = zt
647 
648 ! NODE 6 : I,JM,K
649  x_node(6) = xe
650  y_node(6) = ys
651  z_node(6) = zt
652 
653 ! NODE 7 : IM,J,K
654  x_node(7) = xw
655  y_node(7) = yn
656  z_node(7) = zt
657 
658 ! NODE 8 : I,J,K
659  x_node(8) = xe
660  y_node(8) = yn
661  z_node(8) = zt
662 
663  RETURN
664 
665  END SUBROUTINE get_global_cell_node_coordinates
integer, dimension(:), allocatable i_of
Definition: indices_mod.f:45
integer ijkend3
Definition: compar_mod.f:80
subroutine eval_stl_fct_at(TYPE_OF_CELL, IJK, NODE, f_stl, CLIP_FLAG, B
double precision, dimension(:), allocatable yg_n
Definition: cutcell_mod.f:45
integer dimension_3
Definition: param_mod.f:11
double precision, dimension(:), allocatable xg_e
Definition: cutcell_mod.f:44
double precision, dimension(0:15) z_node
Definition: cutcell_mod.f:76
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
Definition: cutcell_mod.f:75
logical print_warnings
Definition: cutcell_mod.f:416
integer, dimension(:), allocatable global_j_of
Definition: vtk_mod.f:47
double precision, dimension(0:dim_j) dy
Definition: geometry_mod.f:70
Definition: vtk_mod.f:1
double precision, dimension(0:dim_k) dz
Definition: geometry_mod.f:72
integer, dimension(:), allocatable k_of
Definition: indices_mod.f:47
subroutine get_global_cell_node_coordinates(IJK, TYPE_OF_CELL)
integer, dimension(:), allocatable global_i_of
Definition: vtk_mod.f:46
subroutine mfix_exit(myID, normal_termination)
Definition: exit.f:5
integer, dimension(:), allocatable j_of
Definition: indices_mod.f:46
Definition: exit.f:2
subroutine get_cell_node_coordinates(IJK, TYPE_OF_CELL)
double precision tol_f
Definition: quadric_mod.f:76
double precision, dimension(0:dim_i) dx
Definition: geometry_mod.f:68
integer n_usr_def
Definition: cutcell_mod.f:424
logical, dimension(:), allocatable intersect_z
Definition: cutcell_mod.f:66
double precision, parameter half
Definition: param1_mod.f:28
Definition: param_mod.f:2
logical no_k
Definition: geometry_mod.f:28
logical do_k
Definition: geometry_mod.f:30
integer mype
Definition: compar_mod.f:24
integer n_polygon
Definition: polygon_mod.f:6
logical, dimension(:), allocatable intersect_x
Definition: cutcell_mod.f:64
integer, dimension(:), allocatable global_k_of
Definition: vtk_mod.f:48
logical, dimension(:), allocatable intersect_y
Definition: cutcell_mod.f:65
subroutine eval_f(METHOD, x1, x2, x3, Q, f, CLIP_FLAG)
double precision, dimension(:), allocatable zg_t
Definition: cutcell_mod.f:46
double precision, dimension(0:15) f_node
Definition: cutcell_mod.f:77
integer, dimension(0:15) ijk_of_node
Definition: cutcell_mod.f:78
double precision, parameter zero
Definition: param1_mod.f:27
double precision, dimension(0:15) x_node
Definition: cutcell_mod.f:74
logical, dimension(:), allocatable snap
Definition: cutcell_mod.f:413