Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
FluidPressLoad.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 fluidpressload(NumNP,R_ex, &
54  interfacesfnumelems, interfacesfnumnodes, &
55  interfacesfelemconn, &
56  mapnodesf,lwrbnd,uppbnd, coor, disp, mapsfelvolel,&
57  elconnvol,ieltype,numelvol,tractpress )
58 
59  IMPLICIT NONE
60 
61 !!****f* Rocfrac/Rocfrac/Source/FluidPressLoad.f90
62 !!
63 !! NAME
64 !! FluidPressLoad
65 !!
66 !! FUNCTION
67 !!
68 !! Transforms the pressure given in the deformed state to
69 !! the undeformed configuration. This subroutine is for
70 !! the formulation where all quantities are with respect to
71 !! the undeformed configuration. Assumes the
72 !! pressure (tractions) are constant over the surface of
73 !! the triangle.
74 !!
75 !! 1-3 for 4 node tet (i.e. 3 node triangles)
76 !! 4-6 for 10 node tet (i.e. 6 node triangles, mid-side nodes get traction)
77 !!
78 !!****
79 
80 
81  INTEGER :: numnp ! number of nodes
82  INTEGER :: lwrbnd,uppbnd
83 
84  INTEGER :: ieltype,numelvol
85  INTEGER, DIMENSION(1:iElType,1:NumElVol) :: elconnvol
86 
87  INTEGER :: interfacesfnumelems,interfacesfnumnodes
88  INTEGER, DIMENSION(1:UppBnd,1:InterfaceSFNumElems) :: interfacesfelemconn
89  INTEGER, DIMENSION(1:InterfaceSFNumNodes) :: mapnodesf
90  REAL*8, DIMENSION(1:3*NumNp) :: disp
91 
92  REAL*8, DIMENSION(1:3*numnp) :: r_ex ! external force
93 
94  INTEGER :: nx, ny, nz
95  INTEGER :: i,j,k
96 
97  INTEGER,DIMENSION(1:3) :: triconn
98  REAL*8,DIMENSION(1:3) :: uniftract
99 
100 ! mesh coordinates
101  REAL*8, DIMENSION(1:3,1:numnp) :: coor
102 
103  REAL*8 :: x0p,y0p,z0p
104  REAL*8 :: x1p,y1p,z1p
105  REAL*8 :: x2p,y2p,z2p
106  REAL*8 :: x3p,y3p,z3p
107 
108 ! Components sides vector
109 
110  REAL*8 :: x1x0, y1y0, z1z0
111  REAL*8 :: x2x0, y2y0, z2z0
112 
113  REAL*8 :: magnorm, area, at
114  REAL*8 :: gauss = 0.333333333333333d0
115  REAL*8 :: weight = 1.0d0
116  REAL*8 :: xnorm,ynorm,znorm
117  REAL*8 :: u1,v1,w1,u2,v2,w2,u3,v3,w3,u4,v4,w4
118  REAL*8 :: x1,y1,z1,x2,y2,z2,x3,y3,z3,x4,y4,z4
119  REAL*8 :: j11,j12,j13,j21,j22,j23
120  REAL*8 :: invdenjplus
121  REAL*8 :: jplus11, jplus12, jplus21, jplus22, jplus31, jplus32
122  REAL*8 :: gradu11, gradu12, gradu13, gradu21, gradu22, gradu23
123  REAL*8 :: gradu31, gradu32, gradu33
124  REAL*8 :: f11t,f12t,f13t,f21t,f22t,f23t,f31t,f32t,f33t
125  REAL*8 :: j1, undefnorm(1:3)
126  INTEGER :: idvol
127 
128  INTEGER :: n1,n2,n3,n4
129 ! -- dummy and counters
130  INTEGER :: k1n1,k1n2,k1n3,k1n4,k2n1,k2n2,k2n3,k2n4
131  INTEGER :: k3n1,k3n2,k3n3,k3n4
132  REAL*8, DIMENSION(1:InterfaceSFNumElems) :: tractpress
133 !-- Coordinate subtractions
134  REAL*8 :: x14, x24, x34, y14, y24, y34, z14, z24, z34
135 !-- Coordinate subtractions: These are to speed up B calculation
136  REAL*8 :: x12, x13, y12, y13, z12, z13!--
137 
138  REAL*8 :: c11, c21, c31
139  REAL*8 :: vx6, vx6inv
140 !-- spacial derivatives
141  REAL*8 :: b1,b2,b3,b4,b5,b6,b7,b8,b9,b10,b11,b12
142 !-- partial derivatives of the displacement
143  REAL*8 :: dudx,dvdy,dwdz,dudy,dvdx,dvdz,dwdy,dudz,dwdx
144  INTEGER, DIMENSION(1:NumElVol) :: mapsfelvolel
145  REAL*8 :: jac3d
146  REAL*8 :: defnorm(1:3)
147  REAL*8 :: denfinvt,magnormdef,area0
148  REAL*8 :: f11,f12,f13,f21,f22,f23,f31,f32,f33
149  REAL*8 :: finvt11, finvt12, finvt13, finvt21, finvt22, finvt23, finvt31, finvt32, finvt33
150 
151 
152  DO i = 1, interfacesfnumelems
153 
154 ! Compute the Gradient of U (disp) Volumetric
155 
156  idvol = mapsfelvolel(i) ! Relates Surface id to Volumetric id
157 
158  n1 = elconnvol(1,idvol)
159  n2 = elconnvol(2,idvol)
160  n3 = elconnvol(3,idvol)
161  n4 = elconnvol(4,idvol)
162 
163  k3n1 = 3*n1
164  k3n2 = 3*n2
165  k3n3 = 3*n3
166  k3n4 = 3*n4
167 
168  k2n1 = k3n1 - 1
169  k2n2 = k3n2 - 1
170  k2n3 = k3n3 - 1
171  k2n4 = k3n4 - 1
172 
173  k1n1 = k3n1 - 2
174  k1n2 = k3n2 - 2
175  k1n3 = k3n3 - 2
176  k1n4 = k3n4 - 2
177 
178  x1 = coor(1,n1)
179  x2 = coor(1,n2)
180  x3 = coor(1,n3)
181  x4 = coor(1,n4)
182  y1 = coor(2,n1)
183  y2 = coor(2,n2)
184  y3 = coor(2,n3)
185  y4 = coor(2,n4)
186  z1 = coor(3,n1)
187  z2 = coor(3,n2)
188  z3 = coor(3,n3)
189  z4 = coor(3,n4)
190 
191  ! k#n# dummy variables replaces:
192  u1 = disp(k1n1) ! (3*n1-2)
193  u2 = disp(k1n2) ! (3*n2-2)
194  u3 = disp(k1n3) ! (3*n3-2)
195  u4 = disp(k1n4) ! (3*n4-2)
196  v1 = disp(k2n1) ! (3*n1-1)
197  v2 = disp(k2n2) ! (3*n2-1)
198  v3 = disp(k2n3) ! (3*n3-1)
199  v4 = disp(k2n4) ! (3*n4-1)
200  w1 = disp(k3n1) ! (3*n1)
201  w2 = disp(k3n2) ! (3*n2)
202  w3 = disp(k3n3) ! (3*n3)
203  w4 = disp(k3n4) ! (3*n4)
204 
205  x12 = x1 - x2 ! not used in vol. calc
206  x13 = x1 - x3 ! not used in vol. calc
207  x14 = x1 - x4
208  x24 = x2 - x4
209  x34 = x3 - x4
210  y12 = y1 - y2 ! not used in vol. calc
211  y13 = y1 - y3 ! not used in vol. calc
212  y14 = y1 - y4
213  y24 = y2 - y4
214  y34 = y3 - y4
215  z12 = z1 - z2 ! not used in vol. calc
216  z13 = z1 - z3 ! not used in vol. calc
217  z14 = z1 - z4
218  z24 = z2 - z4
219  z34 = z3 - z4
220 
221  c11 = y24*z34 - z24*y34
222  c21 = -( x24*z34 - z24*x34 )
223  c31 = x24*y34 - y24*x34
224 
225  vx6 = -( x14*c11 + y14*c21 + z14*c31 )
226 
227  vx6inv = 1.d0 / vx6
228 
229 ! See the maple worksheet 'V3D4.mws' for the derivation of [B]
230 ! NOTE: Factored for a more equivalent/compact form then maple's
231 
232  b1 = (y34*z24 - y24*z34) * vx6inv
233  b2 = (z34*x24 - z24*x34) * vx6inv
234  b3 = (x34*y24 - x24*y34) * vx6inv
235  b4 = (y13*z14 - y14*z13) * vx6inv
236  b5 = (z13*x14 - z14*x13) * vx6inv
237  b6 = (x13*y14 - x14*y13) * vx6inv
238  b7 = (y14*z12 - y12*z14) * vx6inv
239  b8 = (z14*x12 - z12*x14) * vx6inv
240  b9 = (x14*y12 - x12*y14) * vx6inv
241  b10 = (y12*z13 - y13*z12) * vx6inv
242  b11 = (z12*x13 - z13*x12) * vx6inv
243  b12 = (x12*y13 - x13*y12) * vx6inv
244 !
245 ! Calculate displacement gradient (H)
246 !
247  dudx = b1*u1 + b4*u2 + b7*u3 + b10*u4
248  dvdy = b2*v1 + b5*v2 + b8*v3 + b11*v4
249  dwdz = b3*w1 + b6*w2 + b9*w3 + b12*w4
250  dudy = b2*u1 + b5*u2 + b8*u3 + b11*u4
251  dvdx = b1*v1 + b4*v2 + b7*v3 + b10*v4
252  dvdz = b3*v1 + b6*v2 + b9*v3 + b12*v4
253  dwdy = b2*w1 + b5*w2 + b8*w3 + b11*w4
254  dudz = b3*u1 + b6*u2 + b9*u3 + b12*u4
255  dwdx = b1*w1 + b4*w2 + b7*w3 + b10*w4
256 !
257 ! deformation gradients F
258 !
259  f11 = 1.d0 + dudx
260  f12 = dudy
261  f13 = dudz
262  f21 = dvdx
263  f22 = 1.d0 + dvdy
264  f23 = dvdz
265  f31 = dwdx
266  f32 = dwdy
267  f33 = 1.d0 + dwdz
268 
269 !
270 !
271 !
272 
273  denfinvt = f11*(f22*f33-f32*f23) - f12*(f21*f33+f31*f23) + f13*(f21*f32-f31*f22)
274 
275  finvt11 = (f22*f33-f32*f23)/denfinvt
276  finvt12 = -(f21*f33-f31*f23)/denfinvt
277  finvt13 = (f21*f32-f31*f22)/denfinvt
278  finvt21 = -(f12*f33-f32*f13)/denfinvt
279  finvt22 = (f11*f33-f31*f13)/denfinvt
280  finvt23 = -(f11*f32-f31*f12)/denfinvt
281  finvt31 = (f12*f23-f22*f13)/denfinvt
282  finvt32 = -(f11*f23-f21*f13)/denfinvt
283  finvt33 = (f11*f22-f21*f12)/denfinvt
284 
285  jac3d = denfinvt
286 
287 ! Nodes of the Triangle ( Vertex Nodes )
288 
289  triconn(1:3) = interfacesfelemconn(1:3,i)
290 
291 ! 1) Calculate the Normal in the Deformed Configuration
292 
293 ! Uses the fact that the norm of the cross product vector
294 ! is the area of the parallelogram they form. The triangle they
295 ! form has half that area.
296 
297  x1 = coor(1,mapnodesf(triconn(1)))
298  y1 = coor(2,mapnodesf(triconn(1)))
299  z1 = coor(3,mapnodesf(triconn(1)))
300 
301  x2 = coor(1,mapnodesf(triconn(2)))
302  y2 = coor(2,mapnodesf(triconn(2)))
303  z2 = coor(3,mapnodesf(triconn(2)))
304 
305  x3 = coor(1,mapnodesf(triconn(3)))
306  y3 = coor(2,mapnodesf(triconn(3)))
307  z3 = coor(3,mapnodesf(triconn(3)))
308 
309  u1 = disp(3*mapnodesf(triconn(1))-2)
310  v1 = disp(3*mapnodesf(triconn(1))-1)
311  w1 = disp(3*mapnodesf(triconn(1)) )
312 
313  u2 = disp(3*mapnodesf(triconn(2))-2)
314  v2 = disp(3*mapnodesf(triconn(2))-1)
315  w2 = disp(3*mapnodesf(triconn(2)) )
316 
317  u3 = disp(3*mapnodesf(triconn(3))-2)
318  v3 = disp(3*mapnodesf(triconn(3))-1)
319  w3 = disp(3*mapnodesf(triconn(3)) )
320 
321  x0p = x1
322  y0p = y1
323  z0p = z1
324 
325  x1p = x2
326  y1p = y2
327  z1p = z2
328 
329  x2p = x3
330  y2p = y3
331  z2p = z3
332 
333 ! Find vector componets of the sides
334 
335  x1x0 = x1p - x0p
336  y1y0 = y1p - y0p
337  z1z0 = z1p - z0p
338 
339  x2x0 = x2p - x0p
340  y2y0 = y2p - y0p
341  z2z0 = z2p - z0p
342 
343 ! Take the cross product
344 
345  x3p = y1y0 * z2z0 - z1z0 * y2y0
346  y3p = z1z0 * x2x0 - x1x0 * z2z0
347  z3p = x1x0 * y2y0 - y1y0 * x2x0
348 
349 ! Computes the Euclidean norm of a vector in 3D Deformed Config.
350 
351  magnorm = sqrt( x3p*x3p + y3p*y3p + z3p*z3p )
352 
353  xnorm = x3p/magnorm
354  ynorm = y3p/magnorm
355  znorm = z3p/magnorm
356 
357 ! area0 = 0.5*MagNorm
358 
359 ! little n (deformed normal)
360 
361  defnorm(1) = jac3d * (finvt11*xnorm+finvt12*ynorm+finvt13*znorm)
362  defnorm(2) = jac3d * (finvt21*xnorm+finvt22*ynorm+finvt23*znorm)
363  defnorm(3) = jac3d * (finvt31*xnorm+finvt32*ynorm+finvt33*znorm)
364 
365  magnormdef = sqrt( defnorm(1)**2 + defnorm(2)**2 + defnorm(3)**2 )
366 
367  defnorm(1) = defnorm(1)/magnormdef
368  defnorm(2) = defnorm(2)/magnormdef
369  defnorm(3) = defnorm(3)/magnormdef
370 
371  x0p = x1 + u1
372  y0p = y1 + v1
373  z0p = z1 + w1
374 
375  x1p = x2 + u2
376  y1p = y2 + v2
377  z1p = z2 + w2
378 
379  x2p = x3 + u3
380  y2p = y3 + v3
381  z2p = z3 + w3
382 
383 ! Find vector componets of the sides
384 
385  x1x0 = x1p - x0p
386  y1y0 = y1p - y0p
387  z1z0 = z1p - z0p
388 
389  x2x0 = x2p - x0p
390  y2y0 = y2p - y0p
391  z2z0 = z2p - z0p
392 
393 ! Take the cross product
394 
395  x3p = y1y0 * z2z0 - z1z0 * y2y0
396  y3p = z1z0 * x2x0 - x1x0 * z2z0
397  z3p = x1x0 * y2y0 - y1y0 * x2x0
398 
399 ! Computes the Euclidean norm of a vector in 3D Deformed Config.
400 
401  magnormdef = sqrt( x3p*x3p + y3p*y3p + z3p*z3p )
402 
403  area = 0.5*magnormdef
404 
405 ! Pressure * Jac2D * n * Area0 (Jac2D = Area/Area0)
406 
407  uniftract(1) = -tractpress(i)*defnorm(1)*area/3.d0
408  uniftract(2) = -tractpress(i)*defnorm(2)*area/3.d0
409  uniftract(3) = -tractpress(i)*defnorm(3)*area/3.d0
410 
411 ! Assembly into global external load vector R_ex
412 
413  triconn(1:3) = interfacesfelemconn(lwrbnd:uppbnd,i)
414 
415  DO j = 1, 3
416  nz = mapnodesf(triconn(j))*3 ! volume node
417  nx = nz - 2
418  ny = nz - 1
419  r_ex(nx) = r_ex(nx) + uniftract(1)
420  r_ex(ny) = r_ex(ny) + uniftract(2)
421  r_ex(nz) = r_ex(nz) + uniftract(3)
422  ENDDO
423 
424  ENDDO
425 
426 END SUBROUTINE fluidpressload
427 
j indices k indices k
Definition: Indexing.h:6
double sqrt(double d)
Definition: double.h:73
subroutine fluidpressload(NumNP, R_ex, InterfaceSFNumElems, InterfaceSFNumNodes, InterfaceSFElemConn, MapNodeSF, LwrBnd, UppBnd, coor, Disp, MapSFElVolEl, ElConnVol, iElType, NumElVol, TractPress)
blockLoc i
Definition: read.cpp:79
j indices j
Definition: Indexing.h:6