UCREEPNETWORK

User subroutine to define time-dependent behavior (creep) for models defined within the parallel rheological framework.

User subroutine UCREEPNETWORK:

  • is intended to provide creep laws for nonlinear viscoelastic networks for models defined using the parallel rheological framework (see Parallel Rheological Framework);

  • can use and update solution-dependent state variables; and

  • can be used in conjunction with user subroutine USDFLD to redefine any field variables before they are passed in.

This page discusses:

Model Description

The user subroutine allows a creep law of the following general form to be defined:

ε¯˙cr=gcr(ε¯cr,I1cr,I¯1,I¯2,J,p,q~,t,θ,FV),

where

I1cr=I:Ccr,

and

I

is the identity tensor,

Ccr

is the right Cauchy-Green creep strain tensor,

ε¯˙cr

is the equivalent creep strain rate,

ε¯cr

is the equivalent creep strain,

I¯1

is the first invariant of B¯,

I¯2

is the second invariant of B¯,

J

is the determinant of the deformation gradient, F,

p

is the Kirchhoff pressure,

q~

is the equivalent deviatoric Kirchhoff stress,

t

is the time,

θ

is the temperature, and

FV

are field variables.

The left Cauchy-Green strain tensor, B¯, is defined as

B¯=F¯F¯T,

where F¯ is the deformation gradient with volume change eliminated, which is computed using

F¯=J-13F.

The user subroutine must define the increment of creep equivalent strain, Δε¯cr, as a function of the time increment, Δt, and the variables used in the definition of gcr, as well as the derivatives of the equivalent creep strain increment with respect to those variables. If any solution-dependent state variables are included in the definition of gcr, they must also be integrated forward in time in this user subroutine.

User Subroutine Interface

     subroutine ucreepnetwork (
C Must be updated
     *   outputData,
C Can be updated
     *   statev,
C Information (Read only)
     *   nOutput,
     *   nstatv,
     *   networkid,
     *   coords,
     *   temp,
     *   dtemp,
     *   nfield,
     *   predef,
     *   dpred,
     *   nprops,
     *   props,
     *   i_array,
     *   niarray,
     *   r_array,
     *   nrarray,
     *   c_array,
     *   ncarray)
C
      include 'aba_param.inc'
C
      parameter( io_creep_equiv_creepinc       = 1,
     *           io_creep_deqcreepinc_deqcreep = 2,
     *           io_creep_deqcreepinc_dqtild   = 3,
     *           io_creep_deqcreepinc_dinv1crp = 4,
     *           io_creep_deqcreepinc_dinv1    = 5,
     *           io_creep_deqcreepinc_dinv2    = 6,
     *           io_creep_deqcreepinc_ddetf    = 7,
     *           io_creep_deqcreepinc_dpress   = 8 )
C
      parameter( i_creep_kstep   = 1,
     *           i_creep_kinc    = 2,
     *           i_creep_noel    = 3,
     *           i_creep_npt     = 4,
     *           i_creep_layer   = 5,
     *           i_creep_kspt    = 6,
     *           i_creep_lend    = 7 )
C
      parameter( ir_creep_step_time  = 1,
     *           ir_creep_total_time = 2,
     *           ir_creep_creep_time = 3,
     *           ir_creep_timeinc    = 4,
     *           ir_creep_equiv_creep_strain = 5,
     *           ir_creep_qtild      = 6,
     *           ir_creep_inv1crp    = 7,
     *           ir_creep_inv1       = 8,
     *           ir_creep_inv2       = 9,
     *           ir_creep_detf       = 10,
     *           ir_creep_press      = 11 )
C
      parameter( ic_creep_material_name = 1 )
C
      dimension 
     *   statev(nstatv),
     *   predef(nfield),
     *   dpred(nfield),
     *   coords(*),
     *   props(nprops),
     *   outputData(nOutput),
     *   i_array(niarray),
     *   r_array(nrarray)

      character*80 c_array(ncarray)
