OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
alefvm_epsdot.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!|| alefvm_epsdot ../engine/source/ale/alefvm/alefvm_epsdot.F
25!||--- called by ------------------------------------------------------
26!|| sforc3 ../engine/source/elements/solid/solide/sforc3.F
27!||--- uses -----------------------------------------------------
28!|| alefvm_mod ../common_source/modules/ale/alefvm_mod.F
29!||====================================================================
30 SUBROUTINE alefvm_epsdot (
31 1 IXS, VOL,
32 2 N1X, N2X, N3X, N4X, N5X, N6X,
33 3 N1Y, N2Y, N3Y, N4Y, N5Y, N6Y,
34 4 N1Z, N2Z, N3Z, N4Z, N5Z, N6Z,
35 5 DXX, DYY, DZZ, X , IPM, NEL)
36C-----------------------------------------------
37C D e s c r i p t i o n
38C-----------------------------------------------
39C 'alefvm' is related to a collocated scheme (based on Godunov scheme)
40C which was temporarily introduced for experimental option /INTER/TYPE22 (FSI coupling with cut cell method)
41C This cut cell method is not completed, abandoned, and is not an official option.
42C There is no other use for this scheme which is automatically enabled when /INTER/TYPE22 is defined (INT22>0 => IALEFVM=1).
43C
44C This subroutine is treating an uncut cell.
45C-----------------------------------------------
46C M o d u l e s
47C-----------------------------------------------
48 USE alefvm_mod
49C-----------------------------------------------
50C I m p l i c i t T y p e s
51C-----------------------------------------------
52#include "implicit_f.inc"
53C-----------------------------------------------
54C G l o b a l P a r a m e t e r s
55C-----------------------------------------------
56#include "mvsiz_p.inc"
57C-----------------------------------------------
58C C o m m o n B l o c k s
59C-----------------------------------------------
60#include "vect01_c.inc"
61#include "com01_c.inc"
62#include "param_c.inc"
63C-----------------------------------------------
64C D e s c r i p t i o n
65C-----------------------------------------------
66C This subroutines computes strain rate tensor
67C
68C If option is not detected in input file then
69C subroutine is unplugged
70C-----------------------------------------------
71C D u m m y A r g u m e n t s
72C-----------------------------------------------
73 INTEGER :: IXS(NIXS,*),NV46,IPM(NPROPMI,*),NEL
74 my_real :: VOL(MVSIZ),DXX(MVSIZ),DYY(MVSIZ), DZZ(MVSIZ),X(3,*)
75 my_real :: N1X(*), N2X(*), N3X(*), N4X(*), N5X(*), N6X(*),
76 . N1Y(*), N2Y(*), N3Y(*), N4Y(*), N5Y(*), N6Y(*),
77 . N1Z(*), N2Z(*), N3Z(*), N4Z(*), N5Z(*), N6Z(*)
78C-----------------------------------------------
79C L o c a l V a r i a b l e s
80C-----------------------------------------------
81 INTEGER :: I, II, MT, IALEFVM_FLG
82 my_real :: Vface(3,6), GradV(3,3), EPSDOT(6)
83 INTEGER :: NC1(MVSIZ),NC2(MVSIZ),NC3(MVSIZ),NC4(MVSIZ),NC5(MVSIZ),NC6(MVSIZ),NC7(MVSIZ),NC8(MVSIZ)
84 my_real :: X1(MVSIZ), X2(MVSIZ), X3(MVSIZ), X4(MVSIZ), X5(MVSIZ), X6(MVSIZ), X7(MVSIZ), X8(MVSIZ),
85 . Y1(MVSIZ), Y2(MVSIZ), Y3(MVSIZ), Y4(MVSIZ), Y5(MVSIZ), Y6(MVSIZ), Y7(MVSIZ), Y8(MVSIZ),
86 . z1(mvsiz), z2(mvsiz), z3(mvsiz), z4(mvsiz), z5(mvsiz), z6(mvsiz), z7(mvsiz), z8(mvsiz)
87
88 LOGICAL :: debug_outp
89 INTEGER :: idbf,idbl
90C-----------------------------------------------
91C P r e - C o n d i t i o n s
92C-----------------------------------------------
93 IF(alefvm_param%IEnabled==0)RETURN
94 mt = ixs(1,nft+1)
95 ialefvm_flg = ipm(251,mt)
96 IF(ialefvm_flg <= 1)RETURN
97 epsdot(1:6) = zero
98C-----------------------------------------------
99C S o u r c e L i n e s
100C-----------------------------------------------
101
102 !-------------------------------------------------------------!
103 ! NORMAL VECTOR FOR ALE !
104 !-------------------------------------------------------------!
105 IF(jale==1)THEN
106 DO i=1,nel
107 ii = i + nft
108 !---8 local node numbers NC1 TO NC8 for solid element I ---!
109 nc1(i)=ixs(2,ii)
110 nc2(i)=ixs(3,ii)
111 nc3(i)=ixs(4,ii)
112 nc4(i)=ixs(5,ii)
113 nc5(i)=ixs(6,ii)
114 nc6(i)=ixs(7,ii)
115 nc7(i)=ixs(8,ii)
116 nc8(i)=ixs(9,ii)
117 !
118 !---Coordinates of the 8 nodes
119 x1(i)=x(1,nc1(i))
120 y1(i)=x(2,nc1(i))
121 z1(i)=x(3,nc1(i))
122 !
123 x2(i)=x(1,nc2(i))
124 y2(i)=x(2,nc2(i))
125 z2(i)=x(3,nc2(i))
126 !
127 x3(i)=x(1,nc3(i))
128 y3(i)=x(2,nc3(i))
129 z3(i)=x(3,nc3(i))
130 !
131 x4(i)=x(1,nc4(i))
132 y4(i)=x(2,nc4(i))
133 z4(i)=x(3,nc4(i))
134 !
135 x5(i)=x(1,nc5(i))
136 y5(i)=x(2,nc5(i))
137 z5(i)=x(3,nc5(i))
138 !
139 x6(i)=x(1,nc6(i))
140 y6(i)=x(2,nc6(i))
141 z6(i)=x(3,nc6(i))
142 !
143 x7(i)=x(1,nc7(i))
144 y7(i)=x(2,nc7(i))
145 z7(i)=x(3,nc7(i))
146 !
147 x8(i)=x(1,nc8(i))
148 y8(i)=x(2,nc8(i))
149 z8(i)=x(3,nc8(i))
150 ENDDO
151 DO i=1,nel
152 ! Face-1
153 n1x(i)=(y3(i)-y1(i))*(z2(i)-z4(i)) - (z3(i)-z1(i))*(y2(i)-y4(i))
154 n1y(i)=(z3(i)-z1(i))*(x2(i)-x4(i)) - (x3(i)-x1(i))*(z2(i)-z4(i))
155 n1z(i)=(x3(i)-x1(i))*(y2(i)-y4(i)) - (y3(i)-y1(i))*(x2(i)-x4(i))
156 ! Face-2
157 n2x(i)=(y7(i)-y4(i))*(z3(i)-z8(i)) - (z7(i)-z4(i))*(y3(i)-y8(i))
158 n2y(i)=(z7(i)-z4(i))*(x3(i)-x8(i)) - (x7(i)-x4(i))*(z3(i)-z8(i))
159 n2z(i)=(x7(i)-x4(i))*(y3(i)-y8(i)) - (y7(i)-y4(i))*(x3(i)-x8(i))
160 ! Face-3
161 n3x(i)=(y6(i)-y8(i))*(z7(i)-z5(i)) - (z6(i)-z8(i))*(y7(i)-y5(i))
162 n3y(i)=(z6(i)-z8(i))*(x7(i)-x5(i)) - (x6(i)-x8(i))*(z7(i)-z5(i))
163 n3z(i)=(x6(i)-x8(i))*(y7(i)-y5(i)) - (y6(i)-y8(i))*(x7(i)-x5(i))
164 ! Face-4
165 n4x(i)=(y2(i)-y5(i))*(z6(i)-z1(i)) - (z2(i)-z5(i))*(y6(i)-y1(i))
166 n4y(i)=(z2(i)-z5(i))*(x6(i)-x1(i)) - (x2(i)-x5(i))*(z6(i)-z1(i))
167 n4z(i)=(x2(i)-x5(i))*(y6(i)-y1(i)) - (y2(i)-y5(i))*(x6(i)-x1(i))
168 ! Face-5
169 n5x(i)=(y7(i)-y2(i))*(z6(i)-z3(i)) - (z7(i)-z2(i))*(y6(i)-y3(i))
170 n5y(i)=(z7(i)-z2(i))*(x6(i)-x3(i)) - (x7(i)-x2(i))*(z6(i)-z3(i))
171 n5z(i)=(x7(i)-x2(i))*(y6(i)-y3(i)) - (y7(i)-y2(i))*(x6(i)-x3(i))
172 ! Face-6
173 n6x(i)=(y8(i)-y1(i))*(z4(i)-z5(i)) - (z8(i)-z1(i))*(y4(i)-y5(i))
174 n6y(i)=(z8(i)-z1(i))*(x4(i)-x5(i)) - (x8(i)-x1(i))*(z4(i)-z5(i))
175 n6z(i)=(x8(i)-x1(i))*(y4(i)-y5(i)) - (y8(i)-y1(i))*(x4(i)-x5(i))
176 ENDDO
177 ENDIF
178
179 !-------------------------------------------------------------!
180 ! TOTAL TENSOR !
181 !-------------------------------------------------------------!
182 DO i=1,nel
183 ii = i + nft
184 vface(1:3,1) = alefvm_buffer%F_FACE(1:3,1,ii)
185 vface(1:3,2) = alefvm_buffer%F_FACE(1:3,2,ii)
186 vface(1:3,3) = alefvm_buffer%F_FACE(1:3,3,ii)
187 vface(1:3,4) = alefvm_buffer%F_FACE(1:3,4,ii)
188 vface(1:3,5) = alefvm_buffer%F_FACE(1:3,5,ii)
189 vface(1:3,6) = alefvm_buffer%F_FACE(1:3,6,ii)
190 ENDDO
191
192 !-------------------------------------------------------------!
193 ! VELOCITY GRADIENT : Grad(v(1:3)) \in Matrix(3,3) !
194 !-------------------------------------------------------------!
195 ![EPSDOT]=1/2 (grad V + t{gradV} ) -> EPSDOT_if = 1/2 (dvi/dxj + dvj/dxi )
196 ! mean (grad V) = 1/V * Integral (grad V, dV) = 1/V * Integral (V (*) n , dS) where (*) is tensorial product
197 ! = 1/V * SUM( Vf (*) nf . Sf )
198 ! = 1/2/V * SUM ( Vf (*) Nf ) where Nf=2Sf.n
199
200 ! WARNING : Tangentiel velocity is here missing since F_FACE is godunov normal velocity
201
202 DO i=1,nel
203 ii=i+nft
204 gradv(1,1) = half/vol(i) * ( vface(1,1)*n1x(i) + vface(1,2)*n2x(i) + vface(1,3)*n3x(i)
205 . + vface(1,4)*n4x(i) + vface(1,5)*n5x(i) + vface(1,6)*n6x(i) )
206 gradv(1,2) = half/vol(i) * ( vface(1,1)*n1y(i) + vface(1,2)*n2y(i) + vface(1,3)*n3y(i)
207 . + vface(1,4)*n4y(i) + vface(1,5)*n5y(i) + vface(1,6)*n6y(i) )
208 gradv(1,3) = half/vol(i) * ( vface(1,1)*n1z(i) + vface(1,2)*n2z(i) + vface(1,3)*n3z(i)
209 . + vface(1,4)*n4z(i) + vface(1,5)*n5z(i) + vface(1,6)*n6z(i) )
210
211 gradv(2,1) = half/vol(i) * ( vface(2,1)*n1x(i) + vface(2,2)*n2x(i) + vface(2,3)*n3x(i)
212 . + vface(2,4)*n4x(i) + vface(2,5)*n5x(i) + vface(2,6)*n6x(i) )
213 gradv(2,2) = half/vol(i) * ( vface(2,1)*n1y(i) + vface(2,2)*n2y(i) + vface(2,3)*n3y(i)
214 . + vface(2,4)*n4y(i) + vface(2,5)*n5y(i) + vface(2,6)*n6y(i) )
215 gradv(2,3) = half/vol(i) * ( vface(2,1)*n1z(i) + vface(2,2)*n2z(i) + vface(2,3)*n3z(i)
216 . + vface(2,4)*n4z(i) + vface(2,5)*n5z(i) + vface(2,6)*n6z(i) )
217
218 gradv(3,1) = half/vol(i) * ( vface(3,1)*n1x(i) + vface(3,2)*n2x(i) + vface(3,3)*n3x(i)
219 . + vface(3,4)*n4x(i) + vface(3,5)*n5x(i) + vface(3,6)*n6x(i) )
220 gradv(3,2) = half/vol(i) * ( vface(3,1)*n1y(i) + vface(3,2)*n2y(i) + vface(3,3)*n3y(i)
221 . + vface(3,4)*n4y(i) + vface(3,5)*n5y(i) + vface(3,6)*n6y(i) )
222 gradv(3,3) = half/vol(i) * ( vface(3,1)*n1z(i) + vface(3,2)*n2z(i) + vface(3,3)*n3z(i)
223 . + vface(3,4)*n4z(i) + vface(3,5)*n5z(i) + vface(3,6)*n6z(i) )
224
225 epsdot(1) = gradv(1,1)
226 epsdot(2) = gradv(2,2)
227 epsdot(3) = gradv(3,3)
228 epsdot(4) = half*(gradv(1,2)+gradv(2,1))
229 epsdot(5) = half*(gradv(2,3)+gradv(3,2))
230 epsdot(6) = half*(gradv(1,3)+gradv(3,1))
231
232 dxx(i) = epsdot(1)
233 dyy(i) = epsdot(2)
234 dzz(i) = epsdot(3)
235
236 !14.0.220 : strain rate not yet validated. Set to zero while waiting for specification validation
237 dxx(i) = zero
238 dyy(i) = zero
239 dzz(i) = zero
240
241 ENDDO
242
243
244 !DEBUG-OUTPUT---------------!
245 if(alefvm_param%IOUTP_EPSDOT /= 0)then
246 debug_outp = .false.
247 if(alefvm_param%IOUTP_EPSDOT>0)then
248 do i=lft,llt
249 ii = nft + i
250 if(ixs(11,ii)==alefvm_param%IOUTP_EPSDOT)THEN
251 debug_outp = .true.
252 idbf = i
253 idbl = i
254 EXIT
255 endif
256 enddo
257 elseif(alefvm_param%IOUTP_EPSDOT==-1)then
258 debug_outp=.true.
259 idbf = lft
260 idbl = llt
261 endif
262 if(debug_outp)then
263!#!include "lockon.inc"
264 print *, " |----alefvm_stress.F-----|"
265 print *, " | THREAD INFORMATION |"
266 print *, " |------------------------|"
267 print *, " NCYCLE =", ncycle
268 do i=idbf,idbl
269 ii = nft + i
270 print *, " brique=", ixs(11,nft+i)
271 write(*,fmt='(A24,1A26)') " ",
272 . "#-stress Tensor (P+VIS+Q)#"
273
274!! write (*,FMT='(A,3E26.14,A)') " | ", GradV(1,1),GradV(1,2),GradV(1,3), " |"
275!! write (*,FMT='(A,3E26.14,A)') " GradV =| ", GradV(2,1),GradV(2,2),GradV(2,3), " |"
276!! write (*,FMT='(A,3E26.14,A)') " |_", GradV(3,1),GradV(3,2),GradV(3,3), "_|"
277
278! write (*,FMT='(A,3E26.14,A)') " | ", EPSDOT(1),EPSDOT(4),EPSDOT(6), " |"
279! write (*,fmt='(A,3E26.14,A)') " Eps_dot =| ", epsdot(4),epsdot(2),epsdot(5), " |"
280! write (*,FMT='(A,3E26.14,A)') " |_", EPSDOT(6),EPSDOT(5),EPSDOT(3), "_|"
281 write (*,fmt='(a,1e26.14 )') " tr(Eps_dot)/3. = ", THIRD*(EPSDOT(1)+EPSDOT(2)+EPSDOT(3))
282
283 enddo
284!#!include "lockoff.inc"
285 endif
286 endif
287 !-----------------------------------------!
288
289 RETURN
290 END
subroutine alefvm_epsdot(ixs, vol, n1x, n2x, n3x, n4x, n5x, n6x, n1y, n2y, n3y, n4y, n5y, n6y, n1z, n2z, n3z, n4z, n5z, n6z, dxx, dyy, dzz, x, ipm, nel)
type(alefvm_buffer_), target alefvm_buffer
Definition alefvm_mod.F:120
type(alefvm_param_), target alefvm_param
Definition alefvm_mod.F:121