Shop OBEX P1 Docs P2 Docs Learn Events
Help with variable types — Parallax Forums

Help with variable types

Lawrence ShaferLawrence Shafer Posts: 12
edited 2008-01-16 03:37 in BASIC Stamp
I am building a temperature controller for a greenhouse stove so I don't have time to properly search this out for myself, so I ask your help. Why cannot I use "addr = SDEC temp"? how would I go about doing this? everything else works as advertised, but this one last thing... here is the whole code, very messy and big, but so be it for this time. Thank you in advance. ~Lawrence

' =========================================================================
'
'   File....... LCD_AppMod_Demo.BS2
'   Purpose.... Demonstrates the LCD Terminal AppMod
'   Author..... Parallax, Inc.  (Copyright 2003-04, All Rights Reserved)
'   E-mail..... support@parallax.com
'   Started....
'   Updated.... 13 JAN 2004
'
'   {$STAMP BS2}
'   {$PBASIC 2.5}
'
' =========================================================================


' -----[noparse][[/noparse] Program Description ]---------------------------------------------
'
' This program demonstrates the use of the Parallax LCD Terminal AppMod
' with any BS2-series microcontroller. This program uses conditional
' compilation techniques which make it completely BS2-agnostic. Custom
' character generation and animation is demonstrated.


' -----[noparse][[/noparse] I/O Definitions ]-------------------------------------------------

E               PIN     1                       ' LCD Enable (1 = enabled)
RW              PIN     2                       ' Read/Write\
RS              PIN     3                       ' Reg Select (1 = char)
LcdDirs         VAR     DIRB                    ' dirs for I/O redirection
LcdBusOut       VAR     OUTB
LcdBusIn        VAR     INB


' -----[noparse][[/noparse] Constants ]-------------------------------------------------------

#DEFINE _LcdReady = ($STAMP = BS2P) OR ($STAMP = BS2PE)

LcdCls          CON     $01                     ' clear the LCD
LcdHome         CON     $02                     ' move cursor home
LcdCrsrL        CON     $10                     ' move cursor left
LcdCrsrR        CON     $14                     ' move cursor right
LcdDispL        CON     $18                     ' shift chars left
LcdDispR        CON     $1C                     ' shift chars right

LcdDDRam        CON     $80                     ' Display Data RAM control
LcdCGRam        CON     $40                     ' Character Generator RAM
LcdLine1        CON     $80                     ' DDRAM address of line 1
LcdLine2        CON     $C0                     ' DDRAM address of line 2

LcdScrollTm     CON     150                     ' LCD scroll timing (ms)


' -----[noparse][[/noparse] Variables ]-------------------------------------------------------

addr            VAR     Word                    ' address pointer
crsrPos         VAR     Byte                    ' cursor position
char            VAR     Byte                    ' character sent to LCD
idx             VAR     Byte                    ' loop counter
scan            VAR     Byte                    ' loop counter

buttons         VAR     Nib
btnA            VAR     buttons.BIT0            ' left-most button
btnB            VAR     buttons.BIT1
btnC            VAR     buttons.BIT2
btnD            VAR     buttons.BIT3            ' right-most

btnDemo         VAR     Byte                    ' loop counter

set             VAR     Word                    ' set temp
Msg4t           VAR     Word
onOff           VAR     Byte
servoPos        VAR     Word
sign2           VAR     servoPos.BIT15

' ===================== Define Pins and Variables for DS1620================
DQ              CON     15                      ' Pin 2 <=> DQ.
CLK             CON     14                      ' Pin 1  => CLK.
RST             CON     13                      ' Pin 0  => RST (high = active).
DSdata          VAR     Word                    ' Word variable to hold 9-bit data.
DSdataC         VAR     Word                    ' Word variable to hold 9-bit data.
DSdataF         VAR     Word                    ' Word variable to hold 9-bit data.
Sign            VAR     DSdata.BIT8             ' Sign bit of raw temperature data.
T_sign          VAR     Bit                     ' Saved sign bit for converted temperature.

