EFX-TEK

TEK Talk => Prop-SX => Topic started by: robomaster-1 on November 28, 2008, 02:40:52 PM

Title: VMusic2 player SX Code
Post by: robomaster-1 on November 28, 2008, 02:40:52 PM
Jon,

I am in the process of doing a project using the VMusic2 player using a rotary encoder to select and set up the player settings.
Is there any Demo SX code done so I can get an Ideas on how to us it with am SX Chip?



Title: Re: VMusic2 player SX Code
Post by: JonnyMac on November 28, 2008, 03:00:41 PM
Here you go.  You can fold an encoder handler into the ISR (see the SX/B help file for an example).

Listing updated 09 JAN 2009

' =========================================================================
'
'   File...... VMUSIC2_38K4_ASC.SXB
'   Purpose... Test program for the VMusic2 MP3 player
'   Author.... Jon Williams, EFX-TEK
'              Copyright (c) 2008-2009 EFX-TEK
'              Some Rights Reserved
'              -- see http://creativecommons.org/licenses/by/3.0/
'   E-mail.... jwilliams@efx-tek.com
'   Started...
'   Updated... 09 JAN 2009
'
' =========================================================================


' -------------------------------------------------------------------------
' Program Description
' -------------------------------------------------------------------------

' This program uses 38.4K serial and the ASCII (long) command set.

' Playback of MP3s seems more responsive with ID3 tag removed
' -- for tag removal tool:
'      http://www.dalepreston.com/Blog/2007/01/removing-id3-tags.html


' -------------------------------------------------------------------------
' Conditional Compilation Symbols
' -------------------------------------------------------------------------


' -------------------------------------------------------------------------
' Device Settings
' -------------------------------------------------------------------------

ID              "VMUSIC"

DEVICE          SX28, OSCHS2, TURBO, STACKX, OPTIONX, BOR42
FREQ            50_000_000


' -------------------------------------------------------------------------
' I/O Pins
' -------------------------------------------------------------------------

RX              PIN     RC.7 INPUT              ' SETUP = UP, no ULN
TX              PIN     RC.6 OUTPUT             ' SETUP = UP, no ULN


' -------------------------------------------------------------------------
' Constants
' -------------------------------------------------------------------------

IsOn            CON     1
IsOff           CON     0

Yes             CON     1
No              CON     0


' Bit dividers for 6.51 uS interrupt

Baud2400        CON     64
Baud4800        CON     32
Baud9600        CON     16
Baud19K2        CON     8
Baud38K4        CON     4

Baud1x0         CON     Baud38K4                ' 1 bit period (ISR counts)
Baud1x5         CON     Baud1x0 * 3 / 2         ' 1.5 bit periods

CR              CON     $0D


' -------------------------------------------------------------------------
' Variables
' -------------------------------------------------------------------------

flags           VAR     Byte
isrFlag        VAR     flags.0                 ' isr has started
rxReady        VAR     flags.1                 ' rxBuf has byte(s)
isPaused       VAR     flags.7                 ' pause command was issued

level           VAR     Byte

tmpB1           VAR     Byte                    ' for subs/funcs
tmpB2           VAR     Byte
tmpB3           VAR     Byte
tmpB4           VAR     Byte
tmpW1           VAR     Word
tmpW2           VAR     Word

rxSerial        VAR     Byte (16)
rxBuf          VAR     rxSerial(0)             ' 8-byte buffer
rxCount        VAR     rxSerial(8)             ' rx bit count
rxDivide       VAR     rxSerial(9)             ' bit divisor timer
rxByte         VAR     rxSerial(10)            ' recevied byte
rxHead         VAR     rxSerial(11)            ' buffer head (write to)
rxTail         VAR     rxSerial(12)            ' buffer tail (read from)
rxBufCnt       VAR     rxSerial(13)            ' # bytes in buffer

txSerial        VAR     Byte (16)               ' tx serial data
txBuf          VAR     txSerial(0)             ' eight-byte buffer
txCount        VAR     txSerial(8)             ' tx bit count
txDivide       VAR     txSerial(9)             ' bit divisor timer
txLo           VAR     txSerial(10)            ' holds start bit
txHi           VAR     txSerial(11)            ' tx output reg
txHead         VAR     txSerial(12)            ' buffer head (write to)
txTail         VAR     txSerial(13)            ' buffer tail (read from)
txBufCnt       VAR     txSerial(14)            ' # bytes in buffer


' =========================================================================
  INTERRUPT NOCODE 153_600                      ' (3)   6.51 uSecs
' =========================================================================

Mark_ISR:
  \ SETB  isrFlag                               ' (1)


' -------
' RX UART
' -------

