OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sigeps102.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!|| sigeps102 ../engine/source/materials/mat/mat102/sigeps102.F
25!||--- called by ------------------------------------------------------
26!|| mulaw ../engine/source/materials/mat_share/mulaw.F90
27!||====================================================================
28 SUBROUTINE sigeps102(
29 1 NEL , NUPARAM, NUVAR , UPARAM , RHO0 , RHO ,
30 2 DEPSXX , DEPSYY , DEPSZZ , DEPSXY , DEPSYZ , DEPSZX ,
31 3 SIGOXX , SIGOYY , SIGOZZ , SIGOXY , SIGOYZ , SIGOZX ,
32 4 SIGNXX , SIGNYY , SIGNZZ , SIGNXY , SIGNYZ , SIGNZX ,
33 5 SOUNDSP, UVAR , OFF , ET ,
34 6 PSH , PNEW , DPDM , SSP , PLA )
35C-----------------------------------------------
36C I M P L I C I T T Y P E S
37C-----------------------------------------------
38#include "implicit_f.inc"
39C----------------------------------------------------------------
40C I N P U T A R G U M E N T S
41C----------------------------------------------------------------
42 INTEGER NEL,NVARF,NUPARAM,NUVAR
43 my_real :: TIME,TIMESTEP
44 my_real :: UPARAM(NUPARAM)
45 my_real ,DIMENSION(NEL) :: RHO, RHO0,
46 . DEPSXX, DEPSYY, DEPSZZ, DEPSXY, DEPSYZ, DEPSZX,
47 . SIGOXX, SIGOYY, SIGOZZ, SIGOXY, SIGOYZ, SIGOZX,
48 . ssp , dpdm , pnew, psh, pla
49C----------------------------------------------------------------
50C O U T P U T A R G U M E N T S
51C----------------------------------------------------------------
52 my_real
53 . signxx(nel), signyy(nel), signzz(nel),
54 . signxy(nel), signyz(nel), signzx(nel),
55 . soundsp(nel), et(nel)
56C----------------------------------------------------------------
57C I N P U T O U T P U T A R G U M E N T S
58C----------------------------------------------------------------
59 my_real
60 . uvar(nel,nuvar), off(nel) ,mu(nel),mu2(nel)
61C----------------------------------------------------------------
62C L O C A L V A R I B L E S
63C----------------------------------------------------------------
64 my_real :: a0,a1,a2,amax
65 my_real :: dav,pold(nel)
66 my_real :: t1(nel),t2(nel),t3(nel),t4(nel),t5(nel),t6(nel)
67 my_real :: ptot,g0(nel),ratio(nel),yield2(nel)
68 my_real :: pstar,g,gg,scrt(nel),aj2(nel),dpla(nel)
69 my_real :: i3(nel),cos3t(nel),sqrt_j2,theta,c,phi,k
70 integer :: I,IFORM
71C----------------------------------------------------------------
72C S o u r c e L i n e s
73C----------------------------------------------------------------
74 c = uparam(1)
75 phi = uparam(2)
76 pstar = uparam(3)
77 a0 = uparam(4)
78 a1 = uparam(5)
79 a2 = uparam(6)
80 amax = uparam(7)
81 g = uparam(8)
82 gg = two*g
83 iform = nint(uparam(9))
84 !----------------------------------------------------------------!
85 ! STATE INIT. !
86 !----------------------------------------------------------------!
87 DO i=1,nel
88 pold(i) = -(sigoxx(i)+sigoyy(i)+sigozz(i))*third
89 scrt(i) = (depsxx(i)+depsyy(i)+depszz(i))*third
90 mu(i) = rho(i)/rho0(i) - one
91 mu2(i) = mu(i) * max(zero,mu(i))
92 ENDDO !next I
93 !----------------------------------------------------------------!
94 ! TEMPORARY DEVIATORIC STRESS TENSOR : T(1:6) !
95 !----------------------------------------------------------------!
96 DO i=1,nel
97 t1(i)=sigoxx(i)+pold(i)+gg*(depsxx(i)-scrt(i))
98 t2(i)=sigoyy(i)+pold(i)+gg*(depsyy(i)-scrt(i))
99 t3(i)=sigozz(i)+pold(i)+gg*(depszz(i)-scrt(i))
100 t4(i)=sigoxy(i) + g*depsxy(i)
101 t5(i)=sigoyz(i) + g*depsyz(i)
102 t6(i)=sigozx(i) + g*depszx(i)
103 ENDDO !next I
104 !----------------------------------------------------------------!
105 ! SOUND SPEED !
106 !----------------------------------------------------------------!
107 DO i=1,nel
108 dpdm(i) = dpdm(i) + onep333*g
109 ssp(i) = sqrt(abs(dpdm(i))/rho0(i))
110 ENDDO !next I
111 !----------------------------------------------------------------!
112 ! YIELD SURFACE !
113 !----------------------------------------------------------------!
114 DO i=1,nel
115 aj2(i)= half*(t1(i)**2+t2(i)**2+t3(i)**2)+t4(i)**2+t5(i)**2+t6(i)**2
116 ENDDO
117 !----SUBCASE --- ORIGINAL MOHR COULOMB
118 IF(iform==4)THEN
119 k = one/sqrt(three)
120 DO i=1,nel
121 i3(i) = t2(i)*t3(i)*t1(i)-t2(i)*t6(i)*t6(i)-t3(i)*t4(i)*t4(i)-t5(i)*t5(i)*t1(i)+2*t5(i)*t4(i)*t6(i)
122 sqrt_j2 = sqrt(aj2(i))
123 cos3t(i) = nine*i3(i)/two/sqrt(three)/sqrt_j2/sqrt_j2/sqrt_j2
124 theta = acos(max(zero,min(one,cos3t(i))))
125 ptot = pnew(i)+psh(i)
126 g0(i) = -ptot*sin(phi)+sqrt_j2*(cos(theta)-k*sin(theta)*sin(phi))-c*cos(phi)
127 g0(i) = max(zero,g0(i))
128 yield2(i)= aj2(i)-g0(i)
129 ENDDO
130 !----SUBCASE --- FITTED DRUCKER PRAGER FROM MOHR COULOMB PARAMETERS (A0,A1,A2 CALCULATED DURING STARTER)
131 ELSE
132 DO i=1,nel
133 ptot = pnew(i)+psh(i)
134 g0(i) = a0 +a1 *ptot+a2 *ptot*ptot
135 g0(i) = min(amax,g0(i))
136 g0(i) = max(zero,g0(i))
137 IF(ptot <= pstar)g0(i)=zero
138 yield2(i)=aj2(i)-g0(i)
139 ENDDO !next I
140 ENDIF
141
142 !----------------------------------------------------------------!
143 ! PROJECTION FACTOR ON YIELD SURFACE !
144 !----------------------------------------------------------------!
145 DO i=1,nel
146 ratio(i)=zero
147 IF(yield2(i)<=zero .AND. g0(i)>zero)THEN
148 ratio(i)=one
149 ELSE
150 ratio(i)=sqrt(g0(i)/(aj2(i)+ em14))
151 ENDIF
152 ENDDO !next I
153 !----------------------------------------------------------------!
154 ! UPDATE DEVIATORIC STRESS TENSOR IN SIG(:,:) !
155 !----------------------------------------------------------------!
156 DO i=1,nel
157 signxx(i)=ratio(i)*t1(i)*off(i) - pnew(i)
158 signyy(i)=ratio(i)*t2(i)*off(i) - pnew(i)
159 signzz(i)=ratio(i)*t3(i)*off(i) - pnew(i)
160 signxy(i)=ratio(i)*t4(i)*off(i)
161 signyz(i)=ratio(i)*t5(i)*off(i)
162 signzx(i)=ratio(i)*t6(i)*off(i)
163 dpla(i) =(one -ratio(i))*sqrt(aj2(i)) / max(em20,three*g)
164 ENDDO !next I
165 pla(1:nel) = pla(1:nel) + dpla(1:nel)
166c-----------
167 RETURN
168 END
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
subroutine sigeps102(nel, nuparam, nuvar, uparam, rho0, rho, depsxx, depsyy, depszz, depsxy, depsyz, depszx, sigoxx, sigoyy, sigozz, sigoxy, sigoyz, sigozx, signxx, signyy, signzz, signxy, signyz, signzx, soundsp, uvar, off, et, psh, pnew, dpdm, ssp, pla)
Definition sigeps102.F:35