Add scripts and inp files.

This commit is contained in:
James Grogan 2024-05-13 20:50:21 +01:00
parent ad937f2602
commit e19f869a1e
390 changed files with 6580687 additions and 10 deletions

View file

@ -0,0 +1,280 @@
c Abaqus User Defined Material Subroutine - J. Grogan, 2011
c -------------------------------------------------------------------
subroutine vumat (
c Read only -
* nblock,ndir,nshr,nstatev,nfieldv,nprops,lanneal,stepTime,
* totalTime,dt,cmname,coordMp,charLength,props,density,
* strainInc,relSpinInc,tempOld,stretchOld,defgradOld,
* fieldOld,stressOld, stateOld, enerInternOld,enerInelasOld,
* tempNew, stretchNew, defgradNew, fieldNew,
c Write only -
* stressNew, stateNew, enerInternNew, enerInelasNew )
c
include 'vaba_param.inc'
c
dimension coordMp(nblock,3),charLength(nblock),props(nprops),
1 strainInc(nblock,ndir+nshr),stressOld(nblock,ndir+nshr),
2 stateOld(nblock,nstatev),stressNew(nblock,ndir+nshr),
3 stateNew(nblock,nstatev),astr(nblock,ndir+nshr),
4 rKE(3,3),enerInternNew(nblock), enerInternOld(nblock),
5 density(nblock)
c
character*80 cmname
c
parameter (zero = 0.d0, one = 1.d0, two = 2.d0, three = 3.d0,
* four = 4.d0,third = 1.d0 / 3.d0, half = 0.5d0, op5 = 1.5d0)
c -------------------------------------------------------------------
c Common blocks store element status and random number assigment.
common active(400000)
common randnum(400000)
integer active
integer iseed(1)
real randnum
c
do k=1,nblock
c -------------------------------------------------------------------
c Update SDVs
do i=1,9
stateNew(k,i)=stateOld(k,i)
enddo
do i=23,30
stateNew(k,i)=stateOld(k,i)
enddo
c -------------------------------------------------------------------
c Get meterial properties from INP file and form 'C' matrix
e = props(1)
xnu = props(2)
syield=props(3)
b=props(4)
q=props(5)
twomu = e / ( one + xnu )
thremu = op5 * twomu
alamda = xnu * twomu / ( one - two * xnu )
trace=strainInc(k,1)+strainInc(k,2)+strainInc(k,3)
c -------------------------------------------------------------------
c Linear elastic material for Abq/Explicit Packager
if(abs(steptime)<=0.d0)then
do i=1,3
stressNew(k,i)=stressOld(k,i)
* +twomu*strainInc(k,i)+alamda*trace
enddo
do i=4,6
stressNew(k,i)=stressOld(k,i)+twomu*strainInc(k,i)
enddo
else
c -------------------------------------------------------------------
if(totaltime==dt)then
iseed=int(statenew(k,8)*5.74)+int(coordmp(k,1)*1000.)
call random_seed(put=iseed)
call random_number(rand_ini)
stateNew(k,30)=(-log(1.d0-rand_ini))**(1.d0/0.14)
stateNew(k,30)=stateNew(k,30)/1800000.d0
endif
c Get Actual Trial Stress
do i=1,3
astr(k,i)=stateOld(k,9+i)
* +twomu*strainInc(k,i)+alamda*trace
enddo
do i=4,6
astr(k,i)=stateOld(k,9+i)+twomu*strainInc(k,i)
enddo
c -------------------------------------------------------------------
c Partially Convert to Voigt Form
smean = third*(astr(k,1)+astr(k,2)+astr(k,3))
s11 = astr(k,1) - smean
s22 = astr(k,2) - smean
s33 = astr(k,3) - smean
c -------------------------------------------------------------------
c Get Von Mises Stress
stateNew(k,19)=sqrt(op5*(s11*s11+s22*s22+s33*s33
* +two*astr(k,4)*astr(k,4)+two*astr(k,5)*astr(k,5)
* +two*astr(k,6)*astr(k,6)))
c -------------------------------------------------------------------
c Get Max Prin Stress
rKE(1,1)=s11
rKE(2,2)=s22
rKE(3,3)=s33
rKE(1,2)=astr(k,4)
rKE(2,1)=astr(k,4)
rKE(2,3)=astr(k,5)
rKE(3,2)=astr(k,5)
rKE(1,3)=astr(k,6)
rKE(3,1)=astr(k,6)
rq=s11*s22*s33
rq=rq+2.d0*rKE(1,2)*rKE(2,3)*rKE(1,3)
rq=rq-rKE(1,1)*rKE(2,3)*rKE(2,3)
rq=rq-rKE(2,2)*rKE(1,3)*rKE(1,3)
rq=rq-rKE(3,3)*rKE(1,2)*rKE(1,2)
rq=rq/2.d0
p=0.d0
do i=1,3
do j=1,3
p=p+rKE(i,j)*rKE(i,j)
enddo
enddo
p=p/6.d0
if(p<1.e-6)then
phi=(1.d0/3.d0)*(acos(0.d0)/2.d0)
else
if(abs(rq)>abs(p**(1.5)))then
phi=0.d0
else
phi=(1.d0/3.d0)*acos(rq/p**(1.5))
endif
endif
if(phi<0.)then
phi=phi+acos(0.d0)/3.d0
endif
eig1=smean+2.d0*sqrt(p)*cos(phi)
eig2=smean-sqrt(p)*(cos(phi)+sqrt(3.d0)*sin(phi))
eig3=smean-sqrt(p)*(cos(phi)-sqrt(3.d0)*sin(phi))
stateNew(k,16)=max(eig1,eig2,eig3)
c -------------------------------------------------------------------
c Recover Yield Surface
if(stateOld(k,17)<=0.d0)then
yieldOld=syield
else
yieldOld=stateOld(k,17)
endif
c -------------------------------------------------------------------
c Update Hardening Parameters
rold=q*(one-exp(-b*stateOld(k,18)))
hard=b*(q-rold)
c -------------------------------------------------------------------
c Get equivalent plastic strain increment
sigdif = stateNew(k,19) - yieldOld
facyld = zero
if(sigdif.gt.zero)facyld=one
deqps=facyld*sigdif/(thremu+hard)
c -------------------------------------------------------------------
c Update Yield Surface and Eq. Plastic Strain
yieldNew = yieldOld + hard * deqps
stateNew(k,18) = stateOld(k,18) + deqps
stateNew(k,17)= yieldNew
c -------------------------------------------------------------------
c Get Correction Factor for Trial Stress
factor = yieldNew / ( yieldNew + thremu * deqps )
c -------------------------------------------------------------------
c Determine Actual Stress
stateNew(k,10) = s11 * factor + smean
stateNew(k,11) = s22 * factor + smean
stateNew(k,12) = s33 * factor + smean
stateNew(k,13) = astr(k,4) * factor
stateNew(k,14) = astr(k,5) * factor
stateNew(k,15) = astr(k,6) * factor
c -------------------------------------------------------------------
c Update Damage Parameter
if(totaltime>=1.5)then
call apply_damage(stateOld,stateNew,k,nblock,
* nstatev,randnum,charlength,props,nprops,dt,
* active,steptime,totaltime)
endif
c -------------------------------------------------------------------
c Determine Element Stress (Returned to Abaqus)
c Element Stress = Material Stress*(1-D)
do i=1,6
stressNew(k,i)=stateNew(k,9+i)*(one-statenew(k,21))
enddo
endif
C Update the specific internal energy -
stressPower = half * (
1 ( stressOld(k,1)+stressNew(k,1) )*strainInc(k,1)
1 + ( stressOld(k,2)+stressNew(k,2) )*strainInc(k,2)
1 + ( stressOld(k,3)+stressNew(k,3) )*strainInc(k,3)
1 + two*( stressOld(k,4)+stressNew(k,4) )*strainInc(k,4) )
C
enerInternNew(k) = enerInternOld(k)+ stressPower / density(k)
c
end do
return
end subroutine vumat
c -------------------------------------------------------------------
c
c This subroutine updates the value of the damage parameter based on
c corrosion and/or ductile damage evolution. J. Grogan, 2011.
c
subroutine apply_damage(stateOld,stateNew,k,nblock,nstatev,
* rrandnum,charlength,props,nprops,dt,iactive,steptime,
* totaltime)
c
include 'vaba_param.inc'
c
dimension stateNew(nblock,nstatev),charlength(nblock)
dimension props(nprops),stateOld(nblock,nstatev)
c -------------------------------------------------------------------
c Taken from values stored in common blocks in VUMAT
dimension iactive(400000)
dimension rrandnum(400000)
c -------------------------------------------------------------------
c Determine Characteristic Element Length
e_length=charlength(k)
c -------------------------------------------------------------------
c Recover value of damage parameter
if(stateOld(k,21)>0.)then
damage=stateOld(k,21)
else
damage=0.
endif
c -------------------------------------------------------------------
c Check if element is on exposed surface.
do i=1,6
icycle=0
c
c If any surrounding elements have been deleted in the
c previous inc, the number of exposed faces (SDV9) increases.
if(iactive(stateNew(k,i))==1.)then
do j=1,6
c Previously deleted element numbers are
c stored in SDV 22-28.
if(stateNew(k,i)==stateNew(k,22+j))then
icycle=1
endif
enddo
if(icycle==1)then
cycle
endif
stateNew(k,9)=stateNew(k,9)+1.
stateNew(k,22+i)=stateNew(k,i)
c
c Current element assumes random number of deleted
c neighbouring element.
if(rrandnum(stateNew(k,i))>=stateNew(k,30))then
stateNew(k,30)=rrandnum(stateNew(k,i))*0.85d0
endif
endif
enddo
c -------------------------------------------------------------------
c Recover Corrosion Parameters
ukinetic=props(6)
stateNew(k,29)=ukinetic
rand_num=stateNew(k,30)
if((statenew(k,9)>0.99).or.(statenew(k,7)<6.))then
if(totaltime<3.)then
dam_inc=rand_num*(ukinetic/E_LENGTH)*dt
damage=damage+dam_inc
endif
endif
statenew(k,21)=damage
c -------------------------------------------------------------------
c Remove Fully Damaged Elements
if(statenew(k,18)>0.1515)then
damage=1.d0
endif
if(damage>=0.999)then
statenew(k,20)=0.
statenew(k,21)=1.
iactive(statenew(k,8))=1.d0
rrandnum(statenew(k,8))=statenew(k,30)
endif
c
return
end subroutine apply_damage
c -------------------------------------------------------------------