Receive:
  ASM
    BANK  rxSerial                              ' (1)
    JB    rxBufCnt.3, RX_Done                   ' (2/4) skip if buffer is full
    MOVB  C, RX                                 ' (4)   sample serial input
    TEST  rxCount                               ' (1)   receiving now?
    JNZ   RX_Bit                                ' (2/4) yes, get next bit
    MOV   W, #9                                 ' (1)   no, prep for next byte
    SC                                          ' (1/2)
     MOV   rxCount, W                           ' (1)   if start, load  bit count
    MOV   rxDivide, #Baud1x5                    ' (2)   prep for 1.5 bit periods

RX_Bit:
    DJNZ  rxDivide, RX_Done                     ' (2/4) complete bit cycle?
    MOV   rxDivide, #Baud1x0                    ' (2)   yes, reload bit timer
    DEC   rxCount                               ' (1)   update bit count
    SZ                                          ' (1/2)
     RR   rxByte                                ' (1)   position for next bit
    SZ                                          ' (1/2)
    JMP   RX_Done                               ' (3)

RX_Buffer:
    MOV   W, #rxBuf                             ' (1)   point to buffer head
    ADD   W, rxHead                             ' (1)
    MOV   FSR, W                                ' (1)
    MOV   IND, rxByte                           ' (2)   move rxByte to head
    INC   rxHead                                ' (1)   update head
    CLRB  rxHead.3                              ' (1)   keep 0..7
    INC   rxBufCnt                              ' (1)   update buffer count
    BANK  flags                                 ' (1)
    SETB  rxReady                               ' (1)   set ready flag

RX_Done:
    'BANK  $00                                   ' (1)
  ENDASM


' -------
' TX UART
' -------
'
Transmit:
  ASM
    BANK  txSerial                              ' (1)
    TEST  txCount                               ' (1)   transmitting now?
    JZ    TX_Buffer                             ' (2/4) if txCount = 0, no
    DEC   txDivide                              ' (1)   update bit timer
    JNZ   TX_Done                               ' (2/4) time for new bit?
    MOV   txDivide, #Baud1x0                    ' (2)   yes, reload timer
    STC                                         ' (1)   set for stop bit
    RR    txHi                                  ' (1)   rotate TX buf
    RR    txLo                                  ' (1)
    DEC   txCount                               ' (1)   update the bit count
    MOVB  TX, txLo.6                            ' (4)   output the bit
    JMP   TX_Done                               ' (3)

TX_Buffer:
    TEST  txBufCnt                              ' (1)   anything in buffer?
    JZ    TX_Done                               ' (2/4) exit if empty
    MOV   W, #txBuf                             ' (2)   point to buffer tail
    ADD   W, txTail                             ' (1)
    MOV   FSR, W                                ' (1)
    MOV   txHi, IND                             ' (2)   move byte to TX reg
    CLR   txLo                                  ' (1)   clear for start bit
    MOV   txCount, #10                          ' (2)   start + 8 + 1 stop
    INC   txTail                                ' (1)   update tail pointer
    CLRB  txTail.3                              ' (1)   keep 0..7
    DEC   txBufCnt                              ' (1)   update buffer count

TX_Done:
    BANK  $00                                   ' (1)
  ENDASM


  RETURNINT                                     ' (3)


' =========================================================================
' Subroutine / Function Declarations
' =========================================================================

DELAY_MS        SUB     1, 2                    ' shell for PAUSE

RX_BYTE         FUNC    1, 0, 1                 ' shell for SERIN
TX_BYTE         SUB     1                       ' shell for SEROUT
TX_STR          SUB     2                       ' transmit a string
TX_HEX2         SUB     1                       ' transmit in HEX2 format

VM_PLAY         SUB     2                       ' play MP3 file
VM_REPEAT       SUB     2                       ' repeat MP3 file
VM_STOP         SUB     0
VM_PAUSE        SUB     0
VM_RESUME       SUB     0
VM_VOLUME       SUB     1                       ' overall volume
VM_PAN          SUB     2                       ' set left and right levels
VM_WAIT_PROMPT  SUB     0                       ' waits for ">" prompt
VM_WAIT_START   SUB     0                       ' wait for song start


' =========================================================================
  PROGRAM Start
' =========================================================================

Start:
  PLP_A = %0000                                 ' pull-up unused pins

  TX = 1                                        ' set to idle
  DELAY_MS 3_000                                ' let VMUSIC power up
  TX_BYTE CR                                    ' ping (if no power-up)
  VM_WAIT_PROMPT
  VM_STOP                                       ' stop if playing
  VM_WAIT_PROMPT
  VM_VOLUME $00                                 ' reset
  VM_WAIT_PROMPT


