OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s10fint3.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!|| s10fint3 ../engine/source/elements/solid/solide10/s10fint3.F
25!||--- called by ------------------------------------------------------
26!|| s10forc3 ../engine/source/elements/solid/solide10/s10forc3.F
27!||====================================================================
28 SUBROUTINE s10fint3(
29 1 SIG, PX, PY, PZ,
30 2 FX, FY, FZ, VOL,
31 3 QVIS, STI, STIG, EINT,
32 4 RHO, Q, EPLAS, EPSD,
33 5 EPSDG, SIGG, EINTG, RHOG,
34 6 QG, EPLASG, WIP, G_PLA,
35 7 NEL, CONDE, CONDEG, G_EPSD,
36 8 ISRAT, SVIS , NODADT_THERM)
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C G l o b a l P a r a m e t e r s
43C-----------------------------------------------
44#include "mvsiz_p.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER, INTENT(IN) :: ISRAT
49 INTEGER, INTENT(IN) :: G_PLA,NEL,G_EPSD
50 INTEGER, INTENT(IN) :: NODADT_THERM
51C REAL
52 my_real
53 . PX(MVSIZ,10),PY(MVSIZ,10),PZ(MVSIZ,10),
54 . FX(MVSIZ,10), FY(MVSIZ,10), FZ(MVSIZ,10),
55 . SIG(NEL,6),VOL(*),QVIS(*),EINT(*),RHO(*),Q(*),EPLASG(*),EPLAS(*),
56 . sigg(nel,6),eintg(*),rhog(*),qg(*),wip,sti(*),stig(*),epsd(*),
57 . epsdg(*),conde(*),condeg(*)
58 my_real, DIMENSION(MVSIZ,6), INTENT(INOUT) :: svis
59C-----------------------------------------------
60C C o m m o n B l o c k s
61C-----------------------------------------------
62#include "scr18_c.inc"
63C-----------------------------------------------
64C L o c a l V a r i a b l e s
65C-----------------------------------------------
66 INTEGER I,N
67C REAL
68 my_real
69 . S1(MVSIZ), S2(MVSIZ), S3(MVSIZ),
70 . S4(MVSIZ), S5(MVSIZ), S6(MVSIZ),
71 . FINT, QVIS_LOC, VOL_LOC
72C-----------------------------------------------
73 DO I=1,nel
74 qvis_loc = qvis(i)
75 vol_loc = vol(i)
76 sigg(i,1) = sigg(i,1) + wip * sig(i,1)
77 sigg(i,2) = sigg(i,2) + wip * sig(i,2)
78 sigg(i,3) = sigg(i,3) + wip * sig(i,3)
79 sigg(i,4) = sigg(i,4) + wip * sig(i,4)
80 sigg(i,5) = sigg(i,5) + wip * sig(i,5)
81 sigg(i,6) = sigg(i,6) + wip * sig(i,6)
82 rhog(i) = rhog(i) + wip * rho(i)
83 eintg(i) = eintg(i) + wip * eint(i)
84 qg(i) = qg(i) + wip * q(i)
85 stig(i)=stig(i)+sti(i)
86 s1(i)=(sig(i,1)+svis(i,1)-qvis_loc)*vol_loc
87 s2(i)=(sig(i,2)+svis(i,2)-qvis_loc)*vol_loc
88 s3(i)=(sig(i,3)+svis(i,3)-qvis_loc)*vol_loc
89 s4(i)=(sig(i,4)+svis(i,4))*vol_loc
90 s5(i)=(sig(i,5)+svis(i,5))*vol_loc
91 s6(i)=(sig(i,6)+svis(i,6))*vol_loc
92 ENDDO
93C
94 IF(nodadt_therm == 1) THEN
95 DO i=1,nel
96 condeg(i)= condeg(i)+ conde(i)
97 ENDDO
98 ENDIF
99c
100 IF ((israt > 0).OR.(g_epsd > 0)) THEN
101 DO i=1,nel
102 epsdg(i) = epsdg(i) + wip * epsd(i)
103 ENDDO
104 ENDIF
105 IF (g_pla > 0) THEN
106 DO i=1,nel
107 eplasg(i) = eplasg(i) + wip * eplas(i)
108 ENDDO
109 ENDIF
110C
111 DO n=1,10
112 DO i=1,nel
113 fx(i,n)=fx(i,n)-(s1(i)*px(i,n)+s4(i)*py(i,n)+s6(i)*pz(i,n))
114 fy(i,n)=fy(i,n)-(s2(i)*py(i,n)+s5(i)*pz(i,n)+s4(i)*px(i,n))
115 fz(i,n)=fz(i,n)-(s3(i)*pz(i,n)+s6(i)*px(i,n)+s5(i)*py(i,n))
116 ENDDO
117 ENDDO
118C-----------
119 RETURN
120 END
subroutine s10fint3(sig, px, py, pz, fx, fy, fz, vol, qvis, sti, stig, eint, rho, q, eplas, epsd, epsdg, sigg, eintg, rhog, qg, eplasg, wip, g_pla, nel, conde, condeg, g_epsd, israt, svis, nodadt_therm)
Definition s10fint3.F:37