OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
shell_reactivation.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!|| shell_reactivation ../engine/source/tools/seatbelts/shell_reactivation.F
25!||--- called by ------------------------------------------------------
26!|| update_slipring ../engine/source/tools/seatbelts/update_slipring.F
27!||--- calls -----------------------------------------------------
28!|| hencky_strain ../engine/source/tools/seatbelts/shell_reactivation.F
29!||====================================================================
30 SUBROUTINE shell_reactivation(I,II,L0FRAM1,L0FRAM2,NODE_FRAM1,
31 . NODE_FRAM2,GSTR,NEL,XL2,YL2,
32 . XL3,YL3,XL4,YL4,OFFSET,
33 . N_DIR2,DIRA_X,DIRA_Y,SMSTR,ISMSTR,
34 . L_SMSTR,ORIENT)
35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39C-----------------------------------------------
40C D u m m y A r g u m e n t s
41C-----------------------------------------------
42 INTEGER, INTENT(IN) :: I,NODE_FRAM1,NODE_FRAM2,II(6),NEL,ISMSTR,L_SMSTR,ORIENT
43 my_real, INTENT(IN) :: L0FRAM1,L0FRAM2,XL2,YL2,XL3,YL3,XL4,YL4,OFFSET,N_DIR2(2)
44 my_real, INTENT(INOUT) :: GSTR(NEL,8),DIRA_X,DIRA_Y
45 DOUBLE PRECISION, INTENT(INOUT) :: SMSTR(L_SMSTR*NEL)
46C-----------------------------------------------
47C L o c a l V a r i a b l e s
48C-----------------------------------------------
49 INTEGER NODE_FRAM_S,NODE_CORES_DIR1(4)
50 my_real
51 . XLL(4),YLL(4),DIST,AREA0,FF(2,2),HH(2,2),
52 . UX13,UX24,UY13,UY24,PX1B,PX2B,PY1B,PY2B,VEC(2),N_DIR1(2)
53C---------------------------------------------------------
54C
55C---------------------------------------------------------
56C Computation of DIR1
57C---------------------------------------------------------
58C
59 IF (orient == 1) THEN
60 node_cores_dir1(1) = 2
61 node_cores_dir1(2) = 1
62 node_cores_dir1(3) = 4
63 node_cores_dir1(4) = 3
64 ELSE
65 node_cores_dir1(1) = 4
66 node_cores_dir1(2) = 3
67 node_cores_dir1(3) = 2
68 node_cores_dir1(4) = 1
69 ENDIF
70C
71 xll(1) = zero
72 xll(2) = xl2
73 xll(3) = xl3
74 xll(4) = xl4
75 yll(1) = zero
76 yll(2) = yl2
77 yll(3) = yl3
78 yll(4) = yl4
79C
80 node_fram_s = node_cores_dir1(node_fram1)
81 vec(1) = xll(node_fram_s)-xll(node_fram1)
82 vec(2) = yll(node_fram_s)-yll(node_fram1)
83 dist = sqrt(vec(1)**2+vec(2)**2)
84 n_dir1(1) = vec(1)/(dist*two)
85 n_dir1(2) = vec(2)/(dist*two)
86C
87 node_fram_s = node_cores_dir1(node_fram2)
88 vec(1) = xll(node_fram_s)-xll(node_fram2)
89 vec(2) = yll(node_fram_s)-yll(node_fram2)
90 dist = sqrt(vec(1)**2+vec(2)**2)
91 n_dir1(1) = n_dir1(1) + vec(1)/(dist*two)
92 n_dir1(2) = n_dir1(2) + vec(2)/(dist*two)
93C
94C---------------------------------------------------------
95C Computation of new reference configuration
96C---------------------------------------------------------
97C
98C-- first fram released from sliring - node_fram_s moved in ref configuration
99 node_fram_s = node_cores_dir1(node_fram1)
100 xll(node_fram1) = offset*n_dir1(1)
101 yll(node_fram1) = offset*n_dir1(2)
102 xll(node_fram_s) = xll(node_fram1) + l0fram1*n_dir1(1)
103 yll(node_fram_s) = yll(node_fram1) + l0fram1*n_dir1(2)
104C
105C-- second fram released from sliring - node_fram_s moved in ref configuration
106 node_fram_s = node_cores_dir1(node_fram2)
107 xll(node_fram2) = n_dir2(1)
108 yll(node_fram2) = n_dir2(2)
109 xll(node_fram_s) = xll(node_fram2) + l0fram2*n_dir1(1)
110 yll(node_fram_s) = yll(node_fram2) + l0fram2*n_dir1(2)
111
112C-- origin reset to N1
113 xll(2) = xll(2)-xll(1)
114 xll(3) = xll(3)-xll(1)
115 xll(4) = xll(4)-xll(1)
116 yll(2) = yll(2)-yll(1)
117 yll(3) = yll(3)-yll(1)
118 yll(4) = yll(4)-yll(1)
119
120C-- update of orthotropy directions
121 dira_x = n_dir1(1)
122 dira_y = n_dir1(2)
123C
124C---------------------------------------------------------
125C Computation of true strain (Hencky) HH = LOG(SQRT(FT*F))
126C---------------------------------------------------------
127C
128 IF (ismstr /= 11) THEN
129C
130 ux13=-xl3
131 ux24=xl2-xl4
132 uy13=-yl3
133 uy24=yl2-yl4
134C
135 px1b = (yll(2)-yll(4))*half
136 py1b = (xll(4)-xll(2))*half
137 px2b = yll(3)*half
138 py2b = -xll(3)*half
139 area0 = half*((xll(2)-xll(4))*yll(3)-xll(3)*(yll(2)-yll(4)))
140C
141C-- Matrix F (gradient transformation)
142 ff(1,1)=(px1b*ux13+px2b*ux24)/area0
143 ff(2,2)=(py1b*uy13+py2b*uy24)/area0
144 ff(1,2)=(py1b*ux13+py2b*ux24)/area0
145 ff(2,1)=(px1b*uy13+px2b*uy24)/area0
146
147C-- computation of LOG(SQRT(FT*F))
148 CALL hencky_strain(ff,hh)
149C
150 gstr(i,1)=hh(1,1)
151 gstr(i,2)=hh(2,2)
152 gstr(i,3)=hh(1,2)*two
153 gstr(i,4)=zero
154 gstr(i,5)=zero
155 gstr(i,6)=zero
156 gstr(i,7)=zero
157 gstr(i,8)=zero
158C
159 ELSE
160C
161 smstr(ii(1)+i-1)=xll(2)
162 smstr(ii(2)+i-1)=yll(2)
163 smstr(ii(3)+i-1)=xll(3)
164 smstr(ii(4)+i-1)=yll(3)
165 smstr(ii(5)+i-1)=xll(4)
166 smstr(ii(6)+i-1)=yll(4)
167C
168 ENDIF
169C
170C----------------------------------------------------------
171C----------------------------------------------------------
172C----------------------------------------------------------
173C----------------------------------------------------------
174 RETURN
175C
176 END
177C
178!||====================================================================
179!|| hencky_strain ../engine/source/tools/seatbelts/shell_reactivation.F
180!||--- called by ------------------------------------------------------
181!|| shell_reactivation ../engine/source/tools/seatbelts/shell_reactivation.F
182!||--- calls -----------------------------------------------------
183!|| jacobiew ../engine/source/materials/mat/mat033/sigeps33.F
184!||====================================================================
185 SUBROUTINE hencky_strain(FF,HH)
186C-----------------------------------------------
187C I m p l i c i t T y p e s
188C-----------------------------------------------
189#include "implicit_f.inc"
190C-----------------------------------------------
191C D u m m y A r g u m e n t s
192C-----------------------------------------------
193 my_real, INTENT(IN) :: ff(2,2)
194 my_real, INTENT(OUT) :: hh(2,2)
195C-----------------------------------------------
196C L o c a l V a r i a b l e s
197C-----------------------------------------------
198 INTEGER I,J,K,NROT
199 my_real FTF(2,2),FTF_VAL(2),FTF_VEC(2,2),HHB(2,2)
200C------------------------------------------------
201C
202 ftf(1,1) = ff(1,1)**2 + ff(2,1)**2
203 ftf(2,2) = ff(2,2)**2 + ff(1,2)**2
204 ftf(1,2) = ff(1,1)*ff(1,2) + ff(2,1)*ff(2,2)
205 ftf(2,1) = ff(1,1)*ff(1,2) + ff(2,1)*ff(2,2)
206C
207 CALL jacobiew(ftf,2,ftf_val,ftf_vec,nrot)
208C
209 ftf_val(1) = log(sqrt(ftf_val(1)))
210 ftf_val(2) = log(sqrt(ftf_val(2)))
211C
212 hh = zero
213 hhb = zero
214C
215 DO i=1,2
216 DO j=1,2
217 hhb(i,j) = hhb(i,j) + ftf_vec(i,j) * ftf_val(j)
218 ENDDO
219 ENDDO
220C
221 DO i=1,2
222 DO j=1,2
223 DO k=1,2
224 hh(i,j) = hh(i,j) + hhb(i,k) * ftf_vec(j,k)
225 ENDDO
226 ENDDO
227 ENDDO
228C
229 RETURN
230 END
#define my_real
Definition cppsort.cpp:32
subroutine jacobiew(a, n, ew, ev, nrot)
Definition matrix.F:29
subroutine hencky_strain(ff, hh)
subroutine shell_reactivation(i, ii, l0fram1, l0fram2, node_fram1, node_fram2, gstr, nel, xl2, yl2, xl3, yl3, xl4, yl4, offset, n_dir2, dira_x, dira_y, smstr, ismstr, l_smstr, orient)