Turntable Program Code




This page contains the source code portion of the Basic Stamp 2 program that controls the turntable. Note that this program is written using the PBASIC 2.5 version. The complete version 2 code and documentation can be downloaded using this link:  TurntableV2.zip The original code is available here:  Turntable.zip

' ======================================================================
' TurntableV2.bs2                                             5-03-2005

'{$STAMP BS2}
'{$PBASIC 2.5}

' I/O bit definitions (74C922 and Allegro 3977 stepper controller).

KeyData1        PIN     0       ' Keypad chip data in
KeyData2        PIN     1       ' Keypad chip data in
KeyData4        PIN     2       ' Keypad chip data in
KeyData8        PIN     3       ' Keypad chip data in
KeyData         PIN     4       ' Keypad chip data available
KeyEnable       PIN     5       ' Keypad chip data read
StepClock       PIN     6       ' Stepper chip step input
StepDir         PIN     7       ' Stepper chip step direction
StepMs1         PIN     8       ' Stepper chip microstep size input 1
StepMs2         PIN     9       ' Stepper chip microstep size input 2
StepReset       PIN     10      ' Stepper chip reset (active low)
TurnEnable      PIN     11      ' Turnout enable pin
SoundPin        PIN     12      ' Sound output pin
HomeSensor      PIN     13      ' Turntable home position sensor
KeyEntry        PIN     14      ' Keypad data entry Led
Heartbeat       PIN     15      ' BS2 code heartbeat Led
TestMode        VAR     IN15    ' Mode switch

' Program constants

DefaultDir      CON     %1101111111100000
InitRep         CON     150             ' Initial auto-repeat delay
AutoRep         CON     32              ' Auto-repeat key rate
Clockwise       CON     1               ' Clockwise rotation
CounterClock    CON     0               ' Counter-clockwise rotation

' Note: CircleSize, TrackPosH, and TrackPosT point to low memory where the
' position data is stored. Ensure that changes made to program does not cause
' the code to extend below address 44. Verify using the memory map toolbar
' button.

CircleSize      CON     0               ' Calculated circle size
TrackPosH       CON     2               ' Programmed head-end positions
TrackPosT       CON     22              ' Programmed tail-end positions
TT1Close        CON     8               ' 74LS38 pin 8
TT1Open         CON     4               ' 74LS38 pin 11
TT2Close        CON     2               ' 74LS38 pin 6
TT2Open         CON     1               ' 74LS38 pin 3

' Program variables

Control         VAR     Word            ' Program control bits
ProgramMode     VAR     Control.BIT0    ' 0 = Operate, 1 = Program
KeyPressed      VAR     Control.BIT1    ' 1 = Key pressed
MotionKey       VAR     Control.BIT2    ' 1 = Program mode motion key pressed
Alignment       VAR     Control.BIT3    ' 0 = Head-end, 1 = Tail-end
ClearPos        VAR     Control.BIT4    ' 0 = normal, 1 = clear position data
HomeDone        VAR     Control.BIT5    ' 1 = Turntable FindHome done
TT1State        VAR     Control.BIT6    ' 0 = closed, 1 = open
TT2State        VAR     Control.BIT7    ' 0 = closed, 1 = open
RandMvmt        VAR     Control.BIT8    ' 0 = normal, 1 = random movement

LedCount        VAR     Byte            ' Counter for Led state toggle
AutoMove        VAR     Byte            ' Automatic movement delay counter
InactCount      VAR     Nib             ' Keypad inactivity counter
KeyTran         VAR     Nib             ' Translated pressed key value
KeyEnt1         VAR     Nib             ' Keypad first number
KeyEnt2         VAR     Nib             ' Keypad second number

Position        VAR     Word            ' Current turntable position
MoveWork        VAR     Word            ' Working location
MoveSteps       VAR     Word            ' Working location
CircleWork      VAR     Word            ' Working location
RandomNmbr      VAR     Word            ' Random number for auto move

