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

Go to the source code of this file.

Functions/Subroutines

subroutine umat_abaqus (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, istep, kinc, pnewdt, nmethod, iperturb)
 

Function/Subroutine Documentation

◆ umat_abaqus()

subroutine umat_abaqus ( 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,
integer  istep,
integer  kinc,
real*8  pnewdt,
integer  nmethod,
integer, dimension(*)  iperturb 
)
23 !
24 ! calculates stiffness and stresses for a nonlinear material
25 ! defined by an ABAQUS umat routine
26 !
27 ! icmd=3: calculates stress at mechanical strain
28 ! else: calculates stress at mechanical strain and the stiffness
29 ! matrix
30 !
31 ! INPUT:
32 !
33 ! amat material name
34 ! iel element number
35 ! iint integration point number
36 !
37 ! kode material type (-100-#of constants entered
38 ! under *USER MATERIAL): can be used for materials
39 ! with varying number of constants
40 !
41 ! elconloc(21) user defined constants defined by the keyword
42 ! card *USER MATERIAL (max. 21, actual # =
43 ! -kode-100), interpolated for the
44 ! actual temperature t1l
45 !
46 ! emec(6) Lagrange mechanical strain tensor (component order:
47 ! 11,22,33,12,13,23) at the end of the increment
48 ! (thermal strains are subtracted)
49 ! emec0(6) Lagrange mechanical strain tensor at the start of the
50 ! increment (thermal strains are subtracted)
51 ! beta(6) residual stress tensor (the stress entered under
52 ! the keyword *INITIAL CONDITIONS,TYPE=STRESS)
53 !
54 ! xokl(3,3) deformation gradient at the start of the increment
55 ! voj Jacobian at the start of the increment
56 ! xkl(3,3) deformation gradient at the end of the increment
57 ! vj Jacobian at the end of the increment
58 !
59 ! ithermal 0: no thermal effects are taken into account
60 ! >0: thermal effects are taken into account (triggered
61 ! by the keyword *INITIAL CONDITIONS,TYPE=TEMPERATURE)
62 ! t1l temperature at the end of the increment
63 ! dtime time length of the increment
64 ! time step time at the end of the current increment
65 ! ttime total time at the start of the current step
66 !
67 ! icmd not equal to 3: calculate stress and stiffness
68 ! 3: calculate only stress
69 ! ielas 0: no elastic iteration: irreversible effects
70 ! are allowed
71 ! 1: elastic iteration, i.e. no irreversible
72 ! deformation allowed
73 !
74 ! mi(1) max. # of integration points per element in the
75 ! model
76 ! nstate_ max. # of state variables in the model
77 !
78 ! xstateini(nstate_,mi(1),# of elements)
79 ! state variables at the start of the increment
80 ! xstate(nstate_,mi(1),# of elements)
81 ! state variables at the end of the increment
82 !
83 ! stre(6) Piola-Kirchhoff stress of the second kind
84 ! at the start of the increment
85 !
86 ! iorien number of the local coordinate axis system
87 ! in the integration point at stake (takes the value
88 ! 0 if no local system applies)
89 ! pgauss(3) global coordinates of the integration point
90 ! orab(7,*) description of all local coordinate systems.
91 ! If a local coordinate system applies the global
92 ! tensors can be obtained by premultiplying the local
93 ! tensors with skl(3,3). skl is determined by calling
94 ! the subroutine transformatrix:
95 ! call transformatrix(orab(1,iorien),pgauss,skl)
96 !
97 !
98 ! OUTPUT:
99 !
100 ! xstate(nstate_,mi(1),# of elements)
101 ! updated state variables at the end of the increment
102 ! stre(6) Piola-Kirchhoff stress of the second kind at the
103 ! end of the increment
104 ! stiff(21): consistent tangent stiffness matrix in the material
105 ! frame of reference at the end of the increment. In
106 ! other words: the derivative of the PK2 stress with
107 ! respect to the Lagrangian strain tensor. The matrix
108 ! is supposed to be symmetric, only the upper half is
109 ! to be given in the same order as for a fully
110 ! anisotropic elastic material (*ELASTIC,TYPE=ANISO).
111 !
112 ! This routine allows for the use of an ABAQUS umat user subroutine
113 ! in CalculiX.
114 !
115 ! Note that the following fields are not supported
116 ! so far: sse,spd,scd,rpl,ddsddt,drplde,drpldt,predef,
117 ! dpred,drot,pnewdt,celent,layer,kspt
118 !
119 ! Furthermore, the following fields have a different meaning in
120 ! ABAQUS and CalculiX:
121 !
122 ! stran: in CalculiX: Lagrangian strain tensor
123 ! in ABAQUS: logarithmic strain tensor
124 ! dstran: in CalculiX: Lagrangian strain increment tensor
125 ! in ABAQUS: logarithmic strain increment tensor
126 ! temp: in CalculiX: temperature at the end of the increment
127 ! in ABAQUS: temperature at the start of the increment
128 ! dtemp: in CalculiX: zero
129 ! in ABAQUS: temperature increment
130 !
131 ! Because of this, this routine should only be used for small
132 ! deformations and small rotations (in that case all strain
133 ! measures basically reduce to the infinitesimal strain).
134 !
135  implicit none
136 !
137  character*80 amat
138 !
139  integer ithermal,icmd,kode,ielas,iel,iint,nstate_,mi(*),i,
140  & iorien,nmethod,iperturb(*),istep,
141  & ndi,nshr,ntens,nprops,layer,kspt,jstep(4),kinc,kal(2,6),
142  & kel(4,21),j1,j2,j3,j4,j5,j6,j7,j8,jj
143 !
144  real*8 elconloc(21),stiff(21),emec(6),emec0(6),beta(6),stre(6),
145  & vj,t1l,dtime,xkl(3,3),xokl(3,3),voj,pgauss(3),orab(7,*),
146  & time,ttime,skl(3,3),xa(3,3),ya(3,3,3,3),xstate(nstate_,mi(1),*),
147  & xstateini(nstate_,mi(1),*)
148 !
149  real*8 ddsdde(6,6),sse,spd,scd,rpl,ddsddt(6),drplde(6),
150  & drpldt,stran(6),dstran(6),abqtime(2),predef,temp,dtemp,
151  & dpred,drot(3,3),celent,pnewdt
152 !
153  kal=reshape((/1,1,2,2,3,3,1,2,1,3,2,3/),(/2,6/))
154 !
155  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,
156  & 1,1,1,2,2,2,1,2,3,3,1,2,1,2,1,2,1,1,1,3,2,2,1,3,
157  & 3,3,1,3,1,2,1,3,1,3,1,3,1,1,2,3,2,2,2,3,3,3,2,3,
158  & 1,2,2,3,1,3,2,3,2,3,2,3/),(/4,21/))
159 !
160  drot=reshape((/1.d0,0.d0,0.d0,0.d0,1.d0,0.d0,0.d0,0.d0,1.d0/),
161  & (/3,3/))
162 !
163 ! filling field jstep
164 !
165  jstep(1)=istep
166  jstep(2)=nmethod
167  jstep(3)=iperturb(2)
168  if(iperturb(1).eq.1) then
169  jstep(4)=1
170  else
171  jstep(4)=0
172  endif
173 !
174 ! calculating the mechanical strain
175 !
176  do i=1,6
177  stran(i)=emec0(i)
178  dstran(i)=emec(i)-emec0(i)
179  enddo
180 !
181  ntens=6
182 !
183  do i=1,nstate_
184  xstate(i,iint,iel)=xstateini(i,iint,iel)
185  enddo
186 !
187  abqtime(1)=time-dtime
188  abqtime(2)=ttime+time-dtime
189 !
190  temp=t1l
191  dtemp=0.d0
192 !
193  ndi=3
194  nshr=3
195  ntens=ndi+nshr
196 !
197  nprops=-kode-100
198 c nprops=21
199 !
200 ! taking local material orientations into account
201 !
202  if(iorien.ne.0) then
203  call transformatrix(orab(1,iorien),pgauss,skl)
204 !
205 ! rotating the stress into the local system
206 !
207  xa(1,1)=stre(1)
208  xa(1,2)=stre(4)
209  xa(1,3)=stre(5)
210  xa(2,1)=stre(4)
211  xa(2,2)=stre(2)
212  xa(2,3)=stre(6)
213  xa(3,1)=stre(5)
214  xa(3,2)=stre(6)
215  xa(3,3)=stre(3)
216 !
217  do jj=1,6
218  stre(jj)=0.d0
219  j1=kal(1,jj)
220  j2=kal(2,jj)
221  do j3=1,3
222  do j4=1,3
223  stre(jj)=stre(jj)+
224  & xa(j3,j4)*skl(j3,j1)*skl(j4,j2)
225  enddo
226  enddo
227  enddo
228 !
229 ! rotating the strain into the local system
230 !
231  xa(1,1)=stran(1)
232  xa(1,2)=stran(4)
233  xa(1,3)=stran(5)
234  xa(2,1)=stran(4)
235  xa(2,2)=stran(2)
236  xa(2,3)=stran(6)
237  xa(3,1)=stran(5)
238  xa(3,2)=stran(6)
239  xa(3,3)=stran(3)
240 !
241  do jj=1,6
242  stran(jj)=0.d0
243  j1=kal(1,jj)
244  j2=kal(2,jj)
245  do j3=1,3
246  do j4=1,3
247  stran(jj)=stran(jj)+
248  & xa(j3,j4)*skl(j3,j1)*skl(j4,j2)
249  enddo
250  enddo
251  enddo
252 !
253 ! rotating the strain increment into the local system
254 !
255  xa(1,1)=dstran(1)
256  xa(1,2)=dstran(4)
257  xa(1,3)=dstran(5)
258  xa(2,1)=dstran(4)
259  xa(2,2)=dstran(2)
260  xa(2,3)=dstran(6)
261  xa(3,1)=dstran(5)
262  xa(3,2)=dstran(6)
263  xa(3,3)=dstran(3)
264 !
265  do jj=1,6
266  dstran(jj)=0.d0
267  j1=kal(1,jj)
268  j2=kal(2,jj)
269  do j3=1,3
270  do j4=1,3
271  dstran(jj)=dstran(jj)+
272  & xa(j3,j4)*skl(j3,j1)*skl(j4,j2)
273  enddo
274  enddo
275  enddo
276  endif
277 !
278 ! changing physical strain into engineering strain
279 !
280  do i=4,6
281  stran(i)=2.d0*stran(i)
282  dstran(i)=2.d0*dstran(i)
283  enddo
284 !
285  if(amat(1:1).eq.'@') then
286 !
287  call call_external_umat(stre,xstate(1,iint,iel),ddsdde,
288  & sse,spd,scd,rpl,ddsddt,drplde,drpldt,stran,dstran,
289  & abqtime,dtime,temp,dtemp ,predef,dpred,amat,ndi,nshr,
290  & ntens,nstate_,elconloc,nprops,pgauss,drot,pnewdt,
291  & celent,xokl,xkl,iel,iint,layer,kspt,jstep,kinc)
292 !
293  else
294 !
295  call umat(stre,xstate(1,iint,iel),ddsdde,sse,spd,scd,rpl,
296  & ddsddt,drplde,drpldt,stran,dstran,abqtime,dtime,temp,
297  & dtemp,predef,dpred,amat,ndi,nshr,ntens,nstate_,elconloc,
298  & nprops,pgauss,drot,pnewdt,celent,xokl,xkl,iel,iint,layer,
299  & kspt,jstep,kinc)
300 !
301  endif
302 !
303 ! taking local material orientations into account
304 !
305  if(iorien.ne.0) then
306 !
307 ! rotating the stress into the global system
308 !
309  xa(1,1)=stre(1)
310  xa(1,2)=stre(4)
311  xa(1,3)=stre(5)
312  xa(2,1)=stre(4)
313  xa(2,2)=stre(2)
314  xa(2,3)=stre(6)
315  xa(3,1)=stre(5)
316  xa(3,2)=stre(6)
317  xa(3,3)=stre(3)
318 !
319  do jj=1,6
320  stre(jj)=0.d0
321  j1=kal(1,jj)
322  j2=kal(2,jj)
323  do j3=1,3
324  do j4=1,3
325  stre(jj)=stre(jj)+
326  & xa(j3,j4)*skl(j1,j3)*skl(j2,j4)
327  enddo
328  enddo
329  enddo
330  endif
331 !
332 ! calculate the stiffness matrix (the matrix is symmetrized)
333 !
334  if(icmd.ne.3) then
335  stiff(1)=ddsdde(1,1)
336  stiff(2)=(ddsdde(1,2)+ddsdde(2,1))/2.d0
337  stiff(3)=ddsdde(2,2)
338  stiff(4)=(ddsdde(1,3)+ddsdde(3,1))/2.d0
339  stiff(5)=(ddsdde(2,3)+ddsdde(3,2))/2.d0
340  stiff(6)=ddsdde(3,3)
341  stiff(7)=(ddsdde(1,4)+ddsdde(4,1))/2.d0
342  stiff(8)=(ddsdde(2,4)+ddsdde(4,2))/2.d0
343  stiff(9)=(ddsdde(3,4)+ddsdde(4,3))/2.d0
344  stiff(10)=ddsdde(4,4)
345  stiff(11)=(ddsdde(1,5)+ddsdde(5,1))/2.d0
346  stiff(12)=(ddsdde(2,5)+ddsdde(5,2))/2.d0
347  stiff(13)=(ddsdde(3,5)+ddsdde(5,3))/2.d0
348  stiff(14)=(ddsdde(4,5)+ddsdde(5,4))/2.d0
349  stiff(15)=ddsdde(5,5)
350  stiff(16)=(ddsdde(1,6)+ddsdde(6,1))/2.d0
351  stiff(17)=(ddsdde(2,6)+ddsdde(6,2))/2.d0
352  stiff(18)=(ddsdde(3,6)+ddsdde(6,3))/2.d0
353  stiff(19)=(ddsdde(4,6)+ddsdde(6,4))/2.d0
354  stiff(20)=(ddsdde(5,6)+ddsdde(6,5))/2.d0
355  stiff(21)=ddsdde(6,6)
356 !
357  if(iorien.ne.0) then
358 !
359 ! rotating the stiffness coefficients into the global system
360 !
361  call anisotropic(stiff,ya)
362 !
363  do jj=1,21
364  j1=kel(1,jj)
365  j2=kel(2,jj)
366  j3=kel(3,jj)
367  j4=kel(4,jj)
368  stiff(jj)=0.d0
369  do j5=1,3
370  do j6=1,3
371  do j7=1,3
372  do j8=1,3
373  stiff(jj)=stiff(jj)+ya(j5,j6,j7,j8)*
374  & skl(j1,j5)*skl(j2,j6)*skl(j3,j7)*skl(j4,j8)
375  enddo
376  enddo
377  enddo
378  enddo
379  enddo
380  endif
381  endif
382 !
383  return
subroutine umat(stress, statev, ddsdde, sse, spd, scd, rpl, ddsddt, drplde, drpldt, stran, dstran, time, dtime, temp, dtemp, predef, dpred, cmname, ndi, nshr, ntens, nstatv, props, nprops, coords, drot, pnewdt, celent, dfgrd0, dfgrd1, noel, npt, layer, kspt, kstep, kinc)
Definition: umat.f:24
subroutine transformatrix(xab, p, a)
Definition: transformatrix.f:20
subroutine anisotropic(anisol, anisox)
Definition: anisotropic.f:20
Hosted by OpenAircraft.com, (Michigan UAV, LLC)