Main:
  VM_PLAY "serenity"
  VM_WAIT_START
  DELAY_MS 5_000

  VM_VOLUME 40
  VM_WAIT_PROMPT

  DELAY_MS 1_000
  VM_WAIT_PROMPT

  VM_VOLUME $00
  VM_WAIT_PROMPT

  VM_PLAY "spalding"
  VM_WAIT_START

  VM_PAN $00, $FE
  DELAY_MS 3_500

  VM_PAN $FE, $00

  END


' -------------------------------------------------------------------------
' Subroutine / Function Code
' -------------------------------------------------------------------------

' Use: DELAY_MS duration
' -- replaces PAUSE
' -- assumes 6.51 uS interrupt rate

SUB DELAY_MS
  mSecs         VAR     __WPARAM12
  msTix         VAR     __PARAM3

  \ SB   __PARAMCNT.1                           ' skip if word passed
  \ CLR  mSecs_MSB                              ' clear MSB if byte passed

  DO WHILE mSecs > 0
    msTix = 153 + mSecs.0                       ' 153 or 154 (153.5 avg)
    DO WHILE msTix > 0
      \ CLRB isrFlag
      \ JNB  isrFlag, $
      \ DEC  msTix
    LOOP
    DEC mSecs
  LOOP
  ENDSUB

' -------------------------------------------------------------------------

' Use: aByte = RX_BYTE
' -- returns "aByte" from 8-byte circular buffer
' -- will wait if buffer is presently empty
' -- rxBufCnt holds byte count of receive buffer (0 to 8)

FUNC RX_BYTE
  ASM
    JNB   rxReady, $                            ' wait if nothing in buffer
    BANK  rxSerial
    MOV   W, #rxBuf                             ' point to tail
    ADD   W, rxTail
    MOV   FSR, W
    MOV   __PARAM1, IND                         ' get byte at tail
    INC   rxTail                                ' update tail
    CLRB  rxTail.3                              ' keep 0..7
    DEC   rxBufCnt                              ' update buffer count
    TEST  rxBufCnt                              ' check the count
    JNZ    @$+5                                 ' exit if not zero
    BANK  flags
    CLRB  rxReady                               ' else clear ready flag
    BANK  $00
  ENDASM
  ENDFUNC

' -------------------------------------------------------------------------

' Use: TX_BYTE aByte
' -- moves "aByte" to 8-byte circular buffer (when space is available)
' -- will wait if buffer is presently full
' -- txBufCnt holds byte count of transmit buffer (0 to 8)

SUB TX_BYTE
  ASM
    BANK  txSerial                              ' point to tx vars
    JB    txBufCnt.3, $                         ' prevent buffer overrun
    MOV   W, #txBuf                             ' point to buffer head
    ADD   W, txHead
    MOV   FSR, W
    MOV   IND, __PARAM1                         ' move byte to tx buf
    INC   txHead                                ' update head pointer
    CLRB  txHead.3                              ' keep 0..7
    INC   txBufCnt                              ' update buffer count
    BANK  $00
  ENDASM
  ENDSUB

' -------------------------------------------------------------------------

' Use: TX_STR [String | Label]
' -- pass embedded string or DATA label

SUB TX_STR
  strAddr       VAR     tmpW1
  sChar         VAR     __PARAM1

  strAddr = __WPARAM12                          ' get address of string

  DO
    READINC strAddr, sChar                      ' read a character
    IF sChar = 0 THEN EXIT                      ' if 0, string complete
    TX_BYTE sChar                               ' send the byte
  LOOP
  ENDSUB

' -------------------------------------------------------------------------

' Use: TX_HEX2 byteVal
' -- transmit byte in HEX2 format

SUB TX_HEX2
  tmpB1 = __PARAM1

  tmpB2 = tmpB1 & $F0                           ' isolate high nib
  SWAP tmpB2                                    ' move for READ
  READ Hex_Digits + tmpB2, tmpB2                ' convert to ASCII
  TX_BYTE tmpB2
  tmpB1 = tmpB1 & $0F                           ' isolate high nib
  READ Hex_Digits + tmpB1, tmpB1
  TX_BYTE tmpB1
  ENDSUB

' -------------------------------------------------------------------------

' Use: VM_PLAY [String | Label]
' -- issues single play command to VMUSIC player
' -- name should be less than eight characters -- assumes MP3 extension

SUB VM_PLAY
  tmpW2 = __WPARAM12

  TX_STR  "VPF "
  TX_STR  tmpW2
  TX_STR  ".MP3"
  TX_BYTE CR
  isPaused = No                                 ' clear paused flag
  ENDSUB

' -------------------------------------------------------------------------

' Use: VM_REPEAT [String | Label]
' -- issues repeat play command to VMUSIC player
' -- name should be less than eight characters -- assumes MP3 extension