C
      user coding to define outputData(io_creep_equiv_creepinc),
        outputData(io_creep_deqcreepinc_deqcreep),
        outputData(io_creep_deqcreepinc_dqtild),
        outputData(io_creep_deqcreepinc_dinv1crp),
        outputData(io_creep_deqcreepinc_dinv1),
        outputData(io_creep_deqcreepinc_dinv2),
        outputData(io_creep_deqcreepinc_ddetf) and
        outputData(io_creep_deqcreepinc_dpress)

      return
      end

Variables to Be Defined

outputData(io_creep_equiv_creepinc)

Equivalent creep strain increment, Δε¯cr.

outputData(io_creep_deqcreepinc_deqcreep)

The derivative: Δε¯cr/ε¯cr.

outputData(io_creep_deqcreepinc_dqtild)

The derivative: Δε¯cr/q~.

outputData(io_creep_deqcreepinc_dinv1crp)

The derivative: Δε¯cr/I1cr.

outputData(io_creep_deqcreepinc_dinv1)

The derivative: Δε¯cr/I¯1.

outputData(io_creep_deqcreepinc_dinv2)

The derivative: Δε¯cr/I¯2.

outputData(io_creep_deqcreepinc_ddetf)

The derivative: Δε¯cr/J.

outputData(io_creep_deqcreepinc_dpress)

The derivative: Δε¯cr/p.

Variables That Can Be Updated

statev

An array containing the user-defined solution-dependent state variables at this point.

Variables Passed in for Information

nOutput

Size of array outputData.

nstatv

Number of solution-dependent state variables associated with this material.

networkid

Network identification number, which identifies the network for which creep is defined.

coords

An array containing the current coordinates at this point.

temp

Temperature at the end of the increment.

dtemp

Increment of temperature.

nfield

Number of field variables.

predef

An array of interpolated values of predefined field variables at this point at the end of the increment, based on the values read in at the nodes and, optionally, redefined in user subroutine USDFLD.

dpred

An array of increments of predefined field variables.

nprops

User-specified number of property values associated with this creep model.

props

An array of user-specified property values that are used to define the creep model.

i_array(i_creep_kstep)

Step number.

i_array(i_creep_kinc)

Increment number.

i_array(i_creep_noel)

Element number.

i_array(i_creep_npt)

Integration point.

i_array(i_creep_layer)

Layer number (for layered solids).

i_array(i_creep_kspt)

Section point number within the current layer.

i_array(i_creep_lend)

Start/end of increment flag. The value of 0 denotes the beginning of the increment, and the value of 1 denotes the end of the increment.

niarray

Size of array i_array.

r_array(ir_creep_step_time)

Value of step time at the end of the increment.

r_array(ir_creep_total_time)

Value of total time at the end of the increment.

r_array(ir_creep_creep_time)

Value of creep time at the end of the increment.

r_array(ir_creep_timeinc)

Time increment.

r_array(ir_creep_equiv_creep_strain)

Equivalent creep strain.

r_array(ir_creep_qtild)

Equivalent deviatoric Kirchhoff stress.

r_array(ir_creep_inv1crp)

The first invariant, I1cr, of the right Cauchy-Green creep strain tensor, Ccr.

r_array(ir_creep_inv1)

The first invariant, I1¯, of the left Cauchy-Green strain tensor, B¯.

r_array(ir_creep_inv2)

The second invariant, I2¯, of the left Cauchy-Green strain tensor, B¯.

r_array(ir_creep_detf)

The determinant of the deformation gradient, F.

r_array(ir_creep_press)

Kirchhoff pressure.

nrarray

Size of array r_array.

c_array(ic_creep_material_name)

User-specified material name, left justified. Some internal material models are given names starting with the “ABQ_” character string. To avoid conflict, you should not use “ABQ_” as the leading string for the material name.

ncarray

Size of array c_array.

Example: Bergstrom-Boyce Model

As an example of the coding of user subroutine UCREEPNETWORK, consider the Bergstrom-Boyce model. In this case the equivalent creep strain rate is expressed as (see Parallel Rheological Framework)

ε¯˙cr=A(λcr-1+E)C(q~)m,