StepDelay       VAR     Byte            ' Step delay working location
StepRamp        VAR     Byte            ' Ramp up/down point
StepMin         CON     8               ' Minimum step delay
StepMax         CON     20              ' Maximum step delay
PosAdj          CON     4               ' Gear backlash movement
InitPos         CON     8               ' Power up track position
InitEnd         CON     11              ' Power up bridge end position
RandomMove      CON     255             ' Random movement time delay

'--------------------------------------------------------------------------
' This section initializes all working variables to power on settings.

ProgramStart:
   DIRS = DefaultDir                    ' Set default I/O direction bits
   LOW TurnEnable                       ' Disable turnouts
   HIGH KeyEnable                       ' Deselect keypad chip
   HIGH Heartbeat                       ' Turn off heartbeat led
   HIGH KeyEntry                        ' Turn off 1st entry led
   AutoMove = RandomMove                ' Set initial random move count
   HIGH StepMs1                         ' Select 8x microstepping
   HIGH StepMs2                         ' Select 8x microstepping
   HIGH StepReset                       ' Remove stepper chip reset
   INPUT Heartbeat                      ' Set pin to input
   IF TestMode = 0 THEN TestLoop        ' Run test code if in test mode
   OUTPUT Heartbeat                     ' Set pin to output
   GOSUB FindHome                       ' Find reference sensor
   READ CircleSize, CircleWork.HIGHBYTE ' Get the saved circle size
   READ CircleSize +1, CircleWork.LOWBYTE
   IF HomeDone = 1 THEN                 ' Home position found?
      IF InitPos <> 0 AND InitEnd <> 0 THEN  ' Initial track specified?
         KeyEnt1 = InitPos              ' Set initial track position
         KeyEnt2 = InitEnd
         GOSUB OperMove                 ' Process motion operation
      ENDIF
   ENDIF
'--------------------------------------------------------------------------
' Begin main program loop. Each iteration decrements the LedCount variable.
' Calls are made to subroutines for processing of keypad input. In programming
' mode, the heartbeat timing loop counter (LedCount) is used for the initial
' and subsequent auto-repeat time delay.

MainLoop:
   PAUSE 1                              ' Adjust for 1 second heartbeat
   LedCount = LedCount - 1              ' Decrement heartbeat indicator timer
   IF LedCount = 0 THEN                 ' Heartbeat Led state change?
      IF ProgramMode = 1 THEN           ' Programming mode?
         LOW Heartbeat                  ' Heartbeat Led on solid
      ELSE
         TOGGLE Heartbeat               ' Change heartbeat Led state
         IF RandomMove <> 0 THEN        ' Random turntable movement enabled?
            IF AutoMove = 0 THEN        ' Random move delay expired?
               GOSUB RandMove           ' Yes, position to a random track
            ELSE
               AutoMove = AutoMove - 1  ' Decrement auto move delay
            ENDIF
         ENDIF
      ENDIF
      IF KeyEntry = 0 THEN              ' Waiting for second keypad input?
         IF KeyPressed = 0 THEN         ' Yes. Is key still presssed?
            IF InactCount = 0 THEN      ' No. Has inactivity timer expired?
               HIGH KeyEntry            ' Yes, turn off 1st entry Led
            ELSE
               InactCount = InactCount - 1 ' Decrement inactivity counter
            ENDIF
         ENDIF
      ELSE
         IF KeyPressed = 1 THEN         ' Is key still presssed?
            IF ProgramMode = 1 THEN     ' Yes. Programming mode?
               IF MotionKey = 1 THEN    ' Yes. Motion command entered?
                  KeyPressed = 0        ' Reset key pressed flag
                  LedCount = AutoRep    ' Subsequent key auto-repeat delay
               ENDIF
            ENDIF
         ENDIF
      ENDIF
   ENDIF

   IF KeyData = 1 THEN                  ' Keypad input available?
      IF KeyPressed = 0 THEN            ' New key closure?
         GOSUB KeyPadIn                 ' Read key number and save
         KeyPressed = 1                 ' Set key pressed flag
         IF RandomMove <> 0 THEN        ' Random turntable movement enabled?
            AutoMove = RandomMove       ' Reset auto move time delay
         ENDIF
         IF ProgramMode = 1 AND MotionKey = 1 THEN
            IF LedCount <> AutoRep THEN
               LedCount = InitRep       ' Set initial key auto-repeat delay
            ENDIF
         ENDIF
      ENDIF
   ELSE
      KeyPressed = 0                    ' Reset key pressed flag
      MotionKey = 0
   ENDIF
   GOTO MainLoop                        ' Loop forever