SUB VM_REPEAT
  tmpW2 = __WPARAM12

  TX_STR  "VRF "
  TX_STR  tmpW2
  TX_STR  ".MP3"
  TX_BYTE CR
  isPaused = No                                 ' clear paused flag
  ENDSUB

' -------------------------------------------------------------------------

' Use: VST
' -- stops playback of VMUSIC player

SUB VM_STOP
  TX_STR  "VST"
  TX_BYTE CR
  isPaused = No                                 ' clear paused flag
  ENDSUB

' -------------------------------------------------------------------------

' Use: VM_PAUSE
' -- pauses VMUSIC player
' -- using VP allows paused file to be overridden

SUB VM_PAUSE
  IF isPaused = No THEN
    TX_STR  "VP"
    TX_BYTE CR
    isPaused = Yes                              ' toggle paused bit
  ENDIF
  ENDSUB

' -------------------------------------------------------------------------

' Use: VM_RESUME
' -- resumes VMUSIC player

SUB VM_RESUME
  IF isPaused = Yes THEN
    TX_STR  "VP"
    TX_BYTE CR
    isPaused = No
  ENDIF
  ENDSUB

' -------------------------------------------------------------------------

' Use: VM_VOLUME level
' -- sets overall volume of VMUSIC player

SUB VM_VOLUME
  tmpB3 = __PARAM1                              ' capture volume

  tmpB3 = tmpB3 MAX $FE

  TX_STR "VSV $"
  TX_HEX2 tmpB3
  TX_BYTE CR
  ENDSUB

' -------------------------------------------------------------------------

' Use: VM_PAN left, right
' -- sets left and right channels independently

SUB VM_PAN
  tmpB3 = __PARAM1                              ' capture levels
  tmpB4 = __PARAM2

  tmpB3 = tmpB3 MAX $FE
  tmpB4 = tmpB4 MAX $FE

  TX_STR "VWR $0B"                              ' write to VS1003 reg $0B
  TX_HEX2 tmpB4
  TX_HEX2 tmpB3
  TX_BYTE CR
  ENDSUB

' -------------------------------------------------------------------------

' Use: VM_WAIT_PROMPT
' -- waits for caret character at end of command prompt

SUB VM_WAIT_PROMPT
  DO
    tmpB1 = RX_BYTE
  LOOP UNTIL tmpB1 = ">"
  ENDSUB

' -------------------------------------------------------------------------

' Use: VM_WAIT_START
' -- waits for start of MP3 position data: "T $"

SUB VM_WAIT_START
  tmpB1 = RX_BYTE
  IF tmpB1 <> "T" THEN VM_WAIT_START
  tmpB1 = RX_BYTE
  IF tmpB1 <> " " THEN VM_WAIT_START
  tmpB1 = RX_BYTE
  IF tmpB1 <> "$" THEN VM_WAIT_START
  ENDSUB


' =========================================================================
' User Data
' =========================================================================

Hex_Digits:
  DATA  "0123456789ABCDEF"
Title: Re: VMusic2 player SX Code
Post by: randyaz on November 28, 2008, 09:14:36 PM
AAGGGHHHH!!!!!  assembly !!!  (kidding)

What encoder are you using?
Title: Re: VMusic2 player SX Code
Post by: Digital Steve on January 23, 2009, 12:42:50 PM
Having trouble addressing another input onto port 'C'.  I change the PLP_C = %1110_000
for RC.5

i show no change the simulator when actuating this input.  I just want to have one input trigger a message from my usb any tips???
Title: Re: VMusic2 player SX Code
Post by: JonnyMac on January 23, 2009, 01:37:56 PM
Here's an updated VMUSIC program (with a couple additional tweaks) that includes the background button debouncing.  You can look at the bits in btnFlags to see if an input on RC.0 - RC.5 is active.

' =========================================================================
'
'   File...... VMUSIC2_38K4_ASC-v2.SXB
'   Purpose... Test program for the VMusic2 MP3 player
'   Author.... Jon Williams, EFX-TEK
'              Copyright (c) 2008-2009 EFX-TEK
'              Some Rights Reserved
'              -- see http://creativecommons.org/licenses/by/3.0/
'   E-mail.... jwilliams@efx-tek.com
'   Started...
'   Updated... 23 JAN 2009
'
' =========================================================================


' -------------------------------------------------------------------------
' Program Description
' -------------------------------------------------------------------------

' This program uses 38.4K serial and the ASCII (long) command set.

' Playback of MP3s seems more responsive with ID3 tag removed
' -- for tag removal tool:
'      http://www.dalepreston.com/Blog/2007/01/removing-id3-tags.html
'
' Added background button debouncing (23 JAN 09)


' -------------------------------------------------------------------------
' Conditional Compilation Symbols
' -------------------------------------------------------------------------


