OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
ale_element_size_computation.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!|| ale_element_size_computation ../starter/source/initial_conditions/inivol/ale_element_size_computation.F
25!||--- called by ------------------------------------------------------
26!|| init_inivol ../starter/source/initial_conditions/inivol/init_inivol.F90
27!||====================================================================
28 SUBROUTINE ale_element_size_computation(NPARG, NGROUP, NUMELS,NUMELTG,NUMELQ,NUMNOD,N2D,
29 . IPARG,IXS,IXQ,IXTG,
30 . ELEMENT_SIZE,MIN_MAX_POSITION,X,
31 . ALE_ELEMENT_NUMBER,ALE_NODE_NUMBER,LIST_ALE_NODE)
32!$COMMENT
33! ALE_ELEMENT_SIZE_COMPUTATION description
34! ALE_ELEMENT_SIZE_COMPUTATION computes the maximum element size
35! and the min / max position of nodes
36! the maximum element size & min / max position are used to defined the grid
37!
38! ALE_ELEMENT_SIZE_COMPUTATION organization :
39! - loop over the element group
40! - for each ale element group, loop over the nel elements
41! - compute the maximum element size
42! - compute the min/max node's positions & save the ALE node id
43!$ENDCOMMENT
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48C-----------------------------------------------
49C G l o b a l P a r a m e t e r s
50C-----------------------------------------------
51#include "mvsiz_p.inc"
52C-----------------------------------------------
53C D u m m y A r g u m e n t s
54C-----------------------------------------------
55 INTEGER,INTENT(IN) :: NPARG, NGROUP, NUMELS,NUMELTG,NUMELQ,NUMNOD,N2D
56 INTEGER, INTENT(INOUT) :: ALE_ELEMENT_NUMBER ! number of ale element with material 51 or 151
57 INTEGER, INTENT(INOUT) :: ALE_NODE_NUMBER ! number of ale node
58 INTEGER, DIMENSION(NUMNOD), INTENT(INOUT) :: LIST_ALE_NODE ! list of ale node
59 INTEGER, DIMENSION(NPARG,NGROUP), INTENT(IN) :: IPARG ! group data
60 INTEGER, DIMENSION(NIXS,NUMELS),INTENT(IN), TARGET :: IXS ! solid data
61 INTEGER, DIMENSION(NIXQ,NUMELQ),INTENT(IN), TARGET :: IXQ ! quad data
62 INTEGER, DIMENSION(NIXTG,NUMELTG),INTENT(IN), TARGET :: IXTG ! triangle data
63 my_real, INTENT(INOUT) :: element_size ! max element size
64 my_real, DIMENSION(6), INTENT(INOUT) :: min_max_position ! min/max position
65 my_real, DIMENSION(3,NUMNOD), INTENT(IN) :: x ! position
66C-----------------------------------------------
67C L o c a l V a r i a b l e s
68C-----------------------------------------------
69 INTEGER :: I,J,K,NG
70 INTEGER :: MTN,NEL,NFT,ITY,ISOLNOD,INIVOL
71 INTEGER :: NODE_NUMBER,FIRST
72 INTEGER, DIMENSION(:,:), POINTER :: IX
73 INTEGER, DIMENSION(:), ALLOCATABLE :: TAG_ARRAY
74 my_real :: local_size
75 my_real, DIMENSION(3) :: max_node,min_node,distance
76 integer, target :: nothing(1,1) !< dummy for indirection
77C-----------------------------------------------
78 ALLOCATE(tag_array(numnod))
79 tag_array(1:numnod) = 0
80 ix => nothing
81 element_size = -one
82 min_max_position(1:3) = ep30
83 min_max_position(4:6) = -ep30
84 ale_element_number = 0
85 ale_node_number = 0
86 ! -----------------------
87 ! loop over the solid / quad / triangle elements with 51/151 material
88 DO ng=1,ngroup
89 mtn = iparg(1,ng) ! material law
90 nel = iparg(2,ng) ! number of element
91 nft = iparg(3,ng) ! adress of first element
92 ity = iparg(5,ng) ! type of element
93 isolnod = iparg(28,ng)
94 inivol = iparg(53,ng)
95 IF(inivol <= 0) cycle
96 IF(mtn /= 51 .AND. mtn /= 151) cycle
97 IF(n2d == 0 .AND. ity /= 1)THEN
98 cycle
99 ELSEIF(n2d > 0 .AND. ity/=7 .AND. ity /= 2)THEN
100 cycle
101 ENDIF
102 ! total number of ale element with material 51 or 151
103 ale_element_number = ale_element_number + nel
104
105 ! ---------------
106 ! depending on the king of element
107 IF(ity == 1) THEN
108 first = 1
109 node_number = 8
110 ix => ixs(1:node_number+1,nft+1:nft+nel)
111 ELSEIF(ity == 2) THEN
112 first = 2
113 node_number = 4
114 ix => ixq(1:node_number+1,nft+1:nft+nel)
115 ELSEIF(ity == 7) THEN
116 first = 2
117 node_number = 3
118 ix => ixtg(1:node_number+1,nft+1:nft+nel)
119 ELSE
120 first = -huge(first)
121 node_number = -huge(node_number)
122 ix => null()
123 ENDIF
124 ! ---------------
125
126 ! ---------------
127 ! loop over the elements of the group to compute
128 ! the max element size and the min/max position
129 DO j=1,nel
130 max_node(1:3) = -ep20
131 min_node(1:3) = ep20
132 ! ---------------
133 ! max element size
134 DO i=1,node_number
135 max_node(first:3) = max(max_node(first:3),x(first:3,ix(1+i,j)) )
136 min_node(first:3) = min(min_node(first:3),x(first:3,ix(1+i,j)) )
137 ENDDO
138 distance(first:3) = (abs(max_node(first:3)-min_node(first:3)))**2
139 local_size = sqrt( sum(distance(first:3)) )
140 element_size = max(element_size,local_size)
141 ! --------------
142 ! ---------------
143 ! min / max position & save the ALE node id
144 DO k=first,3
145 ! min / max position
146 DO i=1,node_number
147 min_max_position(k) = min(min_max_position(k),x(k,ix(1+i,j)))
148 min_max_position(3+k) = max(min_max_position(3+k),x(k,ix(1+i,j)))
149 IF(tag_array(ix(1+i,j))==0) THEN
150 tag_array(ix(1+i,j)) = 1
151 ale_node_number = ale_node_number + 1
152 list_ale_node(ale_node_number) = ix(1+i,j)
153 ENDIF
154 ENDDO
155 ENDDO
156 ! ---------------
157 ENDDO
158 ! ---------------
159 ENDDO
160
161 DEALLOCATE(tag_array)
162 ! -----------------------
163
164 RETURN
165 END SUBROUTINE ale_element_size_computation
subroutine ale_element_size_computation(nparg, ngroup, numels, numeltg, numelq, numnod, n2d, iparg, ixs, ixq, ixtg, element_size, min_max_position, x, ale_element_number, ale_node_number, list_ale_node)
#define my_real
Definition cppsort.cpp:32
end diagonal values have been computed in the(sparse) matrix id.SOL
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
for(i8=*sizetab-1;i8 >=0;i8--)