'--------------------------------------------------------------------------
' This code is called to process keypad input. The current program mode
' (Operate or Program) determines how the inputs are acted upon. We need
' to translate the read key value due to the wiring of a 12 keypad device
' to a 16 key 74C922 encoder.

KeyPadIn:
   LOW KeyEnable                        ' Enable keypad data read
   LOOKUP INA, [1, 2, 3, 15, 4, 5, 6, 15, 7, 8, 9, 15, 10, 0, 11, 15], KeyTran
   HIGH KeyEnable                       ' Disable keypad data read
   IF KeyTran = 15 THEN                 ' Invalid key entered?
      GOSUB SoundOut                    ' Sound warning tones
      RETURN
   ENDIF
   IF KeyEntry = 1 THEN                 ' First entry led off?
      KeyEnt1 = KeyTran                 ' Yes, store 1st value
      IF ProgramMode = 1 THEN           ' Programming mode?
         KeyTran = 15                   ' Initialize test variable
         LOOKDOWN KeyEnt1, [1, 3, 4, 6, 7, 9], KeyTran
         IF KeyTran <> 15 THEN          ' Motion command entered?
            GOSUB PrgmMove              ' Yes, process motion key
            MotionKey = 1               ' Set motion key flag for auto-repeat.
            RETURN
         ENDIF
         MotionKey = 0                  ' Reset motion key flag
         LOOKDOWN KeyEnt1, [0, 2, 5, 8], KeyTran
         IF KeyTran <> 15 THEN          ' Option command entered?
            GOSUB PrgmOption            ' Process option key
            RETURN
         ENDIF
      ENDIF
      LOW KeyEntry                      ' Turn on 1st entry Led
      InactCount = 10                   ' Set inactivity timer
   ELSE
      KeyEnt2 = KeyTran                 ' Store 2nd value
      HIGH KeyEntry                     ' Turn off 1st entry Led
      InactCount = 0                    ' Reset inactivity timer
      IF KeyEnt1 = 10 AND KeyEnt2 = 10 THEN  ' '**' entered?
         ProgramMode = ~ProgramMode     ' Yes, change program mode
      ELSEIF KeyEnt1 = 1 AND KeyEnt2 = 1 THEN  ' Toggle TT1 ?
         GOSUB TurnoutToggle            ' Yes, do it
      ELSEIF KeyEnt1 = 2 AND KeyEnt2 = 2 THEN  ' Toggle TT2 ?
         GOSUB TurnoutToggle            ' Yes, do it
      ELSEIF KeyEnt1 = 0 AND KeyEnt2 = 0 THEN  ' Re-index to home sensor ?
         GOSUB FindHome                 ' Yes, do it
      ELSE
         IF ProgramMode = 0 THEN        ' Operate mode?
            GOSUB OperMove              ' Process motion operation
         ELSE
            GOSUB PrgmPosition          ' Store position information
         ENDIF
      ENDIF
   ENDIF
   RETURN

'--------------------------------------------------------------------------
' This code is called to process the move command keypad input (keys: 1, 3,
' 4, 6, 7, and 9) as defined in the program mode description.