' -------------------------------------------------------------------------
' Device Settings
' -------------------------------------------------------------------------

ID              "VMUSIC"

DEVICE          SX28, OSCHS2, TURBO, STACKX, OPTIONX, BOR42
FREQ            50_000_000


' -------------------------------------------------------------------------
' I/O Pins
' -------------------------------------------------------------------------

RX              PIN     RC.7 INPUT              ' (P15) SETUP = UP, no ULN
TX              PIN     RC.6 OUTPUT             ' (P14) SETUP = UP, no ULN

Btn6            PIN     RC.5 INPUT              ' (P13) SETUP = DN or OUT
Btn5            PIN     RC.4 INPUT              ' (P12) SETUP = DN or OUT
Btn4            PIN     RC.3 INPUT              ' (P11)
Btn3            PIN     RC.2 INPUT              ' (P10)
Btn2            PIN     RC.1 INPUT              ' (P9)
Btn1            PIN     RC.0 INPUT              ' (P8)


' -------------------------------------------------------------------------
' Constants
' -------------------------------------------------------------------------

IsOn            CON     1
IsOff           CON     0

Yes             CON     1
No              CON     0


' Bit dividers for 6.51 uS interrupt

Baud2400        CON     64
Baud4800        CON     32
Baud9600        CON     16
Baud19K2        CON     8
Baud38K4        CON     4

Baud1x0         CON     Baud38K4                ' 1 bit period (ISR counts)
Baud1x5         CON     Baud1x0 * 3 / 2         ' 1.5 bit periods

CR              CON     $0D


' -------------------------------------------------------------------------
' Variables
' -------------------------------------------------------------------------

flags           VAR     Byte
isrFlag        VAR     flags.0                 ' isr has started
rxReady        VAR     flags.1                 ' rxBuf has byte(s)
isPaused       VAR     flags.7                 ' pause command was issued

btnFlags        VAR     Byte                    ' 1 = debounce button


level           VAR     Byte

tmpB1           VAR     Byte                    ' for subs/funcs
tmpB2           VAR     Byte
tmpB3           VAR     Byte
tmpB4           VAR     Byte
tmpW1           VAR     Word
tmpW2           VAR     Word

rxSerial        VAR     Byte (16)
rxBuf          VAR     rxSerial(0)             ' 8-byte buffer
rxCount        VAR     rxSerial(8)             ' rx bit count
rxDivide       VAR     rxSerial(9)             ' bit divisor timer
rxByte         VAR     rxSerial(10)            ' recevied byte
rxHead         VAR     rxSerial(11)            ' buffer head (write to)
rxTail         VAR     rxSerial(12)            ' buffer tail (read from)
rxBufCnt       VAR     rxSerial(13)            ' # bytes in buffer

txSerial        VAR     Byte (16)               ' tx serial data
txBuf          VAR     txSerial(0)             ' eight-byte buffer
txCount        VAR     txSerial(8)             ' tx bit count
txDivide       VAR     txSerial(9)             ' bit divisor timer
txLo           VAR     txSerial(10)            ' holds start bit
txHi           VAR     txSerial(11)            ' tx output reg
txHead         VAR     txSerial(12)            ' buffer head (write to)
txTail         VAR     txSerial(13)            ' buffer tail (read from)
txBufCnt       VAR     txSerial(14)            ' # bytes in buffer

btnWork         VAR     Byte (4)                ' for button debounce
tmr1ms_LSB     VAR     btnWork(0)              ' 1ms timer
tmr1ms_MSB     VAR     btnWork(1)
tmrScan        VAR     btnWork(2)              ' debounce window timer
btnTemp        VAR     btnWork(3)              ' work var for debounce


' =========================================================================
 INTERRUPT NOCODE 153_600                      ' (3)   6.51 uSecs
' =========================================================================

Mark_ISR:
 \ SETB  isrFlag                               ' (1)


' -------
' RX UART
' -------

Receive:
 ASM
   BANK  rxSerial                              ' (1)
   JB    rxBufCnt.3, RX_Done                   ' (2/4) skip if buffer is full
   MOVB  C, RX                                 ' (4)   sample serial input
   TEST  rxCount                               ' (1)   receiving now?
   JNZ   RX_Bit                                ' (2/4) yes, get next bit
   MOV   W, #9                                 ' (1)   no, prep for next byte
   SC                                          ' (1/2)
    MOV   rxCount, W                           ' (1)   if start, load  bit count
   MOV   rxDivide, #Baud1x5                    ' (2)   prep for 1.5 bit periods

