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

Go to the source code of this file.

Functions/Subroutines

subroutine umat_tension_only (amat, iel, iint, kode, elconloc, emec, emec0, beta, xokl, voj, xkl, vj, ithermal, t1l, dtime, time, ttime, icmd, ielas, mi, nstate_, xstateini, xstate, stre, stiff, iorien, pgauss, orab, pnewdt, ipkon)
 

Function/Subroutine Documentation

◆ umat_tension_only()

subroutine umat_tension_only ( character*80  amat,
integer  iel,
integer  iint,
integer  kode,
real*8, dimension(21)  elconloc,
real*8, dimension(6)  emec,
real*8, dimension(6)  emec0,
real*8, dimension(6)  beta,
real*8, dimension(3,3)  xokl,
real*8  voj,
real*8, dimension(3,3)  xkl,
real*8  vj,
integer  ithermal,
real*8  t1l,
real*8  dtime,
real*8  time,
real*8  ttime,
integer  icmd,
integer  ielas,
integer, dimension(*)  mi,
integer  nstate_,
real*8, dimension(nstate_,mi(1),*)  xstateini,
real*8, dimension(nstate_,mi(1),*)  xstate,
real*8, dimension(6)  stre,
real*8, dimension(21)  stiff,
integer  iorien,
real*8, dimension(3)  pgauss,
real*8, dimension(7,*)  orab,
real*8  pnewdt,
integer, dimension(*)  ipkon 
)
24 !
25 ! calculates stiffness and stresses for a user defined material
26 ! law
27 !
28 ! icmd=3: calcutates stress at mechanical strain
29 ! else: calculates stress at mechanical strain and the stiffness
30 ! matrix
31 !
32 ! INPUT:
33 !
34 ! amat material name
35 ! iel element number
36 ! iint integration point number
37 !
38 ! kode material type (-100-#of constants entered
39 ! under *USER MATERIAL): can be used for materials
40 ! with varying number of constants
41 !
42 ! elconloc(21) user defined constants defined by the keyword
43 ! card *USER MATERIAL (max. 21, actual # =
44 ! -kode-100), interpolated for the
45 ! actual temperature t1l
46 !
47 ! emec(6) Lagrange mechanical strain tensor (component order:
48 ! 11,22,33,12,13,23) at the end of the increment
49 ! (thermal strains are subtracted)
50 ! emec0(6) Lagrange mechanical strain tensor at the start of the
51 ! increment (thermal strains are subtracted)
52 ! beta(6) residual stress tensor (the stress entered under
53 ! the keyword *INITIAL CONDITIONS,TYPE=STRESS)
54 !
55 ! xokl(3,3) deformation gradient at the start of the increment
56 ! voj Jacobian at the start of the increment
57 ! xkl(3,3) deformation gradient at the end of the increment
58 ! vj Jacobian at the end of the increment
59 !
60 ! ithermal 0: no thermal effects are taken into account
61 ! >0: thermal effects are taken into account (triggered
62 ! by the keyword *INITIAL CONDITIONS,TYPE=TEMPERATURE)
63 ! t1l temperature at the end of the increment
64 ! dtime time length of the increment
65 ! time step time at the end of the current increment
66 ! ttime total time at the start of the current step
67 !
68 ! icmd not equal to 3: calculate stress and stiffness
69 ! 3: calculate only stress
70 ! ielas 0: no elastic iteration: irreversible effects
71 ! are allowed
72 ! 1: elastic iteration, i.e. no irreversible
73 ! deformation allowed
74 !
75 ! mi(1) max. # of integration points per element in the
76 ! model
77 ! nstate_ max. # of state variables in the model
78 !
79 ! xstateini(nstate_,mi(1),# of elements)
80 ! state variables at the start of the increment
81 ! xstate(nstate_,mi(1),# of elements)
82 ! state variables at the end of the increment
83 !
84 ! stre(6) Piola-Kirchhoff stress of the second kind
85 ! at the start of the increment
86 !
87 ! iorien number of the local coordinate axis system
88 ! in the integration point at stake (takes the value
89 ! 0 if no local system applies)
90 ! pgauss(3) global coordinates of the integration point
91 ! orab(7,*) description of all local coordinate systems.
92 ! If a local coordinate system applies the global
93 ! tensors can be obtained by premultiplying the local
94 ! tensors with skl(3,3). skl is determined by calling
95 ! the subroutine transformatrix:
96 ! call transformatrix(orab(1,iorien),pgauss,skl)
97 !
98 !
99 ! OUTPUT:
100 !
101 ! xstate(nstate_,mi(1),# of elements)
102 ! updated state variables at the end of the increment
103 ! stre(6) Piola-Kirchhoff stress of the second kind at the
104 ! end of the increment
105 ! stiff(21): consistent tangent stiffness matrix in the material
106 ! frame of reference at the end of the increment. In
107 ! other words: the derivative of the PK2 stress with
108 ! respect to the Lagrangian strain tensor. The matrix
109 ! is supposed to be symmetric, only the upper half is
110 ! to be given in the same order as for a fully
111 ! anisotropic elastic material (*ELASTIC,TYPE=ANISO).
112 ! Notice that the matrix is an integral part of the
113 ! fourth order material tensor, i.e. the Voigt notation
114 ! is not used.
115 ! pnewdt to be specified by the user if the material
116 ! routine is unable to return the stiffness matrix
117 ! and/or the stress due to divergence within the
118 ! routine. pnewdt is the factor by which the time
119 ! increment is to be multiplied in the next
120 ! trial and should exceed zero but be less than 1.
121 ! Default is -1 indicating that the user routine
122 ! has converged.
123 ! ipkon(*) ipkon(iel) points towards the position in field
124 ! kon prior to the first node of the element's
125 ! topology. If ipkon(iel) is set to -1, the
126 ! element is removed from the mesh
127 !
128  implicit none
129 !
130  character*80 amat
131 !
132  integer ithermal,icmd,kode,ielas,iel,iint,nstate_,mi(*),iorien,
133  & ipkon(*),kel(4,21),n,matz,ier,i,j,kal(2,6),j1,j2,j3,j4
134 !
135  real*8 elconloc(21),stiff(21),emec(6),emec0(6),beta(6),stre(6),
136  & vj,t1l,dtime,xkl(3,3),xokl(3,3),voj,pgauss(3),orab(7,*),
137  & time,ttime,pnewdt,xstate(nstate_,mi(1),*),e(3,3),we(3),
138  & xstateini(nstate_,mi(1),*),wc(3),z(3,3),fv1(3),fv2(3),eps,
139  & pi,young,fla(3),xm1(3,3),xm2(3,3),xm3(3,3),dfla(3),a(21),b(21),
140  & d(3,3),c(3,3),xmm1(21),xmm2(21),xmm3(21),ca(3),cb(3)
141 !
142  kal=reshape((/1,1,2,2,3,3,1,2,1,3,2,3/),(/2,6/))
143 !
144  kel=reshape((/1,1,1,1,1,1,2,2,2,2,2,2,1,1,3,3,2,2,3,3,3,3,3,3,
145  & 1,1,1,2,2,2,1,2,3,3,1,2,1,2,1,2,1,1,1,3,2,2,1,3,
146  & 3,3,1,3,1,2,1,3,1,3,1,3,1,1,2,3,2,2,2,3,3,3,2,3,
147  & 1,2,2,3,1,3,2,3,2,3,2,3/),(/4,21/))
148 !
149  d=reshape((/1.d0,0.d0,0.d0,0.d0,1.d0,0.d0,0.d0,0.d0,1.d0/),
150  & (/3,3/))
151 !
152 ! tension-only material. The constants are:
153 ! 1. Young's modulus
154 ! 2. maximum pressure allowed (in absolute value)
155 !
156  pi=4.d0*datan(1.d0)
157 !
158  if(elconloc(1).lt.1.d-30) then
159  write(*,*) '*ERROR in umat_tension_only: the Young modulus'
160  write(*,*) ' is too small'
161  call exit(201)
162  endif
163 !
164  if(elconloc(2).lt.1.d-30) then
165  write(*,*) '*ERROR in umat_tension_only: maximum pressure'
166  write(*,*) ' value is too small'
167  call exit(201)
168  endif
169  young=elconloc(1)
170  eps=elconloc(2)*pi/young
171 !
172 ! calculation of the eigenvalues and eigenvectors of the
173 ! Lagrange strain
174 !
175  e(1,1)=emec(1)
176  e(2,2)=emec(2)
177  e(3,3)=emec(3)
178  e(1,2)=emec(4)
179  e(1,3)=emec(5)
180  e(2,3)=emec(6)
181  e(2,1)=emec(4)
182  e(3,1)=emec(5)
183  e(3,2)=emec(6)
184 c if(iint.eq.1) write(*,*) 'emec'
185 c if(iint.eq.1) write(*,100) (emec(i),i=1,6)
186 !
187  n=3
188  matz=1
189  ier=0
190 !
191  call rs(n,n,e,we,matz,z,fv1,fv2,ier)
192 !
193  if(ier.ne.0) then
194  write(*,*) '
195  & *ERROR calculating the eigenvalues/vectors in umat_tension'
196  call exit(201)
197  endif
198 !
199 ! calculating the eigenvalues of the Cauchy tensor
200 ! at the end of the increment (eigenvalues of the Cauchy tensor)
201 !
202  do i=1,3
203  wc(i)=2.d0*we(i)+1.d0
204 c if(iint.eq.1)
205 c & write(*,*) 'eigenvalues',i,we(i),z(1,i),z(2,i),z(3,i)
206  enddo
207 !
208 ! check for 3 equal eigenvalues
209 !
210  if((dabs(we(3)-we(2)).lt.1.d-10).and.
211  & (dabs(we(2)-we(1)).lt.1.d-10)) then
212  fla(1)=young*we(1)*(0.5d0+datan(we(1)/eps)/pi)
213  do i=1,3
214  stre(i)=fla(1)
215  enddo
216  do i=1,3
217  stre(i)=0.d0
218  enddo
219 c if(iint.eq.1) write(*,*) '1 diff stre'
220 c if(iint.eq.1) write(*,100) (stre(i),i=1,6)
221 !
222  if(icmd.ne.3) then
223  dfla(1)=young*((0.5d0+datan(we(1)/eps)/pi)/2.d0
224  & +we(1)/(2.d0*pi*eps*(1.d0+(we(1)/eps)**2)))
225 !
226  do j=1,21
227  j1=kel(1,j)
228  j2=kel(2,j)
229  j3=kel(3,j)
230  j4=kel(4,j)
231  stiff(j)=dfla(1)*(d(j3,j1)*d(j4,j2)+d(j3,j2)*d(j4,j1))
232  enddo
233 c if(iint.eq.1) write(*,*) '1 diff stiff'
234 c if(iint.eq.1) write(*,100) (stiff(i),i=1,21)
235  endif
236 !
237 ! 2 equal eigenvalues: w2=w3
238 !
239  elseif(dabs(we(3)-we(2)).lt.1.d-10) then
240 !
241 ! calculating the structural tensor for the unequal
242 ! eigenvalue of the Cauchy and the Lagrange tensor
243 !
244  do i=1,3
245  do j=1,3
246  xm1(i,j)=z(i,1)*z(j,1)
247  enddo
248  enddo
249 !
250 ! calculating the modified Young's modulus (due to the
251 ! tension-only modification)
252 !
253  do i=1,2
254  fla(i)=young*we(i)*(0.5d0+datan(we(i)/eps)/pi)
255  enddo
256 !
257 ! calculating the stresses
258 !
259  do j=1,6
260  j1=kal(1,j)
261  j2=kal(2,j)
262  stre(j)=fla(1)*xm1(j1,j2)+fla(2)*(d(j1,j2)-xm1(j1,j2))
263  enddo
264 c if(iint.eq.1) write(*,*) '2 diff stre (w2=w3)'
265 c if(iint.eq.1) write(*,100) (stre(i),i=1,6)
266 !
267  if(icmd.ne.3) then
268 !
269 ! calculating the stiffness matrix
270 !
271 ! derivative of the modified young's modulus w.r.t.
272 ! the Cauchy eigenvalues
273 !
274  do i=1,2
275  dfla(i)=young*((0.5d0+datan(we(i)/eps)/pi)/2.d0
276  & +we(i)/(2.d0*pi*eps*(1.d0+(we(i)/eps)**2)))
277  enddo
278 !
279 ! stiffness matrix
280 !
281  do j=1,21
282  j1=kel(1,j)
283  j2=kel(2,j)
284  j3=kel(3,j)
285  j4=kel(4,j)
286 !
287 ! calculating the auxiliary field xmm1
288 !
289  xmm1(j)=xm1(j1,j2)*xm1(j3,j4)
290 !
291 ! calculating the auxiliary fields a and b
292 !
293  a(j)=(d(j3,j1)*d(j4,j2)+d(j3,j2)*d(j4,j1))/2.d0
294  b(j)=(d(j3,j1)*xm1(j4,j2)+d(j4,j1)*xm1(j3,j2)+
295  & d(j4,j2)*xm1(j1,j3)+d(j3,j2)*xm1(j1,j4))/2.d0
296 !
297 ! calculating the stiffness matrix
298 !
299  stiff(j)=2.d0*(dfla(1)*xmm1(j)
300  & +dfla(2)*(a(j)+xmm1(j)-b(j))
301  & +(fla(1)-fla(2))*(b(j)-2.d0*xmm1(j))
302  & /(2.d0*(we(1)-we(2))))
303  enddo
304 c if(iint.eq.1) write(*,*) '2 diff stiff (w2=w3)'
305 c if(iint.eq.1) write(*,100) (stiff(i),i=1,21)
306  endif
307 !
308 ! 2 equal eigenvalues: w1=w2
309 !
310  elseif(dabs(we(2)-we(1)).lt.1.d-10) then
311 !
312 ! calculating the structural tensor for the unequal
313 ! eigenvalue of the Cauchy and the Lagrange tensor
314 !
315  do i=1,3
316  do j=1,3
317  xm3(i,j)=z(i,3)*z(j,3)
318  enddo
319  enddo
320 !
321 ! calculating the modified Young's modulus (due to the
322 ! tension-only modification)
323 !
324  do i=2,3
325  fla(i)=young*we(i)*(0.5d0+datan(we(i)/eps)/pi)
326  enddo
327 !
328 ! calculating the stresses
329 !
330  do j=1,6
331  j1=kal(1,j)
332  j2=kal(2,j)
333  stre(j)=fla(3)*xm3(j1,j2)+fla(2)*(d(j1,j2)-xm3(j1,j2))
334  enddo
335 c if(iint.eq.1) write(*,*) '2 diff stre (w1=w2)'
336 c if(iint.eq.1) write(*,100) (stre(i),i=1,6)
337 !
338  if(icmd.ne.3) then
339 !
340 ! calculating the stiffness matrix
341 !
342 ! derivative of the modified young's modulus w.r.t.
343 ! the Cauchy eigenvalues
344 !
345  do i=2,3
346  dfla(i)=young*((0.5d0+datan(we(i)/eps)/pi)/2.d0
347  & +we(i)/(2.d0*pi*eps*(1.d0+(we(i)/eps)**2)))
348  enddo
349 !
350 ! stiffness matrix
351 !
352  do j=1,21
353  j1=kel(1,j)
354  j2=kel(2,j)
355  j3=kel(3,j)
356  j4=kel(4,j)
357 !
358 ! calculating the auxiliary field xmm3
359 !
360  xmm3(j)=xm3(j1,j2)*xm3(j3,j4)
361 !
362 ! calculating the auxiliary fields a and b
363 !
364  a(j)=(d(j3,j1)*d(j4,j2)+d(j3,j2)*d(j4,j1))/2.d0
365  b(j)=(d(j3,j1)*xm3(j4,j2)+d(j4,j1)*xm3(j3,j2)+
366  & d(j4,j2)*xm3(j1,j3)+d(j3,j2)*xm3(j1,j4))/2.d0
367 !
368 ! calculating the stiffness matrix
369 !
370  stiff(j)=2.d0*(dfla(3)*xmm3(j)
371  & +dfla(2)*(a(j)+xmm3(j)-b(j))
372  & +(fla(2)-fla(3))*(b(j)-2.d0*xmm3(j))
373  & /(2.d0*(we(2)-we(3))))
374  enddo
375 c if(iint.eq.1) write(*,*) '2 diff stiff (w1=w2)'
376 c if(iint.eq.1) write(*,100) (stiff(i),i=1,21)
377  endif
378 !
379 ! 3 different eigenvalues
380 !
381  else
382 !
383 ! calculating the structural tensors of the Cauchy and the
384 ! Lagrange tensor
385 !
386  do i=1,3
387  do j=1,3
388  xm1(i,j)=z(i,1)*z(j,1)
389  xm2(i,j)=z(i,2)*z(j,2)
390  xm3(i,j)=z(i,3)*z(j,3)
391  enddo
392  enddo
393 !
394 ! calculating the modified Young's modulus (due to the
395 ! tension-only modification)
396 !
397  do i=1,3
398  fla(i)=young*we(i)*(0.5d0+datan(we(i)/eps)/pi)
399  enddo
400 !
401 ! calculating the stresses
402 !
403  do j=1,6
404  j1=kal(1,j)
405  j2=kal(2,j)
406  stre(j)=fla(1)*xm1(j1,j2)+fla(2)*xm2(j1,j2)
407  & +fla(3)*xm3(j1,j2)
408  enddo
409 c if(iint.eq.1) write(*,*) '3 diff stre'
410 c if(iint.eq.1) write(*,100) (stre(i),i=1,6)
411 !
412  if(icmd.ne.3) then
413 !
414 ! calculating the stiffness matrix
415 !
416 ! derivative of the modified young's modulus w.r.t.
417 ! the Cauchy eigenvalues
418 !
419  do i=1,3
420  dfla(i)=young*((0.5d0+datan(we(i)/eps)/pi)/2.d0
421  & +we(i)/(2.d0*pi*eps*(1.d0+(we(i)/eps)**2)))
422  enddo
423 !
424  cb(1)=1.d0/(4.d0*(we(1)-we(2))*(we(1)-we(3)))
425  ca(1)=-(wc(2)+wc(3))*cb(1)
426  cb(2)=1.d0/(4.d0*(we(2)-we(3))*(we(2)-we(1)))
427  ca(2)=-(wc(3)+wc(1))*cb(2)
428  cb(3)=1.d0/(4.d0*(we(3)-we(1))*(we(3)-we(2)))
429  ca(3)=-(wc(1)+wc(2))*cb(3)
430 !
431 ! Cauchy tensor
432 !
433  do i=1,3
434  do j=1,3
435  c(i,j)=2.d0*e(i,j)
436  enddo
437  c(i,i)=c(i,i)+1.d0
438  enddo
439 !
440 ! stiffness matrix
441 !
442  do j=1,21
443  j1=kel(1,j)
444  j2=kel(2,j)
445  j3=kel(3,j)
446  j4=kel(4,j)
447 !
448 ! calculating the auxiliary fields xmm1,xmm2,xmm3
449 !
450  xmm1(j)=xm1(j1,j2)*xm1(j3,j4)
451  xmm2(j)=xm2(j1,j2)*xm2(j3,j4)
452  xmm3(j)=xm3(j1,j2)*xm3(j3,j4)
453 !
454 ! calculating the auxiliary fields a and b
455 ! (Dhondt, G., The Finite Element Method for Three-
456 ! Dimensional Thermomechanical Applications, Wiley 2004,
457 ! formulae (4.203) and (4.204))
458 !
459  a(j)=(d(j3,j1)*d(j4,j2)+d(j3,j2)*d(j4,j1))/2.d0
460  & -xmm1(j)-xmm2(j)-xmm3(j)
461  b(j)=(d(j3,j1)*c(j4,j2)+d(j4,j1)*c(j3,j2)+
462  & d(j4,j2)*c(j1,j3)+d(j3,j2)*c(j1,j4))/2.d0
463  & -2.d0*(wc(1)*xmm1(j)+wc(2)*xmm2(j)+wc(3)*xmm3(j))
464 !
465 ! calculating the stiffness matrix
466 !
467  stiff(j)=2.d0*(dfla(1)*xmm1(j)+dfla(2)*xmm2(j)+
468  & dfla(3)*xmm3(j)
469  & +fla(1)*(cb(1)*b(j)+ca(1)*a(j))
470  & +fla(2)*(cb(2)*b(j)+ca(2)*a(j))
471  & +fla(3)*(cb(3)*b(j)+ca(3)*a(j)))
472  enddo
473 c if(iint.eq.1) write(*,*) '3 diff stiff'
474 c if(iint.eq.1) write(*,100) (stiff(i),i=1,21)
475  endif
476  endif
477 !
478 c 100 format(6(1x,e11.4))
479 !
480  return
subroutine rs(nm, n, a, w, matz, z, fv1, fv2, ierr)
Definition: rs.f:27
Hosted by OpenAircraft.com, (Michigan UAV, LLC)