' ===================== Define DS1620 Constants ===================
' >>> Constants for configuring the DS1620
Rconfig         CON     $AC                     ' Protocol for 'Read Configuration.'
Wconfig         CON     $0C                     ' Protocol for 'Write Configuration.'
CPU             CON     %10                     ' Config bit: serial thermometer mode.
NoCPU           CON     %00                     ' Config bit: standalone thermostat mode.
OneShot         CON     %01                     ' Config bit: one conversion per start request.
Cont            CON     %00                     ' Config bit: continuous conversions after start.
' >>> Constants for serial thermometer applications.
StartC          CON     $EE                     ' Protocol for 'Start Conversion.'
StopC           CON     $22                     ' Protocol for 'Stop Conversion.'
Rtemp           CON     $AA                     ' Protocol for 'Read Temperature.'
' >>> Constants for programming thermostat functions.
RhiT            CON     $A1                     ' Protocol for 'Read High-Temperature Setting.'
WhiT            CON     $01                     ' Protocol for 'Write High-Temperature Setting.'
RloT            CON     $A2                     ' Protocol for 'Read Low-Temperature Setting.'
WloT            CON     $02                     ' Protocol for 'Write Low-Temperature Setting.'


' -----[noparse][[/noparse] EEPROM Data ]-----------------------------------------------------

CC0             DATA    $0E, $1F, $1C, $18, $1C, $1F, $0E, $00  ' char 0
CC1             DATA    $0E, $1F, $1F, $18, $1F, $1F, $0E, $00  ' char 1
CC2             DATA    $0E, $1F, $1F, $1F, $1F, $1F, $0E, $00  ' char 2
Smiley          DATA    $0E, $0A, $0E, $00, $00, $00, $00, $00  ' smiley
Deg             DATA    $0E, $0A, $0E, $00, $00, $00, $00, $00  ' degree sign

Msg1            DATA    "Starting"
Msg20           DATA    "Heat Off"
Msg21           DATA    "Heat  On"
Msg3            DATA    " Set At "
Msg4            DATA    3, "F  "

' -----[noparse][[/noparse] Initialization ]--------------------------------------------------

Initialize:
  NAP 5                                         ' let LCD self-initialize
  DIRL = %11111110                              ' setup pins for LCD

LCD_Init:
  #IF _LcdReady #THEN
    LCDCMD E, %00110000 : PAUSE 5               ' 8-bit mode
    LCDCMD E, %00110000 : PAUSE 0
    LCDCMD E, %00110000 : PAUSE 0
    LCDCMD E, %00100000 : PAUSE 0               ' 4-bit mode
    LCDCMD E, %00101000 : PAUSE 0               ' 2-line mode
    LCDCMD E, %00001100 : PAUSE 0               ' no crsr, no blink
    LCDCMD E, %00000110                         ' inc crsr, no disp shift
  #ELSE
    LcdBusOut = %0011                           ' 8-bit mode
    PULSOUT E, 3 : PAUSE 5
    PULSOUT E, 3 : PAUSE 0
    PULSOUT E, 3 : PAUSE 0
    LcdBusOut = %0010                           ' 4-bit mode
    PULSOUT E, 3
    char = %00101000                            ' 2-line mode
    GOSUB LCD_Command
    char = %00001100                            ' on, no crsr, no blink
    GOSUB LCD_Command
    char = %00000110                            ' inc crsr, no disp shift
    GOSUB LCD_Command
  #ENDIF

Download_Chars:                                 ' download custom chars
  char = LcdCGRam                               ' point to CG RAM
  GOSUB LCD_Command                             ' prepare to write CG data
  FOR idx = CC0 TO (Smiley + 7)                 ' build 4 custom chars
    READ idx, char                              ' get byte from EEPROM
    GOSUB LCD_Write_Char                        ' put into LCD CG RAM
  NEXT


' -----[noparse][[/noparse] Program Code ]----------------------------------------------------

Main:
  set = 74                                      ' default temp
  char = LcdCls                                 ' clear the LCD
  GOSUB LCD_Command
  PAUSE 500

Write_Splash:
  addr = Msg1                                   ' point to message
  GOSUB LCD_Put_String                          ' write it
  PAUSE 1000

Initialize_DS1620:
  LOW RST                                       ' Deactivate '1620 for now.
  HIGH CLK                                      ' Put clock in starting state.
  PAUSE 100                                     ' Let things settle down a moment.

  HIGH RST                                      ' Activate the '1620 and set it for continuous..
  SHIFTOUT DQ,CLK,LSBFIRST,[noparse][[/noparse]Wconfig,CPU+Cont]   ' ..temp conversions.
  LOW RST                                       ' Done--deactivate.
  PAUSE 50                                      ' Wait for the EEPROM to self-program.
  HIGH RST                                      ' Now activate it again and send the..
  SHIFTOUT DQ,CLK,LSBFIRST,[noparse][[/noparse]StartC]             ' Send start-conversion protocol.
  LOW RST                                       ' Done--deactivate.

