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

Copyright(c) 2016-19 Brian W Bush
LicenseMIT
MaintainerBrian W Bush <code@functionally.io>
StabilityProduction
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 # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

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

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

Ord Event Source # 
Instance details

Defined in Network.UI.Kafka.Types

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 # 
Instance details

Defined in Network.UI.Kafka.Types

Show Event Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in Network.UI.Kafka.Types

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

ToJSON Event Source # 
Instance details

Defined in Network.UI.Kafka.Types

FromJSON Event Source # 
Instance details

Defined in Network.UI.Kafka.Types

Binary Event Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

put :: Event -> Put #

get :: Get Event #

putList :: [Event] -> Put #

Serialize Event Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

put :: Putter Event #

get :: Get Event #

type Rep Event Source # 
Instance details

Defined in Network.UI.Kafka.Types

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

Defined in Network.UI.Kafka.Types

Ord SpecialKey Source # 
Instance details

Defined in Network.UI.Kafka.Types

Read SpecialKey Source # 
Instance details

Defined in Network.UI.Kafka.Types

Show SpecialKey Source # 
Instance details

Defined in Network.UI.Kafka.Types

Generic SpecialKey Source # 
Instance details

Defined in Network.UI.Kafka.Types

Associated Types

type Rep SpecialKey :: Type -> Type #

ToJSON SpecialKey Source # 
Instance details

Defined in Network.UI.Kafka.Types

FromJSON SpecialKey Source # 
Instance details

Defined in Network.UI.Kafka.Types

Binary SpecialKey Source # 
Instance details

Defined in Network.UI.Kafka.Types