View file

@ -0,0 +1,394 @@
c User Subroutines for simulating corrosion in Abaqus/Explicit.
c
subroutine vumat (
c Read only -
* nblock,ndir,nshr,nstatev,nfieldv,nprops,lanneal,stepTime,
* totalTime,dt,cmname,coordMp,charLength,props,density,
* strainInc,relSpinInc,tempOld,stretchOld,defgradOld,
* fieldOld,stressOld, stateOld, enerInternOld,enerInelasOld,
* tempNew, stretchNew, defgradNew, fieldNew,
c Write only -
* stressNew, stateNew, enerInternNew, enerInelasNew )
c
c -------------------------------------------------------------------
include 'vaba_param.inc'
dimension strainInc(nblock,ndir+nshr),stressOld(nblock,ndir+nshr),
6 stressNew(nblock,ndir+nshr)
c
character*80 cmname
c
parameter (one = 1.d0, two = 2.d0)
c
if(steptime==0.)then
do k=1,nblock
e = 44000.
xnu = 0.3
twomu = e / ( one + xnu )
alamda = xnu * twomu / ( one - two * xnu )
c
trace=strainInc(k,1)+strainInc(k,2)+strainInc(k,3)
stressNew(k,1)=stressOld(k,1)
* +twomu*strainInc(k,1)+alamda*trace
stressNew(k,2)=stressOld(k,2)
* +twomu*strainInc(k,2)+alamda*trace
stressNew(k,3)=stressOld(k,3)
* +twomu*strainInc(k,3)+alamda*trace
stressNew(k,4)=stressOld(k,4)+twomu*strainInc(k,4)
stressNew(k,5)=stressOld(k,5)+twomu*strainInc(k,5)
stressNew(k,6)=stressOld(k,6)+twomu*strainInc(k,6)
enddo
else
c
call get_elem_con
endif
end subroutine
c
subroutine get_elem_con
include 'vaba_param.inc'
c
character*256 jobname,outdir,filename,input
common neighbour(400000,6,6)
common active(400000,2)
common active_temp(400000,2)
common ele(400000,9)
common cpr(400000)
common iseed(400000)
integer iseed
real cpr
integer neighbour
integer active
integer active_temp
integer ele
integer com_nodes
integer node_store(100)
integer output(6)
integer ipair(6)
integer notpair(6)
integer isize
c
c set-1 - 2288795
iseed=2288795
c set-2 - 752347
c iseed=752347
c set-3 - 100887
c iseed=100887
c set-4 - 9921267
c iseed=9921267
c set-5 - 57269
c iseed=57269
c
c Open INP file for reading.
c
call vgetjobname(jobname,lenjobname)
call vgetoutdir(outdir,lenoutdir)
filename=outdir(1:lenoutdir)//'\'//
* jobname(1:lenjobname)//'.inp'
open(unit=17,file=filename(1:lenoutdir+
* lenjobname+5),status='unknown')
filename=outdir(1:lenoutdir)//'\neighbours_'//
* jobname(1:lenjobname)//'.inc'
open(unit=18,file=filename(1:lenoutdir+lenjobname+
* 16),status='unknown')
filename=outdir(1:lenoutdir)//'\elsets_'//
* jobname(1:lenjobname)//'.inc'
open(unit=19,file=filename(1:lenoutdir+lenjobname+
* 12),status='unknown')
c
ncnt=0
nelcnt=0
icheck=1
c
c Skip down to *Element in INP File
c
do while (index(input,'*Element')==0)
read(17,'(a)')input
end do
c
c Read in Element Nodal Connectivity
c
do while(.true.)
read(17,*)input
if(index(input,'*')==0)then
backspace(17)
nelcnt=nelcnt+1
read(17,*)ele(nelcnt,1),ele(nelcnt,2),
* ele(nelcnt,3),ele(nelcnt,4),ele(nelcnt,5),
* ele(nelcnt,6),ele(nelcnt,7),ele(nelcnt,8),
* ele(nelcnt,9)
else
exit
endif
end do
c
isize=nelcnt
c Get Element Connectivity
call get_surf
c call random_seed(size=isize)
call random_seed(put=iseed(1:isize))
call random_number(cpr(1:isize))
c
do i=1,nelcnt
cpr(i)=(-log(1.d0-cpr(i)))**(1.d0/0.14)
enddo
write(18,*)'*INITIAL CONDITIONS,TYPE=SOLUTION'
do ele_loop1=1,nelcnt
num_neighbours=1
do ele_loop2=1,nelcnt
elecheck=0
com_nodes=0
do nlp1=2,9
do nlp2=2,9
if(ele(ele_loop2,nlp1)==ele(ele_loop1,nlp2))then
if(ele_loop1/=ele_loop2)then
com_nodes=com_nodes+1
node_store(com_nodes)=ele(ele_loop1,nlp2)
if(com_nodes==4)then
elecheck=1
! call vgetinternal('AADEGPART',ele
! * (ele_loop2,1),1,intnum2,jrcd)
! call vgetinternal('AADEGPART',ele
! * (ele_loop1,1),1,intnum1,jrcd)
intnum1=ele(ele_loop1,1)
intnum2=ele(ele_loop2,1)
neighbour(intnum1,num_neighbours,1)
* =intnum2
neighbour(intnum1,1,2)
* =num_neighbours
do i=1,4
neighbour(intnum1,num_neighbours,i+2)
* =node_store(i)
enddo
endif
end if
end if
enddo
enddo
if(elecheck==1)then
num_neighbours=num_neighbours+1
endif
enddo
int_point_num=intnum1
ipair=0
output=0
numpairs=0
c
c Determine which faces of an element are opposite each other
c
do i=1,num_neighbours-1
do k=1,num_neighbours-1
ibreak=0
if(i/=k)then
do m=1,6
if((i==ipair(m)).or.(k==ipair(m)))then
ibreak=1
endif
enddo
if(ibreak==1)then
cycle
endif
icheck=0
do j=1,4
do m=1,4
if(neighbour(int_point_num,i,j+2)==
* neighbour(int_point_num,k,m+2))then
icheck=1
endif
enddo
enddo
if (icheck==0)then
numpairs=numpairs+2
ipair(numpairs-1)=i
ipair(numpairs)=k
endif
endif
enddo
enddo
c
c Order SDV's in convenient format for Main Analysis
c
k=0
do i=1,num_neighbours-1
icheck=0
do j=1,numpairs
if(i==ipair(j))then
icheck=1
endif
enddo
if(icheck==0)then
k=k+1
notpair(k)=i
endif
enddo
do i=1,numpairs,2
output(i)=neighbour(int_point_num,ipair(i),1)
output(i+1)=neighbour(int_point_num,ipair(i+1),1)
if(int_point_num==13)then
print *,i
endif
enddo
do i=1,k
output(numpairs+i)=
* neighbour(int_point_num,notpair(i),1)
enddo
c
c Write output to Abaqus Input file for main analysis
c
c cpr=rand(0)
write(19,*)'*Elset, elset=e',int_point_num,
* ', instance=AADEGPART'
write(19,*)int_point_num,','
write(18,'(a,8(i6,a))')'e',int_point_num,',',
* output(1),',',output(2),',',output(3),',',output(4),',',
* output(5),',',output(6),',',numpairs/2,','
write(18,'(8(i6,a))')active(int_point_num,1),',',
* active(int_point_num,2),',',0,',',0,',',0,',',
* 0,',',0,',',0,','
write(18,'(8(i6,a))')0,',',0,',',0,',',0,',',1,',',
* 0,',',0,',',0,','
write(18,'(6(i6,a),f18.6)')0,',',0,',',0,',',0,',',0,',',
* 0,',',cpr(int_point_num)
enddo
call xplb_exit
return
end subroutine get_elem_con
c
c -------------------------------------------------------------------
c
c get_surf - This subroutine reads element numbers in any surface
c that has been named 'Corrosion'.
c
subroutine get_surf
include 'vaba_param.inc'
c
character*256 input,test_string,output
common neighbour(400000,6,6)
common active(400000,2)
common active_temp(400000,2)
common ele(400000,9)
common cpr(400000)
common iseed(400000)
integer iseed
real cpr
integer neighbour
integer active
integer active_temp
integer ele
c
num_active=0
c
c Find the first Corrosion keyword in the INP file
c
do while (index(input,'Corrosion')==0)
read(17,'(a)')input
end do
c
c For any *Surface definition with the Corrosion Keyword
c read in element numbers.
c
do while (index(input,'*Surface')==0)
if(index(input,'Corrosion')/=0)then
c
c If the generate keyword is found element numbering
c can be generated automatically.
c
if(index(input,'generate')/=0)then
read(17,'(3i)')isurf1,isurf2,isurf3
do i=isurf1,isurf2,isurf3
num_active=num_active+1
active(num_active,1)=i
enddo
else
c
c If not it must be generated manually. An entire line is
c read from file and then split into individual element
c number using ',' as a delimiter.
c
read(17,'(a)')input
do while(index(input,'*')==0)
index_left=1
do index_right=1,128
test_string=input(index_right:index_right)
if((test_string==',').or.
* (index_right==128))then
c Necessary to convert character input to
c Integer output.
write(output,*)input
* (index_left:index_right-1)
num_active=num_active+1
read(output,'(i)')ihold
active(num_active,1)=ihold
index_left=index_right+1
endif
enddo
read(17,'(a)')input
enddo
backspace(17)
endif
endif
read(17,'(a)')input
enddo
do i=1,num_active
call vgetinternal('AADEGPART',active(i,1),1,intnum,jrcd)
c active_temp(i,1)=intnum
active_temp(i,1)=active(i,1)
enddo
active=0
do i=1,num_active
c First Face Exposed
if(active(active_temp(i,1),2)==0)then
active(active_temp(i,1),1)=active(active_temp(i,1),1)+4
c Second Face Exposed
elseif(active(active_temp(i,1),2)==1)then
active(active_temp(i,1),1)=active(active_temp(i,1),1)+2
c Single Element Test - 2 Faces In Plane
c active(active_temp(i,1),1)=8
c Third Face Exposed
elseif(active(active_temp(i,1),2)==2)then
active(active_temp(i,1),1)=active(active_temp(i,1),1)+1
c Single Element Test - 3 Faces In Plane
C active(active_temp(i,1),1)=8
elseif(active(active_temp(i,1),2)==3)then
active(active_temp(i,1),1)=8
endif
active(active_temp(i,1),2)=active(active_temp(i,1),2)+1
c active(active_temp(i,1),11)=0
enddo
end subroutine get_surf
c
c -------------------------------------------------------------------
c
c vusdfld - This subroutine is neccesary due to a limitation in
c Abaqus/Explicit in which element numbering is not
c passed into VUMAT. It is generated here and passed
c into VUMAT as a state variable.
c
subroutine vusdfld(
* nblock,nstatev,nfieldv,nprops,ndir,nshr,jElem,kIntPt,
* kLayer,kSecPt,stepTime,totalTime,dt,cmname,coordMp,
* direct,T,charLength,props,stateOld,stateNew,field)
c
include 'vaba_param.inc'
c
dimension props(nprops),jElem(nblock),coordMp(nblock,*),
* direct(nblock,3,3),T(nblock,3,3),charLength(nblock),
* stateOld(nblock,nstatev),stateNew(nblock,nstatev),
* field(nblock,nfieldv)
c
character*80 cmname
c
do k = 1, nblock
statenew(k,17)=jElem(k)
field(k,1)=0.0
end do
c
return
end subroutine vusdfld
c
c -------------------------------------------------------------------

