lifx-lan-0.3.0: LIFX LAN API
Safe HaskellNone
LanguageHaskell2010

Lifx.Lan

Synopsis

Documentation

discoverDevices :: MonadLifx m => Maybe Int -> m [HostAddress] Source #

If an integer argument is given, wait until we have responses from that number of devices. Otherwise just keep waiting until timeout.

data Message a where Source #

Instances

Instances details
Eq (Message a) Source # 
Instance details

Defined in Lifx.Lan

Methods

(==) :: Message a -> Message a -> Bool #

(/=) :: Message a -> Message a -> Bool #

Ord (Message a) Source # 
Instance details

Defined in Lifx.Lan

Methods

compare :: Message a -> Message a -> Ordering #

(<) :: Message a -> Message a -> Bool #

(<=) :: Message a -> Message a -> Bool #

(>) :: Message a -> Message a -> Bool #

(>=) :: Message a -> Message a -> Bool #

max :: Message a -> Message a -> Message a #

min :: Message a -> Message a -> Message a #

Show (Message a) Source # 
Instance details

Defined in Lifx.Lan

Methods

showsPrec :: Int -> Message a -> ShowS #

show :: Message a -> String #

showList :: [Message a] -> ShowS #

data HSBK Source #

Constructors

HSBK 

Instances

Instances details
Eq HSBK Source # 
Instance details

Defined in Lifx.Lan

Methods

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

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

Ord HSBK Source # 
Instance details

Defined in Lifx.Lan

Methods

compare :: HSBK -> HSBK -> Ordering #

(<) :: HSBK -> HSBK -> Bool #

(<=) :: HSBK -> HSBK -> Bool #

(>) :: HSBK -> HSBK -> Bool #

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

max :: HSBK -> HSBK -> HSBK #

min :: HSBK -> HSBK -> HSBK #

Show HSBK Source # 
Instance details

Defined in Lifx.Lan

Methods

showsPrec :: Int -> HSBK -> ShowS #

show :: HSBK -> String #

showList :: [HSBK] -> ShowS #

Generic HSBK Source # 
Instance details

Defined in Lifx.Lan

Associated Types

type Rep HSBK :: Type -> Type #

Methods

from :: HSBK -> Rep HSBK x #

to :: Rep HSBK x -> HSBK #

type Rep HSBK Source # 
Instance details

Defined in Lifx.Lan

newtype Duration Source #

Constructors

Duration Word32 

Instances

Instances details
Eq Duration Source # 
Instance details

Defined in Lifx.Lan

Ord Duration Source # 
Instance details

Defined in Lifx.Lan

Show Duration Source # 
Instance details

Defined in Lifx.Lan

Generic Duration Source # 
Instance details

Defined in Lifx.Lan

Associated Types

type Rep Duration :: Type -> Type #

Methods

from :: Duration -> Rep Duration x #

to :: Rep Duration x -> Duration #

type Rep Duration Source # 
Instance details

Defined in Lifx.Lan