where

λcr=13I:Ccr

and

Ccr

is the right Cauchy-Green creep strain tensor,

q~

is the equivalent deviatoric Kirchhoff stress, and

A, m, C, and E

are material parameters.

The user subroutine would be coded as follows:

     subroutine ucreepnetwork (
C Must be updated
     *   outputData,
C Can be updated 
     *   statev,
C Information (Read only)
     *   nOutput,
     *   nstatv,
     *   networkid,
     *   coords,
     *   temp,
     *   dtemp,
     *   nfield,
     *   predef,
     *   dpred,
     *   nprops,
     *   props,
     *   i_array,
     *   niarray,
     *   r_array,
     *   nrarray,
     *   c_array,
     *   ncarray)
C
      include 'aba_param.inc'
C
      parameter( io_creep_equiv_creepinc       = 1,
     *           io_creep_deqcreepinc_deqcreep = 2,
     *           io_creep_deqcreepinc_dqtild   = 3,
     *           io_creep_deqcreepinc_dinv1crp = 4,
     *           io_creep_deqcreepinc_dinv1    = 5,
     *           io_creep_deqcreepinc_dinv2    = 6,
     *           io_creep_deqcreepinc_ddetf    = 7,
     *           io_creep_deqcreepinc_dpress   = 8 )
C
      parameter( i_creep_kstep   = 1,
     *           i_creep_kinc    = 2,
     *           i_creep_noel    = 3,
     *           i_creep_npt     = 4,
     *           i_creep_layer   = 5,
     *           i_creep_kspt    = 6,
     *           i_creep_lend    = 7 )
C
      parameter( ir_creep_step_time  = 1,
     *           ir_creep_total_time = 2,
     *           ir_creep_creep_time = 3,
     *           ir_creep_timeinc    = 4,
     *           ir_creep_equiv_creep_strain = 5,
     *           ir_creep_qtild      = 6,
     *           ir_creep_inv1crp    = 7,
     *           ir_creep_inv1       = 8,
     *           ir_creep_inv2       = 9,
     *           ir_creep_detf       = 10,
     *           ir_creep_press      = 11 )
C
      parameter( ic_creep_material_name = 1 )
C
C model parameters
      parameter ( zero=0.0d0,half=0.5d0,one=1.0d0,two=2.0d0,
     &     three=3.0d0,five=5.0d0,six=6.0d0 )
C
      dimension 
     *   statev(nstatv),
     *   predef(nfield),
     *   dpred(nfield),
     *   coords(*),
     *   props(nprops),
     *   outputData(nOutput),
     *   i_array(niarray),
     *   r_array(nrarray)

      character*80 c_array(ncarray)
C
C Bergstrom-Boyce Model
C
      A  = props(1)
      dm = props(2)
      C  = props(3)
      E  = props(4)
C
      dI1    = r_array(ir_creep_inv1crp)
      dLamb  = (dI1/three)**half
      sigmaB = r_array(ir_creep_qtild)
      dt     = r_array(ir_creep_timeinc)
C
C deq
      deq = dt*A*(dLamb-one+E)**C*sigmaB**dm
C
C d(deq)/(dI1crp)
      deqdi1 = deq*C/(dLamb-one+E)/dLamb/six
C
C d(eq)/d(eq)
      deqeq = zero
C
C d(eq)/d(q)
      deqdq = dm*dt*A*(dLamb-one+E)**C*sigmaB**(dm-one)
C
C set output
      outputData(io_creep_equiv_creepinc)       = deq
      outputData(io_creep_deqcreepinc_deqcreep) = deqeq
      outputData(io_creep_deqcreepinc_dqtild)   = deqdq
      outputData(io_creep_deqcreepinc_dinv1crp) = deqdi1
      outputData(io_creep_deqcreepinc_dinv1)    = zero
      outputData(io_creep_deqcreepinc_dinv2)    = zero
      outputData(io_creep_deqcreepinc_ddetf)    = zero
      outputData(io_creep_deqcreepinc_dpress)   = zero
C
      return
      end