PrgmMove:
   IF CircleWork = 0 THEN               ' Zero value CircleWork?
      GOSUB SoundOut1                   ' Sound warning tone
      RETURN
   ENDIF
   LOOKUP KeyEnt1, [0, -1, 0, 1, -64, 0, 64, -128, 0, 128], MoveSteps
   IF MoveSteps > 32767 THEN            ' Negative MoveSteps?
      MoveSteps = ABS MoveSteps
      StepDir = CounterClock            ' Step counter-clockwise
      IF Position < MoveSteps THEN
         Position = (CircleWork + Position) - MoveSteps
      ELSE
         Position = Position - MoveSteps
      ENDIF
   ELSE
      StepDir = Clockwise               ' Step clockwise
      IF MoveSteps > (CircleWork - Position) THEN
         Position = Position + MoveSteps - CircleWork
      ELSE
         Position = Position + MoveSteps
      ENDIF
   ENDIF
   GOSUB DoSteps                        ' Move the turntable
   RETURN

'--------------------------------------------------------------------------
' This code is called to process the option command keypad input (keys: 0,
' 2, 5, and 8) as defined in the program mode description.

PrgmOption:
   SELECT KeyEnt1
      CASE 0
         GOSUB FindHome                         ' Find reference sensor
         GOSUB CalCircle                        ' Determine circle size
      CASE 2
         Alignment = 0                          ' Set head-end alignment
         FREQOUT SoundPin, 15, 523              ' Confirm key press
      CASE 5
         Alignment = 1                          ' Set tail-end alignment
         FREQOUT SoundPin, 15, 523              ' Confirm key press
      CASE 8
         ClearPos = 1                           ' Set position clear flag
      CASE ELSE
         GOSUB SoundOut                         ' Sound invalid key tone
   ENDSELECT
   RETURN

'--------------------------------------------------------------------------
' This code is called to process the position store command keypad input (two
' keys: #x) as defined in the program mode description. A location is written
' only if necessary.

PrgmPosition:
   IF KeyEnt1 = 11 AND KeyEnt2 < 10 THEN        ' Must have entered #x
      IF HomeDone = 0 THEN                      ' Home position found yet?
         GOSUB SoundOut1                        ' No, sound warning tone
      ELSEIF Alignment = 0 THEN
         READ TrackPosH + KeyEnt2*2, MoveWork.HIGHBYTE ' Get current entry position
         READ TrackPosH + KeyEnt2*2+1, MoveWork.LOWBYTE
         IF ClearPos = 1 THEN
            IF MoveWork.HIGHBYTE <> 0 THEN
               WRITE TrackPosH + KeyEnt2*2, 0   ' Clear head-end position
            ENDIF
            IF MoveWork.LOWBYTE <> 0 THEN
               WRITE TrackPosH + KeyEnt2*2+1, 0
            ENDIF
         ELSE
            IF MoveWork.HIGHBYTE <> Position.HIGHBYTE THEN
               WRITE TrackPosH + KeyEnt2*2, Position.HIGHBYTE ' Head-end position
            ENDIF
            IF MoveWork.LOWBYTE <> Position.LOWBYTE THEN
               WRITE TrackPosH + KeyEnt2*2+1, Position.LOWBYTE
            ENDIF
         ENDIF
      ELSE
         READ TrackPosT + KeyEnt2*2, MoveWork.HIGHBYTE ' Get current entry position
         READ TrackPosT + KeyEnt2*2+1, MoveWork.LOWBYTE
         IF ClearPos = 1 THEN
            IF MoveWork.HIGHBYTE <> 0 THEN
               WRITE TrackPosT + KeyEnt2*2, 0    ' Clear tail-end position
            ENDIF
            IF MoveWork.LOWBYTE <> 0 THEN
               WRITE TrackPosT + KeyEnt2*2+1, 0
            ENDIF
         ELSE
            IF MoveWork.HIGHBYTE <> Position.HIGHBYTE THEN
               WRITE TrackPosT + KeyEnt2*2, Position.HIGHBYTE ' Tail-end position
            ENDIF
            IF MoveWork.LOWBYTE <> Position.LOWBYTE THEN
               WRITE TrackPosT + KeyEnt2*2+1, Position.LOWBYTE
            ENDIF
         ENDIF
      ENDIF
      Alignment = 0                              ' Set default alignment
      ClearPos = 0                               ' Reset position clear flag
   ELSE
      GOSUB SoundOut                             ' Sound warning tones
   ENDIF
   RETURN

