100% found this document useful (2 votes)
3K views6 pages

UMAT

Umat for Abaqus, von Mises, isotropic hardening 12 state variables, three for \mu, \kappa and the conjugated thermodynamic force for internal plastic variable, and nine for plastic strain tensor 4 material properties, E, \nu, H (hardening\softening) and yield stress

Uploaded by

shahriar_B
Copyright
© Attribution Non-Commercial (BY-NC)
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as PDF, TXT or read online on Scribd
100% found this document useful (2 votes)
3K views6 pages

UMAT

Umat for Abaqus, von Mises, isotropic hardening 12 state variables, three for \mu, \kappa and the conjugated thermodynamic force for internal plastic variable, and nine for plastic strain tensor 4 material properties, E, \nu, H (hardening\softening) and yield stress

Uploaded by

shahriar_B
Copyright
© Attribution Non-Commercial (BY-NC)
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as PDF, TXT or read online on Scribd
You are on page 1/ 6

Shahriyar Beizaee

C Written by Shahriyar Beizaee


C [email protected]
SUBROUTINE UMAT(STRESS, STATEV, DDSDDE, SSE, SPD, SCD, RPL,
1 DDSDDT, DRPLDE, DRPLDT, STRAN, DSTRAN, TIME, DTIME, TEMP, DTEMP,
2 PREDEF, DPRED, CMNAME, NDI, NSHR, NTENS, NSTATV, PROPS, NPROPS,
3 COORDS, DROT, PNEWDT, CELENT, DFGRD0, DFGRD1, NOEL, NPT, LAYER,
4 KSPT, KSTEP, KINC)
C
INCLUDE 'ABA_PARAM.INC'
C
CHARACTER*8 CMNAME
DIMENSION STRESS(NTENS), STATEV(NSTATV), DDSDDE(NTENS, NTENS),
1 DDSDDT(NTENS), DRPLDE(NTENS), STRAN(NTENS), DSTRAN(NTENS),
2 PREDEF(1), DPRED(1), PROPS(NPROPS), COORDS(3), DROT(3, 3),
3 DFGRD0(3, 3), DFGRD1(3, 3)
C------------------------------------------------------------------------------C
Matrices
DOUBLE PRECISION E_tang(9,9),state_new(12),state_old(12),
1 eps(9,1),oldeps(9,1),sig(9,1),oldsig(9,1),oldmu,mu,kap,oldkap,
2 K_p,oldK_p,E,nu,H,m1,sig_y,p1,K,G,v1(9,1),eye(9,9),p2,
3 Idev(9,9),shear(9,9),vol(9,9),Ee(9,9),v1v1T(9,9),v1T(1,9),
4 I2(9,9),I2dev(9,9),eps_p(9,1),oldeps_p(9,1),K_tr,norm_S_tr
DOUBLE PRECISION sig_tr(9,1),deps(9,1),S_tr(9,1),J2_tr,phi_tr
DOUBLE PRECISION sig_eq,S(9,1),n(9,1),phi,H_tmp,n_T(1,1:9),c
DOUBLE PRECISION norm_S,J2,h22,h_tmp1(1,9),sig_eq_tr,sig_m
DOUBLE PRECISION cnst1,cnst2,pi,Q(3,3),Q_ep(3,3),N1,N2,th
DOUBLE PRECISION Et(9,9),detQ,detQ_ep,Q2,eps_dev(9,1)
DOUBLE PRECISION norm_eps_dev,ee1
INTEGER i,j,cnt,chk1,chk2
C-----------------------------------------C
Configuration
C
C--------- setting initial STATEV -----if (Time .EQ. 0.0) then
state_old(1:12)=0.0
else
state_old(1:12)=STATEV(1:12)
end if
oldmu=state_old(1)
oldK_p=state_old(2)
oldkap=state_old(3)
oldeps_p(1:9,1)=state_old(4:12)
C----------- setting the matrices to zero -----deps(1:9,1)=0.0d0
oldeps(1:9,1)=0.0d0
oldsig(1:9,1)=0.0d0
sig(1:9,1)=0.0d0
eps(1:9,1)=0.0d0
eps_p(1:9,1)=0.0d0
oldeps_p(1:9,1)=0.0d0
sig_tr(1:9,1)=0.0d0
S_tr(1:9,1)=0.0d0
-

Shahriyar Beizaee

