OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
qfint2.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!|| qfint2 ../engine/source/elements/solid_2d/quad/qfint2.F
25!||--- called by ------------------------------------------------------
26!|| bforc2 ../engine/source/ale/bimat/bforc2.F
27!|| qforc2 ../engine/source/elements/solid_2d/quad/qforc2.F
28!||====================================================================
29 SUBROUTINE qfint2(
30 1 SIG, PY1, PY2, PZ1,
31 2 PZ2, AREA, VOL, QVIS,
32 3 F11, F12, F21, F22,
33 4 AX1, AX2, R22, R23,
34 5 R32, R33, NEL, JCVT,
35 6 SVIS)
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C G l o b a l P a r a m e t e r s
42C-----------------------------------------------
43#include "mvsiz_p.inc"
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C-----------------------------------------------
47 INTEGER, INTENT(IN) :: JCVT
48 INTEGER NEL
49 my_real
50 . SIG(NEL,6),
51 . PY1(*), PY2(*), PZ1(*), PZ2(*), AREA(*), VOL(*), QVIS(*),
52 . F11(*), F12(*), F21(*), F22(*), AX1(*),AX2(*),
53 . r22(*), r23(*), r32(*), r33(*)
54 my_real, DIMENSION(MVSIZ,6), INTENT(INOUT) :: svis
55C-----------------------------------------------
56C C o m m o n B l o c k s
57C-----------------------------------------------
58#include "com01_c.inc"
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER I
63 my_real
64 . FAC(MVSIZ), S1(MVSIZ), S2(MVSIZ), S4(MVSIZ),
65 . T1,T2,T3,T4
66C-----------------------------------------------
67 IF (N2D==1) then
68 DO i=1,nel
69 fac(i)=area(i)*area(i)/ max(em15,vol(i))/four
70 ENDDO
71 ELSE
72 DO i=1,nel
73 fac(i)=zero
74 ENDDO
75 ENDIF
76
77 IF(jcvt==0)THEN
78 DO i=1,nel
79 ax1(i)=(sig(i,3)+svis(i,3)-sig(i,1)-svis(i,1))*fac(i)
80 ax2(i)=(sig(i,4)+svis(i,4))*fac(i)
81 END DO
82 ELSE
83 DO i=1,nel
84 s1(i)=sig(i,1)+svis(i,1)
85 s2(i)=sig(i,2)+svis(i,2)
86 s4(i)=sig(i,4)+svis(i,4)
87 t1=s1(i)*r22(i)+s4(i)*r23(i)
88 t2=s4(i)*r32(i)+s2(i)*r33(i)
89 t3=s1(i)*r32(i)+s4(i)*r33(i)
90 t4=s4(i)*r22(i)+s2(i)*r23(i)
91 s1(i)=r22(i)*t1+r23(i)*t4
92 s2(i)=r32(i)*t3+r33(i)*t2
93 s4(i)=r22(i)*t3+r23(i)*t2
94 END DO
95 DO i=1,nel
96 ax1(i)= (sig(i,3)+svis(i,3)-s1(i))*fac(i)
97 ax2(i)= s4(i)*fac(i)
98 END DO
99 END IF
100
101 DO i=1,nel
102 s1(i) = sig(i,1)+svis(i,1)-qvis(i)
103 s2(i) = sig(i,2)+svis(i,2)-qvis(i)
104 s4(i) = sig(i,4)+svis(i,4)
105 f11(i)=s1(i)*py1(i)+s4(i)*pz1(i)
106 f21(i)=s2(i)*pz1(i)+s4(i)*py1(i)
107 f12(i)=s1(i)*py2(i)+s4(i)*pz2(i)
108 f22(i)=s2(i)*pz2(i)+s4(i)*py2(i)
109 ENDDO
110
111 RETURN
112 END
#define max(a, b)
Definition macros.h:21
subroutine qfint2(sig, py1, py2, pz1, pz2, area, vol, qvis, f11, f12, f21, f22, ax1, ax2, r22, r23, r32, r33, nel, jcvt, svis)
Definition qfint2.F:36