'--------------------------------------------------------------------------
' This code is called to process move command keypad input (two keys: x# or
' x*) as defined in the operate mode description. All positioning terminates
' in a clockwise direction to account for gear backlash. The PosAdj constant
' provides for the amount of move depending on gear system used.

OperMove:
   IF KeyEnt1 < 10 AND KeyEnt2 > 9 THEN         ' Must have entered x# or x*
      IF KeyEnt2 = 11 THEN                      ' Head-end alignment?
         READ TrackPosH + KeyEnt1*2, MoveWork.HIGHBYTE ' Yes, Get head-end position
         READ TrackPosH + KeyEnt1*2+1, MoveWork.LOWBYTE
      ELSE
         READ TrackPosT + KeyEnt1*2, MoveWork.HIGHBYTE ' No, Get tail-end position
         READ TrackPosT + KeyEnt1*2+1, MoveWork.LOWBYTE
      ENDIF
      IF MoveWork = 0 THEN                      ' Position programmed?
         IF RandMvmt = 0 THEN                   ' Warning if not random movement
            GOSUB SoundOut2                     ' Sound warning tone
         ENDIF
         RETURN
      ENDIF
      IF HomeDone = 0 THEN                      ' Found reference position yet?
         GOSUB FindHome                         ' No, find it.
      ENDIF
      IF CircleWork = 0 THEN                    ' Zero value CircleWork?
         GOSUB SoundOut1                        ' Sound warning tone
         RETURN
      ENDIF
      IF MoveWork <> Position THEN              ' Not at new position?
         IF MoveWork > Position THEN            ' Compute steps to move
            MoveSteps = MoveWork - Position
            StepDir = Clockwise                 ' Move clockwise
         ELSE
            MoveSteps = Position - MoveWork
            StepDir = CounterClock              ' Move counter-clockwise
         ENDIF
         IF MoveSteps > (CircleWork / 2) THEN   ' Shorter in other direction?
            StepDir = ~StepDir                  ' Yes.
            MoveSteps = CircleWork - MoveSteps
         ENDIF
         GOSUB DoSteps                          ' Move the turntable
         IF StepDir = CounterClock THEN         ' Counter clockwise move?
            MoveSteps = PosAdj                  ' Yes, account for gear backlash
            GOSUB DoSteps                       ' Move the turntable
            MoveSteps = PosAdj                  ' Step to proper position
            StepDir = ~StepDir                  ' Reverse direction
            GOSUB DoSteps                       ' Move the turntable
         ENDIF
         Position = MoveWork                    ' Set new current position
      ENDIF
   ELSE
      GOSUB SoundOut                            ' Sound warning tones
   ENDIF
   RETURN

'--------------------------------------------------------------------------
' This code is called to position to the turntable to a random position. If
' the position has not been programmed, no movement occurs.

RandMove:
   RANDOM RandomNmbr                         ' Get a random number
   IF ProgramMode = 0 THEN                   ' Not in programming mode?
      KeyEnt1 = RandomNmbr DIG 1             ' Set track position
      KeyEnt2 = 10 + RandomNmbr.BIT0         ' Set bridge end
      RandMvmt = 1                           ' Set random movement flag
      GOSUB OperMove                         ' Process motion operation
      RandMvmt = 0                           ' Reset random movement flag
   ENDIF
   AutoMove = RandomMove                     ' Reset auto move time delay
   RETURN

'--------------------------------------------------------------------------
' This code is called to position to the turntable home position sensor. It
' is done in a counter-clockwise direction. Once the sensor is found, we step
' through it until the sensor again in-active. An additional move for gear
' backlash is then performed.  We then step clockwise until the sensor is
' again active. The reference position is the first step that the sensor goes
' active in the clockwise direction.