RX_Bit:
   DJNZ  rxDivide, RX_Done                     ' (2/4) complete bit cycle?
   MOV   rxDivide, #Baud1x0                    ' (2)   yes, reload bit timer
   DEC   rxCount                               ' (1)   update bit count
   SZ                                          ' (1/2)
    RR   rxByte                                ' (1)   position for next bit
   SZ                                          ' (1/2)
   JMP   RX_Done                               ' (3)

RX_Buffer:
   MOV   W, #rxBuf                             ' (1)   point to buffer head
   ADD   W, rxHead                             ' (1)
   MOV   FSR, W                                ' (1)
   MOV   IND, rxByte                           ' (2)   move rxByte to head
   INC   rxHead                                ' (1)   update head
   CLRB  rxHead.3                              ' (1)   keep 0..7
   INC   rxBufCnt                              ' (1)   update buffer count
   BANK  flags                                 ' (1)
   SETB  rxReady                               ' (1)   set ready flag

RX_Done:
 ENDASM


' -------
' TX UART
' -------
'
Transmit:
 ASM
   BANK  txSerial                              ' (1)
   TEST  txCount                               ' (1)   transmitting now?
   JZ    TX_Buffer                             ' (2/4) if txCount = 0, no
   DEC   txDivide                              ' (1)   update bit timer
   JNZ   TX_Done                               ' (2/4) time for new bit?
   MOV   txDivide, #Baud1x0                    ' (2)   yes, reload timer
   STC                                         ' (1)   set for stop bit
   RR    txHi                                  ' (1)   rotate TX buf
   RR    txLo                                  ' (1)
   DEC   txCount                               ' (1)   update the bit count
   MOVB  TX, txLo.6                            ' (4)   output the bit
   JMP   TX_Done                               ' (3)

TX_Buffer:
   TEST  txBufCnt                              ' (1)   anything in buffer?
   JZ    TX_Done                               ' (2/4) exit if empty
   MOV   W, #txBuf                             ' (2)   point to buffer tail
   ADD   W, txTail                             ' (1)
   MOV   FSR, W                                ' (1)
   MOV   txHi, IND                             ' (2)   move byte to TX reg
   CLR   txLo                                  ' (1)   clear for start bit
   MOV   txCount, #10                          ' (2)   start + 8 + 1 stop
   INC   txTail                                ' (1)   update tail pointer
   CLRB  txTail.3                              ' (1)   keep 0..7
   DEC   txBufCnt                              ' (1)   update buffer count

TX_Done:
 ENDASM


' -----------------
' Button debouncing
' -----------------
'
Debounce:
 ASM
   BANK  btnWork                               ' (1)
   INC   tmr1ms_LSB                            ' (1)
   ADDB  tmr1ms_MSB, Z                         ' (2)
   CJNE  tmr1ms_LSB, #$9A, DB_Exit             ' (4/6) at 1ms? (154)
   CJNE  tmr1ms_MSB, #$00, DB_Exit             ' (4/6)
   CLR   tmr1ms_LSB                            ' (1)   yes, restart timer
   CLR   tmr1ms_MSB                            ' (1)
   INC   tmrScan                               ' (1)   update scan timer

DB_Check:
   CJB   tmrScan, #50, DB_Port_Scan            ' (2/4) keep scanning for 50ms
   CLR   tmrScan                               ' (1)   restart scan timer
   MOV   btnFlags, btnTemp                     ' (2)   update program flags
   MOV   btnTemp, #%0011_1111                  ' (2)   reset for next scan
   JMP   DB_Exit

DB_Port_Scan:
   AND   btnTemp, RC                           ' (2)   clear any released buttons

DB_Exit:
 ENDASM


 RETURNINT                                     ' (3)


' =========================================================================
' Subroutine / Function Declarations
' =========================================================================

DELAY_MS        SUB     1, 2                    ' shell for PAUSE

RX_BYTE         FUNC    1, 0, 1                 ' shell for SERIN
TX_BYTE         SUB     1                       ' shell for SEROUT
TX_STR          SUB     2                       ' transmit a string
TX_HEX2         SUB     1                       ' transmit in HEX2 format

VM_PLAY         SUB     2                       ' play MP3 file
VM_REPEAT       SUB     2                       ' repeat MP3 file
VM_STOP         SUB     0
VM_PAUSE        SUB     0
VM_RESUME       SUB     0
VM_VOLUME       SUB     1                       ' overall volume
VM_PAN          SUB     2                       ' set left and right levels
VM_WAIT_PROMPT  SUB     0                       ' waits for ">" prompt
VM_WAIT_START   SUB     0                       ' wait for song start


' =========================================================================
 PROGRAM Start
' =========================================================================

Start:
 PLP_A = %0000                                 ' pull-up unused pins

 TX = 1                                        ' set to idle
 DELAY_MS 3_000                                ' let VMUSIC power up
 TX_BYTE CR                                    ' ping (if no power-up)
 VM_WAIT_PROMPT
 VM_STOP                                       ' stop if playing
 VM_WAIT_PROMPT
 VM_VOLUME $00                                 ' reset
 VM_WAIT_PROMPT