View file

@ -0,0 +1,253 @@
c Abaqus User Defined Material Subroutine - J. Grogan, 2011
c -------------------------------------------------------------------
subroutine vumat (
c Read only -
* nblock,ndir,nshr,nstatev,nfieldv,nprops,lanneal,stepTime,
* totalTime,dt,cmname,coordMp,charLength,props,density,
* strainInc,relSpinInc,tempOld,stretchOld,defgradOld,
* fieldOld,stressOld, stateOld, enerInternOld,enerInelasOld,
* tempNew, stretchNew, defgradNew, fieldNew,
c Write only -
* stressNew, stateNew, enerInternNew, enerInelasNew )
c
include 'vaba_param.inc'
c
dimension coordMp(nblock,3),charLength(nblock),props(nprops),
1 strainInc(nblock,ndir+nshr),stressOld(nblock,ndir+nshr),
2 stateOld(nblock,nstatev),stressNew(nblock,ndir+nshr),
3 stateNew(nblock,nstatev),astr(nblock,ndir+nshr),
4 rKE(3,3),enerInternNew(nblock), enerInternOld(nblock),
5 density(nblock)
c
character*80 cmname
c
parameter (zero = 0.d0, one = 1.d0, two = 2.d0, three = 3.d0,
* four = 4.d0,third = 1.d0 / 3.d0, half = 0.5d0, op5 = 1.5d0,
* max_elements=100000)
c -------------------------------------------------------------------
c Common blocks store element details for all elements.
common el_position_new(max_elements,3)
common el_position_old(max_elements,3)
common el_time_new(max_elements)
common el_time_old(max_elements)
common el_status_new(max_elements)
common el_status_old(max_elements)
c
integer el_status_new,el_status_old
real el_position_new,el_position_old,el_time_new,el_time_old
c
c SDV 16-SDV 2+16: Neighbour Labels
c SDV 1: Element Label
c SDV 2: Number of Neighbouring Elements
c SDV 3: Random Number Assignment
c SDV 4: Minimum Distance to Corrosion Surface
c SDV 5-10: Equivalent Stress Components
c SDV 11: VonMisses Stress
c SDV 12: Yield Stress
c SDV 13: PEEQ
c SDV 14: Damage
c SDV 15: Delete
c
do k=1,nblock
c -------------------------------------------------------------------
c Update SDVs
do i=1,stateOld(k,2)+15
stateNew(k,i)=stateOld(k,i)
enddo
c -------------------------------------------------------------------
c Get meterial properties from INP file and form 'C' matrix
e = props(1)
xnu = props(2)
syield=props(3)
b=props(4)
q=props(5)
twomu = e / ( one + xnu )
thremu = op5 * twomu
alamda = xnu * twomu / ( one - two * xnu )
trace=strainInc(k,1)+strainInc(k,2)+strainInc(k,3)
c -------------------------------------------------------------------
c Linear elastic material for Abq/Explicit Packager
if(abs(steptime)<=0.d0)then
do i=1,3
stressNew(k,i)=stressOld(k,i)
* +twomu*strainInc(k,i)+alamda*trace
enddo
do i=4,6
stressNew(k,i)=stressOld(k,i)+twomu*strainInc(k,i)
enddo
else
c -------------------------------------------------------------------
c Get Actual Trial Stress
do i=1,3
astr(k,i)=stateOld(k,4+i)
* +twomu*strainInc(k,i)+alamda*trace
enddo
do i=4,6
astr(k,i)=stateOld(k,4+i)
* +twomu*strainInc(k,i)
enddo
c -------------------------------------------------------------------
c Partially Convert to Voigt Form
smean = third*(astr(k,1)+astr(k,2)+astr(k,3))
s11 = astr(k,1) - smean
s22 = astr(k,2) - smean
s33 = astr(k,3) - smean
c -------------------------------------------------------------------
c Get Von Mises Stress
stateNew(k,11)=sqrt(
* op5*(s11*s11+s22*s22+s33*s33+
* two*astr(k,4)*astr(k,4)+
* two*astr(k,5)*astr(k,5)+
* two*astr(k,6)*astr(k,6)))
c -------------------------------------------------------------------
c Recover Yield Surface
if(stateOld(k,12)<=0.d0)then
yieldOld=syield
else
yieldOld=stateOld(k,12)
endif
c -------------------------------------------------------------------
c Update Hardening Parameters
rold=q*(one-exp(-b*stateOld(k,13)))
hard=b*(q-rold)
c -------------------------------------------------------------------
c Get equivalent plastic strain increment
sigdif = stateNew(k,11) - yieldOld
facyld = zero
if(sigdif.gt.zero)facyld=one
deqps=facyld*sigdif/(thremu+hard)
c -------------------------------------------------------------------
c Update Yield Surface and Eq. Plastic Strain
yieldNew = yieldOld + hard * deqps
stateNew(k,13) = stateOld(k,13) + deqps
stateNew(k,12)= yieldNew
c -------------------------------------------------------------------
c Get Correction Factor for Trial Stress
factor = yieldNew / ( yieldNew + thremu * deqps )
c -------------------------------------------------------------------
c Determine Actual Stress
stateNew(k,5) = s11 * factor + smean
stateNew(k,6) = s22 * factor + smean
stateNew(k,7) = s33 * factor + smean
stateNew(k,8) = astr(k,4) * factor
stateNew(k,9) = astr(k,5) * factor
stateNew(k,10) = astr(k,6) * factor
c -------------------------------------------------------------------
c Update Damage Parameter
if(totaltime>=0.0)then
tprev=totaltime-dt
tol=dt*0.1d0
c -------------------------------------------------------------------
c Determine Characteristic Element Length
e_length=charlength(k)
c ------------------------------------------------------------------
c Recover value of damage parameter
damage=stateOld(k,14)
c -------------------------------------------------------------------
c Get distance to exposed surface
distmin=stateOld(k,4)
num_nbr=stateold(k,2)
do i=1,num_nbr
tnew=el_time_new(stateold(k,i+15))
told=el_time_old(stateold(k,i+15))
istat=0
if((tnew>tprev-tol).and.(tnew<tprev+tol))then
nestat=el_status_new(stateold(k,i+15))
if(nestat==2)then
xnbr=el_position_new(stateold(k,i+15),1)
ynbr=el_position_new(stateold(k,i+15),2)
znbr=el_position_new(stateold(k,i+15),3)
istat=1
endif
elseif((told>tprev-tol).and.(told<tprev+tol))then
nestat=el_status_old(stateold(k,i+15))
if(nestat==2)then
xnbr=el_position_old(stateold(k,i+15),1)
ynbr=el_position_old(stateold(k,i+15),2)
znbr=el_position_old(stateold(k,i+15),3)
istat=1
endif
else
write(*,*)'TStamp',tprev,i,tnew,told
call xplb_exit
endif
if(istat==1)then
distance=sqrt(
* (xnbr-coordMP(k,1))*(xnbr-coordMP(k,1))+
* (ynbr-coordMP(k,2))*(ynbr-coordMP(k,2))+
* (znbr-coordMP(k,3))*(znbr-coordMP(k,3)))
if(distance<distmin)distmin=distance
endif
enddo
statenew(k,4)=distmin
b_dist=stateold(k,3)
c -------------------------------------------------------------------
c Recover Corrosion Parameters
isurf=0.
if(distmin<1.1*e_length)isurf=1.
ukinetic=props(6)
if(isurf==1)then
rprox=(1.1*e_length-distmin)/(1.1*e_length)
bprox=5*(1.1*e_length-b_dist)/(1.1*e_length)
if(bprox<0.)bprox=0.d0
ukinetic=ukinetic*(rprox+bprox)
if(totaltime<3.)then
dam_inc=(ukinetic/E_LENGTH)*dt
damage=damage+dam_inc
endif
endif
statenew(k,14)=damage
c -------------------------------------------------------------------
c Remove Fully Damaged Elements
if(statenew(k,13)>0.1515)then
damage=1.d0
endif
if(damage>=0.999)then
statenew(k,15)=0.
statenew(k,14)=1.
ielstat=2
else
ielstat=1
endif
endif
c -------------------------------------------------------------------
c Determine Element Stress (Returned to Abaqus)
c Element Stress = Material Stress*(1-D)
do i=1,6
stressNew(k,i)=stateNew(k,4+i)*
* (one-statenew(k,14))
enddo
c -------------------------------------------------------------------
c Update element data from previous increment
ielabel=stateold(k,1)
do i=1,3
el_position_old(ielabel,i)=el_position_new(ielabel,i)
el_position_new(ielabel,i)=coordMP(k,i)
enddo
el_time_old(ielabel)=el_time_new(ielabel)
el_time_new(ielabel)=totaltime
el_status_old(ielabel)=el_status_new(ielabel)
el_status_new(ielabel)=ielstat
endif
c -------------------------------------------------------------------
C Update the specific internal energy -
stressPower = half * (
1 ( stressOld(k,1)+stressNew(k,1) )*strainInc(k,1)
1 + ( stressOld(k,2)+stressNew(k,2) )*strainInc(k,2)
1 + ( stressOld(k,3)+stressNew(k,3) )*strainInc(k,3)
1 + two*( stressOld(k,4)+stressNew(k,4) )*strainInc(k,4) )
C
enerInternNew(k) = enerInternOld(k)+ stressPower / density(k)
c
end do
return
end subroutine vumat
c -------------------------------------------------------------------

