kafka-device-0.2.1.0: UI device events via a Kafka message broker

Copyright(c) 2016-17 Brian W Bush
LicenseMIT
MaintainerBrian W Bush <consult@brianwbush.info>
StabilityExperimental
PortabilityStable
Safe HaskellNone
LanguageHaskell2010

Network.UI.Kafka.Interpretation

Contents

Description

Interpret user-interfaces events on Kafka topics.

Synopsis

Types

data Interpretation a Source #

Instructions for interpreting user-interface events from Kafka.

Constructors

TrackInterpretation 

Fields

Instances

Eq a => Eq (Interpretation a) Source # 
Read a => Read (Interpretation a) Source # 
Show a => Show (Interpretation a) Source # 
Generic (Interpretation a) Source # 

Associated Types

type Rep (Interpretation a) :: * -> * #

ToJSON a => ToJSON (Interpretation a) Source # 
FromJSON a => FromJSON (Interpretation a) Source # 
type Rep (Interpretation a) Source # 
type Rep (Interpretation a) = D1 (MetaData "Interpretation" "Network.UI.Kafka.Interpretation" "kafka-device-0.2.1.0-59TOOcRD1ZyLOqHBhZGRps" False) (C1 (MetaCons "TrackInterpretation" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "kafka") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TopicConnection)) ((:*:) (S1 (MetaSel (Just Symbol "sensor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Sensor)) (S1 (MetaSel (Just Symbol "path") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)))) ((:*:) (S1 (MetaSel (Just Symbol "xAxis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AxisInterpretation a))) ((:*:) (S1 (MetaSel (Just Symbol "yAxis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AxisInterpretation a))) (S1 (MetaSel (Just Symbol "zAxis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AxisInterpretation a)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "phiAxis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AxisInterpretation a))) ((:*:) (S1 (MetaSel (Just Symbol "thetaAxis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AxisInterpretation a))) (S1 (MetaSel (Just Symbol "psiAxis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AxisInterpretation a))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "location") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (V3 a))) (S1 (MetaSel (Just Symbol "orientation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (V3 a)))) ((:*:) (S1 (MetaSel (Just Symbol "flying") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "resetButton") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))))))

data AxisInterpretation a Source #

Instructions for interpreting an axis.

Constructors

AxisInterpretation 

Fields

Instances

Eq a => Eq (AxisInterpretation a) Source # 
Read a => Read (AxisInterpretation a) Source # 
Show a => Show (AxisInterpretation a) Source # 
Generic (AxisInterpretation a) Source # 

Associated Types

type Rep (AxisInterpretation a) :: * -> * #

ToJSON a => ToJSON (AxisInterpretation a) Source # 
FromJSON a => FromJSON (AxisInterpretation a) Source # 
type Rep (AxisInterpretation a) Source # 
type Rep (AxisInterpretation a) = D1 (MetaData "AxisInterpretation" "Network.UI.Kafka.Interpretation" "kafka-device-0.2.1.0-59TOOcRD1ZyLOqHBhZGRps" False) (C1 (MetaCons "AxisInterpretation" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "axisNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "threshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a)))) ((:*:) (S1 (MetaSel (Just Symbol "increment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) ((:*:) (S1 (MetaSel (Just Symbol "lowerBound") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))) (S1 (MetaSel (Just Symbol "upperBound") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a)))))))

type AnalogHandler a b = b -> Maybe (Int, a) Source #

How to handle raw analog events.

type ButtonHandler a b = b -> Maybe (Int, Bool) Source #

How to handle raw button events.

Event handling

interpretationLoop Source #

Arguments

:: (Conjugate a, Epsilon a, Num a, Ord a, RealFloat a) 
=> AnalogHandler a b

How to handle raw analog events.

-> ButtonHandler a b

How to handle raw button events.

-> Interpretation a

The interpretation.

-> IO b

Action for getting the next raw event.

-> IO (ExitAction, LoopAction)

Action to create the exit and loop actions.

Repeatedly interpret events.

Orphan instances