Use of the BX24 to Program a Dallas DS1821 Thermostat

copyright, Peter H. Anderson, Baltimore, MD, Apr, '02, Jan , '08


Note that this DS1821 programmer is available as an assembled unit. for $79.95. The source code is provided below for those who wish to build their own units.

Discussion

This discussion focuses on the use of a BX24 to program a Dallas DS1821 Programmable Thermostat.

The DS1821 may either be used as a thermometer or as a thermostat. In the thermostat mode, the temperature is continually measured and the open drain output goes to the active state when the temperature is above the programmed value of TH and returns to the normal state when the temperature falls below the value of TL. The active state is determined by the setting of the POL (polarity) bit.

For example, if TH and TL are set to 35 and 29 degrees C (corresponding to 95 and 84 degrees F) and POL is set to a one, the output goes to a logic one when the temperature is above 35. This output is an open, which with a 2.2K pullup resistor to +5 VDC might turn on an IRLZ44 FET or a solid state AC relay which might turn on a fan. When the temperature falls below 29, the output of the DS1821 goes to a logic zero (ground), turning off the FET or solid state relay. If POL is set to a zero, when the temperature is above TH, the output is at zero (ground) which might turn on an optocoupler (4N3x) or optoisolator (PVI5010) which in turn controls a FET or relay.

The unit might be used as a cold alarm. For example, if the ambient temperature is 10 degrees C, and TH and TL are set to 4 and 2 degrees C and POL is set to zero, the output will normally be at a logic zero (ground) as T is above TH. When the temperature falls below 2 degrees C, the output goes to a one, operating an alarm.

Note that as the output is an open drain, many of the DS1821's may be wire ored to a single driver if the alarm state is a logic zero.

Note that the DS1821 requires a source of +5 VDC. However, this might be easily derived using a 78L05 or similar regulator or using a series resistor and a 1N4733A 5 VDC zener diode. Thus, a typical thermostat point might consist of simply the DS1821, a regulator or zener diode and resistor, a FET or similar and a pullup resistor. The DS1821 is the cheapest and yet the most accurate implementation of a thermostat that I am aware of

The code presented below may be downloaded to a BX24 and either the BasicX IDE package or Hyperterm or similar terminal emulator may be used to communicate with the BX24 in programming DS1821 thermostats. For users who would rather skip the details of downloading to a BasicX BX24, we also offer an assembled unit for $79.95. This is a complete package including a programmed BX24, assembled printed circuit board, serial cable with a DB9 female connector to interface with a PC, voltage regulators and a wall power unit. One DS1821 in a PR35 (elongated TO92) package is provided. Additional DS1821s in PR35 packages may be purchased for $4.50 each.

The user interfaces with the BX24 using either the BasicX Integrated Development Environment (IDE) or HyperTerm configured as a Direct connection, 19200 baud, 8N1, no flow.

The user is prompted to connect the DS1821 to be programmed. Note that in this implementation the VDD pin of the DS1821 is connected to BX24 terminal 12 and the DQ pin to BX24 terminal 11. The user then enters any character and the BX24 "searches" for the DS1821. If it finds doesn't find the DS1821 in the communications mode, it toggles the device from the thermostat mode to the thermometer (communications) mode.

If the device is found, the program fetches the current values of TH, TL and POL and uses these as the proposed new values. The user is then provided with a menu;

Thus, a user might typically, display ('D') the current settings, set the high and low thresholds using the 'H' and 'L' commands and set the POL using the 'P' command, display the new settings using the 'N' command, save the new settings to the DS1821 using the 'S' command and quit ('Q').

Note that when the new values are saved to the DS1821, the THF and TLF flags are set to zero and the T/R bit is configured for the thermostat mode.

Programming Note.

Note that temperature TC and the high and low thresholds are stored in the DS1821 as signed bytes. However, the BX24 uses unsigned bytes. Thus, when signed bytes are fetched from the DS1821, they are converted to signed integers using function SignedByteToSignedInteger(). This permits negative values to be displayed. New values of TH and TL fetched from the user are in signed integer format. However, when writing the quantities to the DS1821, they are converted to the signed byte format using function SignedIntegerToSignedByte()


