Skip to content
Snippets Groups Projects
Commit 2a308c89 authored by Dave Whipp's avatar Dave Whipp
Browse files

Updated Drucker-Prager yield options

parent e1b2d564
No related branches found
No related tags found
No related merge requests found
...@@ -72,120 +72,245 @@ endif ...@@ -72,120 +72,245 @@ endif
select case (trim(plasticity_type)) select case (trim(plasticity_type))
case ('vM') case ('vM')
yield = plasticity_parameters(1) yield = plasticity_parameters(1)
! strain softening ! strain softening
strain_soft_in=plasticity_parameters(3) strain_soft_in=plasticity_parameters(3)
if (strain_soft_in.gt.0.d0) then if (strain_soft_in.gt.0.d0) then
strain_soft_out=plasticity_parameters(4) strain_soft_out=plasticity_parameters(4)
strain_soft_yield=plasticity_parameters(2) strain_soft_yield=plasticity_parameters(2)
if (straintot.gt.strain_soft_in) then if (straintot.gt.strain_soft_in) then
yield = (strain_soft_yield-yield)/(strain_soft_out-strain_soft_in)*(straintot-strain_soft_out) + strain_soft_yield yield = (strain_soft_yield-yield)/(strain_soft_out-strain_soft_in)*(straintot-strain_soft_out) + strain_soft_yield
yield = max(yield, strain_soft_yield) yield = max(yield, strain_soft_yield)
end if
end if
fail = 2.d0*viscosity*e2d-yield
if (fail.gt.0.d0) then
viscosity=0.5d0*yield/e2d
is_plastic=.true.
else
is_plastic=.false.
end if end if
end if
fail = 2.d0*viscosity*e2d-yield
if (fail.gt.0.d0) then
viscosity=0.5d0*yield/e2d
is_plastic=.true.
else
is_plastic=.false.
end if
case ('DPI','DPII') case ('DPI')
!yield = abs(plasticity_parameters(9)-plasticity_parameters(8)*pressure) ! Strain softening/hardening
! strain softening phi = plasticity_parameters(1)*pi/180.d0
phi=plasticity_parameters(1) strain_soft_in=plasticity_parameters(3)
strain_soft_in=plasticity_parameters(3) if (strain_soft_in.gt.0.d0) then
if (strain_soft_in.gt.0.d0) then strain_soft_out=plasticity_parameters(4)
strain_soft_out=plasticity_parameters(4) strain_soft_phi=plasticity_parameters(5)*pi/180.d0
strain_soft_phi=plasticity_parameters(5)/180.d0*3.141592654d0 if (straintot.gt.strain_soft_in) then
if (straintot.gt.strain_soft_in) then fact=(straintot-strain_soft_in)/(strain_soft_out-strain_soft_in)
fact=(straintot-strain_soft_in)/(strain_soft_out-strain_soft_in) fact=min(fact,1.d0)
fact=min(fact,1.d0) phi=phi+(strain_soft_phi-phi)*fact
phi=phi+(strain_soft_phi-phi)*fact
endif
endif endif
yield = max(plasticity_parameters(2)/compressibility,plasticity_parameters(2)+tan(phi)*pressure) endif
fail = 2.d0*viscosity*e2d-yield c = plasticity_parameters(2)
if (fail.gt.0.d0) then alpha = (2.d0*sin(phi)) /(sqrt(3.d0)*(3.d0-sin(phi)))
viscosity=0.5d0*yield/e2d k = (6.d0*c*cos(phi))/(sqrt(3.d0)*(3.d0-sin(phi)))
is_plastic=.true. yield = max(c/compressibility,k+alpha*pressure)
else fail = 2.d0*viscosity*e2d-yield
is_plastic=.false. if (fail.gt.0.d0) then
end if viscosity=0.5d0*yield/e2d
is_plastic=.true.
else
is_plastic=.false.
end if
case ('DPIII') case ('DPII')
!yield = plasticity_parameters(2)+plasticity_parameters(1)*pressure ! Strain softening/hardening
yield = max(plasticity_parameters(2)/compressibility,plasticity_parameters(2)+plasticity_parameters(1)*pressure) phi = plasticity_parameters(1)*pi/180.d0
fail = 2.d0*viscosity*e2d-yield strain_soft_in=plasticity_parameters(3)
if (fail.gt.0.d0) then if (strain_soft_in.gt.0.d0) then
viscosity=0.5d0*yield/e2d strain_soft_out=plasticity_parameters(4)
is_plastic=.true. strain_soft_phi=plasticity_parameters(5)*pi/180.d0
else if (straintot.gt.strain_soft_in) then
is_plastic=.false. fact=(straintot-strain_soft_in)/(strain_soft_out-strain_soft_in)
end if fact=min(fact,1.d0)
phi=phi+(strain_soft_phi-phi)*fact
endif
endif
c = plasticity_parameters(2)
alpha = (2.d0*sin(phi)) /(sqrt(3.d0)*(3.d0+sin(phi)))
k = (6.d0*c*cos(phi))/(sqrt(3.d0)*(3.d0+sin(phi)))
yield = max(c/compressibility,k+alpha*pressure)
fail = 2.d0*viscosity*e2d-yield
if (fail.gt.0.d0) then
viscosity=0.5d0*yield/e2d
is_plastic=.true.
else
is_plastic=.false.
end if
case ('MC') case ('DPIII')
if (params%init_e2d) then ! Strain softening/hardening
theta = 0.d0 phi = plasticity_parameters(1)*pi/180.d0
else strain_soft_in=plasticity_parameters(3)
theta = lode_angle(J2d,J3d) if (strain_soft_in.gt.0.d0) then
strain_soft_out=plasticity_parameters(4)
strain_soft_phi=plasticity_parameters(5)*pi/180.d0
if (straintot.gt.strain_soft_in) then
fact=(straintot-strain_soft_in)/(strain_soft_out-strain_soft_in)
fact=min(fact,1.d0)
phi=phi+(strain_soft_phi-phi)*fact
endif endif
sin_theta = sin(theta) endif
cos_theta = cos(theta) c = plasticity_parameters(2)
sin_phi = plasticity_parameters(8) alpha = (2.d0*sin(phi)) /(sqrt(3.d0)*3.d0)
cos_phi = plasticity_parameters(9) k = (6.d0*c*cos(phi))/(sqrt(3.d0)*3.d0)
c = plasticity_parameters(2) yield = max(c/compressibility,k+alpha*pressure)
! strain softening fail = 2.d0*viscosity*e2d-yield
strain_soft_in=plasticity_parameters(3) if (fail.gt.0.d0) then
if (strain_soft_in.gt.0.d0) then viscosity=0.5d0*yield/e2d
is_plastic=.true.
else
is_plastic=.false.
end if
case ('DPIV')
! Strain softening/hardening
phi = plasticity_parameters(1)*pi/180.d0
strain_soft_in=plasticity_parameters(3)
if (strain_soft_in.gt.0.d0) then
strain_soft_out=plasticity_parameters(4) strain_soft_out=plasticity_parameters(4)
strain_soft_phi=plasticity_parameters(5)/180.d0*3.141592654d0 strain_soft_phi=plasticity_parameters(5)*pi/180.d0
if (straintot.gt.strain_soft_in) then if (straintot.gt.strain_soft_in) then
phi=atan2(plasticity_parameters(8),plasticity_parameters(9))
fact=(straintot-strain_soft_in)/(strain_soft_out-strain_soft_in) fact=(straintot-strain_soft_in)/(strain_soft_out-strain_soft_in)
fact=min(fact,1.d0) fact=min(fact,1.d0)
phi=phi+(strain_soft_phi-phi)*fact phi=phi+(strain_soft_phi-phi)*fact
sin_phi=sin(phi)
cos_phi=cos(phi)
endif
endif endif
zeta = cos_theta-sin_phi*sin_theta/sqrt3 endif
! modified by Jean c = plasticity_parameters(2)
!fail = -pressure*sin_phi+e2d*zeta-c*cos_phi alpha = tan(phi)/(sqrt(9.d0+12.d0*(tan(phi))**2.d0))
fail = pressure*sin_phi+2.d0*viscosity*e2d*zeta-c*cos_phi k = (3.d0*c)/(sqrt(9.d0+12.d0*(tan(phi))**2.d0))
if (fail.gt.0.d0) then yield = max(c/compressibility,k+alpha*pressure)
viscosity=0.5d0/e2d*(c*cos_phi-pressure*sin_phi)/zeta fail = 2.d0*viscosity*e2d-yield
!if (viscosity<0.d0) then if (fail.gt.0.d0) then
! viscosity=0.d0 viscosity=0.5d0*yield/e2d
! !print *,viscosity,c*cos_phi,pressure*sin_phi is_plastic=.true.
!end if else
is_plastic=.true. is_plastic=.false.
else end if
is_plastic=.false.
end if
case ('Tresca') case ('DPV')
if (params%init_e2d) then alpha = plasticity_parameters(1)
theta = 0.d0 k = plasticity_parameters(2)
else yield = max(k/compressibility,k+alpha*pressure)
theta = lode_angle(J2d,J3d) fail = 2.d0*viscosity*e2d-yield
if (fail.gt.0.d0) then
viscosity=0.5d0*yield/e2d
is_plastic=.true.
else
is_plastic=.false.
end if
case ('DPVI')
! Strain softening/hardening
phi = plasticity_parameters(1)*pi/180.d0
strain_soft_in=plasticity_parameters(3)
if (strain_soft_in.gt.0.d0) then
strain_soft_out=plasticity_parameters(4)
strain_soft_phi=plasticity_parameters(5)*pi/180.d0
if (straintot.gt.strain_soft_in) then
fact=(straintot-strain_soft_in)/(strain_soft_out-strain_soft_in)
fact=min(fact,1.d0)
phi=phi+(strain_soft_phi-phi)*fact
endif endif
yield = plasticity_parameters(1) endif
cos_theta = cos(theta) c = plasticity_parameters(2)
fail = 2.d0*viscosity*e2d*cos_theta-yield yield = max(c/compressibility,c+tan(phi)*pressure)
if (fail.gt.0.d0) then fail = 2.d0*viscosity*e2d-yield
viscosity=0.5d0*yield/e2d/cos_theta if (fail.gt.0.d0) then
is_plastic=.true. viscosity=0.5d0*yield/e2d
else is_plastic=.true.
is_plastic=.false. else
end if is_plastic=.false.
end if
case ('DPVII')
! strain softening
phi = plasticity_parameters(1)
strain_soft_in=plasticity_parameters(3)
if (strain_soft_in.gt.0.d0) then
strain_soft_out=plasticity_parameters(4)
strain_soft_phi=plasticity_parameters(5)*pi/180.d0
if (straintot.gt.strain_soft_in) then
fact=(straintot-strain_soft_in)/(strain_soft_out-strain_soft_in)
fact=min(fact,1.d0)
phi=phi+(strain_soft_phi-phi)*fact
endif
endif
c = plasticity_parameters(2)
sin_phi=sin(phi)
cos_phi=cos(phi)
yield = max(plasticity_parameters(2)/compressibility,pressure*sin_phi+c*cos_phi)
fail = 2.d0*viscosity*e2d-yield
if (fail.gt.0.d0) then
viscosity=0.5d0*yield/e2d
is_plastic=.true.
else
is_plastic=.false.
end if
case ('MC')
if (params%init_e2d) then
theta = 0.d0
else
theta = lode_angle(J2d,J3d)
endif
sin_theta = sin(theta)
cos_theta = cos(theta)
! strain softening
phi = plasticity_parameters(1)
strain_soft_in=plasticity_parameters(3)
if (strain_soft_in.gt.0.d0) then
strain_soft_out=plasticity_parameters(4)
strain_soft_phi=plasticity_parameters(5)*pi/180.d0
if (straintot.gt.strain_soft_in) then
fact=(straintot-strain_soft_in)/(strain_soft_out-strain_soft_in)
fact=min(fact,1.d0)
phi=phi+(strain_soft_phi-phi)*fact
endif
endif
c = plasticity_parameters(2)
sin_phi = sin(phi)
cos_phi = cos(phi)
zeta = cos_theta-sin_phi*sin_theta/sqrt3
! modified by Jean
!fail = -pressure*sin_phi+e2d*zeta-c*cos_phi
fail = pressure*sin_phi+2.d0*viscosity*e2d*zeta-c*cos_phi
if (fail.gt.0.d0) then
viscosity=0.5d0/e2d*(c*cos_phi-pressure*sin_phi)/zeta
!if (viscosity<0.d0) then
! viscosity=0.d0
! !print *,viscosity,c*cos_phi,pressure*sin_phi
!end if
is_plastic=.true.
else
is_plastic=.false.
end if
case ('Tresca')
if (params%init_e2d) then
theta = 0.d0
else
theta = lode_angle(J2d,J3d)
endif
yield = plasticity_parameters(1)
cos_theta = cos(theta)
fail = 2.d0*viscosity*e2d*cos_theta-yield
if (fail.gt.0.d0) then
viscosity=0.5d0*yield/e2d/cos_theta
is_plastic=.true.
else
is_plastic=.false.
end if
case default
print *,plasticity_type
call stop_run('error in vrm$')
flag_vrm_pb = .true.
case default
print *,plasticity_type
call stop_run('error in vrm$')
flag_vrm_pb = .true.
end select end select
!write (*,*) 'vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv' !write (*,*) 'vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv'
...@@ -217,44 +342,38 @@ call mpi_comm_size (mpi_comm_world,nproc,ierr) ...@@ -217,44 +342,38 @@ call mpi_comm_size (mpi_comm_world,nproc,ierr)
call mpi_comm_rank (mpi_comm_world,iproc,ierr) call mpi_comm_rank (mpi_comm_world,iproc,ierr)
do i=0,params%nmat do i=0,params%nmat
select case (trim(mat(i)%plasticity_type)) select case (trim(mat(i)%plasticity_type))
case ('No') case ('No')
case ('vM')
case ('DPI') case ('vM')
phi = mat(i)%plasticity_parameters(1)*pi/180.d0
c = mat(i)%plasticity_parameters(2) case ('DPI')
alpha = 2.d0*sin(phi) /sqrt(3.d0)/(3.d0-sin(phi))
k = 6.d0*c*cos(phi)/sqrt(3.d0)/(3.d0-sin(phi)) case ('DPII')
mat(i)%plasticity_parameters(8)=alpha
mat(i)%plasticity_parameters(9)=k case ('DPIII')
if (iproc.eq.0) then
write(8,*) 'material ',i case ('DPIV')
write(8,*) ' phi =',phi
write(8,*) ' c =',c case ('DPV')
write(8,*) ' alpha=',alpha
write(8,*) ' k =',k case ('DPVI')
end if
case ('DPII') case ('DPVII')
phi = mat(i)%plasticity_parameters(1)*pi/180.d0
c = mat(i)%plasticity_parameters(2) case ('MC')
alpha = tan(phi)/sqrt(9.d0+12.d0*(tan(phi))**2)
k = 3.d0*c /sqrt(9.d0+12.d0*(tan(phi))**2) case ('Tresca')
mat(i)%plasticity_parameters(8)=alpha
mat(i)%plasticity_parameters(9)=k case default
case ('MC') call stop_run('error in compute_plastic_params$')
phi = mat(i)%plasticity_parameters(1)*pi/180.d0
mat(i)%plasticity_parameters(8)=sin(phi) end select
mat(i)%plasticity_parameters(9)=cos(phi) if (iproc.eq.0) then
case ('Tresca') write(8,*) 'material ',i,'plasticity_type ',mat(i)%plasticity_type
case ('DPIII') write(8,*) 'plasticity_parameters',mat(i)%plasticity_parameters(:)
case default end if
call stop_run('error in compute_plastic_params$')
end select
if (iproc.eq.0) then
write(8,*) 'material ',i,'plasticity_type ',mat(i)%plasticity_type
write(8,*) 'plasticity_parameters',mat(i)%plasticity_parameters(:)
end if
end do end do
return return
end end
\ No newline at end of file
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment