cayenne-lpp-0.2.0.0: Cayenne Low Power Payload
Maintainersrk <srk@48.io>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Cayenne.Types

Description

Encoding example:

import qualified Data.Cayenne as CLPP
import qualified Data.ByteString.Base16.Lazy as B16L
import qualified Data.ByteString.Lazy.Char8 as BSL

BSL.putStrLn $ B16L.encode . CLPP.encodeMany [(7, Illum 1337), (0, Power 13.5)]
Synopsis

Documentation

data Sensor Source #

Constructors

DigitalIn Word8

Digital input (8 bits)

DigitalOut Word8

Digital output (8 bits)

AnalogIn Float

Analog input

AnalogOut Float

Analog output

Illum Word16

Illuminance sensor (Lux)

Presence Word8

Presence

Temperature Float

Temperature (Celsius)

Humidity Float

Humidity (%)

Accelerometer Float Float Float

Accelerometer (G)

Barometer Float

Barometer (hPa)

Voltage Float

Voltage (V)

Current Float

Current (A)

Percentage Float

Percentage

Pressure Float

Pressure

Power Float

Power (W)

Energy Float

Energy (J)

Direction Float

Angle (Deg)

Gyrometer Float Float Float

Gyrometer (°/s)

GPS Float Float Float

GPS Latitude (°) ,Longitude (°), Altitude (m)

Instances

Instances details
Eq Sensor Source # 
Instance details

Defined in Data.Cayenne.Types

Methods

(==) :: Sensor -> Sensor -> Bool #

(/=) :: Sensor -> Sensor -> Bool #

Ord Sensor Source # 
Instance details

Defined in Data.Cayenne.Types

Show Sensor Source # 
Instance details

Defined in Data.Cayenne.Types

Generic Sensor Source # 
Instance details

Defined in Data.Cayenne.Types

Associated Types

type Rep Sensor :: Type -> Type #

Methods

from :: Sensor -> Rep Sensor x #

to :: Rep Sensor x -> Sensor #

type Rep Sensor Source # 
Instance details

Defined in Data.Cayenne.Types

type Rep Sensor = D1 ('MetaData "Sensor" "Data.Cayenne.Types" "cayenne-lpp-0.2.0.0-FoGndC9Kd8w5kzDe3u8oCZ" 'False) ((((C1 ('MetaCons "DigitalIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)) :+: C1 ('MetaCons "DigitalOut" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8))) :+: (C1 ('MetaCons "AnalogIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)) :+: C1 ('MetaCons "AnalogOut" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)))) :+: ((C1 ('MetaCons "Illum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)) :+: C1 ('MetaCons "Presence" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8))) :+: (C1 ('MetaCons "Temperature" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)) :+: (C1 ('MetaCons "Humidity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)) :+: C1 ('MetaCons "Accelerometer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))))))) :+: (((C1 ('MetaCons "Barometer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)) :+: C1 ('MetaCons "Voltage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))) :+: (C1 ('MetaCons "Current" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)) :+: (C1 ('MetaCons "Percentage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)) :+: C1 ('MetaCons "Pressure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))))) :+: ((C1 ('MetaCons "Power" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)) :+: C1 ('MetaCons "Energy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))) :+: (C1 ('MetaCons "Direction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)) :+: (C1 ('MetaCons "Gyrometer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))) :+: C1 ('MetaCons "GPS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))))))))

encode :: Reading -> ByteString Source #

Encode a single Reading

encodeMany :: [Reading] -> ByteString Source #

Encode a list of Readings

decode :: ByteString -> Reading Source #

Decode a single Reading, may fail

decodeMany :: ByteString -> [Reading] Source #

Decode multiple Readings, returns empty list if nothing is decoded

decodeMaybe :: ByteString -> Maybe Reading Source #

Maybe decode a single Reading