type Rep Duration = D1 ('MetaData "Duration" "Lifx.Lan" "lifx-lan-0.3.0-GAAfhhepnfu1kJe4hZeFDh" 'True) (C1 ('MetaCons "Duration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

runLifx :: Lifx a -> IO a Source #

Note that this throws LifxErrors as IOExceptions, and sets timeout to 5 seconds. Use runLifxT for more control.

newtype LifxT m a Source #

Constructors

LifxT 

Instances

Instances details
Monad m => Monad (LifxT m) Source # 
Instance details

Defined in Lifx.Lan

Methods

(>>=) :: LifxT m a -> (a -> LifxT m b) -> LifxT m b #

(>>) :: LifxT m a -> LifxT m b -> LifxT m b #

return :: a -> LifxT m a #

Functor m => Functor (LifxT m) Source # 
Instance details

Defined in Lifx.Lan

Methods

fmap :: (a -> b) -> LifxT m a -> LifxT m b #

(<$) :: a -> LifxT m b -> LifxT m a #

Monad m => Applicative (LifxT m) Source # 
Instance details

Defined in Lifx.Lan

Methods

pure :: a -> LifxT m a #

(<*>) :: LifxT m (a -> b) -> LifxT m a -> LifxT m b #

liftA2 :: (a -> b -> c) -> LifxT m a -> LifxT m b -> LifxT m c #

(*>) :: LifxT m a -> LifxT m b -> LifxT m b #

(<*) :: LifxT m a -> LifxT m b -> LifxT m a #

MonadIO m => MonadIO (LifxT m) Source # 
Instance details

Defined in Lifx.Lan

Methods

liftIO :: IO a -> LifxT m a #

MonadIO m => MonadLifx (LifxT m) Source # 
Instance details

Defined in Lifx.Lan

runLifxT :: MonadIO m => Int -> LifxT m a -> m (Either LifxError a) Source #

data LifxError Source #

Instances

Instances details
Eq LifxError Source # 
Instance details

Defined in Lifx.Lan

Ord LifxError Source # 
Instance details

Defined in Lifx.Lan

Show LifxError Source # 
Instance details

Defined in Lifx.Lan

Generic LifxError Source # 
Instance details

Defined in Lifx.Lan

Associated Types

type Rep LifxError :: Type -> Type #

type Rep LifxError Source # 
Instance details

Defined in Lifx.Lan

type Rep LifxError = D1 ('MetaData "LifxError" "Lifx.Lan" "lifx-lan-0.3.0-GAAfhhepnfu1kJe4hZeFDh" 'False) ((C1 ('MetaCons "DecodeFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteOffset) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "RecvTimeout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BroadcastTimeout" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [HostAddress])))) :+: ((C1 ('MetaCons "WrongPacketType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)) :+: C1 ('MetaCons "WrongSender" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HostAddress) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HostAddress))) :+: (C1 ('MetaCons "UnexpectedSockAddrType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SockAddr)) :+: C1 ('MetaCons "UnexpectedPort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PortNumber)))))

class MonadIO m => MonadLifx m where Source #

Methods

getSocket :: m Socket Source #

getSource :: m Word32 Source #

getTimeout :: m Int Source #

incrementCounter :: m () Source #

getCounter :: m Word8 Source #

lifxThrow :: LifxError -> m a Source #

handleOldMessage Source #

Arguments

:: Word8

expected counter value

-> Word8

actual counter value

-> Word16

packet type

-> ByteString

payload

-> m () 

Instances

Instances details
MonadLifx m => MonadLifx (MaybeT m) Source # 
Instance details

Defined in Lifx.Lan

MonadIO m => MonadLifx (LifxT m) Source # 
Instance details

Defined in Lifx.Lan

MonadLifx m => MonadLifx (ExceptT e m) Source # 
Instance details

Defined in Lifx.Lan

MonadLifx m => MonadLifx (ReaderT e m) Source # 
Instance details

Defined in Lifx.Lan

MonadLifx m => MonadLifx (StateT s m) Source # 
Instance details

Defined in Lifx.Lan

Responses

data LightState Source #

Constructors

LightState 

Fields

Instances

Instances details
Eq LightState Source # 
Instance details

Defined in Lifx.Lan

Ord LightState Source # 
Instance details

Defined in Lifx.Lan

Show LightState Source # 
Instance details

Defined in Lifx.Lan

Generic LightState Source # 
Instance details

Defined in Lifx.Lan

Associated Types

type Rep LightState :: Type -> Type #

type Rep LightState Source # 
Instance details

Defined in Lifx.Lan

type Rep LightState = D1 ('MetaData "LightState" "Lifx.Lan" "lifx-lan-0.3.0-GAAfhhepnfu1kJe4hZeFDh" 'False) (C1 ('MetaCons "LightState" 'PrefixI 'True) (S1 ('MetaSel ('Just "hsbk") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HSBK) :*: (S1 ('MetaSel ('Just "power") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16) :*: S1 ('MetaSel ('Just "label") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))))

data StateService Source #

Constructors

StateService 

Fields

Instances

Instances details
Eq StateService Source # 
Instance details

Defined in Lifx.Lan

Ord StateService Source # 
Instance details

Defined in Lifx.Lan

Show StateService Source # 
Instance details

Defined in Lifx.Lan

Generic StateService Source # 
Instance details

Defined in Lifx.Lan

Associated Types

type Rep StateService :: Type -> Type #

type Rep StateService Source # 
Instance details

Defined in Lifx.Lan

type Rep StateService = D1 ('MetaData "StateService" "Lifx.Lan" "lifx-lan-0.3.0-GAAfhhepnfu1kJe4hZeFDh" 'False) (C1 ('MetaCons "StateService" 'PrefixI 'True) (S1 ('MetaSel ('Just "service") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Service) :*: S1 ('MetaSel ('Just "port") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

data Service Source #

Instances

Instances details
Eq Service Source # 
Instance details

Defined in Lifx.Lan

Methods

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

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

Ord Service Source # 
Instance details

Defined in Lifx.Lan

Show Service Source # 
Instance details

Defined in Lifx.Lan

Generic Service Source # 
Instance details

Defined in Lifx.Lan

Associated Types

type Rep Service :: Type -> Type #

Methods

from :: Service -> Rep Service x #

to :: Rep Service x -> Service #

type Rep Service Source # 
Instance details

Defined in Lifx.Lan

type Rep Service = D1 ('MetaData "Service" "Lifx.Lan" "lifx-lan-0.3.0-GAAfhhepnfu1kJe4hZeFDh" '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))))

newtype StatePower Source #

Constructors

StatePower 

Fields

Instances

Instances details
Eq StatePower Source # 
Instance details

Defined in Lifx.Lan

Ord StatePower Source # 
Instance details

Defined in Lifx.Lan

Show StatePower Source # 
Instance details

Defined in Lifx.Lan

Generic StatePower Source # 
Instance details

Defined in Lifx.Lan

Associated Types

type Rep StatePower :: Type -> Type #

type Rep StatePower Source # 
Instance details

Defined in Lifx.Lan

type Rep StatePower = D1 ('MetaData "StatePower" "Lifx.Lan" "lifx-lan-0.3.0-GAAfhhepnfu1kJe4hZeFDh" 'True) (C1 ('MetaCons "StatePower" 'PrefixI 'True) (S1 ('MetaSel ('Just "power") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))

Low-level

data Header Source #

Instances

Instances details
Eq Header Source # 
Instance details

Defined in Lifx.Lan

Methods

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

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

Ord Header Source # 
Instance details

Defined in Lifx.Lan

Show Header Source # 
Instance details

Defined in Lifx.Lan

Generic Header Source # 
Instance details

Defined in Lifx.Lan

Associated Types

type Rep Header :: Type -> Type #

Methods

from :: Header -> Rep Header x #

to :: Rep Header x -> Header #

Binary Header Source # 
Instance details

Defined in Lifx.Lan

Methods

put :: Header -> Put #

get :: Get Header #

putList :: [Header] -> Put #

type Rep Header Source # 
Instance details

Defined in Lifx.Lan