Program T_STAT.Bas.

' T_STAT.BAS  BX24,  DS1821 Thermostat Programmer
'
' This is an implementation of a system to permit a user to custom
' program a DS1821 thermometer.  It was developed for agricultural
' applications including both thermostat and alarm applications.
'
' The low cost of the DS1821 ($2.50 in quantities of 100) makes it
' attractive in applications where other thermostat and alarm
' arrangement are not feasible.
'
'
' The user is prompted to connect the DS1821 to be programmed.
'
' The program checks to see if DS1821 is in Thermostat mode.  If so,
' the DS1821 is toggled to the communications mode.  If the device is
' found, the user is presented with a menu.
'
'
' The user is prompted to either read the values of T_H, T_L and POL
' currently stored in the DS1821, to set a new value of T_H, T_L or POL,
' to display the new values to be programmed, to display the THF and TLF
' flags, to perform a continual temperature measurement, to save the new
' parameters to the DS1821 or to quit.
'
' When saving, the THF and TLF flag bits are set to zero and T/R is set
' to 1 such that when the DS1821 again boots, it will boot in the
' thermostat mode.
'
' Note that Quitting without Saving will result in the programmed
' settings not being modified.
'
' BX24		                  DS1821 (PR35)
' Term 11 ----------------------- VDD (term 3)
' Term 12 ----------------------- DQ (term 2)
'                                 GRD (term 1)
'
' Note that a 4.7K pullup resistor to +5V is required on the DQ lead.
'
' Compile with SerialPort.Bas.
'
' (Dec, '03).  Modified SignedIntegertoSignedByte as the previous
'
'       RetVal = CByte(I AND &H007f)
'
' will not compile using strict syntax checking.
'
' copyright, Peter H. Anderson, Montpelier, VT, Mar, '02, Jan '08

const DQ_PIN as Byte = 12
const VDD_PIN as Byte = 11

const ONESHOT as Byte = &H01     ' status bits in DS1821
const POL as Byte = &H02
const THERMOSTAT as Byte = &H04
const TLF as Byte = &H08
const THF as Byte = &H10

Sub Main()

   Dim Str as String *16, OpStr as String *1, Op as Byte
   Dim DS1821Exists as Boolean

   Sleep(0.1)

   Call OpenSerialPort(1, 19200)
   Call Sleep(0.5)

   Debug.Print "............."

   Do

       DS1821Exists = DS1821FindAndConfigure()
       ' detect if device exists and if so, config in comm mode
       If (DS1821Exists = FALSE) Then

           Debug.Print "Device not found."
           Debug.Print "Enter X to exit.  Any other key to continue."
           Str = GetString()
           Str = UCase(Str)
           Debug.Print Str
           Op = ASC(Str)
           If (Op = ASC("X")) Then
              Exit Do
           End If

        Else
           Debug.Print "Device found."
           Call DS1821FetchAndConfigure()

           Debug.Print "Done"

           Debug.Print "Enter X to exit."; " Any other key to "; "continue."
           Str = GetString()
           Str = UCase(Str)
           Debug.Print Str
           Op = ASC(Str)
           If (Op = ASC("X")) Then
              Exit Do
           End If

        End If
   Loop

End Sub