Show_Buttons:
  char = LcdCls                                 ' clear the LCD
  GOSUB LCD_Command
  PAUSE 100
  'addr = Msg4                                   ' write "Buttons:"
  'GOSUB LCD_Put_String

MainLoop:
  DO                                            ' Main Loop
  FOR btnDemo = 1 TO 100 STEP 2                        ' read temp once

    IF btnDemo = 1 THEN
      GOSUB Get_Temp
      char = LcdLine1 + 2
      GOSUB LCD_Command
      addr = DSdataF     ' write temp in F
      GOSUB LCD_Put_String
    ENDIF
    GOSUB servo

    char = LcdLine2 + 0                         ' show on 2nd line
    GOSUB LCD_Command

    IF btnDemo = 1 THEN
      addr = SDEC set
      GOSUB LCD_Put_String
    ELSEIF btnDemo = 61 THEN
      IF set < DSdataF THEN
        addr = Msg20
      ELSE
        addr = Msg21
      ENDIF
    ELSEIF btnDemo = 81 THEN
      addr = Msg3
    ENDIF


    GOSUB LCD_Put_String
    'GOSUB LCD_Write_Char

    GOSUB LCD_Get_Buttons                       ' read/debounce buttons

    IF buttons.LOWBIT(3) THEN GOTO MainLoop     ' exit loop and refresh if btn pressed
  NEXT
  LOOP

  GOTO Main                                     ' run demo again
  END


' -----[noparse][[/noparse] Subroutines ]-----------------------------------------------------

' Writes stored (in DATA statement) zero-terminated string to LCD
' -- position LCD cursor
' -- point to 0-terminated string (first location in 'addr')

servo:
  'DEBUG SDEC set, CR
  servoPos = 1000 - (set * 100) + (DSdataF * 100)
  IF sign2 = 1 THEN servoPos = 0
  servoPos = servoPos MIN 500 MAX 2800
    FOR idx = 1 TO 12
      PULSOUT 8, servoPos

      PAUSE 10
    NEXT
RETURN


Get_Temp:
  HIGH RST        ' Activate the '1620.
  SHIFTOUT DQ,CLK,LSBFIRST,[noparse][[/noparse]Rtemp]  ' Request to read temperature.
  SHIFTIN DQ,CLK,LSBPRE,[noparse][[/noparse]DSdata\9]  ' Get the temperature reading.
  LOW RST
  T_sign = Sign      ' Save the sign bit of the reading.
  DSdata = DSdata/2    ' Scale reading to whole degrees C.
  IF T_sign = 0 THEN no_neg1
    DSdata = DSdata | $FF00  ' Extend sign bits for negative temps.
no_neg1:
  'DEBUG SDEC DSdata," degrees C",CR  ' Show signed temperature in C.
    DSdataC = DSdata
    DSdata = (DSdata */ $01CC)    ' Multiply by 1.8.
  IF T_sign = 0 THEN no_neg2    ' If negative, extend sign bits.
    DSdata = DSdata | $FF00
no_neg2:
    DSdata = DSdata + 32    ' Complete the conversion.
    'DEBUG SDEC DSdata," degrees F",CR  ' Show signed temperature in F.
    DSdataF = DSdata - 5
RETURN

LCD_Put_String:
  DO
    READ addr, char
    IF (char = 0) THEN EXIT
    GOSUB LCD_Write_Char
    addr = addr + 1
  LOOP
  RETURN

' Send command to LCD
' -- put command byte in 'char'

LCD_Command:                                    ' write command to LCD
  #IF _LcdReady #THEN
    LCDCMD E, char
    RETURN
  #ELSE
    LOW RS
    GOTO LCD_Write_Char
  #ENDIF


' Write character to current cursor position
' -- but byte to write in 'char'

LCD_Write_Char:                                 ' write character to LCD
  #IF _LcdReady #THEN
    LCDOUT E, 0, [noparse][[/noparse]char]
  #ELSE
    LcdBusOut = char.HIGHNIB                    ' output high nibble
    PULSOUT E, 3                                ' strobe the Enable line
    LcdBusOut = char.LOWNIB                     ' output low nibble
    PULSOUT E, 3
    HIGH RS                                     ' return to character mode
  #ENDIF
  RETURN


