OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
inter_voxel_creation.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| inter_voxel_creation ../engine/source/interfaces/generic/inter_voxel_creation.F
25!||--- called by ------------------------------------------------------
26!|| inter_prepare_sort ../engine/source/interfaces/generic/inter_prepare_sort.F
27!||--- uses -----------------------------------------------------
28!|| intbufdef_mod ../common_source/modules/interfaces/intbufdef_mod.F90
29!|| inter_sorting_mod ../engine/share/modules/inter_sorting_mod.F
30!||====================================================================
31 SUBROUTINE inter_voxel_creation(IPARI,INTBUF_TAB,X,NIN,SORT_COMM)
32!$COMMENT
33! INTER_VOXEL_CREATION description :
34!
35! INTER_VOXEL_CREATION organization :
36!$ENDCOMMENT
37C-----------------------------------------------
38C M o d u l e s
39C-----------------------------------------------
41 USE intbufdef_mod
42C-----------------------------------------------
43C I m p l i c i t T y p e s
44C-----------------------------------------------
45#include "implicit_f.inc"
46#include "comlock.inc"
47C-----------------------------------------------
48C C o m m o n B l o c k s
49C-----------------------------------------------
50#include "com04_c.inc"
51#include "param_c.inc"
52C-----------------------------------------------
53C D u m m y A r g u m e n t s
54C-----------------------------------------------
55 INTEGER, INTENT(in) :: NIN
56 INTEGER, DIMENSION(NPARI,NINTER), INTENT(in) :: IPARI ! interface data
57 TYPE(intbuf_struct_),DIMENSION(NINTER), INTENT(in) :: INTBUF_TAB ! interface data
58 my_real, DIMENSION(3,NUMNOD), INTENT(in), TARGET :: x ! position
59 TYPE(sorting_comm_type), DIMENSION(NINTER), INTENT(inout) :: SORT_COMM ! structure for interface sorting comm
60C-----------------------------------------------
61C L o c a l V a r i a b l e s
62C-----------------------------------------------
63 INTEGER :: I,J
64 INTEGER :: NSN
65 INTEGER :: FIRST, LAST
66 my_real :: xminb,xmaxb
67 my_real :: yminb,ymaxb
68 my_real :: zminb,zmaxb
69! ----------------------------------------
70
71 xmaxb = box_limit(1)
72 ymaxb = box_limit(2)
73 zmaxb = box_limit(3)
74 xminb = box_limit(4)
75 yminb = box_limit(5)
76 zminb = box_limit(6)
77 ! ------------------
78 ! Create the secondary node voxel :
79 nsn = ipari(5,nin)
80 IF(nsn==0) RETURN
81 ! ------------------
82 ! allocation
83 IF( ALLOCATED( sort_comm(nin)%NEXT_NOD ) ) DEALLOCATE(sort_comm(nin)%NEXT_NOD)
84 IF( ALLOCATED( sort_comm(nin)%LAST_NOD ) ) DEALLOCATE(sort_comm(nin)%LAST_NOD)
85
86 IF( ALLOCATED( sort_comm(nin)%IIX ) ) DEALLOCATE(sort_comm(nin)%IIX)
87 IF( ALLOCATED( sort_comm(nin)%IIY ) ) DEALLOCATE(sort_comm(nin)%IIY)
88 IF( ALLOCATED( sort_comm(nin)%IIZ ) ) DEALLOCATE(sort_comm(nin)%IIZ)
89 IF( ALLOCATED( sort_comm(nin)%VOXEL ) ) DEALLOCATE(sort_comm(nin)%VOXEL)
90
91 ALLOCATE(sort_comm(nin)%NEXT_NOD(nsn))
92 ALLOCATE(sort_comm(nin)%LAST_NOD(nsn))
93 ALLOCATE(sort_comm(nin)%IIX(nsn))
94 ALLOCATE(sort_comm(nin)%IIY(nsn))
95 ALLOCATE(sort_comm(nin)%IIZ(nsn))
96
97 ALLOCATE(sort_comm(nin)%VOXEL(nb_cell_x,nb_cell_y,nb_cell_z) )
98 sort_comm(nin)%VOXEL(1:nb_cell_x,1:nb_cell_y,1:nb_cell_z) = 0
99 ! ------------------
100
101 ! ------------------
102 ! loop over the secondary nodes
103 first = 0
104 last = 0
105 DO i=1,nsn
106 sort_comm(nin)%IIX(i)=0
107 sort_comm(nin)%IIY(i)=0
108 sort_comm(nin)%IIZ(i)=0
109 IF(intbuf_tab(nin)%STFNS(i)==zero)cycle
110 j=intbuf_tab(nin)%NSV(i) ! id of the node (pointer to X position)
111 ! ------------------
112 ! computation of the index iix/y/z
113
114 sort_comm(nin)%IIX(i)=int(nb_cell_x*(x(1,j)-xminb)/(xmaxb-xminb))
115 sort_comm(nin)%IIY(i)=int(nb_cell_y*(x(2,j)-yminb)/(ymaxb-yminb))
116 sort_comm(nin)%IIZ(i)=int(nb_cell_z*(x(3,j)-zminb)/(zmaxb-zminb))
117 sort_comm(nin)%IIX(i)=max(1,min(nb_cell_x,sort_comm(nin)%IIX(i)))
118 sort_comm(nin)%IIY(i)=max(1,min(nb_cell_y,sort_comm(nin)%IIY(i)))
119 sort_comm(nin)%IIZ(i)=max(1,min(nb_cell_z,sort_comm(nin)%IIZ(i)))
120 ! ------------------
121 first = sort_comm(nin)%VOXEL( sort_comm(nin)%IIX(i),
122 . sort_comm(nin)%IIY(i),
123 . sort_comm(nin)%IIZ(i) )
124 ! ------------------
125 IF(first == 0)THEN
126 ! the cell iix/iiy/iiz is empty
127 sort_comm(nin)%VOXEL( sort_comm(nin)%IIX(i),
128 . sort_comm(nin)%IIY(i),
129 . sort_comm(nin)%IIZ(i)) = i ! first node of the cell
130 sort_comm(nin)%NEXT_NOD(i) = 0 ! there is no next node after I node
131 sort_comm(nin)%LAST_NOD(i) = 0 ! there is no last node after I node
132 ELSEIF(sort_comm(nin)%LAST_NOD(first) == 0)THEN
133 ! the cell has only one node, add the I node
134 sort_comm(nin)%NEXT_NOD(first) = i ! I node is the next node
135 sort_comm(nin)%LAST_NOD(first) = i ! I node is the last node
136 sort_comm(nin)%NEXT_NOD(i) = 0 ! there is no last node after I node
137 ELSE
138 ! the cell has several nodes
139 ! need to add the I node to the last position
140 last = sort_comm(nin)%LAST_NOD(first) ! last position of the cell
141 sort_comm(nin)%NEXT_NOD(last) = i ! I node is the next node
142 sort_comm(nin)%LAST_NOD(first) = i ! I node is the last node
143 sort_comm(nin)%NEXT_NOD(i) = 0 ! there is next node after I node
144 ENDIF
145 ! ------------------
146 ENDDO
147 ! ------------------
148
149 RETURN
150 END SUBROUTINE inter_voxel_creation
#define my_real
Definition cppsort.cpp:32
subroutine inter_voxel_creation(ipari, intbuf_tab, x, nin, sort_comm)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21