Shop OBEX P1 Docs P2 Docs Learn Events
Senserion SHTxx and CRC Calculation — Parallax Forums

Senserion SHTxx and CRC Calculation

hbpatehbpate Posts: 5
edited 2004-08-11 07:45 in BASIC Stamp
Has anyone been successful in coding the CRC calculations for the SHTxx sensor? I have studied their information on it but do not want to use the table method for checking it. I want to do this as a calculation but it is way over my head. I am using a BS2p40 stamp.

Any help would be appreciated!!!!

·

Comments

  • dlborgmandlborgman Posts: 11
    edited 2004-08-06 02:18
    This is a long reply, but you can dig thru it and see what I did to
    use the crc error checking.

    As noted, parts of this code were born from Tracy Allen's
    excellent examples for the sensirion sensors. Tracy's
    web site is at www.emesystems.com

    This code reads 2 sht sensors and outputs the results on a
    4 channel D/A converter.

    good luck,
    Dennis


    '{$STAMP BS2sx}
    '{$PBASIC 2.5}
    ' hksht.bsx· rev 1.0
    ' (C)2003 Dennis Borgman, borgmandl@cs.com
    ' Includes code from Tracy Allen examples
    '· from his web site at www.emesystems.com
    ' Scan Sensirion sht71 humidity and temperature sensors
    ' for indoor and outdoor values and output them on DAC
    ' outputs as analog values.
    '
    DACd·· CON· 0···· ' DAC data out
    DACc·· CON· 1···· ' DAC clock out
    DACs·· CON· 2···· ' DAC chip select
    DACreg0· CON $1000 ' DAC input register 0
    DACreg1· CON $5000 ' DAC input register 1
    DACreg2· CON $9000 ' DAC input register 2
    DACreg3· CON $D000 ' DAC input register 3
    DACupdt· CON $4000 ' DAC register update
    clkI·· CON 15···· ' indoor sht71 clock line
    dtaI·· CON 14···· ' indoor sht71 data line, with 10k pullup and 390ohm isolation from stamp
    dtaIin VAR IN14·· ' data for indoor sht71, referenced as input 14 on stamp
    clkO·· CON 13···· ' outdoor sht71 clock line
    dtaO·· CON 12···· ' outdoor sht71 data line, with 10k pullup and 390ohm isolation from stamp
    dtaOin VAR IN12·· ' data for outdoor sht71, referenced as input 12 on stamp
    shtTR CON 3······ ' read temperature, sht71 command
    shtRH CON 5······ ' read humidity
    shtSW CON 6······ ' status register write
    shtSR CON 7······ ' status register read
    shtS0 CON 30····· ' restore status register defaults (then delay 11 milliseconds)
    baud· CON $f0···· ' 9600, $f0 for BS2sx
    degC· VAR Word··· ' degrees Celsius * 100
    degF· VAR Word··· ' degrees Fahrenheit * 100
    RH··· VAR Word··· ' %RH
    RHtc· VAR Word··· ' temperature compensated RH
    logEW VAR Word··· ' log10 of saturation vapor pressure, calculated from degC & RH
    DP··· VAR Word··· ' dew point, calculated from degC & RH
    wx··· VAR Word··· ' temporary variable
    result· VAR wx··· ' alias, result from sht
    r0··· VAR result.BYTE0
    r1··· VAR result.BYTE1
    wy··· VAR Word··· ' temporary in calculations
    wz··· VAR Word··· ' ditto
    wj··· VAR Word··· ' ditto, integer part
    DACdat VAR wx···· ' DAC data value
    DACloc VAR wy···· ' DAC location value
    cmd·· VAR Byte··· ' command to sht71
    c0··· VAR Byte··· ' crc from sht71
    ix··· VAR Byte··· ' loop index
    crc·· VAR Byte··· ' computed crc
    sign· VAR Bit···· ' sign in calculations
    signF VAR Bit···· ' sign for farenheit
    bt··· VAR Bit···· ' for calculations
    cflag VAR Bit···· ' crc check result, true=crc error
    initialize:
    · OUTS=0················ ' set all output latches to zero
    · HIGH DACs············· ' deselect DAC
    · DIRS=%1010111111111110 ' P0, P12, P14 are inputs
    · PAUSE 500
    · GOSUB shtrst·········· ' reset communication with sht71s
    mainloop:
    · SEROUT 16,baud,[noparse][[/noparse]">"]
    · GOSUB getITemp
    · IF cflag=0 THEN
    ··· PUT 0,Word((degF+400)**33860)··· ' scale and store ITmp
    ··· SEROUT 16,baud,[noparse][[/noparse]TAB,"IdgC=",REP "-"\sign,DEC ABS degC/10,".",DEC1 ABS degC]
    ··· SEROUT 16,baud,[noparse][[/noparse]"·· IdgF=",REP "-"\signF,DEC ABS degF/10,".",DEC1 ABS degF,CR]
    · ENDIF
    · GOSUB getIHum
    · IF cflag=0 THEN
    ··· PUT 2,Word(130+(RHtc**58648))··· ' scale and store IRh
    ··· SEROUT 16,baud,[noparse][[/noparse]TAB,"%IRH=",DEC RHtc/10,".",DEC1 RHtc,CR,LF]
    · ENDIF
    · GOSUB getOTemp
    · IF cflag=0 THEN
    ··· PUT 4,Word((degF+400)**33860)··· ' scale and store OTmp
    ··· SEROUT 16,baud,[noparse][[/noparse]TAB,"OdgC=",REP "-"\sign,DEC ABS degC/10,".",DEC1 ABS degC]
    ··· SEROUT 16,baud,[noparse][[/noparse]"·· OdgF=",REP "-"\signF,DEC ABS degF/10,".",DEC1 ABS degF,CR]
    · ENDIF
    · GOSUB getOHum
    · IF cflag=0 THEN
    ··· PUT 6,Word(130+(RHtc**58648))··· ' scale and store ORh
    ··· SEROUT 16,baud,[noparse][[/noparse]TAB,"%ORH=",DEC RHtc/10,".",DEC1 RHtc,CR]
    · ENDIF
    · GOSUB getDewPoint
    · SEROUT 16,baud,[noparse][[/noparse]TAB,"OdpC=",REP "-"\sign,DEC ABS DP/10,".",DEC1 ABS DP,CR,LF]
    · GOSUB loadDAC·· ' update DAC outputs
    · PAUSE 5000
    GOTO mainloop
    getITemp:
    · cmd=shtTR
    · GOSUB shtgetI24
    · GOSUB chkcrc··· ' assumes cmd, r1, r0, c0 as input
    · IF cflag THEN RETURN··· ' crc error
    · 'result=6500··· ' test value, =26dC =77dF
    · 'degC = -40 + 0.01 * result
    · 'degCx100 = -4000 + 1 * result
    · degC=result-4000·················· ' deg C * 100
    · degF= result*8/10 + result - 4000· ' deg F * 100
    · sign=degC.BIT15··················· ' 1 = negative
    · 'degC = (-sign XOR (((ABS degC) + 5)/10)) + sign
    · degC=-sign^(ABS degC +5/10)+sign·· 'reduce degrees C to x10 and round off
    · signF=degF.BIT15·················· ' 1 = negative
    · degF=-signF^(ABS degF +5/10)+signF 'reduce degrees F to x10 and round off
    RETURN
    getOTemp:
    · cmd=shtTR
    · GOSUB shtgetO24
    · GOSUB chkcrc··· ' assumes cmd, r1, r0, c0 as input
    · IF cflag THEN RETURN··· ' crc error
    · 'degC = -40 + 0.01 * result
    · 'degCx100 = -4000 + 1 * result
    · degC=result-4000·················· ' deg C * 100
    · degF= result*8/10 + result - 4000· ' deg F * 100
    · sign=degC.BIT15··················· ' 1 = negative
    · 'degC = (-sign XOR (((ABS degC) + 5)/10)) + sign
    · degC=-sign^(ABS degC +5/10)+sign·· 'reduce degrees C to x10 and round off
    · signF=degF.BIT15·················· ' 1 = negative
    · degF=-signF^(ABS degF +5/10)+signF 'reduce degrees F to x10 and round off
    RETURN
    getIHum:
    · cmd=shtRH
    · GOSUB shtgetI24
    · GOSUB chkcrc··· ' assumes cmd, r1, r0, c0 as input
    · IF cflag THEN RETURN··· ' crc error
    · 'result=1742··· ' test value, =58%RH
    '· SEROUT 16,baud,[noparse][[/noparse]TAB,"RHresult=",DEC result,CR,REP LF\LFb]
    · 'RH··· = -c1 + (·· c2 * result) - (····· c3 * result * result)
    · 'RH··· = -4· + (.0405 * result) - (.0000028 * result * result)
    · 'RHx10 = -40 + ( .405 * result) - ( .000028 * result * result)
    · 'c1 = -4····· stamp uses -40, to give result in RH*10
    · 'c2 = 0.0405· stamp uses 0.405 * 65536 = 26542 (factor of 10 too)
    · 'c3 = -2.8E-6 stamp uses 2.8E-6 * 65536 * 65536 * 10 = 120259 (factor of 10 too)
    · '······································· = 54723/65536 + 65536/65536 = 1.835
    · ' Convert tics to RH
    · RH=(26542-(54722**result+result))**result-40
    '· SEROUT 16,baud,[noparse][[/noparse]TAB,"RHraw=",DEC RH,CR,REP LF\LFb]
    · '
    · 'In order to avoid negative temperatures (which cause problems with the Stamp
    · 'integer math ** operator), transform the temperature to Kelvin, by adding 273.
    · 'AND note that 273-25 = 248. Use temperature * 10 in the calculations,
    · 'so that the compensated humidity value will come out as RH*10. The value of
    · 'temperature held by variable degC, is actually Celsius*100, so I have to
    · 'divide that by 10 to get Celsius*10. Since 273 was added, it must also be
    · 'subtracted back out.· The equation for the stamp rewritten is:
    · 'RHtc = ((degC/10 + 2480) * factor) - (2730 * factor) + RH
    · '
    · 'RHtc = (Tc-25) * (.01 + .00008*result) + RH
    · '0.01*65536 = 655
    · '0.00008*65536*65536 = 5*65536+15917 giving the stamp factor: 655+(result*5)+(result**15917)
    · 'FOR example, the raw result = 2353 when RH=75.79%.
    · 'The factor is 0.01 + 0.00008*2353 = 0.01 + 0.1882 = 0.1982
    · 'AND in Stampese, 655+(2353*5)+(2353**15917)=655+11765+571=12991 (12991/65536=.1982)
    · ' Temperature factor
    · RHtc=655+(result*5)+(result**15917)
    · ' Temperature compensated RH
    · RHtc=(RHtc**(degC+2730-250))-(RHtc**2730)+RH
    RETURN:
    getOHum:
    · cmd=shtRH
    · GOSUB shtgetO24
    · GOSUB chkcrc··· ' assumes cmd, r1, r0, c0 as input
    · IF cflag THEN RETURN··· ' crc error
    · ' Convert tics to RH
    · RH=(26542-(54722**result+result))**result-40
    · ' Temperature factor
    · RHtc=655+(result*5)+(result**15917)
    · ' Temperature compensated RH
    · RHtc=(RHtc**(degC+2730-250))-(RHtc**2730)+RH
    RETURN:
    getdewPoint:
    · ' enter with -400<degC<1000 (temperature times 10)
    · ' and 0<RHtc<1000 (relative humidity times 10)
    · ' uses Magnus Tetens formula
    · ' first the logarithm of the saturation vapor pressure over water at temperature
    · ' then from that the dew point temperature
    · ' logEW = (0.66077 + 7.5*T/(237.3+T) + log (RH/100)
    · ' DP = ((0.66077 - logEW)*237.3)/(logEW-8.16077)
    · ' The error is large when the dewpoint is below freezing (where the
    · ' formula could be modified for saturation vapor pressure over ice.)
    · logEW=6608
    · '
    · sign=degC.BIT15
    · wz=ABS degC
    · wx=7*wz+(wz/2)· ' 7.5*wz
    · wy=2373+wz
    · GOSUB divide········· ' wx/wy· return with wj=integer part, wz=fractional x/65536
    · ' -1.52<EW1<+2.22 for -40<degC<100, and EW1=1.305 at degC=0
    · ' -15200<EW1<22200 for -400<degC<1000
    · wx=-sign^(wj*10000+(wz**10000))+sign··· ' convert to decimal x.xxxx * 10000 & extend sign
    · logEW=wx+logEW
    · wx=RHtc
    · GOSUB log2······················· ' find log base 2 of RH
    · wx=(wj*4000**49321)+(wz**6021)··· ' convert lg2 to log10 x.xxxx * 10000
    · logEW=wx+logEW-30000············· ' -30000, because RH is 0->1000
    ' maximum at +100 degrees C, 100%RH, where logEW=+28843 (+2.8843)
    ' minimum at -40 degrees C, 1%RH, where logEW=-28598 (-2.8598)
    ' calculate logEW/4, so divisor in divide below will be <32768
    · sign=logEW.BIT15
    · logEW=-sign^(ABS logEW+2/4)+sign· ' logEW/4, sign extended
    · wx=1652-logEW········ ' numerator
    · sign=~wx.BIT15······· ' for dewpoint calculation, DP sign is opposite of wx
    · wx=ABS wx
    · wy=20402-logEW
    · GOSUB divide········· ' this a always a proper fraction, no integer part
    · DP=23730**wz+5/10···· ' fractional multiply, note extra decimal place and roundoff
    · DP=-sign^DP+sign····· ' extend sign
    RETURN

    divide:················ ' enter with wx and wy positive integers to divide
    · wj=wx/wy············· ' integer part of result
    · FOR ix=15 TO 0······· ' wz to be fractional part (as wz/65536 implied)
    ··· wx=wx//wy<<1
    ··· wz.BIT0(ix)=wx/wy
    · NEXT
    RETURN

    log2:············ ' enter with wx, to find log base 2
    · wj=NCD wx - 1·· ' integer part of result (characteristic, 0<=wb<=15)
    · wx=wx<<(15-wj)· ' left justify the operand
    · wz=0
    · FOR ix=14 TO 0· ' wz to be fractional part (mantissa, as wz/32768 implied)
    ··· wy=wx**wx
    ··· wz.BIT0(ix)=wy.BIT15
    ··· bt=~wy.BIT15
    ··· wx=wy<<bt+(bt & wx.BIT15)
    · NEXT
    RETURN
    shtRst:
    · SHIFTOUT dtaI,clkI,LSBFIRST,[noparse][[/noparse]$ffff\16]·· ' reset indoor sht71
    · PAUSE 12
    · SHIFTOUT dtaO,clkO,LSBFIRST,[noparse][[/noparse]$ffff\16]·· ' reset outdoor sht71
    · PAUSE 12
    · SEROUT 16,baud,[noparse][[/noparse]TAB,"okay",CR,LF]
    RETURN
    ·' get 16 bits of data and 8 bit crc, enter with command in "cmd"
    shtgetI24:
    · GOSUB shtIcmd················ ' send the command "cmd"
    · GOSUB shtIwait··············· ' wait 50-220ms for command to finish
    · SHIFTIN dtaI,clkI,MSBPRE,[noparse][[/noparse]r1] ' read msbyte
    · LOW dtaI····················· ' send acknowledge
    · PULSOUT clkI,10·············· ' clk for ack
    · INPUT dtaI··················· ' data line back to pull-up
    · SHIFTIN dtaI,clkI,MSBPRE,[noparse][[/noparse]r0] ' read lsbyte
    · LOW dtaI····················· ' send acknowledge
    · PULSOUT clkI,10·············· ' clk for ack
    · INPUT dtaI··················· ' data line back to pull-up
    · SHIFTIN dtaI,clkI,MSBPRE,[noparse][[/noparse]c0] ' read crc
    · INPUT dtaI··················· ' terminate communication w/dta high
    · PULSOUT clkI,10·············· ' clk for ack
    · c0 = c0 REV 8················ ' mirror the received crc bits
    RETURN
    ·' get 16 bits of data and 8 bit crc, enter with command in "cmd"
    shtgetO24:
    · GOSUB shtOcmd················ ' send the command "cmd"
    · GOSUB shtOwait··············· ' wait 50-220ms for command to finish
    · SHIFTIN dtaO,clkO,MSBPRE,[noparse][[/noparse]r1] ' read msbyte
    · LOW dtaO····················· ' send acknowledge
    · PULSOUT clkO,10·············· ' clk for ack
    · INPUT dtaO··················· ' data line back to pull-up
    · SHIFTIN dtaO,clkO,MSBPRE,[noparse][[/noparse]r0] ' read lsbyte
    · LOW dtaO····················· ' send acknowledge
    · PULSOUT clkO,10·············· ' clk for ack
    · INPUT dtaO··················· ' data line back to pull-up
    · SHIFTIN dtaO,clkO,MSBPRE,[noparse][[/noparse]c0] ' read crc
    · INPUT dtaO··················· ' terminate communication w/dta high
    · PULSOUT clkO,10·············· ' clk for ack
    · c0 = c0 REV 8················ ' mirror the received crc bits
    RETURN
    ' send start sequence and command
    shtIcmd:
    · ' dta: ~~~~~|_____|~~~~~~
    · ' sck: ___|~~~|_|~~~~|____
    · ' while dta is low, clock goes low and then high
    · INPUT dtaI······ ' pullup high
    · HIGH· clkI
    · LOW·· dtaI
    · LOW·· clkI
    · HIGH· clkI
    · INPUT dtaI
    · LOW·· clkI
    · SHIFTOUT dtaI,clkI,MSBFIRST,[noparse][[/noparse]cmd]
    · INPUT dtaI······ ' allow acknowledge (dta = 0 from sht)
    · PULSOUT clkI,10· ' pulse clk to let sht turn off ack
    RETURN
    ' send start sequence and command
    shtOcmd:
    · ' dta: ~~~~~|_____|~~~~~~
    · ' sck: ___|~~~|_|~~~~|____
    · ' while dta is low, clock goes low and then high
    · INPUT dtaO······ ' pullup high
    · HIGH· clkO
    · LOW·· dtaO
    · LOW·· clkO
    · HIGH· clkO
    · INPUT dtaO
    · LOW·· clkO
    · SHIFTOUT dtaO,clkO,MSBFIRST,[noparse][[/noparse]cmd]
    · INPUT dtaO······ ' allow acknowledge (dta = 0 from sht)
    · PULSOUT clkO,10· ' pulse clk to let sht turn off ack
    RETURN
    ' wait for sht to pull data pin low or for time out
    shtIwait:
    · wj=4096 '1000h
    shtIwait2:
    · wj=wj-1 'FFFh
    · IF dtaIin & wj.BIT11 THEN shtIwait2 'ends on dtain=0 or 7FFh(2048 loops)
    RETURN
    ' wait for sht to pull data pin low or for time out
    shtOwait:
    · wj=4096 '1000h
    shtOwait2:
    · wj=wj-1 'FFFh
    · IF dtaOin & wj.BIT11 THEN shtOwait2 'ends on dtain=0 or 7FFh(2048 loops)
    RETURN

    ' Check CRC
    ' Assumes cmd, r1, r0 as inputs
    ' Destroys cmd, ix, bt, crc
    chkcrc:
    · crc = 0· ' initial crc = sht status register
    · GOSUB crcx
    · cmd = r1
    · GOSUB crcx
    · cmd = r0
    · GOSUB crcx
    · IF crc <> c0 THEN
    ··· cflag = 1
    · ELSE
    ··· cflag = 0
    · ENDIF
    RETURN
    ' Assumes cmd = byte to generate crc from
    ' Assumes crc = initialized value or value from last call
    ' Destroys cmd, ix, bt, crc
    crcx:
    · FOR ix = 0 TO 7
    ··· bt = cmd.BIT7················· ' msb
    ··· cmd = cmd << 1················ ' shift left to next bit in msb
    ··· IF (bt XOR (crc.BIT7)) THEN
    ······· crc = (crc << 1) | 1······ ' bit and crc msb different
    ······· crc = crc ^ %00110000····· ' shift crc w/1 in lsb, toggle bits 4 and 5
    ··· ELSE
    ······· crc = crc << 1············ ' bit and crc msb same, shift crc w/0 in lsb
    ··· ENDIF
    · NEXT
    RETURN······ 'CRC computed

    ' Retrieve the indoor and outdoor temperature
    ' and humidity values and write them to the DAC
    loadDAC:
    · GET 0,Word DACdat· ' get the indoor temp value
    · DACloc = DACreg0·· ' load DAC channel 0
    · GOSUB write_DAC
    · GET 2,Word DACdat· ' get the indoor humidity value
    · DACloc = DACreg1·· ' load DAC channel 1
    · GOSUB write_DAC
    · GET 4,Word DACdat· ' get the outdoor temp value
    · DACloc = DACreg2·· ' load DAC channel 2
    · GOSUB write_DAC
    · GET 6,Word DACdat· ' get the outdoor humidity value
    · DACloc = DACreg3·· ' load DAC channel 3
    · GOSUB write_DAC
    · DACdat = 0
    · DACloc = DACupdt·· ' update DAC outputs
    · GOSUB write_DAC
    RETURN
    write_DAC:
    '· SEROUT 16,baud,[noparse][[/noparse]"DACdat=",HEX DACdat]
    · DACdat = DACdat<<2····· ' shift value by two bits
    · DACdat = DACdat | DACloc· ' add address to value
    '· SEROUT 16,baud,[noparse][[/noparse]"·· DACdat=",HEX DACdat,CR]
    · LOW· DACs·············· ' select DAC
    · SHIFTOUT DACd,DACc,MSBFIRST,[noparse][[/noparse]DACdat\16]
    · HIGH DACs·············· ' deselect DAC and latch data
    · RETURN

    DEBUG HOME
    END
  • Tracy AllenTracy Allen Posts: 6,656
    edited 2004-08-06 05:35
    Nice job with the CRC calculation, Dennis. I wonder, do you have a sense how often CRC errors occur in the normal course of operation? I see that your code just skips the temperature and humidity calculation and display altogether if it detects a bad checksum.

    I've never bothered with the CRC, thinking that in my systems with fairly short and direct wiring paths, there is little danger of error in the communications channel. When the readings fail, it is in a dramatic way that is pretty obvious in the data set, returned data of $0000 or $ffff. That usually comes about from a bad power supply or bad pullup or pulldown resistors. I'd be interested to hear your observations about the CRC and when it is effective.

    -- Tracy

    ▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔
    Tracy Allen
    www.emesystems.com
  • hbpatehbpate Posts: 5
    edited 2004-08-06 12:59
    Dennis,

    This is a very nice piece of code! Looks like you have lots of time in it. I too have studied Tracy Allen's work on the SHTxx and would not even be close to worrying about CRC's if it was not for his sharing of his work.

    I am cusious about your application. I am trying to dry out a wet crawl space at our house and I am using·dewpoint as the comparison to determine when to turn on a vent fan. My concern about the CRC is I will have to use long cable runs and want to make sure there is no corrupt data. I am also curious about the length and type of cable you used in your application. I need between 6 and 10 ft between sensor and stamp.

    Thank you and Tracy for the inspiration !

    Harry
  • dlborgmandlborgman Posts: 11
    edited 2004-08-06 17:10
    Tracy Allen said...
    Nice job with the CRC calculation, Dennis. I wonder, do you have a sense how often CRC errors occur in the normal course of operation? I see that your code just skips the temperature and humidity calculation and display altogether if it detects a bad checksum.

    I've never bothered with the CRC, thinking that in my systems with fairly short and direct wiring paths, there is little danger of error in the communications channel. When the readings fail, it is in a dramatic way that is pretty obvious in the data set, returned data of $0000 or $ffff. That usually comes about from a bad power supply or bad pullup or pulldown resistors. I'd be interested to hear your observations about the CRC and when it is effective.

    -- Tracy

    Thanks Tracy,
    My outdoor temperature probe is on about 75 feet of cable and it seemed prudent to filter out
    noisy readings. What I'm doing is "replacing" the humidity and temperature sensors on my Heath
    Advanced Weather Computer. Their humidity sensors weren't very good and wouldn't stay accurate.
    I'm driving the old Heath analog inputs with the DAC outputs from this little stamp circuit. I can
    keep the analog runs real short and fairly noise free. Any crc errors are just floated out since the
    DAC outputs aren't updated.

    Unfortunately, I haven't been able to compile any statistics on the crc error rate.

    Dennis


    Post Edited (dlborgman) : 8/6/2004 5:21:40 PM GMT
  • dlborgmandlborgman Posts: 11
    edited 2004-08-06 17:19
    hbpate said...
    Dennis,

    This is a very nice piece of code! Looks like you have lots of time in it. I too have studied Tracy Allen's work on the SHTxx and would not even be close to worrying about CRC's if it was not for his sharing of his work.

    I am cusious about your application. I am trying to dry out a wet crawl space at our house and I am using·dewpoint as the comparison to determine when to turn on a vent fan. My concern about the CRC is I will have to use long cable runs and want to make sure there is no corrupt data. I am also curious about the length and type of cable you used in your application. I need between 6 and 10 ft between sensor and stamp.

    Thank you and Tracy for the inspiration !

    Harry
    Harry, Thanks for the kind words!

    I'm using 75 feet of belden 8723 shielded twisted pair cable. I put the ground and clock on one
    pair and the 5 volts and data on the other. Initial monitoring didn't indicate any crc errors, but
    I have no long term statistics. I don't think I have a very noisy environment, but times during
    thunderstorms and such are certain to produce induced noise in my cable run.

    I wouldn't worry too much if your only using 6 to 10 feet of cable. If you think you have an
    electrically noisy environment, it couldn't hurt anything though. The code is cheap insurance
    against unwanted fan starts and stops.

    Let me know if I can provide any more help.

    Dennis
  • hbpatehbpate Posts: 5
    edited 2004-08-09 15:59
    Dennis,
    Thanks again for the help. The fact that you are using 75 feet of cable makes me feel much better! I tried using phone cable with the data and clock on the outside wires but was not able to get it to work at much more than 5 ft.
    I am curious about what other weather projects you have worked on.

    Thanks again
    Harry
  • dlborgmandlborgman Posts: 11
    edited 2004-08-10 00:41
    Harry and Tracy,

    Just completed about 72 hours of CRC testing on my 2 sht71 sensors.
    One is on about 3 feet of wire and the other is on about 75 feet.

    The wire is belden 8723 and is 2 twisted shielded pairs. Ground and
    clock is on one pair and 5 vdc power and data is on the other pair.

    No CRC errors were detected in 72 hours of storm free weather.
    Over 43,000 mainloops in the program (172,000 poll/replies to sensors).


    Harry, My Heathkit ID5001 Advanced Weather Computer and these
    Sensirion temp/humidty sensors are the only weather related stuff
    I've used and/or programmed. I recently retired from 30 years of
    electronic and programming support for a Houston oil company.
    Three years of tech school, then work and futsing is where I acquired
    my electronics background.

    All the best,
    Dennis
    ·
  • Tracy AllenTracy Allen Posts: 6,656
    edited 2004-08-11 07:45
    Hi Dennis,

    Thats good, and a confidence builder too, that the sensor went through all those 172000 loops without a hitch. It almost makes you itch for at big lightning storm to give it the big challenge! But why press your luck? Jorg Fetz at Sensirion might be interested in your results.

    -- Tracy

    ▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔▔
    Tracy Allen
    www.emesystems.com
Sign In or Register to comment.