1.1.58 UVARM
User subroutine to generate element output.

Product: Abaqus/Standard  

References

Overview

User subroutine UVARM:

Accessing material point data

You are provided with access to the values of the material point quantities through the utility routine GETVRM described in Obtaining material point information in an Abaqus/Standard analysis, Section 2.1.6. In a nonlinear analysis values returned will correspond to the current solution iteration, representing a converged solution only at the final iteration for each increment. The values of the material point data are recovered in the arrays ARRAY, JARRAY, and FLGRAY for floating point, integer, and character data, respectively. Floating point data are recovered as double-precision data.

Using user-defined output variables

The output identifier for the user-defined output quantities is UVARM. Individual components are accessed with UVARMn, where , NUVARM. You must specify the number of user-defined output variables, NUVARM, for a given material to allocate space at each material calculation point for each variable. The user-defined output variables are available for both printed and results file output and are written to the output database and restart files for contouring, printing, and X–Y plotting in Abaqus/CAE. Any number of user-defined output variables can be used.

Output precision

The data are provided in double precision for output to the data (.dat) and results (.fil) files and are written to the output database (.odb) file in single precision. Because the user provides UVARM output variables in double precision, numeric overflow errors related to output to the output database file may occur in cases where the output results exceed the capacity for single-precision representation even when no overflow errors occur in UVARM.

User subroutine interface

      SUBROUTINE UVARM(UVAR,DIRECT,T,TIME,DTIME,CMNAME,ORNAME,
     1 NUVARM,NOEL,NPT,LAYER,KSPT,KSTEP,KINC,NDI,NSHR,COORD,
     2 JMAC,JMATYP,MATLAYO,LACCFLA)
      INCLUDE 'ABA_PARAM.INC'
C
      CHARACTER*80 CMNAME,ORNAME
      CHARACTER*3 FLGRAY(15)
      DIMENSION UVAR(NUVARM),DIRECT(3,3),T(3,3),TIME(2)
      DIMENSION ARRAY(15),JARRAY(15),JMAC(*),JMATYP(*),COORD(*)

C     The dimensions of the variables FLGRAY, ARRAY and JARRAY
C     must be set equal to or greater than 15.


      user coding to define UVAR


      RETURN
      END

Variable to be defined

UVAR(NUVARM)

An array containing the user-defined output variables. These are passed in as the values at the beginning of the increment and must be returned as the values at the end of the increment.

Variables passed in for information

DIRECT(3,3)

An array containing the direction cosines of the material directions in terms of the global basis directions. DIRECT(1,1), DIRECT(2,1), DIRECT(3,1) give the (1, 2, 3) components of the first material direction; DIRECT(1,2), DIRECT(2,2), DIRECT(3,2) give the second material direction, etc. For shell and membrane elements the first two directions are in the plane of the element and the third direction is the normal. This information is not available for beam and truss elements.

T(3,3)

An array containing the direction cosines of the material orientation components relative to the element basis directions. This is the orientation that defines the material directions (DIRECT) in terms of the element basis directions. For continuum elements T and DIRECT are identical. For shell and membrane elements T(1,1) , T(1,2) , T(2,1) , T(2,2) , T(3,3) , and all other components are zero, where is the counterclockwise rotation around the normal vector that defines the orientation. If no orientation is used, T is an identity matrix. Orientation is not available for beam and truss elements.

TIME(1)

Value of step time at the end of the current increment.

TIME(2)

Value of total time at the end of the current increment.

DTIME

Time increment.

CMNAME

User-specified material name, left justified.

ORNAME

User-specified local orientation name, left justified.

NUVARM

User-specified number of user-defined output variables.

NOEL

Element number.

NPT

Integration point number.

LAYER

Layer number (for composite shells and layered solids).

KSPT

Section point number within the current layer.

KSTEP

Step number.

KINC

Increment number.

NDI

Number of direct stress components at this point.

NSHR

Number of shear stress components at this point.

COORD

Coordinates at this material point.

JMAC

Variable that must be passed into the GETVRM utility routine to access an output variable.

JMATYP

Variable that must be passed into the GETVRM utility routine to access an output variable.

MATLAYO

Variable that must be passed into the GETVRM utility routine to access an output variable.

LACCFLA

Variable that must be passed into the GETVRM utility routine to access an output variable.

Example: Calculation of stress relative to shift tensor

Below is an example of user subroutine UVARM. The subroutine calculates the position of the current state of stress relative to the center of the yield surface for the kinematic hardening plasticity model by subtracting the kinematic shift tensor, , from the stress tensor, . See Metal plasticity models, Section 4.3.1 of the Abaqus Theory Guide, for additional details.

      SUBROUTINE UVARM(UVAR,DIRECT,T,TIME,DTIME,CMNAME,ORNAME,
     1 NUVARM,NOEL,NPT,LAYER,KSPT,KSTEP,KINC,NDI,NSHR,COORD,
     2 JMAC,JMATYP,MATLAYO,LACCFLA) 
C
      INCLUDE 'ABA_PARAM.INC'
C
      CHARACTER*80 CMNAME,ORNAME
      CHARACTER*3 FLGRAY(15)
      DIMENSION UVAR(NUVARM),DIRECT(3,3),T(3,3),TIME(2)
      DIMENSION ARRAY(15),JARRAY(15),JMAC(*),JMATYP(*),COORD(*)
C
C Error counter:
      JERROR = 0
C Stress tensor:
      CALL GETVRM('S',ARRAY,JARRAY,FLGRAY,JRCD,JMAC,JMATYP,
     1 MATLAYO,LACCFLA)
      JERROR = JERROR + JRCD
      UVAR(1) = ARRAY(1)
      UVAR(2) = ARRAY(2)
      UVAR(3) = ARRAY(3)
      UVAR(4) = ARRAY(4)
      UVAR(5) = ARRAY(5)
      UVAR(6) = ARRAY(6)
C Kinematic shift tensor:
      CALL GETVRM('ALPHA',ARRAY,JARRAY,FLGRAY,JRCD,JMAC,JMATYP,
     1 MATLAYO,LACCFLA)
      JERROR = JERROR + JRCD
C Calculate the position relative to the center of the
C yield surface:
      UVAR(1) = UVAR(1) - ARRAY(1)
      UVAR(2) = UVAR(2) - ARRAY(2)
      UVAR(3) = UVAR(3) - ARRAY(3)
      UVAR(4) = UVAR(4) - ARRAY(4)
      UVAR(5) = UVAR(5) - ARRAY(5)
      UVAR(6) = UVAR(6) - ARRAY(6)
C If error, write comment to .DAT file:
      IF(JERROR.NE.0)THEN
        WRITE(6,*) 'REQUEST ERROR IN UVARM FOR ELEMENT NUMBER ',
     1      NOEL,'INTEGRATION POINT NUMBER ',NPT
      ENDIF
      RETURN
      END