OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
mmodul24c.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!|| mmodul24c ../engine/source/elements/solid/solidez/mmodul24c.F
25!||--- called by ------------------------------------------------------
26!|| mdama24 ../engine/source/elements/solid/solidez/mdama24.F
27!||====================================================================
28 SUBROUTINE mmodul24c(NEL ,PM ,DAM ,CRAK ,
29 . CDAM ,G3 ,ANG ,DAMANG ,NBDAMA)
30C-----------------------------------------------
31C I m p l i c i t T y p e s
32C-----------------------------------------------
33#include "implicit_f.inc"
34C-----------------------------------------------
35C C o m m o n B l o c k s
36C-----------------------------------------------
37#include "mvsiz_p.inc"
38#include "param_c.inc"
39C-----------------------------------------------
40C D u m m y A r g u m e n t s
41C-----------------------------------------------
42 INTEGER NEL,NBDAMA
43 my_real pm(npropm)
44 my_real, DIMENSION(NEL,3) ,INTENT(IN):: dam,crak
45 my_real, DIMENSION(NEL,6) ,INTENT(IN):: ang
46 my_real, DIMENSION(MVSIZ,3,3) ,INTENT(OUT):: cdam
47 my_real, DIMENSION(MVSIZ,3) ,INTENT(OUT):: g3
48 my_real, DIMENSION(MVSIZ,6) ,INTENT(OUT):: damang
49C-----------------------------------------------
50C L o c a l V a r i a b l e s
51C-----------------------------------------------
52 INTEGER I,K,NBDAMA0
53 INTEGER, DIMENSION(NEL) :: DAMAI,DAMA0I
54 my_real young,nu,g,a11,a12,de1,de2,de3,de4,de5,de6,den,
55 . scal1,scal2,scal3,d_max
56C=======================================================================
57c DEi = (1 - DAMi) coefficients d endommagement de la matrice Hook
58c-----------------------------------------------------------------------
59 young = pm(20)
60 nu = pm(21)
61 g = pm(22)
62 a11 = pm(24)
63 a12 = pm(25)
64c
65c test of damaged elements
66c
67 nbdama = 0
68 nbdama0 = 0
69 d_max=zero
70 DO i = 1,nel
71 IF (dam(i,1) + dam(i,2) + dam(i,3) > zero) THEN
72 nbdama = nbdama + 1
73 damai(nbdama)=i
74 d_max =max(d_max,dam(i,1),dam(i,2),dam(i,3))
75 ELSE
76 nbdama0 = nbdama0 + 1
77 dama0i(nbdama0)=i
78 ENDIF
79 ENDDO
80c-----------------------------------------------------------
81c DAMAGED ELEMENT GROUP => modified Hook matrix
82c-----------------------------------------------------------
83 DO k=1,nbdama
84 i = damai(k)
85c
86 de1 = one - max( zero , sign(dam(i,1),crak(i,1)) )
87 de2 = one - max( zero , sign(dam(i,2),crak(i,2)) )
88 de3 = one - max( zero , sign(dam(i,3),crak(i,3)) )
89 scal1= half + sign(half,de1-one)
90 scal2= half + sign(half,de2-one)
91 scal3= half + sign(half,de3-one)
92 de4 = scal1*scal2
93 de5 = scal2*scal3
94 de6 = scal3*scal1
95c
96c NOUVELLE MATRICE ELASTIQUE DE HOOKE ENDOMMAGEE
97c
98 den = one - nu**2 *(de4 + de5 + de6
99 . + two*nu*scal1*scal2*scal3)
100C
101 cdam(i,1,1) = young*de1*(one - nu**2*de5)/den
102 cdam(i,2,2) = young*de2*(one - nu**2*de6)/den
103 cdam(i,3,3) = young*de3*(one - nu**2*de4)/den
104 cdam(i,1,2) = nu*young*de4 *(one + nu*scal3)/den
105 cdam(i,1,3) = nu*young*de6 *(one + nu*scal2)/den
106 cdam(i,2,3) = nu*young*de5 *(one + nu*scal1)/den
107 cdam(i,2,1) = cdam(i,1,2)
108 cdam(i,3,1) = cdam(i,1,3)
109 cdam(i,3,2) = cdam(i,2,3)
110c
111 g3(i,1) = g*de4
112 g3(i,2) = g*de5
113 g3(i,3) = g*de6
114 damang(i,1:6) = ang(i,1:6)
115 ENDDO
116c------------------------------------------------------------------------
117c NON DAMAGED ELEMENT GROUP => initial Hook matrix
118c------------------------------------------------------------------------
119 DO k=1,nbdama0
120 i = dama0i(k)
121 cdam(i,1,1) = a11
122 cdam(i,2,2) = a11
123 cdam(i,3,3) = a11
124 cdam(i,1,2) = a12
125 cdam(i,2,1) = a12
126 cdam(i,1,3) = a12
127 cdam(i,3,1) = a12
128 cdam(i,2,3) = a12
129 cdam(i,3,2) = a12
130 g3(i,1:3) = g
131 damang(i,1) = one
132 damang(i,2) = zero
133 damang(i,3) = zero
134 damang(i,4) = zero
135 damang(i,5) = one
136 damang(i,6) = zero
137 ENDDO
138c-----------
139 RETURN
140 END
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21
subroutine mmodul24c(nel, pm, dam, crak, cdam, g3, ang, damang, nbdama)
Definition mmodul24c.F:30