OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sigeps34pi.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!|| sigeps34pi ../engine/source/materials/mat/mat034/sigeps34pi.f
25!||--- called by ------------------------------------------------------
26!|| mulaw_ib ../engine/source/elements/beam/mulaw_ib.F
27!||====================================================================
28 SUBROUTINE sigeps34pi(
29 1 NEL ,NUPARAM ,UPARAM ,IPM ,IMAT ,
30 2 NUVAR ,UVAR ,DEPSXX ,DEPSXY ,DEPSXZ ,
31 3 EPSXX ,SIGOXX ,SIGOXY ,SIGOXZ ,
32 5 SIGNXX ,SIGNXY ,SIGNXZ ,TIMESTEP,
33 6 EPSXY ,EPSXZ )
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 "param_c.inc"
42#include "com04_c.inc"
43C-----------------------------------------------
44C I N P U T A r g u m e n t s
45C-----------------------------------------------
46 INTEGER ,INTENT(IN) :: IMAT
47 INTEGER ,INTENT(IN) :: NEL,NUPARAM,NUVAR
48 INTEGER ,DIMENSION(NPROPMI,NUMMAT) ,INTENT(IN) :: IPM
49 my_real :: TIMESTEP
50 my_real ,DIMENSION(NEL) ,INTENT(IN) ::
51 . epsxx,depsxx,depsxy,depsxz,sigoxx,sigoxy,sigoxz,
52 . epsxy,epsxz
53 my_real ,DIMENSION(*) ,INTENT(IN) :: uparam
54C-----------------------------------------------
55C O U T P U T A r g u m e n t s
56C-----------------------------------------------
57 my_real ,DIMENSION(NEL) ,INTENT(OUT) :: signxx,signxy,signxz
58 my_real ,DIMENSION(NEL,NUVAR) ,INTENT(INOUT):: uvar
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER :: I,IADBUF
63 my_real :: ddexx,ddexy,ddexz,depsdxx,dexx,depsvxx,depsvxy,depsvxz,dp
64 my_real, DIMENSION(NEL) :: bulk,g_ins,g_inf,ge,ge2,gv,gv2,beta,c1,c2,
65 . epspxx,epspxy,epspxz
66C=======================================================================
67!! SHFACT = FIVE_OVER_6
68c
69 iadbuf = ipm(7,imat)-1
70 DO i=1,nel
71 bulk(i) = uparam(iadbuf+1)
72 g_ins(i) = uparam(iadbuf+2)
73 g_inf(i) = uparam(iadbuf+3)
74 beta(i) = uparam(iadbuf+4)
75 ENDDO
76c
77 ge(1:nel) = g_inf(1:nel) ! elastic part of shear modulus
78 gv(1:nel) = g_ins(1:nel) - g_inf(1:nel) ! viscous part of shear modulus
79 ge2(1:nel) = ge(1:nel) * two
80 gv2(1:nel) = gv(1:nel) * two
81 c1(1:nel) = one - exp(-beta(1:nel)*timestep)
82 c2(1:nel) =-c1(1:nel) / beta(1:nel)
83 epspxx(1:nel) = depsxx(1:nel)/max(em20,timestep)
84 epspxy(1:nel) = depsxy(1:nel)/max(em20,timestep)
85 epspxz(1:nel) = depsxz(1:nel)/max(em20,timestep)
86c
87 DO i=1,nel
88 ddexx = two_third*depsxx(i)
89 ddexy = depsxy(i)
90 ddexz = depsxz(i)
91
92 depsdxx = two_third*epspxx(i)
93 dexx = two_third*epsxx(i)
94 !
95 depsvxx = c1(i)*(dexx - uvar(i,1)) + c2(i)*depsdxx
96 depsvxy = c1(i)*(epsxy(i) - uvar(i,2)) + c2(i)*epspxy(i)
97 depsvxz = c1(i)*(epsxz(i) - uvar(i,3)) + c2(i)*epspxz(i)
98 dp = bulk(i)*depsxx(i)
99 !!
100 signxx(i) = sigoxx(i) + ge2(i)*ddexx - gv2(i)*depsvxx + dp
101 signxy(i) = sigoxy(i) + ge(i) *ddexy - gv(i) *depsvxy
102 signxz(i) = sigoxz(i) + ge(i) *ddexz - gv(i) *depsvxz
103
104 uvar(i,1) = uvar(i,1) + depsvxx + ddexx
105 uvar(i,2) = uvar(i,2) + depsvxy + ddexy
106 uvar(i,3) = uvar(i,3) + depsvxz + ddexz
107c
108 END DO
109c-----------
110 RETURN
111 END
#define max(a, b)
Definition macros.h:21
subroutine sigeps34pi(nel, nuparam, uparam, ipm, imat, nuvar, uvar, depsxx, depsxy, depsxz, epsxx, sigoxx, sigoxy, sigoxz, signxx, signxy, signxz, timestep, epsxy, epsxz)
Definition sigeps34pi.F:34