OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
czstrah3.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!|| czstrah3 ../engine/source/elements/shell/coquez/czstrah3.F
25!||--- called by ------------------------------------------------------
26!|| czforc3 ../engine/source/elements/shell/coquez/czforc3.F
27!||====================================================================
28 SUBROUTINE czstrah3(JFT ,JLT ,STRA_H,VHG ,A_I ,
29 3 MX23 ,MX34 ,MY23 ,MY34 ,DT1C ,
30 4 EXX ,EYY ,EXY ,EXZ ,EYZ ,
31 3 KXX ,KYY ,KXY ,NEL )
32C-----------------------------------------------
33C I m p l i c i t T y p e s
34C-----------------------------------------------
35#include "implicit_f.inc"
36C-----------------------------------------------
37C G l o b a l P a r a m e t e r s
38C-----------------------------------------------
39#include "mvsiz_p.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43C-----------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER, INTENT(IN) :: JFT, JLT,NEL
47 my_real, DIMENSION(MVSIZ),INTENT(IN) :: A_I,
48 . DT1C,MX23,MX34,MY23,MY34,
49 . exx,eyy,exy,exz,eyz,
50 . kxx ,kyy ,kxy
51 my_real, DIMENSION(MVSIZ,6),INTENT(IN) :: vhg
52 my_real, DIMENSION(NEL,8,4),INTENT(INOUT) :: stra_h
53C-----------------------------------------------
54C L o c a l V a r i a b l e s
55C-----------------------------------------------
56 INTEGER PT,PT00,PT0,I,J,EP,IUN,NG,K,NPG
57 MY_REAL
58 . HX(MVSIZ),HY(MVSIZ),DHG(MVSIZ,6),PG1,PG,VPG(2,4)
59 my_real
60 . a4_1(mvsiz),a_4(mvsiz),strain(8),hxz(mvsiz),hyz(mvsiz)
61 PARAMETER (pg=.577350269189626)
62 parameter(pg1=-.577350269189626)
63 DATA vpg/pg1,pg1,pg,pg1,pg,pg,pg1,pg/ ! VPG(1:2,4):ksi,eta
64C---+----1----+----2----+----3----+----4----+----5----+----6----+----7--
65 npg =4
66 a4_1(jft:jlt) = four*a_i(jft:jlt)
67 a_4(jft:jlt) = fourth*a_i(jft:jlt)
68 DO j=1,6
69 dhg(jft:jlt,j) = vhg(jft:jlt,j) * dt1c(jft:jlt)
70 ENDDO
71 DO ng = 1,npg
72 DO i=jft,jlt
73 hx(i) = a4_1(i)*(my34(i)*vpg(2,ng)- my23(i)*vpg(1,ng))
74 hy(i) = a4_1(i)*(-mx34(i)*vpg(2,ng)+mx23(i)*vpg(1,ng))
75 hxz(i)= a_4(i)*(my34(i)*vpg(2,ng)*dhg(i,5)- my23(i)*vpg(1,ng)*dhg(i,6))
76 hyz(i)= a_4(i)*(mx23(i)*vpg(1,ng)*dhg(i,5)- mx34(i)*vpg(2,ng)*dhg(i,6))
77 strain(1) = exx(i) + hx(i)*dhg(i,1)
78 strain(2) = eyy(i) + hy(i)*dhg(i,2)
79 strain(3) = exy(i)
80 strain(6) = kxx(i) + hx(i)*dhg(i,3)
81 strain(7) = kyy(i) + hy(i)*dhg(i,4)
82 strain(8) = kxy(i)
83 strain(5) = exz(i) + hxz(i)
84 strain(4) = eyz(i) + hyz(i)
85 stra_h(i,1,ng) = stra_h(i,1,ng) + strain(1)
86 stra_h(i,2,ng) = stra_h(i,2,ng) + strain(2)
87 stra_h(i,3,ng) = stra_h(i,3,ng) + strain(3)
88 stra_h(i,4,ng) = stra_h(i,4,ng) + strain(4)
89 stra_h(i,5,ng) = stra_h(i,5,ng) + strain(5)
90 stra_h(i,6,ng) = stra_h(i,6,ng) + strain(6)
91 stra_h(i,7,ng) = stra_h(i,7,ng) + strain(7)
92 stra_h(i,8,ng) = stra_h(i,8,ng) + strain(8)
93 ENDDO
94 ENDDO
95C
96 RETURN
97 END
subroutine czstrah3(jft, jlt, stra_h, vhg, a_i, mx23, mx34, my23, my34, dt1c, exx, eyy, exy, exz, eyz, kxx, kyy, kxy, nel)
Definition czstrah3.F:32