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

Copyright(c) 2016-19 Brian W Bush
LicenseMIT
MaintainerBrian W Bush <code@functionally.io>
StabilityBeta
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Network.UI.Kafka.Types

Contents

Description

Event types.

Synopsis

Types

data Event Source #

An event.

Constructors

KeyEvent

A character from a keyboard.

Fields

SpecialKeyEvent

A special key from a keyboard.

Fields

MouseEvent

A button press on a mouse.

Fields

ButtonEvent

The press of of a button.

Fields

ButtonsEvent

The pressing of several buttons.

Fields

PositionEvent

The movement of a mouse.

Fields

MotionEvent

Motion.

Fields

RotationEvent

Rotation.

Fields

JoystickEvent

Joystick position.

Fields

FingerEvent

Moving a finger.

Fields

PointerEvent

Moving a pointer.

Fields

AnalogEvent

An analog value.

Fields

DialEvent

A dial value.

Fields

LocationEvent

Location in space.

Fields

OrientationEvent

Orientation in space.

Fields

EventError

An error.

Fields

Instances

Eq Event Source # 

Methods

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

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

Ord Event Source # 

Methods

compare :: Event -> Event -> Ordering #

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

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

(>) :: Event -> Event -> Bool #

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

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

Read Event Source # 
Show Event Source # 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 

Associated Types

type Rep Event :: * -> * #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

ToJSON Event Source # 
FromJSON Event Source # 
Binary Event Source # 

Methods

put :: Event -> Put #

get :: Get Event #

putList :: [Event] -> Put #

Serialize Event Source # 

Methods

put :: Putter Event #

get :: Get Event #

