| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Lifx.Lan
Description
-- these should be enabled by default in a future version of GHC
-- (they aren't entirely necessary here anyway - they just make the example even simpler)
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE NamedFieldPuns #-}
import Control.Monad.IO.Class (liftIO)
import Data.Foldable (for_)
import Lifx.Lan
-- | Find all devices on the network, print their addresses, and set their brightness to 50%.
main :: IO ()
main = runLifx do
devs <- discoverDevices Nothing
liftIO $ print devs
for_ devs \d -> do
LightState{hsbk} <- sendMessage d GetColor
sendMessage d $ SetColor hsbk{brightness = maxBound `div` 2} 3
Synopsis
- data Device
- deviceAddress :: Device -> HostAddress
- deviceFromAddress :: (Word8, Word8, Word8, Word8) -> Device
- data Message r where
- GetService :: Message StateService
- GetHostFirmware :: Message StateHostFirmware
- GetPower :: Message StatePower
- SetPower :: Bool -> Message ()
- GetVersion :: Message StateVersion
- GetColor :: Message LightState
- SetColor :: HSBK -> NominalDiffTime -> Message ()
- SetLightPower :: Bool -> NominalDiffTime -> Message ()
- data HSBK = HSBK {
- hue :: Word16
- saturation :: Word16
- brightness :: Word16
- kelvin :: Word16
- type Lifx = LifxT IO
- runLifx :: Lifx a -> IO a
- data LifxT m a
- runLifxT :: MonadIO m => Int -> LifxT m a -> m (Either LifxError a)
- data LifxError
- data ProductLookupError
- class Monad m => MonadLifx m where
- type MonadLifxError m
- liftProductLookupError :: ProductLookupError -> MonadLifxError m
- lifxThrow :: MonadLifxError m -> m a
- sendMessage :: Device -> Message r -> m r
- broadcastMessage :: Message r -> m [(Device, r)]
- discoverDevices :: Maybe Int -> m [Device]
- sendMessageAndWait :: (MonadLifx m, MonadIO m) => Device -> Message () -> m ()
- data StateService = StateService {
- service :: Service
- port :: PortNumber
- data Service
- data StateHostFirmware = StateHostFirmware {
- build :: Word64
- versionMinor :: Word16
- versionMajor :: Word16
- newtype StatePower = StatePower {}
- data StateVersion = StateVersion {}
- data LightState = LightState {}
- getProductInfo :: forall m. MonadLifx m => Device -> m Product
- data Product = Product {}
- data Features = Features {}
- encodeMessage :: Bool -> Bool -> Word8 -> Word32 -> Message r -> ByteString
- data Header = Header {
- size :: Word16
- protocol :: Word16
- addressable :: Bool
- tagged :: Bool
- origin :: Word8
- source :: Word32
- target :: Word64
- resRequired :: Bool
- ackRequired :: Bool
- sequenceCounter :: Word8
- packetType :: Word16
Documentation
deviceAddress :: Device -> HostAddress Source #
deviceFromAddress :: (Word8, Word8, Word8, Word8) -> Device Source #
>>>deviceFromAddress (192, 168, 0, 1)192.168.0.1
If we know the IP address of a Device, we can create it directly, rather than calling discoverDevices.
A message we can send to a Device. r is the type of the expected response.
Constructors
Instances
| Show (Message r) Source # | |
| Eq (Message r) Source # | |
| Ord (Message r) Source # | |
Constructors
| HSBK | |
Fields
| |
Instances
| Generic HSBK Source # | |
| Show HSBK Source # | |
| Eq HSBK Source # | |
| Ord HSBK Source # | |
| type Rep HSBK Source # | |
Defined in Lifx.Lan.Internal type Rep HSBK = D1 ('MetaData "HSBK" "Lifx.Lan.Internal" "lifx-lan-0.8.0-DQBIsgHV1Wl9JdIUUqinTJ" 'False) (C1 ('MetaCons "HSBK" 'PrefixI 'True) ((S1 ('MetaSel ('Just "hue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16) :*: S1 ('MetaSel ('Just "saturation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)) :*: (S1 ('MetaSel ('Just "brightness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16) :*: S1 ('MetaSel ('Just "kelvin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))) | |
Instances
Constructors
Instances
data ProductLookupError Source #
Constructors
| UnknownVendorId Word32 | |
| UnknownProductId Word32 |
Instances
class Monad m => MonadLifx m where Source #
Methods
liftProductLookupError :: ProductLookupError -> MonadLifxError m Source #
lifxThrow :: MonadLifxError m -> m a Source #
sendMessage :: Device -> Message r -> m r Source #
Send a message and wait for a response.
broadcastMessage :: Message r -> m [(Device, r)] Source #
Broadcast a message and wait for responses.
discoverDevices :: Maybe Int -> m [Device] Source #
Search for devices on the local network. If an integer argument is given, wait until we have found that number of devices - otherwise just keep waiting until timeout.
Instances
sendMessageAndWait :: (MonadLifx m, MonadIO m) => Device -> Message () -> m () Source #
Like sendMessage, but for messages whose effect is not instantaneous (e.g. SetColor),
block (using threadDelay) until completion.
Responses
data StateService Source #
Constructors
| StateService | |
Fields
| |
Instances
Instances
| Generic Service Source # | |
| Show Service Source # | |
| Eq Service Source # | |
| Ord Service Source # | |
| type Rep Service Source # | |
Defined in Lifx.Lan type Rep Service = D1 ('MetaData "Service" "Lifx.Lan" "lifx-lan-0.8.0-DQBIsgHV1Wl9JdIUUqinTJ" 'False) ((C1 ('MetaCons "ServiceUDP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ServiceReserved1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ServiceReserved2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ServiceReserved3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ServiceReserved4" 'PrefixI 'False) (U1 :: Type -> Type)))) | |
data StateHostFirmware Source #
Constructors
| StateHostFirmware | |
Fields
| |
Instances
newtype StatePower Source #
Constructors
| StatePower | |
Instances
| Generic StatePower Source # | |
| Show StatePower Source # | |
Defined in Lifx.Lan Methods showsPrec :: Int -> StatePower -> ShowS # show :: StatePower -> String # showList :: [StatePower] -> ShowS # | |
| Eq StatePower Source # | |
Defined in Lifx.Lan | |
| Ord StatePower Source # | |
Defined in Lifx.Lan Methods compare :: StatePower -> StatePower -> Ordering # (<) :: StatePower -> StatePower -> Bool # (<=) :: StatePower -> StatePower -> Bool # (>) :: StatePower -> StatePower -> Bool # (>=) :: StatePower -> StatePower -> Bool # max :: StatePower -> StatePower -> StatePower # min :: StatePower -> StatePower -> StatePower # | |
| type Rep StatePower Source # | |
Defined in Lifx.Lan type Rep StatePower = D1 ('MetaData "StatePower" "Lifx.Lan" "lifx-lan-0.8.0-DQBIsgHV1Wl9JdIUUqinTJ" 'True) (C1 ('MetaCons "StatePower" 'PrefixI 'True) (S1 ('MetaSel ('Just "power") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16))) | |
data StateVersion Source #
Constructors
| StateVersion | |
Instances
data LightState Source #
Instances
Product info
getProductInfo :: forall m. MonadLifx m => Device -> m Product Source #
Ask a device for its vendor and product ID, and look up info on it from the official database.
Information about a particular LIFX product.
Instances
| Generic Product Source # | |
| Show Product Source # | |
| Eq Product Source # | |
| Ord Product Source # | |
Defined in Lifx.Internal.ProductInfoMap | |
| type Rep Product Source # | |
Defined in Lifx.Internal.ProductInfoMap type Rep Product = D1 ('MetaData "Product" "Lifx.Internal.ProductInfoMap" "lifx-lan-0.8.0-DQBIsgHV1Wl9JdIUUqinTJ" 'False) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "features") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Features)))) | |
Constructors
| Features | |
Fields
| |
Instances
Message encoding
These are used internally by LifxT's sendMessage and broadcastMessage.
They are exposed in order to support some advanced use cases.
Constructors
| Header | |
Fields
| |