Product: Abaqus/Explicit

User subroutine VUAMP:
allows you to define the current value of an amplitude definition as a function of time;
can be used to model control engineering aspects of your system when sensors are used (sensor values are from the beginning of the increment);
can use a predefined number of state variables in its definition; and
can optionally compute the derivatives and integrals of the amplitude function.

The solution dependence introduced in this user subroutine is explicit: all data passed in the subroutine for information or to be updated are values at the beginning of that increment.

SUBROUTINE VUAMP(
* ampName, time, ampValueOld, dt, nprops, props, nSvars,
* svars, lFlagsInfo, nSensor, sensorValues, sensorNames,
* jSensorLookUpTable,
* AmpValueNew,
* lFlagsDefine,
* AmpDerivative, AmpSecDerivative, AmpIncIntegral)
INCLUDE 'VABA_PARAM.INC'
C time indices
parameter (iStepTime = 1,
* iTotalTime = 2,
* nTime = 2)
C flags passed in for information
parameter (iInitialization = 1,
* iRegularInc = 2,
* ikStep = 3,
* nFlagsInfo = 3)
C optional flags to be defined
parameter (iComputeDeriv = 1,
* iComputeSecDeriv = 2,
* iComputeInteg = 3,
* iStopAnalysis = 4,
* iConcludeStep = 5,
* nFlagsDefine = 5)
dimension time(nTime), lFlagsInfo(nFlagsInfo),
* lFlagsDefine(nFlagsDefine),
* sensorValues(nSensor),
* props(nprops),
* sVars(nSvars)
character*80 sensorNames(nSensor)
character*80 ampName
dimension jSensorLookUpTable(*)
user coding to define AmpValueNew, and
optionally lFlagsDefine, AmpDerivative, AmpSecDerivative,
AmpIncIntegral
RETURN
END
lFlagsDefine
Integer flag array to determine whether the computation of additional quantities is necessary or to set step continuation requirements.
| lFlagsDefine(iComputeDeriv) | If set to 1, you must provide the computation of the amplitude derivative. The default is 0, which means that Abaqus computes the derivative automatically. |
| lFlagsDefine(iComputeSecDeriv) | If set to 1, you must provide the computation of the amplitude second derivative. The default is 0, which means that Abaqus computes the second derivative automatically. |
| lFlagsDefine(iComputeInteg) | If set to 1, you must provide the computation of the amplitude incremental integral. The default is 0, which means that Abaqus computes the incremental integral automatically. |
| lFlagsDefine(iStopAnalysis) | If set to 1, the analysis will be stopped and an error message will be issued. The default is 0, which means that Abaqus will not stop the analysis. |
| lFlagsDefine(iConcludeStep) | If set to 1, Abaqus will conclude the step execution and advance to the next step (if a next step is available). The default is 0. |
svars
An array containing the values of the solution-dependent state variables associated with this amplitude definition. The number of such variables is nsvars (see above). You define the meaning of these variables.
This array is passed into VUAMP containing the values of these variables at the start of the current increment. In most cases they should be updated to be the values at the end of the increment.
AmpDerivative
Current value of the amplitude derivative.
AmpSecDerivative
Current value of the amplitude second derivative.
AmpIncIntegral
Current value of the amplitude incremental integral.

ampName
User-specified amplitude name, left justified.
time(iStepTime)
Current value of step time.
time(iTotalTime)
Current value of total time.
ampValueOld
Old value of the amplitude from the previous increment.
dt
Current stable time increment.
nprops
User-defined number of properties associated with this amplitude definition.
props(nprops)
User-supplied amplitude properties.
nSvars
User-defined number of solution-dependent state variables associated with this amplitude definition.
lFlagsInfo
Integer flag array with information regrading the current call to VUAMP:
nSensor
Total number of sensors in the model.
sensorValues
Array with sensor values at the end of the previous increment. Each sensor value corresponds to a history output variable associated with the output database request defining the sensor.
sensorNames
Array with user-defined sensor names in the entire model, left justified. Each sensor name corresponds to a sensor value provided with the output database request. All names will be converted to uppercase characters if lowercase or mixed-case characters were used in their definition.
jSensorLookUpTable
Variable that must be passed into the utility functions IVGETSENSORID and VGETSENSORVALUE.

c user amplitude subroutine
Subroutine VUAMP(
C passed in for information and state variables
* ampName, time, ampValueOld, dt, nprops, props, nSvars,
* svars, lFlagsInfo, nSensor, sensorValues, sensorNames,
* jSensorLookUpTable,
C to be defined
* ampValueNew,
* lFlagsDefine,
* AmpDerivative, AmpSecDerivative, AmpIncIntegral)
include 'vaba_param.inc'
C svars - additional state variables, similar to (V)UEL
dimension sensorValues(nSensor), props(nprops),
* svars(nSvars)
character*80 sensorNames(nSensor)
character*80 ampName
C time indices
parameter( iStepTime = 1,
* iTotalTime = 2,
* nTime = 2)
C flags passed in for information
parameter( iInitialization = 1,
* iRegularInc = 2,
* ikStep = 3,
* nFlagsInfo = 3)
C optional flags to be defined
parameter( iComputeDeriv = 1,
* iComputeSecDeriv = 2,
* iComputeInteg = 3,
* iStopAnalysis = 4,
* iConcludeStep = 5,
* nFlagsDefine = 5)
parameter( tStep=0.18, tAccelerateMotor = .00375,
* omegaFinal=23.26)
c Alternatively, assign the user-defined amplitude
c properties on the data lines rather than using a parameter
c definition above.
c tStep = props(1)
c tAccelerateMotor = props(2)
c omegaFinal = props(3)
dimension time(nTime), lFlagsInfo(nFlagsInfo),
* lFlagsDefine(nFlagsDefine)
dimension jSensorLookUpTable(*)
lFlagsDefine(iComputeDeriv) = 1
lFlagsDefine(iComputeSecDeriv) = 1
c get sensor value
vTrans_CU1 = vGetSensorValue('HORIZ_TRANSL_MOTION',
* jSensorLookUpTable,
* sensorValues)
if (ampName(1:22) .eq. 'MOTOR_WITH_STOP_SENSOR' ) then
if (lFlagsInfo(iInitialization).eq.1) then
ampValueNew = ampValueOld
svars(1) = 0.0
svars(2) = 0.0
else
tim = time(iStepTime)
c ramp up the angular rot velocity of the electric
c motor after which hold constant
if (tim .le. tAccelerateMotor) then
ampValueNew = omegaFinal*tim/tAccelerateMotor
else
ampValueNew = omegaFinal
end if
c retrieve old sensor value
vTrans_CU1_old = svars(1)
c detect a zero crossing and count the number of
c crossings
if (vTrans_CU1_old*vTrans_CU1 .le. 0.0 .and.
* tim .gt. tAccelerateMotor ) then
svars(2) = svars(2) + 1.0
end if
nrCrossings = int(svars(2))
c stop the motor if sensor crosses zero the second
c time
if (nrCrossings.eq.2) then
ampValueNew = 0.0
lFlagsDefine(iConcludeStep)=1
end if
c store sensor value
svars(1) = vTrans_CU1
end if
end if
return
end