OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s8efmoy3.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!|| s8efmoy3 ../engine/source/elements/solid/solide8e/s8efmoy3.F
25!||--- called by ------------------------------------------------------
26!|| q4forc2 ../engine/source/elements/solid_2d/quad4/q4forc2.F
27!|| s8eforc3 ../engine/source/elements/solid/solide8e/s8eforc3.F
28!|| s8sforc3 ../engine/source/elements/solid/solide8s/s8sforc3.F
29!||====================================================================
30 SUBROUTINE s8efmoy3(
31 1 SIGOR, VOL, QVIS, PP,
32 2 EINT, RHO, Q, DEFP,
33 3 EPSD, EPSDM, SIGM, EINTM,
34 4 RHOM, QM, DEFPM, VOLG,
35 5 STI, STIN, ICP, OFF,
36 6 VOL0, VOL0G, G_PLA, G_EPSD,
37 7 EINTTH, EINTTHM, IEXPAN, NEL,
38 8 CONDE, CONDEN, SVIS ,NODADT_THERM,
39 9 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 C o m m o n B l o c k s
50C-----------------------------------------------
51#include "scr18_c.inc"
52C-----------------------------------------------
53C D u m m y A r g u m e n t s
54C-----------------------------------------------
55 INTEGER ICP,G_PLA,G_EPSD,IEXPAN,NEL
56 INTEGER, INTENT(IN) :: NODADT_THERM
57 my_real
58 . SIGOR(NEL,6),
59 . VOL(*),QVIS(*),PP(*),
60 . EINT(*),RHO(*),Q(*),DEFPM(*),DEFP(*),
61 . SIGM(NEL,6),EINTM(*),RHOM(*),QM(*),EPSD(*),EPSDM(*),
62 . VOLG(*),STI(*),STIN(*),OFF(*),VOL0(*),VOL0G(*),
63 . EINTTH(*),EINTTHM(*),CONDE(*),CONDEN(*)
64 my_real, DIMENSION(MVSIZ,6), INTENT(INOUT) :: svis
65 INTEGER, INTENT(IN) :: G_WPLA_FLAG
66 my_real,DIMENSION(NEL*G_WPLA_FLAG), INTENT(INOUT) :: g_wpla
67 my_real,DIMENSION(NEL*G_WPLA_FLAG), INTENT(IN) :: l_wpla
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
71 INTEGER I, J
72C REAL
73 my_real
74 . p,fac(mvsiz),fac2(mvsiz)
75C-----------------------------------------------
76C - post-traitement-valeur moyenne au sens a'=(_/ a dv ) /v
77 DO i=1,nel
78 fac(i) = off(i)*vol(i)/volg(i)
79 fac2(i) = vol(i)/volg(i)
80 sigm(i,1) = sigm(i,1) + fac(i) * sigor(i,1)
81 sigm(i,2) = sigm(i,2) + fac(i) * sigor(i,2)
82 sigm(i,3) = sigm(i,3) + fac(i) * sigor(i,3)
83 sigm(i,4) = sigm(i,4) + fac(i) * sigor(i,4)
84 sigm(i,5) = sigm(i,5) + fac(i) * sigor(i,5)
85 sigm(i,6) = sigm(i,6) + fac(i) * sigor(i,6)
86 rhom(i) = rhom(i) + fac2(i)* rho(i)
87 eintm(i) = eintm(i) + eint(i)* vol0(i)/vol0g(i)
88 IF (g_wpla_flag > 0) g_wpla(i) = g_wpla(i) + l_wpla(i)
89 qm(i) = qm(i) + fac(i) * q(i)
90 stin(i) = stin(i) + sti(i)
91 ENDDO
92C
93 IF(nodadt_therm == 1) THEN
94 DO i=1,nel
95 conden(i)= conden(i)+ conde(i)
96 ENDDO
97 ENDIF
98C
99 IF (iexpan > 0) THEN
100 DO i=1,nel
101 eintthm(i) = eintthm(i) + eintth(i)*vol0(i)/vol0g(i)
102 ENDDO
103 ENDIF
104C
105 IF (g_pla > 0) THEN
106 DO i=1,nel
107 defpm(i) = defpm(i) + fac(i) * defp(i)
108 ENDDO
109 ENDIF
110c
111 IF (g_epsd > 0) THEN
112 DO i=1,nel
113 epsdm(i) = epsdm(i) + fac(i) * epsd(i)
114 ENDDO
115 ENDIF
116c
117 IF (icp == 1) THEN
118 DO i=1,nel
119 p =zep3*(sigor(i,1)+sigor(i,2)+sigor(i,3)
120 . +svis(i,1)+svis(i,2)+svis(i,3))
121 pp(i) = pp(i) + fac(i)* (p-qvis(i))
122 ENDDO
123 ENDIF
124C-----------
125 RETURN
126 END
subroutine s8efmoy3(sigor, vol, qvis, pp, eint, rho, q, defp, epsd, epsdm, sigm, eintm, rhom, qm, defpm, volg, sti, stin, icp, off, vol0, vol0g, g_pla, g_epsd, eintth, eintthm, iexpan, nel, conde, conden, svis, nodadt_therm, g_wpla, l_wpla, g_wpla_flag)
Definition s8efmoy3.F:40