FindHome:
   IF HomeSensor = 1 THEN               ' Already at home position?
      MoveSteps = 200                   ' Set step size to clear sensor
      StepDir = Clockwise               ' Step clockwise
      GOSUB DoSteps                     ' Move the turntable
   ENDIF

   MoveSteps = 1                        ' Set step size
   StepDir = CounterClock               ' Step counter-clockwise
   DO
      GOSUB DoSteps                     ' Move the turntable
   LOOP UNTIL (HomeSensor = 1)          ' Step until sensor is active
   GOSUB DoSteps                        ' Make sure sensor is active

   DO
      GOSUB DoSteps                     ' Move the turntable
   LOOP UNTIL (HomeSensor = 0)          ' Step until sensor is inactive
   FOR StepRamp = PosAdj TO 0 STEP -1   ' Additional move for gear backlash
      GOSUB DoSteps                     ' Move the turntable
   NEXT

   StepDir = Clockwise                  ' Step clockwise
   DO
      GOSUB DoSteps                     ' Move the turntable slowly
      PAUSE 20
   LOOP UNTIL (HomeSensor = 1)          ' Step until sensor is active
   GOSUB DoSteps                        ' Make sure sensor is active
   Position = 0                         ' Set current turntable position
   HomeDone = 1                         ' Mark home performed bit
   RETURN

'--------------------------------------------------------------------------
' This code is called to determine the total number of steps in the circle.
' It assumes that the FindHome routine was called previously and that the
' turntable is currently in the home position. The calculated size is stored
' in NVRAM.

CalCircle:
   StepDir = Clockwise                  ' Step clockwise
   MoveSteps = 200                      ' Set step size to clear sensor
   GOSUB DoSteps                        ' Move the turntable
   MoveWork = 200

   MoveSteps = 1                        ' Set step size
   DO WHILE (HomeSensor = 0)
      GOSUB DoSteps                     ' Move the turntable
      MoveWork = MoveWork + 1
      IF MoveWork = $FFFF THEN          ' If overflow, circle too big
         GOSUB SoundOut2                ' Need less steps in circle
         RETURN
      ENDIF
   LOOP
   GOSUB DoSteps                        ' Make sure sensor is active
   MoveWork = MoveWork + 1

   READ CircleSize, CircleWork.HIGHBYTE ' Get the saved circle size
   READ CircleSize +1, CircleWork.LOWBYTE
   IF CircleWork <> MoveWork THEN
      WRITE CircleSize, MoveWork.HIGHBYTE ' Save new circle size
      WRITE CircleSize +1, MoveWork.LOWBYTE
   ENDIF
   CircleWork = MoveWork                ' Set new circle size
   Alignment = 0                        ' Set default alignment value
   ClearPos = 0                         ' Reset position clear flag
   RETURN

'--------------------------------------------------------------------------
' This code is called to position the turntable. MoveSteps contains the
' step count. StepDir must be set by the calling routine to the required
' rotation direction.
'
' The variables StepDelay, StepRamp, StepMin, and StepMax are used to
' effect the delay between each step pulse. Stepping begins using StepMax
' (slowest motor rotation) and gradually decrease to StepMin (fastest
' motor rotation). At the mid point of the MoveSteps count, the delay
' period will begin increasing toward the StepMax value. This technique
' serves to smoothly ramp up/down the motor speed.

