Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
v3d4_thermalExp2.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_thermalexp2(coor,matcstet,lmcstet,R_in,d,ci, &
54  s11,s22,s33,s12,s23,s13,numnp,nstart,nend,numcstet,numat_vol,&
55  coeffexp,temperature,temperature0)
56 !________________________________________________________________________
57 !
58 ! V3D4 - Performs displacement based computations for Volumetric 3D
59 ! 4-node tetrahedra linear elastic elements with linear
60 ! interpolation functions. (constant strain tetrahedra).
61 ! Returns the internal force vector R_in.
62 !
63 ! DATE: 04.2000 AUTHOR: SCOT BREITENFELD
64 !________________________________________________________________________
65 
66  IMPLICIT NONE
67 !---- Global variables
68  INTEGER :: numnp ! number of nodal points
69  INTEGER :: numcstet ! number of CSTet elements
70  INTEGER :: numat_vol ! number of volumetric materials
71 !-- coordinate array
72  REAL*8, DIMENSION(1:3,1:numnp) :: coor
73 !-- elastic stiffness consts
74  REAL*8, DIMENSION(1:9,1:numat_vol) :: ci
75 
76  REAL*8, DIMENSION(1:numat_vol) :: coeffexp
77  REAL*8, DIMENSION(1:NumNP) :: temperature
78  REAL*8 :: temperaturegauss,temperature0
79 
80 !-- internal force
81  REAL*8, DIMENSION(1:3*numnp) :: r_in
82 !-- displacement vector
83  REAL*8, DIMENSION(1:3*numnp) :: d
84 !-- CSTet stress
85  REAL*8, DIMENSION(1:numcstet) :: s11, s22, s33, s12, s23, s13
86 !-- connectivity table for CSTet
87  INTEGER, DIMENSION(1:4,1:numcstet) :: lmcstet
88 !-- mat number for CSTet element
89  INTEGER, DIMENSION(1:numcstet) :: matcstet
90 !---- Local variables
91 !-- node numbers
92  INTEGER :: n1,n2,n3,n4
93 !-- x, y, and z displacements of nodes
94  REAL*8 :: u1,u2,u3,u4,v1,v2,v3,v4,w1,w2,w3,w4
95 !-- 6*volume, inverse(6*volume), and the volume
96  REAL*8 :: vx6, vx6inv, vol
97 !-- spacial derivatives
98  REAL*8 :: b1,b2,b3,b4,b5,b6,b7,b8,b9,b10,b11,b12
99 !-- strains
100  REAL*8 :: e11,e22,e33,e12,e23,e13
101 !-- coordinate holding variable
102  REAL*8 :: x1,x2,x3,x4,y1,y2,y3,y4,z1,z2,z3,z4
103 !-- Coordinate subtractions
104  REAL*8 :: x14, x24, x34, y14, y24, y34, z14, z24, z34
105 !-- Coordinate subtractions: These are to speed up B calculation
106  REAL*8 :: x12, x13, y12, y13, z12, z13
107 !-- Dummy
108  REAL*8 :: c11, c21, c31
109 !-- dummy and counters
110  INTEGER :: i,j,nstart,nend
111  INTEGER :: k1n1,k1n2,k1n3,k1n4,k2n1,k2n2,k2n3,k2n4
112  INTEGER :: k3n1,k3n2,k3n3,k3n4
113 
114  DO i = nstart, nend
115  j = matcstet(i)
116 
117  n1 = lmcstet(1,i)
118  n2 = lmcstet(2,i)
119  n3 = lmcstet(3,i)
120  n4 = lmcstet(4,i)
121 
122  k3n1 = 3*n1
123  k3n2 = 3*n2
124  k3n3 = 3*n3
125  k3n4 = 3*n4
126 
127  k2n1 = k3n1 - 1
128  k2n2 = k3n2 - 1
129  k2n3 = k3n3 - 1
130  k2n4 = k3n4 - 1
131 
132  k1n1 = k3n1 - 2
133  k1n2 = k3n2 - 2
134  k1n3 = k3n3 - 2
135  k1n4 = k3n4 - 2
136  ! k#n# dummy variables replaces:
137  u1 = d(k1n1) ! (3*n1-2)
138  u2 = d(k1n2) ! (3*n2-2)
139  u3 = d(k1n3) ! (3*n3-2)
140  u4 = d(k1n4) ! (3*n4-2)
141  v1 = d(k2n1) ! (3*n1-1)
142  v2 = d(k2n2) ! (3*n2-1)
143  v3 = d(k2n3) ! (3*n3-1)
144  v4 = d(k2n4) ! (3*n4-1)
145  w1 = d(k3n1) ! (3*n1)
146  w2 = d(k3n2) ! (3*n2)
147  w3 = d(k3n3) ! (3*n3)
148  w4 = d(k3n4) ! (3*n4)
149 
150  x1 = coor(1,n1) ! Node 1, x-coor
151  x2 = coor(1,n2) ! Node 2, x-coor
152  x3 = coor(1,n3) ! Node 3, x-coor
153  x4 = coor(1,n4) ! Node 4, x-coor
154  y1 = coor(2,n1) ! Node 1, y-coor
155  y2 = coor(2,n2) ! Node 2, y-coor
156  y3 = coor(2,n3) ! Node 3, y-coor
157  y4 = coor(2,n4) ! Node 4, y-coor
158  z1 = coor(3,n1) ! Node 1, z-coor
159  z2 = coor(3,n2) ! Node 2, z-coor
160  z3 = coor(3,n3) ! Node 3, z-coor
161  z4 = coor(3,n4) ! Node 4, z-coor
162 
163  x12 = x1 - x2 ! not used in vol. calc
164  x13 = x1 - x3 ! not used in vol. calc
165  x14 = x1 - x4
166  x24 = x2 - x4
167  x34 = x3 - x4
168  y12 = y1 - y2 ! not used in vol. calc
169  y13 = y1 - y3 ! not used in vol. calc
170  y14 = y1 - y4
171  y24 = y2 - y4
172  y34 = y3 - y4
173  z12 = z1 - z2 ! not used in vol. calc
174  z13 = z1 - z3 ! not used in vol. calc
175  z14 = z1 - z4
176  z24 = z2 - z4
177  z34 = z3 - z4
178 
179  c11 = y24*z34 - z24*y34
180  c21 = -( x24*z34 - z24*x34 )
181  c31 = x24*y34 - y24*x34
182 
183  vx6 = -( x14*c11 + y14*c21 + z14*c31 )
184 
185  vx6inv = 1.d0 / vx6
186 
187 ! See the maple worksheet 'V3D4.mws' for the derivation of [B]
188 ! NOTE: Factored for a more equivalent/compact form then maple's
189 
190  b1 = (y34*z24 - y24*z34) * vx6inv
191  b2 = (z34*x24 - z24*x34) * vx6inv
192  b3 = (x34*y24 - x24*y34) * vx6inv
193  b4 = (y13*z14 - y14*z13) * vx6inv
194  b5 = (z13*x14 - z14*x13) * vx6inv
195  b6 = (x13*y14 - x14*y13) * vx6inv
196  b7 = (y14*z12 - y12*z14) * vx6inv
197  b8 = (z14*x12 - z12*x14) * vx6inv
198  b9 = (x14*y12 - x12*y14) * vx6inv
199  b10 = (y12*z13 - y13*z12) * vx6inv
200  b11 = (z12*x13 - z13*x12) * vx6inv
201  b12 = (x12*y13 - x13*y12) * vx6inv
202 
203 ! calculate the strain
204 ! [E] = [B]{d}
205 !
206  e11 = b1*u1 + b4*u2 + b7*u3 + b10*u4
207  e22 = b2*v1 + b5*v2 + b8*v3 + b11*v4
208  e33 = b3*w1 + b6*w2 + b9*w3 + b12*w4
209  e12 = b2*u1 + b1*v1 + b5*u2 + b4*v2 + b8*u3 + b7*v3 + b11*u4 + b10*v4
210  e23 = b3*v1 + b2*w1 + b6*v2 + b5*w2 + b9*v3 + b8*w3 + b12*v4 + b11*w4
211  e13 = b3*u1 + b1*w1 + b6*u2 + b4*w2 + b9*u3 + b7*w3 + b12*u4 + b10*w4
212 
213 ! include the effects of Temperature
214 
215  temperaturegauss = ( temperature(n1) + &
216  temperature(n2) + &
217  temperature(n3) + &
218  temperature(n4) )*0.25d0
219 
220  e11 = e11 - coeffexp(j)*( temperaturegauss - temperature0 )
221  e22 = e22 - coeffexp(j)*( temperaturegauss - temperature0 )
222  e33 = e33 - coeffexp(j)*( temperaturegauss - temperature0 )
223 
224 
225 ! calculate the stress -1
226 ! [S] = [C] {E}
227 !
228  s11(i) = e11*ci(1,j) + e22*ci(2,j) + e33*ci(4,j)
229  s22(i) = e11*ci(2,j) + e22*ci(3,j) + e33*ci(5,j)
230  s33(i) = e11*ci(4,j) + e22*ci(5,j) + e33*ci(6,j)
231  s12(i) = e12*ci(7,j)
232  s23(i) = e23*ci(8,j)
233  s13(i) = e13*ci(9,j)
234 
235 ! calculate the volume
236 
237  vol = vx6 / 6.d0
238 
239 ! ASSEMBLE THE INTERNAL FORCE VECTOR
240 
241 ! local node 1
242  r_in(k1n1) = r_in(k1n1) - (s11(i)*b1 + s12(i)*b2 + s13(i)*b3)*vol
243  r_in(k2n1) = r_in(k2n1) - (s22(i)*b2 + s12(i)*b1 + s23(i)*b3)*vol
244  r_in(k3n1) = r_in(k3n1) - (s33(i)*b3 + s23(i)*b2 + s13(i)*b1)*vol
245 ! local node 2
246  r_in(k1n2) = r_in(k1n2) - (s11(i)*b4 + s12(i)*b5 + s13(i)*b6)*vol
247  r_in(k2n2) = r_in(k2n2) - (s22(i)*b5 + s12(i)*b4 + s23(i)*b6)*vol
248  r_in(k3n2) = r_in(k3n2) - (s33(i)*b6 + s23(i)*b5 + s13(i)*b4)*vol
249 ! local node 3
250  r_in(k1n3) = r_in(k1n3) - (s11(i)*b7 + s12(i)*b8 + s13(i)*b9 )*vol
251  r_in(k2n3) = r_in(k2n3) - (s22(i)*b8 + s12(i)*b7 + s23(i)*b9 )*vol
252  r_in(k3n3) = r_in(k3n3) - (s33(i)*b9 + s23(i)*b8 + s13(i)*b7 )*vol
253 ! local node 4
254  r_in(k1n4) = r_in(k1n4) - (s11(i)*b10 + s12(i)*b11 + s13(i)*b12 )*vol
255  r_in(k2n4) = r_in(k2n4) - (s22(i)*b11 + s12(i)*b10 + s23(i)*b12 )*vol
256  r_in(k3n4) = r_in(k3n4) - (s33(i)*b12 + s23(i)*b11 + s13(i)*b10 )*vol
257 
258  x1 = coor(1,n1) + u1
259  x2 = coor(1,n2) + u2
260  x3 = coor(1,n3) + u3
261  x4 = coor(1,n4) + u4
262  y1 = coor(2,n1) + v1
263  y2 = coor(2,n2) + v2
264  y3 = coor(2,n3) + v3
265  y4 = coor(2,n4) + v4
266  z1 = coor(3,n1) + w1
267  z2 = coor(3,n2) + w2
268  z3 = coor(3,n3) + w3
269  z4 = coor(3,n4) + w4
270 
271  x14 = x1 - x4
272  x24 = x2 - x4
273  x34 = x3 - x4
274  y14 = y1 - y4
275  y24 = y2 - y4
276  y34 = y3 - y4
277  z14 = z1 - z4
278  z24 = z2 - z4
279  z34 = z3 - z4
280 
281  c11 = y24*z34 - z24*y34
282  c21 = -( x24*z34 - z24*x34 )
283  c31 = x24*y34 - y24*x34
284 
285  vx6 = -( x14*c11 + y14*c21 + z14*c31 )
286 
287  IF(vx6.LT.0.d0) THEN
288  print*,'DEFORMED VOLUME TURNED NEGATIVE'
289  stop
290  ENDIF
291 
292  ENDDO
293  RETURN
294 END SUBROUTINE v3d4_thermalexp2
295 
const NT & d
subroutine v3d4_thermalexp2(coor, matcstet, lmcstet, R_in, d, ci, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol, CoeffExp, Temperature, Temperature0)
blockLoc i
Definition: read.cpp:79
virtual std::ostream & print(std::ostream &os) const
j indices j
Definition: Indexing.h:6