OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
q4fint2.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!|| q4fint2 ../engine/source/elements/solid_2d/quad4/q4fint2.F
25!||--- called by ------------------------------------------------------
26!|| q4forc2 ../engine/source/elements/solid_2d/quad4/q4forc2.F
27!||====================================================================
28 SUBROUTINE q4fint2(
29 1 SIG, AY, FAY, FAZ,
30 2 PY1, PY2, PY3, PY4,
31 3 PZ1, PZ2, PZ3, PZ4,
32 4 BYZ1, BYZ2, BYZ3, BYZ4,
33 5 BZY1, BZY2, BZY3, BZY4,
34 6 FY1, FZ1, FY2, FZ2,
35 7 FY3, FZ3, FY4, FZ4,
36 8 R22, R23, R32, R33,
37 9 AIR, VOL, QVIS, ICP,
38 A NEL, JHBE, JCVT, SVIS)
39C-----------------------------------------------
40C I m p l i c i t T y p e s
41C-----------------------------------------------
42#include "implicit_f.inc"
43C-----------------------------------------------
44C G l o b a l P a r a m e t e r s
45C-----------------------------------------------
46#include "mvsiz_p.inc"
47C-----------------------------------------------
48C C o m m o n B l o c k s
49C-----------------------------------------------
50#include "com01_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER, INTENT(IN) :: JHBE
55 INTEGER, INTENT(IN) :: JCVT
56 INTEGER ICP,NEL
57C REAL
58 my_real
59 . SIG(NEL,6),AY(*),FAY(*),FAZ(*),
60 . PY1(*),PY2(*),PY3(*),PY4(*),
61 . PZ1(*),PZ2(*),PZ3(*),PZ4(*),
62 . BYZ1(*),BYZ2(*),BYZ3(*),BYZ4(*),
63 . BZY1(*),BZY2(*),BZY3(*),BZY4(*),
64 . fy1(*),fz1(*),fy2(*),fz2(*),
65 . fy3(*),fz3(*),fy4(*),fz4(*),
66 . r22(*),r23(*),r32(*),r33(*),
67 . air(*),vol(*),qvis(*)
68 my_real, DIMENSION(MVSIZ,6), INTENT(INOUT) :: svis
69C-----------------------------------------------
70C FUNCTION:
71C ARGUMENTS: (I: input, O: output, IO: input & output, W: workspace)
72C TYPE NAME FUNCTION
73C I SIG(NEL,6) - STRESS COMPONENTS
74C I AY(*) - Ni/r AT CENTER FOR AXISYMMETRIC CASE
75C I FAY(*),FAZ(*) - COMPONENT OF INTERNAL FORCE FOR AXISYMMETRIC CASE
76C I PY1(*)~PZ4(*) - SHAPE DERIVATIVES (dNi/dY, dNi/dZ)
77C O FY1(*)~FZ4(*) - INTERNAL FORCE IN LOCAL STORAGE
78C I R22(*)~R33(*) - TRANSFORMATION MATRIX
79C I AIR(*) - W*|J|
80C I VOL(*) - W*|J| FOR PLAIN CASE; r'*W*|J| FOR AXISYMMETRIC CASE
81C I QVIS(*) - VISCOUS PRESSURE
82C I ICP - FLAG FOR CONSTANT PRESURE
83C-----------------------------------------------
84C L o c a l V a r i a b l e s
85C-----------------------------------------------
86 INTEGER I
87C REAL
88 my_real
89 . S1(MVSIZ),S2(MVSIZ),S3(MVSIZ),S4(MVSIZ),
90 . FAC(MVSIZ),P(MVSIZ),T1,T2,T3,T4
91C-----------------------------------------------
92C S o u r c e L i n e s
93C-----------------------------------------------
94 IF(N2D==1 .AND. jhbe==17) THEN
95 DO i=1,nel
96 fac(i) = air(i)
97 ENDDO
98 ELSE
99 DO i=1,nel
100 fac(i) = vol(i)
101 ENDDO
102 ENDIF
103C
104C ADD VISCOUS STRESSES "SVIS" & "QVIS" INTO THE TOTAL ONES
105C REMOVE PRESSURE FROM STRESSES FOR THE CONSTANT PRESSURE CASE
106 IF(icp==1) THEN
107 DO i=1,nel
108 p(i)=third*(sig(i,1)+sig(i,2)+sig(i,3)+
109 . svis(i,1)+svis(i,2)+svis(i,3))
110 s1(i)=(sig(i,1)+svis(i,1)-p(i))*fac(i)
111 s2(i)=(sig(i,2)+svis(i,2)-p(i))*fac(i)
112 ENDDO
113 ELSE
114 DO i=1,nel
115 s1(i)=(sig(i,1)+svis(i,1)-qvis(i))*fac(i)
116 s2(i)=(sig(i,2)+svis(i,2)-qvis(i))*fac(i)
117 ENDDO
118 ENDIF
119C
120 DO i=1,nel
121 fy1(i) = fy1(i) - s1(i)*py1(i)- s2(i)*bzy1(i)
122 fy2(i) = fy2(i) - s1(i)*py2(i)- s2(i)*bzy2(i)
123 fy3(i) = fy3(i) - s1(i)*py3(i)- s2(i)*bzy3(i)
124 fy4(i) = fy4(i) - s1(i)*py4(i)- s2(i)*bzy4(i)
125 fz1(i) = fz1(i) - s2(i)*pz1(i)- s1(i)*byz1(i)
126 fz2(i) = fz2(i) - s2(i)*pz2(i)- s1(i)*byz2(i)
127 fz3(i) = fz3(i) - s2(i)*pz3(i)- s1(i)*byz3(i)
128 fz4(i) = fz4(i) - s2(i)*pz4(i)- s1(i)*byz4(i)
129 ENDDO
130C
131 IF(n2d==1.AND.jhbe==17) THEN
132 IF(icp==1) THEN
133 DO i=1,nel
134 s3(i)=(sig(i,3)+svis(i,3)-p(i))*fac(i)
135 s4(i)=(sig(i,4)+svis(i,4))*fac(i)
136 ENDDO
137 ELSE
138 DO i=1,nel
139 s3(i)=(sig(i,3)+svis(i,3)-qvis(i))*fac(i)
140 s4(i)=(sig(i,4)+svis(i,4))*fac(i)
141 ENDDO
142 END IF
143 IF(jcvt/=0) THEN
144 DO i=1,nel
145 t1=s1(i)*r22(i)+s4(i)*r23(i)
146 t2=s4(i)*r32(i)+s2(i)*r33(i)
147 t3=s1(i)*r32(i)+s4(i)*r33(i)
148 t4=s4(i)*r22(i)+s2(i)*r23(i)
149 s1(i)=r22(i)*t1+r23(i)*t4
150 s2(i)=r32(i)*t3+r33(i)*t2
151 s4(i)=r22(i)*t3+r23(i)*t2
152 ENDDO
153 ENDIF
154 DO i=1,nel
155 fay(i) = fay(i) + (s1(i)-s3(i))*ay(i)
156 faz(i) = faz(i) + s4(i)*ay(i)
157 ENDDO
158 ENDIF
159C
160 RETURN
161 END
162
subroutine q4fint2(sig, ay, fay, faz, py1, py2, py3, py4, pz1, pz2, pz3, pz4, byz1, byz2, byz3, byz4, bzy1, bzy2, bzy3, bzy4, fy1, fz1, fy2, fz2, fy3, fz3, fy4, fz4, r22, r23, r32, r33, air, vol, qvis, icp, nel, jhbe, jcvt, svis)
Definition q4fint2.F:39