Main:
  IF btnFlags.0 = Yes THEN
    VM_PLAY "serenity"
    VM_WAIT_START
    VM_WAIT_PROMPT
  ENDIF

  GOTO Main


' -------------------------------------------------------------------------
' Subroutine / Function Code
' -------------------------------------------------------------------------

' Use: DELAY_MS duration
' -- replaces PAUSE
' -- assumes 6.51 uS interrupt rate

SUB DELAY_MS
 mSecs         VAR     __WPARAM12
 msTix         VAR     __PARAM3

 \ SB   __PARAMCNT.1                           ' skip if word passed
 \ CLR  mSecs_MSB                              ' clear MSB if byte passed

 DO WHILE mSecs > 0
   msTix = 153 + mSecs.0                       ' 153 or 154 (153.5 avg)
   DO WHILE msTix > 0
     \ CLRB isrFlag
     \ JNB  isrFlag, $
     \ DEC  msTix
   LOOP
   DEC mSecs
 LOOP
 ENDSUB

' -------------------------------------------------------------------------

' Use: aByte = RX_BYTE
' -- returns "aByte" from 8-byte ring buffer
' -- will wait if buffer is presently empty
' -- rxBufCnt holds byte count of receive buffer (0 to 8)

FUNC RX_BYTE
 ASM
   JNB   rxReady, $                            ' wait if buffer empty
   BANK  rxSerial
   MOV   W, #rxBuf                             ' point to tail
   ADD   W, rxTail
   MOV   FSR, W
   MOV   __PARAM1, IND                         ' get byte at tail
   INC   rxTail                                ' update tail
   CLRB  rxTail.3                              ' keep 0..7
   DEC   rxBufCnt                              ' update buffer count
   SNZ                                         ' exit if not zero
    CLRB rxReady                               ' else clear ready flag
   BANK  $00
 ENDASM
 ENDFUNC

' -------------------------------------------------------------------------

' Use: TX_BYTE aByte
' -- moves "aByte" to 8-byte ring buffer (when space is available)
' -- will wait if buffer is presently full
' -- txBufCnt holds byte count of transmit buffer (0 to 8)

SUB TX_BYTE
 ASM
   BANK  txSerial                              ' point to tx vars
   JB    txBufCnt.3, $                         ' prevent buffer overrun
   MOV   W, #txBuf                             ' point to buffer head
   ADD   W, txHead
   MOV   FSR, W
   MOV   IND, __PARAM1                         ' move byte to tx buf
   INC   txHead                                ' update head pointer
   CLRB  txHead.3                              ' keep 0..7
   INC   txBufCnt                              ' update buffer count
   BANK  $00
 ENDASM
 ENDSUB

' -------------------------------------------------------------------------

' Use: TX_STR [String | Label]
' -- pass embedded string or DATA label

SUB TX_STR
 sAddr         VAR     tmpW1
 sChar         VAR     __PARAM1

 sAddr = __WPARAM12                            ' get address of string

 DO
   READINC sAddr, sChar                        ' read a character
   IF sChar = 0 THEN EXIT                      ' if 0, string complete
   TX_BYTE sChar                               ' send the byte
 LOOP
 ENDSUB

' -------------------------------------------------------------------------

' Use: TX_HEX2 byteVal
' -- transmit byte in HEX2 format

SUB TX_HEX2
 hxOut         VAR     tmpB1
 hxNib         VAR     tmpB2

 hxOut = __PARAM1

 hxNib = hxOut & $F0                           ' isolate high nib
 SWAP hxNib                                    ' move for READ
 READ Hex_Digits + hxNib, hxNib                ' convert to ASCII
 TX_BYTE hxNib
 hxNib = hxOut & $0F                           ' isolate low nib
 READ Hex_Digits + hxNib, hxNib                ' convert to ASCII
 TX_BYTE hxNib
 ENDSUB

' -------------------------------------------------------------------------

' Use: VM_PLAY [String | Label]
' -- issues single play command to VMUSIC player
' -- name should be less than eight characters -- assumes MP3 extension

SUB VM_PLAY
 vpfAddr       VAR     tmpW2                   ' address of string

 vpfAddr = __WPARAM12

 TX_STR  "VPF "
 TX_STR  vpfAddr
 TX_STR  ".MP3"
 TX_BYTE CR
 isPaused = No                                 ' clear paused flag
 ENDSUB

' -------------------------------------------------------------------------

' Use: VM_REPEAT [String | Label]
' -- issues repeat play command to VMUSIC player
' -- name should be less than eight characters -- assumes MP3 extension