type Rep Event Source # 
type Rep Event = D1 * (MetaData "Event" "Network.UI.Kafka.Types" "kafka-device-1.0.0.0-7U9qgkxLORxLpEJz1lnLpE" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KeyEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "key") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Char)) (S1 * (MetaSel (Just Symbol "toggle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Toggle)))) ((:*:) * (S1 * (MetaSel (Just Symbol "modifiers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Modifiers))) (S1 * (MetaSel (Just Symbol "mousePosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Double, Double))))))) (C1 * (MetaCons "SpecialKeyEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "specialKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SpecialKey)) (S1 * (MetaSel (Just Symbol "toggle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Toggle)))) ((:*:) * (S1 * (MetaSel (Just Symbol "modifiers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Modifiers))) (S1 * (MetaSel (Just Symbol "mousePosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Double, Double)))))))) ((:+:) * (C1 * (MetaCons "MouseEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "button") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ButtonState)) ((:*:) * (S1 * (MetaSel (Just Symbol "modifiers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Modifiers))) (S1 * (MetaSel (Just Symbol "mousePosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Double, Double))))))) (C1 * (MetaCons "ButtonEvent" PrefixI True) (S1 * (MetaSel (Just Symbol "button") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ButtonState))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ButtonsEvent" PrefixI True) (S1 * (MetaSel (Just Symbol "buttons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ButtonState]))) (C1 * (MetaCons "PositionEvent" PrefixI True) (S1 * (MetaSel (Just Symbol "mousePosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Double, Double)))))) ((:+:) * (C1 * (MetaCons "MotionEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "motionRightward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)) ((:*:) * (S1 * (MetaSel (Just Symbol "motionUpward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)) (S1 * (MetaSel (Just Symbol "motionBackward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double))))) (C1 * (MetaCons "RotationEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "rotationForward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)) ((:*:) * (S1 * (MetaSel (Just Symbol "rotationClockwise") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)) (S1 * (MetaSel (Just Symbol "rotationRightward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "JoystickEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "joystickRightward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)) (S1 * (MetaSel (Just Symbol "joystickForward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double))) ((:*:) * (S1 * (MetaSel (Just Symbol "joystickUpward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)) (S1 * (MetaSel (Just Symbol "buttons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ButtonState]))))) (C1 * (MetaCons "FingerEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "hand") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Hand)) ((:*:) * (S1 * (MetaSel (Just Symbol "finger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Finger)) (S1 * (MetaSel (Just Symbol "pointerPosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Double, Double, Double))))))) ((:+:) * (C1 * (MetaCons "PointerEvent" PrefixI True) (S1 * (MetaSel (Just Symbol "pointerPosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Double, Double, Double)))) (C1 * (MetaCons "AnalogEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "axis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "analogValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "DialEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "axis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "dialValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)))) (C1 * (MetaCons "LocationEvent" PrefixI True) (S1 * (MetaSel (Just Symbol "location") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Double, Double, Double))))) ((:+:) * (C1 * (MetaCons "OrientationEvent" PrefixI True) (S1 * (MetaSel (Just Symbol "orientation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Double, Double, Double, Double)))) (C1 * (MetaCons "EventError" PrefixI True) (S1 * (MetaSel (Just Symbol "message") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))))

data SpecialKey Source #

A special key.

Constructors

KeyF1

F1

KeyF2

F2

KeyF3

F3

KeyF4

F4

KeyF5

F5

KeyF6

F6

KeyF7

F7

KeyF8

F8

KeyF9

F9

KeyF10

F10

KeyF11

F11

KeyF12

F12

KeyLeft

left arrow

KeyUp

up arrow

KeyRight

right arrow

KeyDown

down arrow

KeyPageUp

page up

KeyPageDown

page down

KeyHome

home

KeyEnd

end

KeyInsert

insert

KeyNumLock

number lock

KeyBegin

begin

KeyDelete

delete

KeyShiftL

left shift

KeyShiftR

right shift

KeyCtrlL

left control

KeyCtrlR

right control

KeyAltL

left alt

KeyAltR

right alt

KeyUnknown Int

unknown, with a specified index

Instances

Eq SpecialKey Source # 
Ord SpecialKey Source # 
Read SpecialKey Source # 
Show SpecialKey Source # 
Generic SpecialKey Source # 

Associated Types

type Rep SpecialKey :: * -> * #

ToJSON SpecialKey Source # 
FromJSON SpecialKey Source # 
Binary SpecialKey Source # 
Serialize SpecialKey Source # 
type Rep SpecialKey Source # 
type Rep SpecialKey = D1 * (MetaData "SpecialKey" "Network.UI.Kafka.Types" "kafka-device-1.0.0.0-7U9qgkxLORxLpEJz1lnLpE" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KeyF1" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "KeyF2" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyF3" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "KeyF4" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyF5" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KeyF6" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyF7" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KeyF8" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyF9" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KeyF10" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyF11" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "KeyF12" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyLeft" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KeyUp" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyRight" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KeyDown" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyPageUp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KeyPageDown" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyHome" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "KeyEnd" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyInsert" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KeyNumLock" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyBegin" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KeyDelete" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyShiftL" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KeyShiftR" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyCtrlL" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "KeyCtrlR" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyAltL" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KeyAltR" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyUnknown" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))))))

data Toggle Source #

The state of a button.

Constructors

Down

pressed down

Up

released and up

Instances

Bounded Toggle Source # 
Enum Toggle Source # 
Eq Toggle Source # 

Methods

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

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

Ord Toggle Source # 
Read Toggle Source # 
Show Toggle Source # 
Generic Toggle Source # 

Associated Types

type Rep Toggle :: * -> * #

Methods

from :: Toggle -> Rep Toggle x #

to :: Rep Toggle x -> Toggle #

ToJSON Toggle Source # 
FromJSON Toggle Source # 
Binary Toggle Source # 

Methods

put :: Toggle -> Put #

get :: Get Toggle #

putList :: [Toggle] -> Put #

Serialize Toggle Source # 
type Rep Toggle Source # 
type Rep Toggle = D1 * (MetaData "Toggle" "Network.UI.Kafka.Types" "kafka-device-1.0.0.0-7U9qgkxLORxLpEJz1lnLpE" False) ((:+:) * (C1 * (MetaCons "Down" PrefixI False) (U1 *)) (C1 * (MetaCons "Up" PrefixI False) (U1 *)))

data Modifiers Source #

Keyboard modifiers.

Constructors

Modifiers 

Fields

Instances

Eq Modifiers Source # 
Ord Modifiers Source # 
Read Modifiers Source # 
Show Modifiers Source # 
Generic Modifiers Source # 

Associated Types

type Rep Modifiers :: * -> * #

ToJSON Modifiers Source # 
FromJSON Modifiers Source # 
Binary Modifiers Source # 
Serialize Modifiers Source # 
type Rep Modifiers Source # 
type Rep Modifiers = D1 * (MetaData "Modifiers" "Network.UI.Kafka.Types" "kafka-device-1.0.0.0-7U9qgkxLORxLpEJz1lnLpE" False) (C1 * (MetaCons "Modifiers" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "shiftModifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "ctrlModifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "altModifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))

data Button Source #

A button.

Constructors

LeftButton

left mouse button

MiddleButton

middle mouse button

RightButton

right mouse button

WheelUp

mouse wheel upward

WheelDown

mouse wheel downward

IndexButton Int

button specified by an index

LetterButton Char

button specified by a letter

Instances

Eq Button Source # 

Methods

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

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

Ord Button Source # 
Read Button Source # 
Show Button Source # 
Generic Button Source # 

Associated Types

type Rep Button :: * -> * #

Methods

from :: Button -> Rep Button x #

to :: Rep Button x -> Button #

ToJSON Button Source # 
FromJSON Button Source # 
Binary Button Source # 

Methods

put :: Button -> Put #

get :: Get Button #

putList :: [Button] -> Put #

Serialize Button Source # 
type Rep Button Source # 
type Rep Button = D1 * (MetaData "Button" "Network.UI.Kafka.Types" "kafka-device-1.0.0.0-7U9qgkxLORxLpEJz1lnLpE" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LeftButton" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MiddleButton" PrefixI False) (U1 *)) (C1 * (MetaCons "RightButton" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "WheelUp" PrefixI False) (U1 *)) (C1 * (MetaCons "WheelDown" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "IndexButton" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "LetterButton" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Char))))))

type ButtonState = (Button, Toggle) Source #

A button and its state.

data Hand Source #

A hand.

Constructors

RightHand

right hand

LeftHand

left hand

Instances

Bounded Hand Source # 
Enum Hand Source # 

Methods

succ :: Hand -> Hand #

pred :: Hand -> Hand #

toEnum :: Int -> Hand #

fromEnum :: Hand -> Int #

enumFrom :: Hand -> [Hand] #

enumFromThen :: Hand -> Hand -> [Hand] #

enumFromTo :: Hand -> Hand -> [Hand] #

enumFromThenTo :: Hand -> Hand -> Hand -> [Hand] #

Eq Hand Source # 

Methods

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

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

Ord Hand Source # 

Methods

compare :: Hand -> Hand -> Ordering #

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

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

(>) :: Hand -> Hand -> Bool #

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

max :: Hand -> Hand -> Hand #

min :: Hand -> Hand -> Hand #

Read Hand Source # 
Show Hand Source # 

Methods

showsPrec :: Int -> Hand -> ShowS #

show :: Hand -> String #

showList :: [Hand] -> ShowS #

Generic Hand Source # 

Associated Types

type Rep Hand :: * -> * #

Methods

from :: Hand -> Rep Hand x #

to :: Rep Hand x -> Hand #

ToJSON Hand Source # 
FromJSON Hand Source # 
Binary Hand Source # 

Methods

put :: Hand -> Put #

get :: Get Hand #

putList :: [Hand] -> Put #

Serialize Hand Source # 

Methods

put :: Putter Hand #

get :: Get Hand #

type Rep Hand Source # 
type Rep Hand = D1 * (MetaData "Hand" "Network.UI.Kafka.Types" "kafka-device-1.0.0.0-7U9qgkxLORxLpEJz1lnLpE" False) ((:+:) * (C1 * (MetaCons "RightHand" PrefixI False) (U1 *)) (C1 * (MetaCons "LeftHand" PrefixI False) (U1 *)))

data Finger Source #

A finger.

Constructors

Thumb

thumb

IndexFinger

first or index finger

MiddleFinger

second or middle finger

RingFinger

third of ring finger

Pinky

fourth finger or pinky

Instances

Bounded Finger Source # 
Enum Finger Source # 
Eq Finger Source # 

Methods

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

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

Ord Finger Source # 
Read Finger Source # 
Show Finger Source # 
Generic Finger Source # 

Associated Types

type Rep Finger :: * -> * #

Methods

from :: Finger -> Rep Finger x #

to :: Rep Finger x -> Finger #

ToJSON Finger Source # 
FromJSON Finger Source # 
Binary Finger Source # 

Methods

put :: Finger -> Put #

get :: Get Finger #

putList :: [Finger] -> Put #

Serialize Finger Source # 
type Rep Finger Source # 
type Rep Finger = D1 * (MetaData "Finger" "Network.UI.Kafka.Types" "kafka-device-1.0.0.0-7U9qgkxLORxLpEJz1lnLpE" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Thumb" PrefixI False) (U1 *)) (C1 * (MetaCons "IndexFinger" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MiddleFinger" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "RingFinger" PrefixI False) (U1 *)) (C1 * (MetaCons "Pinky" PrefixI False) (U1 *)))))