Shop OBEX P1 Docs P2 Docs Learn Events
SX52 DS1302 LCD now on a 16x16 LED matrix - combination question? — Parallax Forums

SX52 DS1302 LCD now on a 16x16 LED matrix - combination question?

T&E EngineerT&E Engineer Posts: 1,396
edited 2007-04-08 18:05 in General Discussion
As many of you know from my past posts, I have been trying to work on a way to combine a working DS1302 program on an SX28 to an LCD - to - a working 16x16 LED matrix scrolling program on an SX52. The 16x16 LED matrix can scroll messages that are in a DATA statement either on the top 8 rows or bottom 8 rows of the matrix and it works well thanks to great help from JonnyMac. I thought before that I did not have enough RAM in the SX52 to run both programs on the SX52. However, I was able to remove some other scrolling test routines and now seem to have enough RAM with no problems.

I have been struggling with this for many nights now and feel I am very close now that I do not have to use RX and TX commands from one SX28 DS1032 circuit to another SX52 16x16 LED matrix circuit. Everything is being controlled now by 1 SX52 chip.

What I need help with is for someone to look over the combined program and tell me how I can take the DS1302 LCD writing subroutine statements and make it work in the LED matrix scrolling routine that normally looks for its bytes to come in the form of a DATA statement and not as an LCD·writing routine.

However, I do have to comment out the LED matrix INTERRUPT routine command if I connect the SX52 to an LCD. Otherwise odd timing characters show up an the LCD display.

The program currently has the Interrupt calling commented out and the 16x16 LED scrolling message calling commented out so that you can connect an LCD.

Since this circuit and program uses RA0-3, RB, RC, RD and RE, this could also be built on an SX48 (with all available I/O pins being used up). On the SX52 I still have RA4-7 available for future usage like programing buttons or something - but that's later.

