UAMP

User subroutine to specify amplitudes.

User subroutine UAMP:

  • 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 their definition; and

  • can optionally compute the derivatives and integrals of the amplitude function.

This page discusses:

Explicit Solution Dependence

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.

User Subroutine Interface

      SUBROUTINE UAMP(
     *     ampName, time, ampValueOld, dt, nProps, props, nSvars, 
     *     svars, lFlagsInfo,
     *     nSensor, sensorValues, sensorNames, jSensorLookUpTable, 
     *     AmpValueNew, 
     *     lFlagsDefine,
     *     AmpDerivative, AmpSecDerivative, AmpIncIntegral,
     *     AmpDoubleIntegral)
C
      INCLUDE 'ABA_PARAM.INC'

C     time indices
      parameter (iStepTime        = 1,
     *           iTotalTime       = 2,
     *           nTime            = 2)
C     flags passed in for information
      parameter (iInitialization   = 1,
     *           iRegularInc       = 2,
     *           iCuts             = 3,
     *           ikStep            = 4,
     *           nFlagsInfo        = 4)
C     optional flags to be defined
      parameter (iComputeDeriv       = 1,
     *           iComputeSecDeriv    = 2,
     *           iComputeInteg       = 3,
     *           iComputeDoubleInteg = 4,
     *           iStopAnalysis       = 5,
     *           iConcludeStep       = 6,
     *           nFlagsDefine        = 6)
      dimension time(nTime), lFlagsInfo(nFlagsInfo),
     *          lFlagsDefine(nFlagsDefine)
      dimension jSensorLookUpTable(*)
      dimension sensorValues(nSensor), svars(nSvars), props(nProps)
      character*80 sensorNames(nSensor)
      character*80 ampName

      user coding to define AmpValueNew, and 
      optionally lFlagsDefine, AmpDerivative, AmpSecDerivative, 
      AmpIncIntegral, AmpDoubleIntegral

      RETURN
      END

Variables to Be Defined

AmpValueNew

Current value of the amplitude.

Variables That Can Be Updated

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(iComputeDoubleInteg) If set to 1, you must provide the computation of the amplitude incremental double 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 exists). 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 UAMP 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.

AmpDoubleIntegral

Current value of the amplitude incremental double integral.

Variables Passed in for Information

ampName

User-specified amplitude name, left justified.

time(iStepTime)

Current value of step time or frequency.

time(iTotalTime)

Current value of total time.

ampValueOld

Old value of the amplitude from the previous increment.

dt

Time increment.

props

User-specified array of material constants associated with this amplitude definition.

nProps

User-defined number of material constants associated with this amplitude definition.

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

lFlagsInfo(iInitialization) This flag is equal to 1 if UAMP is called from the initialization phase of the first analysis step and is set to 0 otherwise.
lFlagsInfo(iRegularInc) This flag is equal to 1 if UAMP is called from a regular increment and is set to 0 if called from the initialization phase of the first analysis step.
lFlagsInfo(iCuts) Number of cutbacks in this increment.
lFlagsInfo(ikStep) Step number.
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 IGETSENSORID and GETSENSORVALUE.

Example: Amplitude Definition Using Sensor and State Variables

c     user amplitude subroutine
      Subroutine UAMP(
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,
     *     AmpDoubleIntegral)
      
      include 'aba_param.inc'

C     svars - additional state variables, similar to (V)UEL
      dimension sensorValues(nSensor), svars(nSvars),
     * props(nProps)
      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,
     *           iCuts             = 3,
     *           ikStep            = 4,
     *           nFlagsInfo        = 4)
C     optional flags to be defined
      parameter( iComputeDeriv       	= 1,
     *           iComputeSecDeriv    	= 2,
    	*           iComputeInteg      		= 3,
	    *           iComputeDoubleInteg 	= 4,
     *           iStopAnalysis       	= 5,
     *           iConcludeStep     	  	= 6,
     *           nFlagsDefine       		= 6)

      parameter( tStep=0.18d0, tAccelerateMotor = .00375d0, 
     *           	omegaFinal=23.26d0,
     * zero=0.0d0, one=1.0d0, two=2.0d0, four=4.0d0)

      dimension time(nTime), lFlagsInfo(nFlagsInfo),
     *          lFlagsDefine(nFlagsDefine)
      dimension jSensorLookUpTable(*)

      lFlagsDefine(iComputeDeriv)       = 1
      lFlagsDefine(iComputeSecDeriv)    = 1
      lFlagsDefine(iComputeInteg)       = 1
      lFlagsDefine(iComputeDoubleInteg) = 1

c     get sensor value
      vTrans_CU1  = GetSensorValue('HORIZ_TRANSL_MOTION',
     *                             jSensorLookUpTable,
     *                             sensorValues)

      if (ampName(1:22) .eq. 'MOTOR_WITH_STOP_SENSOR' ) then
         if (lFlagsInfo(iInitialization).eq.1) then 
            AmpSecDerivative  = zero
            AmpDerivative     = omegaFinal/tAccelerateMotor
            ampValueNew       = zero
            AmpIncIntegral    = zero
            AmpDoubleIntegral = zero

            svars(1) = zero
            svars(2) = zero
         else
            tim = time(iStepTime)

c           ramp up the angular rot velocity  of the 
c           electric motor
c           after which hold constant
            if (tim .le. tAccelerateMotor) then 
               AmpSecDerivative  = zero
               AmpDerivative     = omegaFinal/tAccelerateMotor
               ampValueNew       = omegaFinal*tim/tAccelerateMotor
               AmpIncIntegral    = dt*(ampValueOld+ampValueNew)/
               two
               AmpDoubleIntegral = dt**2*(ampValueOld+ampValueNew)/
               four
            else
               AmpSecDerivative  = zero
               AmpDerivative     = zero
               ampValueNew       = omegaFinal
               AmpIncIntegral    = dt*(ampValueOld+ampValueNew)/
               two
               AmpDoubleIntegral = dt**2*(ampValueOld+ampValueNew)/
               four
            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. zero .and.
     *          tim .gt. tAccelerateMotor ) then 
               svars(2) = svars(2) + one
            end if            
            nrCrossings = int(svars(2))

c           stop the motor if sensor crosses zero the second
            time 
            if (nrCrossings.eq.2) then 
               ampValueNew =  zero
               lFlagsDefine(iConcludeStep)=1
            end if

c           store sensor value
            svars(1) = vTrans_CU1

         end if         
      end if 

      return
      end