' Reads byte from LCD
' -- put byte address in 'addr'
' -- returns byte read in 'char'

LCD_Read_Char:                                  ' read character from LCD
  #IF _LcdReady #THEN
    LCDIN E, addr, [noparse][[/noparse]char]
  #ELSE
    char = addr                                 ' move cursor
    GOSUB LCD_Command
    HIGH RS                                     ' data command
    HIGH RW                                     ' read
    LcdDirs = %0000                             ' make LCD bus inputs
    HIGH E
    char.HIGHNIB = LcdBusIn                     ' get high nibble
    LOW E
    HIGH E
    char.LOWNIB = LcdBusIn                      ' get low nibble
    LOW E
    LcdDirs = %1111                             ' return data lines to outputs
    LOW RW
  #ENDIF
  RETURN


' Read and debounce the LCD AppMod buttons

LCD_Get_Buttons:
  LcdDirs = %0000                               ' make LCD bus inputs
  buttons = %1111                               ' assume all pressed
  FOR scan = 1 TO 10
    buttons = buttons & LcdBusIn                ' make sure button held
    PAUSE 10                                     ' debounce 10 x 5 ms
  NEXT
  LcdDirs = %1111                               ' return bus to outputs
      IF buttons.LOWBIT(0) THEN
      set = set - 1
      GOTO MainLoop
    ELSEIF buttons.LOWBIT(1) THEN
      set = set + 1
      GOTO MainLoop
    ENDIF
RETURN

Comments

  • Mike GreenMike Green Posts: 23,101
    edited 2008-01-15 05:06
    The "formatters" like SDEC are special operators that can only occur in input and output statements like SERIN and SEROUT.
    It's not hard to write a simple output conversion routine. The biggest problem is where to put the result (as a string). With
    the limited variable storage in the Stamps (26 bytes of variable space), it's much better to do conversions one character at
    a time and send it to the specific device rather than store it. The LCDOUT statement, for example, allows the SDEC formatter.
  • Lawrence ShaferLawrence Shafer Posts: 12
    edited 2008-01-15 05:18
    Yes, but this is a BS2 and I'm converting the code from BS2p code. I had LCDOUT statements there and now am trying to use the code provided by the LCD APPMOD DEMO, the BS2 has no LCDOUT commands. What to do?
  • Mike GreenMike Green Posts: 23,101
    edited 2008-01-15 05:48
    Well, you'll have to write your own formatting routine using the DIG operator (look it up in the manual for a description) adding a "0" like
    if value < 0 then
      value = -value
      char = "-"
      gosub sendToLCD
    endif
    leading = 0
    for i = 4 to 0
       if ((value dig i) > 0) or (leading <> 0) or (i = 0)
          char = (value dig i) + "0"
          gosub sendToLCD
          leading = 1
       endif
    next i
    
    


    This routine outputs a sign if the value is negative, suppresses leading zeros, and outputs at least one digit.
    The routine sendToLCD sends the character in char to the LCD.
  • Lawrence ShaferLawrence Shafer Posts: 12
    edited 2008-01-15 13:42
    I'm still not sure this will do what I need. The problem is without the DEC it is telling the LCD to write an alphabetical char instead of a number. If I do a "debug DEC temp" I get 72 or whatever, "debug temp" gives me J . Same with the LCD. I'll play around with what you gave me, but signed negatives are not what I'm after, just numbers! Thanks for your help.
  • Tracy AllenTracy Allen Posts: 6,667
    edited 2008-01-15 17:41
    Mikes routine is a substitute for the DEC, or more specifically for the SDEC that you asked for in your first post. It converts a value, say 72, into a string of two characters "72" to send one at a time to the LCD. You have your routine, "LCD_Write_Char:", and Mike used the name "sendToLCD" for that same function. Where Mike used "value", you would have your word variable "DSdata".

    Like the DEC operator, it suppresses leading zeros, so it comes out as two characters "72" instead of "00072".


    DSdata might possibly go negative. Maybe not in your application. But I think there is a bug lurking in your get_Temp routine for the DS1620. The */ operator does not work correctly on negatives.

    ▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔
    Tracy Allen
    www.emesystems.com
  • Lawrence ShaferLawrence Shafer Posts: 12
    edited 2008-01-16 03:37
    Thanks guys, it works perfectly. Sometimes I'm just slow to understand...
Sign In or Register to comment.