Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
v3d4_NeoHookeanInCompress.f90
Go to the documentation of this file.
1 !*********************************************************************
2 !* Illinois Open Source License *
3 !* *
4 !* University of Illinois/NCSA *
5 !* Open Source License *
6 !* *
7 !* Copyright@2008, University of Illinois. All rights reserved. *
8 !* *
9 !* Developed by: *
10 !* *
11 !* Center for Simulation of Advanced Rockets *
12 !* *
13 !* University of Illinois *
14 !* *
15 !* www.csar.uiuc.edu *
16 !* *
17 !* Permission is hereby granted, free of charge, to any person *
18 !* obtaining a copy of this software and associated documentation *
19 !* files (the "Software"), to deal with the Software without *
20 !* restriction, including without limitation the rights to use, *
21 !* copy, modify, merge, publish, distribute, sublicense, and/or *
22 !* sell copies of the Software, and to permit persons to whom the *
23 !* Software is furnished to do so, subject to the following *
24 !* conditions: *
25 !* *
26 !* *
27 !* @ Redistributions of source code must retain the above copyright *
28 !* notice, this list of conditions and the following disclaimers. *
29 !* *
30 !* @ Redistributions in binary form must reproduce the above *
31 !* copyright notice, this list of conditions and the following *
32 !* disclaimers in the documentation and/or other materials *
33 !* provided with the distribution. *
34 !* *
35 !* @ Neither the names of the Center for Simulation of Advanced *
36 !* Rockets, the University of Illinois, nor the names of its *
37 !* contributors may be used to endorse or promote products derived *
38 !* from this Software without specific prior written permission. *
39 !* *
40 !* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
41 !* EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
42 !* OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
43 !* NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
44 !* COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
45 !* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
46 !* ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
47 !* USE OR OTHER DEALINGS WITH THE SOFTWARE. *
48 !*********************************************************************
49 !* Please acknowledge The University of Illinois Center for *
50 !* Simulation of Advanced Rockets in works and publications *
51 !* resulting from this software or its derivatives. *
52 !*********************************************************************
53 SUBROUTINE v3d4_neohookeanincompress(coor,matcstet,lmcstet,R_in,d, &
54  s11,s22,s33,s12,s23,s13,&
55  numnp,nstart,nend,numcstet,numat_vol, &
56  xmu,xkappa)
57 
58 !________________________________________________________________________
59 !
60 ! V3D4 - Performs displacement based computations for Volumetric 3D
61 ! 4-node tetrahedra large deformation (i.e. nonlinear) elastic
62 ! elements with linear interpolation functions. (constant strain
63 ! tetrahedra). Returns the internal force vector R_in.
64 !
65 ! DATE: 04.2000 AUTHOR: SCOT BREITENFELD
66 !
67 ! Source:
68 ! "Nonlinear continuum mechanics for finite element analysis"
69 ! Javier Bonet and Richard D. Wood
70 ! ISBN 0-521-57272-X
71 
72 !________________________________________________________________________
73 
74  IMPLICIT NONE
75 !---- Global variables
76  INTEGER :: numnp ! number of nodal points
77  INTEGER :: numcstet ! number of CSTet elements
78  INTEGER :: numat_vol ! number of volumetric materials
79  INTEGER :: istrgss
80 !-- coordinate array
81  REAL*8, DIMENSION(1:3,1:numnp) :: coor
82 !-- internal force
83  REAL*8, DIMENSION(1:3*numnp) :: r_in
84 !-- displacement vector
85  REAL*8, DIMENSION(1:3*numnp) :: d
86 !-- CSTet stress
87  REAL*8, DIMENSION(1:numcstet) :: s11, s22, s33, s12, s23, s13
88 !-- x, y and z displacements of nodes
89  REAL*8 :: u1,u2,u3,u4,v1,v2,v3,v4,w1,w2,w3,w4
90 !-- coordinate holding variable
91  REAL*8 :: x1,x2,x3,x4,y1,y2,y3,y4,z1,z2,z3,z4
92 !-- coordinate holding variable
93  REAL*8 :: x1d,x2d,x3d,x4d,y1d,y2d,y3d,y4d,z1d,z2d,z3d,z4d
94 !-- Coordinate subtractions
95  REAL*8 :: x14, x24, x34, y14, y24, y34, z14, z24, z34
96 !-- 6*volume, inverse(6*volume), and the volume
97 ! REAL*8 :: Vx6, vol
98 !-- spacial derivatives
99  REAL*8 :: b1,b2,b3,b4,b5,b6,b7,b8,b9,b10,b11,b12
100 !-- partial derivatives of the displacement
101  REAL*8 :: dudx,dvdy,dwdz,dudy,dvdx,dvdz,dwdy,dudz,dwdx
102 !-- strains
103  REAL*8 :: e11,e22,e33,e12,e23,e13
104 ! -- connectivity table for CSTet
105  INTEGER, DIMENSION(1:4,1:numcstet) :: lmcstet
106 ! -- mat number for CST element
107  INTEGER, DIMENSION(1:numcstet) :: matcstet
108 ! -- node numbers
109  INTEGER :: n1,n2,n3,n4
110 ! -- dummy and counters
111  INTEGER :: i,j,nstart,nend
112  INTEGER :: k1n1,k1n2,k1n3,k1n4,k2n1,k2n2,k2n3,k2n4
113  INTEGER :: k3n1,k3n2,k3n3,k3n4
114 ! --
115  REAL*8 :: f11, f12, f13, f21, f22, f23, f31, f32, f33
116  REAL*8 :: j1,jsqrd,jsqrdinv
117  REAL*8 :: c11, c12, c13, c21, c22, c23, c31, c32, c33
118  REAL*8, DIMENSION(1:numat_vol) :: xmu,xkappa
119  REAL*8, DIMENSION(1:4,1:4) :: eledb
120  REAL*8,DIMENSION(1:3,1:3) :: xj
121  REAL*8,DIMENSION(1:3,1:3) :: xjv0
122  REAL*8 :: weight = 1.d0/6.d0
123  INTEGER :: id, jd, in, ip
124  REAL*8 :: xcoor
125  REAL*8 :: detjb,detjbv0,evol,theta,press
126  REAL*8 :: ic, iiic,vx6old0,vx6old
127  REAL*8 :: onethird = 1.d0/3.d0
128  REAL*8 :: val11, val21, val31
129 
130  REAL*8 :: v0x6, v0x6inv
131  REAL*8 :: vx6, vx6inv
132  REAL*8 :: vol, vol0
133  REAL*8 :: term1, term2, cinv
134 
135  DO i = nstart, nend
136  j = matcstet(i)
137 
138  n1 = lmcstet(1,i)
139  n2 = lmcstet(2,i)
140  n3 = lmcstet(3,i)
141  n4 = lmcstet(4,i)
142 
143  k3n1 = 3*n1
144  k3n2 = 3*n2
145  k3n3 = 3*n3
146  k3n4 = 3*n4
147 
148  k2n1 = k3n1 - 1
149  k2n2 = k3n2 - 1
150  k2n3 = k3n3 - 1
151  k2n4 = k3n4 - 1
152 
153  k1n1 = k3n1 - 2
154  k1n2 = k3n2 - 2
155  k1n3 = k3n3 - 2
156  k1n4 = k3n4 - 2
157  ! k#n# dummy variables replaces:
158  u1 = d(k1n1) ! (3*n1-2)
159  u2 = d(k1n2) ! (3*n2-2)
160  u3 = d(k1n3) ! (3*n3-2)
161  u4 = d(k1n4) ! (3*n4-2)
162  v1 = d(k2n1) ! (3*n1-1)
163  v2 = d(k2n2) ! (3*n2-1)
164  v3 = d(k2n3) ! (3*n3-1)
165  v4 = d(k2n4) ! (3*n4-1)
166  w1 = d(k3n1) ! (3*n1)
167  w2 = d(k3n2) ! (3*n2)
168  w3 = d(k3n3) ! (3*n3)
169  w4 = d(k3n4) ! (3*n4)
170 
171  x1 = coor(1,n1)
172  x2 = coor(1,n2)
173  x3 = coor(1,n3)
174  x4 = coor(1,n4)
175  y1 = coor(2,n1)
176  y2 = coor(2,n2)
177  y3 = coor(2,n3)
178  y4 = coor(2,n4)
179  z1 = coor(3,n1)
180  z2 = coor(3,n2)
181  z3 = coor(3,n3)
182  z4 = coor(3,n4)
183 
184  x1d = x1 + u1
185  x2d = x2 + u2
186  x3d = x3 + u3
187  x4d = x4 + u4
188  y1d = y1 + v1
189  y2d = y2 + v2
190  y3d = y3 + v3
191  y4d = y4 + v4
192  z1d = z1 + w1
193  z2d = z2 + w2
194  z3d = z3 + w3
195  z4d = z4 + w4
196 !
197 ! creates the Jacobian matrix using equation ???
198 ! Using undeformed coordinates
199 
200  x14 = x1 - x4
201  x24 = x2 - x4
202  x34 = x3 - x4
203  y14 = y1 - y4
204  y24 = y2 - y4
205  y34 = y3 - y4
206  z14 = z1 - z4
207  z24 = z2 - z4
208  z34 = z3 - z4
209 
210  val11 = y24*z34 - z24*y34
211  val21 = -( x24*z34 - z24*x34 )
212  val31 = x24*y34 - y24*x34
213 
214  v0x6 = -( x14*val11 + y14*val21 + z14*val31 )
215 !
216 ! creates the Jacobian matrix using equation ???
217 ! Determines the determinant of xj and checks for zero values
218 !
219 ! Using deformed coordinates
220 
221  x14 = x1d - x4d
222  x24 = x2d - x4d
223  x34 = x3d - x4d
224  y14 = y1d - y4d
225  y24 = y2d - y4d
226  y34 = y3d - y4d
227  z14 = z1d - z4d
228  z24 = z2d - z4d
229  z34 = z3d - z4d
230 
231  val11 = y24*z34 - z24*y34
232  val21 = -( x24*z34 - z24*x34 )
233  val31 = x24*y34 - y24*x34
234 
235  vx6 = -( x14*val11 + y14*val21 + z14*val31 )
236 
237  IF(vx6.LE.0.d0) THEN
238  WRITE(*,100) i
239  stop
240  ENDIF
241 
242 
243 ! calculate the volume
244 
245  vol0 = v0x6/6.d0
246  vol = vx6/6.d0
247 
248  v0x6inv = 1.d0/v0x6
249 
250 ! See the maple worksheet 'V3D4.mws' for the derivation of Vx6
251 
252 ! See the maple worksheet 'V3D4.mws' for the derivation of [B]
253 ! NOTE: Factored for a more equivalent/compact form then maple's
254 
255  b1 = ( (y3-y4)*(z2-z4) - (y2-y4)*(z3-z4) ) * v0x6inv
256  b2 = ( (z3-z4)*(x2-x4) - (z2-z4)*(x3-x4) ) * v0x6inv
257  b3 = ( (x3-x4)*(y2-y4) - (x2-x4)*(y3-y4) ) * v0x6inv
258  b4 = ( (y1-y3)*(z1-z4) - (y1-y4)*(z1-z3) ) * v0x6inv
259  b5 = ( (z1-z3)*(x1-x4) - (z1-z4)*(x1-x3) ) * v0x6inv
260  b6 = ( (x1-x3)*(y1-y4) - (x1-x4)*(y1-y3) ) * v0x6inv
261  b7 = ( (y1-y4)*(z1-z2) - (y1-y2)*(z1-z4) ) * v0x6inv
262  b8 = ( (z1-z4)*(x1-x2) - (z1-z2)*(x1-x4) ) * v0x6inv
263  b9 = ( (x1-x4)*(y1-y2) - (x1-x2)*(y1-y4) ) * v0x6inv
264  b10 = ( (y1-y2)*(z1-z3) - (y1-y3)*(z1-z2) ) * v0x6inv
265  b11 = ( (z1-z2)*(x1-x3) - (z1-z3)*(x1-x2) ) * v0x6inv
266  b12 = ( (x1-x2)*(y1-y3) - (x1-x3)*(y1-y2) ) * v0x6inv
267 !
268 ! deformation gradients F
269 !
270  f11 = 1.d0 + ( b1*u1 + b4*u2 + b7*u3 + b10*u4 ) ! 1 + ( dudx )
271  f22 = 1.d0 + ( b2*v1 + b5*v2 + b8*v3 + b11*v4 ) ! 1 + ( dvdy )
272  f33 = 1.d0 + ( b3*w1 + b6*w2 + b9*w3 + b12*w4 ) ! 1 + ( dwdz )
273  f12 = b2*u1 + b5*u2 + b8*u3 + b11*u4 ! dudy
274  f21 = b1*v1 + b4*v2 + b7*v3 + b10*v4 ! dvdx
275  f23 = b3*v1 + b6*v2 + b9*v3 + b12*v4 ! dvdz
276  f32 = b2*w1 + b5*w2 + b8*w3 + b11*w4 ! dwdy
277  f13 = b3*u1 + b6*u2 + b9*u3 + b12*u4 ! dudz
278  f31 = b1*w1 + b4*w2 + b7*w3 + b10*w4 ! dwdx
279 
280  theta = vol/vol0
281 
282  press = xkappa(j)*(theta-1.d0)
283 
284  j1 = f11*(f22*f33-f23*f32)+f12*(f31*f23-f21*f33)+f13*(-f31*f22+f21*f32)
285  IF(j1.LE.0.d0) THEN
286  WRITE(*,*)'Volume has become zero for element',i
287  stop
288  ENDIF
289  jsqrd = j1*j1
290 
291 ! first invariant of C
292 
293  ic = f11**2+f21**2+f31**2+f12**2+f22**2+f32**2+f13**2+f23**2+f33**2
294 
295 ! Third invariant of C
296 
297  iiic = jsqrd
298 
299 ! T
300 ! C = F F = right Cauchy-Green deformation tensor
301 !
302  c11 = (f11*f11+f21*f21+f31*f31)
303  c12 = (f11*f12+f21*f22+f31*f32)
304  c13 = (f11*f13+f21*f23+f31*f33)
305  c21 = c12
306  c22 = (f12*f12+f22*f22+f32*f32)
307  c23 = (f12*f13+f22*f23+f32*f33)
308  c31 = c13
309  c32 = c23
310  c33 = (f13*f13+f23*f23+f33*f33)
311 !
312 ! Second Piola-Kirchoff tensor
313 ! Eq. (5.28), pg. 124
314 
315  jsqrdinv = 1.d0/jsqrd
316 
317  term1 = xmu(j)*iiic**(-onethird)
318  term2 = press*j1
319 
320  cinv = (c22*c33-c23*c32)*jsqrdinv
321  s11(i) = term1*(1.d0-onethird*ic*cinv) + term2*cinv
322  cinv = (c11*c33-c31*c13)*jsqrdinv
323  s22(i) = term1*(1.d0-onethird*ic*cinv) + term2*cinv
324  cinv = (c11*c22-c12*c21)*jsqrdinv
325  s33(i) = term1*(1.d0-onethird*ic*cinv) + term2*cinv
326  cinv = (-c12*c33+c13*c32)*jsqrdinv
327  s12(i) = cinv*(-term1*onethird*ic + term2)
328  cinv = (-c11*c23+c13*c21)*jsqrdinv
329  s23(i) = cinv*(-term1*onethird*ic + term2)
330  cinv = ( c12*c23-c13*c22)*jsqrdinv
331  s13(i) = cinv*(-term1*onethird*ic + term2)
332 
333 ! ASSEMBLE THE INTERNAL FORCE VECTOR
334 !
335 ! local node 1
336 
337  r_in(k1n1) = r_in(k1n1) - vol0* &
338  ( s11(i)*b1*f11 + s22(i)*b2*f12 + s33(i)*b3*f13 &
339  + s12(i)*( b2*f11 + b1*f12 ) &
340  + s23(i)*( b3*f12 + b2*f13 ) &
341  + s13(i)*( b3*f11 + b1*f13 ) )
342  r_in(k2n1) = r_in(k2n1) - vol0* &
343  ( s11(i)*b1*f21 + s22(i)*b2*f22 + s33(i)*b3*f23 &
344  + s12(i)*( b1*f22 + b2*f21 ) &
345  + s23(i)*( b3*f22 + b2*f23 ) &
346  + s13(i)*( b3*f21 + b1*f23 ) )
347  r_in(k3n1) = r_in(k3n1) - vol0* &
348  ( s11(i)*b1*f31 + s22(i)*b2*f32 + s33(i)*b3*f33 &
349  + s12(i)*( b2*f31 + b1*f32 ) &
350  + s23(i)*( b3*f32 + b2*f33 ) &
351  + s13(i)*( b3*f31 + b1*f33 ) )
352 ! local node 2
353  r_in(k1n2) = r_in(k1n2) - vol0* &
354  ( s11(i)*b4*f11 + s22(i)*b5*f12 + s33(i)*b6*f13 &
355  + s12(i)*( b5*f11 + b4*f12 ) &
356  + s23(i)*( b6*f12 + b5*f13 ) &
357  + s13(i)*( b6*f11 + b4*f13 ) )
358  r_in(k2n2) = r_in(k2n2) - vol0* &
359  ( s11(i)*b4*f21 + s22(i)*b5*f22 + s33(i)*b6*f23 &
360  + s12(i)*( b4*f22 + b5*f21 ) &
361  + s23(i)*( b6*f22 + b5*f23 ) &
362  + s13(i)*( b6*f21 + b4*f23 ) )
363  r_in(k3n2) = r_in(k3n2) - vol0* &
364  ( s11(i)*b4*f31 + s22(i)*b5*f32 + s33(i)*b6*f33 &
365  + s12(i)*( b5*f31 + b4*f32 ) &
366  + s23(i)*( b6*f32 + b5*f33 ) &
367  + s13(i)*( b6*f31 + b4*f33 ) )
368 ! local node 3
369  r_in(k1n3) = r_in(k1n3) - vol0* &
370  ( s11(i)*b7*f11 + s22(i)*b8*f12 + s33(i)*b9*f13 &
371  + s12(i)*( b8*f11 + b7*f12 ) &
372  + s23(i)*( b9*f12 + b8*f13 ) &
373  + s13(i)*( b9*f11 + b7*f13 ) )
374  r_in(k2n3) = r_in(k2n3) - vol0* &
375  ( s11(i)*b7*f21 + s22(i)*b8*f22 + s33(i)*b9*f23 &
376  + s12(i)*( b7*f22 + b8*f21 ) &
377  + s23(i)*( b9*f22 + b8*f23 ) &
378  + s13(i)*( b9*f21 + b7*f23 ) )
379  r_in(k3n3) = r_in(k3n3) - vol0* &
380  ( s11(i)*b7*f31 + s22(i)*b8*f32 + s33(i)*b9*f33 &
381  + s12(i)*( b8*f31 + b7*f32 ) &
382  + s23(i)*( b9*f32 + b8*f33 ) &
383  + s13(i)*( b9*f31 + b7*f33 ) )
384 ! local node 4
385  r_in(k1n4) = r_in(k1n4) - vol0* &
386  ( s11(i)*b10*f11 + s22(i)*b11*f12+s33(i)*b12*f13 &
387  + s12(i)*( b11*f11 + b10*f12 ) &
388  + s23(i)*( b12*f12 + b11*f13 ) &
389  + s13(i)*( b12*f11 + b10*f13 ) )
390  r_in(k2n4) = r_in(k2n4) - vol0* &
391  ( s11(i)*b10*f21 + s22(i)*b11*f22 + s33(i)*b12*f23 &
392  + s12(i)*( b10*f22 + b11*f21 ) &
393  + s23(i)*( b12*f22 + b11*f23 ) &
394  + s13(i)*( b12*f21 + b10*f23 ) )
395  r_in(k3n4) = r_in(k3n4) - vol0* &
396  ( s11(i)*b10*f31 + s22(i)*b11*f32 + s33(i)*b12*f33 &
397  + s12(i)*( b11*f31 + b10*f32 ) &
398  + s23(i)*( b12*f32 + b11*f33 ) &
399  + s13(i)*( b12*f31 + b10*f33 ) )
400  ENDDO
401 
402  RETURN
403 
404 100 FORMAT(' Negative Jacobian for element: ',i10)
405 END SUBROUTINE v3d4_neohookeanincompress
406 
const NT & d
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE ic
subroutine v3d4_neohookeanincompress(coor, matcstet, lmcstet, R_in, d, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol, xmu, xkappa)
blockLoc i
Definition: read.cpp:79
j indices j
Definition: Indexing.h:6
unsigned long id(const Leda_like_handle &x)
Definition: Handle.h:107