S(1:9,1)=0.0d0
n(1:9,1)=0.0d0
n_T(1,1:9)=0.0d0
h_tmp1(1,1:9)=0.0d0
Idev(1:9,1:9)=0.0d0
Et(1:9,1:9)=0.d0
eps_dev(1:9,1)=0.0d0
C---------- getting data from Abaqus ---------oldsig(1:6,1)=STRESS(1:NTENS)
oldsig(7:9,1)=oldsig(4:6,1)
oldeps(1:6,1)=STRAN(1:NTENS)
oldeps(7:9,1)=oldeps(4:6,1)
deps(1:6,1)=DSTRAN(1:NTENS)
deps(7:9,1)=deps(4:6,1)
oldeps_p(1:9,1)=state_old(4:12)
C------------ material properties from Abaqus ------E=PROPS(1)
nu=PROPS(2)
H=PROPS(3)
sig_y=PROPS(4)
C-------------- building Ee -------------------K=E/(3.0d0*(1.0d0-2.0d0*nu))
G=E/(2.0d0*(1.0d0+nu))
v1(1:9,1)=(/1.0d0,1.0d0,1.0d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0/)
eye(1:9,1:9)=0
Do i=1,9
Do j=1,9
if (i.EQ.j) then
eye(i,j)=1.0d0
if (i<4) then
I2(i,j)=1.0d0
else
I2(i,j)=0.50d0
end if
end if
End do
End do
call Trans(v1,v1T,9)
v1v1T=matmul(v1,v1T)
Do j=1,9
Do i=1,9
Idev(i,j)=eye(i,j)-(1.0d0/3.0d0)*v1v1T(i,j)
I2dev(i,j)=I2(i,j)-(1.0d0/3.0d0)*v1v1T(i,j)
End do
End do
Do j=1,9
Do i=1,9
shear(i,j)=2.0d0*G*I2dev(i,j)
vol(i,j)=K*v1v1T(i,j)
Ee(i,j)=shear(i,j)+vol(i,j)
End do
End do
C--------- creating trial values -----------------

Shahriyar Beizaee

sig_tr(1:9,1)=oldsig(1:9,1)+matmul(Ee(1:9,1:9),deps(1:9,1))
K_tr=oldK_p
eps=oldeps+deps
eps_dev=matmul(Idev,eps)
call norm(eps_dev,norm_eps_dev,9)
ee1=(2.0d0/3.0d0)*norm_eps_dev
S_tr=matmul(Idev,sig_tr)
call norm(S_tr,norm_S_tr,9)
J2_tr=0.5d0*(norm_S_tr**2.0d0)
Phi_tr=sqrt(3.0d0*J2_tr)-(sig_y+K_tr)
C------------- check if it is plastic or elastic -------if (phi_tr.LT.0) then
eps_p(1:9,1)=oldeps_p(1:9,1)
E_tang=Ee
sig(1:9,1)=sig_tr(1:9,1)
mu=oldmu
kap=oldkap
K_p=oldK_p
else
C--------------- Plastic -----mu=phi_tr/(3.0d0*G+H)
sig_eq_tr=sqrt(3.0d0*J2_tr)
sig_eq=sig_eq_tr-3.0d0*G*mu
c=1-mu*3.0d0*G/sig_eq_tr
S(1:9,1)=S_tr(1:9,1)*c
sig_m=(sig_tr(1,1)+sig_tr(2,1)+sig_tr(3,1))/3.0d0
sig(1:9,1)=S(1:9,1)+v1(1:9,1)*sig_m
n(1:9,1)=(3.0d0/(2.0d0*sig_eq_tr))*S_tr(1:9,1)
eps_p(1:9,1)=oldeps_p(1:9,1)+mu*n(1:9,1)
kap=oldkap+mu
K_p=H*kap
call Trans(n(1:9,1),n_T(1,1:9),9)
cnst1=((2.0d0*G/(3.0d0*G+H))*((oldkap+sig_y)/sig_eq_tr))
cnst2=(2.0d0*G)*(mu*3.0d0*G/sig_eq_tr)
E_tang=Ee-(2.0d0*G)*cnst1*matmul(n,n_T)+cnst2*I2dev
end if
DDSDDE=E_tang(1:6,1:6)
STRESS=sig(1:6,1)
STATEV(1)=mu
STATEV(2)=K_p
STATEV(3)=kap
STATEV(4:12)=eps_p(1:9,1)
if (NOEL.EQ.1) then
if (NPT.EQ.1) then
print *, Time
end if
end if
SSE=0
SPD=0
SCD=0
RETURN
END
C--------------------------------------------