View file

@ -0,0 +1,272 @@
c Abaqus User Defined Material Subroutine - J. Grogan, 2011
c -------------------------------------------------------------------
subroutine vumat (
c Read only -
* nblock,ndir,nshr,nstatev,nfieldv,nprops,lanneal,stepTime,
* totalTime,dt,cmname,coordMp,charLength,props,density,
* strainInc,relSpinInc,tempOld,stretchOld,defgradOld,
* fieldOld,stressOld, stateOld, enerInternOld,enerInelasOld,
* tempNew, stretchNew, defgradNew, fieldNew,
c Write only -
* stressNew, stateNew, enerInternNew, enerInelasNew )
c
include 'vaba_param.inc'
c
dimension coordMp(nblock,3),charLength(nblock),props(nprops),
1 strainInc(nblock,ndir+nshr),stressOld(nblock,ndir+nshr),
2 stateOld(nblock,nstatev),stressNew(nblock,ndir+nshr),
3 stateNew(nblock,nstatev),astr(nblock,ndir+nshr),
4 rKE(3,3),enerInternNew(nblock), enerInternOld(nblock),
5 density(nblock)
c
character*80 cmname
c
parameter (zero = 0.d0, one = 1.d0, two = 2.d0, three = 3.d0,
* four = 4.d0,third = 1.d0 / 3.d0, half = 0.5d0, op5 = 1.5d0)
c -------------------------------------------------------------------
c Common blocks store element status and random number assigment.
common active(400000)
common randnum(400000)
integer active
real randnum
c
do k=1,nblock
c -------------------------------------------------------------------
c Update SDVs
do i=1,9
stateNew(k,i)=stateOld(k,i)
enddo
do i=23,30
stateNew(k,i)=stateOld(k,i)
enddo
c -------------------------------------------------------------------
c Get meterial properties from INP file and form 'C' matrix
e = props(1)
xnu = props(2)
syield=props(3)
b=props(4)
q=props(5)
twomu = e / ( one + xnu )
thremu = op5 * twomu
alamda = xnu * twomu / ( one - two * xnu )
trace=strainInc(k,1)+strainInc(k,2)+strainInc(k,3)
c -------------------------------------------------------------------
c Linear elastic material for Abq/Explicit Packager
if(abs(steptime)<=0.d0)then
do i=1,3
stressNew(k,i)=stressOld(k,i)
* +twomu*strainInc(k,i)+alamda*trace
enddo
do i=4,6
stressNew(k,i)=stressOld(k,i)+twomu*strainInc(k,i)
enddo
else
c -------------------------------------------------------------------
c Get Actual Trial Stress
do i=1,3
astr(k,i)=stateOld(k,9+i)
* +twomu*strainInc(k,i)+alamda*trace
enddo
do i=4,6
astr(k,i)=stateOld(k,9+i)+twomu*strainInc(k,i)
enddo
c -------------------------------------------------------------------
c Partially Convert to Voigt Form
smean = third*(astr(k,1)+astr(k,2)+astr(k,3))
s11 = astr(k,1) - smean
s22 = astr(k,2) - smean
s33 = astr(k,3) - smean
c -------------------------------------------------------------------
c Get Von Mises Stress
stateNew(k,19)=sqrt(op5*(s11*s11+s22*s22+s33*s33
* +two*astr(k,4)*astr(k,4)+two*astr(k,5)*astr(k,5)
* +two*astr(k,6)*astr(k,6)))
c -------------------------------------------------------------------
c Get Max Prin Stress
rKE(1,1)=s11
rKE(2,2)=s22
rKE(3,3)=s33
rKE(1,2)=astr(k,4)
rKE(2,1)=astr(k,4)
rKE(2,3)=astr(k,5)
rKE(3,2)=astr(k,5)
rKE(1,3)=astr(k,6)
rKE(3,1)=astr(k,6)
rq=s11*s22*s33
rq=rq+2.d0*rKE(1,2)*rKE(2,3)*rKE(1,3)
rq=rq-rKE(1,1)*rKE(2,3)*rKE(2,3)
rq=rq-rKE(2,2)*rKE(1,3)*rKE(1,3)
rq=rq-rKE(3,3)*rKE(1,2)*rKE(1,2)
rq=rq/2.d0
p=0.d0
do i=1,3
do j=1,3
p=p+rKE(i,j)*rKE(i,j)
enddo
enddo
p=p/6.d0
if(p<1.e-6)then
phi=(1.d0/3.d0)*(acos(0.d0)/2.d0)
else
if(abs(rq)>abs(p**(1.5)))then
phi=0.d0
else
phi=(1.d0/3.d0)*acos(rq/p**(1.5))
endif
endif
if(phi<0.)then
phi=phi+acos(0.d0)/3.d0
endif
eig1=smean+2.d0*sqrt(p)*cos(phi)
eig2=smean-sqrt(p)*(cos(phi)+sqrt(3.d0)*sin(phi))
eig3=smean-sqrt(p)*(cos(phi)-sqrt(3.d0)*sin(phi))
stateNew(k,16)=max(eig1,eig2,eig3)
c -------------------------------------------------------------------
c Recover Yield Surface
if(stateOld(k,17)<=0.d0)then
yieldOld=syield
else
yieldOld=stateOld(k,17)
endif
c -------------------------------------------------------------------
c Update Hardening Parameters
rold=q*(one-exp(-b*stateOld(k,18)))
hard=b*(q-rold)
c -------------------------------------------------------------------
c Get equivalent plastic strain increment
sigdif = stateNew(k,19) - yieldOld
facyld = zero
if(sigdif.gt.zero)facyld=one
deqps=facyld*sigdif/(thremu+hard)
c -------------------------------------------------------------------
c Update Yield Surface and Eq. Plastic Strain
yieldNew = yieldOld + hard * deqps
stateNew(k,18) = stateOld(k,18) + deqps
stateNew(k,17)= yieldNew
c -------------------------------------------------------------------
c Get Correction Factor for Trial Stress
factor = yieldNew / ( yieldNew + thremu * deqps )
c -------------------------------------------------------------------
c Determine Actual Stress
stateNew(k,10) = s11 * factor + smean
stateNew(k,11) = s22 * factor + smean
stateNew(k,12) = s33 * factor + smean
stateNew(k,13) = astr(k,4) * factor
stateNew(k,14) = astr(k,5) * factor
stateNew(k,15) = astr(k,6) * factor
c -------------------------------------------------------------------
c Update Damage Parameter
if(totaltime>=1.5)then
call apply_damage(stateOld,stateNew,k,nblock,
* nstatev,randnum,charlength,props,nprops,dt,
* active,steptime,totaltime)
endif
c -------------------------------------------------------------------
c Determine Element Stress (Returned to Abaqus)
c Element Stress = Material Stress*(1-D)
do i=1,6
stressNew(k,i)=stateNew(k,9+i)*(one-statenew(k,21))
enddo
endif
C Update the specific internal energy -
stressPower = half * (
1 ( stressOld(k,1)+stressNew(k,1) )*strainInc(k,1)
1 + ( stressOld(k,2)+stressNew(k,2) )*strainInc(k,2)
1 + ( stressOld(k,3)+stressNew(k,3) )*strainInc(k,3)
1 + two*( stressOld(k,4)+stressNew(k,4) )*strainInc(k,4) )
C
enerInternNew(k) = enerInternOld(k)+ stressPower / density(k)
c
end do
return
end subroutine vumat
c -------------------------------------------------------------------
c
c This subroutine updates the value of the damage parameter based on
c corrosion and/or ductile damage evolution. J. Grogan, 2011.
c
subroutine apply_damage(stateOld,stateNew,k,nblock,nstatev,
* rrandnum,charlength,props,nprops,dt,iactive,steptime,
* totaltime)
c
include 'vaba_param.inc'
c
dimension stateNew(nblock,nstatev),charlength(nblock)
dimension props(nprops),stateOld(nblock,nstatev)
c -------------------------------------------------------------------
c Taken from values stored in common blocks in VUMAT
dimension iactive(400000)
dimension rrandnum(400000)
c -------------------------------------------------------------------
c Determine Characteristic Element Length
e_length=charlength(k)
c -------------------------------------------------------------------
c Recover value of damage parameter
if(stateOld(k,21)>0.)then
damage=stateOld(k,21)
else
damage=0.
endif
c -------------------------------------------------------------------
c Check if element is on exposed surface.
do i=1,6
icycle=0
c
c If any surrounding elements have been deleted in the
c previous inc, the number of exposed faces (SDV9) increases.
if(iactive(stateNew(k,i))==1.)then
do j=1,6
c Previously deleted element numbers are
c stored in SDV 22-28.
if(stateNew(k,i)==stateNew(k,22+j))then
icycle=1
endif
enddo
if(icycle==1)then
cycle
endif
stateNew(k,9)=stateNew(k,9)+1.
stateNew(k,22+i)=stateNew(k,i)
c
c Current element assumes random number of deleted
c neighbouring element.
if(rrandnum(stateNew(k,i))>=stateNew(k,30))then
stateNew(k,30)=rrandnum(stateNew(k,i))*0.85
endif
endif
enddo
c -------------------------------------------------------------------
c Recover Corrosion Parameters
ukinetic=props(6)
stateNew(k,29)=ukinetic
rand_num=stateNew(k,30)
if((statenew(k,9)>0.99))then
if(totaltime<3.)then
dam_inc=(ukinetic/E_LENGTH)*dt
damage=damage+dam_inc
endif
endif
statenew(k,21)=damage
c -------------------------------------------------------------------
c Remove Fully Damaged Elements
if(statenew(k,18)>0.1515)then
damage=1.d0
endif
if(damage>=0.999)then
statenew(k,20)=0.
statenew(k,21)=1.
iactive(statenew(k,8))=1.d0
rrandnum(statenew(k,8))=statenew(k,30)
endif
c
return
end subroutine apply_damage
c -------------------------------------------------------------------