OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s4cumu3.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!|| s4cumu3 ../engine/source/elements/solid/solide4/s4cumu3.F
25!||--- called by ------------------------------------------------------
26!|| multi_fvm2fem ../engine/source/multifluid/multi_fvm2fem.F
27!|| s4forc3 ../engine/source/elements/solid/solide4/s4forc3.f
28!||====================================================================
29 SUBROUTINE s4cumu3(
30 1 OFFG, E, NC1, NC2,
31 2 NC3, NC4, STIFN, STI,
32 3 F11, F21, F31, F12,
33 4 F22, F32, F13, F23,
34 5 F33, F14, F24, F34,
35 6 THEM, FTHE, CONDN, CONDE,
36 7 NEL, JTHE, 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) :: NEL
49 INTEGER, INTENT(IN) :: JTHE
50 INTEGER, INTENT(IN) :: NODADT_THERM
51 INTEGER NC1(*), NC2(*), NC3(*), NC4(*)
52C REAL
53 my_real
54 . OFFG(*),E(3,*),STIFN(*),STI(*),
55 . f11(*),f21(*),f31(*),f12(*),f22(*),f32(*),
56 . f13(*),f23(*),f33(*),f14(*),f24(*),f34(*),
57 . them(mvsiz,4),fthe(*),condn(*),conde(*)
58CMasParINCLUDE 'scumu3.intmap.inc'
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,J
67 my_real
68 . OFF_L
69C-----------------------------------------------
70 OFF_L = 0.
71 do i=1,nel
72 off_l = min(off_l,offg(i))
73 ENDDO
74 IF(off_l<zero)THEN
75 DO i=1,nel
76 IF(offg(i)<zero)THEN
77 f11(i)=zero
78 f21(i)=zero
79 f31(i)=zero
80 f12(i)=zero
81 f22(i)=zero
82 f32(i)=zero
83 f13(i)=zero
84 f23(i)=zero
85 f33(i)=zero
86 f14(i)=zero
87 f24(i)=zero
88 f34(i)=zero
89 sti(i)=zero
90 ENDIF
91 ENDDO
92 ENDIF
93 IF(jthe < 0 ) THEN
94 IF(off_l<=zero)THEN
95 DO j=1,4
96 DO i=1,nel
97 IF(offg(i)<=zero)THEN
98 them(i,j)=zero
99 ENDIF
100 ENDDO
101 ENDDO
102 ENDIF
103 IF(nodadt_therm == 1) THEN
104 IF(off_l<zero)THEN
105 DO i=1,nel
106 IF(offg(i)<zero)THEN
107 conde(i)=zero
108 ENDIF
109 ENDDO
110 ENDIF
111 ENDIF
112 ENDIF
113C-----------------------------------------------
114C
115C because 2*Mnodal = 2*Melement/4
116 DO i=1,nel
117 sti(i)=half*sti(i)
118 END DO
119 IF(nodadt_therm == 1 ) THEN
120 DO i=1,nel
121 conde(i)=fourth*conde(i)
122 END DO
123 ENDIF
124C
125 IF(jthe < 0 ) THEN
126 IF(nodadt_therm == 1) THEN
127 DO i=1,nel
128C
129 e(1,nc1(i))=e(1,nc1(i))+f11(i)
130 e(2,nc1(i))=e(2,nc1(i))+f21(i)
131 e(3,nc1(i))=e(3,nc1(i))+f31(i)
132 stifn(nc1(i))=stifn(nc1(i))+sti(i)
133 fthe(nc1(i)) = fthe(nc1(i)) + them(i,1)
134 condn(nc1(i))= condn(nc1(i))+conde(i)
135C
136 e(1,nc2(i))=e(1,nc2(i))+f12(i)
137 e(2,nc2(i))=e(2,nc2(i))+f22(i)
138 e(3,nc2(i))=e(3,nc2(i))+f32(i)
139 stifn(nc2(i))=stifn(nc2(i))+sti(i)
140 fthe(nc2(i)) = fthe(nc2(i)) + them(i,2)
141 condn(nc2(i))= condn(nc2(i))+ conde(i)
142C
143 e(1,nc3(i))=e(1,nc3(i))+f13(i)
144 e(2,nc3(i))=e(2,nc3(i))+f23(i)
145 e(3,nc3(i))=e(3,nc3(i))+f33(i)
146 stifn(nc3(i))=stifn(nc3(i))+sti(i)
147 fthe(nc3(i)) = fthe(nc3(i)) + them(i,3)
148 condn(nc3(i))= condn(nc3(i))+ conde(i)
149C
150 e(1,nc4(i))=e(1,nc4(i))+f14(i)
151 e(2,nc4(i))=e(2,nc4(i))+f24(i)
152 e(3,nc4(i))=e(3,nc4(i))+f34(i)
153 stifn(nc4(i))=stifn(nc4(i))+sti(i)
154 fthe(nc4(i)) = fthe(nc4(i)) + them(i,4)
155 condn(nc4(i))= condn(nc4(i))+ conde(i)
156C
157 ENDDO
158 ELSE
159 DO i=1,nel
160C
161 e(1,nc1(i))=e(1,nc1(i))+f11(i)
162 e(2,nc1(i))=e(2,nc1(i))+f21(i)
163 e(3,nc1(i))=e(3,nc1(i))+f31(i)
164 stifn(nc1(i))=stifn(nc1(i))+sti(i)
165 fthe(nc1(i)) = fthe(nc1(i)) + them(i,1)
166C
167 e(1,nc2(i))=e(1,nc2(i))+f12(i)
168 e(2,nc2(i))=e(2,nc2(i))+f22(i)
169 e(3,nc2(i))=e(3,nc2(i))+f32(i)
170 stifn(nc2(i))=stifn(nc2(i))+sti(i)
171 fthe(nc2(i)) = fthe(nc2(i)) + them(i,2)
172C
173 e(1,nc3(i))=e(1,nc3(i))+f13(i)
174 e(2,nc3(i))=e(2,nc3(i))+f23(i)
175 e(3,nc3(i))=e(3,nc3(i))+f33(i)
176 stifn(nc3(i))=stifn(nc3(i))+sti(i)
177 fthe(nc3(i)) = fthe(nc3(i)) + them(i,3)
178C
179 e(1,nc4(i))=e(1,nc4(i))+f14(i)
180 e(2,nc4(i))=e(2,nc4(i))+f24(i)
181 e(3,nc4(i))=e(3,nc4(i))+f34(i)
182 stifn(nc4(i))=stifn(nc4(i))+sti(i)
183 fthe(nc4(i)) = fthe(nc4(i)) + them(i,4)
184C
185 ENDDO
186 ENDIF
187 ELSE
188 DO 100 i=1,nel
189C
190 e(1,nc1(i))=e(1,nc1(i))+f11(i)
191 e(2,nc1(i))=e(2,nc1(i))+f21(i)
192 e(3,nc1(i))=e(3,nc1(i))+f31(i)
193 stifn(nc1(i))=stifn(nc1(i))+sti(i)
194C
195 e(1,nc2(i))=e(1,nc2(i))+f12(i)
196 e(2,nc2(i))=e(2,nc2(i))+f22(i)
197 e(3,nc2(i))=e(3,nc2(i))+f32(i)
198 stifn(nc2(i))=stifn(nc2(i))+sti(i)
199C
200 e(1,nc3(i))=e(1,nc3(i))+f13(i)
201 e(2,nc3(i))=e(2,nc3(i))+f23(i)
202 e(3,nc3(i))=e(3,nc3(i))+f33(i)
203 stifn(nc3(i))=stifn(nc3(i))+sti(i)
204C
205 e(1,nc4(i))=e(1,nc4(i))+f14(i)
206 e(2,nc4(i))=e(2,nc4(i))+f24(i)
207 e(3,nc4(i))=e(3,nc4(i))+f34(i)
208 stifn(nc4(i))=stifn(nc4(i))+sti(i)
209C
210 100 CONTINUE
211
212 ENDIF
213
214 RETURN
215 END
#define min(a, b)
Definition macros.h:20
subroutine s4cumu3(offg, e, nc1, nc2, nc3, nc4, stifn, sti, f11, f21, f31, f12, f22, f32, f13, f23, f33, f14, f24, f34, them, fthe, condn, conde, nel, jthe, nodadt_therm)
Definition s4cumu3.F:37
subroutine s4forc3(timers, output, elbuf_tab, ng, pm, geo, ixs, x, a, v, ms, w, flux, flu1, veul, fv, ale_connect, iparg, tf, npf, bufmat, partsav, nloc_dmg, dt2t, neltst, ityptst, stifn, fsky, iads, offset, eani, iparts, f11, f21, f31, f12, f22, f32, f13, f23, f33, f14, f24, f34, nel, fskym, msnf, ipm, igeo, bufvois, istrain, itask, temp, fthe, fthesky, iexpan, gresav, grth, igrth, mssa, dmels, table, xdp, sfem_nodvar, voln, condn, condnsky, d, sensors, ioutprt, mat_elem, h3d_strain, dt, idel7nok, nsvois, sz_bufvois, snpc, stf, sbufmat, svis, idtmins, iresp, idel7ng, maxfunc, userl_avail, glob_therm, impl_s, idyna, s_sfem_nodvar)
Definition s4forc3.F:109