Sub DS1821FetchAndConfigure()

    Dim THNew as Byte, TLNew as Byte, POLNew as Byte, Config as Byte, Op as Byte
    Dim THCurrent as Byte, TLCurrent as Byte, POLCurrent as Byte, TC as Byte
    Dim Proposed as Integer, X as Integer, Y as Integer
    Dim Val as Single, Success as Boolean

    Dim FetchStr as String *16

    ' set proposed settings to the current programmed settings
    POLNew = (DS1821GetStatus() AND &H02) \ 2
    THNew = DS1821GetTH()
    TLNew = DS1821GetTL()

    Do

       Debug.Print "Enter C to "; "display Current "; "programmed "; "settings."
       Debug.Print "Enter N to "; "display New "; "settings ";  "to be programmed."
       Debug.Print "Enter H to "; "set T_HI_new."
       Debug.Print "Enter L to "; "set T_LO_new."
       Debug.Print "Enter P to "; "set POL_new."
       Debug.Print "Enter M to "; "Measure "; "temperature."
       Debug.Print "Enter F to "; "View Flags."
       Debug.Print "Enter S to "; "Save new "; "settings."
       Debug.Print "Enter Q to "; "Quit and "; "toggle to "; "thermostat mode."

       FetchStr = GetString()
       FetchStr = UCase(FetchStr)
       Debug.Print FetchStr
       Op = ASC(FetchStr)

       If (Op = ASC("C")) Then

	  ' Display current programmed settings
          POLCurrent = (DS1821GetStatus() AND &H02) \ 2
          THCurrent = DS1821GetTH()
          TLCurrent = DS1821GetTL()

          Debug.Print "Current Programmed Settings:"
          Debug.Print "   POL =  "; CStr(POLCurrent)
          X = SignedByteToSignedInteger(THCurrent)
          Debug.Print "   TH =  "; CStr(X)
          X = SignedByteToSignedInteger(TLCurrent)
          Debug.Print "   TL =  "; CStr(X)

       ElseIf (Op = ASC("N")) Then

         ' Proposed new settings
          Debug.Print "New Settings:"
          Debug.Print "   POLNew = "; CStr(POLNew)
          X = SignedByteToSignedInteger(THNew)
          Debug.Print "   THNew = "; CStr(X)
          X = SignedByteToSignedInteger(TLNew)
          Debug.Print "   TLNew = "; CStr(X)

       ElseIf (Op = ASC("H")) Then

	 ' High trip point
          Debug.Print "Enter TH "; "(-55 to 125)"
          FetchStr = GetString()
          FetchStr = UCase(FetchStr)
          Debug.Print FetchStr
          Call ValueS(FetchStr, Val, Success)
          If (Success = FALSE) Then
             Debug.Print "Invalid TH"
          Else
              Proposed = CInt(Val)
              If ((Proposed < -55) OR (Proposed > 125)) Then
                  Debug.Print "Invalid TH"
              Else
                  THNew = SignedIntegerToSignedByte(Proposed)
                  X = SignedByteToSignedInteger(THNew)
                  Debug.Print "THNew = "; CStr(X)
              End If
          End If

       ElseIf (Op = ASC("L")) Then

	 ' Low trip point
          Debug.Print "Enter TL "; "(-55 to 125)"
          FetchStr = GetString()
	  FetchStr = UCase(FetchStr)
          Debug.Print FetchStr
          Call ValueS(FetchStr, Val, Success)
          If (Success = FALSE) Then
             Debug.Print "Invalid TL"
          Else
              Proposed = CInt(Val)
              If ((Proposed < -55) OR (Proposed > 125)) Then
                  Debug.Print "Invalid TL"
              Else
                 TLNew = SignedIntegerToSignedByte(Proposed)
                 X = SignedByteToSignedInteger(THNew)
                 Debug.Print "TLNew = "; CStr(X)
              End If
          End If

       ElseIf (Op = ASC("P")) Then

          ' thermostat active setting

          Debug.Print "Enter POL (0 or 1):"
          FetchStr = GetString()
          FetchStr = UCase(FetchStr)
          Debug.Print FetchStr
          Proposed = CInt(ASC(FetchStr) - ASC("0"))

          If ((Proposed < 0) OR (Proposed > 1)) Then

             Debug.Print "Invalid value of POL - "; CStr(Proposed)

          Else
             POLNew = CByte(Proposed)
             Debug.Print "POL = "; CStr(POLNew)
          End If

       ElseIf (Op = ASC("M")) Then

          ' Measure temperature
          Debug.Print "Hit any key to halt"

          Do

             TC = DS1821MakeMeas()
             X = SignedByteToSignedInteger(TC)
             Debug.Print "TC = "; CStr(X)
          Loop Until (KBHit())


       ElseIf (Op = ASC("F")) Then

          ' Display THF and TLF flag bits
           Config = DS1821GetStatus()

           If ((Config AND THF) = THF) Then
              Debug.Print "THF = 1"
           Else
              Debug.Print "THF = 0"
           End If

           If ((Config AND TLF) = TLF) Then
              Debug.Print "TLF = 1"
           Else
              Debug.Print "TLF = 0"
           End If

       ElseIf (Op = ASC("Q")) Then

           Call DS1821ToggleMode()
           Debug.Print "Quit"
           Exit Do

       ElseIf (Op = ASC("S")) Then
           X = SignedByteToSignedInteger(THNew)
           Y = SignedByteToSignedInteger(TLNew)
           If (X < Y) Then
              Debug.Print "Invalid. "; "TH is less "; "than TL."
           Else

              Debug.Print "Saving to DS1821"
              Config = THERMOSTAT + ONESHOT + (POLNew * 2)
                 ' THF, TLF are zero
              Call DS1821ProgramStatus(Config)
              Call DS1821ProgramTH(THNew)
              Call DS1821ProgramTL(TLNew)

           End If

       Else
           Debug.Print "Invalid Command"
       End If

    Loop