Serialize SpecialKey Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep SpecialKey Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep SpecialKey = D1 (MetaData "SpecialKey" "Network.UI.Kafka.Types" "kafka-device-1.0.2.1-7kJVqFIu9rZFmREYnQHF34" False) ((((C1 (MetaCons "KeyF1" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "KeyF2" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyF3" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "KeyF4" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyF5" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "KeyF6" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyF7" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "KeyF8" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyF9" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "KeyF10" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyF11" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "KeyF12" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyLeft" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "KeyUp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyRight" PrefixI False) (U1 :: Type -> Type))))) :+: ((((C1 (MetaCons "KeyDown" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyPageUp" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "KeyPageDown" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyHome" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "KeyEnd" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyInsert" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "KeyNumLock" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyBegin" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "KeyDelete" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyShiftL" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "KeyShiftR" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyCtrlL" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "KeyCtrlR" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyAltL" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "KeyAltR" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyUnknown" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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 # 
Instance details

Defined in Network.UI.Kafka.Types

Enum Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

Eq Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

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

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

Ord Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

Read Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

Show Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

Generic Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

Associated Types

type Rep Toggle :: Type -> Type #

Methods

from :: Toggle -> Rep Toggle x #

to :: Rep Toggle x -> Toggle #

ToJSON Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

FromJSON Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

Binary Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

put :: Toggle -> Put #

get :: Get Toggle #

putList :: [Toggle] -> Put #

Serialize Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep Toggle Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep Toggle = D1 (MetaData "Toggle" "Network.UI.Kafka.Types" "kafka-device-1.0.2.1-7kJVqFIu9rZFmREYnQHF34" False) (C1 (MetaCons "Down" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Up" PrefixI False) (U1 :: Type -> Type))

data Modifiers Source #

Keyboard modifiers.

Constructors

Modifiers 

Fields

Instances
Eq Modifiers Source # 
Instance details

Defined in Network.UI.Kafka.Types

Ord Modifiers Source # 
Instance details

Defined in Network.UI.Kafka.Types

Read Modifiers Source # 
Instance details

Defined in Network.UI.Kafka.Types

Show Modifiers Source # 
Instance details

Defined in Network.UI.Kafka.Types

Generic Modifiers Source # 
Instance details

Defined in Network.UI.Kafka.Types

Associated Types

type Rep Modifiers :: Type -> Type #

ToJSON Modifiers Source # 
Instance details

Defined in Network.UI.Kafka.Types

FromJSON Modifiers Source # 
Instance details

Defined in Network.UI.Kafka.Types

Binary Modifiers Source # 
Instance details

Defined in Network.UI.Kafka.Types

Serialize Modifiers Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep Modifiers Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep Modifiers = D1 (MetaData "Modifiers" "Network.UI.Kafka.Types" "kafka-device-1.0.2.1-7kJVqFIu9rZFmREYnQHF34" False) (C1 (MetaCons "Modifiers" PrefixI True) (S1 (MetaSel (Just "shiftModifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: (S1 (MetaSel (Just "ctrlModifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

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

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

Ord Button Source # 
Instance details

Defined in Network.UI.Kafka.Types

Read Button Source # 
Instance details

Defined in Network.UI.Kafka.Types

Show Button Source # 
Instance details

Defined in Network.UI.Kafka.Types

Generic Button Source # 
Instance details

Defined in Network.UI.Kafka.Types

Associated Types

type Rep Button :: Type -> Type #

Methods

from :: Button -> Rep Button x #

to :: Rep Button x -> Button #

ToJSON Button Source # 
Instance details

Defined in Network.UI.Kafka.Types

FromJSON Button Source # 
Instance details

Defined in Network.UI.Kafka.Types

Binary Button Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

put :: Button -> Put #

get :: Get Button #

putList :: [Button] -> Put #

Serialize Button Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep Button Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep Button = D1 (MetaData "Button" "Network.UI.Kafka.Types" "kafka-device-1.0.2.1-7kJVqFIu9rZFmREYnQHF34" False) ((C1 (MetaCons "LeftButton" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MiddleButton" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RightButton" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "WheelUp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WheelDown" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "IndexButton" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "LetterButton" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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 # 
Instance details

Defined in Network.UI.Kafka.Types

Enum Hand Source # 
Instance details

Defined in Network.UI.Kafka.Types

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 # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

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

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

Ord Hand Source # 
Instance details

Defined in Network.UI.Kafka.Types

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 # 
Instance details

Defined in Network.UI.Kafka.Types

Show Hand Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

showsPrec :: Int -> Hand -> ShowS #

show :: Hand -> String #

showList :: [Hand] -> ShowS #

Generic Hand Source # 
Instance details

Defined in Network.UI.Kafka.Types

Associated Types

type Rep Hand :: Type -> Type #

Methods

from :: Hand -> Rep Hand x #

to :: Rep Hand x -> Hand #

ToJSON Hand Source # 
Instance details

Defined in Network.UI.Kafka.Types

FromJSON Hand Source # 
Instance details

Defined in Network.UI.Kafka.Types

Binary Hand Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

put :: Hand -> Put #

get :: Get Hand #

putList :: [Hand] -> Put #

Serialize Hand Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

put :: Putter Hand #

get :: Get Hand #

type Rep Hand Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep Hand = D1 (MetaData "Hand" "Network.UI.Kafka.Types" "kafka-device-1.0.2.1-7kJVqFIu9rZFmREYnQHF34" False) (C1 (MetaCons "RightHand" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LeftHand" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Network.UI.Kafka.Types

Enum Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

Eq Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

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

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

Ord Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

Read Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

Show Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

Generic Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

Associated Types

type Rep Finger :: Type -> Type #

Methods

from :: Finger -> Rep Finger x #

to :: Rep Finger x -> Finger #

ToJSON Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

FromJSON Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

Binary Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

Methods

put :: Finger -> Put #

get :: Get Finger #

putList :: [Finger] -> Put #

Serialize Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep Finger Source # 
Instance details

Defined in Network.UI.Kafka.Types

type Rep Finger = D1 (MetaData "Finger" "Network.UI.Kafka.Types" "kafka-device-1.0.2.1-7kJVqFIu9rZFmREYnQHF34" False) ((C1 (MetaCons "Thumb" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IndexFinger" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MiddleFinger" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RingFinger" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Pinky" PrefixI False) (U1 :: Type -> Type))))