SUB VM_REPEAT
 vrfAddr       VAR     tmpW2                   ' address of string

 vrfAddr = __WPARAM12

 TX_STR  "VRF "
 TX_STR  vrfAddr
 TX_STR  ".MP3"
 TX_BYTE CR
 isPaused = No                                 ' clear paused flag
 ENDSUB

' -------------------------------------------------------------------------

' Use: VST
' -- stops playback of VMUSIC player

SUB VM_STOP
 TX_STR  "VST"
 TX_BYTE CR
 isPaused = No                                 ' clear paused flag
 ENDSUB

' -------------------------------------------------------------------------

' Use: VM_PAUSE
' -- pauses VMUSIC player
' -- using VP allows paused file to be overridden

SUB VM_PAUSE
 IF isPaused = No THEN
   TX_STR  "VP"
   TX_BYTE CR
   isPaused = Yes                              ' toggle paused bit
 ENDIF
 ENDSUB

' -------------------------------------------------------------------------

' Use: VM_RESUME
' -- resumes VMUSIC player

SUB VM_RESUME
 IF isPaused = Yes THEN
   TX_STR  "VP"
   TX_BYTE CR
   isPaused = No
 ENDIF
 ENDSUB

' -------------------------------------------------------------------------

' Use: VM_VOLUME level
' -- sets overall volume of VMUSIC player

SUB VM_VOLUME
 attLevel      VAR     tmpB3                   ' attenuation level

 attLevel = __PARAM1                           ' capture attenuation
 attLevel = attLevel MAX $FE                   ' limit

 TX_STR "VSV $"
 TX_HEX2 attLevel
 TX_BYTE CR
 ENDSUB

' -------------------------------------------------------------------------

' Use: VM_PAN left, right
' -- sets left and right channels independently

SUB VM_PAN
 attLf         VAR     tmpB3
 attRt         VAR     tmpB4

 attLf = __PARAM1
 attRt = __PARAM2

 attLf = attLf MAX $FE
 attRt = attRt MAX $FE

 TX_STR "VWR $0B"                              ' write to VS1003 reg $0B
 TX_HEX2 attRt
 TX_HEX2 attLf
 TX_BYTE CR
 ENDSUB

' -------------------------------------------------------------------------

' Use: VM_WAIT_PROMPT
' -- waits for caret character at end of command prompt

SUB VM_WAIT_PROMPT
 target        VAR     tmpB1

 DO
   target = RX_BYTE
 LOOP UNTIL target = ">"
 ENDSUB

' -------------------------------------------------------------------------

' Use: VM_WAIT_START
' -- waits for start of MP3 position data: "T $"

SUB VM_WAIT_START
 wChar         VAR     tmpB1

 wChar = RX_BYTE
 IF wChar <> "T" THEN VM_WAIT_START
 wChar = RX_BYTE
 IF wChar <> " " THEN VM_WAIT_START
 wChar = RX_BYTE
 IF wChar <> "$" THEN VM_WAIT_START
 ENDSUB


' =========================================================================
' User Data
' =========================================================================

Hex_Digits:
 DATA  "0123456789ABCDEF"




Title: Re: VMusic2 player SX Code
Post by: Digital Steve on January 23, 2009, 02:38:33 PM
I get no response, when i toggle a PB set on RC.5.  I do not see any chage to the register when the input is toggled as well.  When i toggle any inputs in the simulator the mp3 will not play.  Yet the program works well otherwise, and the outputs can be turned on easily.  Any ideas
Title: Re: VMusic2 player SX Code
Post by: JonnyMac on January 23, 2009, 04:24:44 PM
It works fine here -- just double-checked by copying the program above into the SX-Key editor and downloading it into the Prop-SX.  Make sure that you still have the ULN pins on RC.0-RC.5 to act as pull-downs for the button inputs.

Do you have Prop-1 Trainer?  If yes, plug it in to P0-P7 and run this code (I'm just showing the stuff at Main).  It will toggle the LEDs on the P1-T based on the button inputs on RC.0-RC.5.

Main:
  RB = %0000_0000
  TRIS_B = %1100_0000                           ' RB.0 - RB.5 are outputs

  DO
    RB = RB ^ btnFlags                          ' toggle active inputs
    DELAY_MS 250                                ' allow button release
  LOOP

  GOTO Main
Title: Re: VMusic2 player SX Code
Post by: Digital Steve on January 28, 2009, 08:20:16 PM
Ok got everything working, had to save modified file as a new file and reload, something was getting confused. Vmusic2 was going into sleep mode, reflashed with factory bootloader and the loaded FTD file with new parameters. So far so go I have 4 i/ps triggering 4 messages in any order.

Thanks for all the help.