End Sub

Function DS1821FindAndConfigure() as Boolean
' Check to see if DS1821 exists and if so configure in communications mode

   Call PutPin(DQ_PIN, 2)
   Call PutPin(VDD_PIN, 2)	' no power
   Debug.Print "Insert DS1821 "; "in Circuit "; "and hit "; "any key to "; "continue."

   Do

      If (KBHit()) Then
         Exit Do
      End If
   Loop

   Call PutPin(VDD_PIN, 1)	' power the device
   Call Sleep(1.0)		' wait for the device to settle

   If (GetPin(DQ_PIN) = 0) Then	' probably in thermostat mode
      Call DS1821ToggleMode()
      If (DS1821Presence()) Then' present and in communications mode
         DS1821FindAndConfigure = TRUE
      Else
         DS1821FindAndConfigure = FALSE
         			' apparently doesn't exist
      End If
   Else		' may be in the communications mode
      If (DS1821Presence() = TRUE) Then
         DS1821FindAndConfigure = TRUE
      Else
         Call DS1821ToggleMode()
         If (DS1821Presence()) Then' present and in communications mode
	    DS1821FindAndConfigure = TRUE
	 Else
	    DS1821FindAndConfigure = FALSE	    ' apparently doesn't exist
        End If
      End If
   End If

End Function

Function DS1821MakeMeas() as Byte

'  measure temperature
   Dim Val as Byte, Presence as Boolean

   Presence = DS1821Presence()
   Call OutByte_1W(&Hee)  ' start a temperature
   Call Sleep(0.750)  ' wait for it to complete

   Presence = DS1821Presence()
   Call OutByte_1W(&Haa)  ' read temperature
   Val = InByte_1W()
   DS1821MakeMeas = Val

End Function

Function DS1821GetTH() as Byte
   ' fetch programmed value of high trip point
   Dim Val as Byte, Presence as Boolean

   Presence = DS1821Presence()
   Call OutByte_1W(&Ha1)	' read T_H
   Val = InByte_1W()
   DS1821GetTH = Val
End Function

Function DS1821GetTL() as Byte
   ' fetch programmed value of low trip point
   Dim Val as Byte, Presence as Boolean

   Presence = DS1821Presence()
   Call OutByte_1W(&Ha2)   	' read T_L
   Val = InByte_1W()
   DS1821GetTL = Val
End Function

Function DS1821GetStatus() as Byte
   ' fetch status register
   Dim Val as Byte, Presence as Boolean

   Presence = DS1821Presence()
   Call OutByte_1W(&Hac)   	' read Status
   Val = InByte_1W()
   DS1821GetStatus = Val
End Function

Sub DS1821ProgramTH(ByVal T as Byte)
   Dim Presence as Boolean

   Presence = DS1821Presence()
   Call OutByte_1W(&H01)	' write TH
   Call OutByte_1W(T)
   Call Sleep(0.05)		' wait for EEPROM
End Sub

Sub DS1821ProgramTL(ByVal T as Byte)
   Dim Presence as Boolean

   Presence = DS1821Presence()
   Call OutByte_1W(&H02)	' write TL
   Call OutByte_1W(T)
   Call Sleep(0.05)		' wait for EEPROM