I have attached the combination program. If someone can look at this and give me some ideas on how to take the LCD subroutines and insert them into scrolling message subroutine (that is looking for it's Byte message in a DATA statement).

Thanks to everyone for helping me on this big project. It has certainly been a huge learning experience for me!

Comments / Assistance...

Comments

  • Capt. QuirkCapt. Quirk Posts: 872
    edited 2007-04-06 05:42
    How exactly do you want your LCD to be formatted? Could you post a representation of it including underscores for the spaces between the statements and data to be displayed? and which LCD do you have?
  • T&E EngineerT&E Engineer Posts: 1,396
    edited 2007-04-06 09:36
    The LCD part of the program is currently set up and working in this program. However, if you are refering to the LED matrix, then any format that can take a similar display to the LCD format (scrolling would be nice - as the LED matrix is set up to do already - if the INTERRUPT is uncommented and other minor details made in the main loop).

    If you look in the current DATA statement that the LED matrix could read in, something like this would be good.

    Please help if you can.

    Thanks.
  • T&E EngineerT&E Engineer Posts: 1,396
    edited 2007-04-06 16:45
    Perhaps to cut to the chase and see what I am looking for is in the following:
    : :
    StringWriter:
    For I = 0 to 255
      IF tmpB1 = 0 THEN
     'DataChr = ???????
        Read String_Data + I, DataChr
      ELSE
         Read String_Data2 + I, DataChr
      ENDIF
    :
    

    As you can see the Variable DataChr is being populated with Bytes coming from a DATA statement as seen below:
    DataChr   Var  Byte
     
     
    ' Here are the DATA statements that can be used to scroll across the 16x16 LED matrix
    
    String_Data:
    Data "  11:59:50 AM          12/31/07 Monday     ",0
     
    String_Data2:
    Data "  More scrolling here   ",0
    

    This part of the program is working correctly and it scrolls the message across the 16x16 LED matrix display.
    HOWEVER - Here is what I want to be able to do.......
    In another part of the program exists DS1302 Real Time Clock code that is working and sends time and date information out to a 2x16 Parallax Serial LCD.
    But....Instead of sending these time and date bytes to a LCD, I want them to be fed into a DATA statement so that the DataChr variable can READ it.
    If this is not possible then I want to find a way to take the Time and Date data and put it into a format that the scrolling routine can use (maybe an array instead of a READ / DATA statement - it doesn't really mater what format this is in as long as it works).
    The core of the LCD writing routines are·from these subroutines:


    ClockDisplay  VAR BYTE 
     
    TimeDate(Secs) =  $50
    TimeDate(Mins) =  $59
    TimeDate(Hrs) =   $11  
    TimeDate(Date) =  $31
    TimeDate(Month) = $12
    TimeDate(Day) =   $01
    TimeDate(Year) =  $07
    TimeDate(Ctrl) =  $00
     
     
     
            SendByte $82 ' set LCD cursor to 1st line, 4th character in (for time)
            WriteDataToDisplay TimeDate(Hrs),":"
            WriteDataToDisplay TimeDate(Mins),":"
            WriteDataToDisplay TimeDate(Secs),$20
     
     
     
    WriteDataToDisplay:
     temp3=__PARAM1
     temp4=__PARAM2
     FOR Idx=0 to 1
      ClockDisplay=temp3
      IF Idx=0 THEN
       SWAP ClockDisplay
      ENDIF
      ClockDisplay=ClockDisplay & $0f
      ClockDisplay=ClockDisplay | $30
      SendByte ClockDisplay
     NEXT
     SendByte temp4
    RETURN
     
     
    SendByte:
        temp1 = __PARAM1                 ' save the byte
        IF __PARAMCNT = 2 THEN             ' "count" specified?
            temp2 = __PARAM2                ' yes, save
        ELSE
            temp2 = 1                     ' no, set to 1
        ENDIF
        DO WHILE temp2 > 0
            SEROUT DISPLAYComPort, DisplayBaud, temp1    ' transmit
            DEC temp2
        LOOP
    RETURN
    
    



    If anyone can see a simple solution to take this time and date data bytes and be able to bring them into the LED scrolling message subroutine...I would be very interested and gratefull.

    Thanks again to all that can help me figure this out.

    ·
  • PJAllenPJAllen Banned Posts: 5,065
    edited 2007-04-06 17:57
    Here's a RAM matrix, if you will, for the SX28 (it can be adapted for SX-you-name-it.)· It's a Proof of Concept program, not the answers to anyone's prayers.
    I assigned VALues to rcv_data, but you'll have to make a program that'll read your DS....device and place those values, accordingly.

    The values get placed on the B outputs in succession, as the FOR r = loop repeats.
    (If you whump your LEDs on RB.0, .1, .2, .3, .4 then everything should be apparent.)

    DEVICE sx28, oschs3, TURBO, STACKX, OPTIONX
    IRC_CAL  IRC_SLOW
    FREQ     28_000_000
     
    PROGRAM  starter
     
    starter:
    TRIS_B = $00
    rcv_data     VAR  Byte (3)
    r            VAR  Byte
     
    rcv_data (0) = $11
    rcv_data (1) = $0E
    rcv_data (2) = $15
     
    Place_data:
       FOR r = 0 TO 2
       RB = rcv_data (r)
       PAUSE 2000
       NEXT
    GOTO Place_data
    
  • T&E EngineerT&E Engineer Posts: 1,396
    edited 2007-04-06 18:35
    PJ Allen,
    Thank you. I understand what this is doing but I don't see if it will be what I need - understanding it is a·proof of concept. I will look at it tonight.

    In the mean time, I wrote this to compare the outputs of the DS1302 and the DATA statements first character (e.g. "A").
    String_Data3:
    Data "ABC",0
     
     
     
    DO
    
     TimeDate(Hrs) = $41 'Ascii "A"
    
     J = TimeDate(Hrs)
     
     FOR I = 0 to 0
    
       Read String_Data3 + I, DataChr  'String_Data3 has an "A" as the first byte. 
     
       \ WATCH DataChr, 8, uhex  'The \ WATCH statements should be the same
    
       \ WATCH J, 8, uhex        'being an ASCII "A" or $41.
     
       BREAK
     
     NEXT
    
    LOOP
    
  • Sparks-R-FunSparks-R-Fun Posts: 388
    edited 2007-04-06 18:55
    T&E Engineer,

    As I think you already know, using a READ statement to access your time and date information is not a valid option since the READ statement can only read bytes/data (semi-)permanently stored in the program memory. (The program memory contents can only be changed by programming the SX, not while a program is actively running on the SX.)

    You will want to use an array. This is not as hard as it might seem. First you need to create an array. The array will exist in your variable memory. So make it as large as you need but not much larger.

    In the following example I created a constant called MESSAGESIZE that makes it much easier to change the size of the array(s) by changing only this value. If you make it too large you will run out of variable space and generate a compiler error.
    MESSAGESIZE   CON 32
    Message1      VAR BYTE (MESSAGESIZE)
    Message2      VAR BYTE (MESSAGESIZE)
    

    Each location in the array(s) can hold one character. I find it helps to use graph paper or a spreadsheet to keep track of each character and its location.

    Let me jump right into modifying your StringWriter subroutine as follows:
    StringWriter:
    'For I = 0 to 255
    For I = 0 to MESSAGESIZE
      IF tmpB1 = 0 THEN
    '    Read String_Data + I, DataChr
         DataChr = Message1(I)
      ELSE
    '     Read String_Data2 + I, DataChr
         DataChr = Message2(I)
      ENDIF
    

    Here the variable ‘I’ is just a position pointer that indicates which character in the array to return. Easy, eh? The first position is zero. The last is MESSAGESIZE-1. That might be the most confusing part!

    Now for the "magic!" Since the array is stored in Random Access Memory (RAM) you can change the values of each entry on the fly as your program runs. That is what you should do with the data coming from your DS1302 Real Time Clock.

    You currently have this DATA statement:
    Data "  11:59:50 AM          12/31/07 Monday     ",0
    


    Suppose you want to replicate in the Message1 array the format of the data statement you provided. You begin with two leading spaces. So position 0 and position 1 of Message1 should contain the decimal value 32, which is the ASCII code for a space.

    You could do this, though it is not very efficient:
    Message1(0) = 32
    Message1(1) = 32
    

    Or this which is more human readable:
    Message1(0) = “ “
    Message1(1) = “ “
    

    Either set creates the two leading spaces you had.

    The ten's place of the hour entry comes next and occupies position 2. (I hope you see the progression.) Skipping ahead a bit, the one’s digit of the seconds entry is located at position 9. So once every second your program will be changing the value of position 9 and once every ten seconds it will be changing the value of position 8, the tens of seconds place. It is ok to update both positions every second, as I show below, if that is easier.


    At this point I need to stop as I have only glanced at some of your program and have not spent the time required to understand the whole of it. The fact that it is working and scrolling messages is great! But I have to question your use of hex values as either you or I do not correctly understand how they are being used.

    For example, you have the assignment "TimeDate(Secs) = $50". The entry $50 as a hex value is the same as having 80 (eighty) decimal seconds! I can not imagine that anyone would actually count this way but perhaps you are receiving the data in this format. For the rest of this post I am going to assume that you are actually receiving hex values from the Real Time Clock.

    If that is the case then this next bit of code should update the appropriate values for you!

    First you will need to declare the subroutine along with a few convenient constants.
    PosSecs          CON 8                         ‘ Start position of the seconds display
    PosMins          CON 5                         ‘ Start position of the minues display
    PosHrs           CON 2                         ‘ Start position of the hours display
    
    HEXUPDATE   SUB 2, 2                       ' Places a value (in hex) in Message1 starting at the position (in decimal)
                                                  ' USAGE: HEXUPDATE HexValue, Message1Position
                                                  ' EXAMPLE: HEXUPDATE $59, 8
    


    Then you will need to define it as follows:
    HEXUPDATE:
    ' USAGE: HEXUPDATE HexValue, Message1Position
    ' EXAMPLE: HEXUPDATE $59, 8                     ' Updates the seconds display
    
    
      tmpB1 = __PARAM1                              ' get hex value as first parameter
      tmpB3 = __PARAM2                              ' get message position as second parameter
      tmpB2 = tmpB1 AND $F0                         ' isolate 1st hex value
      SWAP tmpB2                                    ' swap the nibbles
      READ Hex_Digit + tmpB2, tmpB2                 ' read the ASCII hex character
    
      Message1(tmpB3) = tmpB2                       ' display the hex character
      INC tmpB3                                     ' increment to the next message position
    
      tmpB2 = tmpB1 AND $0F                         ' isolate 2nd hex value
      READ Hex_Digit + tmpB2, tmpB2                 ' read the ASCII  hex character
    
      Message1(tmpB3) = tmpB2                       ' display the hex character
    
    RETURN
    


    Finally you can call it like this:
    HEXUPDATE TimeDate(Secs), PosSecs                   ' Updates the seconds display
    HEXUPDATE TimeDate(Mins), PosMins                   ' Updates the minutes display
    HEXUPDATE TimeDate(Hrs), PosHrs                     ' Updates the hours display
    


    I think you get the idea. You will note that I added a new variable tmpB3. You will need to either create it or change its name to an appropriate temporary variable.

    If that helps you in any way, great! If not... keeping asking questions!


    - Sparks
  • T&E EngineerT&E Engineer Posts: 1,396
    edited 2007-04-06 19:09
    Sparks-R-Fun,

    Wow! This looks great. I can't wait to try out your ideas tonight.

    BTW: The TimeDate( ) variables must be in HEX format for the clock updates to work as I beleive the DS1302 works in BCD formating. Trust me it works. Decimal formats will not.

    I did have a problem when I pieced it together as I ran out of RAM when adding tmpB3. I believe if I substitute Idx for tmpB3, this should work ok.

    I also added in:

    Hex_Digit:
    DATA "0123456789ABCDEF"

    I hope this is correct!!!


    I will post the results later. I have attached the pieced together program. Let me know if this looks right. I will post my results tonight.

    Thanks so much!!

    Post Edited (T&E Engineer) : 4/6/2007 7:29:08 PM GMT
  • Sparks-R-FunSparks-R-Fun Posts: 388
    edited 2007-04-06 20:09
    T&E Engineer,

    Any unused temporary byte variable that is not altered by the ISR should work in place of tmpB3.

    Yes, I expect you will still need the Hex_Digit DATA statement. Good call!

    I expect that there is still a LOT of work you will need to do to get everything running as you would like. One thing that I did notice upon taking a second glance at your program is that the SendByte subroutine will probably need to be replaced as it currently sends data to the serial port. You may not even need it!

    For displaying the day you can probably get away with the following (shown only for Monday and Tuesday).
          Monday:
               Message1(PosDay0) = $4D    ' M
               Message1(PosDay1) = $6F    ' o
               Message1(PosDay2) = $6E    ' n
               Goto Finish
          Tuesday:
               Message1(PosDay0) = $54    ' T
               Message1(PosDay1) = $75    ' u
               Message1(PosDay2) = $65    ' e
               Goto Finish
    


    This assumes that you have defined some constants earlier in the program like the following:
    STARTOFDAYENTRY CON 20                      '  Start position of the Day Entry
    
    PosDay0         CON STARTOFDAYENTRY         '  Start position of the Day Entry
    PosDay1         CON STARTOFDAYENTRY + 1     '  next character position
    PosDay2         CON STARTOFDAYENTRY + 2     '  next character position
    


    Doing this allows you to alter the day position simply by changing the STARTOFDAYENTRY constant and recompiling!

    Finally, I noticed that your rewrite of the StringWriter subroutine references Message1 in both branches of the IF...THEN statement. The second reference should be to Message2 if you indeed keep two separate messages.

    I hope this helps!

    - Sparks
  • T&E EngineerT&E Engineer Posts: 1,396
    edited 2007-04-07 01:05
    Well I am making some progress. However the DS1302 routines (e.g. "SetMode", ·"SetTimeAndDate" and "GetTimeAndDate") are bringing on problems with TimeDate( ).

    I first quickly found out that I first needed to set the Message1 array to something first like spaces otherwise nothing happened on the LED matrix display. This is noted in the program below with the FOR Idx = 0 to MESSAGESIZE section.

    Also if I comment out the SetMode, SetTimeAndDate and GetTimeAndDate (including the IF TimeDate(secs)<>temp1 ... ENDIF section) then I can scroll 11 59 50 as you would expect which reflects what you see in the program below.

    If the IF TimeDate(secs)<>temp1 .... ENDIF··· is not commented out then it only scrolls through once because the GetTimeAndDate is commented out and it never gets the update for TimeDate(secs) to compare with temp1.

    As seen in the program below, the TimeDate( )·data·scrolls 11 59 50· across the display as it should. However you will see that SetMode is commented out and SetTimeAnd Date and GetTimeAndDate·are commented out too.

    Here is where the problems occur:

    If I uncomment SetMode then I get· B1 59 50 scrolling as it clears the TimeDate(Hrs) bit 7. However, this subroutine works·as it should·on the LCD program. The only difference between the LCD program and the LED matrix is commenting out the INTERRUPT to turn it off (LCD gets weird characters if the·LED matrix INTERRUPT is left on).

    If I further uncomment SetTimeAndDate then I continue to get the B1 59 50 scrolling. So no apparent change here.

    However, if I further uncomment GetTimeAndDate I get 51 09 01···· then···· 59 09·09··· then· 00 00 83· etc... (as you can see the seconds are changing <even though everything is wrong> and it goes into the next day (e.g. 00 00 xx, etc.)

    As you can see TimeDate(Hrs) which was originally 11 and then B1 is now 51 after the GetTimeAndDate call. Also TimeDate(Mins) which was originally 59 is now 09. And finally TimeDate(secs) consistently changes orginally from 50 to 01 to 09 to·83 (??) etc.. which is all wrong.

    TimeDate(Secs) =  $50
    TimeDate(Mins) =  $59
    TimeDate(Hrs) =   $11 ' if modeFlag is set to Hr24, TimeDate(Hrs) = $00 to $23 otherwise $00 to $11 when Hr12 is set
    TimeDate(Date) =  $31
    TimeDate(Month) = $12
    TimeDate(Day) =   $01
    TimeDate(Year) =  $07
    TimeDate(Ctrl) =  $00
    ampmFlag = PM  ' if modeFlag is set to Hr12, ampmFlag is AM or PM
    modeFlag = Hr12  ' set to either modeFlag = Hr12 or Hr24
     
    For Idx = 0 to MESSAGESIZE
     Message1(Idx) = " "
    NEXT
     
    'SetMode
     
    'SetTimeAndDate
     
    temp1=0
    
    Main:
    
    DO
       'GetTimeAndDate
     
     'IF TimeDate(Secs) <> temp1 THEN
     
    ' Subroutines to send the Time and Date to the LCD
             'WriteTimeToDisplay
             'WriteDateToDisplay
    
    HEXUPDATE TimeDate(Secs), PosSecs                   ' Updates the seconds display
    HEXUPDATE TimeDate(Mins), PosMins                   ' Updates the minutes display
    HEXUPDATE TimeDate(Hrs), PosHrs                     ' Updates the hours display
    
    ' Subroutine to set up the message DATA statement to the 16x16 LED matrix
     
      Scroll_Dir = 0
      tmpB1 = 0
      tmpB2 = 2
      StringWriter
    
        'ENDIF
     
       'temp1=TimeDate(Secs)
     
    LOOP
    END
     
     
     
     
    SetMode:
      ' Setting clockMode to modeFlag will effectively
      '  set or clear BIT7 in the hrs variable.
      clockMode = modeFlag
      ' Setting ampm to ampmFlag will effectively set BIT5 in the
      ' hrs variable to the proper value.
      ' This must only be done when modeFlag is set (12 Hour Mode),
      ' otherwise you can destroy hours above 19 in 24 Hour Mode.
      IF modeFlag = Hr12 THEN 
       ampm = ampmFlag
      ENDIF
    RETURN
     
     
    SetTimeAndDate:
     HIGH RTCCS    ' start transaction
     SHIFTOUT Dta, Clk, LSBFIRST, BurstWrite ' write address
     FOR Idx = Secs TO Ctrl   ' write all registers
     SHIFTOUT Dta, Clk, LSBFIRST, TimeDate(Idx)
     NEXT
     LOW RTCCS
    RETURN
     
     
    GetTimeAndDate:
     HIGH RTCCS    ' start transaction
     SHIFTOUT Dta, Clk, LSBFIRST, BurstRead ' write address
     FOR Idx = Secs TO Ctrl   ' read time registers
     SHIFTIN Dta, Clk, LSBPRE, TimeDate(Idx)
     NEXT
     LOW RTCCS
    RETURN
    

    I was thinking what do they have in common is the INTERRUPT routine that is required to display the LED messages but can't be on when modifying the program for LCD usage. Is there a timing issue perhaps as SetTimeAndDate uses a SHIFTOUT and GetTimeAndDate uses a SHIFTIN command. Could this be the problem I have had all along with trying to display TimeDate( ) data?

    Well I did another test and found out that the INTERRUPT had nothing to do with the problem.

    I removed the 4 MHZ external resonator and changed the DEVICE code to reflect.

    DEVICE   SX52, OSC4MHZ, BOR42 'Use an internal 4 MHZ clock
    FREQ            4_000_000
    ID              "16x16"
    


    I then added some / WATCH statements. As you can see below, all of the code is NOT commented like before.

    TimeDate(Secs) =  $50
    TimeDate(Mins) =  $59
    TimeDate(Hrs) =   $11 ' if modeFlag is set to Hr24, TimeDate(Hrs) = $00 to $23 otherwise $00 to $11 when Hr12 is set
    TimeDate(Date) =  $31
    TimeDate(Month) = $12
    TimeDate(Day) =   $01
    TimeDate(Year) =  $07
    TimeDate(Ctrl) =  $00
    ampmFlag = PM  ' if modeFlag is set to Hr12, ampmFlag is AM or PM
    modeFlag = Hr12  ' set to either modeFlag = Hr12 or Hr24
     
    For Idx = 0 to MESSAGESIZE
     Message1(Idx) = " "
    NEXT
     
    SetMode
    
     
    SetTimeAndDate
    temp1=0
    
    Main:
    
    DO
    
     
       GetTimeAndDate
    
     
     IF TimeDate(Secs) <> temp1 THEN
    ' Subroutines to send the Time and Date to the LCD
             'WriteTimeToDisplay
             'WriteDateToDisplay
    
    HEXUPDATE TimeDate(Secs), PosSecs                   ' Updates the seconds display
    HEXUPDATE TimeDate(Mins), PosMins                   ' Updates the minutes display
    HEXUPDATE TimeDate(Hrs), PosHrs                     ' Updates the hours display
     
    J = TimeDate(Hrs)
    \ WATCH J, 8, uhex
     
    K = TimeDate(Mins)
    \ WATCH K, 8, uhex
     
    X = TimeDate(Secs)
    \ WATCH X, 8, uhex
    
     
    BREAK
     
    ' Subroutine to set up the message DATA statement to the 16x16 LED matrix
      Scroll_Dir = 0
      tmpB1 = 0
      tmpB2 = 2
      StringWriter
    
        ENDIF
       temp1=TimeDate(Secs)
    LOOP
    
    END
    


    Now I went into DEBUG mode and saw the SAME wrong data as before (51 09 01·· not the 11 59 50 as I hoped for) for all of the TimeDate( ).

    I verified this by commented and uncommenting the Interrupt routine calls between DEBUG sessions. I always got the 51 09 01 and not the 11 59·50.

    ' Comment out the INTERRUPT 1000 {if not using the 16x16 LED matrix - LCD use only)
    ' Comment out the GOTO INT_HANDLER (if not using the 16x16 LED matrix - LCD use only)                 ' -------------------------------------------------------------------------
      
      'INTERRUPT 1000    ' run every millisecond
      
    ' -------------------------------------------------------------------------
    

      'GOTO INT_HANDLER
    



    Any ideas on this?? What do I look at next?

    Thank you for your help.

    Post Edited (T&E Engineer) : 4/7/2007 1:37:12 AM GMT
  • T&amp;E EngineerT&amp;E Engineer Posts: 1,396
    edited 2007-04-07 18:16
    I got it to work finally. I had to move somethings around and I also converted some tmpB1 and temp variables into Array variable s to make more variable space which was a plus.

    I can display the time on top or bottom· OR· the date on top or bottom (scrolling left to right for either).

    What I can't do properly is have them both (Time and Date) on the display scrolling at the same time. I will work on this some more over the weekend.
  • PJAllenPJAllen Banned Posts: 5,065
    edited 2007-04-07 18:58
    Once you get it all squared away, hopefully you will/can

    compose a video or something and put that on youtube.com
  • T&amp;E EngineerT&amp;E Engineer Posts: 1,396
    edited 2007-04-08 12:04
    Here is the link (bottom post) of a YouTube.com video I made last night:

    http://forums.parallax.com/showthread.php?p=643703


    PS: I also added a bit more code that scrolls up a 16x16 picture in a WDATA statement.



    I also added another video that shows connecting and disconnecting a serial LCD (ground and RX only) and how it does not update the time display if disconnected. It does work as long as the serial LCD is connected to one of the unused RA lines. It also has to have some sort of a SEROUT command OR a TRIS_A command (0's or 1's doesn't seem to matter after the TRIS_A xxxxxxxx).

    http://www.youtube.com/watch?v=Uj3GMY8hTp8

    ·I have also attached the latest code to review.

    Post Edited (T&E Engineer) : 4/8/2007 4:41:36 PM GMT
  • T&amp;E EngineerT&amp;E Engineer Posts: 1,396
    edited 2007-04-08 18:05
Sign In or Register to comment.