Shahriyar Beizaee

SUBROUTINE Trans(vec,vecT,n)
vec(n,1) vecT(1,n)
implicit none
double precision, INTENT (IN) :: vec(n,1)
double precision, INTENT (OUT) :: vecT(1,n)
integer ii,n
vecT(1,1:n)=0
do ii=1,n
vecT(1,ii)=vec(ii,1)
End do
End
C---------------------------------------------SUBROUTINE detM(A,detA)
implicit none
double precision A(3,3),detA
detA=0
detA=A(1,1)*A(2,2)*A(3,3)+A(1,2)*A(2,3)*A(3,1)+
1 A(1,3)*A(2,1)*A(3,2)-A(1,1)*A(2,3)*A(3,2)2 A(1,2)*A(2,1)*A(3,3)-A(1,3)*A(2,2)*A(3,1)
end
C---------------------------------------------SUBROUTINE MATINV(N1,N2,A,AINV)
C Download URL: http://wp.me/p61TQ-zb
C Last modified: 2011/07/19
C

C A general purpose matrix inverter by augmenting-pivoting technique:


C
C
C

A B C | 1 0 0
D E F | 0 1 0
G H I | 0 0 1

=>

1 0 0 | J K L
0 1 0 | M N O
0 0 1 | P Q R

C Based on a lecture by Prof. McFarland


C http://math.uww.edu/~mcfarlat/inverse.htm
C Explanation of passed parameters:
C
N1: lower dimension of square matrix
C
N2: upper dimension of square matrix
C
A: square matrix of dimension N1:N2,N1:N2 to be inverted
C
AINV: the inverted matrix
IMPLICIT NONE
!N2-N1+1
INTEGER I,J,K,N1,N2
double precision A(N1:N2,N1:N2),AINV(N1:N2,N1:N2),
1 B(N1:N2,N1:2*N2-N1+1),PIVOT,XNUM

INITIALIZATION
DO I=N1,N2
DO J=N1,N2
AINV(I,J)=0.0D0
END DO
END DO

Shahriyar Beizaee

C MAKE AUGMENTED MATRIX


DO I=N1,N2
DO J=N1,N2
B(I,J)=0.0D0
B(I,J+N2-N1+1)=0.0D0
B(I,J)=A(I,J)
IF(I.EQ.J) THEN
B(I,J+N2-N1+1)=1.0D0
END IF
END DO
END DO
DO I=N1,N2
C CHOOSE THE LEFTMOST NON-ZERO ELEMENT AS PIVOT
DO J=N1,N2
IF(DABS(B(I,J)).GT.0)THEN
PIVOT=B(I,J)
EXIT
END IF
END DO
C STEP 1: Change the chosen pivot into "1" by dividing
C the pivot's row by the pivot number
DO J=N1,2*N2-N1+1
B(I,J)=B(I,J)/PIVOT
END DO
PIVOT=B(I,I) !UPDATE PIVOT VALUE
C STEP 2: Change the remainder of the pivot's COLUMN into 0's
C by adding to each row a suitable multiple of the PIVOT ROW
DO K=N1,N2 !ROW
IF(K.NE.I) THEN
XNUM=B(K,I)/PIVOT !SAME COLUMN WITH THE CURRENT PIVOT
DO J=N1,2*N2-N1+1 !COL
B(K,J)=B(K,J)-XNUM*B(I,J)
END DO
END IF
END DO
END DO
C PREPARE THE FINAL INVERTED MATRIX
DO I=N1,N2
DO J=N1,N2
AINV(I,J)=B(I,J+N2-N1+1)
END DO
END DO
RETURN
END
C-----------------------------------------------------------

Shahriyar Beizaee

SUBROUTINE norm(vector,scalar,n)
implicit none
double precision vector(n,1),scalar
Integer ii,n
scalar=0
Do ii=1,n
scalar=scalar+vector(ii,1)**2
End do
scalar=sqrt(scalar)
Return
End
C---------------------------------------------subroutine zarb(a,b,c,n)
implicit none
double precision a(1,n),b(n,1),c
integer ii,n
c=0.0
do ii=1,n
c=c+a(1,ii)*b(ii,1)
end do
end
c----------------------------------------------

You might also like