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 -------------------------------------------------------------------

68194
ActaBiomat13/C1D1.inp Normal file

File diff suppressed because it is too large Load diff

488
ActaBiomat13/ale_c1d1.f Normal file
View file

@ -0,0 +1,488 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
TERM1=4.d0*d21*d1t
TERM2=(d21-d2t+d1t)**2
if (term2>term1)then
print *,'oops'
y1=0.d0
else
y1=sqrt((term1-term2)/(4.d0*d21))
endif
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(134.d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*.10575d0*0.507013518d0/(1735.d0-134.d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
c if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c1d1.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(134.d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=0.03
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.005)PNEWDT=0.005d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c1d2.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(134.d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*1.0575d0*0.507013518d0/(1735.d0-134.d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c1d3.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(134.d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*0.010575d0*0.507013518d0/(1735.d0-134.d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c1d4.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(134.d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*0.50575d0*0.507013518d0/(1735.d0-134.d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c2d4.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(60.d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*0.50575d0*0.507013518d0/(1735.d0-60.d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c3d1.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(13.4d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*.10575d0*0.507013518d0/(1735.d0-13.4d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c3d2.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(13.4d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*1.0575d0*0.507013518d0/(1735.d0-13.4d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c3d3.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(13.4d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*0.010575d0*0.507013518d0/(1735.d0-13.4d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c3d4.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(13.4d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*0.50575d0*0.507013518d0/(1735.d0-13.4d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c4d1.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(1.34d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*.10575d0*0.507013518d0/(1735.d0-1.34d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c4d2.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(1.34d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*1.0575d0*0.507013518d0/(1735.d0-1.34d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c4d3.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(1.34d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*0.010575d0*0.507013518d0/(1735.d0-1.34d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

484
ActaBiomat13/ale_c4d4.for Normal file
View file

@ -0,0 +1,484 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData4.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=40000,maxFacets=100000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(1.34d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=grad*0.50575d0*0.507013518d0/(1735.d0-1.34d0)
dist(i)=vel*dtime
dtnew=abs(0.5d-3/(vel*dtime))
if(dtnew<PNEWDT)pnewdt=dtnew
if(pnewdt*dtime>=0.002)PNEWDT=0.002d0/dtime
c if(dtime>=0.002)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

483
ActaBiomat13/ale_phenom.for Normal file
View file

@ -0,0 +1,483 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=47000,maxFacets=80000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer n(16)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData3.inc',
1 status='old')
read(101,*)numNodes
ntotalFacets=1
do i=1,numNodes
read(101,*)nodeLabel,numFacets
ndata(nodeLabel,1)=ntotalFacets
ndata(nodeLabel,2)=numFacets
do j=1,numFacets
read(101,*)nbr1,nbr2
read(101,*)n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
read(101,*)n(9),n(10),n(11),n(12),n(13),n(14),n(15),n(16)
facet(ntotalFacets-1+j,1)=nbr1
facet(ntotalFacets-1+j,2)=nbr2
do k=3,18
facet(ntotalFacets-1+j,k)=n(k-2)
enddo
enddo
ntotalFacets=ntotalFacets+numFacets
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3),TEMP(NSECPT)
c Common Block Declarations
parameter (maxNodes=47000,maxFacets=80000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
tmp(node)=temp(1)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=47000,maxFacets=80000)
integer ndata(maxNodes,2),facet(maxFacets,18)
real crd(maxNodes,3),tmp(maxNodes)
common ndata,facet,crd,tmp
c Other Declarations
integer np(3)
real fp(4,9),fc(4,3),fe(4,3),fn(4,3),a(3),b(3),Amat(4,4)
real c(3),d(3),q(3),qnew(3),cp1(3),cp2(3),cp3(3),dist(4)
real pt(3),qd(3,2),p1(3),p2(3),rn(8,4)
integer flabel(10,3)
if(lnodetype>=3.and.lnodetype<=5)then
c print *,node,time(1),'in'
c Analysis Parameters
tol=1.d-5
numFacets=ndata(node,2)
c get facet point coords (fp).
do i=1,numFacets
nFacet=ndata(node,1)-1+i
nbr1=facet(nFacet,1)
nbr2=facet(nFacet,2)
do k=1,3
fp(i,k)=crd(node,k)
fp(i,k+3)=crd(nbr1,k)
fp(i,k+6)=crd(nbr2,k)
enddo
enddo
c get facet element centroid(fe)
fe=0.d0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
do j=1,8
nNode=facet(nFacet,j+10)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.d0
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.d0
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.d0
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c get facet velocity
c PNEWDT=10000.
if_check=0
do i=1,numFacets
nFacet=ndata(node,1)-1+i
c check if facet has neighbours
if(Facet(nFacet,3)==0)then
dist(i)=0.d0
else
do j=1,8
rn(j,1)=crd(Facet(nFacet,2+j),1)
rn(j,2)=crd(Facet(nFacet,2+j),2)
rn(j,3)=crd(Facet(nFacet,2+j),3)
rn(j,4)=tmp(Facet(nFacet,2+j))
enddo
call getFlabels(flabel)
do j=1,10
label1=flabel(j,1)
label2=flabel(j,2)
label3=flabel(j,3)
do k=1,3
Amat(1,k)=1.d0
enddo
Amat(1,4)=0.d0
do k=1,3
Amat(k+1,1)=rn(label1,k)
Amat(k+1,2)=rn(label2,k)
Amat(k+1,3)=rn(label3,k)
Amat(k+1,4)=fn(i,k)
enddo
call getDet(Amat,Det1)
if (Det1==0)cycle
Amat(1,4)=1.d0
do k=1,3
Amat(k+1,4)=fc(i,k)
enddo
call getDet(Amat,Det2)
t=-det2/det1
do k=1,3
pt(k)=fc(i,k)+fn(i,k)*t
p1(k)=rn(label1,k)
p2(k)=rn(label2,k)
enddo
call getDist(p1,p2,d21)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d31)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=rn(label3,k)
enddo
call getDist(p1,p2,d23)
qd(1,1)=0.d0
qd(1,2)=0.d0
qd(2,1)=sqrt(d21)
qd(2,2)=0.d0
qd(3,1)=(d21-d23+d31)/(2.d0*sqrt(d21))
term=4.d0*d21*d31-(d21-d23+d31)**2
qd(3,2)=sqrt(term/(4.d0*d21))
if(qd(3,2)<0)qd(3,2)=-qd(3,2)
do k=1,3
p1(k)=rn(label1,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d1t)
do k=1,3
p1(k)=rn(label2,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d2t)
do k=1,3
p1(k)=rn(label3,k)
p2(k)=pt(k)
enddo
call getDist(p1,p2,d3t)
x=(d21-d2t+d1t)/(2.d0*sqrt(d21))
y1=sqrt((4.d0*d21*d1t-(d21-d2t+d1t)**2)
$ /(4.d0*d21))
d1=(x-qd(3,1))*(x-qd(3,1))
d2=(y1-qd(3,2))*(y1-qd(3,2))
dst=d1+d2
if((dst>=d3t-0.0001).or.(dst<=d3t+0.0001))then
y=y1
else
y=-y1
endif
t1=(x-qd(3,1))/(qd(1,1)-qd(3,1))
t2=(y-qd(3,2))/(qd(1,2)-qd(3,2))
t3=(qd(2,1)-qd(3,1))/(qd(1,1)-qd(3,1))
t4=(qd(2,2)-qd(3,2))/(qd(1,2)-qd(3,2))
t=(t1-t2)/(t3-t4)
term=t*(qd(3,2)-qd(2,2))+y-qd(3,2)
s=term/(qd(1,2)-qd(3,2))
if((s>=0.).and.(t>=0.).and.(1.-s-t>=0.))then
temp=rn(label1,4)*s+rn(label2,4)*t
temp=temp+rn(label3,4)*(1.-s-t)
dx=(pt(1)-fc(i,1))*(pt(1)-fc(i,1))
dy=(pt(2)-fc(i,2))*(pt(2)-fc(i,2))
dz=(pt(3)-fc(i,3))*(pt(3)-fc(i,3))
grad=(134.d0-temp)/(sqrt(dx+dy+dz))
exit
endif
enddo
vel=0.03
dist(i)=vel*dtime
c dtnew=abs(0.5d-4/(vel*dtime))
c if(dtnew<PNEWDT)pnewdt=dtnew
c if(dtime>=0.007)PNEWDT=1.d0
end if
enddo
c move non-fixed facets along unit normals - update fp
do i=1,numFacets
nFacet=ndata(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist(i)
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist(i)
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist(i)
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.d0
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.d0
dp2=0.d0
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.d0
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.d0
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.d0
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,time(1),pnewdt,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.d0
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end
subroutine getFlabels(flabel)
include 'aba_param.inc'
integer flabel(10,3)
flabel(1,1)=6
flabel(1,2)=8
flabel(1,3)=7
flabel(2,1)=6
flabel(2,2)=7
flabel(2,3)=5
flabel(3,1)=6
flabel(3,2)=2
flabel(3,3)=4
flabel(4,1)=6
flabel(4,2)=4
flabel(4,3)=8
flabel(5,1)=5
flabel(5,2)=1
flabel(5,3)=3
flabel(6,1)=5
flabel(6,2)=3
flabel(6,3)=7
flabel(7,1)=3
flabel(7,2)=4
flabel(7,3)=8
flabel(8,1)=3
flabel(8,2)=8
flabel(8,3)=7
flabel(9,1)=1
flabel(9,2)=2
flabel(9,3)=6
flabel(10,1)=1
flabel(10,2)=6
flabel(10,3)=5
return
end subroutine
subroutine getDet(A,Det)
include 'aba_param.inc'
real A(4,4)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,2)-A(3,2)*A(4,4)
A3=A(3,2)*A(4,3)-A(3,3)*A(4,2)
B1=A(1,1)*(A(2,2)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,3)*A(4,4)-A(3,4)*A(4,3)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,3)-A(3,3)*A(4,1)
B2=A(1,2)*(A(2,1)*A1+A(2,3)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,4)-A(3,4)*A(4,2)
A2=A(3,4)*A(4,1)-A(3,1)*A(4,4)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B3=A(1,3)*(A(2,1)*A1+A(2,2)*A2+A(2,4)*A3)
A1=A(3,2)*A(4,3)-A(3,3)*A(4,2)
A2=A(3,3)*A(4,1)-A(3,1)*A(4,3)
A3=A(3,1)*A(4,2)-A(3,2)*A(4,1)
B4=A(1,4)*(A(2,1)*A1+A(2,2)*A2+A(2,3)*A3)
DET =B1-B2+B3-B4
end subroutine
subroutine getDist(p1,p2,dist)
include 'aba_param.inc'
real p1(3),p2(3)
d21x=(p2(1)-p1(1))*(p2(1)-p1(1))
d21y=(p2(2)-p1(2))*(p2(2)-p1(2))
d21z=(p2(3)-p1(3))*(p2(3)-p1(3))
dist=d21x+d21y+d21z
end subroutine

View file

@ -0,0 +1,91 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
from abaqus import *
aModel=mdb.models['Trial2']
aPart=aModel.parts['Mesh8']
incFile=open('NodeData4.inc','w')
# Cycle through all interface nodes
interfaceNodes=aPart.sets['InterfaceN'].nodes
interfaceElements=aPart.sets['InterfaceE'].elements
pstring=str(len(interfaceNodes))+' \n'
ic=0
for eachNode in interfaceNodes:
nodeLabel=eachNode.label
nodeFaces=eachNode.getElemFaces()
nodeEdges=eachNode.getElemEdges()
numFacets=len(nodeFaces)
nstring=' '
numFaces=0
for eachFace in nodeFaces:
# Check if face is on outer boundary
faceElems=eachFace.getElements()
bound=0
if len(faceElems)==1:
if faceElems[0] in interfaceElements:
bound=1
# Check if face is on interface
interface=0
faceNodes=eachFace.getNodes()
for eachFNode in faceNodes:
if eachFNode in interfaceNodes:
interface=interface+1
if interface==4 or bound==1:
facetNodes=[]
numFaces=numFaces+1
for eachFNode in eachFace.getNodes():
if eachFNode.label!=nodeLabel:
for eachEdge in eachFNode.getElemEdges():
if eachEdge in nodeEdges:
facetNodes.append(eachFNode)
nstring=nstring+str(facetNodes[0].label)+' '+str(facetNodes[1].label)+' \n'
faceElems=eachFace.getElements()
if bound==0:
if faceElems[0] in interfaceElements:
intNodes=faceElems[0].getNodes()
nbrElem=faceElems[1]
else:
nbrElem=faceElems[0]
intNodes=faceElems[1].getNodes()
nbrNodes=nbrElem.getNodes()
n1=eachNode
n2=facetNodes[0]
n3=facetNodes[1]
for eachFNode in faceNodes:
if eachFNode!=n1 and eachFNode!=n2 and eachFNode!=n3:
n4=eachFNode
break
for eachEEdge in n1.getElemEdges():
for eachENode in eachEEdge.getNodes():
if eachENode in nbrNodes and eachENode!=n1 and eachENode!=n2 and eachENode!=n3:
n5=eachENode
break
for eachEEdge in n2.getElemEdges():
for eachENode in eachEEdge.getNodes():
if eachENode in nbrNodes and eachENode!=n1 and eachENode!=n2 and eachENode!=n4:
n6=eachENode
break
for eachEEdge in n3.getElemEdges():
for eachENode in eachEEdge.getNodes():
if eachENode in nbrNodes and eachENode!=n1 and eachENode!=n4 and eachENode!=n3:
n7=eachENode
break
for eachEEdge in n4.getElemEdges():
for eachENode in eachEEdge.getNodes():
if eachENode in nbrNodes and eachENode!=n4 and eachENode!=n2 and eachENode!=n3:
n8=eachENode
break
nstring=nstring+str(n1.label)+' '+str(n2.label)+' '+str(n3.label)+' '+str(n4.label)+' '
nstring=nstring+str(n5.label)+' '+str(n6.label)+' '+str(n7.label)+' '+str(n8.label)+' '
nstring=nstring+'\n'
for eachNNode in intNodes:
nstring=nstring+str(eachNNode.label)+' '
else:
nstring=nstring+'0 0 0 0 0 0 0 0 \n'
for eachNNode in faceElems[0].getNodes():
nstring=nstring+str(eachNNode.label)+' '
nstring=nstring+'\n'
pstring=pstring+str(nodeLabel)+' '+str(numFaces)+' \n'+nstring
ic=ic+1
print ic,len(interfaceNodes)
incFile.write(pstring)
incFile.close()

68194
ActaBiomat13/pres.inp Normal file

File diff suppressed because it is too large Load diff

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

View file

@ -0,0 +1,316 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer n(8)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
nbr=0
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData.inc',
1 status='old')
read(101,*)numfaces
do i=1,4*numfaces,4
read(101,*)nfix,n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
c facet(*,12)=fized face flag, facet(*,4-11)=element nodes
do j=1,4
ind=i+j-1
facet(ind,12)=nfix
do k=1,8
facet(ind,3+k)=n(k)
enddo
enddo
do j=1,4
ind=i+j-1
c facet(*,1-3)=nodes in facet
read(101,*)facet(ind,1),facet(ind,2),facet(ind,3)
node=facet(ind,1)
c nbr(node,1)=counter for facets per node
if(nbr(node,1)==0)nbr(node,1)=1
nbr(node,1)=nbr(node,1)+1
c nbr(node,>1)=facet number
nbr(node,nbr(node,1))=ind
enddo
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer np(3)
real fp(6,9),fc(6,3),fe(6,3),fn(6,3),a(3),b(3),c(3),d(3),q(3)
real qnew(3),cp1(3),cp2(3),cp3(3)
if(lnodetype>=3.and.lnodetype<=5)then
C PRINT *,NODE,'IN'
c Analysis Parameters
velocity=0.01d0
tol=1.d-5
c
numFacets=nbr(node,1)-1
c get facet point coords (fp).
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,3
nNode=facet(nFacet,j)
if (j==1)nnode=node
do k=1,3
fp(i,3*(j-1)+k)=crd(nNode,k)
enddo
c print *,node,nNode
c print *,crd(nNode,1),crd(nNode,2),crd(nNode,3)
enddo
enddo
c get facet element centroid(fe)
fe=0.
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,8
nNode=facet(nFacet,j+3)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c move non-fixed facets along unit normals - update fp
dist=velocity*dtime
do i=1,numFacets
nFacet=nbr(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.
dp2=0.
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end

View file

@ -0,0 +1,27 @@
#!/bin/bash
#PBS -l nodes=2:ppn=12
#PBS -l walltime=9:00:00
#PBS -N Opt_Stiffness_P3
#PBS -A ngeng036b
#PBS -r n
#PBS -j oe
#PBS -m bea
#PBS -M lumpwood@gmail.com
#PBS -V
cd $PBS_O_WORKDIR
module load taskfarm2
module load intel-cc
module load intel-fc
module load intel-mkl
module load boost-intel
module load intel-mpi
module load abaqus
taskfarm tasks.inp

Binary file not shown.

View file

@ -0,0 +1,30 @@
strategy,
single
#pareto_set
#graphics
#opt_method_pointer = "NLP"
#multi_objective_weight_sets =
#1. 0.
#0. 1.
#.5 .5
tabular_graphics_data
method,
id_method = "NLP"
efficient_global
seed = 79877
variables,
continuous_design = 6
lower_bounds 0.11 0.11 0.6 1.0 0.1 0.001
upper_bounds 0.16 0.14 1.0 1.2 0.5 0.04
descriptors "x1" "x2" "x3" "x4" "x5" "x6"
interface,
fork asynchronous evaluation_concurrency = 1
analysis_drivers = 'abaqus python PyWrapperB.py --'
parameters_file = 'Bparams.in'
results_file = 'Bresults.out'
file_tag
file_save
responses,
objective_functions = 1
no_gradients
no_hessians

View file

@ -0,0 +1,14 @@
from part import *
from material import *
from section import *
from assembly import *
from step import *
from interaction import *
from load import *
from mesh import *
from job import *
from sketch import *
from visualization import *
from connectorBehavior import *
mdb.models['Dream6'].boundaryConditions['BC-2'].setValues(u1=-0.7)
# Save by 05365350 on Fri Oct 19 21:01:57 2012

View file

@ -0,0 +1,126 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
from abaqus import *
from odbAccess import *
import regionToolset
import sys
import os
import interaction
import mesh
#Read in Model Parameters
paramFile=sys.argv[-1]
jobName=paramFile.encode("hex")
os.system ("cp %s %s" % ('OptB.cae', jobName+'.cae'))
mdb=openMdb(jobName+'.cae')
inFile = open(paramFile,"r")
inFile.readline()
x1,name1=inFile.readline().split()
x2,name2=inFile.readline().split()
x3,name3=inFile.readline().split()
x4,name4=inFile.readline().split()
x5,name5=inFile.readline().split()
x6,name6=inFile.readline().split()
mname='Dream6'
#Generate New Model
aModel=mdb.models[mname]
aAss=aModel.rootAssembly
tol=0.0001
radius=0.75
numCrowns=6.
W=float(x1)
T=float(x2)
L1=float(x3)
L2=float(x4)*L1
L3=float(x5)
H2=float(x6)
H1=(pi*radius)/(2.*numCrowns)
# Modify Part
aPart=aModel.parts['Geom']
aSketch=aPart.features['Solid extrude-1'].sketch
aModel.ConstrainedSketch(name='__edit__', objectToCopy=aSketch)
bSketch=aModel.sketches['__edit__']
bSketch.parameters['w'].setValues(expression=str(W/2.))
bSketch.parameters['h1'].setValues(expression=str(H1))
bSketch.parameters['h2'].setValues(expression=str(H2))
bSketch.parameters['l1'].setValues(expression=str(L1))
bSketch.parameters['l2'].setValues(expression=str(L2))
bSketch.parameters['l3'].setValues(expression=str(L3))
aPart.features['Solid extrude-1'].setValues(sketch=bSketch)
del aModel.sketches['__edit__']
aPart.features['Solid extrude-1'].setValues(depth=T)
aPart.regenerate()
# Mesh Part
aPart.seedPart(size=W/6., deviationFactor=0.1)
aPart.generateMesh()
# Create Orphan Mesh
aPart.PartFromMesh(name='AMesh')
bPart=aModel.parts['AMesh']
# Create Sets,Sections,Surfaces
for nameSet,eachSet in aPart.sets.items():
bPart.Set(name=nameSet, nodes=eachSet.nodes)
bPart.Set(name='AllE', elements=aPart.sets['All'].elements)
bPart.Set(name='InnerE', elements=aPart.sets['Inner'].elements)
bPart.Set(name='OuterE', elements=aPart.sets['Outer'].elements)
region = regionToolset.Region(elements=bPart.elements)
bPart.SectionAssignment(region=region, sectionName='Magnesium')
aPart=aModel.parts['AMesh']
elemType1 = mesh.ElemType(elemCode=C3D8R, elemLibrary=STANDARD,
kinematicSplit=AVERAGE_STRAIN, secondOrderAccuracy=OFF,
hourglassControl=ENHANCED, distortionControl=DEFAULT)
pickedRegions =(aPart.elements, )
aPart.setElementType(regions=pickedRegions, elemTypes=(elemType1, ))
# Wrap Part
nlist=[]
clist=[]
for eachnode in aPart.nodes:
theta=eachnode.coordinates[1]/radius
newcoord1=eachnode.coordinates[0]
newcoord2=(radius-eachnode.coordinates[2])*cos(theta)
newcoord3=(radius-eachnode.coordinates[2])*sin(theta)
nlist.append(eachnode)
clist.append((newcoord1,newcoord2,newcoord3))
aPart.editNode(nodes=nlist,coordinates=clist)
aPart.regenerate()
aAss.regenerate()
aInst=aAss.instances['AMesh-1']
aModel.rootAssembly.Set(name='Set-1',nodes=aInst.nodes)
incFile=open('NodeData.inc','w')
numFaces=0
pstring=''
# Cycle through all element faces
for eachFace in aPart.elementFaces:
# Check if Face is on external Surface
if len(eachFace.getElements())==1:
numFaces=numFaces+1
faceNodes=eachFace.getNodes()
# Identify 'Fixed' Faces
fixed=1
try:
fSet=aPart.sets['Fixed']
for eachNode in faceNodes:
if eachNode not in fSet.nodes:
fixed=0
break
except:
fixed=0
pstring=pstring+str(fixed)+' '
# Write Element Nodes
eNodes=[]
for eachNode in eachFace.getElements()[0].getNodes():
pstring=pstring+str(eachNode.label)+' '
pstring=pstring+'\n'
# Write Each Face Nodes and Corresponding Connected Nodes
for eachNode in faceNodes:
pstring=pstring+str(eachNode.label)+' '
for eachEdge in eachNode.getElemEdges():
for eachENode in eachEdge.getNodes():
if eachENode.label != eachNode.label and eachENode in faceNodes:
pstring=pstring+str(eachENode.label)+' '
pstring=pstring+'\n'
incFile.write(str(numFaces)+'\n')
incFile.write(pstring)
incFile.close()
mdb.Job(name=jobName, model=mname)
mdb.jobs[jobName].writeInput(consistencyChecking=OFF)
mdb.close()

View file

@ -0,0 +1,34 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
from odbAccess import *
import sys
import os
jobName=sys.argv[-2]
resFile=sys.argv[-1]
resFile2=resFile+'.b'
odbfilename=jobName+'.odb'
odb=openOdb(path=odbfilename)
aFrame=odb.steps["Step-1"].frames[-1]
maxStrain=0.
for currentStrain in aFrame.fieldOutputs["LE"].values:
if currentStrain.instance.name=='AMESH-1':
if currentStrain.maxPrincipal>maxStrain:
maxStrain=currentStrain.maxPrincipal
outFile = open(resFile,"w")
if maxStrain>0.1256:
outFile = open(resFile,"w")
outFile2 = open(resFile2,"w")
objFn=1.+maxStrain
outFile.write("%12.6f \n " % (objFn))
outFile2.write("%12.6f \n " % (maxStrain))
outFile.close()
outFile2.close()
odb.close()
else:
outFile2 = open(resFile2,"w")
outFile2.write("%12.6f \n " % (maxStrain))
outFile2.close()
odb.close()
os.system('abaqus j=R1'+jobName+' oldjob='+jobName+' inp=Restart1 cpus=6 inter user=ALE20')
os.system('abaqus j=R2'+jobName+' oldjob=R1'+jobName+' inp=Restart2 cpus=6 inter user=ALE20')
os.system('abaqus python OptPostB2.py -- R2'+jobName+' '+resFile)

View file

@ -0,0 +1,46 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
from odbAccess import *
import sys
import os
jobName=sys.argv[-2]
resFile=sys.argv[-1]
odbfilename=jobName+'.odb'
try:
odb=openOdb(path=odbfilename)
aNod=odb.rootAssembly.instances['AMESH-1'].nodeSets['E1'].nodes[0].coordinates[0]
bNod=odb.rootAssembly.instances['AMESH-1'].nodeSets['E2'].nodes[0].coordinates[0]
rlen=abs(aNod-bNod)
check=0.
try:
for eachFrame in odb.steps["Step-5"].frames:
tforce=0.
for currentForce in eachFrame.fieldOutputs["CNORMF ASSEMBLY_AOUTER/ASSEMBLY_SURF-1"].values:
fx=currentForce.data[0]
fy=currentForce.data[1]
fz=currentForce.data[2]
tforce=tforce+sqrt(fx*fx+fy*fy+fz*fz)
aSet=odb.rootAssembly.instances['OUTER-1']
uy=eachFrame.fieldOutputs["U"].getSubset(region=aSet).values[0].data[1]
uz=eachFrame.fieldOutputs["U"].getSubset(region=aSet).values[0].data[2]
rad=sqrt(uy*uy+uz*uz)
if tforce>0.:
check=check+1
if check==2:
f1=tforce
r1=rad
if check==5:
f2=tforce
r2=rad
break
stiff=abs(f2-f1)/abs(r2-r1)
except:
stiff=0.
stiff=stiff/rlen
except:
stiff=0.
outFile = open(resFile,"w")
objFn=1.-(0.15*abs(stiff))
outFile.write("%12.6f \n " % (objFn))
outFile.close()
odb.close()

View file

@ -0,0 +1,15 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
import sys
import os
import subprocess
#
resFile=sys.argv[-1]
paramFile=sys.argv[-2]
jobName=paramFile.encode("hex")
# Run Preprocessor
os.system("abaqus cae noGUI=OptB.py -- "+paramFile)
# Run Job
os.system('abaqus j='+jobName+' cpus=6 inter user=ALE20 mp_mode=mpi')
# Run Postprocessor
os.system('abaqus python OptPostB1.py -- '+jobName+' '+resFile)

View file

@ -0,0 +1,69 @@
*Heading
** Job name: Restart Model name: Dream6R
** Generated by: Abaqus/CAE 6.10-1
*Preprint, echo=NO, model=NO, history=NO, contact=NO
*Restart, read, step=2
**
** STEP: Step-3
**
*Step, name=Step-3, nlgeom=YES
*Static
0.05, 1., 1e-05, 0.05
*Adaptive Mesh, elset=AMesh-1.AllE, frequency=1, mesh sweeps=10, op=NEW
**
** ADAPTIVE MESH CONSTRAINTS
**
** Name: Ada-Cons-1 Type: Velocity/Angular velocity
*Adaptive Mesh Constraint, user, type=VELOCITY
AMesh-1.Const
**
** OUTPUT REQUESTS
**
**
*field,user
set-1
** FIELD OUTPUT: F-Output-1
**
*Output, field
*Node Output
CF, RF, U
*Element Output, directions=YES
LE, PE, PEEQ, PEMAG, S
*Contact Output
CDISP, CFORCE, CSTRESS
**
** HISTORY OUTPUT: H-Output-1
**
*Output, history, variable=PRESELECT
*End Step
** ----------------------------------------------------------------
** STEP: Step-4
**
*Step, name=Step-4, nlgeom=YES
*Static
0.05, 0.05, 5e-07, 0.05
*Adaptive Mesh, op=NEW
**
** ADAPTIVE MESH CONSTRAINTS
**
** Name: Ada-Cons-1 Type: Velocity/Angular velocity
*Adaptive Mesh Constraint, op=NEW
**
** OUTPUT REQUESTS
**
*Restart, write, number interval=1, time marks=NO
**
** FIELD OUTPUT: F-Output-1
**
*Output, field
*Node Output
CF, RF, U
*Element Output, directions=YES
LE, PE, PEEQ, PEMAG, S
*Contact Output
CDISP, CFORCE, CSTRESS
**
** HISTORY OUTPUT: H-Output-1
**
*Output, history, variable=PRESELECT
*End Step

View file

@ -0,0 +1,28 @@
*Heading
** Job name: Restart Model name: Dream6R
** Generated by: Abaqus/CAE 6.10-1
*Preprint, echo=NO, model=NO, history=NO, contact=NO
*Restart, read, step=4
** ----------------------------------------------------------------
** STEP: Step-5
**
*Step, name=Step-5, nlgeom=YES
*Static
0.02, 1., 1e-05, 0.02
**
** OUTPUT REQUESTS
**
*Restart, write, frequency=0
**
** FIELD OUTPUT: F-Output-1
**
*Output, field
*Node Output
CF, RF, U
*Contact Output
CDISP, CFORCE, CSTRESS
**
** HISTORY OUTPUT: H-Output-1
**
*Output, history, variable=PRESELECT
*End Step

View file

@ -0,0 +1,36 @@
Using the optimization scripts. Contact james.grogan@universityofgalway.ie for further details.
--------------------------------------------------------------
These scripts were developed to perform optmizations with Abaqus and DAKOTA on the ICHEC
system. With small modifications they can also be used to perform optimizations on
windows systems.
Prerequisites:
Abaqus (tested in v6.10)
DAKOTA (tested in v5.2) - needs to be built from source on ICHEC.
Sequence:
1. Launch.pbs
Sends optimization job to ICHEC queue. Loads modules neccessary for DAKOTA and runs the optimization job as
a taskfarm.
2. tasks.inp
Input file for the taskfarm program. Changes to a unique directory for each task an runs DAKOTA with the input file
OptB.in.
3. OptB.in
DAKOTA input file. Tells DAKOTA what sort of optimization to perform. How many parameters to use and what ranges the
parameters fall in. Launchs the preprocessing wrapper script 'PyWrapperB.py' and designates 'Bparams.in' and 'Bparams.out' as the optimization input and output files.
4. PyWrapperB.py
Python wrapper script. Launchs the Abaqus geometry kernel file 'OptB.py'. Launches each abaqus job. Launches the
postprocessor python file 'OptPostB1.py'.
5. OptB.py
Abaqus kernel script. Creates the FE model. Model parameters are read in from DAKOTA through the Bparams.in file.
6. OptPostB1.py
Post-processes the initial simulation. If a design looks promising it launches a corrosion simulation and a second postprocessor OptPostB2.py.
7. OptPostB2.py
Post-processes the corrosion simulation. Returns the objective function value to DAKOTA through the Bparams.out text file.

View file

@ -0,0 +1,4 @@
cd $PBS_O_WORKDIR/N1/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/N2/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/N3/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/N4/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in

View file

@ -0,0 +1,4 @@
cd $PBS_O_WORKDIR/P1/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/P2/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/P3/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/P4/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in

View file

@ -0,0 +1,4 @@
cd $PBS_O_WORKDIR/P1/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in -r dakota.rst -s 114 -w dakota3.rst
cd $PBS_O_WORKDIR/P2/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in -r dakota.rst -s 116 -w dakota3.rst
cd $PBS_O_WORKDIR/P3/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in -r dakota.rst -s 125 -w dakota3.rst
cd $PBS_O_WORKDIR/P4/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in -r dakota.rst -s 138 -w dakota3.rst

View file

@ -0,0 +1 @@
cd $PBS_O_WORKDIR/N1/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in -r dakota.rst -s 124 -w dakota3.rst

View file

@ -0,0 +1,316 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer n(8)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
nbr=0
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData.inc',
1 status='old')
read(101,*)numfaces
do i=1,4*numfaces,4
read(101,*)nfix,n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
c facet(*,12)=fized face flag, facet(*,4-11)=element nodes
do j=1,4
ind=i+j-1
facet(ind,12)=nfix
do k=1,8
facet(ind,3+k)=n(k)
enddo
enddo
do j=1,4
ind=i+j-1
c facet(*,1-3)=nodes in facet
read(101,*)facet(ind,1),facet(ind,2),facet(ind,3)
node=facet(ind,1)
c nbr(node,1)=counter for facets per node
if(nbr(node,1)==0)nbr(node,1)=1
nbr(node,1)=nbr(node,1)+1
c nbr(node,>1)=facet number
nbr(node,nbr(node,1))=ind
enddo
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer np(3)
real fp(6,9),fc(6,3),fe(6,3),fn(6,3),a(3),b(3),c(3),d(3),q(3)
real qnew(3),cp1(3),cp2(3),cp3(3)
if(lnodetype>=3.and.lnodetype<=5)then
C PRINT *,NODE,'IN'
c Analysis Parameters
velocity=0.02d0
tol=1.d-5
c
numFacets=nbr(node,1)-1
c get facet point coords (fp).
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,3
nNode=facet(nFacet,j)
if (j==1)nnode=node
do k=1,3
fp(i,3*(j-1)+k)=crd(nNode,k)
enddo
c print *,node,nNode
c print *,crd(nNode,1),crd(nNode,2),crd(nNode,3)
enddo
enddo
c get facet element centroid(fe)
fe=0.
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,8
nNode=facet(nFacet,j+3)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c move non-fixed facets along unit normals - update fp
dist=velocity*dtime
do i=1,numFacets
nFacet=nbr(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.
dp2=0.
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end

View file

@ -0,0 +1,31 @@
# Python Preprocessor Script for Abaqus Corrosion Model
# J. Grogan, D. Gastaldi - Created. 19-07-11
# Import abaqus modules
from abaqusConstants import *
from abaqus import *
import random
# Create Model, Assembly and Instance objects
modelNames=mdb.models.keys()
corModel=mdb.models[modelNames[0]]
corAssembly=corModel.rootAssembly
corInst=corAssembly.instances['Corrode']
# Create list to store labels of surface elements
numElems=len(corInst.elements)
elemList=[0]*numElems*2
randList=[0]*numElems*2
corSurf=corAssembly.surfaces['CorSurf']
random.seed()
for eachElem in corSurf.elements:
elemList[eachElem.label]=1
randList[eachElem.label]=random.weibullvariate(1.,0.14)
# For each element write surface flag and random number to INC file
incFile=open(modelNames[0]+'.inc','w')
incFile.write("*Initial Conditions,type=solution \n")
j=0
for eachElem in corInst.elements:
label=eachElem.label
incFile.write ("Assembly.Corrode.%i,%i,%f,%i,%i\n"%(label,
elemList[label],randList[label],0,0))
j=j+1
print (float(j)/float(len(corInst.elements)))*100.
incFile.close()

View file

@ -0,0 +1,181 @@
c J. Grogan, 2012
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 jElem(nblock),stateNew(nblock,nstatev),
* field(nblock,nfieldv),stateOld(nblock,nstatev),
* charLength(nblock),rPEEQ(maxblk,1),
* Stress(nblock*6),jData(nblock*6),
* eigVal(nblock,3),coordMp(nblock,3)
c -------------------------------------------------------------------
c Common blocks store element status and random number assigment.
common active(600000)
common rnum(600000)
integer active
integer rnum
c
do k=1,nblock
c -------------------------------------------------------------------
c Update SDVs
do i=1,7
stateNew(k,i)=stateOld(k,i)
enddo
stateNew(k,11)=stateOld(k,11)
c -------------------------------------------------------------------
c Determine Characteristic Element Length
damage=stateOld(k,8)
randE=stateOld(k,9)
activeE=stateOld(k,10)
c -------------------------------------------------------------------
c Check if element is on exposed surface.
do i=2,7
nNum=stateNew(k,i)
if(nNum==0.)cycle
if(active(nNum)==1)then
activeE=1.
if(rnum(nNum)*0.9547>randE)randE=rnum(nNum)*0.9547
endif
enddo
c -------------------------------------------------------------------
c Recover Corrosion Parameters
ukinetic=0.05d0
randE=1.d0
if(activeE>0.99d0)then
if(totaltime>1.5d0)then
dam_inc=(ukinetic/charlength(k))*randE*dt
damage=damage+dam_inc
endif
endif
c -------------------------------------------------------------------
c Remove Fully Damaged Elements
if(damage>=0.999)then
damage=1.d0
stateNew(k,11)=0.d0
active(statenew(k,1))=1.d0
rnum(statenew(k,1))=randE
endif
c -------------------------------------------------------------------
stateNew(k,8)=damage
field(k,1)=damage
stateNew(k,9)=randE
stateNew(k,10)=activeE
c -------------------------------------------------------------------
end do
return
end subroutine vusdfld
subroutine vuanisohyper_inv(nblock,nFiber,nInv,jElem,kIntPt,
* kLayer,kSecPt,cmname,nstatev, nfieldv, nprops,props,tempOld,
* tempNew,fieldOld,fieldNew,stateOld,sInvariant,zeta,uDev,duDi,
* d2uDiDi,stateNew)
c
include 'vaba_param.inc'
c
dimension props(nprops),tempOld(nblock),
* fieldOld(nblock,nfieldv),stateOld(nblock,nstatev),
* tempNew(nblock), fieldNew(nblock,nfieldv),
* stateNew(nblock,nstatev),sInvariant(nblock,nInv),
* zeta(nblock,nFiber*(nFiber-1)/2),uDev(nblock),
* duDi(nblock,nInv),d2uDiDi(nblock,nInv*(nInv+1)/2)
c
parameter(zero = 0.d0, one = 1.d0, two = 2.d0, three = 3.d0)
common active(600000)
common rnum(600000)
integer active
integer rnum
c Material Properties
u = props(1)
rkap = props(2)
rk1 = props(3)
rk2 = props(4)
rp = props(5)
c
c Loop Over Each Element
do k = 1,nblock
c Index Each Invariant according to Abaqus Convention
i1 = 1
i1i1 = 1
i3 = 3
i3i3 = 6
i4 = 4
i1i4 = 7
i4i4 = 10
i6 = 8
i1i6 = 29
i6i6 = 36
c Get Values of each Invariant
ri1 = sinvariant(k,i1)
ri4 = sinvariant(k,i4)
ri6 = sinvariant(k,i6)
c Get Fibre Contributions to UDEV
t = (one - rp) * (ri1 - three) * (ri1 - three)
if(ri4>1.)then
t1 = rk2 * (t + rp * (ri4 - one) * (ri4 - one))
else
t1=0.
endif
if(ri6>1.)then
t2 = rk2 * (t + rp * (ri6 - one) * (ri6 - one))
else
t2=0.
endif
et1 = exp(t1)
et2 = exp(t2)
term1 = rk1 / (two * rk2)
ufibres = term1 * (et1 + et2 - two)
c Get UDEV
udev(k) = u * (ri1 - three) + ufibres
c Get dUdI1
dt1di1 = rk2 * two * (one - rp) * (ri1 - three)
dudi(k,i1) = term1 * dt1di1 * (et1 + et2) + u
c Get dUdI4 and dUdI6
if(ri4>1.)then
dt1di4 = rk2 * two * rp * (ri4 - one)
else
dt1di4 = 0.
endif
if(ri6>1.)then
dt2di6 = rk2 * two * rp * (ri6 - one)
else
dt2di6 = 0.
endif
dudi(k,i4) = term1 * dt1di4 * et1
dudi(k,i6) = term1 * dt2di6 * et2
c Get d2UdI1dI1
d2t1di1di1 = rk2 * two * (one - rp)
d2udidi(k,i1i1) = term1 * (d2t1di1di1 + dt1di1 * dt1di1)
d2udidi(k,i1i1) = d2udidi(k,i1i1) * (et1 + et2)
c Get d2UdI1dI4 and d2UdI4dI4
d2udidi(k,i1i4) = term1 * dt1di4 * dt1di1 * et1
d2t1di4di4 = rk2 * two * rp
d2udidi(k,i4i4) = term1 * (dt1di4 * dt1di4 + d2t1di4di4)
d2udidi(k,i4i4) = d2udidi(k,i4i4) * et1
c Get d2UdI1dI6 and d2UdI6dI6
d2udidi(k,i1i6) = term1 * dt2di6 * dt1di1 * et2
d2t2di6di6 = rk2 * two * rp
d2udidi(k,i6i6) = term1 * (dt2di6 * dt2di6 + d2t2di6di6)
d2udidi(k,i6i6) = d2udidi(k,i6i6) * et2
end do
c For the compressible case
if(rkap > zero) then
do k = 1,nblock
rj = sInvariant(k,i3)
dudi(k,i3) = rkap * (rj-one)
c duDi(k,i3) = (rkap/two) * (rj - one/rj)
d2udidi(k,i3i3) = rkap
c d2uDiDi(k,i3i3)= (rkap/two) * (one + one/ rj / rj)
end do
end if
return
end

View file

@ -0,0 +1,201 @@
c J. Grogan, 2012
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 jElem(nblock),stateNew(nblock,nstatev),
* field(nblock,nfieldv),stateOld(nblock,nstatev),
* charLength(nblock),rPEEQ(maxblk,1),
* Stress(nblock*6),jData(nblock*6),
* eigVal(nblock,3),coordMp(nblock,3)
c -------------------------------------------------------------------
c Common blocks store element status and random number assigment.
common active(600000)
common rnum(600000)
common ibcheck
integer active
integer rnum
integer ibcheck
character*256 outdir
c
if (ibcheck/=5)then
call vgetoutdir(outdir,lenoutdir)
open(unit=105,file=outdir(1:lenoutdir)//'/NBOPTP.inc',
* status='old')
do while (ioe==0)
read(105,*,iostat=ioe)ielnum,frnum
if(ioe==0)rnum(ielnum)=frnum
enddo
close(unit=105)
ibcheck=5
endif
do k=1,nblock
c -------------------------------------------------------------------
c Update SDVs
do i=1,7
stateNew(k,i)=stateOld(k,i)
enddo
stateNew(k,11)=stateOld(k,11)
c -------------------------------------------------------------------
c Determine Characteristic Element Length
damage=stateOld(k,8)
if(steptime<2.*dt)then
randE=rnum(statenew(k,1))
else
randE=stateOld(k,9)
endif
activeE=stateOld(k,10)
c -------------------------------------------------------------------
c Check if element is on exposed surface.
do i=2,7
nNum=stateNew(k,i)
if(nNum==0.)cycle
if(active(nNum)==1)then
activeE=1.
if(rnum(nNum)*0.94>randE)randE=rnum(nNum)*0.94
endif
enddo
c -------------------------------------------------------------------
c Recover Corrosion Parameters
ukinetic=0.000025d0
c randE=1.d0
if(activeE>0.99d0)then
if(totaltime>1.5d0)then
dam_inc=(ukinetic/charlength(k))*randE*dt
damage=damage+dam_inc
endif
endif
c -------------------------------------------------------------------
c Remove Fully Damaged Elements
if(damage>=0.999)then
damage=1.d0
stateNew(k,11)=0.d0
active(statenew(k,1))=1.d0
rnum(statenew(k,1))=randE
endif
c -------------------------------------------------------------------
stateNew(k,8)=damage
field(k,1)=damage
stateNew(k,9)=randE
stateNew(k,10)=activeE
c -------------------------------------------------------------------
end do
return
end subroutine vusdfld
subroutine vuanisohyper_inv(nblock,nFiber,nInv,jElem,kIntPt,
* kLayer,kSecPt,cmname,nstatev, nfieldv, nprops,props,tempOld,
* tempNew,fieldOld,fieldNew,stateOld,sInvariant,zeta,uDev,duDi,
* d2uDiDi,stateNew)
c
include 'vaba_param.inc'
c
dimension props(nprops),tempOld(nblock),
* fieldOld(nblock,nfieldv),stateOld(nblock,nstatev),
* tempNew(nblock), fieldNew(nblock,nfieldv),
* stateNew(nblock,nstatev),sInvariant(nblock,nInv),
* zeta(nblock,nFiber*(nFiber-1)/2),uDev(nblock),
* duDi(nblock,nInv),d2uDiDi(nblock,nInv*(nInv+1)/2)
c
parameter(zero = 0.d0, one = 1.d0, two = 2.d0, three = 3.d0)
common active(600000)
common rnum(600000)
common ibcheck
integer active
integer rnum
integer ibcheck
c Material Properties
u = props(1)
rkap = props(2)
rk1 = props(3)
rk2 = props(4)
rp = props(5)
c
c Loop Over Each Element
do k = 1,nblock
c Index Each Invariant according to Abaqus Convention
i1 = 1
i1i1 = 1
i3 = 3
i3i3 = 6
i4 = 4
i1i4 = 7
i4i4 = 10
i6 = 8
i1i6 = 29
i6i6 = 36
c Get Values of each Invariant
ri1 = sinvariant(k,i1)
ri4 = sinvariant(k,i4)
ri6 = sinvariant(k,i6)
c Get Fibre Contributions to UDEV
t = (one - rp) * (ri1 - three) * (ri1 - three)
if(ri4>1.)then
t1 = rk2 * (t + rp * (ri4 - one) * (ri4 - one))
else
t1=0.
endif
if(ri6>1.)then
t2 = rk2 * (t + rp * (ri6 - one) * (ri6 - one))
else
t2=0.
endif
et1 = exp(t1)
et2 = exp(t2)
term1 = rk1 / (two * rk2)
ufibres = term1 * (et1 + et2 - two)
c Get UDEV
udev(k) = u * (ri1 - three) + ufibres
c Get dUdI1
dt1di1 = rk2 * two * (one - rp) * (ri1 - three)
dudi(k,i1) = term1 * dt1di1 * (et1 + et2) + u
c Get dUdI4 and dUdI6
if(ri4>1.)then
dt1di4 = rk2 * two * rp * (ri4 - one)
else
dt1di4 = 0.
endif
if(ri6>1.)then
dt2di6 = rk2 * two * rp * (ri6 - one)
else
dt2di6 = 0.
endif
dudi(k,i4) = term1 * dt1di4 * et1
dudi(k,i6) = term1 * dt2di6 * et2
c Get d2UdI1dI1
d2t1di1di1 = rk2 * two * (one - rp)
d2udidi(k,i1i1) = term1 * (d2t1di1di1 + dt1di1 * dt1di1)
d2udidi(k,i1i1) = d2udidi(k,i1i1) * (et1 + et2)
c Get d2UdI1dI4 and d2UdI4dI4
d2udidi(k,i1i4) = term1 * dt1di4 * dt1di1 * et1
d2t1di4di4 = rk2 * two * rp
d2udidi(k,i4i4) = term1 * (dt1di4 * dt1di4 + d2t1di4di4)
d2udidi(k,i4i4) = d2udidi(k,i4i4) * et1
c Get d2UdI1dI6 and d2UdI6dI6
d2udidi(k,i1i6) = term1 * dt2di6 * dt1di1 * et2
d2t2di6di6 = rk2 * two * rp
d2udidi(k,i6i6) = term1 * (dt2di6 * dt2di6 + d2t2di6di6)
d2udidi(k,i6i6) = d2udidi(k,i6i6) * et2
end do
c For the compressible case
if(rkap > zero) then
do k = 1,nblock
rj = sInvariant(k,i3)
dudi(k,i3) = rkap * (rj-one)
c duDi(k,i3) = (rkap/two) * (rj - one/rj)
d2udidi(k,i3i3) = rkap
c d2uDiDi(k,i3i3)= (rkap/two) * (one + one/ rj / rj)
end do
end if
return
end

View file

@ -0,0 +1,100 @@
subroutine vuanisohyper_inv(nblock,nFiber,nInv,jElem,kIntPt,
* kLayer,kSecPt,cmname,nstatev, nfieldv, nprops,props,tempOld,
* tempNew,fieldOld,fieldNew,stateOld,sInvariant,zeta,uDev,duDi,
* d2uDiDi,stateNew)
c
include 'vaba_param.inc'
c
dimension props(nprops),tempOld(nblock),
* fieldOld(nblock,nfieldv),stateOld(nblock,nstatev),
* tempNew(nblock), fieldNew(nblock,nfieldv),
* stateNew(nblock,nstatev),sInvariant(nblock,nInv),
* zeta(nblock,nFiber*(nFiber-1)/2),uDev(nblock),
* duDi(nblock,nInv),d2uDiDi(nblock,nInv*(nInv+1)/2)
c
parameter(zero = 0.d0, one = 1.d0, two = 2.d0, three = 3.d0)
c Material Properties
u = props(1)
rkap = props(2)
rk1 = props(3)
rk2 = props(4)
rp = props(5)
c
c Loop Over Each Element
do k = 1,nblock
c Index Each Invariant according to Abaqus Convention
i1 = 1
i1i1 = 1
i3 = 3
i3i3 = 6
i4 = 4
i1i4 = 7
i4i4 = 10
i6 = 8
i1i6 = 29
i6i6 = 36
c Get Values of each Invariant
ri1 = sinvariant(k,i1)
ri4 = sinvariant(k,i4)
ri6 = sinvariant(k,i6)
c Get Fibre Contributions to UDEV
t = (one - rp) * (ri1 - three) * (ri1 - three)
if(ri4>1.)then
t1 = rk2 * (t + rp * (ri4 - one) * (ri4 - one))
else
t1=0.
endif
if(ri6>1.)then
t2 = rk2 * (t + rp * (ri6 - one) * (ri6 - one))
else
t2=0.
endif
et1 = exp(t1)
et2 = exp(t2)
term1 = rk1 / (two * rk2)
ufibres = term1 * (et1 + et2 - two)
c Get UDEV
udev(k) = u * (ri1 - three) + ufibres
c Get dUdI1
dt1di1 = rk2 * two * (one - rp) * (ri1 - three)
dudi(k,i1) = term1 * dt1di1 * (et1 + et2) + u
c Get dUdI4 and dUdI6
if(ri4>1.)then
dt1di4 = rk2 * two * rp * (ri4 - one)
else
dt1di4 = 0.
endif
if(ri6>1.)then
dt2di6 = rk2 * two * rp * (ri6 - one)
else
dt2di6 = 0.
endif
dudi(k,i4) = term1 * dt1di4 * et1
dudi(k,i6) = term1 * dt2di6 * et2
c Get d2UdI1dI1
d2t1di1di1 = rk2 * two * (one - rp)
d2udidi(k,i1i1) = term1 * (d2t1di1di1 + dt1di1 * dt1di1)
d2udidi(k,i1i1) = d2udidi(k,i1i1) * (et1 + et2)
c Get d2UdI1dI4 and d2UdI4dI4
d2udidi(k,i1i4) = term1 * dt1di4 * dt1di1 * et1
d2t1di4di4 = rk2 * two * rp
d2udidi(k,i4i4) = term1 * (dt1di4 * dt1di4 + d2t1di4di4)
d2udidi(k,i4i4) = d2udidi(k,i4i4) * et1
c Get d2UdI1dI6 and d2UdI6dI6
d2udidi(k,i1i6) = term1 * dt2di6 * dt1di1 * et2
d2t2di6di6 = rk2 * two * rp
d2udidi(k,i6i6) = term1 * (dt2di6 * dt2di6 + d2t2di6di6)
d2udidi(k,i6i6) = d2udidi(k,i6i6) * et2
end do
c For the compressible case
if(rkap > zero) then
do k = 1,nblock
rj = sInvariant(k,i3)
dudi(k,i3) = rkap * (rj-one)
c duDi(k,i3) = (rkap/two) * (rj - one/rj)
d2udidi(k,i3i3) = rkap
c d2uDiDi(k,i3i3)= (rkap/two) * (one + one/ rj / rj)
end do
end if
return
end

View file

@ -0,0 +1,48 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
from abaqus import *
# Define Part
aModel=mdb.models['Straight']
aAss=aModel.rootAssembly
bPart=aModel.parts['p3']
tb=0.24
A=2.4
ecen=0.
ellip=0.
bean_m=0.
bean_exp=1.5
t1=5.
t2=5.
xp1=0.5
xp2=0.5
rL1=11.
rL2=10.1787602
radius=rL2/(2.*pi)
r2=15.
# Map Part
nodelist=[]
coordlist=[]
for eachnode in bPart.nodes:
x_cor=eachnode.coordinates[0]
y_cor=eachnode.coordinates[1]
z_cor=eachnode.coordinates[2]
rFraction=z_cor/tb
rindex1=(y_cor/rL1)**(-log(2.)/log(xp1))
rbracket1=(sin(pi*rindex1))**t1
rad_plaque=1.+A*rbracket1
rheight1=tb+(A-tb)*rbracket1
theta=x_cor/radius
x_cor=(radius-rad_plaque*z_cor)*cos(theta)
y_cor=y_cor
z_cor=(radius-rad_plaque*z_cor)*sin(theta)-ecen*rbracket1*rFraction
if x_cor>0.:
x_cor=x_cor+ellip*abs(x_cor)*rFraction*rbracket1
else:
x_cor=x_cor-ellip*abs(x_cor)*rFraction*rbracket1
z_cor=z_cor+bean_m*(abs(x_cor)**bean_exp)*rFraction*rbracket1
# theta=y_cor/r2
# y_cor=(r2-z_cor)*cos(theta)
# z_cor=(r2-z_cor)*sin(theta)
nodelist.append(eachnode)
coordlist.append((x_cor,y_cor,z_cor))
bPart.editNode(nodes=nodelist,coordinates=coordlist)

View file

@ -0,0 +1,45 @@
# This is a pre-processor script for 3D ALE corrosion analysis.
# Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
from abaqusConstants import *
from abaqus import *
#
aModel=mdb.models['Dream6']
aPart=aModel.parts['AMesh']
incFile=open('NodeData.inc','w')
#
numFaces=0
pstring=''
# Cycle through all element faces
for eachFace in aPart.elementFaces:
# Check if Face is on external Surface
if len(eachFace.getElements())==1:
numFaces=numFaces+1
faceNodes=eachFace.getNodes()
# Identify 'Fixed' Faces
fixed=1
try:
fSet=aPart.sets['Fixed']
for eachNode in faceNodes:
if eachNode not in fSet.nodes:
fixed=0
break
except:
fixed=0
pstring=pstring+str(fixed)+' '
# Write Element Nodes
eNodes=[]
for eachNode in eachFace.getElements()[0].getNodes():
pstring=pstring+str(eachNode.label)+' '
pstring=pstring+'\n'
# Write Each Face Nodes and Corresponding Connected Nodes
for eachNode in faceNodes:
pstring=pstring+str(eachNode.label)+' '
for eachEdge in eachNode.getElemEdges():
for eachENode in eachEdge.getNodes():
if eachENode.label != eachNode.label and eachENode in faceNodes:
pstring=pstring+str(eachENode.label)+' '
pstring=pstring+'\n'
#
incFile.write(str(numFaces)+'\n')
incFile.write(pstring)
incFile.close()

View file

@ -0,0 +1,33 @@
from abaqusConstants import *
from odbAccess import *
odbfilename='tpit3.odb'
resFile='Diams20.dat'
outFile = open(resFile,"w")
odb=openOdb(path=odbfilename)
# create sets
addNodes=[]
tol1=0.005
tol2=0.005
minval=-5.0
# Find Inner Nodes
for eachNode in odb.rootAssembly.instances['PLAQUE-1'].nodes:
x=eachNode.coordinates[0]
y=eachNode.coordinates[1]
dist=sqrt(x*x+y*y)
if dist<0.82:
addNodes.append(eachNode.label)
odb.rootAssembly.NodeSetFromNodeLabels(name='Min13', nodeLabels=(('PLAQUE-1',addNodes),))
aSet=odb.rootAssembly.nodeSets['Min13']
print aSet
# Find Min Radius
for eachFrame in odb.steps['Step-3'].frames:
if eachFrame.frameValue>.5:
dist=0.
for eachValue in eachFrame.fieldOutputs["U"].getSubset(region=aSet).values:
x=eachValue.data[0]
y=eachValue.data[1]
dist=dist+sqrt(x*x+y*y)
dist=dist/(len(eachFrame.fieldOutputs["U"].getSubset(region=aSet).values))
print dist,eachFrame.frameValue
outFile.write('%f %f \n'%(dist,eachFrame.frameValue))
outFile.close()

View file

@ -0,0 +1,40 @@
Program Balloon_Wrap
!
! Program to map plaque from flat to cylindrical shape.
!
real pi,x_cor,y_cor,z_cor,theta,radius,theta_hat,rad_hat,alpha,beta,phi
real inner_radius,outer_radius,num_folds,multiplier
integer node_num
!
open(unit=10,file='in.dat',status='old')
open(unit=11,file='out.dat',status='unknown')
!
tb=0.2
A=0.5
ecen=0.2
t1=5.
t2=5.
xp1=0.5
xp2=0.5
rL1=11.
rL2=8.6708
radius=1.38
!
do i=1, 69264
read(10,*)node_num,x_cor,y_cor,z_cor
rFraction=z_cor/tb
rindex1=(y_cor/rL1)**(-log(2.)/log(xp1))
rbracket1=(sin(3.1415*rindex1))**t1
rad_plaque=1.+A*rbracket1
rheight1=tb+(A-tb)*rbracket1
!
z_cor=rheight1*rFraction
!
xfrac=x_cor/rL2
theta=x_cor/radius
x_cor=(radius-rad_plaque*z_cor)*cos(theta)
y_cor=y_cor
z_cor=(radius-rad_plaque*z_cor)*sin(theta)+ecen*rbracket1*rFraction
write(11,*)node_num,',',x_cor,',',y_cor,',',z_cor
enddo
end program

View file

@ -0,0 +1,40 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
from abaqus import *
from odbAccess import *
import regionToolset
import sys
import os
import interaction
import random
mname='StraightMagic2'
mtype=1
jobName=mname
aModel=mdb.models[mname]
aAss=aModel.rootAssembly
bPart=aModel.parts['Stent1']
random.seed(2344564)
incFile=open('NBR.inc','w')
onSurf=[]
for i in range(0,300000):
onSurf.append(0)
incFile.write("*INITIAL CONDITIONS,TYPE=SOLUTION \n")
if mtype==1:
for eachSN in bPart.sets['Set-1'].elements:
onSurf[eachSN.label]=1
for eachElement in bPart.elements:
label=eachElement.label
nbrs=[]
for eachNbr in eachElement.getAdjacentElements():
nbrs.append(eachNbr.label)
for i in range(0,6-len(eachElement.getAdjacentElements())):
nbrs.append(0)
if onSurf[label]==1:
rnum=random.weibullvariate(1.,0.2)
else:
rnum=0.
incFile.write("Assembly.Stent1-1.%i, %i, %i, %i, %i, %i, %i, %i, \n"%(label,label,
nbrs[0],nbrs[1],nbrs[2],nbrs[3],nbrs[4],nbrs[5]))
incFile.write("%i, %f, %i, %i, \n"%(0,rnum,onSurf[label],0))
incFile.close()

View file

@ -0,0 +1,12 @@
from abaqusConstants import *
from abaqus import *
aModel=mdb.models['Straight']
aPart=aModel.parts['PLAQUE1']
Radius=15.
for eachnode in aPart.nodes:
theta=eachnode.coordinates[1]/Radius
newcoord1=(Radius-eachnode.coordinates[0])*sin(theta)
newcoord2=(Radius-eachnode.coordinates[0])*cos(theta)
newcoord3=eachnode.coordinates[2]
aPart.editNode(nodes=eachnode,coordinate1=newcoord1,coordinate2=newcoord2,
coordinate3=newcoord3)

View file

@ -0,0 +1,55 @@
Program Balloon_Wrap
!
! Program to map an unfolded ballon geometry onto a folded configuration (Based on Laroche Paper)
! Input: File containing nodal coords of ballon geometry (Abaqus INP Format)
! Output: File containing nodal coords of mapped ballon geometry (Abaqus INP Format)
! Rev. 1 - J. Grogan - 07/07/10
!
real pi,x_cor,y_cor,z_cor,theta,radius,theta_hat,rad_hat,alpha,beta,phi
real inner_radius,outer_radius,num_folds,multiplier
integer node_num
logical outer_flap
!
open(unit=10,file='in.dat',status='old')
open(unit=11,file='out.dat',status='unknown')
!
pi=acos(-1.)
inner_radius=0.25
outer_radius=0.43
num_folds=3.
phi=(2*pi)/num_folds
outer_flap=.false.
!
do i=1, 9821
read(10,*)node_num,x_cor,y_cor,z_cor
theta=(atan2(z_cor,x_cor))
radius=sqrt(z_cor*z_cor+x_cor*x_cor)
!
if(theta<0.)then
theta=theta+2*pi
endif
!
beta=(phi/2.)*(1.+(2*radius)/(inner_radius+outer_radius))
alpha=((outer_radius+inner_radius)/(2*radius))*beta
!
do j=1,num_folds
if((theta>=(j-1)*phi).and.(theta<=(alpha+(j-1)*phi)))then
multiplier=j-1
outer_flap=.true.
elseif((theta>=(alpha+(j-1)*phi)).and.(theta<=(j*phi)))then
multiplier=j
outer_flap=.false.
endif
enddo
!
if(outer_flap)then
theta_hat=(beta/alpha)*(theta-multiplier*phi)+multiplier*phi
rad_hat=inner_radius+((outer_radius-inner_radius)/beta)*(theta_hat-multiplier*phi)
else
theta_hat=((beta-phi)/(phi-alpha))*(multiplier*phi-theta)+multiplier*phi
rad_hat=inner_radius+((outer_radius-inner_radius)/(beta-phi))*(theta_hat-multiplier*phi)
endif
!
write(11,*)node_num,',',rad_hat*cos(theta_hat),',',y_cor,',',rad_hat*sin(theta_hat)
enddo
end program

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

View file

@ -0,0 +1,316 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer n(8)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
nbr=0
open(unit=101,file=outdir(1:lenoutdir)//'/NodeData.inc',
1 status='old')
read(101,*)numfaces
do i=1,4*numfaces,4
read(101,*)nfix,n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
c facet(*,12)=fized face flag, facet(*,4-11)=element nodes
do j=1,4
ind=i+j-1
facet(ind,12)=nfix
do k=1,8
facet(ind,3+k)=n(k)
enddo
enddo
do j=1,4
ind=i+j-1
c facet(*,1-3)=nodes in facet
read(101,*)facet(ind,1),facet(ind,2),facet(ind,3)
node=facet(ind,1)
c nbr(node,1)=counter for facets per node
if(nbr(node,1)==0)nbr(node,1)=1
nbr(node,1)=nbr(node,1)+1
c nbr(node,>1)=facet number
nbr(node,nbr(node,1))=ind
enddo
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer np(3)
real fp(6,9),fc(6,3),fe(6,3),fn(6,3),a(3),b(3),c(3),d(3),q(3)
real qnew(3),cp1(3),cp2(3),cp3(3)
if(lnodetype>=3.and.lnodetype<=5)then
C PRINT *,NODE,'IN'
c Analysis Parameters
velocity=0.01d0
tol=1.d-5
c
numFacets=nbr(node,1)-1
c get facet point coords (fp).
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,3
nNode=facet(nFacet,j)
if (j==1)nnode=node
do k=1,3
fp(i,3*(j-1)+k)=crd(nNode,k)
enddo
c print *,node,nNode
c print *,crd(nNode,1),crd(nNode,2),crd(nNode,3)
enddo
enddo
c get facet element centroid(fe)
fe=0.
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,8
nNode=facet(nFacet,j+3)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c move non-fixed facets along unit normals - update fp
dist=velocity*dtime
do i=1,numFacets
nFacet=nbr(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.
dp2=0.
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end

View file

@ -0,0 +1,27 @@
#!/bin/bash
#PBS -l nodes=2:ppn=12
#PBS -l walltime=9:00:00
#PBS -N Opt_Stiffness_P3
#PBS -A ngeng036b
#PBS -r n
#PBS -j oe
#PBS -m bea
#PBS -M lumpwood@gmail.com
#PBS -V
cd $PBS_O_WORKDIR
module load taskfarm2
module load intel-cc
module load intel-fc
module load intel-mkl
module load boost-intel
module load intel-mpi
module load abaqus
taskfarm tasks.inp

Binary file not shown.

View file

@ -0,0 +1,30 @@
strategy,
single
#pareto_set
#graphics
#opt_method_pointer = "NLP"
#multi_objective_weight_sets =
#1. 0.
#0. 1.
#.5 .5
tabular_graphics_data
method,
id_method = "NLP"
efficient_global
seed = 79877
variables,
continuous_design = 6
lower_bounds 0.11 0.11 0.6 1.0 0.1 0.001
upper_bounds 0.16 0.14 1.0 1.2 0.5 0.04
descriptors "x1" "x2" "x3" "x4" "x5" "x6"
interface,
fork asynchronous evaluation_concurrency = 1
analysis_drivers = 'abaqus python PyWrapperB.py --'
parameters_file = 'Bparams.in'
results_file = 'Bresults.out'
file_tag
file_save
responses,
objective_functions = 1
no_gradients
no_hessians

View file

@ -0,0 +1,14 @@
from part import *
from material import *
from section import *
from assembly import *
from step import *
from interaction import *
from load import *
from mesh import *
from job import *
from sketch import *
from visualization import *
from connectorBehavior import *
mdb.models['Dream6'].boundaryConditions['BC-2'].setValues(u1=-0.7)
# Save by 05365350 on Fri Oct 19 21:01:57 2012

View file

@ -0,0 +1,126 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
from abaqus import *
from odbAccess import *
import regionToolset
import sys
import os
import interaction
import mesh
#Read in Model Parameters
paramFile=sys.argv[-1]
jobName=paramFile.encode("hex")
os.system ("cp %s %s" % ('OptB.cae', jobName+'.cae'))
mdb=openMdb(jobName+'.cae')
inFile = open(paramFile,"r")
inFile.readline()
x1,name1=inFile.readline().split()
x2,name2=inFile.readline().split()
x3,name3=inFile.readline().split()
x4,name4=inFile.readline().split()
x5,name5=inFile.readline().split()
x6,name6=inFile.readline().split()
mname='Dream6'
#Generate New Model
aModel=mdb.models[mname]
aAss=aModel.rootAssembly
tol=0.0001
radius=0.75
numCrowns=6.
W=float(x1)
T=float(x2)
L1=float(x3)
L2=float(x4)*L1
L3=float(x5)
H2=float(x6)
H1=(pi*radius)/(2.*numCrowns)
# Modify Part
aPart=aModel.parts['Geom']
aSketch=aPart.features['Solid extrude-1'].sketch
aModel.ConstrainedSketch(name='__edit__', objectToCopy=aSketch)
bSketch=aModel.sketches['__edit__']
bSketch.parameters['w'].setValues(expression=str(W/2.))
bSketch.parameters['h1'].setValues(expression=str(H1))
bSketch.parameters['h2'].setValues(expression=str(H2))
bSketch.parameters['l1'].setValues(expression=str(L1))
bSketch.parameters['l2'].setValues(expression=str(L2))
bSketch.parameters['l3'].setValues(expression=str(L3))
aPart.features['Solid extrude-1'].setValues(sketch=bSketch)
del aModel.sketches['__edit__']
aPart.features['Solid extrude-1'].setValues(depth=T)
aPart.regenerate()
# Mesh Part
aPart.seedPart(size=W/6., deviationFactor=0.1)
aPart.generateMesh()
# Create Orphan Mesh
aPart.PartFromMesh(name='AMesh')
bPart=aModel.parts['AMesh']
# Create Sets,Sections,Surfaces
for nameSet,eachSet in aPart.sets.items():
bPart.Set(name=nameSet, nodes=eachSet.nodes)
bPart.Set(name='AllE', elements=aPart.sets['All'].elements)
bPart.Set(name='InnerE', elements=aPart.sets['Inner'].elements)
bPart.Set(name='OuterE', elements=aPart.sets['Outer'].elements)
region = regionToolset.Region(elements=bPart.elements)
bPart.SectionAssignment(region=region, sectionName='Magnesium')
aPart=aModel.parts['AMesh']
elemType1 = mesh.ElemType(elemCode=C3D8R, elemLibrary=STANDARD,
kinematicSplit=AVERAGE_STRAIN, secondOrderAccuracy=OFF,
hourglassControl=ENHANCED, distortionControl=DEFAULT)
pickedRegions =(aPart.elements, )
aPart.setElementType(regions=pickedRegions, elemTypes=(elemType1, ))
# Wrap Part
nlist=[]
clist=[]
for eachnode in aPart.nodes:
theta=eachnode.coordinates[1]/radius
newcoord1=eachnode.coordinates[0]
newcoord2=(radius-eachnode.coordinates[2])*cos(theta)
newcoord3=(radius-eachnode.coordinates[2])*sin(theta)
nlist.append(eachnode)
clist.append((newcoord1,newcoord2,newcoord3))
aPart.editNode(nodes=nlist,coordinates=clist)
aPart.regenerate()
aAss.regenerate()
aInst=aAss.instances['AMesh-1']
aModel.rootAssembly.Set(name='Set-1',nodes=aInst.nodes)
incFile=open('NodeData.inc','w')
numFaces=0
pstring=''
# Cycle through all element faces
for eachFace in aPart.elementFaces:
# Check if Face is on external Surface
if len(eachFace.getElements())==1:
numFaces=numFaces+1
faceNodes=eachFace.getNodes()
# Identify 'Fixed' Faces
fixed=1
try:
fSet=aPart.sets['Fixed']
for eachNode in faceNodes:
if eachNode not in fSet.nodes:
fixed=0
break
except:
fixed=0
pstring=pstring+str(fixed)+' '
# Write Element Nodes
eNodes=[]
for eachNode in eachFace.getElements()[0].getNodes():
pstring=pstring+str(eachNode.label)+' '
pstring=pstring+'\n'
# Write Each Face Nodes and Corresponding Connected Nodes
for eachNode in faceNodes:
pstring=pstring+str(eachNode.label)+' '
for eachEdge in eachNode.getElemEdges():
for eachENode in eachEdge.getNodes():
if eachENode.label != eachNode.label and eachENode in faceNodes:
pstring=pstring+str(eachENode.label)+' '
pstring=pstring+'\n'
incFile.write(str(numFaces)+'\n')
incFile.write(pstring)
incFile.close()
mdb.Job(name=jobName, model=mname)
mdb.jobs[jobName].writeInput(consistencyChecking=OFF)
mdb.close()

View file

@ -0,0 +1,34 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
from odbAccess import *
import sys
import os
jobName=sys.argv[-2]
resFile=sys.argv[-1]
resFile2=resFile+'.b'
odbfilename=jobName+'.odb'
odb=openOdb(path=odbfilename)
aFrame=odb.steps["Step-1"].frames[-1]
maxStrain=0.
for currentStrain in aFrame.fieldOutputs["LE"].values:
if currentStrain.instance.name=='AMESH-1':
if currentStrain.maxPrincipal>maxStrain:
maxStrain=currentStrain.maxPrincipal
outFile = open(resFile,"w")
if maxStrain>0.1256:
outFile = open(resFile,"w")
outFile2 = open(resFile2,"w")
objFn=1.+maxStrain
outFile.write("%12.6f \n " % (objFn))
outFile2.write("%12.6f \n " % (maxStrain))
outFile.close()
outFile2.close()
odb.close()
else:
outFile2 = open(resFile2,"w")
outFile2.write("%12.6f \n " % (maxStrain))
outFile2.close()
odb.close()
os.system('abaqus j=R1'+jobName+' oldjob='+jobName+' inp=Restart1 cpus=6 inter user=ALE20')
os.system('abaqus j=R2'+jobName+' oldjob=R1'+jobName+' inp=Restart2 cpus=6 inter user=ALE20')
os.system('abaqus python OptPostB2.py -- R2'+jobName+' '+resFile)

View file

@ -0,0 +1,46 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
from odbAccess import *
import sys
import os
jobName=sys.argv[-2]
resFile=sys.argv[-1]
odbfilename=jobName+'.odb'
try:
odb=openOdb(path=odbfilename)
aNod=odb.rootAssembly.instances['AMESH-1'].nodeSets['E1'].nodes[0].coordinates[0]
bNod=odb.rootAssembly.instances['AMESH-1'].nodeSets['E2'].nodes[0].coordinates[0]
rlen=abs(aNod-bNod)
check=0.
try:
for eachFrame in odb.steps["Step-5"].frames:
tforce=0.
for currentForce in eachFrame.fieldOutputs["CNORMF ASSEMBLY_AOUTER/ASSEMBLY_SURF-1"].values:
fx=currentForce.data[0]
fy=currentForce.data[1]
fz=currentForce.data[2]
tforce=tforce+sqrt(fx*fx+fy*fy+fz*fz)
aSet=odb.rootAssembly.instances['OUTER-1']
uy=eachFrame.fieldOutputs["U"].getSubset(region=aSet).values[0].data[1]
uz=eachFrame.fieldOutputs["U"].getSubset(region=aSet).values[0].data[2]
rad=sqrt(uy*uy+uz*uz)
if tforce>0.:
check=check+1
if check==2:
f1=tforce
r1=rad
if check==5:
f2=tforce
r2=rad
break
stiff=abs(f2-f1)/abs(r2-r1)
except:
stiff=0.
stiff=stiff/rlen
except:
stiff=0.
outFile = open(resFile,"w")
objFn=1.-(0.15*abs(stiff))
outFile.write("%12.6f \n " % (objFn))
outFile.close()
odb.close()

View file

@ -0,0 +1,15 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
import sys
import os
import subprocess
#
resFile=sys.argv[-1]
paramFile=sys.argv[-2]
jobName=paramFile.encode("hex")
# Run Preprocessor
os.system("abaqus cae noGUI=OptB.py -- "+paramFile)
# Run Job
os.system('abaqus j='+jobName+' cpus=6 inter user=ALE20 mp_mode=mpi')
# Run Postprocessor
os.system('abaqus python OptPostB1.py -- '+jobName+' '+resFile)

View file

@ -0,0 +1,69 @@
*Heading
** Job name: Restart Model name: Dream6R
** Generated by: Abaqus/CAE 6.10-1
*Preprint, echo=NO, model=NO, history=NO, contact=NO
*Restart, read, step=2
**
** STEP: Step-3
**
*Step, name=Step-3, nlgeom=YES
*Static
0.05, 1., 1e-05, 0.05
*Adaptive Mesh, elset=AMesh-1.AllE, frequency=1, mesh sweeps=10, op=NEW
**
** ADAPTIVE MESH CONSTRAINTS
**
** Name: Ada-Cons-1 Type: Velocity/Angular velocity
*Adaptive Mesh Constraint, user, type=VELOCITY
AMesh-1.Const
**
** OUTPUT REQUESTS
**
**
*field,user
set-1
** FIELD OUTPUT: F-Output-1
**
*Output, field
*Node Output
CF, RF, U
*Element Output, directions=YES
LE, PE, PEEQ, PEMAG, S
*Contact Output
CDISP, CFORCE, CSTRESS
**
** HISTORY OUTPUT: H-Output-1
**
*Output, history, variable=PRESELECT
*End Step
** ----------------------------------------------------------------
** STEP: Step-4
**
*Step, name=Step-4, nlgeom=YES
*Static
0.05, 0.05, 5e-07, 0.05
*Adaptive Mesh, op=NEW
**
** ADAPTIVE MESH CONSTRAINTS
**
** Name: Ada-Cons-1 Type: Velocity/Angular velocity
*Adaptive Mesh Constraint, op=NEW
**
** OUTPUT REQUESTS
**
*Restart, write, number interval=1, time marks=NO
**
** FIELD OUTPUT: F-Output-1
**
*Output, field
*Node Output
CF, RF, U
*Element Output, directions=YES
LE, PE, PEEQ, PEMAG, S
*Contact Output
CDISP, CFORCE, CSTRESS
**
** HISTORY OUTPUT: H-Output-1
**
*Output, history, variable=PRESELECT
*End Step

View file

@ -0,0 +1,28 @@
*Heading
** Job name: Restart Model name: Dream6R
** Generated by: Abaqus/CAE 6.10-1
*Preprint, echo=NO, model=NO, history=NO, contact=NO
*Restart, read, step=4
** ----------------------------------------------------------------
** STEP: Step-5
**
*Step, name=Step-5, nlgeom=YES
*Static
0.02, 1., 1e-05, 0.02
**
** OUTPUT REQUESTS
**
*Restart, write, frequency=0
**
** FIELD OUTPUT: F-Output-1
**
*Output, field
*Node Output
CF, RF, U
*Contact Output
CDISP, CFORCE, CSTRESS
**
** HISTORY OUTPUT: H-Output-1
**
*Output, history, variable=PRESELECT
*End Step

View file

@ -0,0 +1,36 @@
Using the optimization scripts. Contact james.grogan@universityofgalway.ie for further details.
--------------------------------------------------------------
These scripts were developed to perform optmizations with Abaqus and DAKOTA on the ICHEC
system. With small modifications they can also be used to perform optimizations on
windows systems.
Prerequisites:
Abaqus (tested in v6.10)
DAKOTA (tested in v5.2) - needs to be built from source on ICHEC.
Sequence:
1. Launch.pbs
Sends optimization job to ICHEC queue. Loads modules neccessary for DAKOTA and runs the optimization job as
a taskfarm.
2. tasks.inp
Input file for the taskfarm program. Changes to a unique directory for each task an runs DAKOTA with the input file
OptB.in.
3. OptB.in
DAKOTA input file. Tells DAKOTA what sort of optimization to perform. How many parameters to use and what ranges the
parameters fall in. Launchs the preprocessing wrapper script 'PyWrapperB.py' and designates 'Bparams.in' and 'Bparams.out' as the optimization input and output files.
4. PyWrapperB.py
Python wrapper script. Launchs the Abaqus geometry kernel file 'OptB.py'. Launches each abaqus job. Launches the
postprocessor python file 'OptPostB1.py'.
5. OptB.py
Abaqus kernel script. Creates the FE model. Model parameters are read in from DAKOTA through the Bparams.in file.
6. OptPostB1.py
Post-processes the initial simulation. If a design looks promising it launches a corrosion simulation and a second postprocessor OptPostB2.py.
7. OptPostB2.py
Post-processes the corrosion simulation. Returns the objective function value to DAKOTA through the Bparams.out text file.

View file

@ -0,0 +1,4 @@
cd $PBS_O_WORKDIR/N1/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/N2/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/N3/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/N4/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in

View file

@ -0,0 +1,4 @@
cd $PBS_O_WORKDIR/P1/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/P2/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/P3/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in
cd $PBS_O_WORKDIR/P4/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in

View file

@ -0,0 +1,4 @@
cd $PBS_O_WORKDIR/P1/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in -r dakota.rst -s 114 -w dakota3.rst
cd $PBS_O_WORKDIR/P2/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in -r dakota.rst -s 116 -w dakota3.rst
cd $PBS_O_WORKDIR/P3/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in -r dakota.rst -s 125 -w dakota3.rst
cd $PBS_O_WORKDIR/P4/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in -r dakota.rst -s 138 -w dakota3.rst

View file

@ -0,0 +1 @@
cd $PBS_O_WORKDIR/N1/;$PBS_O_WORKDIR/DBUILD/src/dakota -i OptB.in -r dakota.rst -s 124 -w dakota3.rst

View file

@ -0,0 +1,316 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer n(8)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
nbr=0
open(unit=101,file=outdir(1:lenoutdir)//'\nodedata.inc',
1 status='old')
read(101,*)numfaces
do i=1,4*numfaces,4
read(101,*)nfix,n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
c facet(*,12)=fized face flag, facet(*,4-11)=element nodes
do j=1,4
ind=i+j-1
facet(ind,12)=nfix
do k=1,8
facet(ind,3+k)=n(k)
enddo
enddo
do j=1,4
ind=i+j-1
c facet(*,1-3)=nodes in facet
read(101,*)facet(ind,1),facet(ind,2),facet(ind,3)
node=facet(ind,1)
c nbr(node,1)=counter for facets per node
if(nbr(node,1)==0)nbr(node,1)=1
nbr(node,1)=nbr(node,1)+1
c nbr(node,>1)=facet number
nbr(node,nbr(node,1))=ind
enddo
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer np(3)
real fp(6,9),fc(6,3),fe(6,3),fn(6,3),a(3),b(3),c(3),d(3),q(3)
real qnew(3),cp1(3),cp2(3),cp3(3)
if(lnodetype>=3.and.lnodetype<=5)then
C PRINT *,NODE,'IN'
c Analysis Parameters
velocity=0.0d0
tol=1.d-5
c
numFacets=nbr(node,1)-1
c get facet point coords (fp).
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,3
nNode=facet(nFacet,j)
if (j==1)nnode=node
do k=1,3
fp(i,3*(j-1)+k)=crd(nNode,k)
enddo
c print *,node,nNode
c print *,crd(nNode,1),crd(nNode,2),crd(nNode,3)
enddo
enddo
c get facet element centroid(fe)
fe=0.
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,8
nNode=facet(nFacet,j+3)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c move non-fixed facets along unit normals - update fp
dist=velocity*dtime
do i=1,numFacets
nFacet=nbr(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.
dp2=0.
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end

View file

@ -0,0 +1,316 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer n(8)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
nbr=0
open(unit=101,file=outdir(1:lenoutdir)//'\nodedata.inc',
1 status='old')
read(101,*)numfaces
do i=1,4*numfaces,4
read(101,*)nfix,n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
c facet(*,12)=fized face flag, facet(*,4-11)=element nodes
do j=1,4
ind=i+j-1
facet(ind,12)=nfix
do k=1,8
facet(ind,3+k)=n(k)
enddo
enddo
do j=1,4
ind=i+j-1
c facet(*,1-3)=nodes in facet
read(101,*)facet(ind,1),facet(ind,2),facet(ind,3)
node=facet(ind,1)
c nbr(node,1)=counter for facets per node
if(nbr(node,1)==0)nbr(node,1)=1
nbr(node,1)=nbr(node,1)+1
c nbr(node,>1)=facet number
nbr(node,nbr(node,1))=ind
enddo
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer np(3)
real fp(6,9),fc(6,3),fe(6,3),fn(6,3),a(3),b(3),c(3),d(3),q(3)
real qnew(3),cp1(3),cp2(3),cp3(3)
if(lnodetype>=3.and.lnodetype<=5)then
C PRINT *,NODE,'IN'
c Analysis Parameters
velocity=0.005d0
tol=1.d-5
c
numFacets=nbr(node,1)-1
c get facet point coords (fp).
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,3
nNode=facet(nFacet,j)
if (j==1)nnode=node
do k=1,3
fp(i,3*(j-1)+k)=crd(nNode,k)
enddo
c print *,node,nNode
c print *,crd(nNode,1),crd(nNode,2),crd(nNode,3)
enddo
enddo
c get facet element centroid(fe)
fe=0.
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,8
nNode=facet(nFacet,j+3)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c move non-fixed facets along unit normals - update fp
dist=velocity*dtime
do i=1,numFacets
nFacet=nbr(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.
dp2=0.
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end

View file

@ -0,0 +1,316 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer n(8)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
nbr=0
open(unit=101,file=outdir(1:lenoutdir)//'\nodedata.inc',
1 status='old')
read(101,*)numfaces
do i=1,4*numfaces,4
read(101,*)nfix,n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
c facet(*,12)=fized face flag, facet(*,4-11)=element nodes
do j=1,4
ind=i+j-1
facet(ind,12)=nfix
do k=1,8
facet(ind,3+k)=n(k)
enddo
enddo
do j=1,4
ind=i+j-1
c facet(*,1-3)=nodes in facet
read(101,*)facet(ind,1),facet(ind,2),facet(ind,3)
node=facet(ind,1)
c nbr(node,1)=counter for facets per node
if(nbr(node,1)==0)nbr(node,1)=1
nbr(node,1)=nbr(node,1)+1
c nbr(node,>1)=facet number
nbr(node,nbr(node,1))=ind
enddo
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer np(3)
real fp(6,9),fc(6,3),fe(6,3),fn(6,3),a(3),b(3),c(3),d(3),q(3)
real qnew(3),cp1(3),cp2(3),cp3(3)
if(lnodetype>=3.and.lnodetype<=5)then
C PRINT *,NODE,'IN'
c Analysis Parameters
velocity=0.01d0
tol=1.d-5
c
numFacets=nbr(node,1)-1
c get facet point coords (fp).
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,3
nNode=facet(nFacet,j)
if (j==1)nnode=node
do k=1,3
fp(i,3*(j-1)+k)=crd(nNode,k)
enddo
c print *,node,nNode
c print *,crd(nNode,1),crd(nNode,2),crd(nNode,3)
enddo
enddo
c get facet element centroid(fe)
fe=0.
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,8
nNode=facet(nFacet,j+3)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c move non-fixed facets along unit normals - update fp
dist=velocity*dtime
do i=1,numFacets
nFacet=nbr(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.
dp2=0.
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end

View file

@ -0,0 +1,316 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer n(8)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
nbr=0
open(unit=101,file=outdir(1:lenoutdir)//'\nodedata.inc',
1 status='old')
read(101,*)numfaces
do i=1,4*numfaces,4
read(101,*)nfix,n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
c facet(*,12)=fized face flag, facet(*,4-11)=element nodes
do j=1,4
ind=i+j-1
facet(ind,12)=nfix
do k=1,8
facet(ind,3+k)=n(k)
enddo
enddo
do j=1,4
ind=i+j-1
c facet(*,1-3)=nodes in facet
read(101,*)facet(ind,1),facet(ind,2),facet(ind,3)
node=facet(ind,1)
c nbr(node,1)=counter for facets per node
if(nbr(node,1)==0)nbr(node,1)=1
nbr(node,1)=nbr(node,1)+1
c nbr(node,>1)=facet number
nbr(node,nbr(node,1))=ind
enddo
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer np(3)
real fp(6,9),fc(6,3),fe(6,3),fn(6,3),a(3),b(3),c(3),d(3),q(3)
real qnew(3),cp1(3),cp2(3),cp3(3)
if(lnodetype>=3.and.lnodetype<=5)then
C PRINT *,NODE,'IN'
c Analysis Parameters
velocity=0.02d0
tol=1.d-5
c
numFacets=nbr(node,1)-1
c get facet point coords (fp).
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,3
nNode=facet(nFacet,j)
if (j==1)nnode=node
do k=1,3
fp(i,3*(j-1)+k)=crd(nNode,k)
enddo
c print *,node,nNode
c print *,crd(nNode,1),crd(nNode,2),crd(nNode,3)
enddo
enddo
c get facet element centroid(fe)
fe=0.
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,8
nNode=facet(nFacet,j+3)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c move non-fixed facets along unit normals - update fp
dist=velocity*dtime
do i=1,numFacets
nFacet=nbr(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.
dp2=0.
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end

View file

@ -0,0 +1,316 @@
c These subroutines control the velocity of exterior nodes in the
c ALE adaptive mesh domain for 3D uniform corrosion analysis.
c Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
c ------------------------------------------------------------------
c SUB UEXTERNALDB: This is used only at the begining of an analysis.
c It populates the 'facet' and 'nbr' common block arrays.
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
include 'aba_param.inc'
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer n(8)
character*256 outdir
c
if(lop==0.or.lop==4)then
call getoutdir(outdir,lenoutdir)
nbr=0
open(unit=101,file=outdir(1:lenoutdir)//'\nodedata.inc',
1 status='old')
read(101,*)numfaces
do i=1,4*numfaces,4
read(101,*)nfix,n(1),n(2),n(3),n(4),n(5),n(6),n(7),n(8)
c facet(*,12)=fized face flag, facet(*,4-11)=element nodes
do j=1,4
ind=i+j-1
facet(ind,12)=nfix
do k=1,8
facet(ind,3+k)=n(k)
enddo
enddo
do j=1,4
ind=i+j-1
c facet(*,1-3)=nodes in facet
read(101,*)facet(ind,1),facet(ind,2),facet(ind,3)
node=facet(ind,1)
c nbr(node,1)=counter for facets per node
if(nbr(node,1)==0)nbr(node,1)=1
nbr(node,1)=nbr(node,1)+1
c nbr(node,>1)=facet number
nbr(node,nbr(node,1))=ind
enddo
enddo
close(unit=101)
endif
return
end
c ------------------------------------------------------------------
c SUB UFIELD: This is used at the start of each analysis increment.
c It populates the 'crd' common block array.
subroutine ufield(field,kfield,nsecpt,kstep,kinc,time,node,
1 coords,temp,dtemp,nfield)
include 'aba_param.inc'
dimension coords(3)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c
crd(node,1)=coords(1)
crd(node,2)=coords(2)
crd(node,3)=coords(3)
return
end
c ------------------------------------------------------------------
c SUB UMESHMOTION: This is used at the start of each mesh sweep.
c It calculates the velocity of each node in the local coord system.
subroutine umeshmotion(uref,ulocal,node,nndof,lnodetype,alocal,
$ ndim,time,dtime,pnewdt,kstep,kinc,kmeshsweep,jmatyp,jgvblock,
$ lsmooth)
include 'aba_param.inc'
c user defined dimension statements
dimension ulocal(*),uglobal(ndim),tlocal(ndim)
dimension alocal(ndim,*),time(2)
c Common Block Declarations
parameter (maxNodes=700000,maxFacets=700000)
integer nbr(maxNodes,5),facet(maxFacets,12)
real crd(maxNodes,3)
common nbr,facet,crd
c Other Declarations
integer np(3)
real fp(6,9),fc(6,3),fe(6,3),fn(6,3),a(3),b(3),c(3),d(3),q(3)
real qnew(3),cp1(3),cp2(3),cp3(3)
if(lnodetype>=3.and.lnodetype<=5)then
C PRINT *,NODE,'IN'
c Analysis Parameters
velocity=0.025d0
tol=1.d-5
c
numFacets=nbr(node,1)-1
c get facet point coords (fp).
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,3
nNode=facet(nFacet,j)
if (j==1)nnode=node
do k=1,3
fp(i,3*(j-1)+k)=crd(nNode,k)
enddo
c print *,node,nNode
c print *,crd(nNode,1),crd(nNode,2),crd(nNode,3)
enddo
enddo
c get facet element centroid(fe)
fe=0.
do i=1,numFacets
nFacet=nbr(node,i+1)
do j=1,8
nNode=facet(nFacet,j+3)
do k=1,3
fe(i,k)=fe(i,k)+crd(nNode,k)/8.
enddo
enddo
enddo
c get facet centroids (fc)
do i=1,numFacets
do j=1,3
fc(i,j)=(fp(i,j)+fp(i,j+3)+fp(i,j+6))/3.
enddo
enddo
c get facet normals (fn)
do i=1,numFacets
do j=1,3
a(j)=fp(i,j+3)-fp(i,j)
b(j)=fp(i,j+6)-fp(i,j)
enddo
call crossprod(a,b,c)
rlen=sqrt(c(1)*c(1)+c(2)*c(2)+c(3)*c(3))
c get inward pointing unit normal
dp=0.
do j=1,3
dp=dp+c(j)*(fe(i,j)-fc(i,j))
enddo
rsign=1
if(dp<0.)rsign=-1
do j=1,3
fn(i,j)=rsign*c(j)/rlen
enddo
enddo
c move non-fixed facets along unit normals - update fp
dist=velocity*dtime
do i=1,numFacets
nFacet=nbr(node,i+1)
if(facet(nFacet,12)/=1)then
do j=1,3
fp(i,j)=fp(i,j)+fn(i,j)*dist
fp(i,j+3)=fp(i,j+3)+fn(i,j)*dist
fp(i,j+6)=fp(i,j+6)+fn(i,j)*dist
enddo
endif
enddo
c get old node position (q)
do i=1,3
q(i)=crd(node,i)
enddo
c determine method to get qnew and relevant planes
c method depends on # of unique normal directions
numpairs=0
if(numfacets==1)then
method=1
else
numdir=0
do i=1,numfacets-1
do j=i+1,numfacets
dp=0.
do k=1,3
dp=dp+fn(i,k)*fn(j,k)
enddo
if(abs(dp)<1.-tol.or.abs(dp)>1.+tol)then
np(1)=i
np(2)=j
numdir=2
endif
if (numdir==2)continue
enddo
if(numdir==2)continue
enddo
if(numdir==2)then
method=3
do i=1,numfacets
if(i/=np(1).and.i/=np(2))then
dp1=0.
dp2=0.
do j=1,3
dp1=dp1+fn(np(1),j)*fn(i,j)
dp2=dp2+fn(np(2),j)*fn(i,j)
enddo
if(abs(dp1)<1.-tol.or.abs(dp1)>1.+tol)then
if(abs(dp2)<1.-tol.or.
$ abs(dp2)>1.+tol)then
np(3)=i
numdir=3
method=2
endif
endif
endif
enddo
else
method=1
endif
endif
c Get new node position
if(method==1)then
c get projection of old point q onto any plane
c qnew = q - ((q - p1).n)*n
dp=0.
do i=1,3
dp=dp+(q(i)-fp(1,i))*fn(1,i)
enddo
do i=1,3
qnew(i)=q(i)-dp*fn(1,i)
enddo
elseif(method==2)then
c get distances d from each plane to origin
do i=1,3
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
c get n2 x n3
do i=1,3
a(i)=fn(np(2),i)
b(i)=fn(np(3),i)
enddo
call crossprod(a,b,cp2)
c get n3 x n1
do i=1,3
a(i)=fn(np(3),i)
b(i)=fn(np(1),i)
enddo
call crossprod(a,b,cp3)
c get intersection of 3 planes
c qnew = (-d1(n2 x n3)-d2(n3 x n1)-d3(n1 x n2))/(n1.(n2 x n3))
denom=fn(np(1),1)*cp2(1)+fn(np(1),2)*cp2(2)
$ +fn(np(1),3)*cp2(3)
do i=1,3
qnew(i)=-(d(1)*cp2(i)+d(2)*cp3(i)+d(3)*cp1(i))
$ /denom
enddo
else
c find line of intersection of planes given by a point
c and vector
do i=1,2
d(i)=0.
do j=1,3
d(i)=d(i)-fn(np(i),j)*fp(np(i),j)
enddo
enddo
c get n1 x n2
do i=1,3
a(i)=fn(np(1),i)
b(i)=fn(np(2),i)
enddo
call crossprod(a,b,cp1)
rlen=sqrt(cp1(1)*cp1(1)+cp1(2)*cp1(2)+cp1(3)*cp1(3))
do i=1,3
a(i)=d(2)*fn(np(1),i)-d(1)*fn(np(2),i)
enddo
c get (d2n1 - d1n2) x (n1 x n2)
call crossprod(a,cp1,cp2)
c a = unit vector along line
c b = point on line
do i=1,3
a(i)=cp1(i)/rlen
b(i)=cp2(i)/(rlen*rlen)
enddo
c get projection of node onto line
c bq'=((bq).a)*a
dp=0.
do i=1,3
dp=dp+(q(i)-b(i))*a(i)
enddo
do i=1,3
qnew(i)=b(i)+dp*a(i)
enddo
endif
do i=1,3
a(i)=(qnew(i)-q(i))/dtime
enddo
c print *,node,a(1),a(2),a(3)
do i=1,3
uglobal(i) = a(i)
enddo
do i=1,ndim
tlocal(i)=0.
do j=1,ndim
tlocal(i)=tlocal(i)+uglobal(j)*alocal(j,i)
enddo
enddo
do i=1,ndim
ulocal(i)=tlocal(i)
enddo
endif
lsmooth=1
return
end
c Return cross product(c) for input vectors (a, b)
subroutine crossprod(a,b,c)
include 'aba_param.inc'
real a(3),b(3),c(3)
c(1)=a(2)*b(3)-a(3)*b(2)
c(2)=a(3)*b(1)-a(1)*b(3)
c(3)=a(1)*b(2)-a(2)*b(1)
return
end

File diff suppressed because it is too large Load diff

File diff suppressed because it is too large Load diff

File diff suppressed because it is too large Load diff

Binary file not shown.

Binary file not shown.

Binary file not shown.

File diff suppressed because it is too large Load diff

File diff suppressed because it is too large Load diff

File diff suppressed because it is too large Load diff

File diff suppressed because it is too large Load diff

File diff suppressed because it is too large Load diff

View file

@ -0,0 +1,45 @@
# This is a pre-processor script for 3D ALE corrosion analysis.
# Author: J. Grogan - BMEC, NUI Galway. Created: 19/09/2012
from abaqusConstants import *
from abaqus import *
#
aModel=mdb.models['Square6']
aPart=aModel.parts['Geom']
incFile=open('NodeData.inc','w')
#
numFaces=0
pstring=''
# Cycle through all element faces
for eachFace in aPart.elementFaces:
# Check if Face is on external Surface
if len(eachFace.getElements())==1:
numFaces=numFaces+1
faceNodes=eachFace.getNodes()
# Identify 'Fixed' Faces
fixed=1
try:
fSet=aPart.sets['Fixed']
for eachNode in faceNodes:
if eachNode not in fSet.nodes:
fixed=0
break
except:
fixed=0
pstring=pstring+str(fixed)+' '
# Write Element Nodes
eNodes=[]
for eachNode in eachFace.getElements()[0].getNodes():
pstring=pstring+str(eachNode.label)+' '
pstring=pstring+'\n'
# Write Each Face Nodes and Corresponding Connected Nodes
for eachNode in faceNodes:
pstring=pstring+str(eachNode.label)+' '
for eachEdge in eachNode.getElemEdges():
for eachENode in eachEdge.getNodes():
if eachENode.label != eachNode.label and eachENode in faceNodes:
pstring=pstring+str(eachENode.label)+' '
pstring=pstring+'\n'
#
incFile.write(str(numFaces)+'\n')
incFile.write(pstring)
incFile.close()

View file

@ -0,0 +1,31 @@
# Import Neccesary Abaqus Modules
from abaqusConstants import *
from odbAccess import *
import sys
import os
resFile='E6R.dat'
outFile = open(resFile,"w")
for i in range(1,6):
jobName='E6R'+str(i)
odbfilename=jobName+'.odb'
odb=openOdb(path=odbfilename)
j=0.
for eachFrame in odb.steps["Step-5"].frames:
j=j+1
aSet=odb.rootAssembly.instances['GEOM-1'].nodeSets['BCT']
cforce=0.
for currentForce in eachFrame.fieldOutputs["RF"].getSubset(region=aSet).values:
cforce=cforce+currentForce.data[1]
bSet=odb.rootAssembly.instances['GEOM-1'].nodeSets['BC4']
disp=eachFrame.fieldOutputs["U"].getSubset(region=bSet).values[0].data[1]
if j==2:
cf2=cforce
d2=disp
elif j==4:
cf4=cforce
d4=disp
stiff=abs(cf4-cf2)/abs(d4-d2)
outFile.write("%12.6f \n " % (stiff))
break
odb.close()
outFile.close()

7
Biomaterials13/StudyP1/run.bat Executable file
View file

@ -0,0 +1,7 @@
(
abq6101 j=C6R1 inp=C6 user=ALE0 inter
abq6101 j=C6R2 inp=C6 user=ALE05 inter
abq6101 j=C6R3 inp=C6 user=ALE10 inter
abq6101 j=C6R4 inp=C6 user=ALE20 inter
abq6101 j=C6R5 inp=C6 user=ALE25 inter
)

File diff suppressed because it is too large Load diff

View file

@ -0,0 +1,875 @@
*Heading
** Job name: Press_CoCr Model name: Model-1
** Generated by: Abaqus/CAE 6.10-1
*Preprint, echo=NO, model=NO, history=NO, contact=NO
**
** PARTS
**
**
** ASSEMBLY
**
*Assembly, name=Assembly
**
*Instance, library=Full_CoCr, instance=Stent
**
** PREDEFINED FIELD
**
** Name: Predefined Field-1 Type: Initial State
*Import, state=yes, update=no
*End Instance
**
*Nset, nset=_PickedSet48, internal, instance=Stent
337, 338, 339, 340, 381, 382, 383, 384, 425, 426, 427, 428, 469, 470, 471, 472
513, 514, 515, 516, 557, 558, 559, 560, 5663, 5664, 5665, 5666, 5667, 5698, 5699, 5700
5701, 5702, 5703, 5704, 5705, 5706, 5707, 5708, 6360, 6361, 6362, 6363, 6364, 6395, 6396, 6397
6398, 6399, 6415, 6416, 7083, 7084, 7085, 7086, 7087, 7118, 7119, 7120, 7121, 7122, 7123, 7124
7784, 7785, 7786, 7787, 7788, 7819, 7820, 7821, 7822, 7823, 7839, 7840, 8523, 8524, 8525, 8526
8527, 8558, 8559, 8560, 8561, 8562, 8563, 8564, 8565, 8566, 8567, 8568, 9228, 9229, 9230, 9231
9232, 9263, 9264, 9265, 9266, 9267, 9283, 9284, 9285, 9286, 9287, 9288, 29141, 29142, 29143, 29144
29145, 29146, 29147, 29148, 29149, 29150, 29151, 29152, 29153, 29154, 29155, 31546, 31547, 31548, 31549, 31550
33881, 33882, 33883, 33884, 33885, 36356, 36357, 36358, 36359, 36360, 38911, 38912, 38913, 38914, 38915, 38916
38917, 38918, 38919, 38920, 38921, 38922, 38923, 38924, 38925, 41396, 41397, 41398, 41399, 41400, 41401, 41402
41403, 41404, 41405, 41406, 41407, 41408, 41409, 41410
*Nset, nset=_PickedSet49, internal, instance=Stent
5704, 5707, 6415, 6416, 7124, 7839, 7840, 8564, 8567, 9284, 9287, 29146, 29147, 29148, 29149, 29150
31546, 31547, 31548, 31549, 31550, 33881, 33882, 33883, 33884, 33885, 36356, 36357, 36358, 36359, 36360, 38916
38917, 38918, 38919, 38920, 41401, 41402, 41403, 41404, 41405, 50745
*Nset, nset=Set-1, instance=Stent
49, 50, 51, 52, 97, 98, 99, 100, 145, 146, 147, 148, 193, 194, 195, 196
241, 242, 243, 244, 289, 290, 291, 292, 1264, 1265, 1266, 1267, 1268, 1299, 1300, 1301
1302, 1303, 1319, 1320, 1321, 1322, 1323, 1324, 2003, 2004, 2005, 2006, 2007, 2038, 2039, 2040
2041, 2042, 2043, 2044, 2708, 2709, 2710, 2711, 2712, 2743, 2744, 2745, 2746, 2747, 2763, 2764
3455, 3456, 3457, 3458, 3459, 3490, 3491, 3492, 3493, 3494, 3495, 3496, 4180, 4181, 4182, 4183
4184, 4215, 4216, 4217, 4218, 4219, 4235, 4236, 4237, 4238, 4239, 4240, 4919, 4920, 4921, 4922
4923, 4954, 4955, 4956, 4957, 4958, 4959, 4960, 14341, 14342, 14343, 14344, 14345, 14346, 14347, 14349
14350, 14351, 14352, 14353, 14354, 14355, 16751, 16752, 16753, 16754, 16755, 19091, 19092, 19093, 19094, 19095
21581, 21582, 21583, 21584, 21585, 24151, 24152, 24153, 24154, 24155, 24156, 24157, 24158, 24159, 24160, 24161
24162, 24163, 24164, 24165, 26561, 26562, 26563, 26564, 26565
*Nset, nset=Set-2, instance=Stent
14348,
*Elset, elset=__PickedSurf53_S1, internal, instance=Stent
46273, 46274, 46275, 46276, 46277, 46278, 46279, 46280, 46281, 46282, 46283, 46284, 46285, 46286, 46287, 46288
46289, 46290, 46291, 46292, 46293, 46294, 46295, 46296, 46297, 46298, 46299, 46300, 46301, 46302, 46303, 46304
46305, 46306, 46307, 46308, 46309, 46310, 46311, 46312, 46313, 46314, 46315, 46316, 46317, 46318, 46319, 46320
46321, 46322, 46323, 46324, 46325, 46326, 46327, 46328, 46329, 46330, 46331, 46332, 46333, 46334, 46335, 46336
46337, 46338, 46339, 46340, 46341, 46342, 46343, 46344, 46345, 46346, 46347, 46348, 46349, 46350, 46351, 46352
46353, 46354, 46355, 46356, 46357, 46358, 46359, 46360, 46361, 46362, 46363, 46364, 46365, 46366, 46367, 46368
46369, 46370, 46371, 46372, 46373, 46374, 46375, 46376, 46377, 46378, 46379, 46380, 46381, 46382, 46383, 46384
46385, 46386, 46387, 46388, 46389, 46390, 46391, 46392, 46393, 46394, 46395, 46396, 46397, 46398, 46399, 46400
46401, 46402, 46403, 46404, 46405, 46406, 46407, 46408, 46409, 46410, 46411, 46412, 46413, 46414, 46415, 46416
46417, 46418, 46419, 46420, 46421, 46422, 46423, 46424, 46425, 46426, 46427, 46428, 46429, 46430, 46431, 46432
46433, 46434, 46435, 46436, 46437, 46438, 46439, 46440, 46441, 46442, 46443, 46444, 46445, 46446, 46447, 46448
46449, 46450, 46451, 46452, 48433, 48434, 48435, 48436, 48437, 48438, 48439, 48440, 48441, 48442, 48443, 48444
48445, 48446, 48447, 48448, 48449, 48450, 48451, 48452, 48453, 48454, 48455, 48456, 48457, 48458, 48459, 48460
48461, 48462, 48463, 48464, 48465, 48466, 48467, 48468, 48469, 48470, 48471, 48472, 48473, 48474, 48475, 48476
48477, 48478, 48479, 48480, 48481, 48482, 48483, 48484, 48485, 48486, 48487, 48488, 48489, 48490, 48491, 48492
48493, 48494, 48495, 48496, 48497, 48498, 48499, 48500, 48501, 48502, 48503, 48504, 48505, 48506, 48507, 48508
48509, 48510, 48511, 48512, 48513, 48514, 48515, 48516, 48517, 48518, 48519, 48520, 48521, 48522, 48523, 48524
48525, 48526, 48527, 48528, 48529, 48530, 48531, 48532, 48533, 48534, 48535, 48536, 48537, 48538, 48539, 48540
48541, 48542, 48543, 48544, 48545, 48546, 48547, 48548, 48549, 48550, 48551, 48552, 48553, 48554, 48555, 48556
48557, 48558, 48559, 48560, 48561, 48562, 48563, 48564, 48565, 48566, 48567, 48568, 48569, 48570, 48571, 48572
48573, 48574, 48575, 48576, 48577, 48578, 48579, 48580, 48581, 48582, 48583, 48584, 48585, 48586, 48587, 48588
48589, 48590, 48591, 48592, 48593, 48594, 48595, 48596, 48597, 48598, 48599, 48600, 50449, 50450, 50451, 50452
50453, 50454, 50455, 50456, 50457, 50458, 50459, 50460, 50461, 50462, 50463, 50464, 50465, 50466, 50467, 50468
50469, 50470, 50471, 50472, 50473, 50474, 50475, 50476, 50477, 50478, 50479, 50480, 50481, 50482, 50483, 50484
50485, 50486, 50487, 50488, 50489, 50490, 50491, 50492, 50493, 50494, 50495, 50496, 50497, 50498, 50499, 50500
50501, 50502, 50503, 50504, 50505, 50506, 50507, 50508, 50509, 50510, 50511, 50512, 50513, 50514, 50515, 50516
50517, 50518, 50519, 50520, 50521, 50522, 50523, 50524, 50525, 50526, 50527, 50528, 50529, 50530, 50531, 50532
50533, 50534, 50535, 50536, 50537, 50538, 50539, 50540, 50541, 50542, 50543, 50544, 50545, 50546, 50547, 50548
50549, 50550, 50551, 50552, 50553, 50554, 50555, 50556, 50557, 50558, 50559, 50560, 50561, 50562, 50563, 50564
50565, 50566, 50567, 50568, 50569, 50570, 50571, 50572, 50573, 50574, 50575, 50576, 50577, 50578, 50579, 50580
50581, 50582, 50583, 50584, 50585, 50586, 50587, 50588, 50589, 50590, 50591, 50592, 50593, 50594, 50595, 50596
50597, 50598, 50599, 50600, 50601, 50602, 50603, 50604, 50605, 50606, 50607, 50608, 50609, 50610, 50611, 50612
50613, 50614, 50615, 50616, 52465, 52466, 52467, 52468, 52469, 52470, 52471, 52472, 52473, 52474, 52475, 52476
52477, 52478, 52479, 52480, 52481, 52482, 52483, 52484, 52485, 52486, 52487, 52488, 52489, 52490, 52491, 52492
52493, 52494, 52495, 52496, 52497, 52498, 52499, 52500, 52501, 52502, 52503, 52504, 52505, 52506, 52507, 52508
52509, 52510, 52511, 52512, 52513, 52514, 52515, 52516, 52517, 52518, 52519, 52520, 52521, 52522, 52523, 52524
52525, 52526, 52527, 52528, 52529, 52530, 52531, 52532, 52533, 52534, 52535, 52536, 52537, 52538, 52539, 52540
52541, 52542, 52543, 52544, 52545, 52546, 52547, 52548, 52549, 52550, 52551, 52552, 52553, 52554, 52555, 52556
52557, 52558, 52559, 52560, 52561, 52562, 52563, 52564, 52565, 52566, 52567, 52568, 52569, 52570, 52571, 52572
52573, 52574, 52575, 52576, 52577, 52578, 52579, 52580, 52581, 52582, 52583, 52584, 52585, 52586, 52587, 52588
52589, 52590, 52591, 52592, 52593, 52594, 52595, 52596, 52597, 52598, 52599, 52600, 52601, 52602, 52603, 52604
52605, 52606, 52607, 52608, 52609, 52610, 52611, 52612, 52613, 52614, 52615, 52616, 52617, 52618, 52619, 52620
52621, 52622, 52623, 52624, 52625, 52626, 52627, 52628, 52629, 52630, 52631, 52632, 52633, 52634, 52635, 52636
52637, 52638, 52639, 52640, 52641, 52642, 52643, 52644, 54553, 54554, 54555, 54556, 54557, 54558, 54559, 54560
54561, 54562, 54563, 54564, 54565, 54566, 54567, 54568, 54569, 54570, 54571, 54572, 54573, 54574, 54575, 54576
54577, 54578, 54579, 54580, 54581, 54582, 54583, 54584, 54585, 54586, 54587, 54588, 54589, 54590, 54591, 54592
54593, 54594, 54595, 54596, 54597, 54598, 54599, 54600, 54601, 54602, 54603, 54604, 54605, 54606, 54607, 54608
54609, 54610, 54611, 54612, 54613, 54614, 54615, 54616, 54617, 54618, 54619, 54620, 54621, 54622, 54623, 54624
54625, 54626, 54627, 54628, 54629, 54630, 54631, 54632, 54633, 54634, 54635, 54636, 54637, 54638, 54639, 54640
54641, 54642, 54643, 54644, 54645, 54646, 54647, 54648, 54649, 54650, 54651, 54652, 54653, 54654, 54655, 54656
54657, 54658, 54659, 54660, 54661, 54662, 54663, 54664, 54665, 54666, 54667, 54668, 54669, 54670, 54671, 54672
54673, 54674, 54675, 54676, 54677, 54678, 54679, 54680, 54681, 54682, 54683, 54684, 54685, 54686, 54687, 54688
54689, 54690, 54691, 54692, 54693, 54694, 54695, 54696, 54697, 54698, 54699, 54700, 54701, 54702, 54703, 54704
54705, 54706, 54707, 54708, 54709, 54710, 54711, 54712, 54713, 54714, 54715, 54716, 54717, 54718, 54719, 54720
54721, 54722, 54723, 54724, 54725, 54726, 54727, 54728, 54729, 54730, 54731, 54732, 56713, 56714, 56715, 56716
56717, 56718, 56719, 56720, 56721, 56722, 56723, 56724, 56725, 56726, 56727, 56728, 56729, 56730, 56731, 56732
56733, 56734, 56735, 56736, 56737, 56738, 56739, 56740, 56741, 56742, 56743, 56744, 56745, 56746, 56747, 56748
56749, 56750, 56751, 56752, 56753, 56754, 56755, 56756, 56757, 56758, 56759, 56760, 56761, 56762, 56763, 56764
56765, 56766, 56767, 56768, 56769, 56770, 56771, 56772, 56773, 56774, 56775, 56776, 56777, 56778, 56779, 56780
56781, 56782, 56783, 56784, 56785, 56786, 56787, 56788, 56789, 56790, 56791, 56792, 56793, 56794, 56795, 56796
56797, 56798, 56799, 56800, 56801, 56802, 56803, 56804, 56805, 56806, 56807, 56808, 56809, 56810, 56811, 56812
56813, 56814, 56815, 56816, 56817, 56818, 56819, 56820, 56821, 56822, 56823, 56824, 56825, 56826, 56827, 56828
56829, 56830, 56831, 56832, 56833, 56834, 56835, 56836, 56837, 56838, 56839, 56840, 56841, 56842, 56843, 56844
56845, 56846, 56847, 56848, 56849, 56850, 56851, 56852, 56853, 56854, 56855, 56856, 56857, 56858, 56859, 56860
56861, 56862, 56863, 56864, 56865, 56866, 56867, 56868, 56869, 56870, 56871, 56872, 56873, 56874, 56875, 56876
56877, 56878, 56879, 56880, 59809, 59810, 59811, 59812, 59813, 59814, 59815, 59816, 59817, 59818, 59819, 59820
59821, 59822, 59823, 59824, 59825, 59826, 59827, 59828, 59829, 59830, 59831, 59832, 59833, 59834, 59835, 59836
59837, 59838, 59839, 59840, 59841, 59842, 59843, 59844, 59845, 59846, 59847, 59848, 59849, 59850, 59851, 59852
59853, 59854, 59855, 59856, 59857, 59858, 59859, 59860, 59861, 59862, 59863, 59864, 59865, 59866, 59867, 59868
59869, 59870, 59871, 59872, 59873, 59874, 59875, 59876, 59877, 59878, 59879, 59880, 59881, 59882, 59883, 59884
59885, 59886, 59887, 59888, 59889, 59890, 59891, 59892, 59893, 59894, 59895, 59896, 59897, 59898, 59899, 59900
59901, 59902, 59903, 59904, 59905, 59906, 59907, 59908, 59909, 59910, 59911, 59912, 59913, 59914, 59915, 59916
59917, 59918, 59919, 59920, 59921, 59922, 59923, 59924, 59925, 59926, 59927, 59928, 59929, 59930, 59931, 59932
59933, 59934, 59935, 59936, 59937, 59938, 59939, 59940, 59941, 59942, 59943, 59944, 59945, 59946, 59947, 59948
59949, 59950, 59951, 59952, 59953, 59954, 59955, 59956, 59957, 59958, 59959, 59960, 59961, 59962, 59963, 59964
59965, 59966, 59967, 59968, 59969, 59970, 59971, 59972, 59973, 59974, 59975, 59976, 59977, 59978, 59979, 59980
59981, 59982, 59983, 59984, 59985, 59986, 59987, 59988, 61897, 61898, 61899, 61900, 61901, 61902, 61903, 61904
61905, 61906, 61907, 61908, 61909, 61910, 61911, 61912, 61913, 61914, 61915, 61916, 61917, 61918, 61919, 61920
61921, 61922, 61923, 61924, 61925, 61926, 61927, 61928, 61929, 61930, 61931, 61932, 61933, 61934, 61935, 61936
61937, 61938, 61939, 61940, 61941, 61942, 61943, 61944, 61945, 61946, 61947, 61948, 61949, 61950, 61951, 61952
61953, 61954, 61955, 61956, 61957, 61958, 61959, 61960, 61961, 61962, 61963, 61964, 61965, 61966, 61967, 61968
61969, 61970, 61971, 61972, 61973, 61974, 61975, 61976, 61977, 61978, 61979, 61980, 61981, 61982, 61983, 61984
61985, 61986, 61987, 61988, 61989, 61990, 61991, 61992, 61993, 61994, 61995, 61996, 61997, 61998, 61999, 62000
62001, 62002, 62003, 62004, 62005, 62006, 62007, 62008, 62009, 62010, 62011, 62012, 62013, 62014, 62015, 62016
62017, 62018, 62019, 62020, 62021, 62022, 62023, 62024, 62025, 62026, 62027, 62028, 62029, 62030, 62031, 62032
62033, 62034, 62035, 62036, 62037, 62038, 62039, 62040, 62041, 62042, 62043, 62044, 62045, 62046, 62047, 62048
62049, 62050, 62051, 62052, 62053, 62054, 62055, 62056, 62057, 62058, 62059, 62060, 62061, 62062, 62063, 62064
63913, 63914, 63915, 63916, 63917, 63918, 63919, 63920, 63921, 63922, 63923, 63924, 63925, 63926, 63927, 63928
63929, 63930, 63931, 63932, 63933, 63934, 63935, 63936, 63937, 63938, 63939, 63940, 63941, 63942, 63943, 63944
63945, 63946, 63947, 63948, 63949, 63950, 63951, 63952, 63953, 63954, 63955, 63956, 63957, 63958, 63959, 63960
63961, 63962, 63963, 63964, 63965, 63966, 63967, 63968, 63969, 63970, 63971, 63972, 63973, 63974, 63975, 63976
63977, 63978, 63979, 63980, 63981, 63982, 63983, 63984, 63985, 63986, 63987, 63988, 63989, 63990, 63991, 63992
63993, 63994, 63995, 63996, 63997, 63998, 63999, 64000, 64001, 64002, 64003, 64004, 64005, 64006, 64007, 64008
64009, 64010, 64011, 64012, 64013, 64014, 64015, 64016, 64017, 64018, 64019, 64020, 64021, 64022, 64023, 64024
64025, 64026, 64027, 64028, 64029, 64030, 64031, 64032, 64033, 64034, 64035, 64036, 64037, 64038, 64039, 64040
64041, 64042, 64043, 64044, 64045, 64046, 64047, 64048, 64049, 64050, 64051, 64052, 64053, 64054, 64055, 64056
64057, 64058, 64059, 64060, 64061, 64062, 64063, 64064, 64065, 64066, 64067, 64068, 64069, 64070, 64071, 64072
64073, 64074, 64075, 64076, 64077, 64078, 64079, 64080, 66001, 66002, 66003, 66004, 66005, 66006, 66007, 66008
66009, 66010, 66011, 66012, 66013, 66014, 66015, 66016, 66017, 66018, 66019, 66020, 66021, 66022, 66023, 66024
66025, 66026, 66027, 66028, 66029, 66030, 66031, 66032, 66033, 66034, 66035, 66036, 66037, 66038, 66039, 66040
66041, 66042, 66043, 66044, 66045, 66046, 66047, 66048, 66049, 66050, 66051, 66052, 66053, 66054, 66055, 66056
66057, 66058, 66059, 66060, 66061, 66062, 66063, 66064, 66065, 66066, 66067, 66068, 66069, 66070, 66071, 66072
66073, 66074, 66075, 66076, 66077, 66078, 66079, 66080, 66081, 66082, 66083, 66084, 66085, 66086, 66087, 66088
66089, 66090, 66091, 66092, 66093, 66094, 66095, 66096, 66097, 66098, 66099, 66100, 66101, 66102, 66103, 66104
66105, 66106, 66107, 66108, 66109, 66110, 66111, 66112, 66113, 66114, 66115, 66116, 66117, 66118, 66119, 66120
66121, 66122, 66123, 66124, 66125, 66126, 66127, 66128, 66129, 66130, 66131, 66132, 66133, 66134, 66135, 66136
66137, 66138, 66139, 66140, 66141, 66142, 66143, 66144, 66145, 66146, 66147, 66148, 66149, 66150, 66151, 66152
66153, 66154, 66155, 66156, 66157, 66158, 66159, 66160, 66161, 66162, 66163, 66164, 66165, 66166, 66167, 66168
68089, 68090, 68091, 68092, 68093, 68094, 68095, 68096, 68097, 68098, 68099, 68100, 68101, 68102, 68103, 68104
68105, 68106, 68107, 68108, 68109, 68110, 68111, 68112, 68113, 68114, 68115, 68116, 68117, 68118, 68119, 68120
68121, 68122, 68123, 68124, 68125, 68126, 68127, 68128, 68129, 68130, 68131, 68132, 68133, 68134, 68135, 68136
68137, 68138, 68139, 68140, 68141, 68142, 68143, 68144, 68145, 68146, 68147, 68148, 68149, 68150, 68151, 68152
68153, 68154, 68155, 68156, 68157, 68158, 68159, 68160, 68161, 68162, 68163, 68164, 68165, 68166, 68167, 68168
68169, 68170, 68171, 68172, 68173, 68174, 68175, 68176, 68177, 68178, 68179, 68180, 68181, 68182, 68183, 68184
68185, 68186, 68187, 68188, 68189, 68190, 68191, 68192, 68193, 68194, 68195, 68196, 68197, 68198, 68199, 68200
68201, 68202, 68203, 68204, 68205, 68206, 68207, 68208, 68209, 68210, 68211, 68212, 68213, 68214, 68215, 68216
68217, 68218, 68219, 68220, 68221, 68222, 68223, 68224, 68225, 68226, 68227, 68228, 68229, 68230, 68231, 68232
68233, 68234, 68235, 68236, 68237, 68238, 68239, 68240, 68241, 68242, 68243, 68244, 68245, 68246, 68247, 68248
68249, 68250, 68251, 68252, 68253, 68254, 68255, 68256, 68257, 68258, 68259, 68260, 68261, 68262, 68263, 68264
68265, 68266, 68267, 68268, 70177, 70178, 70179, 70180, 70181, 70182, 70183, 70184, 70185, 70186, 70187, 70188
70189, 70190, 70191, 70192, 70193, 70194, 70195, 70196, 70197, 70198, 70199, 70200, 70201, 70202, 70203, 70204
70205, 70206, 70207, 70208, 70209, 70210, 70211, 70212, 70213, 70214, 70215, 70216, 70217, 70218, 70219, 70220
70221, 70222, 70223, 70224, 70225, 70226, 70227, 70228, 70229, 70230, 70231, 70232, 70233, 70234, 70235, 70236
70237, 70238, 70239, 70240, 70241, 70242, 70243, 70244, 70245, 70246, 70247, 70248, 70249, 70250, 70251, 70252
70253, 70254, 70255, 70256, 70257, 70258, 70259, 70260, 70261, 70262, 70263, 70264, 70265, 70266, 70267, 70268
70269, 70270, 70271, 70272, 70273, 70274, 70275, 70276, 70277, 70278, 70279, 70280, 70281, 70282, 70283, 70284
70285, 70286, 70287, 70288, 70289, 70290, 70291, 70292, 70293, 70294, 70295, 70296, 70297, 70298, 70299, 70300
70301, 70302, 70303, 70304, 70305, 70306, 70307, 70308, 70309, 70310, 70311, 70312, 70313, 70314, 70315, 70316
70317, 70318, 70319, 70320, 70321, 70322, 70323, 70324, 70325, 70326, 70327, 70328, 70329, 70330, 70331, 70332
70333, 70334, 70335, 70336, 70337, 70338, 70339, 70340, 70341, 70342, 70343, 70344, 70345, 70346, 70347, 70348
70349, 70350, 70351, 70352, 70353, 70354, 70355, 70356
*Elset, elset=__PickedSurf53_S2, internal, instance=Stent
48253, 48254, 48255, 48256, 48257, 48258, 48259, 48260, 48261, 48262, 48263, 48264, 48265, 48266, 48267, 48268
48269, 48270, 48271, 48272, 48273, 48274, 48275, 48276, 48277, 48278, 48279, 48280, 48281, 48282, 48283, 48284
48285, 48286, 48287, 48288, 48289, 48290, 48291, 48292, 48293, 48294, 48295, 48296, 48297, 48298, 48299, 48300
48301, 48302, 48303, 48304, 48305, 48306, 48307, 48308, 48309, 48310, 48311, 48312, 48313, 48314, 48315, 48316
48317, 48318, 48319, 48320, 48321, 48322, 48323, 48324, 48325, 48326, 48327, 48328, 48329, 48330, 48331, 48332
48333, 48334, 48335, 48336, 48337, 48338, 48339, 48340, 48341, 48342, 48343, 48344, 48345, 48346, 48347, 48348
48349, 48350, 48351, 48352, 48353, 48354, 48355, 48356, 48357, 48358, 48359, 48360, 48361, 48362, 48363, 48364
48365, 48366, 48367, 48368, 48369, 48370, 48371, 48372, 48373, 48374, 48375, 48376, 48377, 48378, 48379, 48380
48381, 48382, 48383, 48384, 48385, 48386, 48387, 48388, 48389, 48390, 48391, 48392, 48393, 48394, 48395, 48396
48397, 48398, 48399, 48400, 48401, 48402, 48403, 48404, 48405, 48406, 48407, 48408, 48409, 48410, 48411, 48412
48413, 48414, 48415, 48416, 48417, 48418, 48419, 48420, 48421, 48422, 48423, 48424, 48425, 48426, 48427, 48428
48429, 48430, 48431, 48432, 50281, 50282, 50283, 50284, 50285, 50286, 50287, 50288, 50289, 50290, 50291, 50292
50293, 50294, 50295, 50296, 50297, 50298, 50299, 50300, 50301, 50302, 50303, 50304, 50305, 50306, 50307, 50308
50309, 50310, 50311, 50312, 50313, 50314, 50315, 50316, 50317, 50318, 50319, 50320, 50321, 50322, 50323, 50324
50325, 50326, 50327, 50328, 50329, 50330, 50331, 50332, 50333, 50334, 50335, 50336, 50337, 50338, 50339, 50340
50341, 50342, 50343, 50344, 50345, 50346, 50347, 50348, 50349, 50350, 50351, 50352, 50353, 50354, 50355, 50356
50357, 50358, 50359, 50360, 50361, 50362, 50363, 50364, 50365, 50366, 50367, 50368, 50369, 50370, 50371, 50372
50373, 50374, 50375, 50376, 50377, 50378, 50379, 50380, 50381, 50382, 50383, 50384, 50385, 50386, 50387, 50388
50389, 50390, 50391, 50392, 50393, 50394, 50395, 50396, 50397, 50398, 50399, 50400, 50401, 50402, 50403, 50404
50405, 50406, 50407, 50408, 50409, 50410, 50411, 50412, 50413, 50414, 50415, 50416, 50417, 50418, 50419, 50420
50421, 50422, 50423, 50424, 50425, 50426, 50427, 50428, 50429, 50430, 50431, 50432, 50433, 50434, 50435, 50436
50437, 50438, 50439, 50440, 50441, 50442, 50443, 50444, 50445, 50446, 50447, 50448, 52297, 52298, 52299, 52300
52301, 52302, 52303, 52304, 52305, 52306, 52307, 52308, 52309, 52310, 52311, 52312, 52313, 52314, 52315, 52316
52317, 52318, 52319, 52320, 52321, 52322, 52323, 52324, 52325, 52326, 52327, 52328, 52329, 52330, 52331, 52332
52333, 52334, 52335, 52336, 52337, 52338, 52339, 52340, 52341, 52342, 52343, 52344, 52345, 52346, 52347, 52348
52349, 52350, 52351, 52352, 52353, 52354, 52355, 52356, 52357, 52358, 52359, 52360, 52361, 52362, 52363, 52364
52365, 52366, 52367, 52368, 52369, 52370, 52371, 52372, 52373, 52374, 52375, 52376, 52377, 52378, 52379, 52380
52381, 52382, 52383, 52384, 52385, 52386, 52387, 52388, 52389, 52390, 52391, 52392, 52393, 52394, 52395, 52396
52397, 52398, 52399, 52400, 52401, 52402, 52403, 52404, 52405, 52406, 52407, 52408, 52409, 52410, 52411, 52412
52413, 52414, 52415, 52416, 52417, 52418, 52419, 52420, 52421, 52422, 52423, 52424, 52425, 52426, 52427, 52428
52429, 52430, 52431, 52432, 52433, 52434, 52435, 52436, 52437, 52438, 52439, 52440, 52441, 52442, 52443, 52444
52445, 52446, 52447, 52448, 52449, 52450, 52451, 52452, 52453, 52454, 52455, 52456, 52457, 52458, 52459, 52460
52461, 52462, 52463, 52464, 54385, 54386, 54387, 54388, 54389, 54390, 54391, 54392, 54393, 54394, 54395, 54396
54397, 54398, 54399, 54400, 54401, 54402, 54403, 54404, 54405, 54406, 54407, 54408, 54409, 54410, 54411, 54412
54413, 54414, 54415, 54416, 54417, 54418, 54419, 54420, 54421, 54422, 54423, 54424, 54425, 54426, 54427, 54428
54429, 54430, 54431, 54432, 54433, 54434, 54435, 54436, 54437, 54438, 54439, 54440, 54441, 54442, 54443, 54444
54445, 54446, 54447, 54448, 54449, 54450, 54451, 54452, 54453, 54454, 54455, 54456, 54457, 54458, 54459, 54460
54461, 54462, 54463, 54464, 54465, 54466, 54467, 54468, 54469, 54470, 54471, 54472, 54473, 54474, 54475, 54476
54477, 54478, 54479, 54480, 54481, 54482, 54483, 54484, 54485, 54486, 54487, 54488, 54489, 54490, 54491, 54492
54493, 54494, 54495, 54496, 54497, 54498, 54499, 54500, 54501, 54502, 54503, 54504, 54505, 54506, 54507, 54508
54509, 54510, 54511, 54512, 54513, 54514, 54515, 54516, 54517, 54518, 54519, 54520, 54521, 54522, 54523, 54524
54525, 54526, 54527, 54528, 54529, 54530, 54531, 54532, 54533, 54534, 54535, 54536, 54537, 54538, 54539, 54540
54541, 54542, 54543, 54544, 54545, 54546, 54547, 54548, 54549, 54550, 54551, 54552, 56533, 56534, 56535, 56536
56537, 56538, 56539, 56540, 56541, 56542, 56543, 56544, 56545, 56546, 56547, 56548, 56549, 56550, 56551, 56552
56553, 56554, 56555, 56556, 56557, 56558, 56559, 56560, 56561, 56562, 56563, 56564, 56565, 56566, 56567, 56568
56569, 56570, 56571, 56572, 56573, 56574, 56575, 56576, 56577, 56578, 56579, 56580, 56581, 56582, 56583, 56584
56585, 56586, 56587, 56588, 56589, 56590, 56591, 56592, 56593, 56594, 56595, 56596, 56597, 56598, 56599, 56600
56601, 56602, 56603, 56604, 56605, 56606, 56607, 56608, 56609, 56610, 56611, 56612, 56613, 56614, 56615, 56616
56617, 56618, 56619, 56620, 56621, 56622, 56623, 56624, 56625, 56626, 56627, 56628, 56629, 56630, 56631, 56632
56633, 56634, 56635, 56636, 56637, 56638, 56639, 56640, 56641, 56642, 56643, 56644, 56645, 56646, 56647, 56648
56649, 56650, 56651, 56652, 56653, 56654, 56655, 56656, 56657, 56658, 56659, 56660, 56661, 56662, 56663, 56664
56665, 56666, 56667, 56668, 56669, 56670, 56671, 56672, 56673, 56674, 56675, 56676, 56677, 56678, 56679, 56680
56681, 56682, 56683, 56684, 56685, 56686, 56687, 56688, 56689, 56690, 56691, 56692, 56693, 56694, 56695, 56696
56697, 56698, 56699, 56700, 56701, 56702, 56703, 56704, 56705, 56706, 56707, 56708, 56709, 56710, 56711, 56712
58561, 58562, 58563, 58564, 58565, 58566, 58567, 58568, 58569, 58570, 58571, 58572, 58573, 58574, 58575, 58576
58577, 58578, 58579, 58580, 58581, 58582, 58583, 58584, 58585, 58586, 58587, 58588, 58589, 58590, 58591, 58592
58593, 58594, 58595, 58596, 58597, 58598, 58599, 58600, 58601, 58602, 58603, 58604, 58605, 58606, 58607, 58608
58609, 58610, 58611, 58612, 58613, 58614, 58615, 58616, 58617, 58618, 58619, 58620, 58621, 58622, 58623, 58624
58625, 58626, 58627, 58628, 58629, 58630, 58631, 58632, 58633, 58634, 58635, 58636, 58637, 58638, 58639, 58640
58641, 58642, 58643, 58644, 58645, 58646, 58647, 58648, 58649, 58650, 58651, 58652, 58653, 58654, 58655, 58656
58657, 58658, 58659, 58660, 58661, 58662, 58663, 58664, 58665, 58666, 58667, 58668, 58669, 58670, 58671, 58672
58673, 58674, 58675, 58676, 58677, 58678, 58679, 58680, 58681, 58682, 58683, 58684, 58685, 58686, 58687, 58688
58689, 58690, 58691, 58692, 58693, 58694, 58695, 58696, 58697, 58698, 58699, 58700, 58701, 58702, 58703, 58704
58705, 58706, 58707, 58708, 58709, 58710, 58711, 58712, 58713, 58714, 58715, 58716, 58717, 58718, 58719, 58720
58721, 58722, 58723, 58724, 58725, 58726, 58727, 58728, 59629, 59630, 59631, 59632, 59633, 59634, 59635, 59636
59637, 59638, 59639, 59640, 59641, 59642, 59643, 59644, 59645, 59646, 59647, 59648, 59649, 59650, 59651, 59652
59653, 59654, 59655, 59656, 59657, 59658, 59659, 59660, 59661, 59662, 59663, 59664, 59665, 59666, 59667, 59668
59669, 59670, 59671, 59672, 59673, 59674, 59675, 59676, 59677, 59678, 59679, 59680, 59681, 59682, 59683, 59684
59685, 59686, 59687, 59688, 59689, 59690, 59691, 59692, 59693, 59694, 59695, 59696, 59697, 59698, 59699, 59700
59701, 59702, 59703, 59704, 59705, 59706, 59707, 59708, 59709, 59710, 59711, 59712, 59713, 59714, 59715, 59716
59717, 59718, 59719, 59720, 59721, 59722, 59723, 59724, 59725, 59726, 59727, 59728, 59729, 59730, 59731, 59732
59733, 59734, 59735, 59736, 59737, 59738, 59739, 59740, 59741, 59742, 59743, 59744, 59745, 59746, 59747, 59748
59749, 59750, 59751, 59752, 59753, 59754, 59755, 59756, 59757, 59758, 59759, 59760, 59761, 59762, 59763, 59764
59765, 59766, 59767, 59768, 59769, 59770, 59771, 59772, 59773, 59774, 59775, 59776, 59777, 59778, 59779, 59780
59781, 59782, 59783, 59784, 59785, 59786, 59787, 59788, 59789, 59790, 59791, 59792, 59793, 59794, 59795, 59796
59797, 59798, 59799, 59800, 59801, 59802, 59803, 59804, 59805, 59806, 59807, 59808, 61729, 61730, 61731, 61732
61733, 61734, 61735, 61736, 61737, 61738, 61739, 61740, 61741, 61742, 61743, 61744, 61745, 61746, 61747, 61748
61749, 61750, 61751, 61752, 61753, 61754, 61755, 61756, 61757, 61758, 61759, 61760, 61761, 61762, 61763, 61764
61765, 61766, 61767, 61768, 61769, 61770, 61771, 61772, 61773, 61774, 61775, 61776, 61777, 61778, 61779, 61780
61781, 61782, 61783, 61784, 61785, 61786, 61787, 61788, 61789, 61790, 61791, 61792, 61793, 61794, 61795, 61796
61797, 61798, 61799, 61800, 61801, 61802, 61803, 61804, 61805, 61806, 61807, 61808, 61809, 61810, 61811, 61812
61813, 61814, 61815, 61816, 61817, 61818, 61819, 61820, 61821, 61822, 61823, 61824, 61825, 61826, 61827, 61828
61829, 61830, 61831, 61832, 61833, 61834, 61835, 61836, 61837, 61838, 61839, 61840, 61841, 61842, 61843, 61844
61845, 61846, 61847, 61848, 61849, 61850, 61851, 61852, 61853, 61854, 61855, 61856, 61857, 61858, 61859, 61860
61861, 61862, 61863, 61864, 61865, 61866, 61867, 61868, 61869, 61870, 61871, 61872, 61873, 61874, 61875, 61876
61877, 61878, 61879, 61880, 61881, 61882, 61883, 61884, 61885, 61886, 61887, 61888, 61889, 61890, 61891, 61892
61893, 61894, 61895, 61896, 63745, 63746, 63747, 63748, 63749, 63750, 63751, 63752, 63753, 63754, 63755, 63756
63757, 63758, 63759, 63760, 63761, 63762, 63763, 63764, 63765, 63766, 63767, 63768, 63769, 63770, 63771, 63772
63773, 63774, 63775, 63776, 63777, 63778, 63779, 63780, 63781, 63782, 63783, 63784, 63785, 63786, 63787, 63788
63789, 63790, 63791, 63792, 63793, 63794, 63795, 63796, 63797, 63798, 63799, 63800, 63801, 63802, 63803, 63804
63805, 63806, 63807, 63808, 63809, 63810, 63811, 63812, 63813, 63814, 63815, 63816, 63817, 63818, 63819, 63820
63821, 63822, 63823, 63824, 63825, 63826, 63827, 63828, 63829, 63830, 63831, 63832, 63833, 63834, 63835, 63836
63837, 63838, 63839, 63840, 63841, 63842, 63843, 63844, 63845, 63846, 63847, 63848, 63849, 63850, 63851, 63852
63853, 63854, 63855, 63856, 63857, 63858, 63859, 63860, 63861, 63862, 63863, 63864, 63865, 63866, 63867, 63868
63869, 63870, 63871, 63872, 63873, 63874, 63875, 63876, 63877, 63878, 63879, 63880, 63881, 63882, 63883, 63884
63885, 63886, 63887, 63888, 63889, 63890, 63891, 63892, 63893, 63894, 63895, 63896, 63897, 63898, 63899, 63900
63901, 63902, 63903, 63904, 63905, 63906, 63907, 63908, 63909, 63910, 63911, 63912, 65821, 65822, 65823, 65824
65825, 65826, 65827, 65828, 65829, 65830, 65831, 65832, 65833, 65834, 65835, 65836, 65837, 65838, 65839, 65840
65841, 65842, 65843, 65844, 65845, 65846, 65847, 65848, 65849, 65850, 65851, 65852, 65853, 65854, 65855, 65856
65857, 65858, 65859, 65860, 65861, 65862, 65863, 65864, 65865, 65866, 65867, 65868, 65869, 65870, 65871, 65872
65873, 65874, 65875, 65876, 65877, 65878, 65879, 65880, 65881, 65882, 65883, 65884, 65885, 65886, 65887, 65888
65889, 65890, 65891, 65892, 65893, 65894, 65895, 65896, 65897, 65898, 65899, 65900, 65901, 65902, 65903, 65904
65905, 65906, 65907, 65908, 65909, 65910, 65911, 65912, 65913, 65914, 65915, 65916, 65917, 65918, 65919, 65920
65921, 65922, 65923, 65924, 65925, 65926, 65927, 65928, 65929, 65930, 65931, 65932, 65933, 65934, 65935, 65936
65937, 65938, 65939, 65940, 65941, 65942, 65943, 65944, 65945, 65946, 65947, 65948, 65949, 65950, 65951, 65952
65953, 65954, 65955, 65956, 65957, 65958, 65959, 65960, 65961, 65962, 65963, 65964, 65965, 65966, 65967, 65968
65969, 65970, 65971, 65972, 65973, 65974, 65975, 65976, 65977, 65978, 65979, 65980, 65981, 65982, 65983, 65984
65985, 65986, 65987, 65988, 65989, 65990, 65991, 65992, 65993, 65994, 65995, 65996, 65997, 65998, 65999, 66000
67909, 67910, 67911, 67912, 67913, 67914, 67915, 67916, 67917, 67918, 67919, 67920, 67921, 67922, 67923, 67924
67925, 67926, 67927, 67928, 67929, 67930, 67931, 67932, 67933, 67934, 67935, 67936, 67937, 67938, 67939, 67940
67941, 67942, 67943, 67944, 67945, 67946, 67947, 67948, 67949, 67950, 67951, 67952, 67953, 67954, 67955, 67956
67957, 67958, 67959, 67960, 67961, 67962, 67963, 67964, 67965, 67966, 67967, 67968, 67969, 67970, 67971, 67972
67973, 67974, 67975, 67976, 67977, 67978, 67979, 67980, 67981, 67982, 67983, 67984, 67985, 67986, 67987, 67988
67989, 67990, 67991, 67992, 67993, 67994, 67995, 67996, 67997, 67998, 67999, 68000, 68001, 68002, 68003, 68004
68005, 68006, 68007, 68008, 68009, 68010, 68011, 68012, 68013, 68014, 68015, 68016, 68017, 68018, 68019, 68020
68021, 68022, 68023, 68024, 68025, 68026, 68027, 68028, 68029, 68030, 68031, 68032, 68033, 68034, 68035, 68036
68037, 68038, 68039, 68040, 68041, 68042, 68043, 68044, 68045, 68046, 68047, 68048, 68049, 68050, 68051, 68052
68053, 68054, 68055, 68056, 68057, 68058, 68059, 68060, 68061, 68062, 68063, 68064, 68065, 68066, 68067, 68068
68069, 68070, 68071, 68072, 68073, 68074, 68075, 68076, 68077, 68078, 68079, 68080, 68081, 68082, 68083, 68084
68085, 68086, 68087, 68088, 70009, 70010, 70011, 70012, 70013, 70014, 70015, 70016, 70017, 70018, 70019, 70020
70021, 70022, 70023, 70024, 70025, 70026, 70027, 70028, 70029, 70030, 70031, 70032, 70033, 70034, 70035, 70036
70037, 70038, 70039, 70040, 70041, 70042, 70043, 70044, 70045, 70046, 70047, 70048, 70049, 70050, 70051, 70052
70053, 70054, 70055, 70056, 70057, 70058, 70059, 70060, 70061, 70062, 70063, 70064, 70065, 70066, 70067, 70068
70069, 70070, 70071, 70072, 70073, 70074, 70075, 70076, 70077, 70078, 70079, 70080, 70081, 70082, 70083, 70084
70085, 70086, 70087, 70088, 70089, 70090, 70091, 70092, 70093, 70094, 70095, 70096, 70097, 70098, 70099, 70100
70101, 70102, 70103, 70104, 70105, 70106, 70107, 70108, 70109, 70110, 70111, 70112, 70113, 70114, 70115, 70116
70117, 70118, 70119, 70120, 70121, 70122, 70123, 70124, 70125, 70126, 70127, 70128, 70129, 70130, 70131, 70132
70133, 70134, 70135, 70136, 70137, 70138, 70139, 70140, 70141, 70142, 70143, 70144, 70145, 70146, 70147, 70148
70149, 70150, 70151, 70152, 70153, 70154, 70155, 70156, 70157, 70158, 70159, 70160, 70161, 70162, 70163, 70164
70165, 70166, 70167, 70168, 70169, 70170, 70171, 70172, 70173, 70174, 70175, 70176
*Elset, elset=__PickedSurf53_S3, internal, instance=Stent
2521, 2522, 2523, 2524, 2525, 2526, 2527, 2528, 2529, 2530, 2531, 2532, 2533, 2534, 2535, 2536
2537, 2538, 2539, 2635, 2636, 2637, 2638, 2639, 2640, 2641, 2642, 2643, 2644, 2645, 2646, 2647
2648, 2649, 2650, 2651, 2652, 2653, 2749, 2750, 2751, 2752, 2753, 2754, 2755, 2756, 2757, 2758
2759, 2760, 2761, 2762, 2763, 2764, 2765, 2766, 2767, 2863, 2864, 2865, 2866, 2867, 2868, 2869
2870, 2871, 2872, 2873, 2874, 2875, 2876, 2877, 2878, 2879, 2880, 2881, 2977, 2978, 2979, 2980
2981, 2982, 2983, 2984, 2985, 2986, 2987, 2988, 2989, 2990, 2991, 2992, 2993, 2994, 2995, 3091
3092, 3093, 3094, 3095, 3096, 3097, 3098, 3099, 3100, 3101, 3102, 3103, 3104, 3105, 3106, 3107
3108, 3109, 3205, 3206, 3207, 3208, 3209, 3210, 3211, 3212, 3213, 3214, 3215, 3216, 3217, 3218
3219, 3220, 3221, 3222, 3223, 3319, 3320, 3321, 3322, 3323, 3324, 3325, 3326, 3327, 3328, 3329
3330, 3331, 3332, 3333, 3334, 3335, 3336, 3337, 3433, 3434, 3435, 3436, 3437, 3438, 3439, 3440
3441, 3442, 3443, 3444, 3445, 3446, 3447, 3448, 3449, 3450, 3451, 3547, 3548, 3549, 3550, 3551
3552, 3553, 3554, 3555, 3556, 3557, 3558, 3559, 3560, 3561, 3562, 3563, 3564, 3565, 3661, 3662
3663, 3664, 3665, 3666, 3667, 3668, 3669, 3670, 3671, 3672, 3673, 3674, 3675, 3676, 3677, 3678
3679, 3775, 3776, 3777, 3778, 3779, 3780, 3781, 3782, 3783, 3784, 3785, 3786, 3787, 3788, 3789
3790, 3791, 3792, 3793, 6217, 6218, 6219, 6220, 6221, 6222, 6223, 6224, 6225, 6226, 6227, 6228
6229, 6230, 6231, 6232, 6233, 6234, 6235, 6331, 6332, 6333, 6334, 6335, 6336, 6337, 6338, 6339
6340, 6341, 6342, 6343, 6344, 6345, 6346, 6347, 6348, 6349, 6445, 6446, 6447, 6448, 6449, 6450
6451, 6452, 6453, 6454, 6455, 6456, 6457, 6458, 6459, 6460, 6461, 6462, 6463, 6559, 6560, 6561
6562, 6563, 6564, 6565, 6566, 6567, 6568, 6569, 6570, 6571, 6572, 6573, 6574, 6575, 6576, 6577
6673, 6674, 6675, 6676, 6677, 6678, 6679, 6680, 6681, 6682, 6683, 6684, 6685, 6686, 6687, 6688
6689, 6690, 6691, 6787, 6788, 6789, 6790, 6791, 6792, 6793, 6794, 6795, 6796, 6797, 6798, 6799
6800, 6801, 6802, 6803, 6804, 6805, 6901, 6902, 6903, 6904, 6905, 6906, 6907, 6908, 6909, 6910
6911, 6912, 6913, 6914, 6915, 6916, 6917, 6918, 6919, 7015, 7016, 7017, 7018, 7019, 7020, 7021
7022, 7023, 7024, 7025, 7026, 7027, 7028, 7029, 7030, 7031, 7032, 7033, 7129, 7130, 7131, 7132
7133, 7134, 7135, 7136, 7137, 7138, 7139, 7140, 7141, 7142, 7143, 7144, 7145, 7146, 7147, 7243
7244, 7245, 7246, 7247, 7248, 7249, 7250, 7251, 7252, 7253, 7254, 7255, 7256, 7257, 7258, 7259
7260, 7261, 7357, 7358, 7359, 7360, 7361, 7362, 7363, 7364, 7365, 7366, 7367, 7368, 7369, 7370
7371, 7372, 7373, 7374, 7375, 7471, 7472, 7473, 7474, 7475, 7476, 7477, 7478, 7479, 7480, 7481
7482, 7483, 7484, 7485, 7486, 7487, 7488, 7489, 9721, 9722, 9723, 9724, 9725, 9726, 9727, 9728
9729, 9730, 9731, 9732, 9733, 9734, 9735, 9736, 9737, 9738, 9739, 9835, 9836, 9837, 9838, 9839
9840, 9841, 9842, 9843, 9844, 9845, 9846, 9847, 9848, 9849, 9850, 9851, 9852, 9853, 9949, 9950
9951, 9952, 9953, 9954, 9955, 9956, 9957, 9958, 9959, 9960, 9961, 9962, 9963, 9964, 9965, 9966
9967, 10063, 10064, 10065, 10066, 10067, 10068, 10069, 10070, 10071, 10072, 10073, 10074, 10075, 10076, 10077
10078, 10079, 10080, 10081, 10177, 10178, 10179, 10180, 10181, 10182, 10183, 10184, 10185, 10186, 10187, 10188
10189, 10190, 10191, 10192, 10193, 10194, 10195, 10291, 10292, 10293, 10294, 10295, 10296, 10297, 10298, 10299
10300, 10301, 10302, 10303, 10304, 10305, 10306, 10307, 10308, 10309, 10405, 10406, 10407, 10408, 10409, 10410
10411, 10412, 10413, 10414, 10415, 10416, 10417, 10418, 10419, 10420, 10421, 10422, 10423, 10519, 10520, 10521
10522, 10523, 10524, 10525, 10526, 10527, 10528, 10529, 10530, 10531, 10532, 10533, 10534, 10535, 10536, 10537
10633, 10634, 10635, 10636, 10637, 10638, 10639, 10640, 10641, 10642, 10643, 10644, 10645, 10646, 10647, 10648
10649, 10650, 10651, 10747, 10748, 10749, 10750, 10751, 10752, 10753, 10754, 10755, 10756, 10757, 10758, 10759
10760, 10761, 10762, 10763, 10764, 10765, 10861, 10862, 10863, 10864, 10865, 10866, 10867, 10868, 10869, 10870
10871, 10872, 10873, 10874, 10875, 10876, 10877, 10878, 10879, 10975, 10976, 10977, 10978, 10979, 10980, 10981
10982, 10983, 10984, 10985, 10986, 10987, 10988, 10989, 10990, 10991, 10992, 10993, 13609, 13610, 13611, 13612
13613, 13614, 13615, 13616, 13617, 13618, 13619, 13620, 13621, 13622, 13623, 13624, 13625, 13626, 13627, 13723
13724, 13725, 13726, 13727, 13728, 13729, 13730, 13731, 13732, 13733, 13734, 13735, 13736, 13737, 13738, 13739
13740, 13741, 13837, 13838, 13839, 13840, 13841, 13842, 13843, 13844, 13845, 13846, 13847, 13848, 13849, 13850
13851, 13852, 13853, 13854, 13855, 13951, 13952, 13953, 13954, 13955, 13956, 13957, 13958, 13959, 13960, 13961
13962, 13963, 13964, 13965, 13966, 13967, 13968, 13969, 14065, 14066, 14067, 14068, 14069, 14070, 14071, 14072
14073, 14074, 14075, 14076, 14077, 14078, 14079, 14080, 14081, 14082, 14083, 14179, 14180, 14181, 14182, 14183
14184, 14185, 14186, 14187, 14188, 14189, 14190, 14191, 14192, 14193, 14194, 14195, 14196, 14197, 14293, 14294
14295, 14296, 14297, 14298, 14299, 14300, 14301, 14302, 14303, 14304, 14305, 14306, 14307, 14308, 14309, 14310
14311, 14407, 14408, 14409, 14410, 14411, 14412, 14413, 14414, 14415, 14416, 14417, 14418, 14419, 14420, 14421
14422, 14423, 14424, 14425, 14521, 14522, 14523, 14524, 14525, 14526, 14527, 14528, 14529, 14530, 14531, 14532
14533, 14534, 14535, 14536, 14537, 14538, 14539, 14635, 14636, 14637, 14638, 14639, 14640, 14641, 14642, 14643
14644, 14645, 14646, 14647, 14648, 14649, 14650, 14651, 14652, 14653, 14749, 14750, 14751, 14752, 14753, 14754
14755, 14756, 14757, 14758, 14759, 14760, 14761, 14762, 14763, 14764, 14765, 14766, 14767, 14863, 14864, 14865
14866, 14867, 14868, 14869, 14870, 14871, 14872, 14873, 14874, 14875, 14876, 14877, 14878, 14879, 14880, 14881
17689, 17690, 17691, 17692, 17693, 17694, 17695, 17696, 17697, 17698, 17699, 17700, 17701, 17702, 17703, 17704
17705, 17706, 17707, 17803, 17804, 17805, 17806, 17807, 17808, 17809, 17810, 17811, 17812, 17813, 17814, 17815
17816, 17817, 17818, 17819, 17820, 17821, 17917, 17918, 17919, 17920, 17921, 17922, 17923, 17924, 17925, 17926
17927, 17928, 17929, 17930, 17931, 17932, 17933, 17934, 17935, 18031, 18032, 18033, 18034, 18035, 18036, 18037
18038, 18039, 18040, 18041, 18042, 18043, 18044, 18045, 18046, 18047, 18048, 18049, 18145, 18146, 18147, 18148
18149, 18150, 18151, 18152, 18153, 18154, 18155, 18156, 18157, 18158, 18159, 18160, 18161, 18162, 18163, 18259
18260, 18261, 18262, 18263, 18264, 18265, 18266, 18267, 18268, 18269, 18270, 18271, 18272, 18273, 18274, 18275
18276, 18277, 18373, 18374, 18375, 18376, 18377, 18378, 18379, 18380, 18381, 18382, 18383, 18384, 18385, 18386
18387, 18388, 18389, 18390, 18391, 18487, 18488, 18489, 18490, 18491, 18492, 18493, 18494, 18495, 18496, 18497
18498, 18499, 18500, 18501, 18502, 18503, 18504, 18505, 18601, 18602, 18603, 18604, 18605, 18606, 18607, 18608
18609, 18610, 18611, 18612, 18613, 18614, 18615, 18616, 18617, 18618, 18619, 18715, 18716, 18717, 18718, 18719
18720, 18721, 18722, 18723, 18724, 18725, 18726, 18727, 18728, 18729, 18730, 18731, 18732, 18733, 18829, 18830
18831, 18832, 18833, 18834, 18835, 18836, 18837, 18838, 18839, 18840, 18841, 18842, 18843, 18844, 18845, 18846
18847, 18943, 18944, 18945, 18946, 18947, 18948, 18949, 18950, 18951, 18952, 18953, 18954, 18955, 18956, 18957
18958, 18959, 18960, 18961, 21385, 21386, 21387, 21388, 21389, 21390, 21391, 21392, 21393, 21394, 21395, 21396
21397, 21398, 21399, 21400, 21401, 21402, 21403, 21499, 21500, 21501, 21502, 21503, 21504, 21505, 21506, 21507
21508, 21509, 21510, 21511, 21512, 21513, 21514, 21515, 21516, 21517, 21613, 21614, 21615, 21616, 21617, 21618
21619, 21620, 21621, 21622, 21623, 21624, 21625, 21626, 21627, 21628, 21629, 21630, 21631, 21727, 21728, 21729
21730, 21731, 21732, 21733, 21734, 21735, 21736, 21737, 21738, 21739, 21740, 21741, 21742, 21743, 21744, 21745
21841, 21842, 21843, 21844, 21845, 21846, 21847, 21848, 21849, 21850, 21851, 21852, 21853, 21854, 21855, 21856
21857, 21858, 21859, 21955, 21956, 21957, 21958, 21959, 21960, 21961, 21962, 21963, 21964, 21965, 21966, 21967
21968, 21969, 21970, 21971, 21972, 21973, 22069, 22070, 22071, 22072, 22073, 22074, 22075, 22076, 22077, 22078
22079, 22080, 22081, 22082, 22083, 22084, 22085, 22086, 22087, 22183, 22184, 22185, 22186, 22187, 22188, 22189
22190, 22191, 22192, 22193, 22194, 22195, 22196, 22197, 22198, 22199, 22200, 22201, 22297, 22298, 22299, 22300
22301, 22302, 22303, 22304, 22305, 22306, 22307, 22308, 22309, 22310, 22311, 22312, 22313, 22314, 22315, 22411
22412, 22413, 22414, 22415, 22416, 22417, 22418, 22419, 22420, 22421, 22422, 22423, 22424, 22425, 22426, 22427
22428, 22429, 22525, 22526, 22527, 22528, 22529, 22530, 22531, 22532, 22533, 22534, 22535, 22536, 22537, 22538
22539, 22540, 22541, 22542, 22543, 22639, 22640, 22641, 22642, 22643, 22644, 22645, 22646, 22647, 22648, 22649
22650, 22651, 22652, 22653, 22654, 22655, 22656, 22657, 22945, 22946, 22947, 22948, 22949, 22950, 22951, 22952
22953, 22954, 22955, 22956, 22957, 22958, 22959, 22960, 23041, 23042, 23043, 23044, 23045, 23046, 23047, 23048
23049, 23050, 23051, 23052, 23053, 23054, 23055, 23056, 23137, 23138, 23139, 23140, 23141, 23142, 23143, 23144
23145, 23146, 23147, 23148, 23149, 23150, 23151, 23152, 23233, 23234, 23235, 23236, 23237, 23238, 23239, 23240
23241, 23242, 23243, 23244, 23245, 23246, 23247, 23248, 23329, 23330, 23331, 23332, 23333, 23334, 23335, 23336
23337, 23338, 23339, 23340, 23341, 23342, 23343, 23344, 23345, 23346, 23347, 23443, 23444, 23445, 23446, 23447
23448, 23449, 23450, 23451, 23452, 23453, 23454, 23455, 23456, 23457, 23458, 23459, 23460, 23461, 23557, 23558
23559, 23560, 23561, 23562, 23563, 23564, 23565, 23566, 23567, 23568, 23569, 23570, 23571, 23572, 23573, 23574
23575, 23671, 23672, 23673, 23674, 23675, 23676, 23677, 23678, 23679, 23680, 23681, 23682, 23683, 23684, 23685
23686, 23687, 23688, 23689, 23785, 23786, 23787, 23788, 23789, 23790, 23791, 23792, 23793, 23794, 23795, 23796
23797, 23798, 23799, 23800, 23801, 23802, 23803, 23899, 23900, 23901, 23902, 23903, 23904, 23905, 23906, 23907
23908, 23909, 23910, 23911, 23912, 23913, 23914, 23915, 23916, 23917, 24013, 24014, 24015, 24016, 24017, 24018
24019, 24020, 24021, 24022, 24023, 24024, 24025, 24026, 24027, 24028, 24029, 24030, 24031, 24127, 24128, 24129
24130, 24131, 24132, 24133, 24134, 24135, 24136, 24137, 24138, 24139, 24140, 24141, 24142, 24143, 24144, 24145
24241, 24242, 24243, 24244, 24245, 24246, 24247, 24248, 24249, 24250, 24251, 24252, 24253, 24254, 24255, 24256
24257, 24258, 24259, 24355, 24356, 24357, 24358, 24359, 24360, 24361, 24362, 24363, 24364, 24365, 24366, 24367
24368, 24369, 24370, 24371, 24372, 24373, 24469, 24470, 24471, 24472, 24473, 24474, 24475, 24476, 24477, 24478
24479, 24480, 24481, 24482, 24483, 24484, 24485, 24486, 24487, 24583, 24584, 24585, 24586, 24587, 24588, 24589
24590, 24591, 24592, 24593, 24594, 24595, 24596, 24597, 24598, 24599, 24600, 24601, 24697, 24698, 24699, 24700
24701, 24702, 24703, 24704, 24705, 24706, 24707, 24708, 24709, 24710, 24711, 24712, 24793, 24794, 24795, 24796
24797, 24798, 24799, 24800, 24801, 24802, 24803, 24804, 24805, 24806, 24807, 24808, 24889, 24890, 24891, 24892
24893, 24894, 24895, 24896, 24897, 24898, 24899, 24900, 24901, 24902, 24903, 24904, 24985, 24986, 24987, 24988
24989, 24990, 24991, 24992, 24993, 24994, 24995, 24996, 24997, 24998, 24999, 25000, 27217, 27218, 27219, 27220
27221, 27222, 27223, 27224, 27225, 27226, 27227, 27228, 27229, 27230, 27231, 27232, 27313, 27314, 27315, 27316
27317, 27318, 27319, 27320, 27321, 27322, 27323, 27324, 27325, 27326, 27327, 27328, 27409, 27410, 27411, 27412
27413, 27414, 27415, 27416, 27417, 27418, 27419, 27420, 27421, 27422, 27423, 27424, 27425, 27426, 27427, 27523
27524, 27525, 27526, 27527, 27528, 27529, 27530, 27531, 27532, 27533, 27534, 27535, 27536, 27537, 27538, 27539
27540, 27541, 27637, 27638, 27639, 27640, 27641, 27642, 27643, 27644, 27645, 27646, 27647, 27648, 27649, 27650
27651, 27652, 27653, 27654, 27655, 27751, 27752, 27753, 27754, 27755, 27756, 27757, 27758, 27759, 27760, 27761
27762, 27763, 27764, 27765, 27766, 27767, 27768, 27769, 27865, 27866, 27867, 27868, 27869, 27870, 27871, 27872
27873, 27874, 27875, 27876, 27877, 27878, 27879, 27880, 27881, 27882, 27883, 27979, 27980, 27981, 27982, 27983
27984, 27985, 27986, 27987, 27988, 27989, 27990, 27991, 27992, 27993, 27994, 27995, 27996, 27997, 28093, 28094
28095, 28096, 28097, 28098, 28099, 28100, 28101, 28102, 28103, 28104, 28105, 28106, 28107, 28108, 28109, 28110
28111, 28207, 28208, 28209, 28210, 28211, 28212, 28213, 28214, 28215, 28216, 28217, 28218, 28219, 28220, 28221
28222, 28223, 28224, 28225, 28321, 28322, 28323, 28324, 28325, 28326, 28327, 28328, 28329, 28330, 28331, 28332
28333, 28334, 28335, 28336, 28337, 28338, 28339, 28435, 28436, 28437, 28438, 28439, 28440, 28441, 28442, 28443
28444, 28445, 28446, 28447, 28448, 28449, 28450, 28451, 28452, 28453, 28549, 28550, 28551, 28552, 28553, 28554
28555, 28556, 28557, 28558, 28559, 28560, 28561, 28562, 28563, 28564, 28565, 28566, 28567, 28663, 28664, 28665
28666, 28667, 28668, 28669, 28670, 28671, 28672, 28673, 28674, 28675, 28676, 28677, 28678, 28679, 28680, 28681
28777, 28778, 28779, 28780, 28781, 28782, 28783, 28784, 28785, 28786, 28787, 28788, 28789, 28790, 28791, 28792
28873, 28874, 28875, 28876, 28877, 28878, 28879, 28880, 28881, 28882, 28883, 28884, 28885, 28886, 28887, 28888
30721, 30722, 30723, 30724, 30725, 30726, 30727, 30728, 30729, 30730, 30731, 30732, 30733, 30734, 30735, 30736
30817, 30818, 30819, 30820, 30821, 30822, 30823, 30824, 30825, 30826, 30827, 30828, 30829, 30830, 30831, 30832
30913, 30914, 30915, 30916, 30917, 30918, 30919, 30920, 30921, 30922, 30923, 30924, 30925, 30926, 30927, 30928
30929, 30930, 30931, 31027, 31028, 31029, 31030, 31031, 31032, 31033, 31034, 31035, 31036, 31037, 31038, 31039
31040, 31041, 31042, 31043, 31044, 31045, 31141, 31142, 31143, 31144, 31145, 31146, 31147, 31148, 31149, 31150
31151, 31152, 31153, 31154, 31155, 31156, 31157, 31158, 31159, 31255, 31256, 31257, 31258, 31259, 31260, 31261
31262, 31263, 31264, 31265, 31266, 31267, 31268, 31269, 31270, 31271, 31272, 31273, 31369, 31370, 31371, 31372
31373, 31374, 31375, 31376, 31377, 31378, 31379, 31380, 31381, 31382, 31383, 31384, 31385, 31386, 31387, 31483
31484, 31485, 31486, 31487, 31488, 31489, 31490, 31491, 31492, 31493, 31494, 31495, 31496, 31497, 31498, 31499
31500, 31501, 31597, 31598, 31599, 31600, 31601, 31602, 31603, 31604, 31605, 31606, 31607, 31608, 31609, 31610
31611, 31612, 31613, 31614, 31615, 31711, 31712, 31713, 31714, 31715, 31716, 31717, 31718, 31719, 31720, 31721
31722, 31723, 31724, 31725, 31726, 31727, 31728, 31729, 31825, 31826, 31827, 31828, 31829, 31830, 31831, 31832
31833, 31834, 31835, 31836, 31837, 31838, 31839, 31840, 31841, 31842, 31843, 31939, 31940, 31941, 31942, 31943
31944, 31945, 31946, 31947, 31948, 31949, 31950, 31951, 31952, 31953, 31954, 31955, 31956, 31957, 32053, 32054
32055, 32056, 32057, 32058, 32059, 32060, 32061, 32062, 32063, 32064, 32065, 32066, 32067, 32068, 32069, 32070
32071, 32167, 32168, 32169, 32170, 32171, 32172, 32173, 32174, 32175, 32176, 32177, 32178, 32179, 32180, 32181
32182, 32183, 32184, 32185, 32281, 32282, 32283, 32284, 32285, 32286, 32287, 32288, 32289, 32290, 32291, 32292
32293, 32294, 32295, 32296, 32377, 32378, 32379, 32380, 32381, 32382, 32383, 32384, 32385, 32386, 32387, 32388
32389, 32390, 32391, 32392, 34225, 34226, 34227, 34228, 34229, 34230, 34231, 34232, 34233, 34234, 34235, 34236
34237, 34238, 34239, 34240, 34321, 34322, 34323, 34324, 34325, 34326, 34327, 34328, 34329, 34330, 34331, 34332
34333, 34334, 34335, 34336, 34417, 34418, 34419, 34420, 34421, 34422, 34423, 34424, 34425, 34426, 34427, 34428
34429, 34430, 34431, 34432, 34513, 34514, 34515, 34516, 34517, 34518, 34519, 34520, 34521, 34522, 34523, 34524
34525, 34526, 34527, 34528, 34609, 34610, 34611, 34612, 34613, 34614, 34615, 34616, 34617, 34618, 34619, 34620
34621, 34622, 34623, 34624, 34625, 34626, 34627, 34723, 34724, 34725, 34726, 34727, 34728, 34729, 34730, 34731
34732, 34733, 34734, 34735, 34736, 34737, 34738, 34739, 34740, 34741, 34837, 34838, 34839, 34840, 34841, 34842
34843, 34844, 34845, 34846, 34847, 34848, 34849, 34850, 34851, 34852, 34853, 34854, 34855, 34951, 34952, 34953
34954, 34955, 34956, 34957, 34958, 34959, 34960, 34961, 34962, 34963, 34964, 34965, 34966, 34967, 34968, 34969
35065, 35066, 35067, 35068, 35069, 35070, 35071, 35072, 35073, 35074, 35075, 35076, 35077, 35078, 35079, 35080
35081, 35082, 35083, 35179, 35180, 35181, 35182, 35183, 35184, 35185, 35186, 35187, 35188, 35189, 35190, 35191
35192, 35193, 35194, 35195, 35196, 35197, 35293, 35294, 35295, 35296, 35297, 35298, 35299, 35300, 35301, 35302
35303, 35304, 35305, 35306, 35307, 35308, 35309, 35310, 35311, 35407, 35408, 35409, 35410, 35411, 35412, 35413
35414, 35415, 35416, 35417, 35418, 35419, 35420, 35421, 35422, 35423, 35424, 35425, 35521, 35522, 35523, 35524
35525, 35526, 35527, 35528, 35529, 35530, 35531, 35532, 35533, 35534, 35535, 35536, 35537, 35538, 35539, 35635
35636, 35637, 35638, 35639, 35640, 35641, 35642, 35643, 35644, 35645, 35646, 35647, 35648, 35649, 35650, 35651
35652, 35653, 35749, 35750, 35751, 35752, 35753, 35754, 35755, 35756, 35757, 35758, 35759, 35760, 35761, 35762
35763, 35764, 35765, 35766, 35767, 35863, 35864, 35865, 35866, 35867, 35868, 35869, 35870, 35871, 35872, 35873
35874, 35875, 35876, 35877, 35878, 35879, 35880, 35881, 35977, 35978, 35979, 35980, 35981, 35982, 35983, 35984
35985, 35986, 35987, 35988, 35989, 35990, 35991, 35992, 36073, 36074, 36075, 36076, 36077, 36078, 36079, 36080
36081, 36082, 36083, 36084, 36085, 36086, 36087, 36088, 36169, 36170, 36171, 36172, 36173, 36174, 36175, 36176
36177, 36178, 36179, 36180, 36181, 36182, 36183, 36184, 36265, 36266, 36267, 36268, 36269, 36270, 36271, 36272
36273, 36274, 36275, 36276, 36277, 36278, 36279, 36280, 38113, 38114, 38115, 38116, 38117, 38118, 38119, 38120
38121, 38122, 38123, 38124, 38125, 38126, 38127, 38128, 38209, 38210, 38211, 38212, 38213, 38214, 38215, 38216
38217, 38218, 38219, 38220, 38221, 38222, 38223, 38224, 38305, 38306, 38307, 38308, 38309, 38310, 38311, 38312
38313, 38314, 38315, 38316, 38317, 38318, 38319, 38320, 38401, 38402, 38403, 38404, 38405, 38406, 38407, 38408
38409, 38410, 38411, 38412, 38413, 38414, 38415, 38416, 38497, 38498, 38499, 38500, 38501, 38502, 38503, 38504
38505, 38506, 38507, 38508, 38509, 38510, 38511, 38512, 38513, 38514, 38515, 38611, 38612, 38613, 38614, 38615
38616, 38617, 38618, 38619, 38620, 38621, 38622, 38623, 38624, 38625, 38626, 38627, 38628, 38629, 38725, 38726
38727, 38728, 38729, 38730, 38731, 38732, 38733, 38734, 38735, 38736, 38737, 38738, 38739, 38740, 38741, 38742
38743, 38839, 38840, 38841, 38842, 38843, 38844, 38845, 38846, 38847, 38848, 38849, 38850, 38851, 38852, 38853
38854, 38855, 38856, 38857, 38953, 38954, 38955, 38956, 38957, 38958, 38959, 38960, 38961, 38962, 38963, 38964
38965, 38966, 38967, 38968, 38969, 38970, 38971, 39067, 39068, 39069, 39070, 39071, 39072, 39073, 39074, 39075
39076, 39077, 39078, 39079, 39080, 39081, 39082, 39083, 39084, 39085, 39181, 39182, 39183, 39184, 39185, 39186
39187, 39188, 39189, 39190, 39191, 39192, 39193, 39194, 39195, 39196, 39197, 39198, 39199, 39295, 39296, 39297
39298, 39299, 39300, 39301, 39302, 39303, 39304, 39305, 39306, 39307, 39308, 39309, 39310, 39311, 39312, 39313
39409, 39410, 39411, 39412, 39413, 39414, 39415, 39416, 39417, 39418, 39419, 39420, 39421, 39422, 39423, 39424
39425, 39426, 39427, 39523, 39524, 39525, 39526, 39527, 39528, 39529, 39530, 39531, 39532, 39533, 39534, 39535
39536, 39537, 39538, 39539, 39540, 39541, 39637, 39638, 39639, 39640, 39641, 39642, 39643, 39644, 39645, 39646
39647, 39648, 39649, 39650, 39651, 39652, 39653, 39654, 39655, 39751, 39752, 39753, 39754, 39755, 39756, 39757
39758, 39759, 39760, 39761, 39762, 39763, 39764, 39765, 39766, 39767, 39768, 39769, 39865, 39866, 39867, 39868
39869, 39870, 39871, 39872, 39873, 39874, 39875, 39876, 39877, 39878, 39879, 39880, 39961, 39962, 39963, 39964
39965, 39966, 39967, 39968, 39969, 39970, 39971, 39972, 39973, 39974, 39975, 39976, 40057, 40058, 40059, 40060
40061, 40062, 40063, 40064, 40065, 40066, 40067, 40068, 40069, 40070, 40071, 40072, 40153, 40154, 40155, 40156
40157, 40158, 40159, 40160, 40161, 40162, 40163, 40164, 40165, 40166, 40167, 40168, 42385, 42386, 42387, 42388
42389, 42390, 42391, 42392, 42393, 42394, 42395, 42396, 42397, 42398, 42399, 42400, 42481, 42482, 42483, 42484
42485, 42486, 42487, 42488, 42489, 42490, 42491, 42492, 42493, 42494, 42495, 42496, 42577, 42578, 42579, 42580
42581, 42582, 42583, 42584, 42585, 42586, 42587, 42588, 42589, 42590, 42591, 42592, 42593, 42594, 42595, 42691
42692, 42693, 42694, 42695, 42696, 42697, 42698, 42699, 42700, 42701, 42702, 42703, 42704, 42705, 42706, 42707
42708, 42709, 42805, 42806, 42807, 42808, 42809, 42810, 42811, 42812, 42813, 42814, 42815, 42816, 42817, 42818
42819, 42820, 42821, 42822, 42823, 42919, 42920, 42921, 42922, 42923, 42924, 42925, 42926, 42927, 42928, 42929
42930, 42931, 42932, 42933, 42934, 42935, 42936, 42937, 43033, 43034, 43035, 43036, 43037, 43038, 43039, 43040
43041, 43042, 43043, 43044, 43045, 43046, 43047, 43048, 43049, 43050, 43051, 43147, 43148, 43149, 43150, 43151
43152, 43153, 43154, 43155, 43156, 43157, 43158, 43159, 43160, 43161, 43162, 43163, 43164, 43165, 43261, 43262
43263, 43264, 43265, 43266, 43267, 43268, 43269, 43270, 43271, 43272, 43273, 43274, 43275, 43276, 43277, 43278
43279, 43375, 43376, 43377, 43378, 43379, 43380, 43381, 43382, 43383, 43384, 43385, 43386, 43387, 43388, 43389
43390, 43391, 43392, 43393, 43489, 43490, 43491, 43492, 43493, 43494, 43495, 43496, 43497, 43498, 43499, 43500
43501, 43502, 43503, 43504, 43505, 43506, 43507, 43603, 43604, 43605, 43606, 43607, 43608, 43609, 43610, 43611
43612, 43613, 43614, 43615, 43616, 43617, 43618, 43619, 43620, 43621, 43717, 43718, 43719, 43720, 43721, 43722
43723, 43724, 43725, 43726, 43727, 43728, 43729, 43730, 43731, 43732, 43733, 43734, 43735, 43831, 43832, 43833
43834, 43835, 43836, 43837, 43838, 43839, 43840, 43841, 43842, 43843, 43844, 43845, 43846, 43847, 43848, 43849
43945, 43946, 43947, 43948, 43949, 43950, 43951, 43952, 43953, 43954, 43955, 43956, 43957, 43958, 43959, 43960
44041, 44042, 44043, 44044, 44045, 44046, 44047, 44048, 44049, 44050, 44051, 44052, 44053, 44054, 44055, 44056
*Elset, elset=__PickedSurf53_S5, internal, instance=Stent
81, 82, 83, 84, 85, 86, 87, 88, 89, 90, 91, 92, 93, 94, 95, 96
177, 178, 179, 180, 181, 182, 183, 184, 185, 186, 187, 188, 189, 190, 191, 192
273, 274, 275, 276, 277, 278, 279, 280, 281, 282, 283, 284, 285, 286, 287, 288
369, 370, 371, 372, 373, 374, 375, 376, 377, 378, 379, 380, 381, 382, 383, 384
480, 481, 482, 483, 484, 485, 486, 487, 488, 489, 490, 491, 492, 493, 494, 495
496, 497, 498, 594, 595, 596, 597, 598, 599, 600, 601, 602, 603, 604, 605, 606
607, 608, 609, 610, 611, 612, 708, 709, 710, 711, 712, 713, 714, 715, 716, 717
718, 719, 720, 721, 722, 723, 724, 725, 726, 822, 823, 824, 825, 826, 827, 828
829, 830, 831, 832, 833, 834, 835, 836, 837, 838, 839, 840, 936, 937, 938, 939
940, 941, 942, 943, 944, 945, 946, 947, 948, 949, 950, 951, 952, 953, 954, 1050
1051, 1052, 1053, 1054, 1055, 1056, 1057, 1058, 1059, 1060, 1061, 1062, 1063, 1064, 1065, 1066
1067, 1068, 1164, 1165, 1166, 1167, 1168, 1169, 1170, 1171, 1172, 1173, 1174, 1175, 1176, 1177
1178, 1179, 1180, 1181, 1182, 1278, 1279, 1280, 1281, 1282, 1283, 1284, 1285, 1286, 1287, 1288
1289, 1290, 1291, 1292, 1293, 1294, 1295, 1296, 1392, 1393, 1394, 1395, 1396, 1397, 1398, 1399
1400, 1401, 1402, 1403, 1404, 1405, 1406, 1407, 1408, 1409, 1410, 1506, 1507, 1508, 1509, 1510
1511, 1512, 1513, 1514, 1515, 1516, 1517, 1518, 1519, 1520, 1521, 1522, 1523, 1524, 1620, 1621
1622, 1623, 1624, 1625, 1626, 1627, 1628, 1629, 1630, 1631, 1632, 1633, 1634, 1635, 1636, 1637
1638, 1734, 1735, 1736, 1737, 1738, 1739, 1740, 1741, 1742, 1743, 1744, 1745, 1746, 1747, 1748
1749, 1750, 1751, 1752, 1833, 1834, 1835, 1836, 1837, 1838, 1839, 1840, 1841, 1842, 1843, 1844
1845, 1846, 1847, 1848, 1929, 1930, 1931, 1932, 1933, 1934, 1935, 1936, 1937, 1938, 1939, 1940
1941, 1942, 1943, 1944, 2025, 2026, 2027, 2028, 2029, 2030, 2031, 2032, 2033, 2034, 2035, 2036
2037, 2038, 2039, 2040, 2121, 2122, 2123, 2124, 2125, 2126, 2127, 2128, 2129, 2130, 2131, 2132
2133, 2134, 2135, 2136, 4353, 4354, 4355, 4356, 4357, 4358, 4359, 4360, 4361, 4362, 4363, 4364
4365, 4366, 4367, 4368, 4449, 4450, 4451, 4452, 4453, 4454, 4455, 4456, 4457, 4458, 4459, 4460
4461, 4462, 4463, 4464, 4560, 4561, 4562, 4563, 4564, 4565, 4566, 4567, 4568, 4569, 4570, 4571
4572, 4573, 4574, 4575, 4576, 4577, 4578, 4674, 4675, 4676, 4677, 4678, 4679, 4680, 4681, 4682
4683, 4684, 4685, 4686, 4687, 4688, 4689, 4690, 4691, 4692, 4788, 4789, 4790, 4791, 4792, 4793
4794, 4795, 4796, 4797, 4798, 4799, 4800, 4801, 4802, 4803, 4804, 4805, 4806, 4902, 4903, 4904
4905, 4906, 4907, 4908, 4909, 4910, 4911, 4912, 4913, 4914, 4915, 4916, 4917, 4918, 4919, 4920
5016, 5017, 5018, 5019, 5020, 5021, 5022, 5023, 5024, 5025, 5026, 5027, 5028, 5029, 5030, 5031
5032, 5033, 5034, 5130, 5131, 5132, 5133, 5134, 5135, 5136, 5137, 5138, 5139, 5140, 5141, 5142
5143, 5144, 5145, 5146, 5147, 5148, 5244, 5245, 5246, 5247, 5248, 5249, 5250, 5251, 5252, 5253
5254, 5255, 5256, 5257, 5258, 5259, 5260, 5261, 5262, 5358, 5359, 5360, 5361, 5362, 5363, 5364
5365, 5366, 5367, 5368, 5369, 5370, 5371, 5372, 5373, 5374, 5375, 5376, 5472, 5473, 5474, 5475
5476, 5477, 5478, 5479, 5480, 5481, 5482, 5483, 5484, 5485, 5486, 5487, 5488, 5489, 5490, 5586
5587, 5588, 5589, 5590, 5591, 5592, 5593, 5594, 5595, 5596, 5597, 5598, 5599, 5600, 5601, 5602
5603, 5604, 5700, 5701, 5702, 5703, 5704, 5705, 5706, 5707, 5708, 5709, 5710, 5711, 5712, 5713
5714, 5715, 5716, 5717, 5718, 5814, 5815, 5816, 5817, 5818, 5819, 5820, 5821, 5822, 5823, 5824
5825, 5826, 5827, 5828, 5829, 5830, 5831, 5832, 5913, 5914, 5915, 5916, 5917, 5918, 5919, 5920
5921, 5922, 5923, 5924, 5925, 5926, 5927, 5928, 6009, 6010, 6011, 6012, 6013, 6014, 6015, 6016
6017, 6018, 6019, 6020, 6021, 6022, 6023, 6024, 7857, 7858, 7859, 7860, 7861, 7862, 7863, 7864
7865, 7866, 7867, 7868, 7869, 7870, 7871, 7872, 7953, 7954, 7955, 7956, 7957, 7958, 7959, 7960
7961, 7962, 7963, 7964, 7965, 7966, 7967, 7968, 8064, 8065, 8066, 8067, 8068, 8069, 8070, 8071
8072, 8073, 8074, 8075, 8076, 8077, 8078, 8079, 8080, 8081, 8082, 8178, 8179, 8180, 8181, 8182
8183, 8184, 8185, 8186, 8187, 8188, 8189, 8190, 8191, 8192, 8193, 8194, 8195, 8196, 8292, 8293
8294, 8295, 8296, 8297, 8298, 8299, 8300, 8301, 8302, 8303, 8304, 8305, 8306, 8307, 8308, 8309
8310, 8406, 8407, 8408, 8409, 8410, 8411, 8412, 8413, 8414, 8415, 8416, 8417, 8418, 8419, 8420
8421, 8422, 8423, 8424, 8520, 8521, 8522, 8523, 8524, 8525, 8526, 8527, 8528, 8529, 8530, 8531
8532, 8533, 8534, 8535, 8536, 8537, 8538, 8634, 8635, 8636, 8637, 8638, 8639, 8640, 8641, 8642
8643, 8644, 8645, 8646, 8647, 8648, 8649, 8650, 8651, 8652, 8748, 8749, 8750, 8751, 8752, 8753
8754, 8755, 8756, 8757, 8758, 8759, 8760, 8761, 8762, 8763, 8764, 8765, 8766, 8862, 8863, 8864
8865, 8866, 8867, 8868, 8869, 8870, 8871, 8872, 8873, 8874, 8875, 8876, 8877, 8878, 8879, 8880
8976, 8977, 8978, 8979, 8980, 8981, 8982, 8983, 8984, 8985, 8986, 8987, 8988, 8989, 8990, 8991
8992, 8993, 8994, 9090, 9091, 9092, 9093, 9094, 9095, 9096, 9097, 9098, 9099, 9100, 9101, 9102
9103, 9104, 9105, 9106, 9107, 9108, 9204, 9205, 9206, 9207, 9208, 9209, 9210, 9211, 9212, 9213
9214, 9215, 9216, 9217, 9218, 9219, 9220, 9221, 9222, 9318, 9319, 9320, 9321, 9322, 9323, 9324
9325, 9326, 9327, 9328, 9329, 9330, 9331, 9332, 9333, 9334, 9335, 9336, 9417, 9418, 9419, 9420
9421, 9422, 9423, 9424, 9425, 9426, 9427, 9428, 9429, 9430, 9431, 9432, 9513, 9514, 9515, 9516
9517, 9518, 9519, 9520, 9521, 9522, 9523, 9524, 9525, 9526, 9527, 9528, 11361, 11362, 11363, 11364
11365, 11366, 11367, 11368, 11369, 11370, 11371, 11372, 11373, 11374, 11375, 11376, 11457, 11458, 11459, 11460
11461, 11462, 11463, 11464, 11465, 11466, 11467, 11468, 11469, 11470, 11471, 11472, 11553, 11554, 11555, 11556
11557, 11558, 11559, 11560, 11561, 11562, 11563, 11564, 11565, 11566, 11567, 11568, 11649, 11650, 11651, 11652
11653, 11654, 11655, 11656, 11657, 11658, 11659, 11660, 11661, 11662, 11663, 11664, 11760, 11761, 11762, 11763
11764, 11765, 11766, 11767, 11768, 11769, 11770, 11771, 11772, 11773, 11774, 11775, 11776, 11777, 11778, 11874
11875, 11876, 11877, 11878, 11879, 11880, 11881, 11882, 11883, 11884, 11885, 11886, 11887, 11888, 11889, 11890
11891, 11892, 11988, 11989, 11990, 11991, 11992, 11993, 11994, 11995, 11996, 11997, 11998, 11999, 12000, 12001
12002, 12003, 12004, 12005, 12006, 12102, 12103, 12104, 12105, 12106, 12107, 12108, 12109, 12110, 12111, 12112
12113, 12114, 12115, 12116, 12117, 12118, 12119, 12120, 12216, 12217, 12218, 12219, 12220, 12221, 12222, 12223
12224, 12225, 12226, 12227, 12228, 12229, 12230, 12231, 12232, 12233, 12234, 12330, 12331, 12332, 12333, 12334
12335, 12336, 12337, 12338, 12339, 12340, 12341, 12342, 12343, 12344, 12345, 12346, 12347, 12348, 12444, 12445
12446, 12447, 12448, 12449, 12450, 12451, 12452, 12453, 12454, 12455, 12456, 12457, 12458, 12459, 12460, 12461
12462, 12558, 12559, 12560, 12561, 12562, 12563, 12564, 12565, 12566, 12567, 12568, 12569, 12570, 12571, 12572
12573, 12574, 12575, 12576, 12672, 12673, 12674, 12675, 12676, 12677, 12678, 12679, 12680, 12681, 12682, 12683
12684, 12685, 12686, 12687, 12688, 12689, 12690, 12786, 12787, 12788, 12789, 12790, 12791, 12792, 12793, 12794
12795, 12796, 12797, 12798, 12799, 12800, 12801, 12802, 12803, 12804, 12900, 12901, 12902, 12903, 12904, 12905
12906, 12907, 12908, 12909, 12910, 12911, 12912, 12913, 12914, 12915, 12916, 12917, 12918, 13014, 13015, 13016
13017, 13018, 13019, 13020, 13021, 13022, 13023, 13024, 13025, 13026, 13027, 13028, 13029, 13030, 13031, 13032
13113, 13114, 13115, 13116, 13117, 13118, 13119, 13120, 13121, 13122, 13123, 13124, 13125, 13126, 13127, 13128
13209, 13210, 13211, 13212, 13213, 13214, 13215, 13216, 13217, 13218, 13219, 13220, 13221, 13222, 13223, 13224
13305, 13306, 13307, 13308, 13309, 13310, 13311, 13312, 13313, 13314, 13315, 13316, 13317, 13318, 13319, 13320
13401, 13402, 13403, 13404, 13405, 13406, 13407, 13408, 13409, 13410, 13411, 13412, 13413, 13414, 13415, 13416
15249, 15250, 15251, 15252, 15253, 15254, 15255, 15256, 15257, 15258, 15259, 15260, 15261, 15262, 15263, 15264
15345, 15346, 15347, 15348, 15349, 15350, 15351, 15352, 15353, 15354, 15355, 15356, 15357, 15358, 15359, 15360
15441, 15442, 15443, 15444, 15445, 15446, 15447, 15448, 15449, 15450, 15451, 15452, 15453, 15454, 15455, 15456
15537, 15538, 15539, 15540, 15541, 15542, 15543, 15544, 15545, 15546, 15547, 15548, 15549, 15550, 15551, 15552
15648, 15649, 15650, 15651, 15652, 15653, 15654, 15655, 15656, 15657, 15658, 15659, 15660, 15661, 15662, 15663
15664, 15665, 15666, 15762, 15763, 15764, 15765, 15766, 15767, 15768, 15769, 15770, 15771, 15772, 15773, 15774
15775, 15776, 15777, 15778, 15779, 15780, 15876, 15877, 15878, 15879, 15880, 15881, 15882, 15883, 15884, 15885
15886, 15887, 15888, 15889, 15890, 15891, 15892, 15893, 15894, 15990, 15991, 15992, 15993, 15994, 15995, 15996
15997, 15998, 15999, 16000, 16001, 16002, 16003, 16004, 16005, 16006, 16007, 16008, 16104, 16105, 16106, 16107
16108, 16109, 16110, 16111, 16112, 16113, 16114, 16115, 16116, 16117, 16118, 16119, 16120, 16121, 16122, 16218
16219, 16220, 16221, 16222, 16223, 16224, 16225, 16226, 16227, 16228, 16229, 16230, 16231, 16232, 16233, 16234
16235, 16236, 16332, 16333, 16334, 16335, 16336, 16337, 16338, 16339, 16340, 16341, 16342, 16343, 16344, 16345
16346, 16347, 16348, 16349, 16350, 16446, 16447, 16448, 16449, 16450, 16451, 16452, 16453, 16454, 16455, 16456
16457, 16458, 16459, 16460, 16461, 16462, 16463, 16464, 16560, 16561, 16562, 16563, 16564, 16565, 16566, 16567
16568, 16569, 16570, 16571, 16572, 16573, 16574, 16575, 16576, 16577, 16578, 16674, 16675, 16676, 16677, 16678
16679, 16680, 16681, 16682, 16683, 16684, 16685, 16686, 16687, 16688, 16689, 16690, 16691, 16692, 16788, 16789
16790, 16791, 16792, 16793, 16794, 16795, 16796, 16797, 16798, 16799, 16800, 16801, 16802, 16803, 16804, 16805
16806, 16902, 16903, 16904, 16905, 16906, 16907, 16908, 16909, 16910, 16911, 16912, 16913, 16914, 16915, 16916
16917, 16918, 16919, 16920, 17001, 17002, 17003, 17004, 17005, 17006, 17007, 17008, 17009, 17010, 17011, 17012
17013, 17014, 17015, 17016, 17097, 17098, 17099, 17100, 17101, 17102, 17103, 17104, 17105, 17106, 17107, 17108
17109, 17110, 17111, 17112, 17193, 17194, 17195, 17196, 17197, 17198, 17199, 17200, 17201, 17202, 17203, 17204
17205, 17206, 17207, 17208, 17289, 17290, 17291, 17292, 17293, 17294, 17295, 17296, 17297, 17298, 17299, 17300
17301, 17302, 17303, 17304, 19521, 19522, 19523, 19524, 19525, 19526, 19527, 19528, 19529, 19530, 19531, 19532
19533, 19534, 19535, 19536, 19617, 19618, 19619, 19620, 19621, 19622, 19623, 19624, 19625, 19626, 19627, 19628
19629, 19630, 19631, 19632, 19728, 19729, 19730, 19731, 19732, 19733, 19734, 19735, 19736, 19737, 19738, 19739
19740, 19741, 19742, 19743, 19744, 19745, 19746, 19842, 19843, 19844, 19845, 19846, 19847, 19848, 19849, 19850
19851, 19852, 19853, 19854, 19855, 19856, 19857, 19858, 19859, 19860, 19956, 19957, 19958, 19959, 19960, 19961
19962, 19963, 19964, 19965, 19966, 19967, 19968, 19969, 19970, 19971, 19972, 19973, 19974, 20070, 20071, 20072
20073, 20074, 20075, 20076, 20077, 20078, 20079, 20080, 20081, 20082, 20083, 20084, 20085, 20086, 20087, 20088
20184, 20185, 20186, 20187, 20188, 20189, 20190, 20191, 20192, 20193, 20194, 20195, 20196, 20197, 20198, 20199
20200, 20201, 20202, 20298, 20299, 20300, 20301, 20302, 20303, 20304, 20305, 20306, 20307, 20308, 20309, 20310
20311, 20312, 20313, 20314, 20315, 20316, 20412, 20413, 20414, 20415, 20416, 20417, 20418, 20419, 20420, 20421
20422, 20423, 20424, 20425, 20426, 20427, 20428, 20429, 20430, 20526, 20527, 20528, 20529, 20530, 20531, 20532
20533, 20534, 20535, 20536, 20537, 20538, 20539, 20540, 20541, 20542, 20543, 20544, 20640, 20641, 20642, 20643
20644, 20645, 20646, 20647, 20648, 20649, 20650, 20651, 20652, 20653, 20654, 20655, 20656, 20657, 20658, 20754
20755, 20756, 20757, 20758, 20759, 20760, 20761, 20762, 20763, 20764, 20765, 20766, 20767, 20768, 20769, 20770
20771, 20772, 20868, 20869, 20870, 20871, 20872, 20873, 20874, 20875, 20876, 20877, 20878, 20879, 20880, 20881
20882, 20883, 20884, 20885, 20886, 20982, 20983, 20984, 20985, 20986, 20987, 20988, 20989, 20990, 20991, 20992
20993, 20994, 20995, 20996, 20997, 20998, 20999, 21000, 21081, 21082, 21083, 21084, 21085, 21086, 21087, 21088
21089, 21090, 21091, 21092, 21093, 21094, 21095, 21096, 21177, 21178, 21179, 21180, 21181, 21182, 21183, 21184
21185, 21186, 21187, 21188, 21189, 21190, 21191, 21192, 25560, 25561, 25562, 25563, 25564, 25565, 25566, 25567
25568, 25569, 25570, 25571, 25572, 25573, 25574, 25575, 25576, 25577, 25578, 25674, 25675, 25676, 25677, 25678
25679, 25680, 25681, 25682, 25683, 25684, 25685, 25686, 25687, 25688, 25689, 25690, 25691, 25692, 25788, 25789
25790, 25791, 25792, 25793, 25794, 25795, 25796, 25797, 25798, 25799, 25800, 25801, 25802, 25803, 25804, 25805
25806, 25902, 25903, 25904, 25905, 25906, 25907, 25908, 25909, 25910, 25911, 25912, 25913, 25914, 25915, 25916
25917, 25918, 25919, 25920, 26016, 26017, 26018, 26019, 26020, 26021, 26022, 26023, 26024, 26025, 26026, 26027
26028, 26029, 26030, 26031, 26032, 26033, 26034, 26130, 26131, 26132, 26133, 26134, 26135, 26136, 26137, 26138
26139, 26140, 26141, 26142, 26143, 26144, 26145, 26146, 26147, 26148, 26244, 26245, 26246, 26247, 26248, 26249
26250, 26251, 26252, 26253, 26254, 26255, 26256, 26257, 26258, 26259, 26260, 26261, 26262, 26358, 26359, 26360
26361, 26362, 26363, 26364, 26365, 26366, 26367, 26368, 26369, 26370, 26371, 26372, 26373, 26374, 26375, 26376
26472, 26473, 26474, 26475, 26476, 26477, 26478, 26479, 26480, 26481, 26482, 26483, 26484, 26485, 26486, 26487
26488, 26489, 26490, 26586, 26587, 26588, 26589, 26590, 26591, 26592, 26593, 26594, 26595, 26596, 26597, 26598
26599, 26600, 26601, 26602, 26603, 26604, 26700, 26701, 26702, 26703, 26704, 26705, 26706, 26707, 26708, 26709
26710, 26711, 26712, 26713, 26714, 26715, 26716, 26717, 26718, 26814, 26815, 26816, 26817, 26818, 26819, 26820
26821, 26822, 26823, 26824, 26825, 26826, 26827, 26828, 26829, 26830, 26831, 26832, 29256, 29257, 29258, 29259
29260, 29261, 29262, 29263, 29264, 29265, 29266, 29267, 29268, 29269, 29270, 29271, 29272, 29273, 29274, 29370
29371, 29372, 29373, 29374, 29375, 29376, 29377, 29378, 29379, 29380, 29381, 29382, 29383, 29384, 29385, 29386
29387, 29388, 29484, 29485, 29486, 29487, 29488, 29489, 29490, 29491, 29492, 29493, 29494, 29495, 29496, 29497
29498, 29499, 29500, 29501, 29502, 29598, 29599, 29600, 29601, 29602, 29603, 29604, 29605, 29606, 29607, 29608
29609, 29610, 29611, 29612, 29613, 29614, 29615, 29616, 29712, 29713, 29714, 29715, 29716, 29717, 29718, 29719
29720, 29721, 29722, 29723, 29724, 29725, 29726, 29727, 29728, 29729, 29730, 29826, 29827, 29828, 29829, 29830
29831, 29832, 29833, 29834, 29835, 29836, 29837, 29838, 29839, 29840, 29841, 29842, 29843, 29844, 29940, 29941
29942, 29943, 29944, 29945, 29946, 29947, 29948, 29949, 29950, 29951, 29952, 29953, 29954, 29955, 29956, 29957
29958, 30054, 30055, 30056, 30057, 30058, 30059, 30060, 30061, 30062, 30063, 30064, 30065, 30066, 30067, 30068
30069, 30070, 30071, 30072, 30168, 30169, 30170, 30171, 30172, 30173, 30174, 30175, 30176, 30177, 30178, 30179
30180, 30181, 30182, 30183, 30184, 30185, 30186, 30282, 30283, 30284, 30285, 30286, 30287, 30288, 30289, 30290
30291, 30292, 30293, 30294, 30295, 30296, 30297, 30298, 30299, 30300, 30396, 30397, 30398, 30399, 30400, 30401
30402, 30403, 30404, 30405, 30406, 30407, 30408, 30409, 30410, 30411, 30412, 30413, 30414, 30510, 30511, 30512
30513, 30514, 30515, 30516, 30517, 30518, 30519, 30520, 30521, 30522, 30523, 30524, 30525, 30526, 30527, 30528
32760, 32761, 32762, 32763, 32764, 32765, 32766, 32767, 32768, 32769, 32770, 32771, 32772, 32773, 32774, 32775
32776, 32777, 32778, 32874, 32875, 32876, 32877, 32878, 32879, 32880, 32881, 32882, 32883, 32884, 32885, 32886
32887, 32888, 32889, 32890, 32891, 32892, 32988, 32989, 32990, 32991, 32992, 32993, 32994, 32995, 32996, 32997
32998, 32999, 33000, 33001, 33002, 33003, 33004, 33005, 33006, 33102, 33103, 33104, 33105, 33106, 33107, 33108
33109, 33110, 33111, 33112, 33113, 33114, 33115, 33116, 33117, 33118, 33119, 33120, 33216, 33217, 33218, 33219
33220, 33221, 33222, 33223, 33224, 33225, 33226, 33227, 33228, 33229, 33230, 33231, 33232, 33233, 33234, 33330
33331, 33332, 33333, 33334, 33335, 33336, 33337, 33338, 33339, 33340, 33341, 33342, 33343, 33344, 33345, 33346
33347, 33348, 33444, 33445, 33446, 33447, 33448, 33449, 33450, 33451, 33452, 33453, 33454, 33455, 33456, 33457
33458, 33459, 33460, 33461, 33462, 33558, 33559, 33560, 33561, 33562, 33563, 33564, 33565, 33566, 33567, 33568
33569, 33570, 33571, 33572, 33573, 33574, 33575, 33576, 33672, 33673, 33674, 33675, 33676, 33677, 33678, 33679
33680, 33681, 33682, 33683, 33684, 33685, 33686, 33687, 33688, 33689, 33690, 33786, 33787, 33788, 33789, 33790
33791, 33792, 33793, 33794, 33795, 33796, 33797, 33798, 33799, 33800, 33801, 33802, 33803, 33804, 33900, 33901
33902, 33903, 33904, 33905, 33906, 33907, 33908, 33909, 33910, 33911, 33912, 33913, 33914, 33915, 33916, 33917
33918, 34014, 34015, 34016, 34017, 34018, 34019, 34020, 34021, 34022, 34023, 34024, 34025, 34026, 34027, 34028
34029, 34030, 34031, 34032, 36648, 36649, 36650, 36651, 36652, 36653, 36654, 36655, 36656, 36657, 36658, 36659
36660, 36661, 36662, 36663, 36664, 36665, 36666, 36762, 36763, 36764, 36765, 36766, 36767, 36768, 36769, 36770
36771, 36772, 36773, 36774, 36775, 36776, 36777, 36778, 36779, 36780, 36876, 36877, 36878, 36879, 36880, 36881
36882, 36883, 36884, 36885, 36886, 36887, 36888, 36889, 36890, 36891, 36892, 36893, 36894, 36990, 36991, 36992
36993, 36994, 36995, 36996, 36997, 36998, 36999, 37000, 37001, 37002, 37003, 37004, 37005, 37006, 37007, 37008
37104, 37105, 37106, 37107, 37108, 37109, 37110, 37111, 37112, 37113, 37114, 37115, 37116, 37117, 37118, 37119
37120, 37121, 37122, 37218, 37219, 37220, 37221, 37222, 37223, 37224, 37225, 37226, 37227, 37228, 37229, 37230
37231, 37232, 37233, 37234, 37235, 37236, 37332, 37333, 37334, 37335, 37336, 37337, 37338, 37339, 37340, 37341
37342, 37343, 37344, 37345, 37346, 37347, 37348, 37349, 37350, 37446, 37447, 37448, 37449, 37450, 37451, 37452
37453, 37454, 37455, 37456, 37457, 37458, 37459, 37460, 37461, 37462, 37463, 37464, 37560, 37561, 37562, 37563
37564, 37565, 37566, 37567, 37568, 37569, 37570, 37571, 37572, 37573, 37574, 37575, 37576, 37577, 37578, 37674
37675, 37676, 37677, 37678, 37679, 37680, 37681, 37682, 37683, 37684, 37685, 37686, 37687, 37688, 37689, 37690
37691, 37692, 37788, 37789, 37790, 37791, 37792, 37793, 37794, 37795, 37796, 37797, 37798, 37799, 37800, 37801
37802, 37803, 37804, 37805, 37806, 37902, 37903, 37904, 37905, 37906, 37907, 37908, 37909, 37910, 37911, 37912
37913, 37914, 37915, 37916, 37917, 37918, 37919, 37920, 40728, 40729, 40730, 40731, 40732, 40733, 40734, 40735
40736, 40737, 40738, 40739, 40740, 40741, 40742, 40743, 40744, 40745, 40746, 40842, 40843, 40844, 40845, 40846
40847, 40848, 40849, 40850, 40851, 40852, 40853, 40854, 40855, 40856, 40857, 40858, 40859, 40860, 40956, 40957
40958, 40959, 40960, 40961, 40962, 40963, 40964, 40965, 40966, 40967, 40968, 40969, 40970, 40971, 40972, 40973
40974, 41070, 41071, 41072, 41073, 41074, 41075, 41076, 41077, 41078, 41079, 41080, 41081, 41082, 41083, 41084
41085, 41086, 41087, 41088, 41184, 41185, 41186, 41187, 41188, 41189, 41190, 41191, 41192, 41193, 41194, 41195
41196, 41197, 41198, 41199, 41200, 41201, 41202, 41298, 41299, 41300, 41301, 41302, 41303, 41304, 41305, 41306
41307, 41308, 41309, 41310, 41311, 41312, 41313, 41314, 41315, 41316, 41412, 41413, 41414, 41415, 41416, 41417
41418, 41419, 41420, 41421, 41422, 41423, 41424, 41425, 41426, 41427, 41428, 41429, 41430, 41526, 41527, 41528
41529, 41530, 41531, 41532, 41533, 41534, 41535, 41536, 41537, 41538, 41539, 41540, 41541, 41542, 41543, 41544
41640, 41641, 41642, 41643, 41644, 41645, 41646, 41647, 41648, 41649, 41650, 41651, 41652, 41653, 41654, 41655
41656, 41657, 41658, 41754, 41755, 41756, 41757, 41758, 41759, 41760, 41761, 41762, 41763, 41764, 41765, 41766
41767, 41768, 41769, 41770, 41771, 41772, 41868, 41869, 41870, 41871, 41872, 41873, 41874, 41875, 41876, 41877
41878, 41879, 41880, 41881, 41882, 41883, 41884, 41885, 41886, 41982, 41983, 41984, 41985, 41986, 41987, 41988
41989, 41990, 41991, 41992, 41993, 41994, 41995, 41996, 41997, 41998, 41999, 42000, 44616, 44617, 44618, 44619
44620, 44621, 44622, 44623, 44624, 44625, 44626, 44627, 44628, 44629, 44630, 44631, 44632, 44633, 44634, 44730
44731, 44732, 44733, 44734, 44735, 44736, 44737, 44738, 44739, 44740, 44741, 44742, 44743, 44744, 44745, 44746
44747, 44748, 44844, 44845, 44846, 44847, 44848, 44849, 44850, 44851, 44852, 44853, 44854, 44855, 44856, 44857
44858, 44859, 44860, 44861, 44862, 44958, 44959, 44960, 44961, 44962, 44963, 44964, 44965, 44966, 44967, 44968
44969, 44970, 44971, 44972, 44973, 44974, 44975, 44976, 45072, 45073, 45074, 45075, 45076, 45077, 45078, 45079
45080, 45081, 45082, 45083, 45084, 45085, 45086, 45087, 45088, 45089, 45090, 45186, 45187, 45188, 45189, 45190
45191, 45192, 45193, 45194, 45195, 45196, 45197, 45198, 45199, 45200, 45201, 45202, 45203, 45204, 45300, 45301
45302, 45303, 45304, 45305, 45306, 45307, 45308, 45309, 45310, 45311, 45312, 45313, 45314, 45315, 45316, 45317
45318, 45414, 45415, 45416, 45417, 45418, 45419, 45420, 45421, 45422, 45423, 45424, 45425, 45426, 45427, 45428
45429, 45430, 45431, 45432, 45528, 45529, 45530, 45531, 45532, 45533, 45534, 45535, 45536, 45537, 45538, 45539
45540, 45541, 45542, 45543, 45544, 45545, 45546, 45642, 45643, 45644, 45645, 45646, 45647, 45648, 45649, 45650
45651, 45652, 45653, 45654, 45655, 45656, 45657, 45658, 45659, 45660, 45756, 45757, 45758, 45759, 45760, 45761
45762, 45763, 45764, 45765, 45766, 45767, 45768, 45769, 45770, 45771, 45772, 45773, 45774, 45870, 45871, 45872
45873, 45874, 45875, 45876, 45877, 45878, 45879, 45880, 45881, 45882, 45883, 45884, 45885, 45886, 45887, 45888
*Surface, type=ELEMENT, name=_PickedSurf53, internal
__PickedSurf53_S1, S1
__PickedSurf53_S2, S2
__PickedSurf53_S3, S3
__PickedSurf53_S5, S5
*Nset, nset="_T-Datum csys-1", internal
_PickedSet48,
_PickedSet49,
Set-1,
Set-2,
*Transform, nset="_T-Datum csys-1", type=C
0., 0., 0., -1., 0., 0.
** Constraint: Constraint-1
*Equation
2
Set-1, 3, 1.
Set-2, 3, -1.
*End Assembly
*Amplitude, name=Amp-2, time=TOTAL TIME, definition=SMOOTH STEP
0., 0., 1., 1., 1.8, 0.85, 1.9, 0.8
2., 0.
*Amplitude, name=Amp-3, definition=SMOOTH STEP
0., 0., 1., 1.
*Amplitude, name=Deploy, time=TOTAL TIME, definition=SMOOTH STEP
0., 0., 1., 1., 1.5, -0.2
**
** MATERIALS
**
*Material, name=Iron
*Density
1e-06,
*Elastic
211000., 0.3
*Plastic
138.09, 0.
231., 0.0481364
308.2, 0.139108
352.5, 0.22249
*Material, name=Magnesium
*Density
1.74e-06,
*Depvar, delete=20
30,
*User Material, constants=6
44000., 0.35, 138.7, 16., 165., 0.025
*Material, name=Plate
*Density
1e-05,
*Elastic
2000., 0.3
*Material, name=Steel
*Density
1e-06,
*Elastic
190000., 0.3
*Plastic
380.76, 0.
605., 0.0933122
804., 0.180324
1050., 0.334474
1140.05, 0.410112
*Material, name=cocr
*Density
1e-06,
*Elastic
243000., 0.3
*Plastic
676.875, 0.
902., 0.0925363
1110., 0.179548
1470., 0.333698
1558.75, 0.36879
*Material, name=plla
*Density
1e-06,
*Elastic
2730., 0.4
*Plastic
16.0938, 0.
29.15, 0.0894665
34.8, 0.176478
39.65, 0.256521
48.98, 0.451581
**
** INTERACTION PROPERTIES
**
*Surface Interaction, name=GeneralProps
*Friction, exponential decay
0.2, 0., 0.
*Surface Behavior, pressure-overclosure=HARD
**
** BOUNDARY CONDITIONS
**
** Name: BC-1 Type: Displacement/Rotation
*Boundary
_PickedSet48, 3, 3
** ----------------------------------------------------------------
**
** STEP: Deploy
**
*Step, name=Deploy
*Dynamic, Explicit
, 1.
*Bulk Viscosity
0.06, 1.2
** Mass Scaling: Semi-Automatic
** Whole Model
*Fixed Mass Scaling, dt=5e-06, type=below min
**
** BOUNDARY CONDITIONS
**
** Name: BC-2 Type: Displacement/Rotation
*Boundary
_PickedSet49, 2, 2
**
** LOADS
**
** Name: Load-1 Type: Pressure
*Dsload, amplitude=Amp-3
_PickedSurf53, P, 2.
**
** INTERACTIONS
**
** Interaction: GeneralProps
*Contact, op=NEW
*Contact Inclusions, ALL EXTERIOR
*Contact Property Assignment
, , GeneralProps
**
** OUTPUT REQUESTS
**
*Restart, write, number interval=5, time marks=NO
**
** FIELD OUTPUT: F-Output-1
**
*Output, field, number interval=100
*Node Output
A, RF, U, V
*Element Output, directions=YES
LE, PE, PEEQ, S, SDV, STATUS
*Contact Output
CSTRESS,
**
** HISTORY OUTPUT: H-Output-1
**
*Output, history, variable=PRESELECT
*End Step

View file

@ -0,0 +1,875 @@
*Heading
** Job name: Press_Iron Model name: Model-1
** Generated by: Abaqus/CAE 6.10-1
*Preprint, echo=NO, model=NO, history=NO, contact=NO
**
** PARTS
**
**
** ASSEMBLY
**
*Assembly, name=Assembly
**
*Instance, library=Full_Iron, instance=Stent
**
** PREDEFINED FIELD
**
** Name: Predefined Field-1 Type: Initial State
*Import, state=yes, update=no
*End Instance
**
*Nset, nset=_PickedSet48, internal, instance=Stent
337, 338, 339, 340, 381, 382, 383, 384, 425, 426, 427, 428, 469, 470, 471, 472
513, 514, 515, 516, 557, 558, 559, 560, 5663, 5664, 5665, 5666, 5667, 5698, 5699, 5700
5701, 5702, 5703, 5704, 5705, 5706, 5707, 5708, 6360, 6361, 6362, 6363, 6364, 6395, 6396, 6397
6398, 6399, 6415, 6416, 7083, 7084, 7085, 7086, 7087, 7118, 7119, 7120, 7121, 7122, 7123, 7124
7784, 7785, 7786, 7787, 7788, 7819, 7820, 7821, 7822, 7823, 7839, 7840, 8523, 8524, 8525, 8526
8527, 8558, 8559, 8560, 8561, 8562, 8563, 8564, 8565, 8566, 8567, 8568, 9228, 9229, 9230, 9231
9232, 9263, 9264, 9265, 9266, 9267, 9283, 9284, 9285, 9286, 9287, 9288, 29141, 29142, 29143, 29144
29145, 29146, 29147, 29148, 29149, 29150, 29151, 29152, 29153, 29154, 29155, 31546, 31547, 31548, 31549, 31550
33881, 33882, 33883, 33884, 33885, 36356, 36357, 36358, 36359, 36360, 38911, 38912, 38913, 38914, 38915, 38916
38917, 38918, 38919, 38920, 38921, 38922, 38923, 38924, 38925, 41396, 41397, 41398, 41399, 41400, 41401, 41402
41403, 41404, 41405, 41406, 41407, 41408, 41409, 41410
*Nset, nset=_PickedSet49, internal, instance=Stent
5704, 5707, 6415, 6416, 7124, 7839, 7840, 8564, 8567, 9284, 9287, 29146, 29147, 29148, 29149, 29150
31546, 31547, 31548, 31549, 31550, 33881, 33882, 33883, 33884, 33885, 36356, 36357, 36358, 36359, 36360, 38916
38917, 38918, 38919, 38920, 41401, 41402, 41403, 41404, 41405, 50745
*Nset, nset=Set-1, instance=Stent
49, 50, 51, 52, 97, 98, 99, 100, 145, 146, 147, 148, 193, 194, 195, 196
241, 242, 243, 244, 289, 290, 291, 292, 1264, 1265, 1266, 1267, 1268, 1299, 1300, 1301
1302, 1303, 1319, 1320, 1321, 1322, 1323, 1324, 2003, 2004, 2005, 2006, 2007, 2038, 2039, 2040
2041, 2042, 2043, 2044, 2708, 2709, 2710, 2711, 2712, 2743, 2744, 2745, 2746, 2747, 2763, 2764
3455, 3456, 3457, 3458, 3459, 3490, 3491, 3492, 3493, 3494, 3495, 3496, 4180, 4181, 4182, 4183
4184, 4215, 4216, 4217, 4218, 4219, 4235, 4236, 4237, 4238, 4239, 4240, 4919, 4920, 4921, 4922
4923, 4954, 4955, 4956, 4957, 4958, 4959, 4960, 14341, 14342, 14343, 14344, 14345, 14346, 14347, 14349
14350, 14351, 14352, 14353, 14354, 14355, 16751, 16752, 16753, 16754, 16755, 19091, 19092, 19093, 19094, 19095
21581, 21582, 21583, 21584, 21585, 24151, 24152, 24153, 24154, 24155, 24156, 24157, 24158, 24159, 24160, 24161
24162, 24163, 24164, 24165, 26561, 26562, 26563, 26564, 26565
*Nset, nset=Set-2, instance=Stent
14348,
*Elset, elset=__PickedSurf53_S1, internal, instance=Stent
46273, 46274, 46275, 46276, 46277, 46278, 46279, 46280, 46281, 46282, 46283, 46284, 46285, 46286, 46287, 46288
46289, 46290, 46291, 46292, 46293, 46294, 46295, 46296, 46297, 46298, 46299, 46300, 46301, 46302, 46303, 46304
46305, 46306, 46307, 46308, 46309, 46310, 46311, 46312, 46313, 46314, 46315, 46316, 46317, 46318, 46319, 46320
46321, 46322, 46323, 46324, 46325, 46326, 46327, 46328, 46329, 46330, 46331, 46332, 46333, 46334, 46335, 46336
46337, 46338, 46339, 46340, 46341, 46342, 46343, 46344, 46345, 46346, 46347, 46348, 46349, 46350, 46351, 46352
46353, 46354, 46355, 46356, 46357, 46358, 46359, 46360, 46361, 46362, 46363, 46364, 46365, 46366, 46367, 46368
46369, 46370, 46371, 46372, 46373, 46374, 46375, 46376, 46377, 46378, 46379, 46380, 46381, 46382, 46383, 46384
46385, 46386, 46387, 46388, 46389, 46390, 46391, 46392, 46393, 46394, 46395, 46396, 46397, 46398, 46399, 46400
46401, 46402, 46403, 46404, 46405, 46406, 46407, 46408, 46409, 46410, 46411, 46412, 46413, 46414, 46415, 46416
46417, 46418, 46419, 46420, 46421, 46422, 46423, 46424, 46425, 46426, 46427, 46428, 46429, 46430, 46431, 46432
46433, 46434, 46435, 46436, 46437, 46438, 46439, 46440, 46441, 46442, 46443, 46444, 46445, 46446, 46447, 46448
46449, 46450, 46451, 46452, 48433, 48434, 48435, 48436, 48437, 48438, 48439, 48440, 48441, 48442, 48443, 48444
48445, 48446, 48447, 48448, 48449, 48450, 48451, 48452, 48453, 48454, 48455, 48456, 48457, 48458, 48459, 48460
48461, 48462, 48463, 48464, 48465, 48466, 48467, 48468, 48469, 48470, 48471, 48472, 48473, 48474, 48475, 48476
48477, 48478, 48479, 48480, 48481, 48482, 48483, 48484, 48485, 48486, 48487, 48488, 48489, 48490, 48491, 48492
48493, 48494, 48495, 48496, 48497, 48498, 48499, 48500, 48501, 48502, 48503, 48504, 48505, 48506, 48507, 48508
48509, 48510, 48511, 48512, 48513, 48514, 48515, 48516, 48517, 48518, 48519, 48520, 48521, 48522, 48523, 48524
48525, 48526, 48527, 48528, 48529, 48530, 48531, 48532, 48533, 48534, 48535, 48536, 48537, 48538, 48539, 48540
48541, 48542, 48543, 48544, 48545, 48546, 48547, 48548, 48549, 48550, 48551, 48552, 48553, 48554, 48555, 48556
48557, 48558, 48559, 48560, 48561, 48562, 48563, 48564, 48565, 48566, 48567, 48568, 48569, 48570, 48571, 48572
48573, 48574, 48575, 48576, 48577, 48578, 48579, 48580, 48581, 48582, 48583, 48584, 48585, 48586, 48587, 48588
48589, 48590, 48591, 48592, 48593, 48594, 48595, 48596, 48597, 48598, 48599, 48600, 50449, 50450, 50451, 50452
50453, 50454, 50455, 50456, 50457, 50458, 50459, 50460, 50461, 50462, 50463, 50464, 50465, 50466, 50467, 50468
50469, 50470, 50471, 50472, 50473, 50474, 50475, 50476, 50477, 50478, 50479, 50480, 50481, 50482, 50483, 50484
50485, 50486, 50487, 50488, 50489, 50490, 50491, 50492, 50493, 50494, 50495, 50496, 50497, 50498, 50499, 50500
50501, 50502, 50503, 50504, 50505, 50506, 50507, 50508, 50509, 50510, 50511, 50512, 50513, 50514, 50515, 50516
50517, 50518, 50519, 50520, 50521, 50522, 50523, 50524, 50525, 50526, 50527, 50528, 50529, 50530, 50531, 50532
50533, 50534, 50535, 50536, 50537, 50538, 50539, 50540, 50541, 50542, 50543, 50544, 50545, 50546, 50547, 50548
50549, 50550, 50551, 50552, 50553, 50554, 50555, 50556, 50557, 50558, 50559, 50560, 50561, 50562, 50563, 50564
50565, 50566, 50567, 50568, 50569, 50570, 50571, 50572, 50573, 50574, 50575, 50576, 50577, 50578, 50579, 50580
50581, 50582, 50583, 50584, 50585, 50586, 50587, 50588, 50589, 50590, 50591, 50592, 50593, 50594, 50595, 50596
50597, 50598, 50599, 50600, 50601, 50602, 50603, 50604, 50605, 50606, 50607, 50608, 50609, 50610, 50611, 50612
50613, 50614, 50615, 50616, 52465, 52466, 52467, 52468, 52469, 52470, 52471, 52472, 52473, 52474, 52475, 52476
52477, 52478, 52479, 52480, 52481, 52482, 52483, 52484, 52485, 52486, 52487, 52488, 52489, 52490, 52491, 52492
52493, 52494, 52495, 52496, 52497, 52498, 52499, 52500, 52501, 52502, 52503, 52504, 52505, 52506, 52507, 52508
52509, 52510, 52511, 52512, 52513, 52514, 52515, 52516, 52517, 52518, 52519, 52520, 52521, 52522, 52523, 52524
52525, 52526, 52527, 52528, 52529, 52530, 52531, 52532, 52533, 52534, 52535, 52536, 52537, 52538, 52539, 52540
52541, 52542, 52543, 52544, 52545, 52546, 52547, 52548, 52549, 52550, 52551, 52552, 52553, 52554, 52555, 52556
52557, 52558, 52559, 52560, 52561, 52562, 52563, 52564, 52565, 52566, 52567, 52568, 52569, 52570, 52571, 52572
52573, 52574, 52575, 52576, 52577, 52578, 52579, 52580, 52581, 52582, 52583, 52584, 52585, 52586, 52587, 52588
52589, 52590, 52591, 52592, 52593, 52594, 52595, 52596, 52597, 52598, 52599, 52600, 52601, 52602, 52603, 52604
52605, 52606, 52607, 52608, 52609, 52610, 52611, 52612, 52613, 52614, 52615, 52616, 52617, 52618, 52619, 52620
52621, 52622, 52623, 52624, 52625, 52626, 52627, 52628, 52629, 52630, 52631, 52632, 52633, 52634, 52635, 52636
52637, 52638, 52639, 52640, 52641, 52642, 52643, 52644, 54553, 54554, 54555, 54556, 54557, 54558, 54559, 54560
54561, 54562, 54563, 54564, 54565, 54566, 54567, 54568, 54569, 54570, 54571, 54572, 54573, 54574, 54575, 54576
54577, 54578, 54579, 54580, 54581, 54582, 54583, 54584, 54585, 54586, 54587, 54588, 54589, 54590, 54591, 54592
54593, 54594, 54595, 54596, 54597, 54598, 54599, 54600, 54601, 54602, 54603, 54604, 54605, 54606, 54607, 54608
54609, 54610, 54611, 54612, 54613, 54614, 54615, 54616, 54617, 54618, 54619, 54620, 54621, 54622, 54623, 54624
54625, 54626, 54627, 54628, 54629, 54630, 54631, 54632, 54633, 54634, 54635, 54636, 54637, 54638, 54639, 54640
54641, 54642, 54643, 54644, 54645, 54646, 54647, 54648, 54649, 54650, 54651, 54652, 54653, 54654, 54655, 54656
54657, 54658, 54659, 54660, 54661, 54662, 54663, 54664, 54665, 54666, 54667, 54668, 54669, 54670, 54671, 54672
54673, 54674, 54675, 54676, 54677, 54678, 54679, 54680, 54681, 54682, 54683, 54684, 54685, 54686, 54687, 54688
54689, 54690, 54691, 54692, 54693, 54694, 54695, 54696, 54697, 54698, 54699, 54700, 54701, 54702, 54703, 54704
54705, 54706, 54707, 54708, 54709, 54710, 54711, 54712, 54713, 54714, 54715, 54716, 54717, 54718, 54719, 54720
54721, 54722, 54723, 54724, 54725, 54726, 54727, 54728, 54729, 54730, 54731, 54732, 56713, 56714, 56715, 56716
56717, 56718, 56719, 56720, 56721, 56722, 56723, 56724, 56725, 56726, 56727, 56728, 56729, 56730, 56731, 56732
56733, 56734, 56735, 56736, 56737, 56738, 56739, 56740, 56741, 56742, 56743, 56744, 56745, 56746, 56747, 56748
56749, 56750, 56751, 56752, 56753, 56754, 56755, 56756, 56757, 56758, 56759, 56760, 56761, 56762, 56763, 56764
56765, 56766, 56767, 56768, 56769, 56770, 56771, 56772, 56773, 56774, 56775, 56776, 56777, 56778, 56779, 56780
56781, 56782, 56783, 56784, 56785, 56786, 56787, 56788, 56789, 56790, 56791, 56792, 56793, 56794, 56795, 56796
56797, 56798, 56799, 56800, 56801, 56802, 56803, 56804, 56805, 56806, 56807, 56808, 56809, 56810, 56811, 56812
56813, 56814, 56815, 56816, 56817, 56818, 56819, 56820, 56821, 56822, 56823, 56824, 56825, 56826, 56827, 56828
56829, 56830, 56831, 56832, 56833, 56834, 56835, 56836, 56837, 56838, 56839, 56840, 56841, 56842, 56843, 56844
56845, 56846, 56847, 56848, 56849, 56850, 56851, 56852, 56853, 56854, 56855, 56856, 56857, 56858, 56859, 56860
56861, 56862, 56863, 56864, 56865, 56866, 56867, 56868, 56869, 56870, 56871, 56872, 56873, 56874, 56875, 56876
56877, 56878, 56879, 56880, 59809, 59810, 59811, 59812, 59813, 59814, 59815, 59816, 59817, 59818, 59819, 59820
59821, 59822, 59823, 59824, 59825, 59826, 59827, 59828, 59829, 59830, 59831, 59832, 59833, 59834, 59835, 59836
59837, 59838, 59839, 59840, 59841, 59842, 59843, 59844, 59845, 59846, 59847, 59848, 59849, 59850, 59851, 59852
59853, 59854, 59855, 59856, 59857, 59858, 59859, 59860, 59861, 59862, 59863, 59864, 59865, 59866, 59867, 59868
59869, 59870, 59871, 59872, 59873, 59874, 59875, 59876, 59877, 59878, 59879, 59880, 59881, 59882, 59883, 59884
59885, 59886, 59887, 59888, 59889, 59890, 59891, 59892, 59893, 59894, 59895, 59896, 59897, 59898, 59899, 59900
59901, 59902, 59903, 59904, 59905, 59906, 59907, 59908, 59909, 59910, 59911, 59912, 59913, 59914, 59915, 59916
59917, 59918, 59919, 59920, 59921, 59922, 59923, 59924, 59925, 59926, 59927, 59928, 59929, 59930, 59931, 59932
59933, 59934, 59935, 59936, 59937, 59938, 59939, 59940, 59941, 59942, 59943, 59944, 59945, 59946, 59947, 59948
59949, 59950, 59951, 59952, 59953, 59954, 59955, 59956, 59957, 59958, 59959, 59960, 59961, 59962, 59963, 59964
59965, 59966, 59967, 59968, 59969, 59970, 59971, 59972, 59973, 59974, 59975, 59976, 59977, 59978, 59979, 59980
59981, 59982, 59983, 59984, 59985, 59986, 59987, 59988, 61897, 61898, 61899, 61900, 61901, 61902, 61903, 61904
61905, 61906, 61907, 61908, 61909, 61910, 61911, 61912, 61913, 61914, 61915, 61916, 61917, 61918, 61919, 61920
61921, 61922, 61923, 61924, 61925, 61926, 61927, 61928, 61929, 61930, 61931, 61932, 61933, 61934, 61935, 61936
61937, 61938, 61939, 61940, 61941, 61942, 61943, 61944, 61945, 61946, 61947, 61948, 61949, 61950, 61951, 61952
61953, 61954, 61955, 61956, 61957, 61958, 61959, 61960, 61961, 61962, 61963, 61964, 61965, 61966, 61967, 61968
61969, 61970, 61971, 61972, 61973, 61974, 61975, 61976, 61977, 61978, 61979, 61980, 61981, 61982, 61983, 61984
61985, 61986, 61987, 61988, 61989, 61990, 61991, 61992, 61993, 61994, 61995, 61996, 61997, 61998, 61999, 62000
62001, 62002, 62003, 62004, 62005, 62006, 62007, 62008, 62009, 62010, 62011, 62012, 62013, 62014, 62015, 62016
62017, 62018, 62019, 62020, 62021, 62022, 62023, 62024, 62025, 62026, 62027, 62028, 62029, 62030, 62031, 62032
62033, 62034, 62035, 62036, 62037, 62038, 62039, 62040, 62041, 62042, 62043, 62044, 62045, 62046, 62047, 62048
62049, 62050, 62051, 62052, 62053, 62054, 62055, 62056, 62057, 62058, 62059, 62060, 62061, 62062, 62063, 62064
63913, 63914, 63915, 63916, 63917, 63918, 63919, 63920, 63921, 63922, 63923, 63924, 63925, 63926, 63927, 63928
63929, 63930, 63931, 63932, 63933, 63934, 63935, 63936, 63937, 63938, 63939, 63940, 63941, 63942, 63943, 63944
63945, 63946, 63947, 63948, 63949, 63950, 63951, 63952, 63953, 63954, 63955, 63956, 63957, 63958, 63959, 63960
63961, 63962, 63963, 63964, 63965, 63966, 63967, 63968, 63969, 63970, 63971, 63972, 63973, 63974, 63975, 63976
63977, 63978, 63979, 63980, 63981, 63982, 63983, 63984, 63985, 63986, 63987, 63988, 63989, 63990, 63991, 63992
63993, 63994, 63995, 63996, 63997, 63998, 63999, 64000, 64001, 64002, 64003, 64004, 64005, 64006, 64007, 64008
64009, 64010, 64011, 64012, 64013, 64014, 64015, 64016, 64017, 64018, 64019, 64020, 64021, 64022, 64023, 64024
64025, 64026, 64027, 64028, 64029, 64030, 64031, 64032, 64033, 64034, 64035, 64036, 64037, 64038, 64039, 64040
64041, 64042, 64043, 64044, 64045, 64046, 64047, 64048, 64049, 64050, 64051, 64052, 64053, 64054, 64055, 64056
64057, 64058, 64059, 64060, 64061, 64062, 64063, 64064, 64065, 64066, 64067, 64068, 64069, 64070, 64071, 64072
64073, 64074, 64075, 64076, 64077, 64078, 64079, 64080, 66001, 66002, 66003, 66004, 66005, 66006, 66007, 66008
66009, 66010, 66011, 66012, 66013, 66014, 66015, 66016, 66017, 66018, 66019, 66020, 66021, 66022, 66023, 66024
66025, 66026, 66027, 66028, 66029, 66030, 66031, 66032, 66033, 66034, 66035, 66036, 66037, 66038, 66039, 66040
66041, 66042, 66043, 66044, 66045, 66046, 66047, 66048, 66049, 66050, 66051, 66052, 66053, 66054, 66055, 66056
66057, 66058, 66059, 66060, 66061, 66062, 66063, 66064, 66065, 66066, 66067, 66068, 66069, 66070, 66071, 66072
66073, 66074, 66075, 66076, 66077, 66078, 66079, 66080, 66081, 66082, 66083, 66084, 66085, 66086, 66087, 66088
66089, 66090, 66091, 66092, 66093, 66094, 66095, 66096, 66097, 66098, 66099, 66100, 66101, 66102, 66103, 66104
66105, 66106, 66107, 66108, 66109, 66110, 66111, 66112, 66113, 66114, 66115, 66116, 66117, 66118, 66119, 66120
66121, 66122, 66123, 66124, 66125, 66126, 66127, 66128, 66129, 66130, 66131, 66132, 66133, 66134, 66135, 66136
66137, 66138, 66139, 66140, 66141, 66142, 66143, 66144, 66145, 66146, 66147, 66148, 66149, 66150, 66151, 66152
66153, 66154, 66155, 66156, 66157, 66158, 66159, 66160, 66161, 66162, 66163, 66164, 66165, 66166, 66167, 66168
68089, 68090, 68091, 68092, 68093, 68094, 68095, 68096, 68097, 68098, 68099, 68100, 68101, 68102, 68103, 68104
68105, 68106, 68107, 68108, 68109, 68110, 68111, 68112, 68113, 68114, 68115, 68116, 68117, 68118, 68119, 68120
68121, 68122, 68123, 68124, 68125, 68126, 68127, 68128, 68129, 68130, 68131, 68132, 68133, 68134, 68135, 68136
68137, 68138, 68139, 68140, 68141, 68142, 68143, 68144, 68145, 68146, 68147, 68148, 68149, 68150, 68151, 68152
68153, 68154, 68155, 68156, 68157, 68158, 68159, 68160, 68161, 68162, 68163, 68164, 68165, 68166, 68167, 68168
68169, 68170, 68171, 68172, 68173, 68174, 68175, 68176, 68177, 68178, 68179, 68180, 68181, 68182, 68183, 68184
68185, 68186, 68187, 68188, 68189, 68190, 68191, 68192, 68193, 68194, 68195, 68196, 68197, 68198, 68199, 68200
68201, 68202, 68203, 68204, 68205, 68206, 68207, 68208, 68209, 68210, 68211, 68212, 68213, 68214, 68215, 68216
68217, 68218, 68219, 68220, 68221, 68222, 68223, 68224, 68225, 68226, 68227, 68228, 68229, 68230, 68231, 68232
68233, 68234, 68235, 68236, 68237, 68238, 68239, 68240, 68241, 68242, 68243, 68244, 68245, 68246, 68247, 68248
68249, 68250, 68251, 68252, 68253, 68254, 68255, 68256, 68257, 68258, 68259, 68260, 68261, 68262, 68263, 68264
68265, 68266, 68267, 68268, 70177, 70178, 70179, 70180, 70181, 70182, 70183, 70184, 70185, 70186, 70187, 70188
70189, 70190, 70191, 70192, 70193, 70194, 70195, 70196, 70197, 70198, 70199, 70200, 70201, 70202, 70203, 70204
70205, 70206, 70207, 70208, 70209, 70210, 70211, 70212, 70213, 70214, 70215, 70216, 70217, 70218, 70219, 70220
70221, 70222, 70223, 70224, 70225, 70226, 70227, 70228, 70229, 70230, 70231, 70232, 70233, 70234, 70235, 70236
70237, 70238, 70239, 70240, 70241, 70242, 70243, 70244, 70245, 70246, 70247, 70248, 70249, 70250, 70251, 70252
70253, 70254, 70255, 70256, 70257, 70258, 70259, 70260, 70261, 70262, 70263, 70264, 70265, 70266, 70267, 70268
70269, 70270, 70271, 70272, 70273, 70274, 70275, 70276, 70277, 70278, 70279, 70280, 70281, 70282, 70283, 70284
70285, 70286, 70287, 70288, 70289, 70290, 70291, 70292, 70293, 70294, 70295, 70296, 70297, 70298, 70299, 70300
70301, 70302, 70303, 70304, 70305, 70306, 70307, 70308, 70309, 70310, 70311, 70312, 70313, 70314, 70315, 70316
70317, 70318, 70319, 70320, 70321, 70322, 70323, 70324, 70325, 70326, 70327, 70328, 70329, 70330, 70331, 70332
70333, 70334, 70335, 70336, 70337, 70338, 70339, 70340, 70341, 70342, 70343, 70344, 70345, 70346, 70347, 70348
70349, 70350, 70351, 70352, 70353, 70354, 70355, 70356
*Elset, elset=__PickedSurf53_S2, internal, instance=Stent
48253, 48254, 48255, 48256, 48257, 48258, 48259, 48260, 48261, 48262, 48263, 48264, 48265, 48266, 48267, 48268
48269, 48270, 48271, 48272, 48273, 48274, 48275, 48276, 48277, 48278, 48279, 48280, 48281, 48282, 48283, 48284
48285, 48286, 48287, 48288, 48289, 48290, 48291, 48292, 48293, 48294, 48295, 48296, 48297, 48298, 48299, 48300
48301, 48302, 48303, 48304, 48305, 48306, 48307, 48308, 48309, 48310, 48311, 48312, 48313, 48314, 48315, 48316
48317, 48318, 48319, 48320, 48321, 48322, 48323, 48324, 48325, 48326, 48327, 48328, 48329, 48330, 48331, 48332
48333, 48334, 48335, 48336, 48337, 48338, 48339, 48340, 48341, 48342, 48343, 48344, 48345, 48346, 48347, 48348
48349, 48350, 48351, 48352, 48353, 48354, 48355, 48356, 48357, 48358, 48359, 48360, 48361, 48362, 48363, 48364
48365, 48366, 48367, 48368, 48369, 48370, 48371, 48372, 48373, 48374, 48375, 48376, 48377, 48378, 48379, 48380
48381, 48382, 48383, 48384, 48385, 48386, 48387, 48388, 48389, 48390, 48391, 48392, 48393, 48394, 48395, 48396
48397, 48398, 48399, 48400, 48401, 48402, 48403, 48404, 48405, 48406, 48407, 48408, 48409, 48410, 48411, 48412
48413, 48414, 48415, 48416, 48417, 48418, 48419, 48420, 48421, 48422, 48423, 48424, 48425, 48426, 48427, 48428
48429, 48430, 48431, 48432, 50281, 50282, 50283, 50284, 50285, 50286, 50287, 50288, 50289, 50290, 50291, 50292
50293, 50294, 50295, 50296, 50297, 50298, 50299, 50300, 50301, 50302, 50303, 50304, 50305, 50306, 50307, 50308
50309, 50310, 50311, 50312, 50313, 50314, 50315, 50316, 50317, 50318, 50319, 50320, 50321, 50322, 50323, 50324
50325, 50326, 50327, 50328, 50329, 50330, 50331, 50332, 50333, 50334, 50335, 50336, 50337, 50338, 50339, 50340
50341, 50342, 50343, 50344, 50345, 50346, 50347, 50348, 50349, 50350, 50351, 50352, 50353, 50354, 50355, 50356
50357, 50358, 50359, 50360, 50361, 50362, 50363, 50364, 50365, 50366, 50367, 50368, 50369, 50370, 50371, 50372
50373, 50374, 50375, 50376, 50377, 50378, 50379, 50380, 50381, 50382, 50383, 50384, 50385, 50386, 50387, 50388
50389, 50390, 50391, 50392, 50393, 50394, 50395, 50396, 50397, 50398, 50399, 50400, 50401, 50402, 50403, 50404
50405, 50406, 50407, 50408, 50409, 50410, 50411, 50412, 50413, 50414, 50415, 50416, 50417, 50418, 50419, 50420
50421, 50422, 50423, 50424, 50425, 50426, 50427, 50428, 50429, 50430, 50431, 50432, 50433, 50434, 50435, 50436
50437, 50438, 50439, 50440, 50441, 50442, 50443, 50444, 50445, 50446, 50447, 50448, 52297, 52298, 52299, 52300
52301, 52302, 52303, 52304, 52305, 52306, 52307, 52308, 52309, 52310, 52311, 52312, 52313, 52314, 52315, 52316
52317, 52318, 52319, 52320, 52321, 52322, 52323, 52324, 52325, 52326, 52327, 52328, 52329, 52330, 52331, 52332
52333, 52334, 52335, 52336, 52337, 52338, 52339, 52340, 52341, 52342, 52343, 52344, 52345, 52346, 52347, 52348
52349, 52350, 52351, 52352, 52353, 52354, 52355, 52356, 52357, 52358, 52359, 52360, 52361, 52362, 52363, 52364
52365, 52366, 52367, 52368, 52369, 52370, 52371, 52372, 52373, 52374, 52375, 52376, 52377, 52378, 52379, 52380
52381, 52382, 52383, 52384, 52385, 52386, 52387, 52388, 52389, 52390, 52391, 52392, 52393, 52394, 52395, 52396
52397, 52398, 52399, 52400, 52401, 52402, 52403, 52404, 52405, 52406, 52407, 52408, 52409, 52410, 52411, 52412
52413, 52414, 52415, 52416, 52417, 52418, 52419, 52420, 52421, 52422, 52423, 52424, 52425, 52426, 52427, 52428
52429, 52430, 52431, 52432, 52433, 52434, 52435, 52436, 52437, 52438, 52439, 52440, 52441, 52442, 52443, 52444
52445, 52446, 52447, 52448, 52449, 52450, 52451, 52452, 52453, 52454, 52455, 52456, 52457, 52458, 52459, 52460
52461, 52462, 52463, 52464, 54385, 54386, 54387, 54388, 54389, 54390, 54391, 54392, 54393, 54394, 54395, 54396
54397, 54398, 54399, 54400, 54401, 54402, 54403, 54404, 54405, 54406, 54407, 54408, 54409, 54410, 54411, 54412
54413, 54414, 54415, 54416, 54417, 54418, 54419, 54420, 54421, 54422, 54423, 54424, 54425, 54426, 54427, 54428
54429, 54430, 54431, 54432, 54433, 54434, 54435, 54436, 54437, 54438, 54439, 54440, 54441, 54442, 54443, 54444
54445, 54446, 54447, 54448, 54449, 54450, 54451, 54452, 54453, 54454, 54455, 54456, 54457, 54458, 54459, 54460
54461, 54462, 54463, 54464, 54465, 54466, 54467, 54468, 54469, 54470, 54471, 54472, 54473, 54474, 54475, 54476
54477, 54478, 54479, 54480, 54481, 54482, 54483, 54484, 54485, 54486, 54487, 54488, 54489, 54490, 54491, 54492
54493, 54494, 54495, 54496, 54497, 54498, 54499, 54500, 54501, 54502, 54503, 54504, 54505, 54506, 54507, 54508
54509, 54510, 54511, 54512, 54513, 54514, 54515, 54516, 54517, 54518, 54519, 54520, 54521, 54522, 54523, 54524
54525, 54526, 54527, 54528, 54529, 54530, 54531, 54532, 54533, 54534, 54535, 54536, 54537, 54538, 54539, 54540
54541, 54542, 54543, 54544, 54545, 54546, 54547, 54548, 54549, 54550, 54551, 54552, 56533, 56534, 56535, 56536
56537, 56538, 56539, 56540, 56541, 56542, 56543, 56544, 56545, 56546, 56547, 56548, 56549, 56550, 56551, 56552
56553, 56554, 56555, 56556, 56557, 56558, 56559, 56560, 56561, 56562, 56563, 56564, 56565, 56566, 56567, 56568
56569, 56570, 56571, 56572, 56573, 56574, 56575, 56576, 56577, 56578, 56579, 56580, 56581, 56582, 56583, 56584
56585, 56586, 56587, 56588, 56589, 56590, 56591, 56592, 56593, 56594, 56595, 56596, 56597, 56598, 56599, 56600
56601, 56602, 56603, 56604, 56605, 56606, 56607, 56608, 56609, 56610, 56611, 56612, 56613, 56614, 56615, 56616
56617, 56618, 56619, 56620, 56621, 56622, 56623, 56624, 56625, 56626, 56627, 56628, 56629, 56630, 56631, 56632
56633, 56634, 56635, 56636, 56637, 56638, 56639, 56640, 56641, 56642, 56643, 56644, 56645, 56646, 56647, 56648
56649, 56650, 56651, 56652, 56653, 56654, 56655, 56656, 56657, 56658, 56659, 56660, 56661, 56662, 56663, 56664
56665, 56666, 56667, 56668, 56669, 56670, 56671, 56672, 56673, 56674, 56675, 56676, 56677, 56678, 56679, 56680
56681, 56682, 56683, 56684, 56685, 56686, 56687, 56688, 56689, 56690, 56691, 56692, 56693, 56694, 56695, 56696
56697, 56698, 56699, 56700, 56701, 56702, 56703, 56704, 56705, 56706, 56707, 56708, 56709, 56710, 56711, 56712
58561, 58562, 58563, 58564, 58565, 58566, 58567, 58568, 58569, 58570, 58571, 58572, 58573, 58574, 58575, 58576
58577, 58578, 58579, 58580, 58581, 58582, 58583, 58584, 58585, 58586, 58587, 58588, 58589, 58590, 58591, 58592
58593, 58594, 58595, 58596, 58597, 58598, 58599, 58600, 58601, 58602, 58603, 58604, 58605, 58606, 58607, 58608
58609, 58610, 58611, 58612, 58613, 58614, 58615, 58616, 58617, 58618, 58619, 58620, 58621, 58622, 58623, 58624
58625, 58626, 58627, 58628, 58629, 58630, 58631, 58632, 58633, 58634, 58635, 58636, 58637, 58638, 58639, 58640
58641, 58642, 58643, 58644, 58645, 58646, 58647, 58648, 58649, 58650, 58651, 58652, 58653, 58654, 58655, 58656
58657, 58658, 58659, 58660, 58661, 58662, 58663, 58664, 58665, 58666, 58667, 58668, 58669, 58670, 58671, 58672
58673, 58674, 58675, 58676, 58677, 58678, 58679, 58680, 58681, 58682, 58683, 58684, 58685, 58686, 58687, 58688
58689, 58690, 58691, 58692, 58693, 58694, 58695, 58696, 58697, 58698, 58699, 58700, 58701, 58702, 58703, 58704
58705, 58706, 58707, 58708, 58709, 58710, 58711, 58712, 58713, 58714, 58715, 58716, 58717, 58718, 58719, 58720
58721, 58722, 58723, 58724, 58725, 58726, 58727, 58728, 59629, 59630, 59631, 59632, 59633, 59634, 59635, 59636
59637, 59638, 59639, 59640, 59641, 59642, 59643, 59644, 59645, 59646, 59647, 59648, 59649, 59650, 59651, 59652
59653, 59654, 59655, 59656, 59657, 59658, 59659, 59660, 59661, 59662, 59663, 59664, 59665, 59666, 59667, 59668
59669, 59670, 59671, 59672, 59673, 59674, 59675, 59676, 59677, 59678, 59679, 59680, 59681, 59682, 59683, 59684
59685, 59686, 59687, 59688, 59689, 59690, 59691, 59692, 59693, 59694, 59695, 59696, 59697, 59698, 59699, 59700
59701, 59702, 59703, 59704, 59705, 59706, 59707, 59708, 59709, 59710, 59711, 59712, 59713, 59714, 59715, 59716
59717, 59718, 59719, 59720, 59721, 59722, 59723, 59724, 59725, 59726, 59727, 59728, 59729, 59730, 59731, 59732
59733, 59734, 59735, 59736, 59737, 59738, 59739, 59740, 59741, 59742, 59743, 59744, 59745, 59746, 59747, 59748
59749, 59750, 59751, 59752, 59753, 59754, 59755, 59756, 59757, 59758, 59759, 59760, 59761, 59762, 59763, 59764
59765, 59766, 59767, 59768, 59769, 59770, 59771, 59772, 59773, 59774, 59775, 59776, 59777, 59778, 59779, 59780
59781, 59782, 59783, 59784, 59785, 59786, 59787, 59788, 59789, 59790, 59791, 59792, 59793, 59794, 59795, 59796
59797, 59798, 59799, 59800, 59801, 59802, 59803, 59804, 59805, 59806, 59807, 59808, 61729, 61730, 61731, 61732
61733, 61734, 61735, 61736, 61737, 61738, 61739, 61740, 61741, 61742, 61743, 61744, 61745, 61746, 61747, 61748
61749, 61750, 61751, 61752, 61753, 61754, 61755, 61756, 61757, 61758, 61759, 61760, 61761, 61762, 61763, 61764
61765, 61766, 61767, 61768, 61769, 61770, 61771, 61772, 61773, 61774, 61775, 61776, 61777, 61778, 61779, 61780
61781, 61782, 61783, 61784, 61785, 61786, 61787, 61788, 61789, 61790, 61791, 61792, 61793, 61794, 61795, 61796
61797, 61798, 61799, 61800, 61801, 61802, 61803, 61804, 61805, 61806, 61807, 61808, 61809, 61810, 61811, 61812
61813, 61814, 61815, 61816, 61817, 61818, 61819, 61820, 61821, 61822, 61823, 61824, 61825, 61826, 61827, 61828
61829, 61830, 61831, 61832, 61833, 61834, 61835, 61836, 61837, 61838, 61839, 61840, 61841, 61842, 61843, 61844
61845, 61846, 61847, 61848, 61849, 61850, 61851, 61852, 61853, 61854, 61855, 61856, 61857, 61858, 61859, 61860
61861, 61862, 61863, 61864, 61865, 61866, 61867, 61868, 61869, 61870, 61871, 61872, 61873, 61874, 61875, 61876
61877, 61878, 61879, 61880, 61881, 61882, 61883, 61884, 61885, 61886, 61887, 61888, 61889, 61890, 61891, 61892
61893, 61894, 61895, 61896, 63745, 63746, 63747, 63748, 63749, 63750, 63751, 63752, 63753, 63754, 63755, 63756
63757, 63758, 63759, 63760, 63761, 63762, 63763, 63764, 63765, 63766, 63767, 63768, 63769, 63770, 63771, 63772
63773, 63774, 63775, 63776, 63777, 63778, 63779, 63780, 63781, 63782, 63783, 63784, 63785, 63786, 63787, 63788
63789, 63790, 63791, 63792, 63793, 63794, 63795, 63796, 63797, 63798, 63799, 63800, 63801, 63802, 63803, 63804
63805, 63806, 63807, 63808, 63809, 63810, 63811, 63812, 63813, 63814, 63815, 63816, 63817, 63818, 63819, 63820
63821, 63822, 63823, 63824, 63825, 63826, 63827, 63828, 63829, 63830, 63831, 63832, 63833, 63834, 63835, 63836
63837, 63838, 63839, 63840, 63841, 63842, 63843, 63844, 63845, 63846, 63847, 63848, 63849, 63850, 63851, 63852
63853, 63854, 63855, 63856, 63857, 63858, 63859, 63860, 63861, 63862, 63863, 63864, 63865, 63866, 63867, 63868
63869, 63870, 63871, 63872, 63873, 63874, 63875, 63876, 63877, 63878, 63879, 63880, 63881, 63882, 63883, 63884
63885, 63886, 63887, 63888, 63889, 63890, 63891, 63892, 63893, 63894, 63895, 63896, 63897, 63898, 63899, 63900
63901, 63902, 63903, 63904, 63905, 63906, 63907, 63908, 63909, 63910, 63911, 63912, 65821, 65822, 65823, 65824
65825, 65826, 65827, 65828, 65829, 65830, 65831, 65832, 65833, 65834, 65835, 65836, 65837, 65838, 65839, 65840
65841, 65842, 65843, 65844, 65845, 65846, 65847, 65848, 65849, 65850, 65851, 65852, 65853, 65854, 65855, 65856
65857, 65858, 65859, 65860, 65861, 65862, 65863, 65864, 65865, 65866, 65867, 65868, 65869, 65870, 65871, 65872
65873, 65874, 65875, 65876, 65877, 65878, 65879, 65880, 65881, 65882, 65883, 65884, 65885, 65886, 65887, 65888
65889, 65890, 65891, 65892, 65893, 65894, 65895, 65896, 65897, 65898, 65899, 65900, 65901, 65902, 65903, 65904
65905, 65906, 65907, 65908, 65909, 65910, 65911, 65912, 65913, 65914, 65915, 65916, 65917, 65918, 65919, 65920
65921, 65922, 65923, 65924, 65925, 65926, 65927, 65928, 65929, 65930, 65931, 65932, 65933, 65934, 65935, 65936
65937, 65938, 65939, 65940, 65941, 65942, 65943, 65944, 65945, 65946, 65947, 65948, 65949, 65950, 65951, 65952
65953, 65954, 65955, 65956, 65957, 65958, 65959, 65960, 65961, 65962, 65963, 65964, 65965, 65966, 65967, 65968
65969, 65970, 65971, 65972, 65973, 65974, 65975, 65976, 65977, 65978, 65979, 65980, 65981, 65982, 65983, 65984
65985, 65986, 65987, 65988, 65989, 65990, 65991, 65992, 65993, 65994, 65995, 65996, 65997, 65998, 65999, 66000
67909, 67910, 67911, 67912, 67913, 67914, 67915, 67916, 67917, 67918, 67919, 67920, 67921, 67922, 67923, 67924
67925, 67926, 67927, 67928, 67929, 67930, 67931, 67932, 67933, 67934, 67935, 67936, 67937, 67938, 67939, 67940
67941, 67942, 67943, 67944, 67945, 67946, 67947, 67948, 67949, 67950, 67951, 67952, 67953, 67954, 67955, 67956
67957, 67958, 67959, 67960, 67961, 67962, 67963, 67964, 67965, 67966, 67967, 67968, 67969, 67970, 67971, 67972
67973, 67974, 67975, 67976, 67977, 67978, 67979, 67980, 67981, 67982, 67983, 67984, 67985, 67986, 67987, 67988
67989, 67990, 67991, 67992, 67993, 67994, 67995, 67996, 67997, 67998, 67999, 68000, 68001, 68002, 68003, 68004
68005, 68006, 68007, 68008, 68009, 68010, 68011, 68012, 68013, 68014, 68015, 68016, 68017, 68018, 68019, 68020
68021, 68022, 68023, 68024, 68025, 68026, 68027, 68028, 68029, 68030, 68031, 68032, 68033, 68034, 68035, 68036
68037, 68038, 68039, 68040, 68041, 68042, 68043, 68044, 68045, 68046, 68047, 68048, 68049, 68050, 68051, 68052
68053, 68054, 68055, 68056, 68057, 68058, 68059, 68060, 68061, 68062, 68063, 68064, 68065, 68066, 68067, 68068
68069, 68070, 68071, 68072, 68073, 68074, 68075, 68076, 68077, 68078, 68079, 68080, 68081, 68082, 68083, 68084
68085, 68086, 68087, 68088, 70009, 70010, 70011, 70012, 70013, 70014, 70015, 70016, 70017, 70018, 70019, 70020
70021, 70022, 70023, 70024, 70025, 70026, 70027, 70028, 70029, 70030, 70031, 70032, 70033, 70034, 70035, 70036
70037, 70038, 70039, 70040, 70041, 70042, 70043, 70044, 70045, 70046, 70047, 70048, 70049, 70050, 70051, 70052
70053, 70054, 70055, 70056, 70057, 70058, 70059, 70060, 70061, 70062, 70063, 70064, 70065, 70066, 70067, 70068
70069, 70070, 70071, 70072, 70073, 70074, 70075, 70076, 70077, 70078, 70079, 70080, 70081, 70082, 70083, 70084
70085, 70086, 70087, 70088, 70089, 70090, 70091, 70092, 70093, 70094, 70095, 70096, 70097, 70098, 70099, 70100
70101, 70102, 70103, 70104, 70105, 70106, 70107, 70108, 70109, 70110, 70111, 70112, 70113, 70114, 70115, 70116
70117, 70118, 70119, 70120, 70121, 70122, 70123, 70124, 70125, 70126, 70127, 70128, 70129, 70130, 70131, 70132
70133, 70134, 70135, 70136, 70137, 70138, 70139, 70140, 70141, 70142, 70143, 70144, 70145, 70146, 70147, 70148
70149, 70150, 70151, 70152, 70153, 70154, 70155, 70156, 70157, 70158, 70159, 70160, 70161, 70162, 70163, 70164
70165, 70166, 70167, 70168, 70169, 70170, 70171, 70172, 70173, 70174, 70175, 70176
*Elset, elset=__PickedSurf53_S3, internal, instance=Stent
2521, 2522, 2523, 2524, 2525, 2526, 2527, 2528, 2529, 2530, 2531, 2532, 2533, 2534, 2535, 2536
2537, 2538, 2539, 2635, 2636, 2637, 2638, 2639, 2640, 2641, 2642, 2643, 2644, 2645, 2646, 2647
2648, 2649, 2650, 2651, 2652, 2653, 2749, 2750, 2751, 2752, 2753, 2754, 2755, 2756, 2757, 2758
2759, 2760, 2761, 2762, 2763, 2764, 2765, 2766, 2767, 2863, 2864, 2865, 2866, 2867, 2868, 2869
2870, 2871, 2872, 2873, 2874, 2875, 2876, 2877, 2878, 2879, 2880, 2881, 2977, 2978, 2979, 2980
2981, 2982, 2983, 2984, 2985, 2986, 2987, 2988, 2989, 2990, 2991, 2992, 2993, 2994, 2995, 3091
3092, 3093, 3094, 3095, 3096, 3097, 3098, 3099, 3100, 3101, 3102, 3103, 3104, 3105, 3106, 3107
3108, 3109, 3205, 3206, 3207, 3208, 3209, 3210, 3211, 3212, 3213, 3214, 3215, 3216, 3217, 3218
3219, 3220, 3221, 3222, 3223, 3319, 3320, 3321, 3322, 3323, 3324, 3325, 3326, 3327, 3328, 3329
3330, 3331, 3332, 3333, 3334, 3335, 3336, 3337, 3433, 3434, 3435, 3436, 3437, 3438, 3439, 3440
3441, 3442, 3443, 3444, 3445, 3446, 3447, 3448, 3449, 3450, 3451, 3547, 3548, 3549, 3550, 3551
3552, 3553, 3554, 3555, 3556, 3557, 3558, 3559, 3560, 3561, 3562, 3563, 3564, 3565, 3661, 3662
3663, 3664, 3665, 3666, 3667, 3668, 3669, 3670, 3671, 3672, 3673, 3674, 3675, 3676, 3677, 3678
3679, 3775, 3776, 3777, 3778, 3779, 3780, 3781, 3782, 3783, 3784, 3785, 3786, 3787, 3788, 3789
3790, 3791, 3792, 3793, 6217, 6218, 6219, 6220, 6221, 6222, 6223, 6224, 6225, 6226, 6227, 6228
6229, 6230, 6231, 6232, 6233, 6234, 6235, 6331, 6332, 6333, 6334, 6335, 6336, 6337, 6338, 6339
6340, 6341, 6342, 6343, 6344, 6345, 6346, 6347, 6348, 6349, 6445, 6446, 6447, 6448, 6449, 6450
6451, 6452, 6453, 6454, 6455, 6456, 6457, 6458, 6459, 6460, 6461, 6462, 6463, 6559, 6560, 6561
6562, 6563, 6564, 6565, 6566, 6567, 6568, 6569, 6570, 6571, 6572, 6573, 6574, 6575, 6576, 6577
6673, 6674, 6675, 6676, 6677, 6678, 6679, 6680, 6681, 6682, 6683, 6684, 6685, 6686, 6687, 6688
6689, 6690, 6691, 6787, 6788, 6789, 6790, 6791, 6792, 6793, 6794, 6795, 6796, 6797, 6798, 6799
6800, 6801, 6802, 6803, 6804, 6805, 6901, 6902, 6903, 6904, 6905, 6906, 6907, 6908, 6909, 6910
6911, 6912, 6913, 6914, 6915, 6916, 6917, 6918, 6919, 7015, 7016, 7017, 7018, 7019, 7020, 7021
7022, 7023, 7024, 7025, 7026, 7027, 7028, 7029, 7030, 7031, 7032, 7033, 7129, 7130, 7131, 7132
7133, 7134, 7135, 7136, 7137, 7138, 7139, 7140, 7141, 7142, 7143, 7144, 7145, 7146, 7147, 7243
7244, 7245, 7246, 7247, 7248, 7249, 7250, 7251, 7252, 7253, 7254, 7255, 7256, 7257, 7258, 7259
7260, 7261, 7357, 7358, 7359, 7360, 7361, 7362, 7363, 7364, 7365, 7366, 7367, 7368, 7369, 7370
7371, 7372, 7373, 7374, 7375, 7471, 7472, 7473, 7474, 7475, 7476, 7477, 7478, 7479, 7480, 7481
7482, 7483, 7484, 7485, 7486, 7487, 7488, 7489, 9721, 9722, 9723, 9724, 9725, 9726, 9727, 9728
9729, 9730, 9731, 9732, 9733, 9734, 9735, 9736, 9737, 9738, 9739, 9835, 9836, 9837, 9838, 9839
9840, 9841, 9842, 9843, 9844, 9845, 9846, 9847, 9848, 9849, 9850, 9851, 9852, 9853, 9949, 9950
9951, 9952, 9953, 9954, 9955, 9956, 9957, 9958, 9959, 9960, 9961, 9962, 9963, 9964, 9965, 9966
9967, 10063, 10064, 10065, 10066, 10067, 10068, 10069, 10070, 10071, 10072, 10073, 10074, 10075, 10076, 10077
10078, 10079, 10080, 10081, 10177, 10178, 10179, 10180, 10181, 10182, 10183, 10184, 10185, 10186, 10187, 10188
10189, 10190, 10191, 10192, 10193, 10194, 10195, 10291, 10292, 10293, 10294, 10295, 10296, 10297, 10298, 10299
10300, 10301, 10302, 10303, 10304, 10305, 10306, 10307, 10308, 10309, 10405, 10406, 10407, 10408, 10409, 10410
10411, 10412, 10413, 10414, 10415, 10416, 10417, 10418, 10419, 10420, 10421, 10422, 10423, 10519, 10520, 10521
10522, 10523, 10524, 10525, 10526, 10527, 10528, 10529, 10530, 10531, 10532, 10533, 10534, 10535, 10536, 10537
10633, 10634, 10635, 10636, 10637, 10638, 10639, 10640, 10641, 10642, 10643, 10644, 10645, 10646, 10647, 10648
10649, 10650, 10651, 10747, 10748, 10749, 10750, 10751, 10752, 10753, 10754, 10755, 10756, 10757, 10758, 10759
10760, 10761, 10762, 10763, 10764, 10765, 10861, 10862, 10863, 10864, 10865, 10866, 10867, 10868, 10869, 10870
10871, 10872, 10873, 10874, 10875, 10876, 10877, 10878, 10879, 10975, 10976, 10977, 10978, 10979, 10980, 10981
10982, 10983, 10984, 10985, 10986, 10987, 10988, 10989, 10990, 10991, 10992, 10993, 13609, 13610, 13611, 13612
13613, 13614, 13615, 13616, 13617, 13618, 13619, 13620, 13621, 13622, 13623, 13624, 13625, 13626, 13627, 13723
13724, 13725, 13726, 13727, 13728, 13729, 13730, 13731, 13732, 13733, 13734, 13735, 13736, 13737, 13738, 13739
13740, 13741, 13837, 13838, 13839, 13840, 13841, 13842, 13843, 13844, 13845, 13846, 13847, 13848, 13849, 13850
13851, 13852, 13853, 13854, 13855, 13951, 13952, 13953, 13954, 13955, 13956, 13957, 13958, 13959, 13960, 13961
13962, 13963, 13964, 13965, 13966, 13967, 13968, 13969, 14065, 14066, 14067, 14068, 14069, 14070, 14071, 14072
14073, 14074, 14075, 14076, 14077, 14078, 14079, 14080, 14081, 14082, 14083, 14179, 14180, 14181, 14182, 14183
14184, 14185, 14186, 14187, 14188, 14189, 14190, 14191, 14192, 14193, 14194, 14195, 14196, 14197, 14293, 14294
14295, 14296, 14297, 14298, 14299, 14300, 14301, 14302, 14303, 14304, 14305, 14306, 14307, 14308, 14309, 14310
14311, 14407, 14408, 14409, 14410, 14411, 14412, 14413, 14414, 14415, 14416, 14417, 14418, 14419, 14420, 14421
14422, 14423, 14424, 14425, 14521, 14522, 14523, 14524, 14525, 14526, 14527, 14528, 14529, 14530, 14531, 14532
14533, 14534, 14535, 14536, 14537, 14538, 14539, 14635, 14636, 14637, 14638, 14639, 14640, 14641, 14642, 14643
14644, 14645, 14646, 14647, 14648, 14649, 14650, 14651, 14652, 14653, 14749, 14750, 14751, 14752, 14753, 14754
14755, 14756, 14757, 14758, 14759, 14760, 14761, 14762, 14763, 14764, 14765, 14766, 14767, 14863, 14864, 14865
14866, 14867, 14868, 14869, 14870, 14871, 14872, 14873, 14874, 14875, 14876, 14877, 14878, 14879, 14880, 14881
17689, 17690, 17691, 17692, 17693, 17694, 17695, 17696, 17697, 17698, 17699, 17700, 17701, 17702, 17703, 17704
17705, 17706, 17707, 17803, 17804, 17805, 17806, 17807, 17808, 17809, 17810, 17811, 17812, 17813, 17814, 17815
17816, 17817, 17818, 17819, 17820, 17821, 17917, 17918, 17919, 17920, 17921, 17922, 17923, 17924, 17925, 17926
17927, 17928, 17929, 17930, 17931, 17932, 17933, 17934, 17935, 18031, 18032, 18033, 18034, 18035, 18036, 18037
18038, 18039, 18040, 18041, 18042, 18043, 18044, 18045, 18046, 18047, 18048, 18049, 18145, 18146, 18147, 18148
18149, 18150, 18151, 18152, 18153, 18154, 18155, 18156, 18157, 18158, 18159, 18160, 18161, 18162, 18163, 18259
18260, 18261, 18262, 18263, 18264, 18265, 18266, 18267, 18268, 18269, 18270, 18271, 18272, 18273, 18274, 18275
18276, 18277, 18373, 18374, 18375, 18376, 18377, 18378, 18379, 18380, 18381, 18382, 18383, 18384, 18385, 18386
18387, 18388, 18389, 18390, 18391, 18487, 18488, 18489, 18490, 18491, 18492, 18493, 18494, 18495, 18496, 18497
18498, 18499, 18500, 18501, 18502, 18503, 18504, 18505, 18601, 18602, 18603, 18604, 18605, 18606, 18607, 18608
18609, 18610, 18611, 18612, 18613, 18614, 18615, 18616, 18617, 18618, 18619, 18715, 18716, 18717, 18718, 18719
18720, 18721, 18722, 18723, 18724, 18725, 18726, 18727, 18728, 18729, 18730, 18731, 18732, 18733, 18829, 18830
18831, 18832, 18833, 18834, 18835, 18836, 18837, 18838, 18839, 18840, 18841, 18842, 18843, 18844, 18845, 18846
18847, 18943, 18944, 18945, 18946, 18947, 18948, 18949, 18950, 18951, 18952, 18953, 18954, 18955, 18956, 18957
18958, 18959, 18960, 18961, 21385, 21386, 21387, 21388, 21389, 21390, 21391, 21392, 21393, 21394, 21395, 21396
21397, 21398, 21399, 21400, 21401, 21402, 21403, 21499, 21500, 21501, 21502, 21503, 21504, 21505, 21506, 21507
21508, 21509, 21510, 21511, 21512, 21513, 21514, 21515, 21516, 21517, 21613, 21614, 21615, 21616, 21617, 21618
21619, 21620, 21621, 21622, 21623, 21624, 21625, 21626, 21627, 21628, 21629, 21630, 21631, 21727, 21728, 21729
21730, 21731, 21732, 21733, 21734, 21735, 21736, 21737, 21738, 21739, 21740, 21741, 21742, 21743, 21744, 21745
21841, 21842, 21843, 21844, 21845, 21846, 21847, 21848, 21849, 21850, 21851, 21852, 21853, 21854, 21855, 21856
21857, 21858, 21859, 21955, 21956, 21957, 21958, 21959, 21960, 21961, 21962, 21963, 21964, 21965, 21966, 21967
21968, 21969, 21970, 21971, 21972, 21973, 22069, 22070, 22071, 22072, 22073, 22074, 22075, 22076, 22077, 22078
22079, 22080, 22081, 22082, 22083, 22084, 22085, 22086, 22087, 22183, 22184, 22185, 22186, 22187, 22188, 22189
22190, 22191, 22192, 22193, 22194, 22195, 22196, 22197, 22198, 22199, 22200, 22201, 22297, 22298, 22299, 22300
22301, 22302, 22303, 22304, 22305, 22306, 22307, 22308, 22309, 22310, 22311, 22312, 22313, 22314, 22315, 22411
22412, 22413, 22414, 22415, 22416, 22417, 22418, 22419, 22420, 22421, 22422, 22423, 22424, 22425, 22426, 22427
22428, 22429, 22525, 22526, 22527, 22528, 22529, 22530, 22531, 22532, 22533, 22534, 22535, 22536, 22537, 22538
22539, 22540, 22541, 22542, 22543, 22639, 22640, 22641, 22642, 22643, 22644, 22645, 22646, 22647, 22648, 22649
22650, 22651, 22652, 22653, 22654, 22655, 22656, 22657, 22945, 22946, 22947, 22948, 22949, 22950, 22951, 22952
22953, 22954, 22955, 22956, 22957, 22958, 22959, 22960, 23041, 23042, 23043, 23044, 23045, 23046, 23047, 23048
23049, 23050, 23051, 23052, 23053, 23054, 23055, 23056, 23137, 23138, 23139, 23140, 23141, 23142, 23143, 23144
23145, 23146, 23147, 23148, 23149, 23150, 23151, 23152, 23233, 23234, 23235, 23236, 23237, 23238, 23239, 23240
23241, 23242, 23243, 23244, 23245, 23246, 23247, 23248, 23329, 23330, 23331, 23332, 23333, 23334, 23335, 23336
23337, 23338, 23339, 23340, 23341, 23342, 23343, 23344, 23345, 23346, 23347, 23443, 23444, 23445, 23446, 23447
23448, 23449, 23450, 23451, 23452, 23453, 23454, 23455, 23456, 23457, 23458, 23459, 23460, 23461, 23557, 23558
23559, 23560, 23561, 23562, 23563, 23564, 23565, 23566, 23567, 23568, 23569, 23570, 23571, 23572, 23573, 23574
23575, 23671, 23672, 23673, 23674, 23675, 23676, 23677, 23678, 23679, 23680, 23681, 23682, 23683, 23684, 23685
23686, 23687, 23688, 23689, 23785, 23786, 23787, 23788, 23789, 23790, 23791, 23792, 23793, 23794, 23795, 23796
23797, 23798, 23799, 23800, 23801, 23802, 23803, 23899, 23900, 23901, 23902, 23903, 23904, 23905, 23906, 23907
23908, 23909, 23910, 23911, 23912, 23913, 23914, 23915, 23916, 23917, 24013, 24014, 24015, 24016, 24017, 24018
24019, 24020, 24021, 24022, 24023, 24024, 24025, 24026, 24027, 24028, 24029, 24030, 24031, 24127, 24128, 24129
24130, 24131, 24132, 24133, 24134, 24135, 24136, 24137, 24138, 24139, 24140, 24141, 24142, 24143, 24144, 24145
24241, 24242, 24243, 24244, 24245, 24246, 24247, 24248, 24249, 24250, 24251, 24252, 24253, 24254, 24255, 24256
24257, 24258, 24259, 24355, 24356, 24357, 24358, 24359, 24360, 24361, 24362, 24363, 24364, 24365, 24366, 24367
24368, 24369, 24370, 24371, 24372, 24373, 24469, 24470, 24471, 24472, 24473, 24474, 24475, 24476, 24477, 24478
24479, 24480, 24481, 24482, 24483, 24484, 24485, 24486, 24487, 24583, 24584, 24585, 24586, 24587, 24588, 24589
24590, 24591, 24592, 24593, 24594, 24595, 24596, 24597, 24598, 24599, 24600, 24601, 24697, 24698, 24699, 24700
24701, 24702, 24703, 24704, 24705, 24706, 24707, 24708, 24709, 24710, 24711, 24712, 24793, 24794, 24795, 24796
24797, 24798, 24799, 24800, 24801, 24802, 24803, 24804, 24805, 24806, 24807, 24808, 24889, 24890, 24891, 24892
24893, 24894, 24895, 24896, 24897, 24898, 24899, 24900, 24901, 24902, 24903, 24904, 24985, 24986, 24987, 24988
24989, 24990, 24991, 24992, 24993, 24994, 24995, 24996, 24997, 24998, 24999, 25000, 27217, 27218, 27219, 27220
27221, 27222, 27223, 27224, 27225, 27226, 27227, 27228, 27229, 27230, 27231, 27232, 27313, 27314, 27315, 27316
27317, 27318, 27319, 27320, 27321, 27322, 27323, 27324, 27325, 27326, 27327, 27328, 27409, 27410, 27411, 27412
27413, 27414, 27415, 27416, 27417, 27418, 27419, 27420, 27421, 27422, 27423, 27424, 27425, 27426, 27427, 27523
27524, 27525, 27526, 27527, 27528, 27529, 27530, 27531, 27532, 27533, 27534, 27535, 27536, 27537, 27538, 27539
27540, 27541, 27637, 27638, 27639, 27640, 27641, 27642, 27643, 27644, 27645, 27646, 27647, 27648, 27649, 27650
27651, 27652, 27653, 27654, 27655, 27751, 27752, 27753, 27754, 27755, 27756, 27757, 27758, 27759, 27760, 27761
27762, 27763, 27764, 27765, 27766, 27767, 27768, 27769, 27865, 27866, 27867, 27868, 27869, 27870, 27871, 27872
27873, 27874, 27875, 27876, 27877, 27878, 27879, 27880, 27881, 27882, 27883, 27979, 27980, 27981, 27982, 27983
27984, 27985, 27986, 27987, 27988, 27989, 27990, 27991, 27992, 27993, 27994, 27995, 27996, 27997, 28093, 28094
28095, 28096, 28097, 28098, 28099, 28100, 28101, 28102, 28103, 28104, 28105, 28106, 28107, 28108, 28109, 28110
28111, 28207, 28208, 28209, 28210, 28211, 28212, 28213, 28214, 28215, 28216, 28217, 28218, 28219, 28220, 28221
28222, 28223, 28224, 28225, 28321, 28322, 28323, 28324, 28325, 28326, 28327, 28328, 28329, 28330, 28331, 28332
28333, 28334, 28335, 28336, 28337, 28338, 28339, 28435, 28436, 28437, 28438, 28439, 28440, 28441, 28442, 28443
28444, 28445, 28446, 28447, 28448, 28449, 28450, 28451, 28452, 28453, 28549, 28550, 28551, 28552, 28553, 28554
28555, 28556, 28557, 28558, 28559, 28560, 28561, 28562, 28563, 28564, 28565, 28566, 28567, 28663, 28664, 28665
28666, 28667, 28668, 28669, 28670, 28671, 28672, 28673, 28674, 28675, 28676, 28677, 28678, 28679, 28680, 28681
28777, 28778, 28779, 28780, 28781, 28782, 28783, 28784, 28785, 28786, 28787, 28788, 28789, 28790, 28791, 28792
28873, 28874, 28875, 28876, 28877, 28878, 28879, 28880, 28881, 28882, 28883, 28884, 28885, 28886, 28887, 28888
30721, 30722, 30723, 30724, 30725, 30726, 30727, 30728, 30729, 30730, 30731, 30732, 30733, 30734, 30735, 30736
30817, 30818, 30819, 30820, 30821, 30822, 30823, 30824, 30825, 30826, 30827, 30828, 30829, 30830, 30831, 30832
30913, 30914, 30915, 30916, 30917, 30918, 30919, 30920, 30921, 30922, 30923, 30924, 30925, 30926, 30927, 30928
30929, 30930, 30931, 31027, 31028, 31029, 31030, 31031, 31032, 31033, 31034, 31035, 31036, 31037, 31038, 31039
31040, 31041, 31042, 31043, 31044, 31045, 31141, 31142, 31143, 31144, 31145, 31146, 31147, 31148, 31149, 31150
31151, 31152, 31153, 31154, 31155, 31156, 31157, 31158, 31159, 31255, 31256, 31257, 31258, 31259, 31260, 31261
31262, 31263, 31264, 31265, 31266, 31267, 31268, 31269, 31270, 31271, 31272, 31273, 31369, 31370, 31371, 31372
31373, 31374, 31375, 31376, 31377, 31378, 31379, 31380, 31381, 31382, 31383, 31384, 31385, 31386, 31387, 31483
31484, 31485, 31486, 31487, 31488, 31489, 31490, 31491, 31492, 31493, 31494, 31495, 31496, 31497, 31498, 31499
31500, 31501, 31597, 31598, 31599, 31600, 31601, 31602, 31603, 31604, 31605, 31606, 31607, 31608, 31609, 31610
31611, 31612, 31613, 31614, 31615, 31711, 31712, 31713, 31714, 31715, 31716, 31717, 31718, 31719, 31720, 31721
31722, 31723, 31724, 31725, 31726, 31727, 31728, 31729, 31825, 31826, 31827, 31828, 31829, 31830, 31831, 31832
31833, 31834, 31835, 31836, 31837, 31838, 31839, 31840, 31841, 31842, 31843, 31939, 31940, 31941, 31942, 31943
31944, 31945, 31946, 31947, 31948, 31949, 31950, 31951, 31952, 31953, 31954, 31955, 31956, 31957, 32053, 32054
32055, 32056, 32057, 32058, 32059, 32060, 32061, 32062, 32063, 32064, 32065, 32066, 32067, 32068, 32069, 32070
32071, 32167, 32168, 32169, 32170, 32171, 32172, 32173, 32174, 32175, 32176, 32177, 32178, 32179, 32180, 32181
32182, 32183, 32184, 32185, 32281, 32282, 32283, 32284, 32285, 32286, 32287, 32288, 32289, 32290, 32291, 32292
32293, 32294, 32295, 32296, 32377, 32378, 32379, 32380, 32381, 32382, 32383, 32384, 32385, 32386, 32387, 32388
32389, 32390, 32391, 32392, 34225, 34226, 34227, 34228, 34229, 34230, 34231, 34232, 34233, 34234, 34235, 34236
34237, 34238, 34239, 34240, 34321, 34322, 34323, 34324, 34325, 34326, 34327, 34328, 34329, 34330, 34331, 34332
34333, 34334, 34335, 34336, 34417, 34418, 34419, 34420, 34421, 34422, 34423, 34424, 34425, 34426, 34427, 34428
34429, 34430, 34431, 34432, 34513, 34514, 34515, 34516, 34517, 34518, 34519, 34520, 34521, 34522, 34523, 34524
34525, 34526, 34527, 34528, 34609, 34610, 34611, 34612, 34613, 34614, 34615, 34616, 34617, 34618, 34619, 34620
34621, 34622, 34623, 34624, 34625, 34626, 34627, 34723, 34724, 34725, 34726, 34727, 34728, 34729, 34730, 34731
34732, 34733, 34734, 34735, 34736, 34737, 34738, 34739, 34740, 34741, 34837, 34838, 34839, 34840, 34841, 34842
34843, 34844, 34845, 34846, 34847, 34848, 34849, 34850, 34851, 34852, 34853, 34854, 34855, 34951, 34952, 34953
34954, 34955, 34956, 34957, 34958, 34959, 34960, 34961, 34962, 34963, 34964, 34965, 34966, 34967, 34968, 34969
35065, 35066, 35067, 35068, 35069, 35070, 35071, 35072, 35073, 35074, 35075, 35076, 35077, 35078, 35079, 35080
35081, 35082, 35083, 35179, 35180, 35181, 35182, 35183, 35184, 35185, 35186, 35187, 35188, 35189, 35190, 35191
35192, 35193, 35194, 35195, 35196, 35197, 35293, 35294, 35295, 35296, 35297, 35298, 35299, 35300, 35301, 35302
35303, 35304, 35305, 35306, 35307, 35308, 35309, 35310, 35311, 35407, 35408, 35409, 35410, 35411, 35412, 35413
35414, 35415, 35416, 35417, 35418, 35419, 35420, 35421, 35422, 35423, 35424, 35425, 35521, 35522, 35523, 35524
35525, 35526, 35527, 35528, 35529, 35530, 35531, 35532, 35533, 35534, 35535, 35536, 35537, 35538, 35539, 35635
35636, 35637, 35638, 35639, 35640, 35641, 35642, 35643, 35644, 35645, 35646, 35647, 35648, 35649, 35650, 35651
35652, 35653, 35749, 35750, 35751, 35752, 35753, 35754, 35755, 35756, 35757, 35758, 35759, 35760, 35761, 35762
35763, 35764, 35765, 35766, 35767, 35863, 35864, 35865, 35866, 35867, 35868, 35869, 35870, 35871, 35872, 35873
35874, 35875, 35876, 35877, 35878, 35879, 35880, 35881, 35977, 35978, 35979, 35980, 35981, 35982, 35983, 35984
35985, 35986, 35987, 35988, 35989, 35990, 35991, 35992, 36073, 36074, 36075, 36076, 36077, 36078, 36079, 36080
36081, 36082, 36083, 36084, 36085, 36086, 36087, 36088, 36169, 36170, 36171, 36172, 36173, 36174, 36175, 36176
36177, 36178, 36179, 36180, 36181, 36182, 36183, 36184, 36265, 36266, 36267, 36268, 36269, 36270, 36271, 36272
36273, 36274, 36275, 36276, 36277, 36278, 36279, 36280, 38113, 38114, 38115, 38116, 38117, 38118, 38119, 38120
38121, 38122, 38123, 38124, 38125, 38126, 38127, 38128, 38209, 38210, 38211, 38212, 38213, 38214, 38215, 38216
38217, 38218, 38219, 38220, 38221, 38222, 38223, 38224, 38305, 38306, 38307, 38308, 38309, 38310, 38311, 38312
38313, 38314, 38315, 38316, 38317, 38318, 38319, 38320, 38401, 38402, 38403, 38404, 38405, 38406, 38407, 38408
38409, 38410, 38411, 38412, 38413, 38414, 38415, 38416, 38497, 38498, 38499, 38500, 38501, 38502, 38503, 38504
38505, 38506, 38507, 38508, 38509, 38510, 38511, 38512, 38513, 38514, 38515, 38611, 38612, 38613, 38614, 38615
38616, 38617, 38618, 38619, 38620, 38621, 38622, 38623, 38624, 38625, 38626, 38627, 38628, 38629, 38725, 38726
38727, 38728, 38729, 38730, 38731, 38732, 38733, 38734, 38735, 38736, 38737, 38738, 38739, 38740, 38741, 38742
38743, 38839, 38840, 38841, 38842, 38843, 38844, 38845, 38846, 38847, 38848, 38849, 38850, 38851, 38852, 38853
38854, 38855, 38856, 38857, 38953, 38954, 38955, 38956, 38957, 38958, 38959, 38960, 38961, 38962, 38963, 38964
38965, 38966, 38967, 38968, 38969, 38970, 38971, 39067, 39068, 39069, 39070, 39071, 39072, 39073, 39074, 39075
39076, 39077, 39078, 39079, 39080, 39081, 39082, 39083, 39084, 39085, 39181, 39182, 39183, 39184, 39185, 39186
39187, 39188, 39189, 39190, 39191, 39192, 39193, 39194, 39195, 39196, 39197, 39198, 39199, 39295, 39296, 39297
39298, 39299, 39300, 39301, 39302, 39303, 39304, 39305, 39306, 39307, 39308, 39309, 39310, 39311, 39312, 39313
39409, 39410, 39411, 39412, 39413, 39414, 39415, 39416, 39417, 39418, 39419, 39420, 39421, 39422, 39423, 39424
39425, 39426, 39427, 39523, 39524, 39525, 39526, 39527, 39528, 39529, 39530, 39531, 39532, 39533, 39534, 39535
39536, 39537, 39538, 39539, 39540, 39541, 39637, 39638, 39639, 39640, 39641, 39642, 39643, 39644, 39645, 39646
39647, 39648, 39649, 39650, 39651, 39652, 39653, 39654, 39655, 39751, 39752, 39753, 39754, 39755, 39756, 39757
39758, 39759, 39760, 39761, 39762, 39763, 39764, 39765, 39766, 39767, 39768, 39769, 39865, 39866, 39867, 39868
39869, 39870, 39871, 39872, 39873, 39874, 39875, 39876, 39877, 39878, 39879, 39880, 39961, 39962, 39963, 39964
39965, 39966, 39967, 39968, 39969, 39970, 39971, 39972, 39973, 39974, 39975, 39976, 40057, 40058, 40059, 40060
40061, 40062, 40063, 40064, 40065, 40066, 40067, 40068, 40069, 40070, 40071, 40072, 40153, 40154, 40155, 40156
40157, 40158, 40159, 40160, 40161, 40162, 40163, 40164, 40165, 40166, 40167, 40168, 42385, 42386, 42387, 42388
42389, 42390, 42391, 42392, 42393, 42394, 42395, 42396, 42397, 42398, 42399, 42400, 42481, 42482, 42483, 42484
42485, 42486, 42487, 42488, 42489, 42490, 42491, 42492, 42493, 42494, 42495, 42496, 42577, 42578, 42579, 42580
42581, 42582, 42583, 42584, 42585, 42586, 42587, 42588, 42589, 42590, 42591, 42592, 42593, 42594, 42595, 42691
42692, 42693, 42694, 42695, 42696, 42697, 42698, 42699, 42700, 42701, 42702, 42703, 42704, 42705, 42706, 42707
42708, 42709, 42805, 42806, 42807, 42808, 42809, 42810, 42811, 42812, 42813, 42814, 42815, 42816, 42817, 42818
42819, 42820, 42821, 42822, 42823, 42919, 42920, 42921, 42922, 42923, 42924, 42925, 42926, 42927, 42928, 42929
42930, 42931, 42932, 42933, 42934, 42935, 42936, 42937, 43033, 43034, 43035, 43036, 43037, 43038, 43039, 43040
43041, 43042, 43043, 43044, 43045, 43046, 43047, 43048, 43049, 43050, 43051, 43147, 43148, 43149, 43150, 43151
43152, 43153, 43154, 43155, 43156, 43157, 43158, 43159, 43160, 43161, 43162, 43163, 43164, 43165, 43261, 43262
43263, 43264, 43265, 43266, 43267, 43268, 43269, 43270, 43271, 43272, 43273, 43274, 43275, 43276, 43277, 43278
43279, 43375, 43376, 43377, 43378, 43379, 43380, 43381, 43382, 43383, 43384, 43385, 43386, 43387, 43388, 43389
43390, 43391, 43392, 43393, 43489, 43490, 43491, 43492, 43493, 43494, 43495, 43496, 43497, 43498, 43499, 43500
43501, 43502, 43503, 43504, 43505, 43506, 43507, 43603, 43604, 43605, 43606, 43607, 43608, 43609, 43610, 43611
43612, 43613, 43614, 43615, 43616, 43617, 43618, 43619, 43620, 43621, 43717, 43718, 43719, 43720, 43721, 43722
43723, 43724, 43725, 43726, 43727, 43728, 43729, 43730, 43731, 43732, 43733, 43734, 43735, 43831, 43832, 43833
43834, 43835, 43836, 43837, 43838, 43839, 43840, 43841, 43842, 43843, 43844, 43845, 43846, 43847, 43848, 43849
43945, 43946, 43947, 43948, 43949, 43950, 43951, 43952, 43953, 43954, 43955, 43956, 43957, 43958, 43959, 43960
44041, 44042, 44043, 44044, 44045, 44046, 44047, 44048, 44049, 44050, 44051, 44052, 44053, 44054, 44055, 44056
*Elset, elset=__PickedSurf53_S5, internal, instance=Stent
81, 82, 83, 84, 85, 86, 87, 88, 89, 90, 91, 92, 93, 94, 95, 96
177, 178, 179, 180, 181, 182, 183, 184, 185, 186, 187, 188, 189, 190, 191, 192
273, 274, 275, 276, 277, 278, 279, 280, 281, 282, 283, 284, 285, 286, 287, 288
369, 370, 371, 372, 373, 374, 375, 376, 377, 378, 379, 380, 381, 382, 383, 384
480, 481, 482, 483, 484, 485, 486, 487, 488, 489, 490, 491, 492, 493, 494, 495
496, 497, 498, 594, 595, 596, 597, 598, 599, 600, 601, 602, 603, 604, 605, 606
607, 608, 609, 610, 611, 612, 708, 709, 710, 711, 712, 713, 714, 715, 716, 717
718, 719, 720, 721, 722, 723, 724, 725, 726, 822, 823, 824, 825, 826, 827, 828
829, 830, 831, 832, 833, 834, 835, 836, 837, 838, 839, 840, 936, 937, 938, 939
940, 941, 942, 943, 944, 945, 946, 947, 948, 949, 950, 951, 952, 953, 954, 1050
1051, 1052, 1053, 1054, 1055, 1056, 1057, 1058, 1059, 1060, 1061, 1062, 1063, 1064, 1065, 1066
1067, 1068, 1164, 1165, 1166, 1167, 1168, 1169, 1170, 1171, 1172, 1173, 1174, 1175, 1176, 1177
1178, 1179, 1180, 1181, 1182, 1278, 1279, 1280, 1281, 1282, 1283, 1284, 1285, 1286, 1287, 1288
1289, 1290, 1291, 1292, 1293, 1294, 1295, 1296, 1392, 1393, 1394, 1395, 1396, 1397, 1398, 1399
1400, 1401, 1402, 1403, 1404, 1405, 1406, 1407, 1408, 1409, 1410, 1506, 1507, 1508, 1509, 1510
1511, 1512, 1513, 1514, 1515, 1516, 1517, 1518, 1519, 1520, 1521, 1522, 1523, 1524, 1620, 1621
1622, 1623, 1624, 1625, 1626, 1627, 1628, 1629, 1630, 1631, 1632, 1633, 1634, 1635, 1636, 1637
1638, 1734, 1735, 1736, 1737, 1738, 1739, 1740, 1741, 1742, 1743, 1744, 1745, 1746, 1747, 1748
1749, 1750, 1751, 1752, 1833, 1834, 1835, 1836, 1837, 1838, 1839, 1840, 1841, 1842, 1843, 1844
1845, 1846, 1847, 1848, 1929, 1930, 1931, 1932, 1933, 1934, 1935, 1936, 1937, 1938, 1939, 1940
1941, 1942, 1943, 1944, 2025, 2026, 2027, 2028, 2029, 2030, 2031, 2032, 2033, 2034, 2035, 2036
2037, 2038, 2039, 2040, 2121, 2122, 2123, 2124, 2125, 2126, 2127, 2128, 2129, 2130, 2131, 2132
2133, 2134, 2135, 2136, 4353, 4354, 4355, 4356, 4357, 4358, 4359, 4360, 4361, 4362, 4363, 4364
4365, 4366, 4367, 4368, 4449, 4450, 4451, 4452, 4453, 4454, 4455, 4456, 4457, 4458, 4459, 4460
4461, 4462, 4463, 4464, 4560, 4561, 4562, 4563, 4564, 4565, 4566, 4567, 4568, 4569, 4570, 4571
4572, 4573, 4574, 4575, 4576, 4577, 4578, 4674, 4675, 4676, 4677, 4678, 4679, 4680, 4681, 4682
4683, 4684, 4685, 4686, 4687, 4688, 4689, 4690, 4691, 4692, 4788, 4789, 4790, 4791, 4792, 4793
4794, 4795, 4796, 4797, 4798, 4799, 4800, 4801, 4802, 4803, 4804, 4805, 4806, 4902, 4903, 4904
4905, 4906, 4907, 4908, 4909, 4910, 4911, 4912, 4913, 4914, 4915, 4916, 4917, 4918, 4919, 4920
5016, 5017, 5018, 5019, 5020, 5021, 5022, 5023, 5024, 5025, 5026, 5027, 5028, 5029, 5030, 5031
5032, 5033, 5034, 5130, 5131, 5132, 5133, 5134, 5135, 5136, 5137, 5138, 5139, 5140, 5141, 5142
5143, 5144, 5145, 5146, 5147, 5148, 5244, 5245, 5246, 5247, 5248, 5249, 5250, 5251, 5252, 5253
5254, 5255, 5256, 5257, 5258, 5259, 5260, 5261, 5262, 5358, 5359, 5360, 5361, 5362, 5363, 5364
5365, 5366, 5367, 5368, 5369, 5370, 5371, 5372, 5373, 5374, 5375, 5376, 5472, 5473, 5474, 5475
5476, 5477, 5478, 5479, 5480, 5481, 5482, 5483, 5484, 5485, 5486, 5487, 5488, 5489, 5490, 5586
5587, 5588, 5589, 5590, 5591, 5592, 5593, 5594, 5595, 5596, 5597, 5598, 5599, 5600, 5601, 5602
5603, 5604, 5700, 5701, 5702, 5703, 5704, 5705, 5706, 5707, 5708, 5709, 5710, 5711, 5712, 5713
5714, 5715, 5716, 5717, 5718, 5814, 5815, 5816, 5817, 5818, 5819, 5820, 5821, 5822, 5823, 5824
5825, 5826, 5827, 5828, 5829, 5830, 5831, 5832, 5913, 5914, 5915, 5916, 5917, 5918, 5919, 5920
5921, 5922, 5923, 5924, 5925, 5926, 5927, 5928, 6009, 6010, 6011, 6012, 6013, 6014, 6015, 6016
6017, 6018, 6019, 6020, 6021, 6022, 6023, 6024, 7857, 7858, 7859, 7860, 7861, 7862, 7863, 7864
7865, 7866, 7867, 7868, 7869, 7870, 7871, 7872, 7953, 7954, 7955, 7956, 7957, 7958, 7959, 7960
7961, 7962, 7963, 7964, 7965, 7966, 7967, 7968, 8064, 8065, 8066, 8067, 8068, 8069, 8070, 8071
8072, 8073, 8074, 8075, 8076, 8077, 8078, 8079, 8080, 8081, 8082, 8178, 8179, 8180, 8181, 8182
8183, 8184, 8185, 8186, 8187, 8188, 8189, 8190, 8191, 8192, 8193, 8194, 8195, 8196, 8292, 8293
8294, 8295, 8296, 8297, 8298, 8299, 8300, 8301, 8302, 8303, 8304, 8305, 8306, 8307, 8308, 8309
8310, 8406, 8407, 8408, 8409, 8410, 8411, 8412, 8413, 8414, 8415, 8416, 8417, 8418, 8419, 8420
8421, 8422, 8423, 8424, 8520, 8521, 8522, 8523, 8524, 8525, 8526, 8527, 8528, 8529, 8530, 8531
8532, 8533, 8534, 8535, 8536, 8537, 8538, 8634, 8635, 8636, 8637, 8638, 8639, 8640, 8641, 8642
8643, 8644, 8645, 8646, 8647, 8648, 8649, 8650, 8651, 8652, 8748, 8749, 8750, 8751, 8752, 8753
8754, 8755, 8756, 8757, 8758, 8759, 8760, 8761, 8762, 8763, 8764, 8765, 8766, 8862, 8863, 8864
8865, 8866, 8867, 8868, 8869, 8870, 8871, 8872, 8873, 8874, 8875, 8876, 8877, 8878, 8879, 8880
8976, 8977, 8978, 8979, 8980, 8981, 8982, 8983, 8984, 8985, 8986, 8987, 8988, 8989, 8990, 8991
8992, 8993, 8994, 9090, 9091, 9092, 9093, 9094, 9095, 9096, 9097, 9098, 9099, 9100, 9101, 9102
9103, 9104, 9105, 9106, 9107, 9108, 9204, 9205, 9206, 9207, 9208, 9209, 9210, 9211, 9212, 9213
9214, 9215, 9216, 9217, 9218, 9219, 9220, 9221, 9222, 9318, 9319, 9320, 9321, 9322, 9323, 9324
9325, 9326, 9327, 9328, 9329, 9330, 9331, 9332, 9333, 9334, 9335, 9336, 9417, 9418, 9419, 9420
9421, 9422, 9423, 9424, 9425, 9426, 9427, 9428, 9429, 9430, 9431, 9432, 9513, 9514, 9515, 9516
9517, 9518, 9519, 9520, 9521, 9522, 9523, 9524, 9525, 9526, 9527, 9528, 11361, 11362, 11363, 11364
11365, 11366, 11367, 11368, 11369, 11370, 11371, 11372, 11373, 11374, 11375, 11376, 11457, 11458, 11459, 11460
11461, 11462, 11463, 11464, 11465, 11466, 11467, 11468, 11469, 11470, 11471, 11472, 11553, 11554, 11555, 11556
11557, 11558, 11559, 11560, 11561, 11562, 11563, 11564, 11565, 11566, 11567, 11568, 11649, 11650, 11651, 11652
11653, 11654, 11655, 11656, 11657, 11658, 11659, 11660, 11661, 11662, 11663, 11664, 11760, 11761, 11762, 11763
11764, 11765, 11766, 11767, 11768, 11769, 11770, 11771, 11772, 11773, 11774, 11775, 11776, 11777, 11778, 11874
11875, 11876, 11877, 11878, 11879, 11880, 11881, 11882, 11883, 11884, 11885, 11886, 11887, 11888, 11889, 11890
11891, 11892, 11988, 11989, 11990, 11991, 11992, 11993, 11994, 11995, 11996, 11997, 11998, 11999, 12000, 12001
12002, 12003, 12004, 12005, 12006, 12102, 12103, 12104, 12105, 12106, 12107, 12108, 12109, 12110, 12111, 12112
12113, 12114, 12115, 12116, 12117, 12118, 12119, 12120, 12216, 12217, 12218, 12219, 12220, 12221, 12222, 12223
12224, 12225, 12226, 12227, 12228, 12229, 12230, 12231, 12232, 12233, 12234, 12330, 12331, 12332, 12333, 12334
12335, 12336, 12337, 12338, 12339, 12340, 12341, 12342, 12343, 12344, 12345, 12346, 12347, 12348, 12444, 12445
12446, 12447, 12448, 12449, 12450, 12451, 12452, 12453, 12454, 12455, 12456, 12457, 12458, 12459, 12460, 12461
12462, 12558, 12559, 12560, 12561, 12562, 12563, 12564, 12565, 12566, 12567, 12568, 12569, 12570, 12571, 12572
12573, 12574, 12575, 12576, 12672, 12673, 12674, 12675, 12676, 12677, 12678, 12679, 12680, 12681, 12682, 12683
12684, 12685, 12686, 12687, 12688, 12689, 12690, 12786, 12787, 12788, 12789, 12790, 12791, 12792, 12793, 12794
12795, 12796, 12797, 12798, 12799, 12800, 12801, 12802, 12803, 12804, 12900, 12901, 12902, 12903, 12904, 12905
12906, 12907, 12908, 12909, 12910, 12911, 12912, 12913, 12914, 12915, 12916, 12917, 12918, 13014, 13015, 13016
13017, 13018, 13019, 13020, 13021, 13022, 13023, 13024, 13025, 13026, 13027, 13028, 13029, 13030, 13031, 13032
13113, 13114, 13115, 13116, 13117, 13118, 13119, 13120, 13121, 13122, 13123, 13124, 13125, 13126, 13127, 13128
13209, 13210, 13211, 13212, 13213, 13214, 13215, 13216, 13217, 13218, 13219, 13220, 13221, 13222, 13223, 13224
13305, 13306, 13307, 13308, 13309, 13310, 13311, 13312, 13313, 13314, 13315, 13316, 13317, 13318, 13319, 13320
13401, 13402, 13403, 13404, 13405, 13406, 13407, 13408, 13409, 13410, 13411, 13412, 13413, 13414, 13415, 13416
15249, 15250, 15251, 15252, 15253, 15254, 15255, 15256, 15257, 15258, 15259, 15260, 15261, 15262, 15263, 15264
15345, 15346, 15347, 15348, 15349, 15350, 15351, 15352, 15353, 15354, 15355, 15356, 15357, 15358, 15359, 15360
15441, 15442, 15443, 15444, 15445, 15446, 15447, 15448, 15449, 15450, 15451, 15452, 15453, 15454, 15455, 15456
15537, 15538, 15539, 15540, 15541, 15542, 15543, 15544, 15545, 15546, 15547, 15548, 15549, 15550, 15551, 15552
15648, 15649, 15650, 15651, 15652, 15653, 15654, 15655, 15656, 15657, 15658, 15659, 15660, 15661, 15662, 15663
15664, 15665, 15666, 15762, 15763, 15764, 15765, 15766, 15767, 15768, 15769, 15770, 15771, 15772, 15773, 15774
15775, 15776, 15777, 15778, 15779, 15780, 15876, 15877, 15878, 15879, 15880, 15881, 15882, 15883, 15884, 15885
15886, 15887, 15888, 15889, 15890, 15891, 15892, 15893, 15894, 15990, 15991, 15992, 15993, 15994, 15995, 15996
15997, 15998, 15999, 16000, 16001, 16002, 16003, 16004, 16005, 16006, 16007, 16008, 16104, 16105, 16106, 16107
16108, 16109, 16110, 16111, 16112, 16113, 16114, 16115, 16116, 16117, 16118, 16119, 16120, 16121, 16122, 16218
16219, 16220, 16221, 16222, 16223, 16224, 16225, 16226, 16227, 16228, 16229, 16230, 16231, 16232, 16233, 16234
16235, 16236, 16332, 16333, 16334, 16335, 16336, 16337, 16338, 16339, 16340, 16341, 16342, 16343, 16344, 16345
16346, 16347, 16348, 16349, 16350, 16446, 16447, 16448, 16449, 16450, 16451, 16452, 16453, 16454, 16455, 16456
16457, 16458, 16459, 16460, 16461, 16462, 16463, 16464, 16560, 16561, 16562, 16563, 16564, 16565, 16566, 16567
16568, 16569, 16570, 16571, 16572, 16573, 16574, 16575, 16576, 16577, 16578, 16674, 16675, 16676, 16677, 16678
16679, 16680, 16681, 16682, 16683, 16684, 16685, 16686, 16687, 16688, 16689, 16690, 16691, 16692, 16788, 16789
16790, 16791, 16792, 16793, 16794, 16795, 16796, 16797, 16798, 16799, 16800, 16801, 16802, 16803, 16804, 16805
16806, 16902, 16903, 16904, 16905, 16906, 16907, 16908, 16909, 16910, 16911, 16912, 16913, 16914, 16915, 16916
16917, 16918, 16919, 16920, 17001, 17002, 17003, 17004, 17005, 17006, 17007, 17008, 17009, 17010, 17011, 17012
17013, 17014, 17015, 17016, 17097, 17098, 17099, 17100, 17101, 17102, 17103, 17104, 17105, 17106, 17107, 17108
17109, 17110, 17111, 17112, 17193, 17194, 17195, 17196, 17197, 17198, 17199, 17200, 17201, 17202, 17203, 17204
17205, 17206, 17207, 17208, 17289, 17290, 17291, 17292, 17293, 17294, 17295, 17296, 17297, 17298, 17299, 17300
17301, 17302, 17303, 17304, 19521, 19522, 19523, 19524, 19525, 19526, 19527, 19528, 19529, 19530, 19531, 19532
19533, 19534, 19535, 19536, 19617, 19618, 19619, 19620, 19621, 19622, 19623, 19624, 19625, 19626, 19627, 19628
19629, 19630, 19631, 19632, 19728, 19729, 19730, 19731, 19732, 19733, 19734, 19735, 19736, 19737, 19738, 19739
19740, 19741, 19742, 19743, 19744, 19745, 19746, 19842, 19843, 19844, 19845, 19846, 19847, 19848, 19849, 19850
19851, 19852, 19853, 19854, 19855, 19856, 19857, 19858, 19859, 19860, 19956, 19957, 19958, 19959, 19960, 19961
19962, 19963, 19964, 19965, 19966, 19967, 19968, 19969, 19970, 19971, 19972, 19973, 19974, 20070, 20071, 20072
20073, 20074, 20075, 20076, 20077, 20078, 20079, 20080, 20081, 20082, 20083, 20084, 20085, 20086, 20087, 20088
20184, 20185, 20186, 20187, 20188, 20189, 20190, 20191, 20192, 20193, 20194, 20195, 20196, 20197, 20198, 20199
20200, 20201, 20202, 20298, 20299, 20300, 20301, 20302, 20303, 20304, 20305, 20306, 20307, 20308, 20309, 20310
20311, 20312, 20313, 20314, 20315, 20316, 20412, 20413, 20414, 20415, 20416, 20417, 20418, 20419, 20420, 20421
20422, 20423, 20424, 20425, 20426, 20427, 20428, 20429, 20430, 20526, 20527, 20528, 20529, 20530, 20531, 20532
20533, 20534, 20535, 20536, 20537, 20538, 20539, 20540, 20541, 20542, 20543, 20544, 20640, 20641, 20642, 20643
20644, 20645, 20646, 20647, 20648, 20649, 20650, 20651, 20652, 20653, 20654, 20655, 20656, 20657, 20658, 20754
20755, 20756, 20757, 20758, 20759, 20760, 20761, 20762, 20763, 20764, 20765, 20766, 20767, 20768, 20769, 20770
20771, 20772, 20868, 20869, 20870, 20871, 20872, 20873, 20874, 20875, 20876, 20877, 20878, 20879, 20880, 20881
20882, 20883, 20884, 20885, 20886, 20982, 20983, 20984, 20985, 20986, 20987, 20988, 20989, 20990, 20991, 20992
20993, 20994, 20995, 20996, 20997, 20998, 20999, 21000, 21081, 21082, 21083, 21084, 21085, 21086, 21087, 21088
21089, 21090, 21091, 21092, 21093, 21094, 21095, 21096, 21177, 21178, 21179, 21180, 21181, 21182, 21183, 21184
21185, 21186, 21187, 21188, 21189, 21190, 21191, 21192, 25560, 25561, 25562, 25563, 25564, 25565, 25566, 25567
25568, 25569, 25570, 25571, 25572, 25573, 25574, 25575, 25576, 25577, 25578, 25674, 25675, 25676, 25677, 25678
25679, 25680, 25681, 25682, 25683, 25684, 25685, 25686, 25687, 25688, 25689, 25690, 25691, 25692, 25788, 25789
25790, 25791, 25792, 25793, 25794, 25795, 25796, 25797, 25798, 25799, 25800, 25801, 25802, 25803, 25804, 25805
25806, 25902, 25903, 25904, 25905, 25906, 25907, 25908, 25909, 25910, 25911, 25912, 25913, 25914, 25915, 25916
25917, 25918, 25919, 25920, 26016, 26017, 26018, 26019, 26020, 26021, 26022, 26023, 26024, 26025, 26026, 26027
26028, 26029, 26030, 26031, 26032, 26033, 26034, 26130, 26131, 26132, 26133, 26134, 26135, 26136, 26137, 26138
26139, 26140, 26141, 26142, 26143, 26144, 26145, 26146, 26147, 26148, 26244, 26245, 26246, 26247, 26248, 26249
26250, 26251, 26252, 26253, 26254, 26255, 26256, 26257, 26258, 26259, 26260, 26261, 26262, 26358, 26359, 26360
26361, 26362, 26363, 26364, 26365, 26366, 26367, 26368, 26369, 26370, 26371, 26372, 26373, 26374, 26375, 26376
26472, 26473, 26474, 26475, 26476, 26477, 26478, 26479, 26480, 26481, 26482, 26483, 26484, 26485, 26486, 26487
26488, 26489, 26490, 26586, 26587, 26588, 26589, 26590, 26591, 26592, 26593, 26594, 26595, 26596, 26597, 26598
26599, 26600, 26601, 26602, 26603, 26604, 26700, 26701, 26702, 26703, 26704, 26705, 26706, 26707, 26708, 26709
26710, 26711, 26712, 26713, 26714, 26715, 26716, 26717, 26718, 26814, 26815, 26816, 26817, 26818, 26819, 26820
26821, 26822, 26823, 26824, 26825, 26826, 26827, 26828, 26829, 26830, 26831, 26832, 29256, 29257, 29258, 29259
29260, 29261, 29262, 29263, 29264, 29265, 29266, 29267, 29268, 29269, 29270, 29271, 29272, 29273, 29274, 29370
29371, 29372, 29373, 29374, 29375, 29376, 29377, 29378, 29379, 29380, 29381, 29382, 29383, 29384, 29385, 29386
29387, 29388, 29484, 29485, 29486, 29487, 29488, 29489, 29490, 29491, 29492, 29493, 29494, 29495, 29496, 29497
29498, 29499, 29500, 29501, 29502, 29598, 29599, 29600, 29601, 29602, 29603, 29604, 29605, 29606, 29607, 29608
29609, 29610, 29611, 29612, 29613, 29614, 29615, 29616, 29712, 29713, 29714, 29715, 29716, 29717, 29718, 29719
29720, 29721, 29722, 29723, 29724, 29725, 29726, 29727, 29728, 29729, 29730, 29826, 29827, 29828, 29829, 29830
29831, 29832, 29833, 29834, 29835, 29836, 29837, 29838, 29839, 29840, 29841, 29842, 29843, 29844, 29940, 29941
29942, 29943, 29944, 29945, 29946, 29947, 29948, 29949, 29950, 29951, 29952, 29953, 29954, 29955, 29956, 29957
29958, 30054, 30055, 30056, 30057, 30058, 30059, 30060, 30061, 30062, 30063, 30064, 30065, 30066, 30067, 30068
30069, 30070, 30071, 30072, 30168, 30169, 30170, 30171, 30172, 30173, 30174, 30175, 30176, 30177, 30178, 30179
30180, 30181, 30182, 30183, 30184, 30185, 30186, 30282, 30283, 30284, 30285, 30286, 30287, 30288, 30289, 30290
30291, 30292, 30293, 30294, 30295, 30296, 30297, 30298, 30299, 30300, 30396, 30397, 30398, 30399, 30400, 30401
30402, 30403, 30404, 30405, 30406, 30407, 30408, 30409, 30410, 30411, 30412, 30413, 30414, 30510, 30511, 30512
30513, 30514, 30515, 30516, 30517, 30518, 30519, 30520, 30521, 30522, 30523, 30524, 30525, 30526, 30527, 30528
32760, 32761, 32762, 32763, 32764, 32765, 32766, 32767, 32768, 32769, 32770, 32771, 32772, 32773, 32774, 32775
32776, 32777, 32778, 32874, 32875, 32876, 32877, 32878, 32879, 32880, 32881, 32882, 32883, 32884, 32885, 32886
32887, 32888, 32889, 32890, 32891, 32892, 32988, 32989, 32990, 32991, 32992, 32993, 32994, 32995, 32996, 32997
32998, 32999, 33000, 33001, 33002, 33003, 33004, 33005, 33006, 33102, 33103, 33104, 33105, 33106, 33107, 33108
33109, 33110, 33111, 33112, 33113, 33114, 33115, 33116, 33117, 33118, 33119, 33120, 33216, 33217, 33218, 33219
33220, 33221, 33222, 33223, 33224, 33225, 33226, 33227, 33228, 33229, 33230, 33231, 33232, 33233, 33234, 33330
33331, 33332, 33333, 33334, 33335, 33336, 33337, 33338, 33339, 33340, 33341, 33342, 33343, 33344, 33345, 33346
33347, 33348, 33444, 33445, 33446, 33447, 33448, 33449, 33450, 33451, 33452, 33453, 33454, 33455, 33456, 33457
33458, 33459, 33460, 33461, 33462, 33558, 33559, 33560, 33561, 33562, 33563, 33564, 33565, 33566, 33567, 33568
33569, 33570, 33571, 33572, 33573, 33574, 33575, 33576, 33672, 33673, 33674, 33675, 33676, 33677, 33678, 33679
33680, 33681, 33682, 33683, 33684, 33685, 33686, 33687, 33688, 33689, 33690, 33786, 33787, 33788, 33789, 33790
33791, 33792, 33793, 33794, 33795, 33796, 33797, 33798, 33799, 33800, 33801, 33802, 33803, 33804, 33900, 33901
33902, 33903, 33904, 33905, 33906, 33907, 33908, 33909, 33910, 33911, 33912, 33913, 33914, 33915, 33916, 33917
33918, 34014, 34015, 34016, 34017, 34018, 34019, 34020, 34021, 34022, 34023, 34024, 34025, 34026, 34027, 34028
34029, 34030, 34031, 34032, 36648, 36649, 36650, 36651, 36652, 36653, 36654, 36655, 36656, 36657, 36658, 36659
36660, 36661, 36662, 36663, 36664, 36665, 36666, 36762, 36763, 36764, 36765, 36766, 36767, 36768, 36769, 36770
36771, 36772, 36773, 36774, 36775, 36776, 36777, 36778, 36779, 36780, 36876, 36877, 36878, 36879, 36880, 36881
36882, 36883, 36884, 36885, 36886, 36887, 36888, 36889, 36890, 36891, 36892, 36893, 36894, 36990, 36991, 36992
36993, 36994, 36995, 36996, 36997, 36998, 36999, 37000, 37001, 37002, 37003, 37004, 37005, 37006, 37007, 37008
37104, 37105, 37106, 37107, 37108, 37109, 37110, 37111, 37112, 37113, 37114, 37115, 37116, 37117, 37118, 37119
37120, 37121, 37122, 37218, 37219, 37220, 37221, 37222, 37223, 37224, 37225, 37226, 37227, 37228, 37229, 37230
37231, 37232, 37233, 37234, 37235, 37236, 37332, 37333, 37334, 37335, 37336, 37337, 37338, 37339, 37340, 37341
37342, 37343, 37344, 37345, 37346, 37347, 37348, 37349, 37350, 37446, 37447, 37448, 37449, 37450, 37451, 37452
37453, 37454, 37455, 37456, 37457, 37458, 37459, 37460, 37461, 37462, 37463, 37464, 37560, 37561, 37562, 37563
37564, 37565, 37566, 37567, 37568, 37569, 37570, 37571, 37572, 37573, 37574, 37575, 37576, 37577, 37578, 37674
37675, 37676, 37677, 37678, 37679, 37680, 37681, 37682, 37683, 37684, 37685, 37686, 37687, 37688, 37689, 37690
37691, 37692, 37788, 37789, 37790, 37791, 37792, 37793, 37794, 37795, 37796, 37797, 37798, 37799, 37800, 37801
37802, 37803, 37804, 37805, 37806, 37902, 37903, 37904, 37905, 37906, 37907, 37908, 37909, 37910, 37911, 37912
37913, 37914, 37915, 37916, 37917, 37918, 37919, 37920, 40728, 40729, 40730, 40731, 40732, 40733, 40734, 40735
40736, 40737, 40738, 40739, 40740, 40741, 40742, 40743, 40744, 40745, 40746, 40842, 40843, 40844, 40845, 40846
40847, 40848, 40849, 40850, 40851, 40852, 40853, 40854, 40855, 40856, 40857, 40858, 40859, 40860, 40956, 40957
40958, 40959, 40960, 40961, 40962, 40963, 40964, 40965, 40966, 40967, 40968, 40969, 40970, 40971, 40972, 40973
40974, 41070, 41071, 41072, 41073, 41074, 41075, 41076, 41077, 41078, 41079, 41080, 41081, 41082, 41083, 41084
41085, 41086, 41087, 41088, 41184, 41185, 41186, 41187, 41188, 41189, 41190, 41191, 41192, 41193, 41194, 41195
41196, 41197, 41198, 41199, 41200, 41201, 41202, 41298, 41299, 41300, 41301, 41302, 41303, 41304, 41305, 41306
41307, 41308, 41309, 41310, 41311, 41312, 41313, 41314, 41315, 41316, 41412, 41413, 41414, 41415, 41416, 41417
41418, 41419, 41420, 41421, 41422, 41423, 41424, 41425, 41426, 41427, 41428, 41429, 41430, 41526, 41527, 41528
41529, 41530, 41531, 41532, 41533, 41534, 41535, 41536, 41537, 41538, 41539, 41540, 41541, 41542, 41543, 41544
41640, 41641, 41642, 41643, 41644, 41645, 41646, 41647, 41648, 41649, 41650, 41651, 41652, 41653, 41654, 41655
41656, 41657, 41658, 41754, 41755, 41756, 41757, 41758, 41759, 41760, 41761, 41762, 41763, 41764, 41765, 41766
41767, 41768, 41769, 41770, 41771, 41772, 41868, 41869, 41870, 41871, 41872, 41873, 41874, 41875, 41876, 41877
41878, 41879, 41880, 41881, 41882, 41883, 41884, 41885, 41886, 41982, 41983, 41984, 41985, 41986, 41987, 41988
41989, 41990, 41991, 41992, 41993, 41994, 41995, 41996, 41997, 41998, 41999, 42000, 44616, 44617, 44618, 44619
44620, 44621, 44622, 44623, 44624, 44625, 44626, 44627, 44628, 44629, 44630, 44631, 44632, 44633, 44634, 44730
44731, 44732, 44733, 44734, 44735, 44736, 44737, 44738, 44739, 44740, 44741, 44742, 44743, 44744, 44745, 44746
44747, 44748, 44844, 44845, 44846, 44847, 44848, 44849, 44850, 44851, 44852, 44853, 44854, 44855, 44856, 44857
44858, 44859, 44860, 44861, 44862, 44958, 44959, 44960, 44961, 44962, 44963, 44964, 44965, 44966, 44967, 44968
44969, 44970, 44971, 44972, 44973, 44974, 44975, 44976, 45072, 45073, 45074, 45075, 45076, 45077, 45078, 45079
45080, 45081, 45082, 45083, 45084, 45085, 45086, 45087, 45088, 45089, 45090, 45186, 45187, 45188, 45189, 45190
45191, 45192, 45193, 45194, 45195, 45196, 45197, 45198, 45199, 45200, 45201, 45202, 45203, 45204, 45300, 45301
45302, 45303, 45304, 45305, 45306, 45307, 45308, 45309, 45310, 45311, 45312, 45313, 45314, 45315, 45316, 45317
45318, 45414, 45415, 45416, 45417, 45418, 45419, 45420, 45421, 45422, 45423, 45424, 45425, 45426, 45427, 45428
45429, 45430, 45431, 45432, 45528, 45529, 45530, 45531, 45532, 45533, 45534, 45535, 45536, 45537, 45538, 45539
45540, 45541, 45542, 45543, 45544, 45545, 45546, 45642, 45643, 45644, 45645, 45646, 45647, 45648, 45649, 45650
45651, 45652, 45653, 45654, 45655, 45656, 45657, 45658, 45659, 45660, 45756, 45757, 45758, 45759, 45760, 45761
45762, 45763, 45764, 45765, 45766, 45767, 45768, 45769, 45770, 45771, 45772, 45773, 45774, 45870, 45871, 45872
45873, 45874, 45875, 45876, 45877, 45878, 45879, 45880, 45881, 45882, 45883, 45884, 45885, 45886, 45887, 45888
*Surface, type=ELEMENT, name=_PickedSurf53, internal
__PickedSurf53_S1, S1
__PickedSurf53_S2, S2
__PickedSurf53_S3, S3
__PickedSurf53_S5, S5
*Nset, nset="_T-Datum csys-1", internal
_PickedSet48,
_PickedSet49,
Set-1,
Set-2,
*Transform, nset="_T-Datum csys-1", type=C
0., 0., 0., -1., 0., 0.
** Constraint: Constraint-1
*Equation
2
Set-1, 3, 1.
Set-2, 3, -1.
*End Assembly
*Amplitude, name=Amp-2, time=TOTAL TIME, definition=SMOOTH STEP
0., 0., 1., 1., 1.8, 0.85, 1.9, 0.8
2., 0.
*Amplitude, name=Amp-3, definition=SMOOTH STEP
0., 0., 1., 1.
*Amplitude, name=Deploy, time=TOTAL TIME, definition=SMOOTH STEP
0., 0., 1., 1., 1.5, -0.2
**
** MATERIALS
**
*Material, name=Iron
*Density
1e-06,
*Elastic
211000., 0.3
*Plastic
138.09, 0.
231., 0.0481364
308.2, 0.139108
352.5, 0.22249
*Material, name=Magnesium
*Density
1.74e-06,
*Depvar, delete=20
30,
*User Material, constants=6
44000., 0.35, 138.7, 16., 165., 0.025
*Material, name=Plate
*Density
1e-05,
*Elastic
2000., 0.3
*Material, name=Steel
*Density
1e-06,
*Elastic
190000., 0.3
*Plastic
380.76, 0.
605., 0.0933122
804., 0.180324
1050., 0.334474
1140.05, 0.410112
*Material, name=cocr
*Density
1e-06,
*Elastic
243000., 0.3
*Plastic
676.875, 0.
902., 0.0925363
1110., 0.179548
1470., 0.333698
1558.75, 0.36879
*Material, name=plla
*Density
1e-06,
*Elastic
2730., 0.4
*Plastic
16.0938, 0.
29.15, 0.0894665
34.8, 0.176478
39.65, 0.256521
48.98, 0.451581
**
** INTERACTION PROPERTIES
**
*Surface Interaction, name=GeneralProps
*Friction, exponential decay
0.2, 0., 0.
*Surface Behavior, pressure-overclosure=HARD
**
** BOUNDARY CONDITIONS
**
** Name: BC-1 Type: Displacement/Rotation
*Boundary
_PickedSet48, 3, 3
** ----------------------------------------------------------------
**
** STEP: Deploy
**
*Step, name=Deploy
*Dynamic, Explicit
, 1.
*Bulk Viscosity
0.06, 1.2
** Mass Scaling: Semi-Automatic
** Whole Model
*Fixed Mass Scaling, dt=5e-06, type=below min
**
** BOUNDARY CONDITIONS
**
** Name: BC-2 Type: Displacement/Rotation
*Boundary
_PickedSet49, 2, 2
**
** LOADS
**
** Name: Load-1 Type: Pressure
*Dsload, amplitude=Amp-3
_PickedSurf53, P, 2.
**
** INTERACTIONS
**
** Interaction: GeneralProps
*Contact, op=NEW
*Contact Inclusions, ALL EXTERIOR
*Contact Property Assignment
, , GeneralProps
**
** OUTPUT REQUESTS
**
*Restart, write, number interval=5, time marks=NO
**
** FIELD OUTPUT: F-Output-1
**
*Output, field, number interval=100
*Node Output
A, RF, U, V
*Element Output, directions=YES
LE, PE, PEEQ, S, SDV, STATUS
*Contact Output
CSTRESS,
**
** HISTORY OUTPUT: H-Output-1
**
*Output, history, variable=PRESELECT
*End Step

View file

@ -0,0 +1,875 @@
*Heading
** Job name: Press_Mag Model name: Model-1
** Generated by: Abaqus/CAE 6.10-1
*Preprint, echo=NO, model=NO, history=NO, contact=NO
**
** PARTS
**
**
** ASSEMBLY
**
*Assembly, name=Assembly
**
*Instance, library=Full_Mg, instance=Stent
**
** PREDEFINED FIELD
**
** Name: Predefined Field-1 Type: Initial State
*Import, state=yes, update=no
*End Instance
**
*Nset, nset=_PickedSet48, internal, instance=Stent
337, 338, 339, 340, 381, 382, 383, 384, 425, 426, 427, 428, 469, 470, 471, 472
513, 514, 515, 516, 557, 558, 559, 560, 5663, 5664, 5665, 5666, 5667, 5698, 5699, 5700
5701, 5702, 5703, 5704, 5705, 5706, 5707, 5708, 6360, 6361, 6362, 6363, 6364, 6395, 6396, 6397
6398, 6399, 6415, 6416, 7083, 7084, 7085, 7086, 7087, 7118, 7119, 7120, 7121, 7122, 7123, 7124
7784, 7785, 7786, 7787, 7788, 7819, 7820, 7821, 7822, 7823, 7839, 7840, 8523, 8524, 8525, 8526
8527, 8558, 8559, 8560, 8561, 8562, 8563, 8564, 8565, 8566, 8567, 8568, 9228, 9229, 9230, 9231
9232, 9263, 9264, 9265, 9266, 9267, 9283, 9284, 9285, 9286, 9287, 9288, 29141, 29142, 29143, 29144
29145, 29146, 29147, 29148, 29149, 29150, 29151, 29152, 29153, 29154, 29155, 31546, 31547, 31548, 31549, 31550
33881, 33882, 33883, 33884, 33885, 36356, 36357, 36358, 36359, 36360, 38911, 38912, 38913, 38914, 38915, 38916
38917, 38918, 38919, 38920, 38921, 38922, 38923, 38924, 38925, 41396, 41397, 41398, 41399, 41400, 41401, 41402
41403, 41404, 41405, 41406, 41407, 41408, 41409, 41410
*Nset, nset=_PickedSet49, internal, instance=Stent
5704, 5707, 6415, 6416, 7124, 7839, 7840, 8564, 8567, 9284, 9287, 29146, 29147, 29148, 29149, 29150
31546, 31547, 31548, 31549, 31550, 33881, 33882, 33883, 33884, 33885, 36356, 36357, 36358, 36359, 36360, 38916
38917, 38918, 38919, 38920, 41401, 41402, 41403, 41404, 41405, 50745
*Nset, nset=Set-1, instance=Stent
49, 50, 51, 52, 97, 98, 99, 100, 145, 146, 147, 148, 193, 194, 195, 196
241, 242, 243, 244, 289, 290, 291, 292, 1264, 1265, 1266, 1267, 1268, 1299, 1300, 1301
1302, 1303, 1319, 1320, 1321, 1322, 1323, 1324, 2003, 2004, 2005, 2006, 2007, 2038, 2039, 2040
2041, 2042, 2043, 2044, 2708, 2709, 2710, 2711, 2712, 2743, 2744, 2745, 2746, 2747, 2763, 2764
3455, 3456, 3457, 3458, 3459, 3490, 3491, 3492, 3493, 3494, 3495, 3496, 4180, 4181, 4182, 4183
4184, 4215, 4216, 4217, 4218, 4219, 4235, 4236, 4237, 4238, 4239, 4240, 4919, 4920, 4921, 4922
4923, 4954, 4955, 4956, 4957, 4958, 4959, 4960, 14341, 14342, 14343, 14344, 14345, 14346, 14347, 14349
14350, 14351, 14352, 14353, 14354, 14355, 16751, 16752, 16753, 16754, 16755, 19091, 19092, 19093, 19094, 19095
21581, 21582, 21583, 21584, 21585, 24151, 24152, 24153, 24154, 24155, 24156, 24157, 24158, 24159, 24160, 24161
24162, 24163, 24164, 24165, 26561, 26562, 26563, 26564, 26565
*Nset, nset=Set-2, instance=Stent
14348,
*Elset, elset=__PickedSurf53_S1, internal, instance=Stent
46273, 46274, 46275, 46276, 46277, 46278, 46279, 46280, 46281, 46282, 46283, 46284, 46285, 46286, 46287, 46288
46289, 46290, 46291, 46292, 46293, 46294, 46295, 46296, 46297, 46298, 46299, 46300, 46301, 46302, 46303, 46304
46305, 46306, 46307, 46308, 46309, 46310, 46311, 46312, 46313, 46314, 46315, 46316, 46317, 46318, 46319, 46320
46321, 46322, 46323, 46324, 46325, 46326, 46327, 46328, 46329, 46330, 46331, 46332, 46333, 46334, 46335, 46336
46337, 46338, 46339, 46340, 46341, 46342, 46343, 46344, 46345, 46346, 46347, 46348, 46349, 46350, 46351, 46352
46353, 46354, 46355, 46356, 46357, 46358, 46359, 46360, 46361, 46362, 46363, 46364, 46365, 46366, 46367, 46368
46369, 46370, 46371, 46372, 46373, 46374, 46375, 46376, 46377, 46378, 46379, 46380, 46381, 46382, 46383, 46384
46385, 46386, 46387, 46388, 46389, 46390, 46391, 46392, 46393, 46394, 46395, 46396, 46397, 46398, 46399, 46400
46401, 46402, 46403, 46404, 46405, 46406, 46407, 46408, 46409, 46410, 46411, 46412, 46413, 46414, 46415, 46416
46417, 46418, 46419, 46420, 46421, 46422, 46423, 46424, 46425, 46426, 46427, 46428, 46429, 46430, 46431, 46432
46433, 46434, 46435, 46436, 46437, 46438, 46439, 46440, 46441, 46442, 46443, 46444, 46445, 46446, 46447, 46448
46449, 46450, 46451, 46452, 48433, 48434, 48435, 48436, 48437, 48438, 48439, 48440, 48441, 48442, 48443, 48444
48445, 48446, 48447, 48448, 48449, 48450, 48451, 48452, 48453, 48454, 48455, 48456, 48457, 48458, 48459, 48460
48461, 48462, 48463, 48464, 48465, 48466, 48467, 48468, 48469, 48470, 48471, 48472, 48473, 48474, 48475, 48476
48477, 48478, 48479, 48480, 48481, 48482, 48483, 48484, 48485, 48486, 48487, 48488, 48489, 48490, 48491, 48492
48493, 48494, 48495, 48496, 48497, 48498, 48499, 48500, 48501, 48502, 48503, 48504, 48505, 48506, 48507, 48508
48509, 48510, 48511, 48512, 48513, 48514, 48515, 48516, 48517, 48518, 48519, 48520, 48521, 48522, 48523, 48524
48525, 48526, 48527, 48528, 48529, 48530, 48531, 48532, 48533, 48534, 48535, 48536, 48537, 48538, 48539, 48540
48541, 48542, 48543, 48544, 48545, 48546, 48547, 48548, 48549, 48550, 48551, 48552, 48553, 48554, 48555, 48556
48557, 48558, 48559, 48560, 48561, 48562, 48563, 48564, 48565, 48566, 48567, 48568, 48569, 48570, 48571, 48572
48573, 48574, 48575, 48576, 48577, 48578, 48579, 48580, 48581, 48582, 48583, 48584, 48585, 48586, 48587, 48588
48589, 48590, 48591, 48592, 48593, 48594, 48595, 48596, 48597, 48598, 48599, 48600, 50449, 50450, 50451, 50452
50453, 50454, 50455, 50456, 50457, 50458, 50459, 50460, 50461, 50462, 50463, 50464, 50465, 50466, 50467, 50468
50469, 50470, 50471, 50472, 50473, 50474, 50475, 50476, 50477, 50478, 50479, 50480, 50481, 50482, 50483, 50484
50485, 50486, 50487, 50488, 50489, 50490, 50491, 50492, 50493, 50494, 50495, 50496, 50497, 50498, 50499, 50500
50501, 50502, 50503, 50504, 50505, 50506, 50507, 50508, 50509, 50510, 50511, 50512, 50513, 50514, 50515, 50516
50517, 50518, 50519, 50520, 50521, 50522, 50523, 50524, 50525, 50526, 50527, 50528, 50529, 50530, 50531, 50532
50533, 50534, 50535, 50536, 50537, 50538, 50539, 50540, 50541, 50542, 50543, 50544, 50545, 50546, 50547, 50548
50549, 50550, 50551, 50552, 50553, 50554, 50555, 50556, 50557, 50558, 50559, 50560, 50561, 50562, 50563, 50564
50565, 50566, 50567, 50568, 50569, 50570, 50571, 50572, 50573, 50574, 50575, 50576, 50577, 50578, 50579, 50580
50581, 50582, 50583, 50584, 50585, 50586, 50587, 50588, 50589, 50590, 50591, 50592, 50593, 50594, 50595, 50596
50597, 50598, 50599, 50600, 50601, 50602, 50603, 50604, 50605, 50606, 50607, 50608, 50609, 50610, 50611, 50612
50613, 50614, 50615, 50616, 52465, 52466, 52467, 52468, 52469, 52470, 52471, 52472, 52473, 52474, 52475, 52476
52477, 52478, 52479, 52480, 52481, 52482, 52483, 52484, 52485, 52486, 52487, 52488, 52489, 52490, 52491, 52492
52493, 52494, 52495, 52496, 52497, 52498, 52499, 52500, 52501, 52502, 52503, 52504, 52505, 52506, 52507, 52508
52509, 52510, 52511, 52512, 52513, 52514, 52515, 52516, 52517, 52518, 52519, 52520, 52521, 52522, 52523, 52524
52525, 52526, 52527, 52528, 52529, 52530, 52531, 52532, 52533, 52534, 52535, 52536, 52537, 52538, 52539, 52540
52541, 52542, 52543, 52544, 52545, 52546, 52547, 52548, 52549, 52550, 52551, 52552, 52553, 52554, 52555, 52556
52557, 52558, 52559, 52560, 52561, 52562, 52563, 52564, 52565, 52566, 52567, 52568, 52569, 52570, 52571, 52572
52573, 52574, 52575, 52576, 52577, 52578, 52579, 52580, 52581, 52582, 52583, 52584, 52585, 52586, 52587, 52588
52589, 52590, 52591, 52592, 52593, 52594, 52595, 52596, 52597, 52598, 52599, 52600, 52601, 52602, 52603, 52604
52605, 52606, 52607, 52608, 52609, 52610, 52611, 52612, 52613, 52614, 52615, 52616, 52617, 52618, 52619, 52620
52621, 52622, 52623, 52624, 52625, 52626, 52627, 52628, 52629, 52630, 52631, 52632, 52633, 52634, 52635, 52636
52637, 52638, 52639, 52640, 52641, 52642, 52643, 52644, 54553, 54554, 54555, 54556, 54557, 54558, 54559, 54560
54561, 54562, 54563, 54564, 54565, 54566, 54567, 54568, 54569, 54570, 54571, 54572, 54573, 54574, 54575, 54576
54577, 54578, 54579, 54580, 54581, 54582, 54583, 54584, 54585, 54586, 54587, 54588, 54589, 54590, 54591, 54592
54593, 54594, 54595, 54596, 54597, 54598, 54599, 54600, 54601, 54602, 54603, 54604, 54605, 54606, 54607, 54608
54609, 54610, 54611, 54612, 54613, 54614, 54615, 54616, 54617, 54618, 54619, 54620, 54621, 54622, 54623, 54624
54625, 54626, 54627, 54628, 54629, 54630, 54631, 54632, 54633, 54634, 54635, 54636, 54637, 54638, 54639, 54640
54641, 54642, 54643, 54644, 54645, 54646, 54647, 54648, 54649, 54650, 54651, 54652, 54653, 54654, 54655, 54656
54657, 54658, 54659, 54660, 54661, 54662, 54663, 54664, 54665, 54666, 54667, 54668, 54669, 54670, 54671, 54672
54673, 54674, 54675, 54676, 54677, 54678, 54679, 54680, 54681, 54682, 54683, 54684, 54685, 54686, 54687, 54688
54689, 54690, 54691, 54692, 54693, 54694, 54695, 54696, 54697, 54698, 54699, 54700, 54701, 54702, 54703, 54704
54705, 54706, 54707, 54708, 54709, 54710, 54711, 54712, 54713, 54714, 54715, 54716, 54717, 54718, 54719, 54720
54721, 54722, 54723, 54724, 54725, 54726, 54727, 54728, 54729, 54730, 54731, 54732, 56713, 56714, 56715, 56716
56717, 56718, 56719, 56720, 56721, 56722, 56723, 56724, 56725, 56726, 56727, 56728, 56729, 56730, 56731, 56732
56733, 56734, 56735, 56736, 56737, 56738, 56739, 56740, 56741, 56742, 56743, 56744, 56745, 56746, 56747, 56748
56749, 56750, 56751, 56752, 56753, 56754, 56755, 56756, 56757, 56758, 56759, 56760, 56761, 56762, 56763, 56764
56765, 56766, 56767, 56768, 56769, 56770, 56771, 56772, 56773, 56774, 56775, 56776, 56777, 56778, 56779, 56780
56781, 56782, 56783, 56784, 56785, 56786, 56787, 56788, 56789, 56790, 56791, 56792, 56793, 56794, 56795, 56796
56797, 56798, 56799, 56800, 56801, 56802, 56803, 56804, 56805, 56806, 56807, 56808, 56809, 56810, 56811, 56812
56813, 56814, 56815, 56816, 56817, 56818, 56819, 56820, 56821, 56822, 56823, 56824, 56825, 56826, 56827, 56828
56829, 56830, 56831, 56832, 56833, 56834, 56835, 56836, 56837, 56838, 56839, 56840, 56841, 56842, 56843, 56844
56845, 56846, 56847, 56848, 56849, 56850, 56851, 56852, 56853, 56854, 56855, 56856, 56857, 56858, 56859, 56860
56861, 56862, 56863, 56864, 56865, 56866, 56867, 56868, 56869, 56870, 56871, 56872, 56873, 56874, 56875, 56876
56877, 56878, 56879, 56880, 59809, 59810, 59811, 59812, 59813, 59814, 59815, 59816, 59817, 59818, 59819, 59820
59821, 59822, 59823, 59824, 59825, 59826, 59827, 59828, 59829, 59830, 59831, 59832, 59833, 59834, 59835, 59836
59837, 59838, 59839, 59840, 59841, 59842, 59843, 59844, 59845, 59846, 59847, 59848, 59849, 59850, 59851, 59852
59853, 59854, 59855, 59856, 59857, 59858, 59859, 59860, 59861, 59862, 59863, 59864, 59865, 59866, 59867, 59868
59869, 59870, 59871, 59872, 59873, 59874, 59875, 59876, 59877, 59878, 59879, 59880, 59881, 59882, 59883, 59884
59885, 59886, 59887, 59888, 59889, 59890, 59891, 59892, 59893, 59894, 59895, 59896, 59897, 59898, 59899, 59900
59901, 59902, 59903, 59904, 59905, 59906, 59907, 59908, 59909, 59910, 59911, 59912, 59913, 59914, 59915, 59916
59917, 59918, 59919, 59920, 59921, 59922, 59923, 59924, 59925, 59926, 59927, 59928, 59929, 59930, 59931, 59932
59933, 59934, 59935, 59936, 59937, 59938, 59939, 59940, 59941, 59942, 59943, 59944, 59945, 59946, 59947, 59948
59949, 59950, 59951, 59952, 59953, 59954, 59955, 59956, 59957, 59958, 59959, 59960, 59961, 59962, 59963, 59964
59965, 59966, 59967, 59968, 59969, 59970, 59971, 59972, 59973, 59974, 59975, 59976, 59977, 59978, 59979, 59980
59981, 59982, 59983, 59984, 59985, 59986, 59987, 59988, 61897, 61898, 61899, 61900, 61901, 61902, 61903, 61904
61905, 61906, 61907, 61908, 61909, 61910, 61911, 61912, 61913, 61914, 61915, 61916, 61917, 61918, 61919, 61920
61921, 61922, 61923, 61924, 61925, 61926, 61927, 61928, 61929, 61930, 61931, 61932, 61933, 61934, 61935, 61936
61937, 61938, 61939, 61940, 61941, 61942, 61943, 61944, 61945, 61946, 61947, 61948, 61949, 61950, 61951, 61952
61953, 61954, 61955, 61956, 61957, 61958, 61959, 61960, 61961, 61962, 61963, 61964, 61965, 61966, 61967, 61968
61969, 61970, 61971, 61972, 61973, 61974, 61975, 61976, 61977, 61978, 61979, 61980, 61981, 61982, 61983, 61984
61985, 61986, 61987, 61988, 61989, 61990, 61991, 61992, 61993, 61994, 61995, 61996, 61997, 61998, 61999, 62000
62001, 62002, 62003, 62004, 62005, 62006, 62007, 62008, 62009, 62010, 62011, 62012, 62013, 62014, 62015, 62016
62017, 62018, 62019, 62020, 62021, 62022, 62023, 62024, 62025, 62026, 62027, 62028, 62029, 62030, 62031, 62032
62033, 62034, 62035, 62036, 62037, 62038, 62039, 62040, 62041, 62042, 62043, 62044, 62045, 62046, 62047, 62048
62049, 62050, 62051, 62052, 62053, 62054, 62055, 62056, 62057, 62058, 62059, 62060, 62061, 62062, 62063, 62064
63913, 63914, 63915, 63916, 63917, 63918, 63919, 63920, 63921, 63922, 63923, 63924, 63925, 63926, 63927, 63928
63929, 63930, 63931, 63932, 63933, 63934, 63935, 63936, 63937, 63938, 63939, 63940, 63941, 63942, 63943, 63944
63945, 63946, 63947, 63948, 63949, 63950, 63951, 63952, 63953, 63954, 63955, 63956, 63957, 63958, 63959, 63960
63961, 63962, 63963, 63964, 63965, 63966, 63967, 63968, 63969, 63970, 63971, 63972, 63973, 63974, 63975, 63976
63977, 63978, 63979, 63980, 63981, 63982, 63983, 63984, 63985, 63986, 63987, 63988, 63989, 63990, 63991, 63992
63993, 63994, 63995, 63996, 63997, 63998, 63999, 64000, 64001, 64002, 64003, 64004, 64005, 64006, 64007, 64008
64009, 64010, 64011, 64012, 64013, 64014, 64015, 64016, 64017, 64018, 64019, 64020, 64021, 64022, 64023, 64024
64025, 64026, 64027, 64028, 64029, 64030, 64031, 64032, 64033, 64034, 64035, 64036, 64037, 64038, 64039, 64040
64041, 64042, 64043, 64044, 64045, 64046, 64047, 64048, 64049, 64050, 64051, 64052, 64053, 64054, 64055, 64056
64057, 64058, 64059, 64060, 64061, 64062, 64063, 64064, 64065, 64066, 64067, 64068, 64069, 64070, 64071, 64072
64073, 64074, 64075, 64076, 64077, 64078, 64079, 64080, 66001, 66002, 66003, 66004, 66005, 66006, 66007, 66008
66009, 66010, 66011, 66012, 66013, 66014, 66015, 66016, 66017, 66018, 66019, 66020, 66021, 66022, 66023, 66024
66025, 66026, 66027, 66028, 66029, 66030, 66031, 66032, 66033, 66034, 66035, 66036, 66037, 66038, 66039, 66040
66041, 66042, 66043, 66044, 66045, 66046, 66047, 66048, 66049, 66050, 66051, 66052, 66053, 66054, 66055, 66056
66057, 66058, 66059, 66060, 66061, 66062, 66063, 66064, 66065, 66066, 66067, 66068, 66069, 66070, 66071, 66072
66073, 66074, 66075, 66076, 66077, 66078, 66079, 66080, 66081, 66082, 66083, 66084, 66085, 66086, 66087, 66088
66089, 66090, 66091, 66092, 66093, 66094, 66095, 66096, 66097, 66098, 66099, 66100, 66101, 66102, 66103, 66104
66105, 66106, 66107, 66108, 66109, 66110, 66111, 66112, 66113, 66114, 66115, 66116, 66117, 66118, 66119, 66120
66121, 66122, 66123, 66124, 66125, 66126, 66127, 66128, 66129, 66130, 66131, 66132, 66133, 66134, 66135, 66136
66137, 66138, 66139, 66140, 66141, 66142, 66143, 66144, 66145, 66146, 66147, 66148, 66149, 66150, 66151, 66152
66153, 66154, 66155, 66156, 66157, 66158, 66159, 66160, 66161, 66162, 66163, 66164, 66165, 66166, 66167, 66168
68089, 68090, 68091, 68092, 68093, 68094, 68095, 68096, 68097, 68098, 68099, 68100, 68101, 68102, 68103, 68104
68105, 68106, 68107, 68108, 68109, 68110, 68111, 68112, 68113, 68114, 68115, 68116, 68117, 68118, 68119, 68120
68121, 68122, 68123, 68124, 68125, 68126, 68127, 68128, 68129, 68130, 68131, 68132, 68133, 68134, 68135, 68136
68137, 68138, 68139, 68140, 68141, 68142, 68143, 68144, 68145, 68146, 68147, 68148, 68149, 68150, 68151, 68152
68153, 68154, 68155, 68156, 68157, 68158, 68159, 68160, 68161, 68162, 68163, 68164, 68165, 68166, 68167, 68168
68169, 68170, 68171, 68172, 68173, 68174, 68175, 68176, 68177, 68178, 68179, 68180, 68181, 68182, 68183, 68184
68185, 68186, 68187, 68188, 68189, 68190, 68191, 68192, 68193, 68194, 68195, 68196, 68197, 68198, 68199, 68200
68201, 68202, 68203, 68204, 68205, 68206, 68207, 68208, 68209, 68210, 68211, 68212, 68213, 68214, 68215, 68216
68217, 68218, 68219, 68220, 68221, 68222, 68223, 68224, 68225, 68226, 68227, 68228, 68229, 68230, 68231, 68232
68233, 68234, 68235, 68236, 68237, 68238, 68239, 68240, 68241, 68242, 68243, 68244, 68245, 68246, 68247, 68248
68249, 68250, 68251, 68252, 68253, 68254, 68255, 68256, 68257, 68258, 68259, 68260, 68261, 68262, 68263, 68264
68265, 68266, 68267, 68268, 70177, 70178, 70179, 70180, 70181, 70182, 70183, 70184, 70185, 70186, 70187, 70188
70189, 70190, 70191, 70192, 70193, 70194, 70195, 70196, 70197, 70198, 70199, 70200, 70201, 70202, 70203, 70204
70205, 70206, 70207, 70208, 70209, 70210, 70211, 70212, 70213, 70214, 70215, 70216, 70217, 70218, 70219, 70220
70221, 70222, 70223, 70224, 70225, 70226, 70227, 70228, 70229, 70230, 70231, 70232, 70233, 70234, 70235, 70236
70237, 70238, 70239, 70240, 70241, 70242, 70243, 70244, 70245, 70246, 70247, 70248, 70249, 70250, 70251, 70252
70253, 70254, 70255, 70256, 70257, 70258, 70259, 70260, 70261, 70262, 70263, 70264, 70265, 70266, 70267, 70268
70269, 70270, 70271, 70272, 70273, 70274, 70275, 70276, 70277, 70278, 70279, 70280, 70281, 70282, 70283, 70284
70285, 70286, 70287, 70288, 70289, 70290, 70291, 70292, 70293, 70294, 70295, 70296, 70297, 70298, 70299, 70300
70301, 70302, 70303, 70304, 70305, 70306, 70307, 70308, 70309, 70310, 70311, 70312, 70313, 70314, 70315, 70316
70317, 70318, 70319, 70320, 70321, 70322, 70323, 70324, 70325, 70326, 70327, 70328, 70329, 70330, 70331, 70332
70333, 70334, 70335, 70336, 70337, 70338, 70339, 70340, 70341, 70342, 70343, 70344, 70345, 70346, 70347, 70348
70349, 70350, 70351, 70352, 70353, 70354, 70355, 70356
*Elset, elset=__PickedSurf53_S2, internal, instance=Stent
48253, 48254, 48255, 48256, 48257, 48258, 48259, 48260, 48261, 48262, 48263, 48264, 48265, 48266, 48267, 48268
48269, 48270, 48271, 48272, 48273, 48274, 48275, 48276, 48277, 48278, 48279, 48280, 48281, 48282, 48283, 48284
48285, 48286, 48287, 48288, 48289, 48290, 48291, 48292, 48293, 48294, 48295, 48296, 48297, 48298, 48299, 48300
48301, 48302, 48303, 48304, 48305, 48306, 48307, 48308, 48309, 48310, 48311, 48312, 48313, 48314, 48315, 48316
48317, 48318, 48319, 48320, 48321, 48322, 48323, 48324, 48325, 48326, 48327, 48328, 48329, 48330, 48331, 48332
48333, 48334, 48335, 48336, 48337, 48338, 48339, 48340, 48341, 48342, 48343, 48344, 48345, 48346, 48347, 48348
48349, 48350, 48351, 48352, 48353, 48354, 48355, 48356, 48357, 48358, 48359, 48360, 48361, 48362, 48363, 48364
48365, 48366, 48367, 48368, 48369, 48370, 48371, 48372, 48373, 48374, 48375, 48376, 48377, 48378, 48379, 48380
48381, 48382, 48383, 48384, 48385, 48386, 48387, 48388, 48389, 48390, 48391, 48392, 48393, 48394, 48395, 48396
48397, 48398, 48399, 48400, 48401, 48402, 48403, 48404, 48405, 48406, 48407, 48408, 48409, 48410, 48411, 48412
48413, 48414, 48415, 48416, 48417, 48418, 48419, 48420, 48421, 48422, 48423, 48424, 48425, 48426, 48427, 48428
48429, 48430, 48431, 48432, 50281, 50282, 50283, 50284, 50285, 50286, 50287, 50288, 50289, 50290, 50291, 50292
50293, 50294, 50295, 50296, 50297, 50298, 50299, 50300, 50301, 50302, 50303, 50304, 50305, 50306, 50307, 50308
50309, 50310, 50311, 50312, 50313, 50314, 50315, 50316, 50317, 50318, 50319, 50320, 50321, 50322, 50323, 50324
50325, 50326, 50327, 50328, 50329, 50330, 50331, 50332, 50333, 50334, 50335, 50336, 50337, 50338, 50339, 50340
50341, 50342, 50343, 50344, 50345, 50346, 50347, 50348, 50349, 50350, 50351, 50352, 50353, 50354, 50355, 50356
50357, 50358, 50359, 50360, 50361, 50362, 50363, 50364, 50365, 50366, 50367, 50368, 50369, 50370, 50371, 50372
50373, 50374, 50375, 50376, 50377, 50378, 50379, 50380, 50381, 50382, 50383, 50384, 50385, 50386, 50387, 50388
50389, 50390, 50391, 50392, 50393, 50394, 50395, 50396, 50397, 50398, 50399, 50400, 50401, 50402, 50403, 50404
50405, 50406, 50407, 50408, 50409, 50410, 50411, 50412, 50413, 50414, 50415, 50416, 50417, 50418, 50419, 50420
50421, 50422, 50423, 50424, 50425, 50426, 50427, 50428, 50429, 50430, 50431, 50432, 50433, 50434, 50435, 50436
50437, 50438, 50439, 50440, 50441, 50442, 50443, 50444, 50445, 50446, 50447, 50448, 52297, 52298, 52299, 52300
52301, 52302, 52303, 52304, 52305, 52306, 52307, 52308, 52309, 52310, 52311, 52312, 52313, 52314, 52315, 52316
52317, 52318, 52319, 52320, 52321, 52322, 52323, 52324, 52325, 52326, 52327, 52328, 52329, 52330, 52331, 52332
52333, 52334, 52335, 52336, 52337, 52338, 52339, 52340, 52341, 52342, 52343, 52344, 52345, 52346, 52347, 52348
52349, 52350, 52351, 52352, 52353, 52354, 52355, 52356, 52357, 52358, 52359, 52360, 52361, 52362, 52363, 52364
52365, 52366, 52367, 52368, 52369, 52370, 52371, 52372, 52373, 52374, 52375, 52376, 52377, 52378, 52379, 52380
52381, 52382, 52383, 52384, 52385, 52386, 52387, 52388, 52389, 52390, 52391, 52392, 52393, 52394, 52395, 52396
52397, 52398, 52399, 52400, 52401, 52402, 52403, 52404, 52405, 52406, 52407, 52408, 52409, 52410, 52411, 52412
52413, 52414, 52415, 52416, 52417, 52418, 52419, 52420, 52421, 52422, 52423, 52424, 52425, 52426, 52427, 52428
52429, 52430, 52431, 52432, 52433, 52434, 52435, 52436, 52437, 52438, 52439, 52440, 52441, 52442, 52443, 52444
52445, 52446, 52447, 52448, 52449, 52450, 52451, 52452, 52453, 52454, 52455, 52456, 52457, 52458, 52459, 52460
52461, 52462, 52463, 52464, 54385, 54386, 54387, 54388, 54389, 54390, 54391, 54392, 54393, 54394, 54395, 54396
54397, 54398, 54399, 54400, 54401, 54402, 54403, 54404, 54405, 54406, 54407, 54408, 54409, 54410, 54411, 54412
54413, 54414, 54415, 54416, 54417, 54418, 54419, 54420, 54421, 54422, 54423, 54424, 54425, 54426, 54427, 54428
54429, 54430, 54431, 54432, 54433, 54434, 54435, 54436, 54437, 54438, 54439, 54440, 54441, 54442, 54443, 54444
54445, 54446, 54447, 54448, 54449, 54450, 54451, 54452, 54453, 54454, 54455, 54456, 54457, 54458, 54459, 54460
54461, 54462, 54463, 54464, 54465, 54466, 54467, 54468, 54469, 54470, 54471, 54472, 54473, 54474, 54475, 54476
54477, 54478, 54479, 54480, 54481, 54482, 54483, 54484, 54485, 54486, 54487, 54488, 54489, 54490, 54491, 54492
54493, 54494, 54495, 54496, 54497, 54498, 54499, 54500, 54501, 54502, 54503, 54504, 54505, 54506, 54507, 54508
54509, 54510, 54511, 54512, 54513, 54514, 54515, 54516, 54517, 54518, 54519, 54520, 54521, 54522, 54523, 54524
54525, 54526, 54527, 54528, 54529, 54530, 54531, 54532, 54533, 54534, 54535, 54536, 54537, 54538, 54539, 54540
54541, 54542, 54543, 54544, 54545, 54546, 54547, 54548, 54549, 54550, 54551, 54552, 56533, 56534, 56535, 56536
56537, 56538, 56539, 56540, 56541, 56542, 56543, 56544, 56545, 56546, 56547, 56548, 56549, 56550, 56551, 56552
56553, 56554, 56555, 56556, 56557, 56558, 56559, 56560, 56561, 56562, 56563, 56564, 56565, 56566, 56567, 56568
56569, 56570, 56571, 56572, 56573, 56574, 56575, 56576, 56577, 56578, 56579, 56580, 56581, 56582, 56583, 56584
56585, 56586, 56587, 56588, 56589, 56590, 56591, 56592, 56593, 56594, 56595, 56596, 56597, 56598, 56599, 56600
56601, 56602, 56603, 56604, 56605, 56606, 56607, 56608, 56609, 56610, 56611, 56612, 56613, 56614, 56615, 56616
56617, 56618, 56619, 56620, 56621, 56622, 56623, 56624, 56625, 56626, 56627, 56628, 56629, 56630, 56631, 56632
56633, 56634, 56635, 56636, 56637, 56638, 56639, 56640, 56641, 56642, 56643, 56644, 56645, 56646, 56647, 56648
56649, 56650, 56651, 56652, 56653, 56654, 56655, 56656, 56657, 56658, 56659, 56660, 56661, 56662, 56663, 56664
56665, 56666, 56667, 56668, 56669, 56670, 56671, 56672, 56673, 56674, 56675, 56676, 56677, 56678, 56679, 56680
56681, 56682, 56683, 56684, 56685, 56686, 56687, 56688, 56689, 56690, 56691, 56692, 56693, 56694, 56695, 56696
56697, 56698, 56699, 56700, 56701, 56702, 56703, 56704, 56705, 56706, 56707, 56708, 56709, 56710, 56711, 56712
58561, 58562, 58563, 58564, 58565, 58566, 58567, 58568, 58569, 58570, 58571, 58572, 58573, 58574, 58575, 58576
58577, 58578, 58579, 58580, 58581, 58582, 58583, 58584, 58585, 58586, 58587, 58588, 58589, 58590, 58591, 58592
58593, 58594, 58595, 58596, 58597, 58598, 58599, 58600, 58601, 58602, 58603, 58604, 58605, 58606, 58607, 58608
58609, 58610, 58611, 58612, 58613, 58614, 58615, 58616, 58617, 58618, 58619, 58620, 58621, 58622, 58623, 58624
58625, 58626, 58627, 58628, 58629, 58630, 58631, 58632, 58633, 58634, 58635, 58636, 58637, 58638, 58639, 58640
58641, 58642, 58643, 58644, 58645, 58646, 58647, 58648, 58649, 58650, 58651, 58652, 58653, 58654, 58655, 58656
58657, 58658, 58659, 58660, 58661, 58662, 58663, 58664, 58665, 58666, 58667, 58668, 58669, 58670, 58671, 58672
58673, 58674, 58675, 58676, 58677, 58678, 58679, 58680, 58681, 58682, 58683, 58684, 58685, 58686, 58687, 58688
58689, 58690, 58691, 58692, 58693, 58694, 58695, 58696, 58697, 58698, 58699, 58700, 58701, 58702, 58703, 58704
58705, 58706, 58707, 58708, 58709, 58710, 58711, 58712, 58713, 58714, 58715, 58716, 58717, 58718, 58719, 58720
58721, 58722, 58723, 58724, 58725, 58726, 58727, 58728, 59629, 59630, 59631, 59632, 59633, 59634, 59635, 59636
59637, 59638, 59639, 59640, 59641, 59642, 59643, 59644, 59645, 59646, 59647, 59648, 59649, 59650, 59651, 59652
59653, 59654, 59655, 59656, 59657, 59658, 59659, 59660, 59661, 59662, 59663, 59664, 59665, 59666, 59667, 59668
59669, 59670, 59671, 59672, 59673, 59674, 59675, 59676, 59677, 59678, 59679, 59680, 59681, 59682, 59683, 59684
59685, 59686, 59687, 59688, 59689, 59690, 59691, 59692, 59693, 59694, 59695, 59696, 59697, 59698, 59699, 59700
59701, 59702, 59703, 59704, 59705, 59706, 59707, 59708, 59709, 59710, 59711, 59712, 59713, 59714, 59715, 59716
59717, 59718, 59719, 59720, 59721, 59722, 59723, 59724, 59725, 59726, 59727, 59728, 59729, 59730, 59731, 59732
59733, 59734, 59735, 59736, 59737, 59738, 59739, 59740, 59741, 59742, 59743, 59744, 59745, 59746, 59747, 59748
59749, 59750, 59751, 59752, 59753, 59754, 59755, 59756, 59757, 59758, 59759, 59760, 59761, 59762, 59763, 59764
59765, 59766, 59767, 59768, 59769, 59770, 59771, 59772, 59773, 59774, 59775, 59776, 59777, 59778, 59779, 59780
59781, 59782, 59783, 59784, 59785, 59786, 59787, 59788, 59789, 59790, 59791, 59792, 59793, 59794, 59795, 59796
59797, 59798, 59799, 59800, 59801, 59802, 59803, 59804, 59805, 59806, 59807, 59808, 61729, 61730, 61731, 61732
61733, 61734, 61735, 61736, 61737, 61738, 61739, 61740, 61741, 61742, 61743, 61744, 61745, 61746, 61747, 61748
61749, 61750, 61751, 61752, 61753, 61754, 61755, 61756, 61757, 61758, 61759, 61760, 61761, 61762, 61763, 61764
61765, 61766, 61767, 61768, 61769, 61770, 61771, 61772, 61773, 61774, 61775, 61776, 61777, 61778, 61779, 61780
61781, 61782, 61783, 61784, 61785, 61786, 61787, 61788, 61789, 61790, 61791, 61792, 61793, 61794, 61795, 61796
61797, 61798, 61799, 61800, 61801, 61802, 61803, 61804, 61805, 61806, 61807, 61808, 61809, 61810, 61811, 61812
61813, 61814, 61815, 61816, 61817, 61818, 61819, 61820, 61821, 61822, 61823, 61824, 61825, 61826, 61827, 61828
61829, 61830, 61831, 61832, 61833, 61834, 61835, 61836, 61837, 61838, 61839, 61840, 61841, 61842, 61843, 61844
61845, 61846, 61847, 61848, 61849, 61850, 61851, 61852, 61853, 61854, 61855, 61856, 61857, 61858, 61859, 61860
61861, 61862, 61863, 61864, 61865, 61866, 61867, 61868, 61869, 61870, 61871, 61872, 61873, 61874, 61875, 61876
61877, 61878, 61879, 61880, 61881, 61882, 61883, 61884, 61885, 61886, 61887, 61888, 61889, 61890, 61891, 61892
61893, 61894, 61895, 61896, 63745, 63746, 63747, 63748, 63749, 63750, 63751, 63752, 63753, 63754, 63755, 63756
63757, 63758, 63759, 63760, 63761, 63762, 63763, 63764, 63765, 63766, 63767, 63768, 63769, 63770, 63771, 63772
63773, 63774, 63775, 63776, 63777, 63778, 63779, 63780, 63781, 63782, 63783, 63784, 63785, 63786, 63787, 63788
63789, 63790, 63791, 63792, 63793, 63794, 63795, 63796, 63797, 63798, 63799, 63800, 63801, 63802, 63803, 63804
63805, 63806, 63807, 63808, 63809, 63810, 63811, 63812, 63813, 63814, 63815, 63816, 63817, 63818, 63819, 63820
63821, 63822, 63823, 63824, 63825, 63826, 63827, 63828, 63829, 63830, 63831, 63832, 63833, 63834, 63835, 63836
63837, 63838, 63839, 63840, 63841, 63842, 63843, 63844, 63845, 63846, 63847, 63848, 63849, 63850, 63851, 63852
63853, 63854, 63855, 63856, 63857, 63858, 63859, 63860, 63861, 63862, 63863, 63864, 63865, 63866, 63867, 63868
63869, 63870, 63871, 63872, 63873, 63874, 63875, 63876, 63877, 63878, 63879, 63880, 63881, 63882, 63883, 63884
63885, 63886, 63887, 63888, 63889, 63890, 63891, 63892, 63893, 63894, 63895, 63896, 63897, 63898, 63899, 63900
63901, 63902, 63903, 63904, 63905, 63906, 63907, 63908, 63909, 63910, 63911, 63912, 65821, 65822, 65823, 65824
65825, 65826, 65827, 65828, 65829, 65830, 65831, 65832, 65833, 65834, 65835, 65836, 65837, 65838, 65839, 65840
65841, 65842, 65843, 65844, 65845, 65846, 65847, 65848, 65849, 65850, 65851, 65852, 65853, 65854, 65855, 65856
65857, 65858, 65859, 65860, 65861, 65862, 65863, 65864, 65865, 65866, 65867, 65868, 65869, 65870, 65871, 65872
65873, 65874, 65875, 65876, 65877, 65878, 65879, 65880, 65881, 65882, 65883, 65884, 65885, 65886, 65887, 65888
65889, 65890, 65891, 65892, 65893, 65894, 65895, 65896, 65897, 65898, 65899, 65900, 65901, 65902, 65903, 65904
65905, 65906, 65907, 65908, 65909, 65910, 65911, 65912, 65913, 65914, 65915, 65916, 65917, 65918, 65919, 65920
65921, 65922, 65923, 65924, 65925, 65926, 65927, 65928, 65929, 65930, 65931, 65932, 65933, 65934, 65935, 65936
65937, 65938, 65939, 65940, 65941, 65942, 65943, 65944, 65945, 65946, 65947, 65948, 65949, 65950, 65951, 65952
65953, 65954, 65955, 65956, 65957, 65958, 65959, 65960, 65961, 65962, 65963, 65964, 65965, 65966, 65967, 65968
65969, 65970, 65971, 65972, 65973, 65974, 65975, 65976, 65977, 65978, 65979, 65980, 65981, 65982, 65983, 65984
65985, 65986, 65987, 65988, 65989, 65990, 65991, 65992, 65993, 65994, 65995, 65996, 65997, 65998, 65999, 66000
67909, 67910, 67911, 67912, 67913, 67914, 67915, 67916, 67917, 67918, 67919, 67920, 67921, 67922, 67923, 67924
67925, 67926, 67927, 67928, 67929, 67930, 67931, 67932, 67933, 67934, 67935, 67936, 67937, 67938, 67939, 67940
67941, 67942, 67943, 67944, 67945, 67946, 67947, 67948, 67949, 67950, 67951, 67952, 67953, 67954, 67955, 67956
67957, 67958, 67959, 67960, 67961, 67962, 67963, 67964, 67965, 67966, 67967, 67968, 67969, 67970, 67971, 67972
67973, 67974, 67975, 67976, 67977, 67978, 67979, 67980, 67981, 67982, 67983, 67984, 67985, 67986, 67987, 67988
67989, 67990, 67991, 67992, 67993, 67994, 67995, 67996, 67997, 67998, 67999, 68000, 68001, 68002, 68003, 68004
68005, 68006, 68007, 68008, 68009, 68010, 68011, 68012, 68013, 68014, 68015, 68016, 68017, 68018, 68019, 68020
68021, 68022, 68023, 68024, 68025, 68026, 68027, 68028, 68029, 68030, 68031, 68032, 68033, 68034, 68035, 68036
68037, 68038, 68039, 68040, 68041, 68042, 68043, 68044, 68045, 68046, 68047, 68048, 68049, 68050, 68051, 68052
68053, 68054, 68055, 68056, 68057, 68058, 68059, 68060, 68061, 68062, 68063, 68064, 68065, 68066, 68067, 68068
68069, 68070, 68071, 68072, 68073, 68074, 68075, 68076, 68077, 68078, 68079, 68080, 68081, 68082, 68083, 68084
68085, 68086, 68087, 68088, 70009, 70010, 70011, 70012, 70013, 70014, 70015, 70016, 70017, 70018, 70019, 70020
70021, 70022, 70023, 70024, 70025, 70026, 70027, 70028, 70029, 70030, 70031, 70032, 70033, 70034, 70035, 70036
70037, 70038, 70039, 70040, 70041, 70042, 70043, 70044, 70045, 70046, 70047, 70048, 70049, 70050, 70051, 70052
70053, 70054, 70055, 70056, 70057, 70058, 70059, 70060, 70061, 70062, 70063, 70064, 70065, 70066, 70067, 70068
70069, 70070, 70071, 70072, 70073, 70074, 70075, 70076, 70077, 70078, 70079, 70080, 70081, 70082, 70083, 70084
70085, 70086, 70087, 70088, 70089, 70090, 70091, 70092, 70093, 70094, 70095, 70096, 70097, 70098, 70099, 70100
70101, 70102, 70103, 70104, 70105, 70106, 70107, 70108, 70109, 70110, 70111, 70112, 70113, 70114, 70115, 70116
70117, 70118, 70119, 70120, 70121, 70122, 70123, 70124, 70125, 70126, 70127, 70128, 70129, 70130, 70131, 70132
70133, 70134, 70135, 70136, 70137, 70138, 70139, 70140, 70141, 70142, 70143, 70144, 70145, 70146, 70147, 70148
70149, 70150, 70151, 70152, 70153, 70154, 70155, 70156, 70157, 70158, 70159, 70160, 70161, 70162, 70163, 70164
70165, 70166, 70167, 70168, 70169, 70170, 70171, 70172, 70173, 70174, 70175, 70176
*Elset, elset=__PickedSurf53_S3, internal, instance=Stent
2521, 2522, 2523, 2524, 2525, 2526, 2527, 2528, 2529, 2530, 2531, 2532, 2533, 2534, 2535, 2536
2537, 2538, 2539, 2635, 2636, 2637, 2638, 2639, 2640, 2641, 2642, 2643, 2644, 2645, 2646, 2647
2648, 2649, 2650, 2651, 2652, 2653, 2749, 2750, 2751, 2752, 2753, 2754, 2755, 2756, 2757, 2758
2759, 2760, 2761, 2762, 2763, 2764, 2765, 2766, 2767, 2863, 2864, 2865, 2866, 2867, 2868, 2869
2870, 2871, 2872, 2873, 2874, 2875, 2876, 2877, 2878, 2879, 2880, 2881, 2977, 2978, 2979, 2980
2981, 2982, 2983, 2984, 2985, 2986, 2987, 2988, 2989, 2990, 2991, 2992, 2993, 2994, 2995, 3091
3092, 3093, 3094, 3095, 3096, 3097, 3098, 3099, 3100, 3101, 3102, 3103, 3104, 3105, 3106, 3107
3108, 3109, 3205, 3206, 3207, 3208, 3209, 3210, 3211, 3212, 3213, 3214, 3215, 3216, 3217, 3218
3219, 3220, 3221, 3222, 3223, 3319, 3320, 3321, 3322, 3323, 3324, 3325, 3326, 3327, 3328, 3329
3330, 3331, 3332, 3333, 3334, 3335, 3336, 3337, 3433, 3434, 3435, 3436, 3437, 3438, 3439, 3440
3441, 3442, 3443, 3444, 3445, 3446, 3447, 3448, 3449, 3450, 3451, 3547, 3548, 3549, 3550, 3551
3552, 3553, 3554, 3555, 3556, 3557, 3558, 3559, 3560, 3561, 3562, 3563, 3564, 3565, 3661, 3662
3663, 3664, 3665, 3666, 3667, 3668, 3669, 3670, 3671, 3672, 3673, 3674, 3675, 3676, 3677, 3678
3679, 3775, 3776, 3777, 3778, 3779, 3780, 3781, 3782, 3783, 3784, 3785, 3786, 3787, 3788, 3789
3790, 3791, 3792, 3793, 6217, 6218, 6219, 6220, 6221, 6222, 6223, 6224, 6225, 6226, 6227, 6228
6229, 6230, 6231, 6232, 6233, 6234, 6235, 6331, 6332, 6333, 6334, 6335, 6336, 6337, 6338, 6339
6340, 6341, 6342, 6343, 6344, 6345, 6346, 6347, 6348, 6349, 6445, 6446, 6447, 6448, 6449, 6450
6451, 6452, 6453, 6454, 6455, 6456, 6457, 6458, 6459, 6460, 6461, 6462, 6463, 6559, 6560, 6561
6562, 6563, 6564, 6565, 6566, 6567, 6568, 6569, 6570, 6571, 6572, 6573, 6574, 6575, 6576, 6577
6673, 6674, 6675, 6676, 6677, 6678, 6679, 6680, 6681, 6682, 6683, 6684, 6685, 6686, 6687, 6688
6689, 6690, 6691, 6787, 6788, 6789, 6790, 6791, 6792, 6793, 6794, 6795, 6796, 6797, 6798, 6799
6800, 6801, 6802, 6803, 6804, 6805, 6901, 6902, 6903, 6904, 6905, 6906, 6907, 6908, 6909, 6910
6911, 6912, 6913, 6914, 6915, 6916, 6917, 6918, 6919, 7015, 7016, 7017, 7018, 7019, 7020, 7021
7022, 7023, 7024, 7025, 7026, 7027, 7028, 7029, 7030, 7031, 7032, 7033, 7129, 7130, 7131, 7132
7133, 7134, 7135, 7136, 7137, 7138, 7139, 7140, 7141, 7142, 7143, 7144, 7145, 7146, 7147, 7243
7244, 7245, 7246, 7247, 7248, 7249, 7250, 7251, 7252, 7253, 7254, 7255, 7256, 7257, 7258, 7259
7260, 7261, 7357, 7358, 7359, 7360, 7361, 7362, 7363, 7364, 7365, 7366, 7367, 7368, 7369, 7370
7371, 7372, 7373, 7374, 7375, 7471, 7472, 7473, 7474, 7475, 7476, 7477, 7478, 7479, 7480, 7481
7482, 7483, 7484, 7485, 7486, 7487, 7488, 7489, 9721, 9722, 9723, 9724, 9725, 9726, 9727, 9728
9729, 9730, 9731, 9732, 9733, 9734, 9735, 9736, 9737, 9738, 9739, 9835, 9836, 9837, 9838, 9839
9840, 9841, 9842, 9843, 9844, 9845, 9846, 9847, 9848, 9849, 9850, 9851, 9852, 9853, 9949, 9950
9951, 9952, 9953, 9954, 9955, 9956, 9957, 9958, 9959, 9960, 9961, 9962, 9963, 9964, 9965, 9966
9967, 10063, 10064, 10065, 10066, 10067, 10068, 10069, 10070, 10071, 10072, 10073, 10074, 10075, 10076, 10077
10078, 10079, 10080, 10081, 10177, 10178, 10179, 10180, 10181, 10182, 10183, 10184, 10185, 10186, 10187, 10188
10189, 10190, 10191, 10192, 10193, 10194, 10195, 10291, 10292, 10293, 10294, 10295, 10296, 10297, 10298, 10299
10300, 10301, 10302, 10303, 10304, 10305, 10306, 10307, 10308, 10309, 10405, 10406, 10407, 10408, 10409, 10410
10411, 10412, 10413, 10414, 10415, 10416, 10417, 10418, 10419, 10420, 10421, 10422, 10423, 10519, 10520, 10521
10522, 10523, 10524, 10525, 10526, 10527, 10528, 10529, 10530, 10531, 10532, 10533, 10534, 10535, 10536, 10537
10633, 10634, 10635, 10636, 10637, 10638, 10639, 10640, 10641, 10642, 10643, 10644, 10645, 10646, 10647, 10648
10649, 10650, 10651, 10747, 10748, 10749, 10750, 10751, 10752, 10753, 10754, 10755, 10756, 10757, 10758, 10759
10760, 10761, 10762, 10763, 10764, 10765, 10861, 10862, 10863, 10864, 10865, 10866, 10867, 10868, 10869, 10870
10871, 10872, 10873, 10874, 10875, 10876, 10877, 10878, 10879, 10975, 10976, 10977, 10978, 10979, 10980, 10981
10982, 10983, 10984, 10985, 10986, 10987, 10988, 10989, 10990, 10991, 10992, 10993, 13609, 13610, 13611, 13612
13613, 13614, 13615, 13616, 13617, 13618, 13619, 13620, 13621, 13622, 13623, 13624, 13625, 13626, 13627, 13723
13724, 13725, 13726, 13727, 13728, 13729, 13730, 13731, 13732, 13733, 13734, 13735, 13736, 13737, 13738, 13739
13740, 13741, 13837, 13838, 13839, 13840, 13841, 13842, 13843, 13844, 13845, 13846, 13847, 13848, 13849, 13850
13851, 13852, 13853, 13854, 13855, 13951, 13952, 13953, 13954, 13955, 13956, 13957, 13958, 13959, 13960, 13961
13962, 13963, 13964, 13965, 13966, 13967, 13968, 13969, 14065, 14066, 14067, 14068, 14069, 14070, 14071, 14072
14073, 14074, 14075, 14076, 14077, 14078, 14079, 14080, 14081, 14082, 14083, 14179, 14180, 14181, 14182, 14183
14184, 14185, 14186, 14187, 14188, 14189, 14190, 14191, 14192, 14193, 14194, 14195, 14196, 14197, 14293, 14294
14295, 14296, 14297, 14298, 14299, 14300, 14301, 14302, 14303, 14304, 14305, 14306, 14307, 14308, 14309, 14310
14311, 14407, 14408, 14409, 14410, 14411, 14412, 14413, 14414, 14415, 14416, 14417, 14418, 14419, 14420, 14421
14422, 14423, 14424, 14425, 14521, 14522, 14523, 14524, 14525, 14526, 14527, 14528, 14529, 14530, 14531, 14532
14533, 14534, 14535, 14536, 14537, 14538, 14539, 14635, 14636, 14637, 14638, 14639, 14640, 14641, 14642, 14643
14644, 14645, 14646, 14647, 14648, 14649, 14650, 14651, 14652, 14653, 14749, 14750, 14751, 14752, 14753, 14754
14755, 14756, 14757, 14758, 14759, 14760, 14761, 14762, 14763, 14764, 14765, 14766, 14767, 14863, 14864, 14865
14866, 14867, 14868, 14869, 14870, 14871, 14872, 14873, 14874, 14875, 14876, 14877, 14878, 14879, 14880, 14881
17689, 17690, 17691, 17692, 17693, 17694, 17695, 17696, 17697, 17698, 17699, 17700, 17701, 17702, 17703, 17704
17705, 17706, 17707, 17803, 17804, 17805, 17806, 17807, 17808, 17809, 17810, 17811, 17812, 17813, 17814, 17815
17816, 17817, 17818, 17819, 17820, 17821, 17917, 17918, 17919, 17920, 17921, 17922, 17923, 17924, 17925, 17926
17927, 17928, 17929, 17930, 17931, 17932, 17933, 17934, 17935, 18031, 18032, 18033, 18034, 18035, 18036, 18037
18038, 18039, 18040, 18041, 18042, 18043, 18044, 18045, 18046, 18047, 18048, 18049, 18145, 18146, 18147, 18148
18149, 18150, 18151, 18152, 18153, 18154, 18155, 18156, 18157, 18158, 18159, 18160, 18161, 18162, 18163, 18259
18260, 18261, 18262, 18263, 18264, 18265, 18266, 18267, 18268, 18269, 18270, 18271, 18272, 18273, 18274, 18275
18276, 18277, 18373, 18374, 18375, 18376, 18377, 18378, 18379, 18380, 18381, 18382, 18383, 18384, 18385, 18386
18387, 18388, 18389, 18390, 18391, 18487, 18488, 18489, 18490, 18491, 18492, 18493, 18494, 18495, 18496, 18497
18498, 18499, 18500, 18501, 18502, 18503, 18504, 18505, 18601, 18602, 18603, 18604, 18605, 18606, 18607, 18608
18609, 18610, 18611, 18612, 18613, 18614, 18615, 18616, 18617, 18618, 18619, 18715, 18716, 18717, 18718, 18719
18720, 18721, 18722, 18723, 18724, 18725, 18726, 18727, 18728, 18729, 18730, 18731, 18732, 18733, 18829, 18830
18831, 18832, 18833, 18834, 18835, 18836, 18837, 18838, 18839, 18840, 18841, 18842, 18843, 18844, 18845, 18846
18847, 18943, 18944, 18945, 18946, 18947, 18948, 18949, 18950, 18951, 18952, 18953, 18954, 18955, 18956, 18957
18958, 18959, 18960, 18961, 21385, 21386, 21387, 21388, 21389, 21390, 21391, 21392, 21393, 21394, 21395, 21396
21397, 21398, 21399, 21400, 21401, 21402, 21403, 21499, 21500, 21501, 21502, 21503, 21504, 21505, 21506, 21507
21508, 21509, 21510, 21511, 21512, 21513, 21514, 21515, 21516, 21517, 21613, 21614, 21615, 21616, 21617, 21618
21619, 21620, 21621, 21622, 21623, 21624, 21625, 21626, 21627, 21628, 21629, 21630, 21631, 21727, 21728, 21729
21730, 21731, 21732, 21733, 21734, 21735, 21736, 21737, 21738, 21739, 21740, 21741, 21742, 21743, 21744, 21745
21841, 21842, 21843, 21844, 21845, 21846, 21847, 21848, 21849, 21850, 21851, 21852, 21853, 21854, 21855, 21856
21857, 21858, 21859, 21955, 21956, 21957, 21958, 21959, 21960, 21961, 21962, 21963, 21964, 21965, 21966, 21967
21968, 21969, 21970, 21971, 21972, 21973, 22069, 22070, 22071, 22072, 22073, 22074, 22075, 22076, 22077, 22078
22079, 22080, 22081, 22082, 22083, 22084, 22085, 22086, 22087, 22183, 22184, 22185, 22186, 22187, 22188, 22189
22190, 22191, 22192, 22193, 22194, 22195, 22196, 22197, 22198, 22199, 22200, 22201, 22297, 22298, 22299, 22300
22301, 22302, 22303, 22304, 22305, 22306, 22307, 22308, 22309, 22310, 22311, 22312, 22313, 22314, 22315, 22411
22412, 22413, 22414, 22415, 22416, 22417, 22418, 22419, 22420, 22421, 22422, 22423, 22424, 22425, 22426, 22427
22428, 22429, 22525, 22526, 22527, 22528, 22529, 22530, 22531, 22532, 22533, 22534, 22535, 22536, 22537, 22538
22539, 22540, 22541, 22542, 22543, 22639, 22640, 22641, 22642, 22643, 22644, 22645, 22646, 22647, 22648, 22649
22650, 22651, 22652, 22653, 22654, 22655, 22656, 22657, 22945, 22946, 22947, 22948, 22949, 22950, 22951, 22952
22953, 22954, 22955, 22956, 22957, 22958, 22959, 22960, 23041, 23042, 23043, 23044, 23045, 23046, 23047, 23048
23049, 23050, 23051, 23052, 23053, 23054, 23055, 23056, 23137, 23138, 23139, 23140, 23141, 23142, 23143, 23144
23145, 23146, 23147, 23148, 23149, 23150, 23151, 23152, 23233, 23234, 23235, 23236, 23237, 23238, 23239, 23240
23241, 23242, 23243, 23244, 23245, 23246, 23247, 23248, 23329, 23330, 23331, 23332, 23333, 23334, 23335, 23336
23337, 23338, 23339, 23340, 23341, 23342, 23343, 23344, 23345, 23346, 23347, 23443, 23444, 23445, 23446, 23447
23448, 23449, 23450, 23451, 23452, 23453, 23454, 23455, 23456, 23457, 23458, 23459, 23460, 23461, 23557, 23558
23559, 23560, 23561, 23562, 23563, 23564, 23565, 23566, 23567, 23568, 23569, 23570, 23571, 23572, 23573, 23574
23575, 23671, 23672, 23673, 23674, 23675, 23676, 23677, 23678, 23679, 23680, 23681, 23682, 23683, 23684, 23685
23686, 23687, 23688, 23689, 23785, 23786, 23787, 23788, 23789, 23790, 23791, 23792, 23793, 23794, 23795, 23796
23797, 23798, 23799, 23800, 23801, 23802, 23803, 23899, 23900, 23901, 23902, 23903, 23904, 23905, 23906, 23907
23908, 23909, 23910, 23911, 23912, 23913, 23914, 23915, 23916, 23917, 24013, 24014, 24015, 24016, 24017, 24018
24019, 24020, 24021, 24022, 24023, 24024, 24025, 24026, 24027, 24028, 24029, 24030, 24031, 24127, 24128, 24129
24130, 24131, 24132, 24133, 24134, 24135, 24136, 24137, 24138, 24139, 24140, 24141, 24142, 24143, 24144, 24145
24241, 24242, 24243, 24244, 24245, 24246, 24247, 24248, 24249, 24250, 24251, 24252, 24253, 24254, 24255, 24256
24257, 24258, 24259, 24355, 24356, 24357, 24358, 24359, 24360, 24361, 24362, 24363, 24364, 24365, 24366, 24367
24368, 24369, 24370, 24371, 24372, 24373, 24469, 24470, 24471, 24472, 24473, 24474, 24475, 24476, 24477, 24478
24479, 24480, 24481, 24482, 24483, 24484, 24485, 24486, 24487, 24583, 24584, 24585, 24586, 24587, 24588, 24589
24590, 24591, 24592, 24593, 24594, 24595, 24596, 24597, 24598, 24599, 24600, 24601, 24697, 24698, 24699, 24700
24701, 24702, 24703, 24704, 24705, 24706, 24707, 24708, 24709, 24710, 24711, 24712, 24793, 24794, 24795, 24796
24797, 24798, 24799, 24800, 24801, 24802, 24803, 24804, 24805, 24806, 24807, 24808, 24889, 24890, 24891, 24892
24893, 24894, 24895, 24896, 24897, 24898, 24899, 24900, 24901, 24902, 24903, 24904, 24985, 24986, 24987, 24988
24989, 24990, 24991, 24992, 24993, 24994, 24995, 24996, 24997, 24998, 24999, 25000, 27217, 27218, 27219, 27220
27221, 27222, 27223, 27224, 27225, 27226, 27227, 27228, 27229, 27230, 27231, 27232, 27313, 27314, 27315, 27316
27317, 27318, 27319, 27320, 27321, 27322, 27323, 27324, 27325, 27326, 27327, 27328, 27409, 27410, 27411, 27412
27413, 27414, 27415, 27416, 27417, 27418, 27419, 27420, 27421, 27422, 27423, 27424, 27425, 27426, 27427, 27523
27524, 27525, 27526, 27527, 27528, 27529, 27530, 27531, 27532, 27533, 27534, 27535, 27536, 27537, 27538, 27539
27540, 27541, 27637, 27638, 27639, 27640, 27641, 27642, 27643, 27644, 27645, 27646, 27647, 27648, 27649, 27650
27651, 27652, 27653, 27654, 27655, 27751, 27752, 27753, 27754, 27755, 27756, 27757, 27758, 27759, 27760, 27761
27762, 27763, 27764, 27765, 27766, 27767, 27768, 27769, 27865, 27866, 27867, 27868, 27869, 27870, 27871, 27872
27873, 27874, 27875, 27876, 27877, 27878, 27879, 27880, 27881, 27882, 27883, 27979, 27980, 27981, 27982, 27983
27984, 27985, 27986, 27987, 27988, 27989, 27990, 27991, 27992, 27993, 27994, 27995, 27996, 27997, 28093, 28094
28095, 28096, 28097, 28098, 28099, 28100, 28101, 28102, 28103, 28104, 28105, 28106, 28107, 28108, 28109, 28110
28111, 28207, 28208, 28209, 28210, 28211, 28212, 28213, 28214, 28215, 28216, 28217, 28218, 28219, 28220, 28221
28222, 28223, 28224, 28225, 28321, 28322, 28323, 28324, 28325, 28326, 28327, 28328, 28329, 28330, 28331, 28332
28333, 28334, 28335, 28336, 28337, 28338, 28339, 28435, 28436, 28437, 28438, 28439, 28440, 28441, 28442, 28443
28444, 28445, 28446, 28447, 28448, 28449, 28450, 28451, 28452, 28453, 28549, 28550, 28551, 28552, 28553, 28554
28555, 28556, 28557, 28558, 28559, 28560, 28561, 28562, 28563, 28564, 28565, 28566, 28567, 28663, 28664, 28665
28666, 28667, 28668, 28669, 28670, 28671, 28672, 28673, 28674, 28675, 28676, 28677, 28678, 28679, 28680, 28681
28777, 28778, 28779, 28780, 28781, 28782, 28783, 28784, 28785, 28786, 28787, 28788, 28789, 28790, 28791, 28792
28873, 28874, 28875, 28876, 28877, 28878, 28879, 28880, 28881, 28882, 28883, 28884, 28885, 28886, 28887, 28888
30721, 30722, 30723, 30724, 30725, 30726, 30727, 30728, 30729, 30730, 30731, 30732, 30733, 30734, 30735, 30736
30817, 30818, 30819, 30820, 30821, 30822, 30823, 30824, 30825, 30826, 30827, 30828, 30829, 30830, 30831, 30832
30913, 30914, 30915, 30916, 30917, 30918, 30919, 30920, 30921, 30922, 30923, 30924, 30925, 30926, 30927, 30928
30929, 30930, 30931, 31027, 31028, 31029, 31030, 31031, 31032, 31033, 31034, 31035, 31036, 31037, 31038, 31039
31040, 31041, 31042, 31043, 31044, 31045, 31141, 31142, 31143, 31144, 31145, 31146, 31147, 31148, 31149, 31150
31151, 31152, 31153, 31154, 31155, 31156, 31157, 31158, 31159, 31255, 31256, 31257, 31258, 31259, 31260, 31261
31262, 31263, 31264, 31265, 31266, 31267, 31268, 31269, 31270, 31271, 31272, 31273, 31369, 31370, 31371, 31372
31373, 31374, 31375, 31376, 31377, 31378, 31379, 31380, 31381, 31382, 31383, 31384, 31385, 31386, 31387, 31483
31484, 31485, 31486, 31487, 31488, 31489, 31490, 31491, 31492, 31493, 31494, 31495, 31496, 31497, 31498, 31499
31500, 31501, 31597, 31598, 31599, 31600, 31601, 31602, 31603, 31604, 31605, 31606, 31607, 31608, 31609, 31610
31611, 31612, 31613, 31614, 31615, 31711, 31712, 31713, 31714, 31715, 31716, 31717, 31718, 31719, 31720, 31721
31722, 31723, 31724, 31725, 31726, 31727, 31728, 31729, 31825, 31826, 31827, 31828, 31829, 31830, 31831, 31832
31833, 31834, 31835, 31836, 31837, 31838, 31839, 31840, 31841, 31842, 31843, 31939, 31940, 31941, 31942, 31943
31944, 31945, 31946, 31947, 31948, 31949, 31950, 31951, 31952, 31953, 31954, 31955, 31956, 31957, 32053, 32054
32055, 32056, 32057, 32058, 32059, 32060, 32061, 32062, 32063, 32064, 32065, 32066, 32067, 32068, 32069, 32070
32071, 32167, 32168, 32169, 32170, 32171, 32172, 32173, 32174, 32175, 32176, 32177, 32178, 32179, 32180, 32181
32182, 32183, 32184, 32185, 32281, 32282, 32283, 32284, 32285, 32286, 32287, 32288, 32289, 32290, 32291, 32292
32293, 32294, 32295, 32296, 32377, 32378, 32379, 32380, 32381, 32382, 32383, 32384, 32385, 32386, 32387, 32388
32389, 32390, 32391, 32392, 34225, 34226, 34227, 34228, 34229, 34230, 34231, 34232, 34233, 34234, 34235, 34236
34237, 34238, 34239, 34240, 34321, 34322, 34323, 34324, 34325, 34326, 34327, 34328, 34329, 34330, 34331, 34332
34333, 34334, 34335, 34336, 34417, 34418, 34419, 34420, 34421, 34422, 34423, 34424, 34425, 34426, 34427, 34428
34429, 34430, 34431, 34432, 34513, 34514, 34515, 34516, 34517, 34518, 34519, 34520, 34521, 34522, 34523, 34524
34525, 34526, 34527, 34528, 34609, 34610, 34611, 34612, 34613, 34614, 34615, 34616, 34617, 34618, 34619, 34620
34621, 34622, 34623, 34624, 34625, 34626, 34627, 34723, 34724, 34725, 34726, 34727, 34728, 34729, 34730, 34731
34732, 34733, 34734, 34735, 34736, 34737, 34738, 34739, 34740, 34741, 34837, 34838, 34839, 34840, 34841, 34842
34843, 34844, 34845, 34846, 34847, 34848, 34849, 34850, 34851, 34852, 34853, 34854, 34855, 34951, 34952, 34953
34954, 34955, 34956, 34957, 34958, 34959, 34960, 34961, 34962, 34963, 34964, 34965, 34966, 34967, 34968, 34969
35065, 35066, 35067, 35068, 35069, 35070, 35071, 35072, 35073, 35074, 35075, 35076, 35077, 35078, 35079, 35080
35081, 35082, 35083, 35179, 35180, 35181, 35182, 35183, 35184, 35185, 35186, 35187, 35188, 35189, 35190, 35191
35192, 35193, 35194, 35195, 35196, 35197, 35293, 35294, 35295, 35296, 35297, 35298, 35299, 35300, 35301, 35302
35303, 35304, 35305, 35306, 35307, 35308, 35309, 35310, 35311, 35407, 35408, 35409, 35410, 35411, 35412, 35413
35414, 35415, 35416, 35417, 35418, 35419, 35420, 35421, 35422, 35423, 35424, 35425, 35521, 35522, 35523, 35524
35525, 35526, 35527, 35528, 35529, 35530, 35531, 35532, 35533, 35534, 35535, 35536, 35537, 35538, 35539, 35635
35636, 35637, 35638, 35639, 35640, 35641, 35642, 35643, 35644, 35645, 35646, 35647, 35648, 35649, 35650, 35651
35652, 35653, 35749, 35750, 35751, 35752, 35753, 35754, 35755, 35756, 35757, 35758, 35759, 35760, 35761, 35762
35763, 35764, 35765, 35766, 35767, 35863, 35864, 35865, 35866, 35867, 35868, 35869, 35870, 35871, 35872, 35873
35874, 35875, 35876, 35877, 35878, 35879, 35880, 35881, 35977, 35978, 35979, 35980, 35981, 35982, 35983, 35984
35985, 35986, 35987, 35988, 35989, 35990, 35991, 35992, 36073, 36074, 36075, 36076, 36077, 36078, 36079, 36080
36081, 36082, 36083, 36084, 36085, 36086, 36087, 36088, 36169, 36170, 36171, 36172, 36173, 36174, 36175, 36176
36177, 36178, 36179, 36180, 36181, 36182, 36183, 36184, 36265, 36266, 36267, 36268, 36269, 36270, 36271, 36272
36273, 36274, 36275, 36276, 36277, 36278, 36279, 36280, 38113, 38114, 38115, 38116, 38117, 38118, 38119, 38120
38121, 38122, 38123, 38124, 38125, 38126, 38127, 38128, 38209, 38210, 38211, 38212, 38213, 38214, 38215, 38216
38217, 38218, 38219, 38220, 38221, 38222, 38223, 38224, 38305, 38306, 38307, 38308, 38309, 38310, 38311, 38312
38313, 38314, 38315, 38316, 38317, 38318, 38319, 38320, 38401, 38402, 38403, 38404, 38405, 38406, 38407, 38408
38409, 38410, 38411, 38412, 38413, 38414, 38415, 38416, 38497, 38498, 38499, 38500, 38501, 38502, 38503, 38504
38505, 38506, 38507, 38508, 38509, 38510, 38511, 38512, 38513, 38514, 38515, 38611, 38612, 38613, 38614, 38615
38616, 38617, 38618, 38619, 38620, 38621, 38622, 38623, 38624, 38625, 38626, 38627, 38628, 38629, 38725, 38726
38727, 38728, 38729, 38730, 38731, 38732, 38733, 38734, 38735, 38736, 38737, 38738, 38739, 38740, 38741, 38742
38743, 38839, 38840, 38841, 38842, 38843, 38844, 38845, 38846, 38847, 38848, 38849, 38850, 38851, 38852, 38853
38854, 38855, 38856, 38857, 38953, 38954, 38955, 38956, 38957, 38958, 38959, 38960, 38961, 38962, 38963, 38964
38965, 38966, 38967, 38968, 38969, 38970, 38971, 39067, 39068, 39069, 39070, 39071, 39072, 39073, 39074, 39075
39076, 39077, 39078, 39079, 39080, 39081, 39082, 39083, 39084, 39085, 39181, 39182, 39183, 39184, 39185, 39186
39187, 39188, 39189, 39190, 39191, 39192, 39193, 39194, 39195, 39196, 39197, 39198, 39199, 39295, 39296, 39297
39298, 39299, 39300, 39301, 39302, 39303, 39304, 39305, 39306, 39307, 39308, 39309, 39310, 39311, 39312, 39313
39409, 39410, 39411, 39412, 39413, 39414, 39415, 39416, 39417, 39418, 39419, 39420, 39421, 39422, 39423, 39424
39425, 39426, 39427, 39523, 39524, 39525, 39526, 39527, 39528, 39529, 39530, 39531, 39532, 39533, 39534, 39535
39536, 39537, 39538, 39539, 39540, 39541, 39637, 39638, 39639, 39640, 39641, 39642, 39643, 39644, 39645, 39646
39647, 39648, 39649, 39650, 39651, 39652, 39653, 39654, 39655, 39751, 39752, 39753, 39754, 39755, 39756, 39757
39758, 39759, 39760, 39761, 39762, 39763, 39764, 39765, 39766, 39767, 39768, 39769, 39865, 39866, 39867, 39868
39869, 39870, 39871, 39872, 39873, 39874, 39875, 39876, 39877, 39878, 39879, 39880, 39961, 39962, 39963, 39964
39965, 39966, 39967, 39968, 39969, 39970, 39971, 39972, 39973, 39974, 39975, 39976, 40057, 40058, 40059, 40060
40061, 40062, 40063, 40064, 40065, 40066, 40067, 40068, 40069, 40070, 40071, 40072, 40153, 40154, 40155, 40156
40157, 40158, 40159, 40160, 40161, 40162, 40163, 40164, 40165, 40166, 40167, 40168, 42385, 42386, 42387, 42388
42389, 42390, 42391, 42392, 42393, 42394, 42395, 42396, 42397, 42398, 42399, 42400, 42481, 42482, 42483, 42484
42485, 42486, 42487, 42488, 42489, 42490, 42491, 42492, 42493, 42494, 42495, 42496, 42577, 42578, 42579, 42580
42581, 42582, 42583, 42584, 42585, 42586, 42587, 42588, 42589, 42590, 42591, 42592, 42593, 42594, 42595, 42691
42692, 42693, 42694, 42695, 42696, 42697, 42698, 42699, 42700, 42701, 42702, 42703, 42704, 42705, 42706, 42707
42708, 42709, 42805, 42806, 42807, 42808, 42809, 42810, 42811, 42812, 42813, 42814, 42815, 42816, 42817, 42818
42819, 42820, 42821, 42822, 42823, 42919, 42920, 42921, 42922, 42923, 42924, 42925, 42926, 42927, 42928, 42929
42930, 42931, 42932, 42933, 42934, 42935, 42936, 42937, 43033, 43034, 43035, 43036, 43037, 43038, 43039, 43040
43041, 43042, 43043, 43044, 43045, 43046, 43047, 43048, 43049, 43050, 43051, 43147, 43148, 43149, 43150, 43151
43152, 43153, 43154, 43155, 43156, 43157, 43158, 43159, 43160, 43161, 43162, 43163, 43164, 43165, 43261, 43262
43263, 43264, 43265, 43266, 43267, 43268, 43269, 43270, 43271, 43272, 43273, 43274, 43275, 43276, 43277, 43278
43279, 43375, 43376, 43377, 43378, 43379, 43380, 43381, 43382, 43383, 43384, 43385, 43386, 43387, 43388, 43389
43390, 43391, 43392, 43393, 43489, 43490, 43491, 43492, 43493, 43494, 43495, 43496, 43497, 43498, 43499, 43500
43501, 43502, 43503, 43504, 43505, 43506, 43507, 43603, 43604, 43605, 43606, 43607, 43608, 43609, 43610, 43611
43612, 43613, 43614, 43615, 43616, 43617, 43618, 43619, 43620, 43621, 43717, 43718, 43719, 43720, 43721, 43722
43723, 43724, 43725, 43726, 43727, 43728, 43729, 43730, 43731, 43732, 43733, 43734, 43735, 43831, 43832, 43833
43834, 43835, 43836, 43837, 43838, 43839, 43840, 43841, 43842, 43843, 43844, 43845, 43846, 43847, 43848, 43849
43945, 43946, 43947, 43948, 43949, 43950, 43951, 43952, 43953, 43954, 43955, 43956, 43957, 43958, 43959, 43960
44041, 44042, 44043, 44044, 44045, 44046, 44047, 44048, 44049, 44050, 44051, 44052, 44053, 44054, 44055, 44056
*Elset, elset=__PickedSurf53_S5, internal, instance=Stent
81, 82, 83, 84, 85, 86, 87, 88, 89, 90, 91, 92, 93, 94, 95, 96
177, 178, 179, 180, 181, 182, 183, 184, 185, 186, 187, 188, 189, 190, 191, 192
273, 274, 275, 276, 277, 278, 279, 280, 281, 282, 283, 284, 285, 286, 287, 288
369, 370, 371, 372, 373, 374, 375, 376, 377, 378, 379, 380, 381, 382, 383, 384
480, 481, 482, 483, 484, 485, 486, 487, 488, 489, 490, 491, 492, 493, 494, 495
496, 497, 498, 594, 595, 596, 597, 598, 599, 600, 601, 602, 603, 604, 605, 606
607, 608, 609, 610, 611, 612, 708, 709, 710, 711, 712, 713, 714, 715, 716, 717
718, 719, 720, 721, 722, 723, 724, 725, 726, 822, 823, 824, 825, 826, 827, 828
829, 830, 831, 832, 833, 834, 835, 836, 837, 838, 839, 840, 936, 937, 938, 939
940, 941, 942, 943, 944, 945, 946, 947, 948, 949, 950, 951, 952, 953, 954, 1050
1051, 1052, 1053, 1054, 1055, 1056, 1057, 1058, 1059, 1060, 1061, 1062, 1063, 1064, 1065, 1066
1067, 1068, 1164, 1165, 1166, 1167, 1168, 1169, 1170, 1171, 1172, 1173, 1174, 1175, 1176, 1177
1178, 1179, 1180, 1181, 1182, 1278, 1279, 1280, 1281, 1282, 1283, 1284, 1285, 1286, 1287, 1288
1289, 1290, 1291, 1292, 1293, 1294, 1295, 1296, 1392, 1393, 1394, 1395, 1396, 1397, 1398, 1399
1400, 1401, 1402, 1403, 1404, 1405, 1406, 1407, 1408, 1409, 1410, 1506, 1507, 1508, 1509, 1510
1511, 1512, 1513, 1514, 1515, 1516, 1517, 1518, 1519, 1520, 1521, 1522, 1523, 1524, 1620, 1621
1622, 1623, 1624, 1625, 1626, 1627, 1628, 1629, 1630, 1631, 1632, 1633, 1634, 1635, 1636, 1637
1638, 1734, 1735, 1736, 1737, 1738, 1739, 1740, 1741, 1742, 1743, 1744, 1745, 1746, 1747, 1748
1749, 1750, 1751, 1752, 1833, 1834, 1835, 1836, 1837, 1838, 1839, 1840, 1841, 1842, 1843, 1844
1845, 1846, 1847, 1848, 1929, 1930, 1931, 1932, 1933, 1934, 1935, 1936, 1937, 1938, 1939, 1940
1941, 1942, 1943, 1944, 2025, 2026, 2027, 2028, 2029, 2030, 2031, 2032, 2033, 2034, 2035, 2036
2037, 2038, 2039, 2040, 2121, 2122, 2123, 2124, 2125, 2126, 2127, 2128, 2129, 2130, 2131, 2132
2133, 2134, 2135, 2136, 4353, 4354, 4355, 4356, 4357, 4358, 4359, 4360, 4361, 4362, 4363, 4364
4365, 4366, 4367, 4368, 4449, 4450, 4451, 4452, 4453, 4454, 4455, 4456, 4457, 4458, 4459, 4460
4461, 4462, 4463, 4464, 4560, 4561, 4562, 4563, 4564, 4565, 4566, 4567, 4568, 4569, 4570, 4571
4572, 4573, 4574, 4575, 4576, 4577, 4578, 4674, 4675, 4676, 4677, 4678, 4679, 4680, 4681, 4682
4683, 4684, 4685, 4686, 4687, 4688, 4689, 4690, 4691, 4692, 4788, 4789, 4790, 4791, 4792, 4793
4794, 4795, 4796, 4797, 4798, 4799, 4800, 4801, 4802, 4803, 4804, 4805, 4806, 4902, 4903, 4904
4905, 4906, 4907, 4908, 4909, 4910, 4911, 4912, 4913, 4914, 4915, 4916, 4917, 4918, 4919, 4920
5016, 5017, 5018, 5019, 5020, 5021, 5022, 5023, 5024, 5025, 5026, 5027, 5028, 5029, 5030, 5031
5032, 5033, 5034, 5130, 5131, 5132, 5133, 5134, 5135, 5136, 5137, 5138, 5139, 5140, 5141, 5142
5143, 5144, 5145, 5146, 5147, 5148, 5244, 5245, 5246, 5247, 5248, 5249, 5250, 5251, 5252, 5253
5254, 5255, 5256, 5257, 5258, 5259, 5260, 5261, 5262, 5358, 5359, 5360, 5361, 5362, 5363, 5364
5365, 5366, 5367, 5368, 5369, 5370, 5371, 5372, 5373, 5374, 5375, 5376, 5472, 5473, 5474, 5475
5476, 5477, 5478, 5479, 5480, 5481, 5482, 5483, 5484, 5485, 5486, 5487, 5488, 5489, 5490, 5586
5587, 5588, 5589, 5590, 5591, 5592, 5593, 5594, 5595, 5596, 5597, 5598, 5599, 5600, 5601, 5602
5603, 5604, 5700, 5701, 5702, 5703, 5704, 5705, 5706, 5707, 5708, 5709, 5710, 5711, 5712, 5713
5714, 5715, 5716, 5717, 5718, 5814, 5815, 5816, 5817, 5818, 5819, 5820, 5821, 5822, 5823, 5824
5825, 5826, 5827, 5828, 5829, 5830, 5831, 5832, 5913, 5914, 5915, 5916, 5917, 5918, 5919, 5920
5921, 5922, 5923, 5924, 5925, 5926, 5927, 5928, 6009, 6010, 6011, 6012, 6013, 6014, 6015, 6016
6017, 6018, 6019, 6020, 6021, 6022, 6023, 6024, 7857, 7858, 7859, 7860, 7861, 7862, 7863, 7864
7865, 7866, 7867, 7868, 7869, 7870, 7871, 7872, 7953, 7954, 7955, 7956, 7957, 7958, 7959, 7960
7961, 7962, 7963, 7964, 7965, 7966, 7967, 7968, 8064, 8065, 8066, 8067, 8068, 8069, 8070, 8071
8072, 8073, 8074, 8075, 8076, 8077, 8078, 8079, 8080, 8081, 8082, 8178, 8179, 8180, 8181, 8182
8183, 8184, 8185, 8186, 8187, 8188, 8189, 8190, 8191, 8192, 8193, 8194, 8195, 8196, 8292, 8293
8294, 8295, 8296, 8297, 8298, 8299, 8300, 8301, 8302, 8303, 8304, 8305, 8306, 8307, 8308, 8309
8310, 8406, 8407, 8408, 8409, 8410, 8411, 8412, 8413, 8414, 8415, 8416, 8417, 8418, 8419, 8420
8421, 8422, 8423, 8424, 8520, 8521, 8522, 8523, 8524, 8525, 8526, 8527, 8528, 8529, 8530, 8531
8532, 8533, 8534, 8535, 8536, 8537, 8538, 8634, 8635, 8636, 8637, 8638, 8639, 8640, 8641, 8642
8643, 8644, 8645, 8646, 8647, 8648, 8649, 8650, 8651, 8652, 8748, 8749, 8750, 8751, 8752, 8753
8754, 8755, 8756, 8757, 8758, 8759, 8760, 8761, 8762, 8763, 8764, 8765, 8766, 8862, 8863, 8864
8865, 8866, 8867, 8868, 8869, 8870, 8871, 8872, 8873, 8874, 8875, 8876, 8877, 8878, 8879, 8880
8976, 8977, 8978, 8979, 8980, 8981, 8982, 8983, 8984, 8985, 8986, 8987, 8988, 8989, 8990, 8991
8992, 8993, 8994, 9090, 9091, 9092, 9093, 9094, 9095, 9096, 9097, 9098, 9099, 9100, 9101, 9102
9103, 9104, 9105, 9106, 9107, 9108, 9204, 9205, 9206, 9207, 9208, 9209, 9210, 9211, 9212, 9213
9214, 9215, 9216, 9217, 9218, 9219, 9220, 9221, 9222, 9318, 9319, 9320, 9321, 9322, 9323, 9324
9325, 9326, 9327, 9328, 9329, 9330, 9331, 9332, 9333, 9334, 9335, 9336, 9417, 9418, 9419, 9420
9421, 9422, 9423, 9424, 9425, 9426, 9427, 9428, 9429, 9430, 9431, 9432, 9513, 9514, 9515, 9516
9517, 9518, 9519, 9520, 9521, 9522, 9523, 9524, 9525, 9526, 9527, 9528, 11361, 11362, 11363, 11364
11365, 11366, 11367, 11368, 11369, 11370, 11371, 11372, 11373, 11374, 11375, 11376, 11457, 11458, 11459, 11460
11461, 11462, 11463, 11464, 11465, 11466, 11467, 11468, 11469, 11470, 11471, 11472, 11553, 11554, 11555, 11556
11557, 11558, 11559, 11560, 11561, 11562, 11563, 11564, 11565, 11566, 11567, 11568, 11649, 11650, 11651, 11652
11653, 11654, 11655, 11656, 11657, 11658, 11659, 11660, 11661, 11662, 11663, 11664, 11760, 11761, 11762, 11763
11764, 11765, 11766, 11767, 11768, 11769, 11770, 11771, 11772, 11773, 11774, 11775, 11776, 11777, 11778, 11874
11875, 11876, 11877, 11878, 11879, 11880, 11881, 11882, 11883, 11884, 11885, 11886, 11887, 11888, 11889, 11890
11891, 11892, 11988, 11989, 11990, 11991, 11992, 11993, 11994, 11995, 11996, 11997, 11998, 11999, 12000, 12001
12002, 12003, 12004, 12005, 12006, 12102, 12103, 12104, 12105, 12106, 12107, 12108, 12109, 12110, 12111, 12112
12113, 12114, 12115, 12116, 12117, 12118, 12119, 12120, 12216, 12217, 12218, 12219, 12220, 12221, 12222, 12223
12224, 12225, 12226, 12227, 12228, 12229, 12230, 12231, 12232, 12233, 12234, 12330, 12331, 12332, 12333, 12334
12335, 12336, 12337, 12338, 12339, 12340, 12341, 12342, 12343, 12344, 12345, 12346, 12347, 12348, 12444, 12445
12446, 12447, 12448, 12449, 12450, 12451, 12452, 12453, 12454, 12455, 12456, 12457, 12458, 12459, 12460, 12461
12462, 12558, 12559, 12560, 12561, 12562, 12563, 12564, 12565, 12566, 12567, 12568, 12569, 12570, 12571, 12572
12573, 12574, 12575, 12576, 12672, 12673, 12674, 12675, 12676, 12677, 12678, 12679, 12680, 12681, 12682, 12683
12684, 12685, 12686, 12687, 12688, 12689, 12690, 12786, 12787, 12788, 12789, 12790, 12791, 12792, 12793, 12794
12795, 12796, 12797, 12798, 12799, 12800, 12801, 12802, 12803, 12804, 12900, 12901, 12902, 12903, 12904, 12905
12906, 12907, 12908, 12909, 12910, 12911, 12912, 12913, 12914, 12915, 12916, 12917, 12918, 13014, 13015, 13016
13017, 13018, 13019, 13020, 13021, 13022, 13023, 13024, 13025, 13026, 13027, 13028, 13029, 13030, 13031, 13032
13113, 13114, 13115, 13116, 13117, 13118, 13119, 13120, 13121, 13122, 13123, 13124, 13125, 13126, 13127, 13128
13209, 13210, 13211, 13212, 13213, 13214, 13215, 13216, 13217, 13218, 13219, 13220, 13221, 13222, 13223, 13224
13305, 13306, 13307, 13308, 13309, 13310, 13311, 13312, 13313, 13314, 13315, 13316, 13317, 13318, 13319, 13320
13401, 13402, 13403, 13404, 13405, 13406, 13407, 13408, 13409, 13410, 13411, 13412, 13413, 13414, 13415, 13416
15249, 15250, 15251, 15252, 15253, 15254, 15255, 15256, 15257, 15258, 15259, 15260, 15261, 15262, 15263, 15264
15345, 15346, 15347, 15348, 15349, 15350, 15351, 15352, 15353, 15354, 15355, 15356, 15357, 15358, 15359, 15360
15441, 15442, 15443, 15444, 15445, 15446, 15447, 15448, 15449, 15450, 15451, 15452, 15453, 15454, 15455, 15456
15537, 15538, 15539, 15540, 15541, 15542, 15543, 15544, 15545, 15546, 15547, 15548, 15549, 15550, 15551, 15552
15648, 15649, 15650, 15651, 15652, 15653, 15654, 15655, 15656, 15657, 15658, 15659, 15660, 15661, 15662, 15663
15664, 15665, 15666, 15762, 15763, 15764, 15765, 15766, 15767, 15768, 15769, 15770, 15771, 15772, 15773, 15774
15775, 15776, 15777, 15778, 15779, 15780, 15876, 15877, 15878, 15879, 15880, 15881, 15882, 15883, 15884, 15885
15886, 15887, 15888, 15889, 15890, 15891, 15892, 15893, 15894, 15990, 15991, 15992, 15993, 15994, 15995, 15996
15997, 15998, 15999, 16000, 16001, 16002, 16003, 16004, 16005, 16006, 16007, 16008, 16104, 16105, 16106, 16107
16108, 16109, 16110, 16111, 16112, 16113, 16114, 16115, 16116, 16117, 16118, 16119, 16120, 16121, 16122, 16218
16219, 16220, 16221, 16222, 16223, 16224, 16225, 16226, 16227, 16228, 16229, 16230, 16231, 16232, 16233, 16234
16235, 16236, 16332, 16333, 16334, 16335, 16336, 16337, 16338, 16339, 16340, 16341, 16342, 16343, 16344, 16345
16346, 16347, 16348, 16349, 16350, 16446, 16447, 16448, 16449, 16450, 16451, 16452, 16453, 16454, 16455, 16456
16457, 16458, 16459, 16460, 16461, 16462, 16463, 16464, 16560, 16561, 16562, 16563, 16564, 16565, 16566, 16567
16568, 16569, 16570, 16571, 16572, 16573, 16574, 16575, 16576, 16577, 16578, 16674, 16675, 16676, 16677, 16678
16679, 16680, 16681, 16682, 16683, 16684, 16685, 16686, 16687, 16688, 16689, 16690, 16691, 16692, 16788, 16789
16790, 16791, 16792, 16793, 16794, 16795, 16796, 16797, 16798, 16799, 16800, 16801, 16802, 16803, 16804, 16805
16806, 16902, 16903, 16904, 16905, 16906, 16907, 16908, 16909, 16910, 16911, 16912, 16913, 16914, 16915, 16916
16917, 16918, 16919, 16920, 17001, 17002, 17003, 17004, 17005, 17006, 17007, 17008, 17009, 17010, 17011, 17012
17013, 17014, 17015, 17016, 17097, 17098, 17099, 17100, 17101, 17102, 17103, 17104, 17105, 17106, 17107, 17108
17109, 17110, 17111, 17112, 17193, 17194, 17195, 17196, 17197, 17198, 17199, 17200, 17201, 17202, 17203, 17204
17205, 17206, 17207, 17208, 17289, 17290, 17291, 17292, 17293, 17294, 17295, 17296, 17297, 17298, 17299, 17300
17301, 17302, 17303, 17304, 19521, 19522, 19523, 19524, 19525, 19526, 19527, 19528, 19529, 19530, 19531, 19532
19533, 19534, 19535, 19536, 19617, 19618, 19619, 19620, 19621, 19622, 19623, 19624, 19625, 19626, 19627, 19628
19629, 19630, 19631, 19632, 19728, 19729, 19730, 19731, 19732, 19733, 19734, 19735, 19736, 19737, 19738, 19739
19740, 19741, 19742, 19743, 19744, 19745, 19746, 19842, 19843, 19844, 19845, 19846, 19847, 19848, 19849, 19850
19851, 19852, 19853, 19854, 19855, 19856, 19857, 19858, 19859, 19860, 19956, 19957, 19958, 19959, 19960, 19961
19962, 19963, 19964, 19965, 19966, 19967, 19968, 19969, 19970, 19971, 19972, 19973, 19974, 20070, 20071, 20072
20073, 20074, 20075, 20076, 20077, 20078, 20079, 20080, 20081, 20082, 20083, 20084, 20085, 20086, 20087, 20088
20184, 20185, 20186, 20187, 20188, 20189, 20190, 20191, 20192, 20193, 20194, 20195, 20196, 20197, 20198, 20199
20200, 20201, 20202, 20298, 20299, 20300, 20301, 20302, 20303, 20304, 20305, 20306, 20307, 20308, 20309, 20310
20311, 20312, 20313, 20314, 20315, 20316, 20412, 20413, 20414, 20415, 20416, 20417, 20418, 20419, 20420, 20421
20422, 20423, 20424, 20425, 20426, 20427, 20428, 20429, 20430, 20526, 20527, 20528, 20529, 20530, 20531, 20532
20533, 20534, 20535, 20536, 20537, 20538, 20539, 20540, 20541, 20542, 20543, 20544, 20640, 20641, 20642, 20643
20644, 20645, 20646, 20647, 20648, 20649, 20650, 20651, 20652, 20653, 20654, 20655, 20656, 20657, 20658, 20754
20755, 20756, 20757, 20758, 20759, 20760, 20761, 20762, 20763, 20764, 20765, 20766, 20767, 20768, 20769, 20770
20771, 20772, 20868, 20869, 20870, 20871, 20872, 20873, 20874, 20875, 20876, 20877, 20878, 20879, 20880, 20881
20882, 20883, 20884, 20885, 20886, 20982, 20983, 20984, 20985, 20986, 20987, 20988, 20989, 20990, 20991, 20992
20993, 20994, 20995, 20996, 20997, 20998, 20999, 21000, 21081, 21082, 21083, 21084, 21085, 21086, 21087, 21088
21089, 21090, 21091, 21092, 21093, 21094, 21095, 21096, 21177, 21178, 21179, 21180, 21181, 21182, 21183, 21184
21185, 21186, 21187, 21188, 21189, 21190, 21191, 21192, 25560, 25561, 25562, 25563, 25564, 25565, 25566, 25567
25568, 25569, 25570, 25571, 25572, 25573, 25574, 25575, 25576, 25577, 25578, 25674, 25675, 25676, 25677, 25678
25679, 25680, 25681, 25682, 25683, 25684, 25685, 25686, 25687, 25688, 25689, 25690, 25691, 25692, 25788, 25789
25790, 25791, 25792, 25793, 25794, 25795, 25796, 25797, 25798, 25799, 25800, 25801, 25802, 25803, 25804, 25805
25806, 25902, 25903, 25904, 25905, 25906, 25907, 25908, 25909, 25910, 25911, 25912, 25913, 25914, 25915, 25916
25917, 25918, 25919, 25920, 26016, 26017, 26018, 26019, 26020, 26021, 26022, 26023, 26024, 26025, 26026, 26027
26028, 26029, 26030, 26031, 26032, 26033, 26034, 26130, 26131, 26132, 26133, 26134, 26135, 26136, 26137, 26138
26139, 26140, 26141, 26142, 26143, 26144, 26145, 26146, 26147, 26148, 26244, 26245, 26246, 26247, 26248, 26249
26250, 26251, 26252, 26253, 26254, 26255, 26256, 26257, 26258, 26259, 26260, 26261, 26262, 26358, 26359, 26360
26361, 26362, 26363, 26364, 26365, 26366, 26367, 26368, 26369, 26370, 26371, 26372, 26373, 26374, 26375, 26376
26472, 26473, 26474, 26475, 26476, 26477, 26478, 26479, 26480, 26481, 26482, 26483, 26484, 26485, 26486, 26487
26488, 26489, 26490, 26586, 26587, 26588, 26589, 26590, 26591, 26592, 26593, 26594, 26595, 26596, 26597, 26598
26599, 26600, 26601, 26602, 26603, 26604, 26700, 26701, 26702, 26703, 26704, 26705, 26706, 26707, 26708, 26709
26710, 26711, 26712, 26713, 26714, 26715, 26716, 26717, 26718, 26814, 26815, 26816, 26817, 26818, 26819, 26820
26821, 26822, 26823, 26824, 26825, 26826, 26827, 26828, 26829, 26830, 26831, 26832, 29256, 29257, 29258, 29259
29260, 29261, 29262, 29263, 29264, 29265, 29266, 29267, 29268, 29269, 29270, 29271, 29272, 29273, 29274, 29370
29371, 29372, 29373, 29374, 29375, 29376, 29377, 29378, 29379, 29380, 29381, 29382, 29383, 29384, 29385, 29386
29387, 29388, 29484, 29485, 29486, 29487, 29488, 29489, 29490, 29491, 29492, 29493, 29494, 29495, 29496, 29497
29498, 29499, 29500, 29501, 29502, 29598, 29599, 29600, 29601, 29602, 29603, 29604, 29605, 29606, 29607, 29608
29609, 29610, 29611, 29612, 29613, 29614, 29615, 29616, 29712, 29713, 29714, 29715, 29716, 29717, 29718, 29719
29720, 29721, 29722, 29723, 29724, 29725, 29726, 29727, 29728, 29729, 29730, 29826, 29827, 29828, 29829, 29830
29831, 29832, 29833, 29834, 29835, 29836, 29837, 29838, 29839, 29840, 29841, 29842, 29843, 29844, 29940, 29941
29942, 29943, 29944, 29945, 29946, 29947, 29948, 29949, 29950, 29951, 29952, 29953, 29954, 29955, 29956, 29957
29958, 30054, 30055, 30056, 30057, 30058, 30059, 30060, 30061, 30062, 30063, 30064, 30065, 30066, 30067, 30068
30069, 30070, 30071, 30072, 30168, 30169, 30170, 30171, 30172, 30173, 30174, 30175, 30176, 30177, 30178, 30179
30180, 30181, 30182, 30183, 30184, 30185, 30186, 30282, 30283, 30284, 30285, 30286, 30287, 30288, 30289, 30290
30291, 30292, 30293, 30294, 30295, 30296, 30297, 30298, 30299, 30300, 30396, 30397, 30398, 30399, 30400, 30401
30402, 30403, 30404, 30405, 30406, 30407, 30408, 30409, 30410, 30411, 30412, 30413, 30414, 30510, 30511, 30512
30513, 30514, 30515, 30516, 30517, 30518, 30519, 30520, 30521, 30522, 30523, 30524, 30525, 30526, 30527, 30528
32760, 32761, 32762, 32763, 32764, 32765, 32766, 32767, 32768, 32769, 32770, 32771, 32772, 32773, 32774, 32775
32776, 32777, 32778, 32874, 32875, 32876, 32877, 32878, 32879, 32880, 32881, 32882, 32883, 32884, 32885, 32886
32887, 32888, 32889, 32890, 32891, 32892, 32988, 32989, 32990, 32991, 32992, 32993, 32994, 32995, 32996, 32997
32998, 32999, 33000, 33001, 33002, 33003, 33004, 33005, 33006, 33102, 33103, 33104, 33105, 33106, 33107, 33108
33109, 33110, 33111, 33112, 33113, 33114, 33115, 33116, 33117, 33118, 33119, 33120, 33216, 33217, 33218, 33219
33220, 33221, 33222, 33223, 33224, 33225, 33226, 33227, 33228, 33229, 33230, 33231, 33232, 33233, 33234, 33330
33331, 33332, 33333, 33334, 33335, 33336, 33337, 33338, 33339, 33340, 33341, 33342, 33343, 33344, 33345, 33346
33347, 33348, 33444, 33445, 33446, 33447, 33448, 33449, 33450, 33451, 33452, 33453, 33454, 33455, 33456, 33457
33458, 33459, 33460, 33461, 33462, 33558, 33559, 33560, 33561, 33562, 33563, 33564, 33565, 33566, 33567, 33568
33569, 33570, 33571, 33572, 33573, 33574, 33575, 33576, 33672, 33673, 33674, 33675, 33676, 33677, 33678, 33679
33680, 33681, 33682, 33683, 33684, 33685, 33686, 33687, 33688, 33689, 33690, 33786, 33787, 33788, 33789, 33790
33791, 33792, 33793, 33794, 33795, 33796, 33797, 33798, 33799, 33800, 33801, 33802, 33803, 33804, 33900, 33901
33902, 33903, 33904, 33905, 33906, 33907, 33908, 33909, 33910, 33911, 33912, 33913, 33914, 33915, 33916, 33917
33918, 34014, 34015, 34016, 34017, 34018, 34019, 34020, 34021, 34022, 34023, 34024, 34025, 34026, 34027, 34028
34029, 34030, 34031, 34032, 36648, 36649, 36650, 36651, 36652, 36653, 36654, 36655, 36656, 36657, 36658, 36659
36660, 36661, 36662, 36663, 36664, 36665, 36666, 36762, 36763, 36764, 36765, 36766, 36767, 36768, 36769, 36770
36771, 36772, 36773, 36774, 36775, 36776, 36777, 36778, 36779, 36780, 36876, 36877, 36878, 36879, 36880, 36881
36882, 36883, 36884, 36885, 36886, 36887, 36888, 36889, 36890, 36891, 36892, 36893, 36894, 36990, 36991, 36992
36993, 36994, 36995, 36996, 36997, 36998, 36999, 37000, 37001, 37002, 37003, 37004, 37005, 37006, 37007, 37008
37104, 37105, 37106, 37107, 37108, 37109, 37110, 37111, 37112, 37113, 37114, 37115, 37116, 37117, 37118, 37119
37120, 37121, 37122, 37218, 37219, 37220, 37221, 37222, 37223, 37224, 37225, 37226, 37227, 37228, 37229, 37230
37231, 37232, 37233, 37234, 37235, 37236, 37332, 37333, 37334, 37335, 37336, 37337, 37338, 37339, 37340, 37341
37342, 37343, 37344, 37345, 37346, 37347, 37348, 37349, 37350, 37446, 37447, 37448, 37449, 37450, 37451, 37452
37453, 37454, 37455, 37456, 37457, 37458, 37459, 37460, 37461, 37462, 37463, 37464, 37560, 37561, 37562, 37563
37564, 37565, 37566, 37567, 37568, 37569, 37570, 37571, 37572, 37573, 37574, 37575, 37576, 37577, 37578, 37674
37675, 37676, 37677, 37678, 37679, 37680, 37681, 37682, 37683, 37684, 37685, 37686, 37687, 37688, 37689, 37690
37691, 37692, 37788, 37789, 37790, 37791, 37792, 37793, 37794, 37795, 37796, 37797, 37798, 37799, 37800, 37801
37802, 37803, 37804, 37805, 37806, 37902, 37903, 37904, 37905, 37906, 37907, 37908, 37909, 37910, 37911, 37912
37913, 37914, 37915, 37916, 37917, 37918, 37919, 37920, 40728, 40729, 40730, 40731, 40732, 40733, 40734, 40735
40736, 40737, 40738, 40739, 40740, 40741, 40742, 40743, 40744, 40745, 40746, 40842, 40843, 40844, 40845, 40846
40847, 40848, 40849, 40850, 40851, 40852, 40853, 40854, 40855, 40856, 40857, 40858, 40859, 40860, 40956, 40957
40958, 40959, 40960, 40961, 40962, 40963, 40964, 40965, 40966, 40967, 40968, 40969, 40970, 40971, 40972, 40973
40974, 41070, 41071, 41072, 41073, 41074, 41075, 41076, 41077, 41078, 41079, 41080, 41081, 41082, 41083, 41084
41085, 41086, 41087, 41088, 41184, 41185, 41186, 41187, 41188, 41189, 41190, 41191, 41192, 41193, 41194, 41195
41196, 41197, 41198, 41199, 41200, 41201, 41202, 41298, 41299, 41300, 41301, 41302, 41303, 41304, 41305, 41306
41307, 41308, 41309, 41310, 41311, 41312, 41313, 41314, 41315, 41316, 41412, 41413, 41414, 41415, 41416, 41417
41418, 41419, 41420, 41421, 41422, 41423, 41424, 41425, 41426, 41427, 41428, 41429, 41430, 41526, 41527, 41528
41529, 41530, 41531, 41532, 41533, 41534, 41535, 41536, 41537, 41538, 41539, 41540, 41541, 41542, 41543, 41544
41640, 41641, 41642, 41643, 41644, 41645, 41646, 41647, 41648, 41649, 41650, 41651, 41652, 41653, 41654, 41655
41656, 41657, 41658, 41754, 41755, 41756, 41757, 41758, 41759, 41760, 41761, 41762, 41763, 41764, 41765, 41766
41767, 41768, 41769, 41770, 41771, 41772, 41868, 41869, 41870, 41871, 41872, 41873, 41874, 41875, 41876, 41877
41878, 41879, 41880, 41881, 41882, 41883, 41884, 41885, 41886, 41982, 41983, 41984, 41985, 41986, 41987, 41988
41989, 41990, 41991, 41992, 41993, 41994, 41995, 41996, 41997, 41998, 41999, 42000, 44616, 44617, 44618, 44619
44620, 44621, 44622, 44623, 44624, 44625, 44626, 44627, 44628, 44629, 44630, 44631, 44632, 44633, 44634, 44730
44731, 44732, 44733, 44734, 44735, 44736, 44737, 44738, 44739, 44740, 44741, 44742, 44743, 44744, 44745, 44746
44747, 44748, 44844, 44845, 44846, 44847, 44848, 44849, 44850, 44851, 44852, 44853, 44854, 44855, 44856, 44857
44858, 44859, 44860, 44861, 44862, 44958, 44959, 44960, 44961, 44962, 44963, 44964, 44965, 44966, 44967, 44968
44969, 44970, 44971, 44972, 44973, 44974, 44975, 44976, 45072, 45073, 45074, 45075, 45076, 45077, 45078, 45079
45080, 45081, 45082, 45083, 45084, 45085, 45086, 45087, 45088, 45089, 45090, 45186, 45187, 45188, 45189, 45190
45191, 45192, 45193, 45194, 45195, 45196, 45197, 45198, 45199, 45200, 45201, 45202, 45203, 45204, 45300, 45301
45302, 45303, 45304, 45305, 45306, 45307, 45308, 45309, 45310, 45311, 45312, 45313, 45314, 45315, 45316, 45317
45318, 45414, 45415, 45416, 45417, 45418, 45419, 45420, 45421, 45422, 45423, 45424, 45425, 45426, 45427, 45428
45429, 45430, 45431, 45432, 45528, 45529, 45530, 45531, 45532, 45533, 45534, 45535, 45536, 45537, 45538, 45539
45540, 45541, 45542, 45543, 45544, 45545, 45546, 45642, 45643, 45644, 45645, 45646, 45647, 45648, 45649, 45650
45651, 45652, 45653, 45654, 45655, 45656, 45657, 45658, 45659, 45660, 45756, 45757, 45758, 45759, 45760, 45761
45762, 45763, 45764, 45765, 45766, 45767, 45768, 45769, 45770, 45771, 45772, 45773, 45774, 45870, 45871, 45872
45873, 45874, 45875, 45876, 45877, 45878, 45879, 45880, 45881, 45882, 45883, 45884, 45885, 45886, 45887, 45888
*Surface, type=ELEMENT, name=_PickedSurf53, internal
__PickedSurf53_S1, S1
__PickedSurf53_S2, S2
__PickedSurf53_S3, S3
__PickedSurf53_S5, S5
*Nset, nset="_T-Datum csys-1", internal
_PickedSet48,
_PickedSet49,
Set-1,
Set-2,
*Transform, nset="_T-Datum csys-1", type=C
0., 0., 0., -1., 0., 0.
** Constraint: Constraint-1
*Equation
2
Set-1, 3, 1.
Set-2, 3, -1.
*End Assembly
*Amplitude, name=Amp-2, time=TOTAL TIME, definition=SMOOTH STEP
0., 0., 1., 1., 1.8, 0.85, 1.9, 0.8
2., 0.
*Amplitude, name=Amp-3, definition=SMOOTH STEP
0., 0., 1., 1.
*Amplitude, name=Deploy, time=TOTAL TIME, definition=SMOOTH STEP
0., 0., 1., 1., 1.5, -0.2
**
** MATERIALS
**
*Material, name=Iron
*Density
1e-06,
*Elastic
211000., 0.3
*Plastic
138.09, 0.
231., 0.0481364
308.2, 0.139108
352.5, 0.22249
*Material, name=Magnesium
*Density
1.74e-06,
*Depvar, delete=20
30,
*User Material, constants=6
44000., 0.35, 138.7, 16., 165., 0.025
*Material, name=Plate
*Density
1e-05,
*Elastic
2000., 0.3
*Material, name=Steel
*Density
1e-06,
*Elastic
190000., 0.3
*Plastic
380.76, 0.
605., 0.0933122
804., 0.180324
1050., 0.334474
1140.05, 0.410112
*Material, name=cocr
*Density
1e-06,
*Elastic
243000., 0.3
*Plastic
676.875, 0.
902., 0.0925363
1110., 0.179548
1470., 0.333698
1558.75, 0.36879
*Material, name=plla
*Density
1e-06,
*Elastic
2730., 0.4
*Plastic
16.0938, 0.
29.15, 0.0894665
34.8, 0.176478
39.65, 0.256521
48.98, 0.451581
**
** INTERACTION PROPERTIES
**
*Surface Interaction, name=GeneralProps
*Friction, exponential decay
0.2, 0., 0.
*Surface Behavior, pressure-overclosure=HARD
**
** BOUNDARY CONDITIONS
**
** Name: BC-1 Type: Displacement/Rotation
*Boundary
_PickedSet48, 3, 3
** ----------------------------------------------------------------
**
** STEP: Deploy
**
*Step, name=Deploy
*Dynamic, Explicit
, 1.
*Bulk Viscosity
0.06, 1.2
** Mass Scaling: Semi-Automatic
** Whole Model
*Fixed Mass Scaling, dt=5e-06, type=below min
**
** BOUNDARY CONDITIONS
**
** Name: BC-2 Type: Displacement/Rotation
*Boundary
_PickedSet49, 2, 2
**
** LOADS
**
** Name: Load-1 Type: Pressure
*Dsload, amplitude=Amp-3
_PickedSurf53, P, 2.
**
** INTERACTIONS
**
** Interaction: GeneralProps
*Contact, op=NEW
*Contact Inclusions, ALL EXTERIOR
*Contact Property Assignment
, , GeneralProps
**
** OUTPUT REQUESTS
**
*Restart, write, number interval=5, time marks=NO
**
** FIELD OUTPUT: F-Output-1
**
*Output, field, number interval=100
*Node Output
A, RF, U, V
*Element Output, directions=YES
LE, PE, PEEQ, S, SDV, STATUS
*Contact Output
CSTRESS,
**
** HISTORY OUTPUT: H-Output-1
**
*Output, history, variable=PRESELECT
*End Step

Some files were not shown because too many files have changed in this diff Show more