CalculiX  2.13
A Free Software Three-Dimensional Structural Finite Element Program
shape26h.f File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine shape26h (xi, et, ze, xl, xsj, shp, iflag, konl)
 

Function/Subroutine Documentation

◆ shape26h()

subroutine shape26h ( real*8, intent(in)  xi,
real*8, intent(in)  et,
real*8, intent(in)  ze,
real*8, dimension(3,26), intent(in)  xl,
real*8, intent(out)  xsj,
real*8, dimension(4,26), intent(out)  shp,
integer, intent(in)  iflag,
integer, dimension(26), intent(in)  konl 
)
20 !
21 ! shape functions and derivatives for a 26-node quadratic
22 ! isoparametric brick element. -1<=xi,et,ze<=1
23 !
24 ! iflag=1: calculate only the value of the shape functions
25 ! iflag=2: calculate the value of the shape functions and
26 ! the Jacobian determinant
27 ! iflag=3: calculate the value of the shape functions, the
28 ! value of their derivatives w.r.t. the global
29 ! coordinates and the Jacobian determinant
30 !
31  implicit none
32 !
33  integer i,j,k,iflag,konl(26),jf(3,6),ifaceq(8,6)
34 !
35  real*8 shp(4,26),xs(3,3),xsi(3,3),xl(3,26),shpe(4,26),dd,
36  & dd1,dd2,dd3,xi,et,ze,xsj,omg,omh,omr,opg,oph,opr,
37  & tpgphpr,tmgphpr,tmgmhpr,tpgmhpr,tpgphmr,tmgphmr,tmgmhmr,tpgmhmr,
38  & omgopg,omhoph,omropr,omgmopg,omhmoph,omrmopr,fxi(3),fet(3),
39  & fze(3),dfxi(3),dfet(3),dfze(3)
40 !
41  intent(in) xi,et,ze,xl,iflag,konl
42 !
43  intent(out) shp,xsj
44 !
45  jf=reshape((/2,2,1,2,2,3,2,1,2,3,2,2,2,3,2,1,2,2/),(/3,6/))
46 !
47  ifaceq=reshape(( /4,3,2,1,11,10,9,12,
48  & 5,6,7,8,13,14,15,16,
49  & 1,2,6,5,9,18,13,17,
50  & 2,3,7,6,10,19,14,18,
51  & 3,4,8,7,11,20,15,19,
52  & 4,1,5,8,12,17,16,20/),(/8,6/))
53 !
54 ! shape functions in one dimension
55 !
56  fxi(1)=xi*(xi-1.d0)/2.d0
57  fxi(2)=(1.d0-xi)*(1.d0+xi)
58  fxi(3)=xi*(xi+1.d0)/2.d0
59 !
60  fet(1)=et*(et-1.d0)/2.d0
61  fet(2)=(1.d0-et)*(1.d0+et)
62  fet(3)=et*(et+1.d0)/2.d0
63 !
64  fze(1)=ze*(ze-1.d0)/2.d0
65  fze(2)=(1.d0-ze)*(1.d0+ze)
66  fze(3)=ze*(ze+1.d0)/2.d0
67 !
68 ! shape functions and their glocal derivatives
69 !
70  omg=1.d0-xi
71  omh=1.d0-et
72  omr=1.d0-ze
73  opg=1.d0+xi
74  oph=1.d0+et
75  opr=1.d0+ze
76  tpgphpr=opg+oph+ze
77  tmgphpr=omg+oph+ze
78  tmgmhpr=omg+omh+ze
79  tpgmhpr=opg+omh+ze
80  tpgphmr=opg+oph-ze
81  tmgphmr=omg+oph-ze
82  tmgmhmr=omg+omh-ze
83  tpgmhmr=opg+omh-ze
84  omgopg=omg*opg/4.d0
85  omhoph=omh*oph/4.d0
86  omropr=omr*opr/4.d0
87  omgmopg=(omg-opg)/4.d0
88  omhmoph=(omh-oph)/4.d0
89  omrmopr=(omr-opr)/4.d0
90 !
91 ! shape functions
92 !
93  shp(4, 1)=-omg*omh*omr*tpgphpr/8.d0
94  shp(4, 2)=-opg*omh*omr*tmgphpr/8.d0
95  shp(4, 3)=-opg*oph*omr*tmgmhpr/8.d0
96  shp(4, 4)=-omg*oph*omr*tpgmhpr/8.d0
97  shp(4, 5)=-omg*omh*opr*tpgphmr/8.d0
98  shp(4, 6)=-opg*omh*opr*tmgphmr/8.d0
99  shp(4, 7)=-opg*oph*opr*tmgmhmr/8.d0
100  shp(4, 8)=-omg*oph*opr*tpgmhmr/8.d0
101  shp(4, 9)=omgopg*omh*omr
102  shp(4,10)=omhoph*opg*omr
103  shp(4,11)=omgopg*oph*omr
104  shp(4,12)=omhoph*omg*omr
105  shp(4,13)=omgopg*omh*opr
106  shp(4,14)=omhoph*opg*opr
107  shp(4,15)=omgopg*oph*opr
108  shp(4,16)=omhoph*omg*opr
109  shp(4,17)=omropr*omg*omh
110  shp(4,18)=omropr*opg*omh
111  shp(4,19)=omropr*opg*oph
112  shp(4,20)=omropr*omg*oph
113 !
114 ! correction for the extra nodes in the middle of the faces
115 !
116  do i=1,6
117  if(konl(20+i).eq.konl(20)) then
118 !
119 ! no extra node in this face
120 !
121  shp(4,20+i)=0.d0
122  else
123  shp(4,20+i)=fxi(jf(1,i))*fet(jf(2,i))*fze(jf(3,i))
124  do j=1,4
125  shp(4,ifaceq(j,i))=shp(4,ifaceq(j,i))+shp(4,20+i)/4.d0
126  enddo
127  do j=5,8
128  shp(4,ifaceq(j,i))=shp(4,ifaceq(j,i))-shp(4,20+i)/2.d0
129  enddo
130  endif
131  enddo
132 !
133  if(iflag.eq.1) return
134 !
135 ! derivative of the shape functions in one dimension
136 !
137  dfxi(1)=(2.d0*xi-1.d0)/2.d0
138  dfxi(2)=-2.d0*xi
139  dfxi(3)=(2.d0*xi+1.d0)/2.d0
140 !
141  dfet(1)=(2.d0*et-1.d0)/2.d0
142  dfet(2)=-2.d0*et
143  dfet(3)=(2.d0*et+1.d0)/2.d0
144 !
145  dfze(1)=(2.d0*ze-1.d0)/2.d0
146  dfze(2)=-2.d0*ze
147  dfze(3)=(2.d0*ze+1.d0)/2.d0
148 !
149 ! local derivatives of the shape functions: xi-derivative
150 !
151  shpe(1, 1)=omh*omr*(tpgphpr-omg)/8.d0
152  shpe(1, 2)=(opg-tmgphpr)*omh*omr/8.d0
153  shpe(1, 3)=(opg-tmgmhpr)*oph*omr/8.d0
154  shpe(1, 4)=oph*omr*(tpgmhpr-omg)/8.d0
155  shpe(1, 5)=omh*opr*(tpgphmr-omg)/8.d0
156  shpe(1, 6)=(opg-tmgphmr)*omh*opr/8.d0
157  shpe(1, 7)=(opg-tmgmhmr)*oph*opr/8.d0
158  shpe(1, 8)=oph*opr*(tpgmhmr-omg)/8.d0
159  shpe(1, 9)=omgmopg*omh*omr
160  shpe(1,10)=omhoph*omr
161  shpe(1,11)=omgmopg*oph*omr
162  shpe(1,12)=-omhoph*omr
163  shpe(1,13)=omgmopg*omh*opr
164  shpe(1,14)=omhoph*opr
165  shpe(1,15)=omgmopg*oph*opr
166  shpe(1,16)=-omhoph*opr
167  shpe(1,17)=-omropr*omh
168  shpe(1,18)=omropr*omh
169  shpe(1,19)=omropr*oph
170  shpe(1,20)=-omropr*oph
171 !
172 ! correction for the extra nodes in the middle of the faces
173 !
174  do i=1,6
175  if(konl(20+i).eq.konl(20)) then
176 !
177 ! no extra node in this face
178 !
179  shpe(1,20+i)=0.d0
180  else
181  shpe(1,20+i)=dfxi(jf(1,i))*fet(jf(2,i))*fze(jf(3,i))
182  do j=1,4
183  shpe(1,ifaceq(j,i))=shpe(1,ifaceq(j,i))+shpe(1,20+i)/4.d0
184  enddo
185  do j=5,8
186  shpe(1,ifaceq(j,i))=shpe(1,ifaceq(j,i))-shpe(1,20+i)/2.d0
187  enddo
188  endif
189  enddo
190 !
191 ! local derivatives of the shape functions: eta-derivative
192 !
193  shpe(2, 1)=omg*omr*(tpgphpr-omh)/8.d0
194  shpe(2, 2)=opg*omr*(tmgphpr-omh)/8.d0
195  shpe(2, 3)=opg*(oph-tmgmhpr)*omr/8.d0
196  shpe(2, 4)=omg*(oph-tpgmhpr)*omr/8.d0
197  shpe(2, 5)=omg*opr*(tpgphmr-omh)/8.d0
198  shpe(2, 6)=opg*opr*(tmgphmr-omh)/8.d0
199  shpe(2, 7)=opg*(oph-tmgmhmr)*opr/8.d0
200  shpe(2, 8)=omg*(oph-tpgmhmr)*opr/8.d0
201  shpe(2, 9)=-omgopg*omr
202  shpe(2,10)=omhmoph*opg*omr
203  shpe(2,11)=omgopg*omr
204  shpe(2,12)=omhmoph*omg*omr
205  shpe(2,13)=-omgopg*opr
206  shpe(2,14)=omhmoph*opg*opr
207  shpe(2,15)=omgopg*opr
208  shpe(2,16)=omhmoph*omg*opr
209  shpe(2,17)=-omropr*omg
210  shpe(2,18)=-omropr*opg
211  shpe(2,19)=omropr*opg
212  shpe(2,20)=omropr*omg
213 !
214 ! correction for the extra nodes in the middle of the faces
215 !
216  do i=1,6
217  if(konl(20+i).eq.konl(20)) then
218 !
219 ! no extra node in this face
220 !
221  shpe(2,20+i)=0.d0
222  else
223  shpe(2,20+i)=fxi(jf(1,i))*dfet(jf(2,i))*fze(jf(3,i))
224  do j=1,4
225  shpe(2,ifaceq(j,i))=shpe(2,ifaceq(j,i))+shpe(2,20+i)/4.d0
226  enddo
227  do j=5,8
228  shpe(2,ifaceq(j,i))=shpe(2,ifaceq(j,i))-shpe(2,20+i)/2.d0
229  enddo
230  endif
231  enddo
232 !
233 ! local derivatives of the shape functions: zeta-derivative
234 !
235  shpe(3, 1)=omg*omh*(tpgphpr-omr)/8.d0
236  shpe(3, 2)=opg*omh*(tmgphpr-omr)/8.d0
237  shpe(3, 3)=opg*oph*(tmgmhpr-omr)/8.d0
238  shpe(3, 4)=omg*oph*(tpgmhpr-omr)/8.d0
239  shpe(3, 5)=omg*omh*(opr-tpgphmr)/8.d0
240  shpe(3, 6)=opg*omh*(opr-tmgphmr)/8.d0
241  shpe(3, 7)=opg*oph*(opr-tmgmhmr)/8.d0
242  shpe(3, 8)=omg*oph*(opr-tpgmhmr)/8.d0
243  shpe(3, 9)=-omgopg*omh
244  shpe(3,10)=-omhoph*opg
245  shpe(3,11)=-omgopg*oph
246  shpe(3,12)=-omhoph*omg
247  shpe(3,13)=omgopg*omh
248  shpe(3,14)=omhoph*opg
249  shpe(3,15)=omgopg*oph
250  shpe(3,16)=omhoph*omg
251  shpe(3,17)=omrmopr*omg*omh
252  shpe(3,18)=omrmopr*opg*omh
253  shpe(3,19)=omrmopr*opg*oph
254  shpe(3,20)=omrmopr*omg*oph
255 !
256 ! correction for the extra nodes in the middle of the faces
257 !
258  do i=1,6
259  if(konl(20+i).eq.konl(20)) then
260 !
261 ! no extra node in this face
262 !
263  shpe(3,20+i)=0.d0
264  else
265  shpe(3,20+i)=fxi(jf(1,i))*fet(jf(2,i))*dfze(jf(3,i))
266  do j=1,4
267  shpe(3,ifaceq(j,i))=shpe(3,ifaceq(j,i))+shpe(3,20+i)/4.d0
268  enddo
269  do j=5,8
270  shpe(3,ifaceq(j,i))=shpe(3,ifaceq(j,i))-shpe(3,20+i)/2.d0
271  enddo
272  endif
273  enddo
274 !
275 ! computation of the local derivative of the global coordinates
276 ! (xs)
277 !
278  do i=1,3
279  do j=1,3
280  xs(i,j)=0.d0
281  do k=1,26
282  xs(i,j)=xs(i,j)+xl(i,k)*shpe(j,k)
283  enddo
284  enddo
285  enddo
286 !
287 ! computation of the jacobian determinant
288 !
289  dd1=xs(2,2)*xs(3,3)-xs(2,3)*xs(3,2)
290  dd2=xs(2,3)*xs(3,1)-xs(2,1)*xs(3,3)
291  dd3=xs(2,1)*xs(3,2)-xs(2,2)*xs(3,1)
292  xsj=xs(1,1)*dd1+xs(1,2)*dd2+xs(1,3)*dd3
293 !
294  if(iflag.eq.2) return
295 !
296  dd=1.d0/xsj
297 !
298 ! computation of the global derivative of the local coordinates
299 ! (xsi) (inversion of xs)
300 !
301  xsi(1,1)=dd1*dd
302  xsi(1,2)=(xs(1,3)*xs(3,2)-xs(1,2)*xs(3,3))*dd
303  xsi(1,3)=(xs(1,2)*xs(2,3)-xs(2,2)*xs(1,3))*dd
304  xsi(2,1)=dd2*dd
305  xsi(2,2)=(xs(1,1)*xs(3,3)-xs(3,1)*xs(1,3))*dd
306  xsi(2,3)=(xs(1,3)*xs(2,1)-xs(1,1)*xs(2,3))*dd
307  xsi(3,1)=dd3*dd
308  xsi(3,2)=(xs(1,2)*xs(3,1)-xs(1,1)*xs(3,2))*dd
309  xsi(3,3)=(xs(1,1)*xs(2,2)-xs(2,1)*xs(1,2))*dd
310 !
311 ! computation of the global derivatives of the shape functions
312 !
313  do k=1,26
314  do j=1,3
315  shp(j,k)=shpe(1,k)*xsi(1,j)+shpe(2,k)*xsi(2,j)
316  & +shpe(3,k)*xsi(3,j)
317  enddo
318  enddo
319 !
320  return
Hosted by OpenAircraft.com, (Michigan UAV, LLC)