OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
cgshell.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!|| cgshell4 ../engine/source/implicit/cgshell.F
25!||--- called by ------------------------------------------------------
26!|| spbrm_pre ../engine/source/implicit/imp_solv.F
27!||--- uses -----------------------------------------------------
28!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
29!||====================================================================
30 SUBROUTINE cgshell4(ELBUF_STR,JFT,JLT ,PM ,IXC ,
31 + X ,MAS,XC ,YC ,ZC )
32C-----------------------------------------------
33 USE elbufdef_mod
34C-----------------------------------------------
35C I m p l i c i t T y p e s
36C-----------------------------------------------
37#include "implicit_f.inc"
38C-----------------------------------------------
39C C o m m o n B l o c k s
40C-----------------------------------------------
41#include "mvsiz_p.inc"
42#include "param_c.inc"
43C-----------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER IXC(NIXC,*), JFT, JLT
47C REAL
49 . pm(npropm,*),x(3,*),mas,xc,yc,zc
50 TYPE (ELBUF_STRUCT_), TARGET :: ELBUF_STR
51C-----------------------------------------------
52C L o c a l V a r i a b l e s
53C-----------------------------------------------
54 INTEGER I,MAT
55C REAL
57 . xx,yy,zz,xmas25,xmas(mvsiz),area(mvsiz),
58 . rx, ry, rz,sx,sy,sz,e3x,e3y,e3z
59 TYPE(g_bufel_) ,POINTER :: GBUF
60C-----------------------------------------------
61 gbuf => elbuf_str%GBUF
62 DO i=jft,jlt
63 rx=x(1,ixc(3,i))+x(1,ixc(4,i))-x(1,ixc(2,i))-x(1,ixc(5,i))
64 sx=x(1,ixc(4,i))+x(1,ixc(5,i))-x(1,ixc(2,i))-x(1,ixc(3,i))
65 ry=x(2,ixc(3,i))+x(2,ixc(4,i))-x(2,ixc(2,i))-x(2,ixc(5,i))
66 sy=x(2,ixc(4,i))+x(2,ixc(5,i))-x(2,ixc(2,i))-x(2,ixc(3,i))
67 rz=x(3,ixc(3,i))+x(3,ixc(4,i))-x(3,ixc(2,i))-x(3,ixc(5,i))
68 sz=x(3,ixc(4,i))+x(3,ixc(5,i))-x(3,ixc(2,i))-x(3,ixc(3,i))
69 e3x = ry * sz - rz * sy
70 e3y = rz * sx - rx * sz
71 e3z = rx * sy - ry * sx
72 area(i) =fourth*sqrt(e3x*e3x + e3y*e3y + e3z*e3z)
73 END DO
74 DO i=jft,jlt
75 mat = ixc(1,i)
76 xmas(i)=pm(1,mat)*area(i)*gbuf%THK(i)
77 END DO
78C
79C
80 DO i=jft,jlt
81 IF (gbuf%OFF(i) ==zero) cycle
82 xx= x(1,ixc(2,i))+x(1,ixc(3,i))+x(1,ixc(4,i))+x(1,ixc(5,i))
83 yy= x(2,ixc(2,i))+x(2,ixc(3,i))+x(2,ixc(4,i))+x(2,ixc(5,i))
84 zz= x(3,ixc(2,i))+x(3,ixc(3,i))+x(3,ixc(4,i))+x(3,ixc(5,i))
85 xmas25 = fourth*xmas(i)
86 mas = mas+xmas(i)
87 xc = xc + xmas25*xx
88 yc = yc + xmas25*yy
89 zc = zc + xmas25*zz
90 ENDDO
91C
92 RETURN
93 END
94!||====================================================================
95!|| cgshell3 ../engine/source/implicit/cgshell.F
96!||--- called by ------------------------------------------------------
97!|| spbrm_pre ../engine/source/implicit/imp_solv.F
98!||--- uses -----------------------------------------------------
99!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
100!||====================================================================
101 SUBROUTINE cgshell3(ELBUF_STR,JFT,JLT ,PM ,IXTG ,
102 + X ,MAS,XC ,YC ,ZC )
103C-----------------------------------------------
104 USE elbufdef_mod
105C-----------------------------------------------
106C I m p l i c i t T y p e s
107C-----------------------------------------------
108#include "implicit_f.inc"
109C-----------------------------------------------
110C C o m m o n B l o c k s
111C-----------------------------------------------
112#include "mvsiz_p.inc"
113#include "param_c.inc"
114C-----------------------------------------------
115C D u m m y A r g u m e n t s
116C-----------------------------------------------
117 INTEGER IXTG(NIXTG,*), JFT, JLT
118C REAL
119 my_real
120 . pm(npropm,*),x(3,*),mas,xc,yc,zc
121 TYPE (ELBUF_STRUCT_), TARGET :: ELBUF_STR
122C-----------------------------------------------
123C L o c a l V a r i a b l e s
124C-----------------------------------------------
125 INTEGER I,MAT
126C REAL
127 my_real
128 . xx,yy,zz,xmas25,xmas(mvsiz),area(mvsiz),
129 . rx, ry, rz,sx,sy,sz,e3x,e3y,e3z
130 TYPE(g_bufel_) ,POINTER :: GBUF
131C-----------------------------------------------
132 gbuf => elbuf_str%GBUF
133 DO i=jft,jlt
134 rx=x(1,ixtg(3,i))-x(1,ixtg(2,i))
135 sx=x(1,ixtg(4,i))-x(1,ixtg(2,i))
136 ry=x(2,ixtg(3,i))-x(2,ixtg(2,i))
137 sy=x(2,ixtg(4,i))-x(2,ixtg(2,i))
138 rz=x(3,ixtg(3,i))-x(3,ixtg(2,i))
139 sz=x(3,ixtg(4,i))-x(3,ixtg(2,i))
140 e3x = ry * sz - rz * sy
141 e3y = rz * sx - rx * sz
142 e3z = rx * sy - ry * sx
143 area(i) =half*sqrt(e3x*e3x + e3y*e3y + e3z*e3z)
144 END DO
145 DO i=jft,jlt
146 mat = ixtg(1,i)
147 xmas(i)=pm(1,mat)*area(i)*gbuf%THK(i)
148 END DO
149C
150C
151 DO i=jft,jlt
152 IF (gbuf%OFF(i) ==zero) cycle
153 xx= x(1,ixtg(2,i))+x(1,ixtg(3,i))+x(1,ixtg(4,i))
154 yy= x(2,ixtg(2,i))+x(2,ixtg(3,i))+x(2,ixtg(4,i))
155 zz= x(3,ixtg(2,i))+x(3,ixtg(3,i))+x(3,ixtg(4,i))
156 xmas25 = third*xmas(i)
157 mas = mas+xmas(i)
158 xc = xc + xmas25*xx
159 yc = yc + xmas25*yy
160 zc = zc + xmas25*zz
161 ENDDO
162C
163 RETURN
164 END
subroutine cgshell4(elbuf_str, jft, jlt, pm, ixc, x, mas, xc, yc, zc)
Definition cgshell.F:32
subroutine cgshell3(elbuf_str, jft, jlt, pm, ixtg, x, mas, xc, yc, zc)
Definition cgshell.F:103
#define my_real
Definition cppsort.cpp:32
subroutine area(d1, x, x2, y, y2, eint, stif0)