End Sub

Sub DS1821ProgramStatus(ByVal Config as Byte)
   Dim Presence as Boolean

   Presence = DS1821Presence()
   Call OutByte_1W(&H0c)	' write status
   Call OutByte_1W(Config)
   Call Sleep(0.05)		' wait for EEPROM
End Sub


Sub DS1821ToggleMode()
'bring V_DD low and pulse DQ low 16 times
   Dim N as Integer

   Call PutPin(DQ_PIN, 1)	' DQ to a hard logic one
   Call PutPin(VDD_PIN, 0)	' power to GRD

   For N= 1 to 16   		' pulse DQ pin 16 times
      Call PutPin(DQ_PIN, 0)
      Call PutPin(DQ_PIN, 1)
   Next

   Call PutPin(VDD_PIN, 1)	' bring VDD back to a one
   Call PutPin(DQ_PIN, 2)	' DQ back to high Z

   Call Sleep(0.05)		' brief delay

End Sub

Function SignedByteToSignedInteger(ByVal B as Byte) as Integer
   Dim RetVal as Integer

   If ((B AND &H80) = &H80) Then
      B = (B XOR &HFF) + 1
      RetVal = -1 * CInt(B)
   Else
      RetVal = CInt(B)
   End If

   SignedByteToSignedInteger = RetVal

End Function

Function SignedIntegerToSignedByte(ByVal I as Integer) as Byte
   Dim RetVal as Byte
   If (I < 0) Then
       RetVal = CByte(I)
       RetVal = RetVal AND &H7F
       RetVal = RetVal OR &H80
   Else
       RetVal = CByte(I)
       RetVal = RetVal AND &H7F
   End If
   SignedIntegerToSignedByte = RetVal
End Function


'''''''''''
' Low Level 1-Wire Routines

Function DS1821Presence() as Boolean

   Dim N as Integer
   Dim Transitions as Long

   Call PutPin(DQ_PIN, 2)	' be sure DQ is an input
   Call PutPin(DQ_PIN, 0)

   For N = 1 to 3	' adjust for 500 usec delay
   Next

   Call PutPin(DQ_PIN, 2)	' not sure if necessary
   Transitions = CountTransitions(DQ_PIN, 200)	' 200 * 2.4 us

   If (Transitions <> 0) Then
      DS1821Presence = TRUE
   Else
      DS1821Presence = FALSE
   End If

End Function


Function InByte_1W() as Byte

   Dim N as Integer, IByte as Byte, B as Byte
   For N =1 to 8
      B = Get1Wire(DQ_Pin)
      If (B=1) then
         IByte = (IByte\2) OR bx10000000
      Else
         IByte = IByte\2
      End If
   Next

   InByte_1W = IByte

End Function

Sub OutByte_1W(ByVal OByte as Byte)

   Dim N as Integer, B as Byte
   For N = 1 to 8
     B = OByte AND bx00000001
     If (B=1) Then
        Call Put1Wire(DQ_Pin, 1)
     Else
        Call Put1Wire(DQ_Pin, 0)
     End If
     OByte = OByte \ 2
   Next
End Sub

Sub StrongPullUp_1W()
   ' Provide a hard logic one for 0.75 secs
   Call PutPin(DQ_Pin, 1)
   Call Sleep(0.75)
   Call PutPin(DQ_Pin, 2)
End Sub


Function GetString() as String	' Fetches characters until newline (13) received
   Dim Str as String
   Dim Ch as Byte
   Dim Success as Boolean

   Str = ""	' start with null

   Do
      Do
         Call GetByte(Ch, Success)
      Loop Until (Success)
      ' Debug.Print Chr(Ch)
      If (Ch = 13) Then
            GoTo GetStringDone
      Else
         Str = Str & Chr(Ch)
         ' Call PutStr(Str)
      End If
   Loop

   GetStringDone:

   GetString = Str
End Function

Function KBHit() as Boolean

   Dim Success as Boolean, Ch as Byte
   Call GetByte(Ch, Success)
   KBHit = Success	' pass back same as Success

End Function