OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
c3deri3.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!|| c3deri3 ../engine/source/elements/sh3n/coque3n/c3deri3.F
25!||--- called by ------------------------------------------------------
26!|| c3forc3 ../engine/source/elements/sh3n/coque3n/c3forc3.F
27!|| c3forc3_crk ../engine/source/elements/xfem/c3forc3_crk.F
28!||====================================================================
29 SUBROUTINE c3deri3(JFT ,JLT ,PX1 ,PY1 ,PY2 ,
30 . SMSTR ,OFFG ,ISMSTR ,ALPE ,ALDT ,
31 . UX1 ,UX2 ,UX3 ,UY1 ,UY2 ,
32 . UY3 ,NEL ,AREA ,X21G ,Y21G ,
33 . Z21G ,X31G ,Y31G ,Z31G ,X2 ,
34 . Y2 ,X3 ,Y3 ,
35 . E1X ,E1Y ,E1Z ,E2X ,
36 . E2Y ,E2Z ,E3X ,E3Y ,E3Z )
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 JFT, JLT,ISMSTR,NEL
49 my_real
50 . PX1(*),PY1(*),PY2(*),OFFG(*),ALPE(MVSIZ),AREA(MVSIZ),
51 . E1X(MVSIZ), E1Y(MVSIZ), E1Z(MVSIZ),
52 . E2X(MVSIZ), E2Y(MVSIZ), E2Z(MVSIZ),
53 . E3X(MVSIZ), E3Y(MVSIZ), E3Z(MVSIZ),
54 . UX1(MVSIZ),UX2(MVSIZ),UX3(MVSIZ),UY1(MVSIZ),
55 . x2(mvsiz),y2(mvsiz),x3(mvsiz),y3(mvsiz),
56 . x21g(mvsiz), y21g(mvsiz), z21g(mvsiz),
57 . x31g(mvsiz), y31g(mvsiz), z31g(mvsiz),
58 . uy2(mvsiz),uy3(mvsiz),aldt(mvsiz)
59 DOUBLE PRECISION SMSTR(*)
60C-----------------------------------------------
61C L o c a l V a r i a b l e s
62C-----------------------------------------------
63 INTEGER I, II(3)
64 my_real AL1, AL2, AL3, ALMAX
65C=======================================================================
66 DO i=jft,jlt
67 x2(i)=e1x(i)*x21g(i)+e1y(i)*y21g(i)+e1z(i)*z21g(i)
68 y2(i)=e2x(i)*x21g(i)+e2y(i)*y21g(i)+e2z(i)*z21g(i)
69 x3(i)=e1x(i)*x31g(i)+e1y(i)*y31g(i)+e1z(i)*z31g(i)
70 y3(i)=e2x(i)*x31g(i)+e2y(i)*y31g(i)+e2z(i)*z31g(i)
71 ENDDO
72C
73 DO i=1,3
74 ii(i) = nel*(i-1)
75 ENDDO
76C
77 IF (ismstr == 11) THEN
78 DO i=jft,jlt
79 IF (abs(offg(i)) == one) offg(i)=sign(two,offg(i))
80 ENDDO
81 DO i=jft,jlt
82 ux1(i) = zero
83 uy1(i) = zero
84 ux2(i) = zero
85 uy2(i) = zero
86 ux3(i) = zero
87 uy3(i) = zero
88 IF(abs(offg(i)) == two)THEN
89 ux2(i) = x2(i)-smstr(ii(1)+i)
90 ux3(i) = x3(i)-smstr(ii(2)+i)
91 uy3(i) = y3(i)-smstr(ii(3)+i)
92 x2(i) = smstr(ii(1)+i)
93 x3(i) = smstr(ii(2)+i)
94 y3(i) = smstr(ii(3)+i)
95 area(i) = half*x2(i)*y3(i)
96 ELSE
97 smstr(ii(1)+i)=x2(i)
98 smstr(ii(2)+i)=x3(i)
99 smstr(ii(3)+i)=y3(i)
100 ENDIF
101 ENDDO
102 ELSEIF (ismstr == 1.OR.ismstr == 2) THEN
103 DO i=jft,jlt
104 IF(offg(i) == two)THEN
105 x2(i)=smstr(ii(1)+i)
106 x3(i)=smstr(ii(2)+i)
107 y3(i)=smstr(ii(3)+i)
108 area(i) = half*x2(i)*y3(i)
109 ELSE
110 smstr(ii(1)+i)=x2(i)
111 smstr(ii(2)+i)=x3(i)
112 smstr(ii(3)+i)=y3(i)
113 ENDIF
114 ENDDO
115 ENDIF
116 IF (ismstr == 1) THEN
117 DO i=jft,jlt
118 IF (offg(i) == one) offg(i)=two
119 ENDDO
120 ENDIF
121C
122 DO i=jft,jlt
123 y3(i) = sign(max(em15,abs(y3(i))),y3(i))
124 px1(i)=-half*y3(i)
125 py1(i)= half*(x3(i)-x2(i))
126 py2(i)=-half*x3(i)
127 ENDDO
128C
129 DO i=jft,jlt
130 al1 = x2(i) * x2(i)
131 al2 = (x3(i)-x2(i)) * (x3(i)-x2(i)) + y3(i) * y3(i)
132 al3 = x3(i) * x3(i) + y3(i) * y3(i)
133 almax = max(al1,al2,al3)
134 aldt(i)= two*area(i) / sqrt(almax)
135 alpe(i)=one
136 ENDDO
137C---------------------------------------------------------
138 RETURN
139C
140 END
subroutine c3deri3(jft, jlt, px1, py1, py2, smstr, offg, ismstr, alpe, aldt, ux1, ux2, ux3, uy1, uy2, uy3, nel, area, x21g, y21g, z21g, x31g, y31g, z31g, x2, y2, x3, y3, e1x, e1y, e1z, e2x, e2y, e2z, e3x, e3y, e3z)
Definition c3deri3.F:37
#define max(a, b)
Definition macros.h:21