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.
Explicit Solution DependenceThe 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
Variables That Can Be Updated
Variables Passed in for Information
Example: Amplitude Definition Using Sensor and State Variablesc 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 | |||||||||||||||||||||||||||||||||