DoSteps:
   IF MoveSteps = 1 THEN                 ' Special case 1 step code
      HIGH StepClock                     ' Pulse the step pin
      LOW StepClock
      PAUSE 5                            ' Don't step too fast
   ELSE
      StepRamp = 0                       ' Initialize speed ramp
      StepDelay = StepMax                ' Set slowest motor speed
      DO WHILE (MoveSteps > 0)
         HIGH StepClock                  ' Pulse the step pin
         LOW StepClock
         MoveSteps = MoveSteps - 1       ' Decrement MoveSteps value
         PAUSE StepDelay
         IF MoveSteps <= StepRamp THEN
            StepDelay = StepDelay + 1    ' Increase delay
         ELSEIF StepDelay > StepMin THEN
            StepDelay = StepDelay - 1    ' Decrease delay
            StepRamp = StepRamp + 1      ' Increment slowdown point
         ENDIF
         IF (MoveSteps // 10) = 0 THEN
            TOGGLE KeyEntry              ' Toggle first entry led
         ENDIF
      LOOP
      HIGH KeyEntry                      ' Turn off first entry led
   ENDIF
   RETURN

'--------------------------------------------------------------------------
' This code is called to sound the invalid keypad input warning tones.

SoundOut:
   FREQOUT SoundPin, 200, 1046           ' Sound note C
   PAUSE 100
SoundOut1:
   FREQOUT SoundPin, 200, 1318           ' Sound note E
   PAUSE 100
SoundOut2:
   FREQOUT SoundPin, 200, 1568           ' Sound note G
   RETURN

'--------------------------------------------------------------------------
' This code is called to change the position of the KeyEnt1 specified
' turnout.

TurnoutToggle:
   KeyEnt2 = 0                           ' Initialize select nothing
   IF KeyEnt1 = 1 THEN
      TT1State = ~TT1State               ' Remember new state
      IF TT1State = 0 THEN
         KeyEnt2 = TT1Open               ' Select TT1Open
      ELSE
         KeyEnt2 = TT1Close              ' Select TT1Close
      ENDIF
   ENDIF
   IF KeyEnt1 = 2 THEN
      TT2State = ~TT2State               ' Remember new state
      IF TT2State = 0 THEN
         KeyEnt2 = TT2Open               ' Select TT2Open
      ELSE
         KeyEnt2 = TT2Close              ' Select TT2Close
      ENDIF
   ENDIF
   DIRA = %1111                          ' Set control bits to output
   OUTA = KeyEnt2                        ' Set selected turnout
   HIGH TurnEnable                       ' Energize turnout coil
   PAUSE 250
   LOW TurnEnable                        ' De-energize turnout coil
   OUTA = 0                              ' Clear output bits
   DIRA = 0                              ' Reset I/O bits to input
   RETURN

'--------------------------------------------------------------------------
' This code is called when the mode switch is placed into the on (TestMode
' = 0) position.

TestLoop:
   MoveSteps = 1                            ' Set step size
   StepDir = Clockwise                      ' Step clockwise
   ClearPos = 0                             ' Clear flag
   StepDir = ~StepDir                       ' Change direction
   KeyEntry = StepDir                       ' Set data entry led
   FOR MoveWork = 1 TO 420
      GOSUB DoSteps                         ' Move the turntable
      IF HomeSensor = 1 THEN                ' Sensor active
         IF ClearPos = 0 THEN               ' Tone already output?
            FREQOUT SoundPin, 50, 1046      ' No, sound tone
            ClearPos = 1                    ' Set tone output flag
         ENDIF
      ENDIF
      IF KeyData = 1 THEN                   ' Keypad input available?
         IF KeyPressed = 0 THEN             ' New key closure?
            LOW KeyEnable                   ' Enable keypad data read
            LOOKUP INA, [1, 2, 3, 15, 4, 5, 6, 15, 7, 8, 9, 15, 10,
                         0, 11, 15], KeyEnt1
            HIGH KeyEnable                  ' Disable keypad data read
            FOR KeyEnt2 = 1 TO KeyEnt1
               FREQOUT SoundPin, 100, 784   ' Sound tone
               PAUSE 100
            NEXT
            KeyPressed = 1                  ' Set key pressed flag
         ENDIF
      ELSE
         KeyPressed = 0                     ' Reset key pressed flag
      ENDIF
   NEXT
   KeyEnt1 = 1
   GOSUB TurnoutToggle
   PAUSE 500
   KeyEnt1 = 2
   GOSUB TurnoutToggle
   PAUSE 500
   GOTO TestLoop
' ======================================================================
      

Color Bar

Navigation:   Turntable   D&B Home   Buczynski.com Index

Copyright © 2006 Don Buczynski
San Diego, California