OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s20fint3.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!|| s20fint3 ../engine/source/elements/solid/solide20/s20fint3.F
25!||--- called by ------------------------------------------------------
26!|| s16forc3 ../engine/source/elements/thickshell/solide16/s16forc3.F
27!|| s20forc3 ../engine/source/elements/solid/solide20/s20forc3.F
28!||====================================================================
29 SUBROUTINE s20fint3(
30 1 NPE, SIG, PX, PY,
31 2 PZ, SSP_EQ, FX, FY,
32 3 FZ, VOL, QVIS, STIG,
33 4 STIN, EINT, RHO, Q,
34 5 EPLAS, EPSD, EPSDG, SIGG,
35 6 EINTG, RHOG, QG, EPLASG,
36 7 WI, VOLG, VOL0, VOL0G,
37 8 G_PLA, NEL, CONDE, DELTAX,
38 9 CONDEG, ISRAT, SVIS , NODADT_THERM,
39 B G_WPLA, L_WPLA, G_WPLA_FLAG)
40C-----------------------------------------------
41C I m p l i c i t T y p e s
42C-----------------------------------------------
43#include "implicit_f.inc"
44C-----------------------------------------------
45C G l o b a l P a r a m e t e r s
46C-----------------------------------------------
47#include "mvsiz_p.inc"
48C-----------------------------------------------
49C D u m m y A r g u m e n t s
50C-----------------------------------------------
51 INTEGER, INTENT(IN) :: ISRAT
52 INTEGER, INTENT(IN) :: NODADT_THERM
53 INTEGER NPE,G_PLA,NEL
54 my_real
55 . PX(MVSIZ,*),PY(MVSIZ,*),PZ(MVSIZ,*),SSP_EQ(*),
56 . FX(MVSIZ,*), FY(MVSIZ,*), FZ(MVSIZ,*),
57 . SIG(NEL,6),VOL(*),QVIS(*),EINT(*),RHO(*),Q(*),EPLASG(*),EPLAS(*),
58 . SIGG(NEL,6),EINTG(NEL),RHOG(*),QG(*),WI,STIG(MVSIZ,*),EPSD(*),
59 . EPSDG(*),STIN(MVSIZ,*),VOLG(*),VOL0(*),VOL0G(*),CONDE(MVSIZ),
60 . DELTAX(MVSIZ), CONDEG(MVSIZ,*)
61 INTEGER, INTENT(IN) :: G_WPLA_FLAG
62 my_real, DIMENSION(MVSIZ,6), INTENT(INOUT) :: svis
63 my_real,DIMENSION(NEL*G_WPLA_FLAG), INTENT(INOUT) :: g_wpla
64 my_real,DIMENSION(NEL*G_WPLA_FLAG), INTENT(IN) :: l_wpla
65C-----------------------------------------------
66C C o m m o n B l o c k s
67C-----------------------------------------------
68#include "scr18_c.inc"
69C-----------------------------------------------
70C L o c a l V a r i a b l e s
71C-----------------------------------------------
72 INTEGER I,N
73C REAL
74 my_real
75 . s1(mvsiz),s2(mvsiz),s3(mvsiz),s4(mvsiz),s5(mvsiz),s6(mvsiz)
76 my_real
77 . fint,aa,wip(mvsiz)
78C=======================================================================
79 DO i=1,nel
80 wip(i) = vol(i)/volg(i)
81 sigg(i,1) = sigg(i,1) + wip(i) * sig(i,1)
82 sigg(i,2) = sigg(i,2) + wip(i) * sig(i,2)
83 sigg(i,3) = sigg(i,3) + wip(i) * sig(i,3)
84 sigg(i,4) = sigg(i,4) + wip(i) * sig(i,4)
85 sigg(i,5) = sigg(i,5) + wip(i) * sig(i,5)
86 sigg(i,6) = sigg(i,6) + wip(i) * sig(i,6)
87 rhog(i) = rhog(i) + wip(i) * rho(i)
88 eintg(i) = eintg(i) + eint(i) * vol0(i)/vol0g(i)
89 IF (g_wpla_flag > 0) g_wpla(i) = g_wpla(i) + l_wpla(i)
90 qg(i) = qg(i) + wip(i) * q(i)
91 s1(i)=(sig(i,1)+svis(i,1)-qvis(i))*vol(i)
92 s2(i)=(sig(i,2)+svis(i,2)-qvis(i))*vol(i)
93 s3(i)=(sig(i,3)+svis(i,3)-qvis(i))*vol(i)
94 s4(i)=(sig(i,4)+svis(i,4))*vol(i)
95 s5(i)=(sig(i,5)+svis(i,5))*vol(i)
96 s6(i)=(sig(i,6)+svis(i,6))*vol(i)
97 ENDDO
98 IF (israt > 0) THEN
99 DO i=1,nel
100 epsdg(i) = epsdg(i) + wip(i) * epsd(i)
101 ENDDO
102 ENDIF
103 IF (g_pla > 0) THEN
104 DO i=1,nel
105 eplasg(i) = eplasg(i) + wip(i) * eplas(i)
106 ENDDO
107 ENDIF
108C
109 DO n=1,npe
110 DO i=1,nel
111 stin(i,n)= vol(i)*
112 . (px(i,n)*px(i,n) + py(i,n)*py(i,n) + pz(i,n)*pz(i,n))
113 aa=rho(i)*ssp_eq(i)*ssp_eq(i)
114 stig(i,n)=stig(i,n)+stin(i,n)*aa
115 fx(i,n)=fx(i,n)-(s1(i)*px(i,n)+s4(i)*py(i,n)+s6(i)*pz(i,n))
116 fy(i,n)=fy(i,n)-(s2(i)*py(i,n)+s5(i)*pz(i,n)+s4(i)*px(i,n))
117 fz(i,n)=fz(i,n)-(s3(i)*pz(i,n)+s6(i)*px(i,n)+s5(i)*py(i,n))
118 ENDDO
119 ENDDO
120 IF(nodadt_therm == 1) THEN
121 DO n=1,npe
122 DO i=1,nel
123 conde(i) = conde(i)*deltax(i)*deltax(i)/four
124 condeg(i,n)= condeg(i,n)+ conde(i)*
125 . (px(i,n)*px(i,n) + py(i,n)*py(i,n) + pz(i,n)*pz(i,n))
126 ENDDO
127 ENDDO
128 ENDIF
129C-----------
130 RETURN
131 END
subroutine s20fint3(npe, sig, px, py, pz, ssp_eq, fx, fy, fz, vol, qvis, stig, stin, eint, rho, q, eplas, epsd, epsdg, sigg, eintg, rhog, qg, eplasg, wi, volg, vol0, vol0g, g_pla, nel, conde, deltax, condeg, israt, svis, nodadt_therm, g_wpla, l_wpla, g_wpla_flag)
Definition s20fint3.F:40