-- GENERATED by C->Haskell Compiler, version 0.28.6 Switcheroo, 25 November 2017 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Evdev/Codes.chs" #-}
{-
TODO haddock doesn't quite work correctly with LINE pragmas
    https://github.com/haskell/haddock/issues/441
    for now we can work around this by deleting the pragmas before upload to hackage

seems to be on its way to being fixed with `.hie` files (enable `-fwrite-ide-info`)
    https://github.com/haskell/haddock/commit/8bc3c2990475a254e168fbdb005af93f9397b19c
-}

-- | Datatypes corresponding to the constants in [input-event-codes.h](https://github.com/torvalds/linux/blob/master/include/uapi/linux/input-event-codes.h).
-- See [the Linux Kernel documentation](https://www.kernel.org/doc/html/latest/input/event-codes.html) for full details, noting that all names have been mechanically transformed into CamelCase.
module Evdev.Codes where





-- | Each of these corresponds to one of the contructors of 'Evdev.EventData'. So you're unlikely to need to use these directly (C doesn't have ADTs - we do).
data EventType = EvSyn
               | EvKey
               | EvRel
               | EvAbs
               | EvMsc
               | EvSw
               | EvLed
               | EvSnd
               | EvRep
               | EvFf
               | EvPwr
               | EvFfStatus
  deriving (EventType
forall a. a -> a -> Bounded a
maxBound :: EventType
$cmaxBound :: EventType
minBound :: EventType
$cminBound :: EventType
Bounded,EventType -> EventType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventType -> EventType -> Bool
$c/= :: EventType -> EventType -> Bool
== :: EventType -> EventType -> Bool
$c== :: EventType -> EventType -> Bool
Eq,Eq EventType
EventType -> EventType -> Bool
EventType -> EventType -> Ordering
EventType -> EventType -> EventType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EventType -> EventType -> EventType
$cmin :: EventType -> EventType -> EventType
max :: EventType -> EventType -> EventType
$cmax :: EventType -> EventType -> EventType
>= :: EventType -> EventType -> Bool
$c>= :: EventType -> EventType -> Bool
> :: EventType -> EventType -> Bool
$c> :: EventType -> EventType -> Bool
<= :: EventType -> EventType -> Bool
$c<= :: EventType -> EventType -> Bool
< :: EventType -> EventType -> Bool
$c< :: EventType -> EventType -> Bool
compare :: EventType -> EventType -> Ordering
$ccompare :: EventType -> EventType -> Ordering
Ord,ReadPrec [EventType]
ReadPrec EventType
Int -> ReadS EventType
ReadS [EventType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EventType]
$creadListPrec :: ReadPrec [EventType]
readPrec :: ReadPrec EventType
$creadPrec :: ReadPrec EventType
readList :: ReadS [EventType]
$creadList :: ReadS [EventType]
readsPrec :: Int -> ReadS EventType
$creadsPrec :: Int -> ReadS EventType
Read,Int -> EventType -> ShowS
[EventType] -> ShowS
EventType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventType] -> ShowS
$cshowList :: [EventType] -> ShowS
show :: EventType -> String
$cshow :: EventType -> String
showsPrec :: Int -> EventType -> ShowS
$cshowsPrec :: Int -> EventType -> ShowS
Show)
instance Enum EventType where
  succ EvSyn = EvKey
  succ EvKey = EvRel
  succ EvRel = EvAbs
  succ EvAbs = EvMsc
  succ EvMsc = EvSw
  succ EvSw = EvLed
  succ EvLed = EvSnd
  succ EvSnd = EvRep
  succ EvRep = EvFf
  succ EvFf = EvPwr
  succ EvPwr = EvFfStatus
  succ EvFfStatus = error "EventType.succ: EvFfStatus has no successor"

  pred :: EventType -> EventType
pred EventType
EvKey = EventType
EvSyn
  pred EventType
EvRel = EventType
EvKey
  pred EventType
EvAbs = EventType
EvRel
  pred EventType
EvMsc = EventType
EvAbs
  pred EvSw = EvMsc
  pred EvLed = EvSw
  pred EvSnd = EvLed
  pred EvRep = EvSnd
  pred EvFf = EvRep
  pred EvPwr = EvFf
  pred EventType
EvFfStatus = EventType
EvPwr
  pred EvSyn = error String
"EventType.pred: EvSyn has no predecessor"

  enumFromTo :: EventType -> EventType -> [EventType]
enumFromTo EventType
from EventType
to = go from
    where
      end = fromEnum to
      go v = case compare (forall a. Enum a => a -> Int
fromEnum EventType
v) Int
end of
                 Ordering
LT -> EventType
v forall a. a -> [a] -> [a]
: EventType -> [EventType]
go (forall a. Enum a => a -> a
succ EventType
v)
                 Ordering
EQ -> [EventType
v]
                 Ordering
GT -> []

  enumFrom :: EventType -> [EventType]
enumFrom EventType
from = forall a. Enum a => a -> a -> [a]
enumFromTo EventType
from EventType
EvFfStatus

  fromEnum :: EventType -> Int
fromEnum EventType
EvSyn = Int
0
  fromEnum EventType
EvKey = Int
1
  fromEnum EventType
EvRel = Int
2
  fromEnum EventType
EvAbs = Int
3
  fromEnum EventType
EvMsc = Int
4
  fromEnum EventType
EvSw = Int
5
  fromEnum EventType
EvLed = Int
17
  fromEnum EventType
EvSnd = Int
18
  fromEnum EventType
EvRep = Int
20
  fromEnum EventType
EvFf = Int
21
  fromEnum EventType
EvPwr = Int
22
  fromEnum EventType
EvFfStatus = Int
23

  toEnum :: Int -> EventType
toEnum Int
0 = EventType
EvSyn
  toEnum Int
1 = EventType
EvKey
  toEnum Int
2 = EventType
EvRel
  toEnum Int
3 = EventType
EvAbs
  toEnum Int
4 = EventType
EvMsc
  toEnum Int
5 = EventType
EvSw
  toEnum Int
17 = EventType
EvLed
  toEnum Int
18 = EventType
EvSnd
  toEnum Int
20 = EventType
EvRep
  toEnum Int
21 = EventType
EvFf
  toEnum Int
22 = EventType
EvPwr
  toEnum Int
23 = EventType
EvFfStatus
  toEnum Int
unmatched = forall a. HasCallStack => String -> a
error (String
"EventType.toEnum: Cannot match " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
unmatched)

{-# LINE 30 "src/Evdev/Codes.chs" #-}


-- | Synchronization events
data SyncEvent = SynReport
               | SynConfig
               | SynMtReport
               | SynDropped
  deriving (Bounded,Eq,Ord,Read,Show)
instance Enum SyncEvent where
  succ SynReport = SynConfig
  succ SynConfig = SynMtReport
  succ SynMtReport = SynDropped
  succ SynDropped = error "SyncEvent.succ: SynDropped has no successor"

  pred SynConfig = SynReport
  pred SynMtReport = SynConfig
  pred SynDropped = SynMtReport
  pred SynReport = error "SyncEvent.pred: SynReport has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from SynDropped

  fromEnum SynReport = 0
  fromEnum SynConfig = 1
  fromEnum SynMtReport = 2
  fromEnum SynDropped = 3

  toEnum 0 = SynReport
  toEnum 1 = SynConfig
  toEnum 2 = SynMtReport
  toEnum 3 = SynDropped
  toEnum unmatched = error ("SyncEvent.toEnum: Cannot match " ++ show unmatched)

{-# LINE 38 "src/Evdev/Codes.chs" #-}


-- | Keys and buttons
data Key = KeyReserved
         | KeyEsc
         | Key1
         | Key2
         | Key3
         | Key4
         | Key5
         | Key6
         | Key7
         | Key8
         | Key9
         | Key0
         | KeyMinus
         | KeyEqual
         | KeyBackspace
         | KeyTab
         | KeyQ
         | KeyW
         | KeyE
         | KeyR
         | KeyT
         | KeyY
         | KeyU
         | KeyI
         | KeyO
         | KeyP
         | KeyLeftbrace
         | KeyRightbrace
         | KeyEnter
         | KeyLeftctrl
         | KeyA
         | KeyS
         | KeyD
         | KeyF
         | KeyG
         | KeyH
         | KeyJ
         | KeyK
         | KeyL
         | KeySemicolon
         | KeyApostrophe
         | KeyGrave
         | KeyLeftshift
         | KeyBackslash
         | KeyZ
         | KeyX
         | KeyC
         | KeyV
         | KeyB
         | KeyN
         | KeyM
         | KeyComma
         | KeyDot
         | KeySlash
         | KeyRightshift
         | KeyKpasterisk
         | KeyLeftalt
         | KeySpace
         | KeyCapslock
         | KeyF1
         | KeyF2
         | KeyF3
         | KeyF4
         | KeyF5
         | KeyF6
         | KeyF7
         | KeyF8
         | KeyF9
         | KeyF10
         | KeyNumlock
         | KeyScrolllock
         | KeyKp7
         | KeyKp8
         | KeyKp9
         | KeyKpminus
         | KeyKp4
         | KeyKp5
         | KeyKp6
         | KeyKpplus
         | KeyKp1
         | KeyKp2
         | KeyKp3
         | KeyKp0
         | KeyKpdot
         | KeyZenkakuhankaku
         | Key102nd
         | KeyF11
         | KeyF12
         | KeyRo
         | KeyKatakana
         | KeyHiragana
         | KeyHenkan
         | KeyKatakanahiragana
         | KeyMuhenkan
         | KeyKpjpcomma
         | KeyKpenter
         | KeyRightctrl
         | KeyKpslash
         | KeySysrq
         | KeyRightalt
         | KeyLinefeed
         | KeyHome
         | KeyUp
         | KeyPageup
         | KeyLeft
         | KeyRight
         | KeyEnd
         | KeyDown
         | KeyPagedown
         | KeyInsert
         | KeyDelete
         | KeyMacro
         | KeyMute
         | KeyVolumedown
         | KeyVolumeup
         | KeyPower
         | KeyKpequal
         | KeyKpplusminus
         | KeyPause
         | KeyScale
         | KeyKpcomma
         | KeyHangeul
         | KeyHanguel
         | KeyHanja
         | KeyYen
         | KeyLeftmeta
         | KeyRightmeta
         | KeyCompose
         | KeyStop
         | KeyAgain
         | KeyProps
         | KeyUndo
         | KeyFront
         | KeyCopy
         | KeyOpen
         | KeyPaste
         | KeyFind
         | KeyCut
         | KeyHelp
         | KeyMenu
         | KeyCalc
         | KeySetup
         | KeySleep
         | KeyWakeup
         | KeyFile
         | KeySendfile
         | KeyDeletefile
         | KeyXfer
         | KeyProg1
         | KeyProg2
         | KeyWww
         | KeyMsdos
         | KeyCoffee
         | KeyScreenlock
         | KeyRotateDisplay
         | KeyDirection
         | KeyCyclewindows
         | KeyMail
         | KeyBookmarks
         | KeyComputer
         | KeyBack
         | KeyForward
         | KeyClosecd
         | KeyEjectcd
         | KeyEjectclosecd
         | KeyNextsong
         | KeyPlaypause
         | KeyPrevioussong
         | KeyStopcd
         | KeyRecord
         | KeyRewind
         | KeyPhone
         | KeyIso
         | KeyConfig
         | KeyHomepage
         | KeyRefresh
         | KeyExit
         | KeyMove
         | KeyEdit
         | KeyScrollup
         | KeyScrolldown
         | KeyKpleftparen
         | KeyKprightparen
         | KeyNew
         | KeyRedo
         | KeyF13
         | KeyF14
         | KeyF15
         | KeyF16
         | KeyF17
         | KeyF18
         | KeyF19
         | KeyF20
         | KeyF21
         | KeyF22
         | KeyF23
         | KeyF24
         | KeyPlaycd
         | KeyPausecd
         | KeyProg3
         | KeyProg4
         | KeyDashboard
         | KeySuspend
         | KeyClose
         | KeyPlay
         | KeyFastforward
         | KeyBassboost
         | KeyPrint
         | KeyHp
         | KeyCamera
         | KeySound
         | KeyQuestion
         | KeyEmail
         | KeyChat
         | KeySearch
         | KeyConnect
         | KeyFinance
         | KeySport
         | KeyShop
         | KeyAlterase
         | KeyCancel
         | KeyBrightnessdown
         | KeyBrightnessup
         | KeyMedia
         | KeySwitchvideomode
         | KeyKbdillumtoggle
         | KeyKbdillumdown
         | KeyKbdillumup
         | KeySend
         | KeyReply
         | KeyForwardmail
         | KeySave
         | KeyDocuments
         | KeyBattery
         | KeyBluetooth
         | KeyWlan
         | KeyUwb
         | KeyUnknown
         | KeyVideoNext
         | KeyVideoPrev
         | KeyBrightnessCycle
         | KeyBrightnessAuto
         | KeyBrightnessZero
         | KeyDisplayOff
         | KeyWwan
         | KeyWimax
         | KeyRfkill
         | KeyMicmute
         | BtnMisc
         | Btn0
         | Btn1
         | Btn2
         | Btn3
         | Btn4
         | Btn5
         | Btn6
         | Btn7
         | Btn8
         | Btn9
         | BtnMouse
         | BtnLeft
         | BtnRight
         | BtnMiddle
         | BtnSide
         | BtnExtra
         | BtnForward
         | BtnBack
         | BtnTask
         | BtnJoystick
         | BtnTrigger
         | BtnThumb
         | BtnThumb2
         | BtnTop
         | BtnTop2
         | BtnPinkie
         | BtnBase
         | BtnBase2
         | BtnBase3
         | BtnBase4
         | BtnBase5
         | BtnBase6
         | BtnDead
         | BtnGamepad
         | BtnSouth
         | BtnA
         | BtnEast
         | BtnB
         | BtnC
         | BtnNorth
         | BtnX
         | BtnWest
         | BtnY
         | BtnZ
         | BtnTl
         | BtnTr
         | BtnTl2
         | BtnTr2
         | BtnSelect
         | BtnStart
         | BtnMode
         | BtnThumbl
         | BtnThumbr
         | BtnDigi
         | BtnToolPen
         | BtnToolRubber
         | BtnToolBrush
         | BtnToolPencil
         | BtnToolAirbrush
         | BtnToolFinger
         | BtnToolMouse
         | BtnToolLens
         | BtnToolQuinttap
         | BtnTouch
         | BtnStylus
         | BtnStylus2
         | BtnToolDoubletap
         | BtnToolTripletap
         | BtnToolQuadtap
         | BtnWheel
         | BtnGearDown
         | BtnGearUp
         | KeyOk
         | KeySelect
         | KeyGoto
         | KeyClear
         | KeyPower2
         | KeyOption
         | KeyInfo
         | KeyTime
         | KeyVendor
         | KeyArchive
         | KeyProgram
         | KeyChannel
         | KeyFavorites
         | KeyEpg
         | KeyPvr
         | KeyMhp
         | KeyLanguage
         | KeyTitle
         | KeySubtitle
         | KeyAngle
         | KeyZoom
         | KeyMode
         | KeyKeyboard
         | KeyScreen
         | KeyPc
         | KeyTv
         | KeyTv2
         | KeyVcr
         | KeyVcr2
         | KeySat
         | KeySat2
         | KeyCd
         | KeyTape
         | KeyRadio
         | KeyTuner
         | KeyPlayer
         | KeyText
         | KeyDvd
         | KeyAux
         | KeyMp3
         | KeyAudio
         | KeyVideo
         | KeyDirectory
         | KeyList
         | KeyMemo
         | KeyCalendar
         | KeyRed
         | KeyGreen
         | KeyYellow
         | KeyBlue
         | KeyChannelup
         | KeyChanneldown
         | KeyFirst
         | KeyLast
         | KeyAb
         | KeyNext
         | KeyRestart
         | KeySlow
         | KeyShuffle
         | KeyBreak
         | KeyPrevious
         | KeyDigits
         | KeyTeen
         | KeyTwen
         | KeyVideophone
         | KeyGames
         | KeyZoomin
         | KeyZoomout
         | KeyZoomreset
         | KeyWordprocessor
         | KeyEditor
         | KeySpreadsheet
         | KeyGraphicseditor
         | KeyPresentation
         | KeyDatabase
         | KeyNews
         | KeyVoicemail
         | KeyAddressbook
         | KeyMessenger
         | KeyDisplaytoggle
         | KeyBrightnessToggle
         | KeySpellcheck
         | KeyLogoff
         | KeyDollar
         | KeyEuro
         | KeyFrameback
         | KeyFrameforward
         | KeyContextMenu
         | KeyMediaRepeat
         | Key10channelsup
         | Key10channelsdown
         | KeyImages
         | KeyDelEol
         | KeyDelEos
         | KeyInsLine
         | KeyDelLine
         | KeyFn
         | KeyFnEsc
         | KeyFnF1
         | KeyFnF2
         | KeyFnF3
         | KeyFnF4
         | KeyFnF5
         | KeyFnF6
         | KeyFnF7
         | KeyFnF8
         | KeyFnF9
         | KeyFnF10
         | KeyFnF11
         | KeyFnF12
         | KeyFn1
         | KeyFn2
         | KeyFnD
         | KeyFnE
         | KeyFnF
         | KeyFnS
         | KeyFnB
         | KeyBrlDot1
         | KeyBrlDot2
         | KeyBrlDot3
         | KeyBrlDot4
         | KeyBrlDot5
         | KeyBrlDot6
         | KeyBrlDot7
         | KeyBrlDot8
         | KeyBrlDot9
         | KeyBrlDot10
         | KeyNumeric0
         | KeyNumeric1
         | KeyNumeric2
         | KeyNumeric3
         | KeyNumeric4
         | KeyNumeric5
         | KeyNumeric6
         | KeyNumeric7
         | KeyNumeric8
         | KeyNumeric9
         | KeyNumericStar
         | KeyNumericPound
         | KeyNumericA
         | KeyNumericB
         | KeyNumericC
         | KeyNumericD
         | KeyCameraFocus
         | KeyWpsButton
         | KeyTouchpadToggle
         | KeyTouchpadOn
         | KeyTouchpadOff
         | KeyCameraZoomin
         | KeyCameraZoomout
         | KeyCameraUp
         | KeyCameraDown
         | KeyCameraLeft
         | KeyCameraRight
         | KeyAttendantOn
         | KeyAttendantOff
         | KeyAttendantToggle
         | KeyLightsToggle
         | BtnDpadUp
         | BtnDpadDown
         | BtnDpadLeft
         | BtnDpadRight
         | KeyAlsToggle
         | KeyButtonconfig
         | KeyTaskmanager
         | KeyJournal
         | KeyControlpanel
         | KeyAppselect
         | KeyScreensaver
         | KeyVoicecommand
         | KeyBrightnessMin
         | KeyBrightnessMax
         | KeyKbdinputassistPrev
         | KeyKbdinputassistNext
         | KeyKbdinputassistPrevgroup
         | KeyKbdinputassistNextgroup
         | KeyKbdinputassistAccept
         | KeyKbdinputassistCancel
         | BtnTriggerHappy
         | BtnTriggerHappy1
         | BtnTriggerHappy2
         | BtnTriggerHappy3
         | BtnTriggerHappy4
         | BtnTriggerHappy5
         | BtnTriggerHappy6
         | BtnTriggerHappy7
         | BtnTriggerHappy8
         | BtnTriggerHappy9
         | BtnTriggerHappy10
         | BtnTriggerHappy11
         | BtnTriggerHappy12
         | BtnTriggerHappy13
         | BtnTriggerHappy14
         | BtnTriggerHappy15
         | BtnTriggerHappy16
         | BtnTriggerHappy17
         | BtnTriggerHappy18
         | BtnTriggerHappy19
         | BtnTriggerHappy20
         | BtnTriggerHappy21
         | BtnTriggerHappy22
         | BtnTriggerHappy23
         | BtnTriggerHappy24
         | BtnTriggerHappy25
         | BtnTriggerHappy26
         | BtnTriggerHappy27
         | BtnTriggerHappy28
         | BtnTriggerHappy29
         | BtnTriggerHappy30
         | BtnTriggerHappy31
         | BtnTriggerHappy32
         | BtnTriggerHappy33
         | BtnTriggerHappy34
         | BtnTriggerHappy35
         | BtnTriggerHappy36
         | BtnTriggerHappy37
         | BtnTriggerHappy38
         | BtnTriggerHappy39
         | BtnTriggerHappy40
  deriving (Key
forall a. a -> a -> Bounded a
maxBound :: Key
$cmaxBound :: Key
minBound :: Key
$cminBound :: Key
Bounded,Key -> Key -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c== :: Key -> Key -> Bool
Eq,Eq Key
Key -> Key -> Bool
Key -> Key -> Ordering
Key -> Key -> Key
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Key -> Key -> Key
$cmin :: Key -> Key -> Key
max :: Key -> Key -> Key
$cmax :: Key -> Key -> Key
>= :: Key -> Key -> Bool
$c>= :: Key -> Key -> Bool
> :: Key -> Key -> Bool
$c> :: Key -> Key -> Bool
<= :: Key -> Key -> Bool
$c<= :: Key -> Key -> Bool
< :: Key -> Key -> Bool
$c< :: Key -> Key -> Bool
compare :: Key -> Key -> Ordering
$ccompare :: Key -> Key -> Ordering
Ord,ReadPrec [Key]
ReadPrec Key
Int -> ReadS Key
ReadS [Key]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Key]
$creadListPrec :: ReadPrec [Key]
readPrec :: ReadPrec Key
$creadPrec :: ReadPrec Key
readList :: ReadS [Key]
$creadList :: ReadS [Key]
readsPrec :: Int -> ReadS Key
$creadsPrec :: Int -> ReadS Key
Read,Int -> Key -> ShowS
[Key] -> ShowS
Key -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Key] -> ShowS
$cshowList :: [Key] -> ShowS
show :: Key -> String
$cshow :: Key -> String
showsPrec :: Int -> Key -> ShowS
$cshowsPrec :: Int -> Key -> ShowS
Show)
instance Enum Key where
  succ :: Key -> Key
succ Key
KeyReserved = Key
KeyEsc
  succ Key
KeyEsc = Key
Key1
  succ Key1 = Key2
  succ Key2 = Key3
  succ Key3 = Key4
  succ Key4 = Key5
  succ Key5 = Key6
  succ Key6 = Key7
  succ Key7 = Key8
  succ Key8 = Key9
  succ Key9 = Key0
  succ Key0 = KeyMinus
  succ KeyMinus = KeyEqual
  succ KeyEqual = KeyBackspace
  succ KeyBackspace = KeyTab
  succ KeyTab = KeyQ
  succ KeyQ = KeyW
  succ KeyW = KeyE
  succ KeyE = KeyR
  succ KeyR = KeyT
  succ KeyT = KeyY
  succ KeyY = KeyU
  succ KeyU = KeyI
  succ KeyI = KeyO
  succ KeyO = KeyP
  succ KeyP = KeyLeftbrace
  succ KeyLeftbrace = KeyRightbrace
  succ KeyRightbrace = KeyEnter
  succ KeyEnter = KeyLeftctrl
  succ KeyLeftctrl = KeyA
  succ KeyA = KeyS
  succ KeyS = KeyD
  succ KeyD = KeyF
  succ KeyF = KeyG
  succ KeyG = KeyH
  succ KeyH = KeyJ
  succ KeyJ = KeyK
  succ KeyK = KeyL
  succ KeyL = KeySemicolon
  succ KeySemicolon = KeyApostrophe
  succ KeyApostrophe = KeyGrave
  succ KeyGrave = KeyLeftshift
  succ KeyLeftshift = KeyBackslash
  succ KeyBackslash = KeyZ
  succ KeyZ = KeyX
  succ KeyX = KeyC
  succ KeyC = KeyV
  succ KeyV = KeyB
  succ KeyB = KeyN
  succ KeyN = KeyM
  succ KeyM = KeyComma
  succ KeyComma = KeyDot
  succ KeyDot = KeySlash
  succ KeySlash = KeyRightshift
  succ KeyRightshift = KeyKpasterisk
  succ KeyKpasterisk = KeyLeftalt
  succ KeyLeftalt = KeySpace
  succ KeySpace = KeyCapslock
  succ KeyCapslock = KeyF1
  succ KeyF1 = KeyF2
  succ KeyF2 = KeyF3
  succ KeyF3 = KeyF4
  succ KeyF4 = KeyF5
  succ KeyF5 = KeyF6
  succ KeyF6 = KeyF7
  succ KeyF7 = KeyF8
  succ KeyF8 = KeyF9
  succ KeyF9 = KeyF10
  succ KeyF10 = KeyNumlock
  succ KeyNumlock = KeyScrolllock
  succ KeyScrolllock = KeyKp7
  succ KeyKp7 = KeyKp8
  succ KeyKp8 = KeyKp9
  succ KeyKp9 = KeyKpminus
  succ KeyKpminus = KeyKp4
  succ KeyKp4 = KeyKp5
  succ KeyKp5 = KeyKp6
  succ KeyKp6 = KeyKpplus
  succ KeyKpplus = KeyKp1
  succ KeyKp1 = KeyKp2
  succ KeyKp2 = KeyKp3
  succ KeyKp3 = KeyKp0
  succ KeyKp0 = KeyKpdot
  succ Key
KeyKpdot = Key
KeyZenkakuhankaku
  succ Key
KeyZenkakuhankaku = Key
Key102nd
  succ Key
Key102nd = Key
KeyF11
  succ Key
KeyF11 = Key
KeyF12
  succ Key
KeyF12 = Key
KeyRo
  succ Key
KeyRo = Key
KeyKatakana
  succ Key
KeyKatakana = Key
KeyHiragana
  succ Key
KeyHiragana = Key
KeyHenkan
  succ Key
KeyHenkan = Key
KeyKatakanahiragana
  succ Key
KeyKatakanahiragana = Key
KeyMuhenkan
  succ Key
KeyMuhenkan = Key
KeyKpjpcomma
  succ Key
KeyKpjpcomma = Key
KeyKpenter
  succ Key
KeyKpenter = Key
KeyRightctrl
  succ Key
KeyRightctrl = Key
KeyKpslash
  succ Key
KeyKpslash = Key
KeySysrq
  succ KeySysrq = KeyRightalt
  succ KeyRightalt = KeyLinefeed
  succ KeyLinefeed = KeyHome
  succ KeyHome = KeyUp
  succ KeyUp = KeyPageup
  succ KeyPageup = KeyLeft
  succ KeyLeft = KeyRight
  succ KeyRight = KeyEnd
  succ KeyEnd = KeyDown
  succ KeyDown = KeyPagedown
  succ KeyPagedown = KeyInsert
  succ KeyInsert = KeyDelete
  succ KeyDelete = KeyMacro
  succ KeyMacro = KeyMute
  succ KeyMute = KeyVolumedown
  succ KeyVolumedown = KeyVolumeup
  succ KeyVolumeup = KeyPower
  succ KeyPower = KeyKpequal
  succ KeyKpequal = KeyKpplusminus
  succ KeyKpplusminus = KeyPause
  succ KeyPause = KeyScale
  succ KeyScale = KeyKpcomma
  succ KeyKpcomma = KeyHangeul
  succ KeyHangeul = KeyHanja
  succ KeyHanguel = KeyHanja
  succ KeyHanja = KeyYen
  succ KeyYen = KeyLeftmeta
  succ KeyLeftmeta = KeyRightmeta
  succ KeyRightmeta = KeyCompose
  succ KeyCompose = KeyStop
  succ KeyStop = KeyAgain
  succ KeyAgain = KeyProps
  succ KeyProps = KeyUndo
  succ KeyUndo = KeyFront
  succ KeyFront = KeyCopy
  succ KeyCopy = KeyOpen
  succ KeyOpen = KeyPaste
  succ KeyPaste = KeyFind
  succ KeyFind = KeyCut
  succ KeyCut = KeyHelp
  succ KeyHelp = KeyMenu
  succ KeyMenu = KeyCalc
  succ KeyCalc = KeySetup
  succ KeySetup = KeySleep
  succ KeySleep = KeyWakeup
  succ KeyWakeup = KeyFile
  succ KeyFile = KeySendfile
  succ KeySendfile = KeyDeletefile
  succ KeyDeletefile = KeyXfer
  succ KeyXfer = KeyProg1
  succ KeyProg1 = KeyProg2
  succ KeyProg2 = KeyWww
  succ KeyWww = KeyMsdos
  succ KeyMsdos = KeyCoffee
  succ KeyCoffee = KeyRotateDisplay
  succ KeyScreenlock = KeyRotateDisplay
  succ KeyRotateDisplay = KeyCyclewindows
  succ KeyDirection = KeyCyclewindows
  succ KeyCyclewindows = KeyMail
  succ KeyMail = KeyBookmarks
  succ KeyBookmarks = KeyComputer
  succ KeyComputer = KeyBack
  succ KeyBack = KeyForward
  succ KeyForward = KeyClosecd
  succ KeyClosecd = KeyEjectcd
  succ KeyEjectcd = KeyEjectclosecd
  succ KeyEjectclosecd = KeyNextsong
  succ KeyNextsong = KeyPlaypause
  succ KeyPlaypause = KeyPrevioussong
  succ KeyPrevioussong = KeyStopcd
  succ KeyStopcd = KeyRecord
  succ KeyRecord = KeyRewind
  succ KeyRewind = KeyPhone
  succ KeyPhone = KeyIso
  succ KeyIso = KeyConfig
  succ KeyConfig = KeyHomepage
  succ KeyHomepage = KeyRefresh
  succ KeyRefresh = KeyExit
  succ KeyExit = KeyMove
  succ KeyMove = KeyEdit
  succ KeyEdit = KeyScrollup
  succ KeyScrollup = KeyScrolldown
  succ KeyScrolldown = KeyKpleftparen
  succ KeyKpleftparen = KeyKprightparen
  succ KeyKprightparen = KeyNew
  succ KeyNew = KeyRedo
  succ KeyRedo = KeyF13
  succ KeyF13 = KeyF14
  succ KeyF14 = KeyF15
  succ KeyF15 = KeyF16
  succ KeyF16 = KeyF17
  succ KeyF17 = KeyF18
  succ KeyF18 = KeyF19
  succ KeyF19 = KeyF20
  succ KeyF20 = KeyF21
  succ KeyF21 = KeyF22
  succ KeyF22 = KeyF23
  succ KeyF23 = KeyF24
  succ KeyF24 = KeyPlaycd
  succ KeyPlaycd = KeyPausecd
  succ KeyPausecd = KeyProg3
  succ KeyProg3 = KeyProg4
  succ KeyProg4 = KeyDashboard
  succ KeyDashboard = KeySuspend
  succ KeySuspend = KeyClose
  succ KeyClose = KeyPlay
  succ KeyPlay = KeyFastforward
  succ KeyFastforward = KeyBassboost
  succ KeyBassboost = KeyPrint
  succ KeyPrint = KeyHp
  succ KeyHp = KeyCamera
  succ KeyCamera = KeySound
  succ KeySound = KeyQuestion
  succ KeyQuestion = KeyEmail
  succ KeyEmail = KeyChat
  succ KeyChat = KeySearch
  succ KeySearch = KeyConnect
  succ KeyConnect = KeyFinance
  succ KeyFinance = KeySport
  succ Key
KeySport = Key
KeyShop
  succ KeyShop = Key
KeyAlterase
  succ Key
KeyAlterase = Key
KeyCancel
  succ KeyCancel = Key
KeyBrightnessdown
  succ Key
KeyBrightnessdown = Key
KeyBrightnessup
  succ Key
KeyBrightnessup = Key
KeyMedia
  succ KeyMedia = Key
KeySwitchvideomode
  succ Key
KeySwitchvideomode = Key
KeyKbdillumtoggle
  succ Key
KeyKbdillumtoggle = Key
KeyKbdillumdown
  succ Key
KeyKbdillumdown = Key
KeyKbdillumup
  succ Key
KeyKbdillumup = Key
KeySend
  succ KeySend = Key
KeyReply
  succ KeyReply = Key
KeyForwardmail
  succ KeyForwardmail = Key
KeySave
  succ KeySave = Key
KeyDocuments
  succ KeyDocuments = Key
KeyBattery
  succ KeyBattery = Key
KeyBluetooth
  succ KeyBluetooth = Key
KeyWlan
  succ KeyWlan = Key
KeyUwb
  succ KeyUwb = Key
KeyUnknown
  succ KeyUnknown = Key
KeyVideoNext
  succ KeyVideoNext = Key
KeyVideoPrev
  succ KeyVideoPrev = Key
KeyBrightnessCycle
  succ Key
KeyBrightnessCycle = Key
KeyBrightnessAuto
  succ KeyBrightnessAuto = Key
KeyDisplayOff
  succ Key
KeyBrightnessZero = Key
KeyDisplayOff
  succ KeyDisplayOff = Key
KeyWwan
  succ KeyWwan = Key
KeyRfkill
  succ KeyWimax = Key
KeyRfkill
  succ KeyRfkill = KeyMicmute
  succ KeyMicmute = Key
BtnMisc
  succ BtnMisc = Key
Btn1
  succ Btn0 = Key
Btn1
  succ Btn1 = Key
Btn2
  succ Btn2 = Key
Btn3
  succ Btn3 = Key
Btn4
  succ Btn4 = Key
Btn5
  succ Btn5 = Key
Btn6
  succ Btn6 = Key
Btn7
  succ Btn7 = Key
Btn8
  succ Btn8 = Key
Btn9
  succ Btn9 = Key
BtnMouse
  succ BtnMouse = Key
BtnRight
  succ BtnLeft = Key
BtnRight
  succ Key
BtnRight = Key
BtnMiddle
  succ Key
BtnMiddle = Key
BtnSide
  succ Key
BtnSide = Key
BtnExtra
  succ Key
BtnExtra = Key
BtnForward
  succ Key
BtnForward = Key
BtnBack
  succ Key
BtnBack = Key
BtnTask
  succ Key
BtnTask = Key
BtnJoystick
  succ Key
BtnJoystick = Key
BtnThumb
  succ Key
BtnTrigger = Key
BtnThumb
  succ Key
BtnThumb = Key
BtnThumb2
  succ Key
BtnThumb2 = Key
BtnTop
  succ Key
BtnTop = Key
BtnTop2
  succ Key
BtnTop2 = Key
BtnPinkie
  succ Key
BtnPinkie = Key
BtnBase
  succ Key
BtnBase = Key
BtnBase2
  succ Key
BtnBase2 = Key
BtnBase3
  succ Key
BtnBase3 = Key
BtnBase4
  succ Key
BtnBase4 = Key
BtnBase5
  succ Key
BtnBase5 = Key
BtnBase6
  succ Key
BtnBase6 = Key
BtnDead
  succ Key
BtnDead = Key
BtnGamepad
  succ Key
BtnGamepad = Key
BtnEast
  succ Key
BtnSouth = Key
BtnEast
  succ Key
BtnA = Key
BtnEast
  succ Key
BtnEast = Key
BtnC
  succ Key
BtnB = Key
BtnC
  succ Key
BtnC = Key
BtnNorth
  succ Key
BtnNorth = Key
BtnWest
  succ Key
BtnX = Key
BtnWest
  succ Key
BtnWest = Key
BtnZ
  succ Key
BtnY = Key
BtnZ
  succ Key
BtnZ = Key
BtnTl
  succ Key
BtnTl = Key
BtnTr
  succ Key
BtnTr = Key
BtnTl2
  succ Key
BtnTl2 = Key
BtnTr2
  succ Key
BtnTr2 = Key
BtnSelect
  succ Key
BtnSelect = Key
BtnStart
  succ Key
BtnStart = Key
BtnMode
  succ Key
BtnMode = Key
BtnThumbl
  succ Key
BtnThumbl = Key
BtnThumbr
  succ Key
BtnThumbr = Key
BtnDigi
  succ Key
BtnDigi = Key
BtnToolRubber
  succ Key
BtnToolPen = Key
BtnToolRubber
  succ Key
BtnToolRubber = Key
BtnToolBrush
  succ Key
BtnToolBrush = Key
BtnToolPencil
  succ Key
BtnToolPencil = Key
BtnToolAirbrush
  succ Key
BtnToolAirbrush = Key
BtnToolFinger
  succ Key
BtnToolFinger = Key
BtnToolMouse
  succ Key
BtnToolMouse = Key
BtnToolLens
  succ Key
BtnToolLens = Key
BtnToolQuinttap
  succ Key
BtnToolQuinttap = Key
BtnTouch
  succ Key
BtnTouch = Key
BtnStylus
  succ Key
BtnStylus = Key
BtnStylus2
  succ Key
BtnStylus2 = Key
BtnToolDoubletap
  succ Key
BtnToolDoubletap = Key
BtnToolTripletap
  succ Key
BtnToolTripletap = Key
BtnToolQuadtap
  succ Key
BtnToolQuadtap = Key
BtnWheel
  succ Key
BtnWheel = Key
BtnGearUp
  succ Key
BtnGearDown = Key
BtnGearUp
  succ Key
BtnGearUp = Key
KeyOk
  succ Key
KeyOk = Key
KeySelect
  succ Key
KeySelect = Key
KeyGoto
  succ Key
KeyGoto = Key
KeyClear
  succ Key
KeyClear = Key
KeyPower2
  succ Key
KeyPower2 = Key
KeyOption
  succ Key
KeyOption = Key
KeyInfo
  succ Key
KeyInfo = Key
KeyTime
  succ Key
KeyTime = Key
KeyVendor
  succ Key
KeyVendor = Key
KeyArchive
  succ Key
KeyArchive = Key
KeyProgram
  succ Key
KeyProgram = Key
KeyChannel
  succ Key
KeyChannel = Key
KeyFavorites
  succ Key
KeyFavorites = Key
KeyEpg
  succ Key
KeyEpg = Key
KeyPvr
  succ Key
KeyPvr = Key
KeyMhp
  succ Key
KeyMhp = Key
KeyLanguage
  succ Key
KeyLanguage = Key
KeyTitle
  succ Key
KeyTitle = Key
KeySubtitle
  succ Key
KeySubtitle = Key
KeyAngle
  succ Key
KeyAngle = Key
KeyZoom
  succ Key
KeyZoom = Key
KeyMode
  succ Key
KeyMode = Key
KeyKeyboard
  succ Key
KeyKeyboard = Key
KeyScreen
  succ Key
KeyScreen = Key
KeyPc
  succ Key
KeyPc = Key
KeyTv
  succ Key
KeyTv = Key
KeyTv2
  succ Key
KeyTv2 = Key
KeyVcr
  succ Key
KeyVcr = Key
KeyVcr2
  succ Key
KeyVcr2 = Key
KeySat
  succ Key
KeySat = Key
KeySat2
  succ Key
KeySat2 = Key
KeyCd
  succ Key
KeyCd = Key
KeyTape
  succ Key
KeyTape = Key
KeyRadio
  succ Key
KeyRadio = Key
KeyTuner
  succ Key
KeyTuner = Key
KeyPlayer
  succ Key
KeyPlayer = Key
KeyText
  succ Key
KeyText = Key
KeyDvd
  succ Key
KeyDvd = Key
KeyAux
  succ Key
KeyAux = Key
KeyMp3
  succ Key
KeyMp3 = Key
KeyAudio
  succ Key
KeyAudio = Key
KeyVideo
  succ Key
KeyVideo = Key
KeyDirectory
  succ Key
KeyDirectory = Key
KeyList
  succ Key
KeyList = Key
KeyMemo
  succ Key
KeyMemo = Key
KeyCalendar
  succ Key
KeyCalendar = Key
KeyRed
  succ Key
KeyRed = Key
KeyGreen
  succ Key
KeyGreen = Key
KeyYellow
  succ Key
KeyYellow = Key
KeyBlue
  succ Key
KeyBlue = Key
KeyChannelup
  succ Key
KeyChannelup = Key
KeyChanneldown
  succ Key
KeyChanneldown = Key
KeyFirst
  succ Key
KeyFirst = Key
KeyLast
  succ Key
KeyLast = Key
KeyAb
  succ Key
KeyAb = Key
KeyNext
  succ Key
KeyNext = Key
KeyRestart
  succ Key
KeyRestart = Key
KeySlow
  succ Key
KeySlow = Key
KeyShuffle
  succ Key
KeyShuffle = Key
KeyBreak
  succ Key
KeyBreak = Key
KeyPrevious
  succ Key
KeyPrevious = Key
KeyDigits
  succ Key
KeyDigits = Key
KeyTeen
  succ Key
KeyTeen = Key
KeyTwen
  succ Key
KeyTwen = Key
KeyVideophone
  succ Key
KeyVideophone = Key
KeyGames
  succ Key
KeyGames = Key
KeyZoomin
  succ Key
KeyZoomin = Key
KeyZoomout
  succ Key
KeyZoomout = Key
KeyZoomreset
  succ Key
KeyZoomreset = Key
KeyWordprocessor
  succ Key
KeyWordprocessor = Key
KeyEditor
  succ Key
KeyEditor = Key
KeySpreadsheet
  succ Key
KeySpreadsheet = Key
KeyGraphicseditor
  succ Key
KeyGraphicseditor = Key
KeyPresentation
  succ Key
KeyPresentation = Key
KeyDatabase
  succ Key
KeyDatabase = Key
KeyNews
  succ Key
KeyNews = Key
KeyVoicemail
  succ Key
KeyVoicemail = Key
KeyAddressbook
  succ Key
KeyAddressbook = Key
KeyMessenger
  succ Key
KeyMessenger = Key
KeyDisplaytoggle
  succ Key
KeyDisplaytoggle = Key
KeySpellcheck
  succ Key
KeyBrightnessToggle = Key
KeySpellcheck
  succ Key
KeySpellcheck = Key
KeyLogoff
  succ Key
KeyLogoff = Key
KeyDollar
  succ Key
KeyDollar = Key
KeyEuro
  succ Key
KeyEuro = Key
KeyFrameback
  succ Key
KeyFrameback = Key
KeyFrameforward
  succ Key
KeyFrameforward = Key
KeyContextMenu
  succ Key
KeyContextMenu = Key
KeyMediaRepeat
  succ Key
KeyMediaRepeat = Key
Key10channelsup
  succ Key
Key10channelsup = Key
Key10channelsdown
  succ Key
Key10channelsdown = Key
KeyImages
  succ Key
KeyImages = Key
KeyDelEol
  succ Key
KeyDelEol = Key
KeyDelEos
  succ Key
KeyDelEos = Key
KeyInsLine
  succ Key
KeyInsLine = Key
KeyDelLine
  succ Key
KeyDelLine = Key
KeyFn
  succ Key
KeyFn = Key
KeyFnEsc
  succ Key
KeyFnEsc = Key
KeyFnF1
  succ Key
KeyFnF1 = Key
KeyFnF2
  succ Key
KeyFnF2 = Key
KeyFnF3
  succ Key
KeyFnF3 = Key
KeyFnF4
  succ Key
KeyFnF4 = Key
KeyFnF5
  succ Key
KeyFnF5 = Key
KeyFnF6
  succ Key
KeyFnF6 = Key
KeyFnF7
  succ Key
KeyFnF7 = Key
KeyFnF8
  succ Key
KeyFnF8 = Key
KeyFnF9
  succ Key
KeyFnF9 = Key
KeyFnF10
  succ Key
KeyFnF10 = Key
KeyFnF11
  succ Key
KeyFnF11 = Key
KeyFnF12
  succ Key
KeyFnF12 = Key
KeyFn1
  succ Key
KeyFn1 = Key
KeyFn2
  succ Key
KeyFn2 = Key
KeyFnD
  succ Key
KeyFnD = Key
KeyFnE
  succ Key
KeyFnE = Key
KeyFnF
  succ Key
KeyFnF = Key
KeyFnS
  succ Key
KeyFnS = Key
KeyFnB
  succ Key
KeyFnB = Key
KeyBrlDot1
  succ Key
KeyBrlDot1 = Key
KeyBrlDot2
  succ Key
KeyBrlDot2 = Key
KeyBrlDot3
  succ Key
KeyBrlDot3 = Key
KeyBrlDot4
  succ Key
KeyBrlDot4 = Key
KeyBrlDot5
  succ Key
KeyBrlDot5 = Key
KeyBrlDot6
  succ Key
KeyBrlDot6 = Key
KeyBrlDot7
  succ Key
KeyBrlDot7 = Key
KeyBrlDot8
  succ Key
KeyBrlDot8 = Key
KeyBrlDot9
  succ Key
KeyBrlDot9 = Key
KeyBrlDot10
  succ Key
KeyBrlDot10 = Key
KeyNumeric0
  succ Key
KeyNumeric0 = Key
KeyNumeric1
  succ Key
KeyNumeric1 = Key
KeyNumeric2
  succ Key
KeyNumeric2 = Key
KeyNumeric3
  succ Key
KeyNumeric3 = Key
KeyNumeric4
  succ Key
KeyNumeric4 = Key
KeyNumeric5
  succ Key
KeyNumeric5 = Key
KeyNumeric6
  succ Key
KeyNumeric6 = Key
KeyNumeric7
  succ Key
KeyNumeric7 = Key
KeyNumeric8
  succ Key
KeyNumeric8 = Key
KeyNumeric9
  succ Key
KeyNumeric9 = Key
KeyNumericStar
  succ Key
KeyNumericStar = Key
KeyNumericPound
  succ Key
KeyNumericPound = Key
KeyNumericA
  succ Key
KeyNumericA = Key
KeyNumericB
  succ Key
KeyNumericB = Key
KeyNumericC
  succ Key
KeyNumericC = Key
KeyNumericD
  succ Key
KeyNumericD = Key
KeyCameraFocus
  succ Key
KeyCameraFocus = Key
KeyWpsButton
  succ Key
KeyWpsButton = Key
KeyTouchpadToggle
  succ Key
KeyTouchpadToggle = Key
KeyTouchpadOn
  succ Key
KeyTouchpadOn = Key
KeyTouchpadOff
  succ Key
KeyTouchpadOff = Key
KeyCameraZoomin
  succ Key
KeyCameraZoomin = Key
KeyCameraZoomout
  succ Key
KeyCameraZoomout = Key
KeyCameraUp
  succ Key
KeyCameraUp = Key
KeyCameraDown
  succ Key
KeyCameraDown = Key
KeyCameraLeft
  succ Key
KeyCameraLeft = Key
KeyCameraRight
  succ Key
KeyCameraRight = Key
KeyAttendantOn
  succ Key
KeyAttendantOn = Key
KeyAttendantOff
  succ Key
KeyAttendantOff = Key
KeyAttendantToggle
  succ Key
KeyAttendantToggle = Key
KeyLightsToggle
  succ Key
KeyLightsToggle = Key
BtnDpadUp
  succ Key
BtnDpadUp = Key
BtnDpadDown
  succ Key
BtnDpadDown = Key
BtnDpadLeft
  succ Key
BtnDpadLeft = Key
BtnDpadRight
  succ Key
BtnDpadRight = Key
KeyAlsToggle
  succ Key
KeyAlsToggle = Key
KeyButtonconfig
  succ Key
KeyButtonconfig = Key
KeyTaskmanager
  succ Key
KeyTaskmanager = Key
KeyJournal
  succ Key
KeyJournal = Key
KeyControlpanel
  succ Key
KeyControlpanel = Key
KeyAppselect
  succ Key
KeyAppselect = Key
KeyScreensaver
  succ Key
KeyScreensaver = Key
KeyVoicecommand
  succ Key
KeyVoicecommand = Key
KeyBrightnessMin
  succ Key
KeyBrightnessMin = Key
KeyBrightnessMax
  succ Key
KeyBrightnessMax = Key
KeyKbdinputassistPrev
  succ Key
KeyKbdinputassistPrev = Key
KeyKbdinputassistNext
  succ Key
KeyKbdinputassistNext = Key
KeyKbdinputassistPrevgroup
  succ Key
KeyKbdinputassistPrevgroup = Key
KeyKbdinputassistNextgroup
  succ Key
KeyKbdinputassistNextgroup = Key
KeyKbdinputassistAccept
  succ Key
KeyKbdinputassistAccept = Key
KeyKbdinputassistCancel
  succ Key
KeyKbdinputassistCancel = Key
BtnTriggerHappy
  succ Key
BtnTriggerHappy = Key
BtnTriggerHappy2
  succ Key
BtnTriggerHappy1 = Key
BtnTriggerHappy2
  succ Key
BtnTriggerHappy2 = Key
BtnTriggerHappy3
  succ Key
BtnTriggerHappy3 = Key
BtnTriggerHappy4
  succ Key
BtnTriggerHappy4 = Key
BtnTriggerHappy5
  succ Key
BtnTriggerHappy5 = Key
BtnTriggerHappy6
  succ Key
BtnTriggerHappy6 = Key
BtnTriggerHappy7
  succ Key
BtnTriggerHappy7 = Key
BtnTriggerHappy8
  succ Key
BtnTriggerHappy8 = Key
BtnTriggerHappy9
  succ Key
BtnTriggerHappy9 = Key
BtnTriggerHappy10
  succ Key
BtnTriggerHappy10 = Key
BtnTriggerHappy11
  succ Key
BtnTriggerHappy11 = Key
BtnTriggerHappy12
  succ Key
BtnTriggerHappy12 = Key
BtnTriggerHappy13
  succ Key
BtnTriggerHappy13 = Key
BtnTriggerHappy14
  succ Key
BtnTriggerHappy14 = Key
BtnTriggerHappy15
  succ Key
BtnTriggerHappy15 = Key
BtnTriggerHappy16
  succ Key
BtnTriggerHappy16 = Key
BtnTriggerHappy17
  succ Key
BtnTriggerHappy17 = Key
BtnTriggerHappy18
  succ Key
BtnTriggerHappy18 = Key
BtnTriggerHappy19
  succ Key
BtnTriggerHappy19 = Key
BtnTriggerHappy20
  succ Key
BtnTriggerHappy20 = Key
BtnTriggerHappy21
  succ Key
BtnTriggerHappy21 = Key
BtnTriggerHappy22
  succ Key
BtnTriggerHappy22 = Key
BtnTriggerHappy23
  succ Key
BtnTriggerHappy23 = Key
BtnTriggerHappy24
  succ Key
BtnTriggerHappy24 = Key
BtnTriggerHappy25
  succ Key
BtnTriggerHappy25 = Key
BtnTriggerHappy26
  succ Key
BtnTriggerHappy26 = Key
BtnTriggerHappy27
  succ Key
BtnTriggerHappy27 = Key
BtnTriggerHappy28
  succ Key
BtnTriggerHappy28 = Key
BtnTriggerHappy29
  succ Key
BtnTriggerHappy29 = Key
BtnTriggerHappy30
  succ Key
BtnTriggerHappy30 = Key
BtnTriggerHappy31
  succ Key
BtnTriggerHappy31 = Key
BtnTriggerHappy32
  succ Key
BtnTriggerHappy32 = Key
BtnTriggerHappy33
  succ Key
BtnTriggerHappy33 = Key
BtnTriggerHappy34
  succ Key
BtnTriggerHappy34 = Key
BtnTriggerHappy35
  succ Key
BtnTriggerHappy35 = Key
BtnTriggerHappy36
  succ Key
BtnTriggerHappy36 = Key
BtnTriggerHappy37
  succ Key
BtnTriggerHappy37 = Key
BtnTriggerHappy38
  succ Key
BtnTriggerHappy38 = Key
BtnTriggerHappy39
  succ Key
BtnTriggerHappy39 = Key
BtnTriggerHappy40
  succ Key
BtnTriggerHappy40 = forall a. HasCallStack => String -> a
error String
"Key.succ: BtnTriggerHappy40 has no successor"

  pred :: Key -> Key
pred Key
KeyEsc = Key
KeyReserved
  pred Key
Key1 = Key
KeyEsc
  pred Key
Key2 = Key
Key1
  pred Key
Key3 = Key
Key2
  pred Key
Key4 = Key
Key3
  pred Key
Key5 = Key
Key4
  pred Key
Key6 = Key
Key5
  pred Key
Key7 = Key
Key6
  pred Key
Key8 = Key
Key7
  pred Key
Key9 = Key
Key8
  pred Key
Key0 = Key
Key9
  pred Key
KeyMinus = Key
Key0
  pred Key
KeyEqual = Key
KeyMinus
  pred Key
KeyBackspace = Key
KeyEqual
  pred Key
KeyTab = Key
KeyBackspace
  pred Key
KeyQ = Key
KeyTab
  pred Key
KeyW = Key
KeyQ
  pred Key
KeyE = Key
KeyW
  pred Key
KeyR = Key
KeyE
  pred Key
KeyT = Key
KeyR
  pred Key
KeyY = Key
KeyT
  pred Key
KeyU = Key
KeyY
  pred Key
KeyI = Key
KeyU
  pred Key
KeyO = Key
KeyI
  pred Key
KeyP = Key
KeyO
  pred Key
KeyLeftbrace = Key
KeyP
  pred Key
KeyRightbrace = Key
KeyLeftbrace
  pred Key
KeyEnter = Key
KeyRightbrace
  pred Key
KeyLeftctrl = Key
KeyEnter
  pred Key
KeyA = Key
KeyLeftctrl
  pred Key
KeyS = Key
KeyA
  pred Key
KeyD = Key
KeyS
  pred Key
KeyF = Key
KeyD
  pred Key
KeyG = Key
KeyF
  pred Key
KeyH = Key
KeyG
  pred Key
KeyJ = Key
KeyH
  pred Key
KeyK = Key
KeyJ
  pred Key
KeyL = Key
KeyK
  pred Key
KeySemicolon = Key
KeyL
  pred Key
KeyApostrophe = Key
KeySemicolon
  pred Key
KeyGrave = Key
KeyApostrophe
  pred Key
KeyLeftshift = Key
KeyGrave
  pred Key
KeyBackslash = Key
KeyLeftshift
  pred Key
KeyZ = Key
KeyBackslash
  pred Key
KeyX = Key
KeyZ
  pred Key
KeyC = Key
KeyX
  pred Key
KeyV = Key
KeyC
  pred Key
KeyB = Key
KeyV
  pred Key
KeyN = Key
KeyB
  pred Key
KeyM = Key
KeyN
  pred Key
KeyComma = Key
KeyM
  pred Key
KeyDot = Key
KeyComma
  pred Key
KeySlash = Key
KeyDot
  pred Key
KeyRightshift = Key
KeySlash
  pred Key
KeyKpasterisk = Key
KeyRightshift
  pred Key
KeyLeftalt = Key
KeyKpasterisk
  pred Key
KeySpace = Key
KeyLeftalt
  pred Key
KeyCapslock = Key
KeySpace
  pred Key
KeyF1 = Key
KeyCapslock
  pred Key
KeyF2 = Key
KeyF1
  pred Key
KeyF3 = Key
KeyF2
  pred Key
KeyF4 = Key
KeyF3
  pred Key
KeyF5 = Key
KeyF4
  pred Key
KeyF6 = Key
KeyF5
  pred Key
KeyF7 = Key
KeyF6
  pred Key
KeyF8 = Key
KeyF7
  pred Key
KeyF9 = Key
KeyF8
  pred Key
KeyF10 = Key
KeyF9
  pred Key
KeyNumlock = Key
KeyF10
  pred Key
KeyScrolllock = Key
KeyNumlock
  pred Key
KeyKp7 = Key
KeyScrolllock
  pred Key
KeyKp8 = Key
KeyKp7
  pred Key
KeyKp9 = Key
KeyKp8
  pred Key
KeyKpminus = Key
KeyKp9
  pred Key
KeyKp4 = Key
KeyKpminus
  pred Key
KeyKp5 = Key
KeyKp4
  pred Key
KeyKp6 = Key
KeyKp5
  pred Key
KeyKpplus = Key
KeyKp6
  pred Key
KeyKp1 = Key
KeyKpplus
  pred Key
KeyKp2 = Key
KeyKp1
  pred Key
KeyKp3 = Key
KeyKp2
  pred Key
KeyKp0 = Key
KeyKp3
  pred Key
KeyKpdot = Key
KeyKp0
  pred Key
KeyZenkakuhankaku = Key
KeyKpdot
  pred Key
Key102nd = Key
KeyZenkakuhankaku
  pred Key
KeyF11 = Key
Key102nd
  pred Key
KeyF12 = Key
KeyF11
  pred Key
KeyRo = Key
KeyF12
  pred Key
KeyKatakana = Key
KeyRo
  pred Key
KeyHiragana = Key
KeyKatakana
  pred Key
KeyHenkan = Key
KeyHiragana
  pred Key
KeyKatakanahiragana = Key
KeyHenkan
  pred Key
KeyMuhenkan = Key
KeyKatakanahiragana
  pred Key
KeyKpjpcomma = Key
KeyMuhenkan
  pred Key
KeyKpenter = Key
KeyKpjpcomma
  pred Key
KeyRightctrl = Key
KeyKpenter
  pred Key
KeyKpslash = Key
KeyRightctrl
  pred Key
KeySysrq = Key
KeyKpslash
  pred Key
KeyRightalt = Key
KeySysrq
  pred Key
KeyLinefeed = Key
KeyRightalt
  pred Key
KeyHome = Key
KeyLinefeed
  pred Key
KeyUp = Key
KeyHome
  pred Key
KeyPageup = Key
KeyUp
  pred Key
KeyLeft = Key
KeyPageup
  pred Key
KeyRight = Key
KeyLeft
  pred Key
KeyEnd = Key
KeyRight
  pred Key
KeyDown = Key
KeyEnd
  pred Key
KeyPagedown = Key
KeyDown
  pred Key
KeyInsert = Key
KeyPagedown
  pred Key
KeyDelete = Key
KeyInsert
  pred Key
KeyMacro = Key
KeyDelete
  pred Key
KeyMute = Key
KeyMacro
  pred Key
KeyVolumedown = Key
KeyMute
  pred Key
KeyVolumeup = Key
KeyVolumedown
  pred Key
KeyPower = Key
KeyVolumeup
  pred Key
KeyKpequal = Key
KeyPower
  pred Key
KeyKpplusminus = Key
KeyKpequal
  pred Key
KeyPause = Key
KeyKpplusminus
  pred Key
KeyScale = Key
KeyPause
  pred Key
KeyKpcomma = Key
KeyScale
  pred Key
KeyHangeul = Key
KeyKpcomma
  pred Key
KeyHanguel = Key
KeyKpcomma
  pred Key
KeyHanja = Key
KeyHangeul
  pred Key
KeyYen = Key
KeyHanja
  pred Key
KeyLeftmeta = Key
KeyYen
  pred Key
KeyRightmeta = Key
KeyLeftmeta
  pred Key
KeyCompose = Key
KeyRightmeta
  pred Key
KeyStop = Key
KeyCompose
  pred Key
KeyAgain = Key
KeyStop
  pred Key
KeyProps = Key
KeyAgain
  pred Key
KeyUndo = Key
KeyProps
  pred Key
KeyFront = Key
KeyUndo
  pred Key
KeyCopy = Key
KeyFront
  pred Key
KeyOpen = Key
KeyCopy
  pred Key
KeyPaste = Key
KeyOpen
  pred Key
KeyFind = Key
KeyPaste
  pred Key
KeyCut = Key
KeyFind
  pred Key
KeyHelp = Key
KeyCut
  pred Key
KeyMenu = Key
KeyHelp
  pred Key
KeyCalc = Key
KeyMenu
  pred Key
KeySetup = Key
KeyCalc
  pred Key
KeySleep = Key
KeySetup
  pred Key
KeyWakeup = Key
KeySleep
  pred Key
KeyFile = Key
KeyWakeup
  pred Key
KeySendfile = Key
KeyFile
  pred Key
KeyDeletefile = Key
KeySendfile
  pred Key
KeyXfer = Key
KeyDeletefile
  pred Key
KeyProg1 = Key
KeyXfer
  pred Key
KeyProg2 = Key
KeyProg1
  pred Key
KeyWww = Key
KeyProg2
  pred Key
KeyMsdos = Key
KeyWww
  pred Key
KeyCoffee = Key
KeyMsdos
  pred Key
KeyScreenlock = Key
KeyMsdos
  pred Key
KeyRotateDisplay = Key
KeyCoffee
  pred Key
KeyDirection = Key
KeyCoffee
  pred Key
KeyCyclewindows = Key
KeyRotateDisplay
  pred Key
KeyMail = Key
KeyCyclewindows
  pred Key
KeyBookmarks = Key
KeyMail
  pred Key
KeyComputer = Key
KeyBookmarks
  pred Key
KeyBack = Key
KeyComputer
  pred Key
KeyForward = Key
KeyBack
  pred Key
KeyClosecd = Key
KeyForward
  pred Key
KeyEjectcd = Key
KeyClosecd
  pred Key
KeyEjectclosecd = Key
KeyEjectcd
  pred Key
KeyNextsong = Key
KeyEjectclosecd
  pred Key
KeyPlaypause = Key
KeyNextsong
  pred Key
KeyPrevioussong = Key
KeyPlaypause
  pred Key
KeyStopcd = Key
KeyPrevioussong
  pred Key
KeyRecord = Key
KeyStopcd
  pred Key
KeyRewind = Key
KeyRecord
  pred Key
KeyPhone = Key
KeyRewind
  pred Key
KeyIso = Key
KeyPhone
  pred Key
KeyConfig = Key
KeyIso
  pred Key
KeyHomepage = Key
KeyConfig
  pred Key
KeyRefresh = Key
KeyHomepage
  pred Key
KeyExit = Key
KeyRefresh
  pred Key
KeyMove = Key
KeyExit
  pred Key
KeyEdit = Key
KeyMove
  pred Key
KeyScrollup = Key
KeyEdit
  pred Key
KeyScrolldown = Key
KeyScrollup
  pred Key
KeyKpleftparen = Key
KeyScrolldown
  pred Key
KeyKprightparen = Key
KeyKpleftparen
  pred Key
KeyNew = Key
KeyKprightparen
  pred Key
KeyRedo = Key
KeyNew
  pred Key
KeyF13 = Key
KeyRedo
  pred Key
KeyF14 = Key
KeyF13
  pred Key
KeyF15 = Key
KeyF14
  pred Key
KeyF16 = Key
KeyF15
  pred Key
KeyF17 = Key
KeyF16
  pred Key
KeyF18 = Key
KeyF17
  pred Key
KeyF19 = Key
KeyF18
  pred Key
KeyF20 = Key
KeyF19
  pred Key
KeyF21 = Key
KeyF20
  pred Key
KeyF22 = Key
KeyF21
  pred Key
KeyF23 = Key
KeyF22
  pred Key
KeyF24 = Key
KeyF23
  pred Key
KeyPlaycd = Key
KeyF24
  pred Key
KeyPausecd = Key
KeyPlaycd
  pred Key
KeyProg3 = Key
KeyPausecd
  pred Key
KeyProg4 = Key
KeyProg3
  pred Key
KeyDashboard = Key
KeyProg4
  pred Key
KeySuspend = Key
KeyDashboard
  pred Key
KeyClose = Key
KeySuspend
  pred Key
KeyPlay = Key
KeyClose
  pred Key
KeyFastforward = Key
KeyPlay
  pred Key
KeyBassboost = Key
KeyFastforward
  pred Key
KeyPrint = Key
KeyBassboost
  pred Key
KeyHp = Key
KeyPrint
  pred Key
KeyCamera = Key
KeyHp
  pred Key
KeySound = Key
KeyCamera
  pred Key
KeyQuestion = Key
KeySound
  pred Key
KeyEmail = Key
KeyQuestion
  pred Key
KeyChat = Key
KeyEmail
  pred Key
KeySearch = Key
KeyChat
  pred Key
KeyConnect = Key
KeySearch
  pred Key
KeyFinance = Key
KeyConnect
  pred Key
KeySport = Key
KeyFinance
  pred Key
KeyShop = Key
KeySport
  pred Key
KeyAlterase = Key
KeyShop
  pred Key
KeyCancel = Key
KeyAlterase
  pred Key
KeyBrightnessdown = Key
KeyCancel
  pred Key
KeyBrightnessup = Key
KeyBrightnessdown
  pred Key
KeyMedia = Key
KeyBrightnessup
  pred Key
KeySwitchvideomode = Key
KeyMedia
  pred Key
KeyKbdillumtoggle = Key
KeySwitchvideomode
  pred Key
KeyKbdillumdown = Key
KeyKbdillumtoggle
  pred Key
KeyKbdillumup = Key
KeyKbdillumdown
  pred Key
KeySend = Key
KeyKbdillumup
  pred Key
KeyReply = Key
KeySend
  pred Key
KeyForwardmail = Key
KeyReply
  pred Key
KeySave = Key
KeyForwardmail
  pred Key
KeyDocuments = Key
KeySave
  pred Key
KeyBattery = Key
KeyDocuments
  pred Key
KeyBluetooth = Key
KeyBattery
  pred Key
KeyWlan = Key
KeyBluetooth
  pred Key
KeyUwb = Key
KeyWlan
  pred Key
KeyUnknown = Key
KeyUwb
  pred Key
KeyVideoNext = Key
KeyUnknown
  pred Key
KeyVideoPrev = Key
KeyVideoNext
  pred Key
KeyBrightnessCycle = Key
KeyVideoPrev
  pred Key
KeyBrightnessAuto = Key
KeyBrightnessCycle
  pred Key
KeyBrightnessZero = Key
KeyBrightnessCycle
  pred Key
KeyDisplayOff = Key
KeyBrightnessAuto
  pred Key
KeyWwan = Key
KeyDisplayOff
  pred Key
KeyWimax = Key
KeyDisplayOff
  pred Key
KeyRfkill = Key
KeyWwan
  pred Key
KeyMicmute = Key
KeyRfkill
  pred Key
BtnMisc = Key
KeyMicmute
  pred Key
Btn0 = Key
KeyMicmute
  pred Key
Btn1 = Key
BtnMisc
  pred Key
Btn2 = Key
Btn1
  pred Key
Btn3 = Key
Btn2
  pred Key
Btn4 = Key
Btn3
  pred Key
Btn5 = Key
Btn4
  pred Key
Btn6 = Key
Btn5
  pred Key
Btn7 = Key
Btn6
  pred Key
Btn8 = Key
Btn7
  pred Key
Btn9 = Key
Btn8
  pred Key
BtnMouse = Key
Btn9
  pred Key
BtnLeft = Key
Btn9
  pred Key
BtnRight = Key
BtnMouse
  pred Key
BtnMiddle = Key
BtnRight
  pred Key
BtnSide = Key
BtnMiddle
  pred Key
BtnExtra = Key
BtnSide
  pred Key
BtnForward = Key
BtnExtra
  pred Key
BtnBack = Key
BtnForward
  pred Key
BtnTask = Key
BtnBack
  pred Key
BtnJoystick = Key
BtnTask
  pred Key
BtnTrigger = Key
BtnTask
  pred Key
BtnThumb = Key
BtnJoystick
  pred Key
BtnThumb2 = Key
BtnThumb
  pred Key
BtnTop = Key
BtnThumb2
  pred Key
BtnTop2 = Key
BtnTop
  pred Key
BtnPinkie = Key
BtnTop2
  pred Key
BtnBase = Key
BtnPinkie
  pred Key
BtnBase2 = Key
BtnBase
  pred Key
BtnBase3 = Key
BtnBase2
  pred Key
BtnBase4 = Key
BtnBase3
  pred Key
BtnBase5 = Key
BtnBase4
  pred Key
BtnBase6 = Key
BtnBase5
  pred Key
BtnDead = Key
BtnBase6
  pred Key
BtnGamepad = Key
BtnDead
  pred Key
BtnSouth = Key
BtnDead
  pred Key
BtnA = Key
BtnDead
  pred Key
BtnEast = Key
BtnGamepad
  pred Key
BtnB = Key
BtnGamepad
  pred Key
BtnC = Key
BtnEast
  pred Key
BtnNorth = Key
BtnC
  pred Key
BtnX = Key
BtnC
  pred Key
BtnWest = Key
BtnNorth
  pred Key
BtnY = Key
BtnNorth
  pred Key
BtnZ = Key
BtnWest
  pred Key
BtnTl = Key
BtnZ
  pred Key
BtnTr = Key
BtnTl
  pred Key
BtnTl2 = Key
BtnTr
  pred Key
BtnTr2 = Key
BtnTl2
  pred Key
BtnSelect = Key
BtnTr2
  pred Key
BtnStart = Key
BtnSelect
  pred Key
BtnMode = Key
BtnStart
  pred Key
BtnThumbl = Key
BtnMode
  pred Key
BtnThumbr = Key
BtnThumbl
  pred Key
BtnDigi = Key
BtnThumbr
  pred Key
BtnToolPen = Key
BtnThumbr
  pred Key
BtnToolRubber = Key
BtnDigi
  pred Key
BtnToolBrush = Key
BtnToolRubber
  pred Key
BtnToolPencil = Key
BtnToolBrush
  pred Key
BtnToolAirbrush = Key
BtnToolPencil
  pred Key
BtnToolFinger = Key
BtnToolAirbrush
  pred Key
BtnToolMouse = Key
BtnToolFinger
  pred Key
BtnToolLens = Key
BtnToolMouse
  pred Key
BtnToolQuinttap = Key
BtnToolLens
  pred Key
BtnTouch = Key
BtnToolQuinttap
  pred Key
BtnStylus = Key
BtnTouch
  pred Key
BtnStylus2 = Key
BtnStylus
  pred Key
BtnToolDoubletap = Key
BtnStylus2
  pred Key
BtnToolTripletap = Key
BtnToolDoubletap
  pred Key
BtnToolQuadtap = Key
BtnToolTripletap
  pred Key
BtnWheel = Key
BtnToolQuadtap
  pred Key
BtnGearDown = Key
BtnToolQuadtap
  pred Key
BtnGearUp = Key
BtnWheel
  pred Key
KeyOk = Key
BtnGearUp
  pred Key
KeySelect = Key
KeyOk
  pred Key
KeyGoto = Key
KeySelect
  pred Key
KeyClear = Key
KeyGoto
  pred Key
KeyPower2 = Key
KeyClear
  pred Key
KeyOption = Key
KeyPower2
  pred Key
KeyInfo = Key
KeyOption
  pred Key
KeyTime = Key
KeyInfo
  pred Key
KeyVendor = Key
KeyTime
  pred Key
KeyArchive = Key
KeyVendor
  pred Key
KeyProgram = Key
KeyArchive
  pred Key
KeyChannel = Key
KeyProgram
  pred Key
KeyFavorites = Key
KeyChannel
  pred Key
KeyEpg = Key
KeyFavorites
  pred Key
KeyPvr = Key
KeyEpg
  pred Key
KeyMhp = Key
KeyPvr
  pred Key
KeyLanguage = Key
KeyMhp
  pred Key
KeyTitle = Key
KeyLanguage
  pred Key
KeySubtitle = Key
KeyTitle
  pred Key
KeyAngle = Key
KeySubtitle
  pred Key
KeyZoom = Key
KeyAngle
  pred Key
KeyMode = Key
KeyZoom
  pred Key
KeyKeyboard = Key
KeyMode
  pred Key
KeyScreen = Key
KeyKeyboard
  pred Key
KeyPc = Key
KeyScreen
  pred Key
KeyTv = Key
KeyPc
  pred Key
KeyTv2 = Key
KeyTv
  pred Key
KeyVcr = Key
KeyTv2
  pred Key
KeyVcr2 = Key
KeyVcr
  pred Key
KeySat = Key
KeyVcr2
  pred Key
KeySat2 = Key
KeySat
  pred Key
KeyCd = Key
KeySat2
  pred Key
KeyTape = Key
KeyCd
  pred Key
KeyRadio = Key
KeyTape
  pred Key
KeyTuner = Key
KeyRadio
  pred Key
KeyPlayer = Key
KeyTuner
  pred Key
KeyText = Key
KeyPlayer
  pred Key
KeyDvd = Key
KeyText
  pred Key
KeyAux = Key
KeyDvd
  pred Key
KeyMp3 = Key
KeyAux
  pred Key
KeyAudio = Key
KeyMp3
  pred Key
KeyVideo = Key
KeyAudio
  pred Key
KeyDirectory = Key
KeyVideo
  pred Key
KeyList = Key
KeyDirectory
  pred Key
KeyMemo = Key
KeyList
  pred Key
KeyCalendar = Key
KeyMemo
  pred Key
KeyRed = Key
KeyCalendar
  pred Key
KeyGreen = Key
KeyRed
  pred Key
KeyYellow = Key
KeyGreen
  pred Key
KeyBlue = Key
KeyYellow
  pred Key
KeyChannelup = Key
KeyBlue
  pred Key
KeyChanneldown = Key
KeyChannelup
  pred Key
KeyFirst = Key
KeyChanneldown
  pred Key
KeyLast = Key
KeyFirst
  pred Key
KeyAb = Key
KeyLast
  pred Key
KeyNext = Key
KeyAb
  pred Key
KeyRestart = Key
KeyNext
  pred Key
KeySlow = Key
KeyRestart
  pred Key
KeyShuffle = Key
KeySlow
  pred Key
KeyBreak = Key
KeyShuffle
  pred Key
KeyPrevious = Key
KeyBreak
  pred Key
KeyDigits = Key
KeyPrevious
  pred Key
KeyTeen = Key
KeyDigits
  pred Key
KeyTwen = Key
KeyTeen
  pred Key
KeyVideophone = Key
KeyTwen
  pred Key
KeyGames = Key
KeyVideophone
  pred Key
KeyZoomin = Key
KeyGames
  pred Key
KeyZoomout = Key
KeyZoomin
  pred Key
KeyZoomreset = Key
KeyZoomout
  pred Key
KeyWordprocessor = Key
KeyZoomreset
  pred Key
KeyEditor = Key
KeyWordprocessor
  pred Key
KeySpreadsheet = Key
KeyEditor
  pred Key
KeyGraphicseditor = Key
KeySpreadsheet
  pred Key
KeyPresentation = Key
KeyGraphicseditor
  pred Key
KeyDatabase = Key
KeyPresentation
  pred Key
KeyNews = Key
KeyDatabase
  pred Key
KeyVoicemail = Key
KeyNews
  pred Key
KeyAddressbook = Key
KeyVoicemail
  pred Key
KeyMessenger = Key
KeyAddressbook
  pred Key
KeyDisplaytoggle = Key
KeyMessenger
  pred Key
KeyBrightnessToggle = Key
KeyMessenger
  pred Key
KeySpellcheck = Key
KeyDisplaytoggle
  pred Key
KeyLogoff = Key
KeySpellcheck
  pred Key
KeyDollar = Key
KeyLogoff
  pred Key
KeyEuro = Key
KeyDollar
  pred Key
KeyFrameback = Key
KeyEuro
  pred Key
KeyFrameforward = Key
KeyFrameback
  pred Key
KeyContextMenu = Key
KeyFrameforward
  pred Key
KeyMediaRepeat = Key
KeyContextMenu
  pred Key
Key10channelsup = Key
KeyMediaRepeat
  pred Key
Key10channelsdown = Key
Key10channelsup
  pred Key
KeyImages = Key
Key10channelsdown
  pred Key
KeyDelEol = Key
KeyImages
  pred Key
KeyDelEos = Key
KeyDelEol
  pred Key
KeyInsLine = Key
KeyDelEos
  pred Key
KeyDelLine = Key
KeyInsLine
  pred Key
KeyFn = Key
KeyDelLine
  pred Key
KeyFnEsc = Key
KeyFn
  pred Key
KeyFnF1 = Key
KeyFnEsc
  pred Key
KeyFnF2 = Key
KeyFnF1
  pred Key
KeyFnF3 = Key
KeyFnF2
  pred Key
KeyFnF4 = Key
KeyFnF3
  pred Key
KeyFnF5 = Key
KeyFnF4
  pred Key
KeyFnF6 = Key
KeyFnF5
  pred Key
KeyFnF7 = Key
KeyFnF6
  pred Key
KeyFnF8 = Key
KeyFnF7
  pred Key
KeyFnF9 = Key
KeyFnF8
  pred Key
KeyFnF10 = Key
KeyFnF9
  pred Key
KeyFnF11 = Key
KeyFnF10
  pred Key
KeyFnF12 = Key
KeyFnF11
  pred Key
KeyFn1 = Key
KeyFnF12
  pred Key
KeyFn2 = Key
KeyFn1
  pred Key
KeyFnD = Key
KeyFn2
  pred Key
KeyFnE = Key
KeyFnD
  pred Key
KeyFnF = Key
KeyFnE
  pred Key
KeyFnS = Key
KeyFnF
  pred Key
KeyFnB = Key
KeyFnS
  pred Key
KeyBrlDot1 = Key
KeyFnB
  pred Key
KeyBrlDot2 = Key
KeyBrlDot1
  pred Key
KeyBrlDot3 = Key
KeyBrlDot2
  pred Key
KeyBrlDot4 = Key
KeyBrlDot3
  pred Key
KeyBrlDot5 = Key
KeyBrlDot4
  pred Key
KeyBrlDot6 = Key
KeyBrlDot5
  pred Key
KeyBrlDot7 = Key
KeyBrlDot6
  pred Key
KeyBrlDot8 = Key
KeyBrlDot7
  pred Key
KeyBrlDot9 = Key
KeyBrlDot8
  pred Key
KeyBrlDot10 = Key
KeyBrlDot9
  pred Key
KeyNumeric0 = Key
KeyBrlDot10
  pred Key
KeyNumeric1 = Key
KeyNumeric0
  pred Key
KeyNumeric2 = Key
KeyNumeric1
  pred Key
KeyNumeric3 = Key
KeyNumeric2
  pred Key
KeyNumeric4 = Key
KeyNumeric3
  pred Key
KeyNumeric5 = Key
KeyNumeric4
  pred Key
KeyNumeric6 = Key
KeyNumeric5
  pred Key
KeyNumeric7 = Key
KeyNumeric6
  pred Key
KeyNumeric8 = Key
KeyNumeric7
  pred Key
KeyNumeric9 = Key
KeyNumeric8
  pred Key
KeyNumericStar = Key
KeyNumeric9
  pred Key
KeyNumericPound = Key
KeyNumericStar
  pred Key
KeyNumericA = Key
KeyNumericPound
  pred Key
KeyNumericB = Key
KeyNumericA
  pred Key
KeyNumericC = Key
KeyNumericB
  pred Key
KeyNumericD = Key
KeyNumericC
  pred Key
KeyCameraFocus = Key
KeyNumericD
  pred Key
KeyWpsButton = Key
KeyCameraFocus
  pred Key
KeyTouchpadToggle = Key
KeyWpsButton
  pred Key
KeyTouchpadOn = Key
KeyTouchpadToggle
  pred Key
KeyTouchpadOff = Key
KeyTouchpadOn
  pred Key
KeyCameraZoomin = Key
KeyTouchpadOff
  pred Key
KeyCameraZoomout = Key
KeyCameraZoomin
  pred Key
KeyCameraUp = Key
KeyCameraZoomout
  pred Key
KeyCameraDown = Key
KeyCameraUp
  pred Key
KeyCameraLeft = Key
KeyCameraDown
  pred Key
KeyCameraRight = Key
KeyCameraLeft
  pred Key
KeyAttendantOn = Key
KeyCameraRight
  pred Key
KeyAttendantOff = Key
KeyAttendantOn
  pred Key
KeyAttendantToggle = Key
KeyAttendantOff
  pred Key
KeyLightsToggle = Key
KeyAttendantToggle
  pred Key
BtnDpadUp = Key
KeyLightsToggle
  pred Key
BtnDpadDown = Key
BtnDpadUp
  pred Key
BtnDpadLeft = Key
BtnDpadDown
  pred Key
BtnDpadRight = Key
BtnDpadLeft
  pred Key
KeyAlsToggle = Key
BtnDpadRight
  pred Key
KeyButtonconfig = Key
KeyAlsToggle
  pred Key
KeyTaskmanager = Key
KeyButtonconfig
  pred Key
KeyJournal = Key
KeyTaskmanager
  pred Key
KeyControlpanel = Key
KeyJournal
  pred Key
KeyAppselect = Key
KeyControlpanel
  pred Key
KeyScreensaver = Key
KeyAppselect
  pred Key
KeyVoicecommand = Key
KeyScreensaver
  pred Key
KeyBrightnessMin = Key
KeyVoicecommand
  pred Key
KeyBrightnessMax = Key
KeyBrightnessMin
  pred Key
KeyKbdinputassistPrev = Key
KeyBrightnessMax
  pred Key
KeyKbdinputassistNext = Key
KeyKbdinputassistPrev
  pred Key
KeyKbdinputassistPrevgroup = Key
KeyKbdinputassistNext
  pred Key
KeyKbdinputassistNextgroup = Key
KeyKbdinputassistPrevgroup
  pred Key
KeyKbdinputassistAccept = Key
KeyKbdinputassistNextgroup
  pred Key
KeyKbdinputassistCancel = Key
KeyKbdinputassistAccept
  pred Key
BtnTriggerHappy = Key
KeyKbdinputassistCancel
  pred Key
BtnTriggerHappy1 = Key
KeyKbdinputassistCancel
  pred Key
BtnTriggerHappy2 = Key
BtnTriggerHappy
  pred Key
BtnTriggerHappy3 = Key
BtnTriggerHappy2
  pred Key
BtnTriggerHappy4 = Key
BtnTriggerHappy3
  pred Key
BtnTriggerHappy5 = Key
BtnTriggerHappy4
  pred Key
BtnTriggerHappy6 = Key
BtnTriggerHappy5
  pred Key
BtnTriggerHappy7 = Key
BtnTriggerHappy6
  pred Key
BtnTriggerHappy8 = Key
BtnTriggerHappy7
  pred Key
BtnTriggerHappy9 = Key
BtnTriggerHappy8
  pred Key
BtnTriggerHappy10 = Key
BtnTriggerHappy9
  pred Key
BtnTriggerHappy11 = Key
BtnTriggerHappy10
  pred Key
BtnTriggerHappy12 = Key
BtnTriggerHappy11
  pred Key
BtnTriggerHappy13 = Key
BtnTriggerHappy12
  pred Key
BtnTriggerHappy14 = Key
BtnTriggerHappy13
  pred Key
BtnTriggerHappy15 = Key
BtnTriggerHappy14
  pred Key
BtnTriggerHappy16 = Key
BtnTriggerHappy15
  pred Key
BtnTriggerHappy17 = Key
BtnTriggerHappy16
  pred Key
BtnTriggerHappy18 = Key
BtnTriggerHappy17
  pred Key
BtnTriggerHappy19 = Key
BtnTriggerHappy18
  pred Key
BtnTriggerHappy20 = Key
BtnTriggerHappy19
  pred Key
BtnTriggerHappy21 = Key
BtnTriggerHappy20
  pred Key
BtnTriggerHappy22 = Key
BtnTriggerHappy21
  pred Key
BtnTriggerHappy23 = Key
BtnTriggerHappy22
  pred Key
BtnTriggerHappy24 = Key
BtnTriggerHappy23
  pred Key
BtnTriggerHappy25 = Key
BtnTriggerHappy24
  pred Key
BtnTriggerHappy26 = Key
BtnTriggerHappy25
  pred Key
BtnTriggerHappy27 = Key
BtnTriggerHappy26
  pred Key
BtnTriggerHappy28 = Key
BtnTriggerHappy27
  pred Key
BtnTriggerHappy29 = Key
BtnTriggerHappy28
  pred Key
BtnTriggerHappy30 = Key
BtnTriggerHappy29
  pred Key
BtnTriggerHappy31 = Key
BtnTriggerHappy30
  pred Key
BtnTriggerHappy32 = Key
BtnTriggerHappy31
  pred Key
BtnTriggerHappy33 = Key
BtnTriggerHappy32
  pred Key
BtnTriggerHappy34 = Key
BtnTriggerHappy33
  pred Key
BtnTriggerHappy35 = Key
BtnTriggerHappy34
  pred Key
BtnTriggerHappy36 = Key
BtnTriggerHappy35
  pred Key
BtnTriggerHappy37 = Key
BtnTriggerHappy36
  pred Key
BtnTriggerHappy38 = Key
BtnTriggerHappy37
  pred Key
BtnTriggerHappy39 = Key
BtnTriggerHappy38
  pred Key
BtnTriggerHappy40 = Key
BtnTriggerHappy39
  pred Key
KeyReserved = forall a. HasCallStack => String -> a
error String
"Key.pred: KeyReserved has no predecessor"

  enumFromTo :: Key -> Key -> [Key]
enumFromTo Key
from Key
to = Key -> [Key]
go Key
from
    where
      end :: Int
end = forall a. Enum a => a -> Int
fromEnum Key
to
      go :: Key -> [Key]
go Key
v = case forall a. Ord a => a -> a -> Ordering
compare (forall a. Enum a => a -> Int
fromEnum Key
v) Int
end of
                 Ordering
LT -> Key
v forall a. a -> [a] -> [a]
: Key -> [Key]
go (forall a. Enum a => a -> a
succ Key
v)
                 Ordering
EQ -> [Key
v]
                 Ordering
GT -> []

  enumFrom :: Key -> [Key]
enumFrom Key
from = forall a. Enum a => a -> a -> [a]
enumFromTo Key
from Key
BtnTriggerHappy40

  fromEnum :: Key -> Int
fromEnum Key
KeyReserved = Int
0
  fromEnum Key
KeyEsc = Int
1
  fromEnum Key
Key1 = Int
2
  fromEnum Key
Key2 = Int
3
  fromEnum Key
Key3 = Int
4
  fromEnum Key
Key4 = Int
5
  fromEnum Key
Key5 = Int
6
  fromEnum Key
Key6 = Int
7
  fromEnum Key
Key7 = Int
8
  fromEnum Key
Key8 = Int
9
  fromEnum Key
Key9 = Int
10
  fromEnum Key
Key0 = Int
11
  fromEnum Key
KeyMinus = Int
12
  fromEnum Key
KeyEqual = Int
13
  fromEnum Key
KeyBackspace = Int
14
  fromEnum Key
KeyTab = Int
15
  fromEnum Key
KeyQ = Int
16
  fromEnum Key
KeyW = Int
17
  fromEnum Key
KeyE = Int
18
  fromEnum Key
KeyR = Int
19
  fromEnum Key
KeyT = Int
20
  fromEnum Key
KeyY = Int
21
  fromEnum Key
KeyU = Int
22
  fromEnum Key
KeyI = Int
23
  fromEnum Key
KeyO = Int
24
  fromEnum Key
KeyP = Int
25
  fromEnum Key
KeyLeftbrace = Int
26
  fromEnum Key
KeyRightbrace = Int
27
  fromEnum Key
KeyEnter = Int
28
  fromEnum Key
KeyLeftctrl = Int
29
  fromEnum Key
KeyA = Int
30
  fromEnum Key
KeyS = Int
31
  fromEnum Key
KeyD = Int
32
  fromEnum Key
KeyF = Int
33
  fromEnum Key
KeyG = Int
34
  fromEnum Key
KeyH = Int
35
  fromEnum Key
KeyJ = Int
36
  fromEnum Key
KeyK = Int
37
  fromEnum Key
KeyL = Int
38
  fromEnum Key
KeySemicolon = Int
39
  fromEnum Key
KeyApostrophe = Int
40
  fromEnum Key
KeyGrave = Int
41
  fromEnum Key
KeyLeftshift = Int
42
  fromEnum Key
KeyBackslash = Int
43
  fromEnum Key
KeyZ = Int
44
  fromEnum Key
KeyX = Int
45
  fromEnum Key
KeyC = Int
46
  fromEnum Key
KeyV = Int
47
  fromEnum Key
KeyB = Int
48
  fromEnum Key
KeyN = Int
49
  fromEnum Key
KeyM = Int
50
  fromEnum Key
KeyComma = Int
51
  fromEnum Key
KeyDot = Int
52
  fromEnum Key
KeySlash = Int
53
  fromEnum Key
KeyRightshift = Int
54
  fromEnum Key
KeyKpasterisk = Int
55
  fromEnum Key
KeyLeftalt = Int
56
  fromEnum Key
KeySpace = Int
57
  fromEnum Key
KeyCapslock = Int
58
  fromEnum Key
KeyF1 = Int
59
  fromEnum Key
KeyF2 = Int
60
  fromEnum Key
KeyF3 = Int
61
  fromEnum Key
KeyF4 = Int
62
  fromEnum Key
KeyF5 = Int
63
  fromEnum Key
KeyF6 = Int
64
  fromEnum Key
KeyF7 = Int
65
  fromEnum Key
KeyF8 = Int
66
  fromEnum Key
KeyF9 = Int
67
  fromEnum Key
KeyF10 = Int
68
  fromEnum Key
KeyNumlock = Int
69
  fromEnum Key
KeyScrolllock = Int
70
  fromEnum Key
KeyKp7 = Int
71
  fromEnum Key
KeyKp8 = Int
72
  fromEnum Key
KeyKp9 = Int
73
  fromEnum Key
KeyKpminus = Int
74
  fromEnum Key
KeyKp4 = Int
75
  fromEnum Key
KeyKp5 = Int
76
  fromEnum Key
KeyKp6 = Int
77
  fromEnum Key
KeyKpplus = Int
78
  fromEnum Key
KeyKp1 = Int
79
  fromEnum Key
KeyKp2 = Int
80
  fromEnum Key
KeyKp3 = Int
81
  fromEnum Key
KeyKp0 = Int
82
  fromEnum Key
KeyKpdot = Int
83
  fromEnum Key
KeyZenkakuhankaku = Int
85
  fromEnum Key
Key102nd = Int
86
  fromEnum Key
KeyF11 = Int
87
  fromEnum Key
KeyF12 = Int
88
  fromEnum Key
KeyRo = Int
89
  fromEnum Key
KeyKatakana = Int
90
  fromEnum Key
KeyHiragana = Int
91
  fromEnum Key
KeyHenkan = Int
92
  fromEnum Key
KeyKatakanahiragana = Int
93
  fromEnum Key
KeyMuhenkan = Int
94
  fromEnum Key
KeyKpjpcomma = Int
95
  fromEnum Key
KeyKpenter = Int
96
  fromEnum Key
KeyRightctrl = Int
97
  fromEnum Key
KeyKpslash = Int
98
  fromEnum Key
KeySysrq = Int
99
  fromEnum Key
KeyRightalt = Int
100
  fromEnum Key
KeyLinefeed = Int
101
  fromEnum Key
KeyHome = Int
102
  fromEnum Key
KeyUp = Int
103
  fromEnum Key
KeyPageup = Int
104
  fromEnum Key
KeyLeft = Int
105
  fromEnum Key
KeyRight = Int
106
  fromEnum Key
KeyEnd = Int
107
  fromEnum Key
KeyDown = Int
108
  fromEnum Key
KeyPagedown = Int
109
  fromEnum Key
KeyInsert = Int
110
  fromEnum Key
KeyDelete = Int
111
  fromEnum Key
KeyMacro = Int
112
  fromEnum Key
KeyMute = Int
113
  fromEnum Key
KeyVolumedown = Int
114
  fromEnum Key
KeyVolumeup = Int
115
  fromEnum Key
KeyPower = Int
116
  fromEnum Key
KeyKpequal = Int
117
  fromEnum Key
KeyKpplusminus = Int
118
  fromEnum Key
KeyPause = Int
119
  fromEnum Key
KeyScale = Int
120
  fromEnum Key
KeyKpcomma = Int
121
  fromEnum Key
KeyHangeul = Int
122
  fromEnum Key
KeyHanguel = Int
122
  fromEnum Key
KeyHanja = Int
123
  fromEnum Key
KeyYen = Int
124
  fromEnum Key
KeyLeftmeta = Int
125
  fromEnum Key
KeyRightmeta = Int
126
  fromEnum Key
KeyCompose = Int
127
  fromEnum Key
KeyStop = Int
128
  fromEnum Key
KeyAgain = Int
129
  fromEnum Key
KeyProps = Int
130
  fromEnum Key
KeyUndo = Int
131
  fromEnum Key
KeyFront = Int
132
  fromEnum Key
KeyCopy = Int
133
  fromEnum Key
KeyOpen = Int
134
  fromEnum Key
KeyPaste = Int
135
  fromEnum Key
KeyFind = Int
136
  fromEnum Key
KeyCut = Int
137
  fromEnum Key
KeyHelp = Int
138
  fromEnum Key
KeyMenu = Int
139
  fromEnum Key
KeyCalc = Int
140
  fromEnum Key
KeySetup = Int
141
  fromEnum Key
KeySleep = Int
142
  fromEnum Key
KeyWakeup = Int
143
  fromEnum Key
KeyFile = Int
144
  fromEnum Key
KeySendfile = Int
145
  fromEnum Key
KeyDeletefile = Int
146
  fromEnum Key
KeyXfer = Int
147
  fromEnum Key
KeyProg1 = Int
148
  fromEnum Key
KeyProg2 = Int
149
  fromEnum Key
KeyWww = Int
150
  fromEnum Key
KeyMsdos = Int
151
  fromEnum Key
KeyCoffee = Int
152
  fromEnum Key
KeyScreenlock = Int
152
  fromEnum Key
KeyRotateDisplay = Int
153
  fromEnum Key
KeyDirection = Int
153
  fromEnum Key
KeyCyclewindows = Int
154
  fromEnum Key
KeyMail = Int
155
  fromEnum Key
KeyBookmarks = Int
156
  fromEnum Key
KeyComputer = Int
157
  fromEnum Key
KeyBack = Int
158
  fromEnum Key
KeyForward = Int
159
  fromEnum Key
KeyClosecd = Int
160
  fromEnum Key
KeyEjectcd = Int
161
  fromEnum Key
KeyEjectclosecd = Int
162
  fromEnum Key
KeyNextsong = Int
163
  fromEnum Key
KeyPlaypause = Int
164
  fromEnum Key
KeyPrevioussong = Int
165
  fromEnum Key
KeyStopcd = Int
166
  fromEnum Key
KeyRecord = Int
167
  fromEnum Key
KeyRewind = Int
168
  fromEnum Key
KeyPhone = Int
169
  fromEnum Key
KeyIso = Int
170
  fromEnum Key
KeyConfig = Int
171
  fromEnum Key
KeyHomepage = Int
172
  fromEnum Key
KeyRefresh = Int
173
  fromEnum Key
KeyExit = Int
174
  fromEnum Key
KeyMove = Int
175
  fromEnum Key
KeyEdit = Int
176
  fromEnum Key
KeyScrollup = Int
177
  fromEnum Key
KeyScrolldown = Int
178
  fromEnum Key
KeyKpleftparen = Int
179
  fromEnum Key
KeyKprightparen = Int
180
  fromEnum Key
KeyNew = Int
181
  fromEnum Key
KeyRedo = Int
182
  fromEnum Key
KeyF13 = Int
183
  fromEnum Key
KeyF14 = Int
184
  fromEnum Key
KeyF15 = Int
185
  fromEnum Key
KeyF16 = Int
186
  fromEnum Key
KeyF17 = Int
187
  fromEnum Key
KeyF18 = Int
188
  fromEnum Key
KeyF19 = Int
189
  fromEnum Key
KeyF20 = Int
190
  fromEnum Key
KeyF21 = Int
191
  fromEnum Key
KeyF22 = Int
192
  fromEnum Key
KeyF23 = Int
193
  fromEnum Key
KeyF24 = Int
194
  fromEnum Key
KeyPlaycd = Int
200
  fromEnum Key
KeyPausecd = Int
201
  fromEnum Key
KeyProg3 = Int
202
  fromEnum Key
KeyProg4 = Int
203
  fromEnum Key
KeyDashboard = Int
204
  fromEnum Key
KeySuspend = Int
205
  fromEnum Key
KeyClose = Int
206
  fromEnum Key
KeyPlay = Int
207
  fromEnum Key
KeyFastforward = Int
208
  fromEnum Key
KeyBassboost = Int
209
  fromEnum Key
KeyPrint = Int
210
  fromEnum Key
KeyHp = Int
211
  fromEnum Key
KeyCamera = Int
212
  fromEnum Key
KeySound = Int
213
  fromEnum Key
KeyQuestion = Int
214
  fromEnum Key
KeyEmail = Int
215
  fromEnum Key
KeyChat = Int
216
  fromEnum Key
KeySearch = Int
217
  fromEnum Key
KeyConnect = Int
218
  fromEnum Key
KeyFinance = Int
219
  fromEnum Key
KeySport = Int
220
  fromEnum Key
KeyShop = Int
221
  fromEnum Key
KeyAlterase = Int
222
  fromEnum Key
KeyCancel = Int
223
  fromEnum Key
KeyBrightnessdown = Int
224
  fromEnum Key
KeyBrightnessup = Int
225
  fromEnum Key
KeyMedia = Int
226
  fromEnum Key
KeySwitchvideomode = Int
227
  fromEnum Key
KeyKbdillumtoggle = Int
228
  fromEnum Key
KeyKbdillumdown = Int
229
  fromEnum Key
KeyKbdillumup = Int
230
  fromEnum Key
KeySend = Int
231
  fromEnum Key
KeyReply = Int
232
  fromEnum Key
KeyForwardmail = Int
233
  fromEnum Key
KeySave = Int
234
  fromEnum Key
KeyDocuments = Int
235
  fromEnum Key
KeyBattery = Int
236
  fromEnum Key
KeyBluetooth = Int
237
  fromEnum Key
KeyWlan = Int
238
  fromEnum Key
KeyUwb = Int
239
  fromEnum Key
KeyUnknown = Int
240
  fromEnum Key
KeyVideoNext = Int
241
  fromEnum Key
KeyVideoPrev = Int
242
  fromEnum Key
KeyBrightnessCycle = Int
243
  fromEnum Key
KeyBrightnessAuto = Int
244
  fromEnum Key
KeyBrightnessZero = Int
244
  fromEnum Key
KeyDisplayOff = Int
245
  fromEnum Key
KeyWwan = Int
246
  fromEnum Key
KeyWimax = Int
246
  fromEnum Key
KeyRfkill = Int
247
  fromEnum Key
KeyMicmute = Int
248
  fromEnum Key
BtnMisc = Int
256
  fromEnum Key
Btn0 = Int
256
  fromEnum Key
Btn1 = Int
257
  fromEnum Key
Btn2 = Int
258
  fromEnum Key
Btn3 = Int
259
  fromEnum Key
Btn4 = Int
260
  fromEnum Key
Btn5 = Int
261
  fromEnum Key
Btn6 = Int
262
  fromEnum Key
Btn7 = Int
263
  fromEnum Key
Btn8 = Int
264
  fromEnum Key
Btn9 = Int
265
  fromEnum Key
BtnMouse = Int
272
  fromEnum Key
BtnLeft = Int
272
  fromEnum Key
BtnRight = Int
273
  fromEnum Key
BtnMiddle = Int
274
  fromEnum Key
BtnSide = Int
275
  fromEnum Key
BtnExtra = Int
276
  fromEnum Key
BtnForward = Int
277
  fromEnum Key
BtnBack = Int
278
  fromEnum Key
BtnTask = Int
279
  fromEnum Key
BtnJoystick = Int
288
  fromEnum Key
BtnTrigger = Int
288
  fromEnum Key
BtnThumb = Int
289
  fromEnum Key
BtnThumb2 = Int
290
  fromEnum Key
BtnTop = Int
291
  fromEnum Key
BtnTop2 = Int
292
  fromEnum Key
BtnPinkie = Int
293
  fromEnum Key
BtnBase = Int
294
  fromEnum Key
BtnBase2 = Int
295
  fromEnum Key
BtnBase3 = Int
296
  fromEnum Key
BtnBase4 = Int
297
  fromEnum Key
BtnBase5 = Int
298
  fromEnum Key
BtnBase6 = Int
299
  fromEnum Key
BtnDead = Int
303
  fromEnum Key
BtnGamepad = Int
304
  fromEnum Key
BtnSouth = Int
304
  fromEnum Key
BtnA = Int
304
  fromEnum Key
BtnEast = Int
305
  fromEnum Key
BtnB = Int
305
  fromEnum Key
BtnC = Int
306
  fromEnum Key
BtnNorth = Int
307
  fromEnum Key
BtnX = Int
307
  fromEnum Key
BtnWest = Int
308
  fromEnum Key
BtnY = Int
308
  fromEnum Key
BtnZ = Int
309
  fromEnum Key
BtnTl = Int
310
  fromEnum Key
BtnTr = Int
311
  fromEnum Key
BtnTl2 = Int
312
  fromEnum Key
BtnTr2 = Int
313
  fromEnum Key
BtnSelect = Int
314
  fromEnum Key
BtnStart = Int
315
  fromEnum Key
BtnMode = Int
316
  fromEnum Key
BtnThumbl = Int
317
  fromEnum Key
BtnThumbr = Int
318
  fromEnum Key
BtnDigi = Int
320
  fromEnum Key
BtnToolPen = Int
320
  fromEnum Key
BtnToolRubber = Int
321
  fromEnum Key
BtnToolBrush = Int
322
  fromEnum Key
BtnToolPencil = Int
323
  fromEnum Key
BtnToolAirbrush = Int
324
  fromEnum Key
BtnToolFinger = Int
325
  fromEnum Key
BtnToolMouse = Int
326
  fromEnum Key
BtnToolLens = Int
327
  fromEnum Key
BtnToolQuinttap = Int
328
  fromEnum Key
BtnTouch = Int
330
  fromEnum Key
BtnStylus = Int
331
  fromEnum Key
BtnStylus2 = Int
332
  fromEnum Key
BtnToolDoubletap = Int
333
  fromEnum Key
BtnToolTripletap = Int
334
  fromEnum Key
BtnToolQuadtap = Int
335
  fromEnum Key
BtnWheel = Int
336
  fromEnum Key
BtnGearDown = Int
336
  fromEnum Key
BtnGearUp = Int
337
  fromEnum Key
KeyOk = Int
352
  fromEnum Key
KeySelect = Int
353
  fromEnum Key
KeyGoto = Int
354
  fromEnum Key
KeyClear = Int
355
  fromEnum Key
KeyPower2 = Int
356
  fromEnum Key
KeyOption = Int
357
  fromEnum Key
KeyInfo = Int
358
  fromEnum Key
KeyTime = Int
359
  fromEnum Key
KeyVendor = Int
360
  fromEnum Key
KeyArchive = Int
361
  fromEnum Key
KeyProgram = Int
362
  fromEnum Key
KeyChannel = Int
363
  fromEnum Key
KeyFavorites = Int
364
  fromEnum Key
KeyEpg = Int
365
  fromEnum Key
KeyPvr = Int
366
  fromEnum Key
KeyMhp = Int
367
  fromEnum Key
KeyLanguage = Int
368
  fromEnum Key
KeyTitle = Int
369
  fromEnum Key
KeySubtitle = Int
370
  fromEnum Key
KeyAngle = Int
371
  fromEnum Key
KeyZoom = Int
372
  fromEnum Key
KeyMode = Int
373
  fromEnum Key
KeyKeyboard = Int
374
  fromEnum Key
KeyScreen = Int
375
  fromEnum Key
KeyPc = Int
376
  fromEnum Key
KeyTv = Int
377
  fromEnum Key
KeyTv2 = Int
378
  fromEnum Key
KeyVcr = Int
379
  fromEnum Key
KeyVcr2 = Int
380
  fromEnum Key
KeySat = Int
381
  fromEnum Key
KeySat2 = Int
382
  fromEnum Key
KeyCd = Int
383
  fromEnum Key
KeyTape = Int
384
  fromEnum Key
KeyRadio = Int
385
  fromEnum Key
KeyTuner = Int
386
  fromEnum Key
KeyPlayer = Int
387
  fromEnum Key
KeyText = Int
388
  fromEnum Key
KeyDvd = Int
389
  fromEnum Key
KeyAux = Int
390
  fromEnum Key
KeyMp3 = Int
391
  fromEnum Key
KeyAudio = Int
392
  fromEnum Key
KeyVideo = Int
393
  fromEnum Key
KeyDirectory = Int
394
  fromEnum Key
KeyList = Int
395
  fromEnum Key
KeyMemo = Int
396
  fromEnum Key
KeyCalendar = Int
397
  fromEnum Key
KeyRed = Int
398
  fromEnum Key
KeyGreen = Int
399
  fromEnum Key
KeyYellow = Int
400
  fromEnum Key
KeyBlue = Int
401
  fromEnum Key
KeyChannelup = Int
402
  fromEnum Key
KeyChanneldown = Int
403
  fromEnum Key
KeyFirst = Int
404
  fromEnum Key
KeyLast = Int
405
  fromEnum Key
KeyAb = Int
406
  fromEnum Key
KeyNext = Int
407
  fromEnum Key
KeyRestart = Int
408
  fromEnum Key
KeySlow = Int
409
  fromEnum Key
KeyShuffle = Int
410
  fromEnum Key
KeyBreak = Int
411
  fromEnum Key
KeyPrevious = Int
412
  fromEnum Key
KeyDigits = Int
413
  fromEnum Key
KeyTeen = Int
414
  fromEnum Key
KeyTwen = Int
415
  fromEnum Key
KeyVideophone = Int
416
  fromEnum Key
KeyGames = Int
417
  fromEnum Key
KeyZoomin = Int
418
  fromEnum Key
KeyZoomout = Int
419
  fromEnum Key
KeyZoomreset = Int
420
  fromEnum Key
KeyWordprocessor = Int
421
  fromEnum Key
KeyEditor = Int
422
  fromEnum Key
KeySpreadsheet = Int
423
  fromEnum Key
KeyGraphicseditor = Int
424
  fromEnum Key
KeyPresentation = Int
425
  fromEnum Key
KeyDatabase = Int
426
  fromEnum Key
KeyNews = Int
427
  fromEnum Key
KeyVoicemail = Int
428
  fromEnum Key
KeyAddressbook = Int
429
  fromEnum Key
KeyMessenger = Int
430
  fromEnum Key
KeyDisplaytoggle = Int
431
  fromEnum Key
KeyBrightnessToggle = Int
431
  fromEnum Key
KeySpellcheck = Int
432
  fromEnum Key
KeyLogoff = Int
433
  fromEnum Key
KeyDollar = Int
434
  fromEnum Key
KeyEuro = Int
435
  fromEnum Key
KeyFrameback = Int
436
  fromEnum Key
KeyFrameforward = Int
437
  fromEnum Key
KeyContextMenu = Int
438
  fromEnum Key
KeyMediaRepeat = Int
439
  fromEnum Key
Key10channelsup = Int
440
  fromEnum Key
Key10channelsdown = Int
441
  fromEnum Key
KeyImages = Int
442
  fromEnum Key
KeyDelEol = Int
448
  fromEnum Key
KeyDelEos = Int
449
  fromEnum Key
KeyInsLine = Int
450
  fromEnum Key
KeyDelLine = Int
451
  fromEnum Key
KeyFn = Int
464
  fromEnum Key
KeyFnEsc = Int
465
  fromEnum Key
KeyFnF1 = Int
466
  fromEnum Key
KeyFnF2 = Int
467
  fromEnum Key
KeyFnF3 = Int
468
  fromEnum Key
KeyFnF4 = Int
469
  fromEnum Key
KeyFnF5 = Int
470
  fromEnum Key
KeyFnF6 = Int
471
  fromEnum Key
KeyFnF7 = Int
472
  fromEnum Key
KeyFnF8 = Int
473
  fromEnum Key
KeyFnF9 = Int
474
  fromEnum Key
KeyFnF10 = Int
475
  fromEnum Key
KeyFnF11 = Int
476
  fromEnum Key
KeyFnF12 = Int
477
  fromEnum Key
KeyFn1 = Int
478
  fromEnum Key
KeyFn2 = Int
479
  fromEnum Key
KeyFnD = Int
480
  fromEnum Key
KeyFnE = Int
481
  fromEnum Key
KeyFnF = Int
482
  fromEnum Key
KeyFnS = Int
483
  fromEnum Key
KeyFnB = Int
484
  fromEnum Key
KeyBrlDot1 = Int
497
  fromEnum Key
KeyBrlDot2 = Int
498
  fromEnum Key
KeyBrlDot3 = Int
499
  fromEnum Key
KeyBrlDot4 = Int
500
  fromEnum Key
KeyBrlDot5 = Int
501
  fromEnum Key
KeyBrlDot6 = Int
502
  fromEnum Key
KeyBrlDot7 = Int
503
  fromEnum Key
KeyBrlDot8 = Int
504
  fromEnum Key
KeyBrlDot9 = Int
505
  fromEnum Key
KeyBrlDot10 = Int
506
  fromEnum Key
KeyNumeric0 = Int
512
  fromEnum Key
KeyNumeric1 = Int
513
  fromEnum Key
KeyNumeric2 = Int
514
  fromEnum Key
KeyNumeric3 = Int
515
  fromEnum Key
KeyNumeric4 = Int
516
  fromEnum Key
KeyNumeric5 = Int
517
  fromEnum Key
KeyNumeric6 = Int
518
  fromEnum Key
KeyNumeric7 = Int
519
  fromEnum Key
KeyNumeric8 = Int
520
  fromEnum Key
KeyNumeric9 = Int
521
  fromEnum Key
KeyNumericStar = Int
522
  fromEnum Key
KeyNumericPound = Int
523
  fromEnum Key
KeyNumericA = Int
524
  fromEnum Key
KeyNumericB = Int
525
  fromEnum Key
KeyNumericC = Int
526
  fromEnum Key
KeyNumericD = Int
527
  fromEnum Key
KeyCameraFocus = Int
528
  fromEnum Key
KeyWpsButton = Int
529
  fromEnum Key
KeyTouchpadToggle = Int
530
  fromEnum Key
KeyTouchpadOn = Int
531
  fromEnum Key
KeyTouchpadOff = Int
532
  fromEnum Key
KeyCameraZoomin = Int
533
  fromEnum Key
KeyCameraZoomout = Int
534
  fromEnum Key
KeyCameraUp = Int
535
  fromEnum Key
KeyCameraDown = Int
536
  fromEnum Key
KeyCameraLeft = Int
537
  fromEnum Key
KeyCameraRight = Int
538
  fromEnum Key
KeyAttendantOn = Int
539
  fromEnum Key
KeyAttendantOff = Int
540
  fromEnum Key
KeyAttendantToggle = Int
541
  fromEnum Key
KeyLightsToggle = Int
542
  fromEnum Key
BtnDpadUp = Int
544
  fromEnum Key
BtnDpadDown = Int
545
  fromEnum Key
BtnDpadLeft = Int
546
  fromEnum Key
BtnDpadRight = Int
547
  fromEnum Key
KeyAlsToggle = Int
560
  fromEnum Key
KeyButtonconfig = Int
576
  fromEnum Key
KeyTaskmanager = Int
577
  fromEnum Key
KeyJournal = Int
578
  fromEnum Key
KeyControlpanel = Int
579
  fromEnum Key
KeyAppselect = Int
580
  fromEnum Key
KeyScreensaver = Int
581
  fromEnum Key
KeyVoicecommand = Int
582
  fromEnum Key
KeyBrightnessMin = Int
592
  fromEnum Key
KeyBrightnessMax = Int
593
  fromEnum Key
KeyKbdinputassistPrev = Int
608
  fromEnum Key
KeyKbdinputassistNext = Int
609
  fromEnum Key
KeyKbdinputassistPrevgroup = Int
610
  fromEnum Key
KeyKbdinputassistNextgroup = Int
611
  fromEnum Key
KeyKbdinputassistAccept = Int
612
  fromEnum Key
KeyKbdinputassistCancel = Int
613
  fromEnum Key
BtnTriggerHappy = Int
704
  fromEnum Key
BtnTriggerHappy1 = Int
704
  fromEnum Key
BtnTriggerHappy2 = Int
705
  fromEnum Key
BtnTriggerHappy3 = Int
706
  fromEnum Key
BtnTriggerHappy4 = Int
707
  fromEnum Key
BtnTriggerHappy5 = Int
708
  fromEnum Key
BtnTriggerHappy6 = Int
709
  fromEnum Key
BtnTriggerHappy7 = Int
710
  fromEnum Key
BtnTriggerHappy8 = Int
711
  fromEnum Key
BtnTriggerHappy9 = Int
712
  fromEnum Key
BtnTriggerHappy10 = Int
713
  fromEnum Key
BtnTriggerHappy11 = Int
714
  fromEnum Key
BtnTriggerHappy12 = Int
715
  fromEnum Key
BtnTriggerHappy13 = Int
716
  fromEnum Key
BtnTriggerHappy14 = Int
717
  fromEnum Key
BtnTriggerHappy15 = Int
718
  fromEnum Key
BtnTriggerHappy16 = Int
719
  fromEnum Key
BtnTriggerHappy17 = Int
720
  fromEnum Key
BtnTriggerHappy18 = Int
721
  fromEnum Key
BtnTriggerHappy19 = Int
722
  fromEnum Key
BtnTriggerHappy20 = Int
723
  fromEnum Key
BtnTriggerHappy21 = Int
724
  fromEnum Key
BtnTriggerHappy22 = Int
725
  fromEnum Key
BtnTriggerHappy23 = Int
726
  fromEnum Key
BtnTriggerHappy24 = Int
727
  fromEnum Key
BtnTriggerHappy25 = Int
728
  fromEnum Key
BtnTriggerHappy26 = Int
729
  fromEnum Key
BtnTriggerHappy27 = Int
730
  fromEnum Key
BtnTriggerHappy28 = Int
731
  fromEnum Key
BtnTriggerHappy29 = Int
732
  fromEnum Key
BtnTriggerHappy30 = Int
733
  fromEnum Key
BtnTriggerHappy31 = Int
734
  fromEnum Key
BtnTriggerHappy32 = Int
735
  fromEnum Key
BtnTriggerHappy33 = Int
736
  fromEnum Key
BtnTriggerHappy34 = Int
737
  fromEnum Key
BtnTriggerHappy35 = Int
738
  fromEnum Key
BtnTriggerHappy36 = Int
739
  fromEnum Key
BtnTriggerHappy37 = Int
740
  fromEnum Key
BtnTriggerHappy38 = Int
741
  fromEnum Key
BtnTriggerHappy39 = Int
742
  fromEnum Key
BtnTriggerHappy40 = Int
743

  toEnum :: Int -> Key
toEnum Int
0 = Key
KeyReserved
  toEnum Int
1 = Key
KeyEsc
  toEnum Int
2 = Key
Key1
  toEnum Int
3 = Key
Key2
  toEnum Int
4 = Key
Key3
  toEnum Int
5 = Key
Key4
  toEnum Int
6 = Key
Key5
  toEnum Int
7 = Key
Key6
  toEnum Int
8 = Key
Key7
  toEnum Int
9 = Key
Key8
  toEnum Int
10 = Key
Key9
  toEnum Int
11 = Key
Key0
  toEnum Int
12 = Key
KeyMinus
  toEnum Int
13 = Key
KeyEqual
  toEnum Int
14 = Key
KeyBackspace
  toEnum Int
15 = Key
KeyTab
  toEnum Int
16 = Key
KeyQ
  toEnum Int
17 = Key
KeyW
  toEnum Int
18 = Key
KeyE
  toEnum Int
19 = Key
KeyR
  toEnum Int
20 = Key
KeyT
  toEnum Int
21 = Key
KeyY
  toEnum Int
22 = Key
KeyU
  toEnum Int
23 = Key
KeyI
  toEnum Int
24 = Key
KeyO
  toEnum Int
25 = Key
KeyP
  toEnum Int
26 = Key
KeyLeftbrace
  toEnum Int
27 = Key
KeyRightbrace
  toEnum Int
28 = Key
KeyEnter
  toEnum Int
29 = Key
KeyLeftctrl
  toEnum Int
30 = Key
KeyA
  toEnum Int
31 = Key
KeyS
  toEnum Int
32 = Key
KeyD
  toEnum Int
33 = Key
KeyF
  toEnum Int
34 = Key
KeyG
  toEnum Int
35 = Key
KeyH
  toEnum Int
36 = Key
KeyJ
  toEnum Int
37 = Key
KeyK
  toEnum Int
38 = Key
KeyL
  toEnum Int
39 = Key
KeySemicolon
  toEnum Int
40 = Key
KeyApostrophe
  toEnum Int
41 = Key
KeyGrave
  toEnum Int
42 = Key
KeyLeftshift
  toEnum Int
43 = Key
KeyBackslash
  toEnum Int
44 = Key
KeyZ
  toEnum Int
45 = Key
KeyX
  toEnum Int
46 = Key
KeyC
  toEnum Int
47 = Key
KeyV
  toEnum Int
48 = Key
KeyB
  toEnum Int
49 = Key
KeyN
  toEnum Int
50 = Key
KeyM
  toEnum Int
51 = Key
KeyComma
  toEnum Int
52 = Key
KeyDot
  toEnum Int
53 = Key
KeySlash
  toEnum Int
54 = Key
KeyRightshift
  toEnum Int
55 = Key
KeyKpasterisk
  toEnum Int
56 = Key
KeyLeftalt
  toEnum Int
57 = Key
KeySpace
  toEnum Int
58 = Key
KeyCapslock
  toEnum Int
59 = Key
KeyF1
  toEnum Int
60 = Key
KeyF2
  toEnum Int
61 = Key
KeyF3
  toEnum Int
62 = Key
KeyF4
  toEnum Int
63 = Key
KeyF5
  toEnum Int
64 = Key
KeyF6
  toEnum Int
65 = Key
KeyF7
  toEnum Int
66 = Key
KeyF8
  toEnum Int
67 = Key
KeyF9
  toEnum Int
68 = Key
KeyF10
  toEnum Int
69 = Key
KeyNumlock
  toEnum Int
70 = Key
KeyScrolllock
  toEnum Int
71 = Key
KeyKp7
  toEnum Int
72 = Key
KeyKp8
  toEnum Int
73 = Key
KeyKp9
  toEnum Int
74 = Key
KeyKpminus
  toEnum Int
75 = Key
KeyKp4
  toEnum Int
76 = Key
KeyKp5
  toEnum Int
77 = Key
KeyKp6
  toEnum Int
78 = Key
KeyKpplus
  toEnum Int
79 = Key
KeyKp1
  toEnum Int
80 = Key
KeyKp2
  toEnum Int
81 = Key
KeyKp3
  toEnum Int
82 = Key
KeyKp0
  toEnum Int
83 = Key
KeyKpdot
  toEnum Int
85 = Key
KeyZenkakuhankaku
  toEnum Int
86 = Key
Key102nd
  toEnum Int
87 = Key
KeyF11
  toEnum Int
88 = Key
KeyF12
  toEnum Int
89 = Key
KeyRo
  toEnum Int
90 = Key
KeyKatakana
  toEnum Int
91 = Key
KeyHiragana
  toEnum Int
92 = Key
KeyHenkan
  toEnum Int
93 = Key
KeyKatakanahiragana
  toEnum Int
94 = Key
KeyMuhenkan
  toEnum Int
95 = Key
KeyKpjpcomma
  toEnum Int
96 = Key
KeyKpenter
  toEnum Int
97 = Key
KeyRightctrl
  toEnum Int
98 = Key
KeyKpslash
  toEnum Int
99 = Key
KeySysrq
  toEnum Int
100 = Key
KeyRightalt
  toEnum Int
101 = Key
KeyLinefeed
  toEnum Int
102 = Key
KeyHome
  toEnum Int
103 = Key
KeyUp
  toEnum Int
104 = Key
KeyPageup
  toEnum Int
105 = Key
KeyLeft
  toEnum Int
106 = Key
KeyRight
  toEnum Int
107 = Key
KeyEnd
  toEnum Int
108 = Key
KeyDown
  toEnum Int
109 = Key
KeyPagedown
  toEnum Int
110 = Key
KeyInsert
  toEnum Int
111 = Key
KeyDelete
  toEnum Int
112 = Key
KeyMacro
  toEnum Int
113 = Key
KeyMute
  toEnum Int
114 = Key
KeyVolumedown
  toEnum Int
115 = Key
KeyVolumeup
  toEnum Int
116 = Key
KeyPower
  toEnum Int
117 = Key
KeyKpequal
  toEnum Int
118 = Key
KeyKpplusminus
  toEnum Int
119 = Key
KeyPause
  toEnum Int
120 = Key
KeyScale
  toEnum Int
121 = Key
KeyKpcomma
  toEnum Int
122 = Key
KeyHangeul
  toEnum Int
123 = Key
KeyHanja
  toEnum Int
124 = Key
KeyYen
  toEnum Int
125 = Key
KeyLeftmeta
  toEnum Int
126 = Key
KeyRightmeta
  toEnum Int
127 = Key
KeyCompose
  toEnum Int
128 = Key
KeyStop
  toEnum Int
129 = Key
KeyAgain
  toEnum Int
130 = Key
KeyProps
  toEnum Int
131 = Key
KeyUndo
  toEnum Int
132 = Key
KeyFront
  toEnum Int
133 = Key
KeyCopy
  toEnum Int
134 = Key
KeyOpen
  toEnum Int
135 = Key
KeyPaste
  toEnum Int
136 = Key
KeyFind
  toEnum Int
137 = Key
KeyCut
  toEnum Int
138 = Key
KeyHelp
  toEnum Int
139 = Key
KeyMenu
  toEnum Int
140 = Key
KeyCalc
  toEnum Int
141 = Key
KeySetup
  toEnum Int
142 = Key
KeySleep
  toEnum Int
143 = Key
KeyWakeup
  toEnum Int
144 = Key
KeyFile
  toEnum Int
145 = Key
KeySendfile
  toEnum Int
146 = Key
KeyDeletefile
  toEnum Int
147 = Key
KeyXfer
  toEnum Int
148 = Key
KeyProg1
  toEnum Int
149 = Key
KeyProg2
  toEnum Int
150 = Key
KeyWww
  toEnum Int
151 = Key
KeyMsdos
  toEnum Int
152 = Key
KeyCoffee
  toEnum Int
153 = Key
KeyRotateDisplay
  toEnum Int
154 = Key
KeyCyclewindows
  toEnum Int
155 = Key
KeyMail
  toEnum Int
156 = Key
KeyBookmarks
  toEnum Int
157 = Key
KeyComputer
  toEnum Int
158 = Key
KeyBack
  toEnum Int
159 = Key
KeyForward
  toEnum Int
160 = Key
KeyClosecd
  toEnum Int
161 = Key
KeyEjectcd
  toEnum Int
162 = Key
KeyEjectclosecd
  toEnum Int
163 = Key
KeyNextsong
  toEnum Int
164 = Key
KeyPlaypause
  toEnum Int
165 = Key
KeyPrevioussong
  toEnum Int
166 = Key
KeyStopcd
  toEnum Int
167 = Key
KeyRecord
  toEnum Int
168 = Key
KeyRewind
  toEnum Int
169 = Key
KeyPhone
  toEnum Int
170 = Key
KeyIso
  toEnum Int
171 = Key
KeyConfig
  toEnum Int
172 = Key
KeyHomepage
  toEnum Int
173 = Key
KeyRefresh
  toEnum Int
174 = Key
KeyExit
  toEnum Int
175 = Key
KeyMove
  toEnum Int
176 = Key
KeyEdit
  toEnum Int
177 = Key
KeyScrollup
  toEnum Int
178 = Key
KeyScrolldown
  toEnum Int
179 = Key
KeyKpleftparen
  toEnum Int
180 = Key
KeyKprightparen
  toEnum Int
181 = Key
KeyNew
  toEnum Int
182 = Key
KeyRedo
  toEnum Int
183 = Key
KeyF13
  toEnum Int
184 = Key
KeyF14
  toEnum Int
185 = Key
KeyF15
  toEnum Int
186 = Key
KeyF16
  toEnum Int
187 = Key
KeyF17
  toEnum Int
188 = Key
KeyF18
  toEnum Int
189 = Key
KeyF19
  toEnum Int
190 = Key
KeyF20
  toEnum Int
191 = Key
KeyF21
  toEnum Int
192 = Key
KeyF22
  toEnum Int
193 = Key
KeyF23
  toEnum Int
194 = Key
KeyF24
  toEnum Int
200 = Key
KeyPlaycd
  toEnum Int
201 = Key
KeyPausecd
  toEnum Int
202 = Key
KeyProg3
  toEnum Int
203 = Key
KeyProg4
  toEnum Int
204 = Key
KeyDashboard
  toEnum Int
205 = Key
KeySuspend
  toEnum Int
206 = Key
KeyClose
  toEnum Int
207 = Key
KeyPlay
  toEnum Int
208 = Key
KeyFastforward
  toEnum Int
209 = Key
KeyBassboost
  toEnum Int
210 = Key
KeyPrint
  toEnum Int
211 = Key
KeyHp
  toEnum Int
212 = Key
KeyCamera
  toEnum Int
213 = Key
KeySound
  toEnum Int
214 = Key
KeyQuestion
  toEnum Int
215 = Key
KeyEmail
  toEnum Int
216 = Key
KeyChat
  toEnum Int
217 = Key
KeySearch
  toEnum Int
218 = Key
KeyConnect
  toEnum Int
219 = Key
KeyFinance
  toEnum Int
220 = Key
KeySport
  toEnum Int
221 = Key
KeyShop
  toEnum Int
222 = Key
KeyAlterase
  toEnum Int
223 = Key
KeyCancel
  toEnum Int
224 = Key
KeyBrightnessdown
  toEnum Int
225 = Key
KeyBrightnessup
  toEnum Int
226 = Key
KeyMedia
  toEnum Int
227 = Key
KeySwitchvideomode
  toEnum Int
228 = Key
KeyKbdillumtoggle
  toEnum Int
229 = Key
KeyKbdillumdown
  toEnum Int
230 = Key
KeyKbdillumup
  toEnum Int
231 = Key
KeySend
  toEnum Int
232 = Key
KeyReply
  toEnum Int
233 = Key
KeyForwardmail
  toEnum Int
234 = Key
KeySave
  toEnum Int
235 = Key
KeyDocuments
  toEnum Int
236 = Key
KeyBattery
  toEnum Int
237 = Key
KeyBluetooth
  toEnum Int
238 = Key
KeyWlan
  toEnum Int
239 = Key
KeyUwb
  toEnum Int
240 = Key
KeyUnknown
  toEnum Int
241 = Key
KeyVideoNext
  toEnum Int
242 = Key
KeyVideoPrev
  toEnum Int
243 = Key
KeyBrightnessCycle
  toEnum Int
244 = Key
KeyBrightnessAuto
  toEnum Int
245 = Key
KeyDisplayOff
  toEnum Int
246 = Key
KeyWwan
  toEnum Int
247 = Key
KeyRfkill
  toEnum Int
248 = Key
KeyMicmute
  toEnum Int
256 = Key
BtnMisc
  toEnum Int
257 = Key
Btn1
  toEnum Int
258 = Key
Btn2
  toEnum Int
259 = Key
Btn3
  toEnum Int
260 = Key
Btn4
  toEnum Int
261 = Key
Btn5
  toEnum Int
262 = Key
Btn6
  toEnum Int
263 = Key
Btn7
  toEnum Int
264 = Key
Btn8
  toEnum Int
265 = Key
Btn9
  toEnum Int
272 = Key
BtnMouse
  toEnum Int
273 = Key
BtnRight
  toEnum Int
274 = Key
BtnMiddle
  toEnum Int
275 = Key
BtnSide
  toEnum Int
276 = Key
BtnExtra
  toEnum Int
277 = Key
BtnForward
  toEnum Int
278 = Key
BtnBack
  toEnum Int
279 = Key
BtnTask
  toEnum Int
288 = Key
BtnJoystick
  toEnum Int
289 = Key
BtnThumb
  toEnum Int
290 = Key
BtnThumb2
  toEnum Int
291 = Key
BtnTop
  toEnum Int
292 = Key
BtnTop2
  toEnum Int
293 = Key
BtnPinkie
  toEnum Int
294 = Key
BtnBase
  toEnum Int
295 = Key
BtnBase2
  toEnum Int
296 = Key
BtnBase3
  toEnum Int
297 = Key
BtnBase4
  toEnum Int
298 = Key
BtnBase5
  toEnum Int
299 = Key
BtnBase6
  toEnum Int
303 = Key
BtnDead
  toEnum Int
304 = Key
BtnGamepad
  toEnum Int
305 = Key
BtnEast
  toEnum Int
306 = Key
BtnC
  toEnum Int
307 = Key
BtnNorth
  toEnum Int
308 = Key
BtnWest
  toEnum Int
309 = Key
BtnZ
  toEnum Int
310 = Key
BtnTl
  toEnum Int
311 = Key
BtnTr
  toEnum Int
312 = Key
BtnTl2
  toEnum Int
313 = Key
BtnTr2
  toEnum Int
314 = Key
BtnSelect
  toEnum Int
315 = Key
BtnStart
  toEnum Int
316 = Key
BtnMode
  toEnum Int
317 = Key
BtnThumbl
  toEnum Int
318 = Key
BtnThumbr
  toEnum Int
320 = Key
BtnDigi
  toEnum Int
321 = Key
BtnToolRubber
  toEnum Int
322 = Key
BtnToolBrush
  toEnum Int
323 = Key
BtnToolPencil
  toEnum Int
324 = Key
BtnToolAirbrush
  toEnum Int
325 = Key
BtnToolFinger
  toEnum Int
326 = Key
BtnToolMouse
  toEnum Int
327 = Key
BtnToolLens
  toEnum Int
328 = Key
BtnToolQuinttap
  toEnum Int
330 = Key
BtnTouch
  toEnum Int
331 = Key
BtnStylus
  toEnum Int
332 = Key
BtnStylus2
  toEnum Int
333 = Key
BtnToolDoubletap
  toEnum Int
334 = Key
BtnToolTripletap
  toEnum Int
335 = Key
BtnToolQuadtap
  toEnum Int
336 = Key
BtnWheel
  toEnum Int
337 = Key
BtnGearUp
  toEnum Int
352 = Key
KeyOk
  toEnum Int
353 = Key
KeySelect
  toEnum Int
354 = Key
KeyGoto
  toEnum Int
355 = Key
KeyClear
  toEnum Int
356 = Key
KeyPower2
  toEnum Int
357 = Key
KeyOption
  toEnum Int
358 = Key
KeyInfo
  toEnum Int
359 = Key
KeyTime
  toEnum Int
360 = Key
KeyVendor
  toEnum Int
361 = Key
KeyArchive
  toEnum Int
362 = Key
KeyProgram
  toEnum Int
363 = Key
KeyChannel
  toEnum Int
364 = Key
KeyFavorites
  toEnum Int
365 = Key
KeyEpg
  toEnum Int
366 = Key
KeyPvr
  toEnum Int
367 = Key
KeyMhp
  toEnum Int
368 = Key
KeyLanguage
  toEnum Int
369 = Key
KeyTitle
  toEnum Int
370 = Key
KeySubtitle
  toEnum Int
371 = Key
KeyAngle
  toEnum Int
372 = Key
KeyZoom
  toEnum Int
373 = Key
KeyMode
  toEnum Int
374 = Key
KeyKeyboard
  toEnum Int
375 = Key
KeyScreen
  toEnum Int
376 = Key
KeyPc
  toEnum Int
377 = Key
KeyTv
  toEnum Int
378 = Key
KeyTv2
  toEnum Int
379 = Key
KeyVcr
  toEnum Int
380 = Key
KeyVcr2
  toEnum Int
381 = Key
KeySat
  toEnum Int
382 = Key
KeySat2
  toEnum Int
383 = Key
KeyCd
  toEnum Int
384 = Key
KeyTape
  toEnum Int
385 = Key
KeyRadio
  toEnum Int
386 = Key
KeyTuner
  toEnum Int
387 = Key
KeyPlayer
  toEnum Int
388 = Key
KeyText
  toEnum Int
389 = Key
KeyDvd
  toEnum Int
390 = Key
KeyAux
  toEnum Int
391 = Key
KeyMp3
  toEnum Int
392 = Key
KeyAudio
  toEnum Int
393 = Key
KeyVideo
  toEnum Int
394 = Key
KeyDirectory
  toEnum Int
395 = Key
KeyList
  toEnum Int
396 = Key
KeyMemo
  toEnum Int
397 = Key
KeyCalendar
  toEnum Int
398 = Key
KeyRed
  toEnum Int
399 = Key
KeyGreen
  toEnum Int
400 = Key
KeyYellow
  toEnum Int
401 = Key
KeyBlue
  toEnum Int
402 = Key
KeyChannelup
  toEnum Int
403 = Key
KeyChanneldown
  toEnum Int
404 = Key
KeyFirst
  toEnum Int
405 = Key
KeyLast
  toEnum Int
406 = Key
KeyAb
  toEnum Int
407 = Key
KeyNext
  toEnum Int
408 = Key
KeyRestart
  toEnum Int
409 = Key
KeySlow
  toEnum Int
410 = Key
KeyShuffle
  toEnum Int
411 = Key
KeyBreak
  toEnum Int
412 = Key
KeyPrevious
  toEnum Int
413 = Key
KeyDigits
  toEnum Int
414 = Key
KeyTeen
  toEnum Int
415 = Key
KeyTwen
  toEnum Int
416 = Key
KeyVideophone
  toEnum Int
417 = Key
KeyGames
  toEnum Int
418 = Key
KeyZoomin
  toEnum Int
419 = Key
KeyZoomout
  toEnum Int
420 = Key
KeyZoomreset
  toEnum Int
421 = Key
KeyWordprocessor
  toEnum Int
422 = Key
KeyEditor
  toEnum Int
423 = Key
KeySpreadsheet
  toEnum Int
424 = Key
KeyGraphicseditor
  toEnum Int
425 = Key
KeyPresentation
  toEnum Int
426 = Key
KeyDatabase
  toEnum Int
427 = Key
KeyNews
  toEnum Int
428 = Key
KeyVoicemail
  toEnum Int
429 = Key
KeyAddressbook
  toEnum Int
430 = Key
KeyMessenger
  toEnum Int
431 = Key
KeyDisplaytoggle
  toEnum Int
432 = Key
KeySpellcheck
  toEnum Int
433 = Key
KeyLogoff
  toEnum Int
434 = Key
KeyDollar
  toEnum Int
435 = Key
KeyEuro
  toEnum Int
436 = Key
KeyFrameback
  toEnum Int
437 = Key
KeyFrameforward
  toEnum Int
438 = Key
KeyContextMenu
  toEnum Int
439 = Key
KeyMediaRepeat
  toEnum Int
440 = Key
Key10channelsup
  toEnum Int
441 = Key
Key10channelsdown
  toEnum Int
442 = Key
KeyImages
  toEnum Int
448 = Key
KeyDelEol
  toEnum Int
449 = Key
KeyDelEos
  toEnum Int
450 = Key
KeyInsLine
  toEnum Int
451 = Key
KeyDelLine
  toEnum Int
464 = Key
KeyFn
  toEnum Int
465 = Key
KeyFnEsc
  toEnum Int
466 = Key
KeyFnF1
  toEnum Int
467 = Key
KeyFnF2
  toEnum Int
468 = Key
KeyFnF3
  toEnum Int
469 = Key
KeyFnF4
  toEnum Int
470 = Key
KeyFnF5
  toEnum Int
471 = Key
KeyFnF6
  toEnum Int
472 = Key
KeyFnF7
  toEnum Int
473 = Key
KeyFnF8
  toEnum Int
474 = Key
KeyFnF9
  toEnum Int
475 = Key
KeyFnF10
  toEnum Int
476 = Key
KeyFnF11
  toEnum Int
477 = Key
KeyFnF12
  toEnum Int
478 = Key
KeyFn1
  toEnum Int
479 = Key
KeyFn2
  toEnum Int
480 = Key
KeyFnD
  toEnum Int
481 = Key
KeyFnE
  toEnum Int
482 = Key
KeyFnF
  toEnum Int
483 = Key
KeyFnS
  toEnum Int
484 = Key
KeyFnB
  toEnum Int
497 = Key
KeyBrlDot1
  toEnum Int
498 = Key
KeyBrlDot2
  toEnum Int
499 = Key
KeyBrlDot3
  toEnum Int
500 = Key
KeyBrlDot4
  toEnum Int
501 = Key
KeyBrlDot5
  toEnum Int
502 = Key
KeyBrlDot6
  toEnum Int
503 = Key
KeyBrlDot7
  toEnum Int
504 = Key
KeyBrlDot8
  toEnum Int
505 = Key
KeyBrlDot9
  toEnum Int
506 = Key
KeyBrlDot10
  toEnum Int
512 = Key
KeyNumeric0
  toEnum Int
513 = Key
KeyNumeric1
  toEnum Int
514 = Key
KeyNumeric2
  toEnum Int
515 = Key
KeyNumeric3
  toEnum Int
516 = Key
KeyNumeric4
  toEnum Int
517 = Key
KeyNumeric5
  toEnum Int
518 = Key
KeyNumeric6
  toEnum Int
519 = Key
KeyNumeric7
  toEnum Int
520 = Key
KeyNumeric8
  toEnum Int
521 = Key
KeyNumeric9
  toEnum Int
522 = Key
KeyNumericStar
  toEnum Int
523 = Key
KeyNumericPound
  toEnum Int
524 = Key
KeyNumericA
  toEnum Int
525 = Key
KeyNumericB
  toEnum Int
526 = Key
KeyNumericC
  toEnum Int
527 = Key
KeyNumericD
  toEnum Int
528 = Key
KeyCameraFocus
  toEnum Int
529 = Key
KeyWpsButton
  toEnum Int
530 = Key
KeyTouchpadToggle
  toEnum Int
531 = Key
KeyTouchpadOn
  toEnum Int
532 = Key
KeyTouchpadOff
  toEnum Int
533 = Key
KeyCameraZoomin
  toEnum Int
534 = Key
KeyCameraZoomout
  toEnum Int
535 = Key
KeyCameraUp
  toEnum Int
536 = Key
KeyCameraDown
  toEnum Int
537 = Key
KeyCameraLeft
  toEnum Int
538 = Key
KeyCameraRight
  toEnum Int
539 = Key
KeyAttendantOn
  toEnum Int
540 = Key
KeyAttendantOff
  toEnum Int
541 = Key
KeyAttendantToggle
  toEnum Int
542 = Key
KeyLightsToggle
  toEnum Int
544 = Key
BtnDpadUp
  toEnum Int
545 = Key
BtnDpadDown
  toEnum Int
546 = Key
BtnDpadLeft
  toEnum Int
547 = Key
BtnDpadRight
  toEnum Int
560 = Key
KeyAlsToggle
  toEnum Int
576 = Key
KeyButtonconfig
  toEnum Int
577 = Key
KeyTaskmanager
  toEnum Int
578 = Key
KeyJournal
  toEnum Int
579 = Key
KeyControlpanel
  toEnum Int
580 = Key
KeyAppselect
  toEnum Int
581 = Key
KeyScreensaver
  toEnum Int
582 = Key
KeyVoicecommand
  toEnum Int
592 = Key
KeyBrightnessMin
  toEnum Int
593 = Key
KeyBrightnessMax
  toEnum Int
608 = Key
KeyKbdinputassistPrev
  toEnum Int
609 = Key
KeyKbdinputassistNext
  toEnum Int
610 = Key
KeyKbdinputassistPrevgroup
  toEnum Int
611 = Key
KeyKbdinputassistNextgroup
  toEnum Int
612 = Key
KeyKbdinputassistAccept
  toEnum Int
613 = Key
KeyKbdinputassistCancel
  toEnum Int
704 = Key
BtnTriggerHappy
  toEnum Int
705 = Key
BtnTriggerHappy2
  toEnum Int
706 = Key
BtnTriggerHappy3
  toEnum Int
707 = Key
BtnTriggerHappy4
  toEnum Int
708 = Key
BtnTriggerHappy5
  toEnum Int
709 = Key
BtnTriggerHappy6
  toEnum Int
710 = Key
BtnTriggerHappy7
  toEnum Int
711 = Key
BtnTriggerHappy8
  toEnum Int
712 = Key
BtnTriggerHappy9
  toEnum Int
713 = Key
BtnTriggerHappy10
  toEnum Int
714 = Key
BtnTriggerHappy11
  toEnum Int
715 = Key
BtnTriggerHappy12
  toEnum Int
716 = Key
BtnTriggerHappy13
  toEnum Int
717 = Key
BtnTriggerHappy14
  toEnum Int
718 = Key
BtnTriggerHappy15
  toEnum Int
719 = Key
BtnTriggerHappy16
  toEnum Int
720 = Key
BtnTriggerHappy17
  toEnum Int
721 = Key
BtnTriggerHappy18
  toEnum Int
722 = Key
BtnTriggerHappy19
  toEnum Int
723 = Key
BtnTriggerHappy20
  toEnum Int
724 = Key
BtnTriggerHappy21
  toEnum Int
725 = Key
BtnTriggerHappy22
  toEnum Int
726 = Key
BtnTriggerHappy23
  toEnum Int
727 = Key
BtnTriggerHappy24
  toEnum Int
728 = Key
BtnTriggerHappy25
  toEnum Int
729 = Key
BtnTriggerHappy26
  toEnum Int
730 = Key
BtnTriggerHappy27
  toEnum Int
731 = Key
BtnTriggerHappy28
  toEnum Int
732 = Key
BtnTriggerHappy29
  toEnum Int
733 = Key
BtnTriggerHappy30
  toEnum Int
734 = Key
BtnTriggerHappy31
  toEnum Int
735 = Key
BtnTriggerHappy32
  toEnum Int
736 = Key
BtnTriggerHappy33
  toEnum Int
737 = Key
BtnTriggerHappy34
  toEnum Int
738 = Key
BtnTriggerHappy35
  toEnum Int
739 = Key
BtnTriggerHappy36
  toEnum Int
740 = Key
BtnTriggerHappy37
  toEnum Int
741 = Key
BtnTriggerHappy38
  toEnum Int
742 = Key
BtnTriggerHappy39
  toEnum Int
743 = Key
BtnTriggerHappy40
  toEnum Int
unmatched = forall a. HasCallStack => String -> a
error (String
"Key.toEnum: Cannot match " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
unmatched)

{-# LINE 582 "src/Evdev/Codes.chs" #-}


-- | Relative changes
data RelativeAxis = RelX
                  | RelY
                  | RelZ
                  | RelRx
                  | RelRy
                  | RelRz
                  | RelHwheel
                  | RelDial
                  | RelWheel
                  | RelMisc
                  | RelReserved
                  | RelWheelHiRes
                  | RelHWheelHiRes
  deriving (Bounded,Eq,Ord,Read,Show)
instance Enum RelativeAxis where
  succ RelX = RelY
  succ RelY = RelZ
  succ RelZ = RelRx
  succ RelRx = RelRy
  succ RelRy = RelRz
  succ RelRz = RelHwheel
  succ RelHwheel = RelDial
  succ RelDial = RelWheel
  succ RelWheel = RelMisc
  succ RelMisc = RelReserved
  succ RelReserved = RelWheelHiRes
  succ RelWheelHiRes = RelHWheelHiRes
  succ RelHWheelHiRes = error "RelativeAxis.succ: RelHWheelHiRes has no successor"

  pred RelY = RelX
  pred RelZ = RelY
  pred RelRx = RelZ
  pred RelRy = RelRx
  pred RelRz = RelRy
  pred RelHwheel = RelRz
  pred RelDial = RelHwheel
  pred RelWheel = RelDial
  pred RelMisc = RelWheel
  pred RelReserved = RelMisc
  pred RelWheelHiRes = RelReserved
  pred RelHWheelHiRes = RelWheelHiRes
  pred RelX = error "RelativeAxis.pred: RelX has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from RelHWheelHiRes

  fromEnum RelX = 0
  fromEnum RelY = 1
  fromEnum RelZ = 2
  fromEnum RelRx = 3
  fromEnum RelRy = 4
  fromEnum RelRz = 5
  fromEnum RelHwheel = 6
  fromEnum RelDial = 7
  fromEnum RelWheel = 8
  fromEnum RelMisc = 9
  fromEnum RelReserved = 10
  fromEnum RelWheelHiRes = 11
  fromEnum RelHWheelHiRes = 12

  toEnum 0 = RelX
  toEnum 1 = RelY
  toEnum 2 = RelZ
  toEnum 3 = RelRx
  toEnum 4 = RelRy
  toEnum 5 = RelRz
  toEnum 6 = RelHwheel
  toEnum 7 = RelDial
  toEnum 8 = RelWheel
  toEnum 9 = RelMisc
  toEnum 10 = RelReserved
  toEnum 11 = RelWheelHiRes
  toEnum 12 = RelHWheelHiRes
  toEnum unmatched = error ("RelativeAxis.toEnum: Cannot match " ++ show unmatched)

{-# LINE 615 "src/Evdev/Codes.chs" #-}


-- | Absolute changes
data AbsoluteAxis = AbsX
                  | AbsY
                  | AbsZ
                  | AbsRx
                  | AbsRy
                  | AbsRz
                  | AbsThrottle
                  | AbsRudder
                  | AbsWheel
                  | AbsGas
                  | AbsBrake
                  | AbsHat0x
                  | AbsHat0y
                  | AbsHat1x
                  | AbsHat1y
                  | AbsHat2x
                  | AbsHat2y
                  | AbsHat3x
                  | AbsHat3y
                  | AbsPressure
                  | AbsDistance
                  | AbsTiltX
                  | AbsTiltY
                  | AbsToolWidth
                  | AbsVolume
                  | AbsMisc
                  | AbsReserved
                  | AbsMtSlot
                  | AbsMtTouchMajor
                  | AbsMtTouchMinor
                  | AbsMtWidthMajor
                  | AbsMtWidthMinor
                  | AbsMtOrientation
                  | AbsMtPositionX
                  | AbsMtPositionY
                  | AbsMtToolType
                  | AbsMtBlobId
                  | AbsMtTrackingId
                  | AbsMtPressure
                  | AbsMtDistance
                  | AbsMtToolX
                  | AbsMtToolY
  deriving (Bounded,Eq,Ord,Read,Show)
instance Enum AbsoluteAxis where
  succ AbsX = AbsY
  succ AbsY = AbsZ
  succ AbsZ = AbsRx
  succ AbsRx = AbsRy
  succ AbsRy = AbsRz
  succ AbsRz = AbsThrottle
  succ AbsThrottle = AbsRudder
  succ AbsRudder = AbsWheel
  succ AbsWheel = AbsGas
  succ AbsGas = AbsBrake
  succ AbsBrake = AbsHat0x
  succ AbsHat0x = AbsHat0y
  succ AbsHat0y = AbsHat1x
  succ AbsHat1x = AbsHat1y
  succ AbsHat1y = AbsHat2x
  succ AbsHat2x = AbsHat2y
  succ AbsHat2y = AbsHat3x
  succ AbsHat3x = AbsHat3y
  succ AbsHat3y = AbsPressure
  succ AbsPressure = AbsDistance
  succ AbsDistance = AbsTiltX
  succ AbsTiltX = AbsTiltY
  succ AbsTiltY = AbsToolWidth
  succ AbsToolWidth = AbsVolume
  succ AbsVolume = AbsMisc
  succ AbsMisc = AbsReserved
  succ AbsReserved = AbsMtSlot
  succ AbsMtSlot = AbsMtTouchMajor
  succ AbsMtTouchMajor = AbsMtTouchMinor
  succ AbsMtTouchMinor = AbsMtWidthMajor
  succ AbsMtWidthMajor = AbsMtWidthMinor
  succ AbsMtWidthMinor = AbsMtOrientation
  succ AbsMtOrientation = AbsMtPositionX
  succ AbsMtPositionX = AbsMtPositionY
  succ AbsMtPositionY = AbsMtToolType
  succ AbsMtToolType = AbsMtBlobId
  succ AbsMtBlobId = AbsMtTrackingId
  succ AbsMtTrackingId = AbsMtPressure
  succ AbsMtPressure = AbsMtDistance
  succ AbsMtDistance = AbsMtToolX
  succ AbsMtToolX = AbsMtToolY
  succ AbsMtToolY = error "AbsoluteAxis.succ: AbsMtToolY has no successor"

  pred AbsY = AbsX
  pred AbsZ = AbsY
  pred AbsRx = AbsZ
  pred AbsRy = AbsRx
  pred AbsRz = AbsRy
  pred AbsThrottle = AbsRz
  pred AbsRudder = AbsThrottle
  pred AbsWheel = AbsRudder
  pred AbsGas = AbsWheel
  pred AbsBrake = AbsGas
  pred AbsHat0x = AbsBrake
  pred AbsHat0y = AbsHat0x
  pred AbsHat1x = AbsHat0y
  pred AbsHat1y = AbsHat1x
  pred AbsHat2x = AbsHat1y
  pred AbsHat2y = AbsHat2x
  pred AbsHat3x = AbsHat2y
  pred AbsHat3y = AbsHat3x
  pred AbsPressure = AbsHat3y
  pred AbsDistance = AbsPressure
  pred AbsTiltX = AbsDistance
  pred AbsTiltY = AbsTiltX
  pred AbsToolWidth = AbsTiltY
  pred AbsVolume = AbsToolWidth
  pred AbsMisc = AbsVolume
  pred AbsReserved = AbsMisc
  pred AbsMtSlot = AbsReserved
  pred AbsMtTouchMajor = AbsMtSlot
  pred AbsMtTouchMinor = AbsMtTouchMajor
  pred AbsMtWidthMajor = AbsMtTouchMinor
  pred AbsMtWidthMinor = AbsMtWidthMajor
  pred AbsMtOrientation = AbsMtWidthMinor
  pred AbsMtPositionX = AbsMtOrientation
  pred AbsMtPositionY = AbsMtPositionX
  pred AbsMtToolType = AbsMtPositionY
  pred AbsMtBlobId = AbsMtToolType
  pred AbsMtTrackingId = AbsMtBlobId
  pred AbsMtPressure = AbsMtTrackingId
  pred AbsMtDistance = AbsMtPressure
  pred AbsMtToolX = AbsMtDistance
  pred AbsMtToolY = AbsMtToolX
  pred AbsX = error "AbsoluteAxis.pred: AbsX has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from AbsMtToolY

  fromEnum AbsX = 0
  fromEnum AbsY = 1
  fromEnum AbsZ = 2
  fromEnum AbsRx = 3
  fromEnum AbsRy = 4
  fromEnum AbsRz = 5
  fromEnum AbsThrottle = 6
  fromEnum AbsRudder = 7
  fromEnum AbsWheel = 8
  fromEnum AbsGas = 9
  fromEnum AbsBrake = 10
  fromEnum AbsHat0x = 16
  fromEnum AbsHat0y = 17
  fromEnum AbsHat1x = 18
  fromEnum AbsHat1y = 19
  fromEnum AbsHat2x = 20
  fromEnum AbsHat2y = 21
  fromEnum AbsHat3x = 22
  fromEnum AbsHat3y = 23
  fromEnum AbsPressure = 24
  fromEnum AbsDistance = 25
  fromEnum AbsTiltX = 26
  fromEnum AbsTiltY = 27
  fromEnum AbsToolWidth = 28
  fromEnum AbsVolume = 32
  fromEnum AbsMisc = 40
  fromEnum AbsReserved = 46
  fromEnum AbsMtSlot = 47
  fromEnum AbsMtTouchMajor = 48
  fromEnum AbsMtTouchMinor = 49
  fromEnum AbsMtWidthMajor = 50
  fromEnum AbsMtWidthMinor = 51
  fromEnum AbsMtOrientation = 52
  fromEnum AbsMtPositionX = 53
  fromEnum AbsMtPositionY = 54
  fromEnum AbsMtToolType = 55
  fromEnum AbsMtBlobId = 56
  fromEnum AbsMtTrackingId = 57
  fromEnum AbsMtPressure = 58
  fromEnum AbsMtDistance = 59
  fromEnum AbsMtToolX = 60
  fromEnum AbsMtToolY = 61

  toEnum 0 = AbsX
  toEnum 1 = AbsY
  toEnum 2 = AbsZ
  toEnum 3 = AbsRx
  toEnum 4 = AbsRy
  toEnum 5 = AbsRz
  toEnum 6 = AbsThrottle
  toEnum 7 = AbsRudder
  toEnum 8 = AbsWheel
  toEnum 9 = AbsGas
  toEnum 10 = AbsBrake
  toEnum 16 = AbsHat0x
  toEnum 17 = AbsHat0y
  toEnum 18 = AbsHat1x
  toEnum 19 = AbsHat1y
  toEnum 20 = AbsHat2x
  toEnum 21 = AbsHat2y
  toEnum 22 = AbsHat3x
  toEnum 23 = AbsHat3y
  toEnum 24 = AbsPressure
  toEnum 25 = AbsDistance
  toEnum 26 = AbsTiltX
  toEnum 27 = AbsTiltY
  toEnum 28 = AbsToolWidth
  toEnum 32 = AbsVolume
  toEnum 40 = AbsMisc
  toEnum 46 = AbsReserved
  toEnum 47 = AbsMtSlot
  toEnum 48 = AbsMtTouchMajor
  toEnum 49 = AbsMtTouchMinor
  toEnum 50 = AbsMtWidthMajor
  toEnum 51 = AbsMtWidthMinor
  toEnum 52 = AbsMtOrientation
  toEnum 53 = AbsMtPositionX
  toEnum 54 = AbsMtPositionY
  toEnum 55 = AbsMtToolType
  toEnum 56 = AbsMtBlobId
  toEnum 57 = AbsMtTrackingId
  toEnum 58 = AbsMtPressure
  toEnum 59 = AbsMtDistance
  toEnum 60 = AbsMtToolX
  toEnum 61 = AbsMtToolY
  toEnum unmatched = error ("AbsoluteAxis.toEnum: Cannot match " ++ show unmatched)

{-# LINE 661 "src/Evdev/Codes.chs" #-}


-- | Stateful binary switches
data SwitchEvent = SwLid
                 | SwTabletMode
                 | SwHeadphoneInsert
                 | SwRfkillAll
                 | SwRadio
                 | SwMicrophoneInsert
                 | SwDock
                 | SwLineoutInsert
                 | SwJackPhysicalInsert
                 | SwVideooutInsert
                 | SwCameraLensCover
                 | SwKeypadSlide
                 | SwFrontProximity
                 | SwRotateLock
                 | SwLineinInsert
                 | SwMuteDevice
  deriving (Bounded,Eq,Ord,Read,Show)
instance Enum SwitchEvent where
  succ SwLid = SwTabletMode
  succ SwTabletMode = SwHeadphoneInsert
  succ SwHeadphoneInsert = SwRfkillAll
  succ SwRfkillAll = SwMicrophoneInsert
  succ SwRadio = SwMicrophoneInsert
  succ SwMicrophoneInsert = SwDock
  succ SwDock = SwLineoutInsert
  succ SwLineoutInsert = SwJackPhysicalInsert
  succ SwJackPhysicalInsert = SwVideooutInsert
  succ SwVideooutInsert = SwCameraLensCover
  succ SwCameraLensCover = SwKeypadSlide
  succ SwKeypadSlide = SwFrontProximity
  succ SwFrontProximity = SwRotateLock
  succ SwRotateLock = SwLineinInsert
  succ SwLineinInsert = SwMuteDevice
  succ SwMuteDevice = error "SwitchEvent.succ: SwMuteDevice has no successor"

  pred SwTabletMode = SwLid
  pred SwHeadphoneInsert = SwTabletMode
  pred SwRfkillAll = SwHeadphoneInsert
  pred SwRadio = SwHeadphoneInsert
  pred SwMicrophoneInsert = SwRfkillAll
  pred SwDock = SwMicrophoneInsert
  pred SwLineoutInsert = SwDock
  pred SwJackPhysicalInsert = SwLineoutInsert
  pred SwVideooutInsert = SwJackPhysicalInsert
  pred SwCameraLensCover = SwVideooutInsert
  pred SwKeypadSlide = SwCameraLensCover
  pred SwFrontProximity = SwKeypadSlide
  pred SwRotateLock = SwFrontProximity
  pred SwLineinInsert = SwRotateLock
  pred SwMuteDevice = SwLineinInsert
  pred SwLid = error "SwitchEvent.pred: SwLid has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from SwMuteDevice

  fromEnum SwLid = 0
  fromEnum SwTabletMode = 1
  fromEnum SwHeadphoneInsert = 2
  fromEnum SwRfkillAll = 3
  fromEnum SwRadio = 3
  fromEnum SwMicrophoneInsert = 4
  fromEnum SwDock = 5
  fromEnum SwLineoutInsert = 6
  fromEnum SwJackPhysicalInsert = 7
  fromEnum SwVideooutInsert = 8
  fromEnum SwCameraLensCover = 9
  fromEnum SwKeypadSlide = 10
  fromEnum SwFrontProximity = 11
  fromEnum SwRotateLock = 12
  fromEnum SwLineinInsert = 13
  fromEnum SwMuteDevice = 14

  toEnum 0 = SwLid
  toEnum 1 = SwTabletMode
  toEnum 2 = SwHeadphoneInsert
  toEnum 3 = SwRfkillAll
  toEnum 4 = SwMicrophoneInsert
  toEnum 5 = SwDock
  toEnum 6 = SwLineoutInsert
  toEnum 7 = SwJackPhysicalInsert
  toEnum 8 = SwVideooutInsert
  toEnum 9 = SwCameraLensCover
  toEnum 10 = SwKeypadSlide
  toEnum 11 = SwFrontProximity
  toEnum 12 = SwRotateLock
  toEnum 13 = SwLineinInsert
  toEnum 14 = SwMuteDevice
  toEnum unmatched = error ("SwitchEvent.toEnum: Cannot match " ++ show unmatched)

{-# LINE 681 "src/Evdev/Codes.chs" #-}


-- | Miscellaneous
data MiscEvent = MscSerial
               | MscPulseled
               | MscGesture
               | MscRaw
               | MscScan
               | MscTimestamp
  deriving (Bounded,Eq,Ord,Read,Show)
instance Enum MiscEvent where
  succ MscSerial = MscPulseled
  succ MscPulseled = MscGesture
  succ MscGesture = MscRaw
  succ MscRaw = MscScan
  succ MscScan = MscTimestamp
  succ MscTimestamp = error "MiscEvent.succ: MscTimestamp has no successor"

  pred MscPulseled = MscSerial
  pred MscGesture = MscPulseled
  pred MscRaw = MscGesture
  pred MscScan = MscRaw
  pred MscTimestamp = MscScan
  pred MscSerial = error "MiscEvent.pred: MscSerial has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from MscTimestamp

  fromEnum MscSerial = 0
  fromEnum MscPulseled = 1
  fromEnum MscGesture = 2
  fromEnum MscRaw = 3
  fromEnum MscScan = 4
  fromEnum MscTimestamp = 5

  toEnum 0 = MscSerial
  toEnum 1 = MscPulseled
  toEnum 2 = MscGesture
  toEnum 3 = MscRaw
  toEnum 4 = MscScan
  toEnum 5 = MscTimestamp
  toEnum unmatched = error ("MiscEvent.toEnum: Cannot match " ++ show unmatched)

{-# LINE 691 "src/Evdev/Codes.chs" #-}


-- | LEDs
data LEDEvent = LedNuml
              | LedCapsl
              | LedScrolll
              | LedCompose
              | LedKana
              | LedSleep
              | LedSuspend
              | LedMute
              | LedMisc
              | LedMail
              | LedCharging
  deriving (Bounded,Eq,Ord,Read,Show)
instance Enum LEDEvent where
  succ LedNuml = LedCapsl
  succ LedCapsl = LedScrolll
  succ LedScrolll = LedCompose
  succ LedCompose = LedKana
  succ LedKana = LedSleep
  succ LedSleep = LedSuspend
  succ LedSuspend = LedMute
  succ LedMute = LedMisc
  succ LedMisc = LedMail
  succ LedMail = LedCharging
  succ LedCharging = error "LEDEvent.succ: LedCharging has no successor"

  pred LedCapsl = LedNuml
  pred LedScrolll = LedCapsl
  pred LedCompose = LedScrolll
  pred LedKana = LedCompose
  pred LedSleep = LedKana
  pred LedSuspend = LedSleep
  pred LedMute = LedSuspend
  pred LedMisc = LedMute
  pred LedMail = LedMisc
  pred LedCharging = LedMail
  pred LedNuml = error "LEDEvent.pred: LedNuml has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from LedCharging

  fromEnum LedNuml = 0
  fromEnum LedCapsl = 1
  fromEnum LedScrolll = 2
  fromEnum LedCompose = 3
  fromEnum LedKana = 4
  fromEnum LedSleep = 5
  fromEnum LedSuspend = 6
  fromEnum LedMute = 7
  fromEnum LedMisc = 8
  fromEnum LedMail = 9
  fromEnum LedCharging = 10

  toEnum 0 = LedNuml
  toEnum 1 = LedCapsl
  toEnum 2 = LedScrolll
  toEnum 3 = LedCompose
  toEnum 4 = LedKana
  toEnum 5 = LedSleep
  toEnum 6 = LedSuspend
  toEnum 7 = LedMute
  toEnum 8 = LedMisc
  toEnum 9 = LedMail
  toEnum 10 = LedCharging
  toEnum unmatched = error ("LEDEvent.toEnum: Cannot match " ++ show unmatched)

{-# LINE 706 "src/Evdev/Codes.chs" #-}


-- | Specifying autorepeating events
data RepeatEvent = RepDelay
                 | RepPeriod
  deriving (Bounded,Eq,Ord,Read,Show)
instance Enum RepeatEvent where
  succ RepDelay = RepPeriod
  succ RepPeriod = error "RepeatEvent.succ: RepPeriod has no successor"

  pred RepPeriod = RepDelay
  pred RepDelay = error "RepeatEvent.pred: RepDelay has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from RepPeriod

  fromEnum RepDelay = 0
  fromEnum RepPeriod = 1

  toEnum 0 = RepDelay
  toEnum 1 = RepPeriod
  toEnum unmatched = error ("RepeatEvent.toEnum: Cannot match " ++ show unmatched)

{-# LINE 712 "src/Evdev/Codes.chs" #-}


-- | For simple sound output devices
data SoundEvent = SndClick
                | SndBell
                | SndTone
  deriving (Bounded,Eq,Ord,Read,Show)
instance Enum SoundEvent where
  succ SndClick = SndBell
  succ SndBell = SndTone
  succ SndTone = error "SoundEvent.succ: SndTone has no successor"

  pred SndBell = SndClick
  pred SndTone = SndBell
  pred SndClick = error "SoundEvent.pred: SndClick has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from SndTone

  fromEnum SndClick = 0
  fromEnum SndBell = 1
  fromEnum SndTone = 2

  toEnum 0 = SndClick
  toEnum 1 = SndBell
  toEnum 2 = SndTone
  toEnum unmatched = error ("SoundEvent.toEnum: Cannot match " ++ show unmatched)

{-# LINE 719 "src/Evdev/Codes.chs" #-}


-- | Device properties
data DeviceProperty = InputPropPointer
                    | InputPropDirect
                    | InputPropButtonpad
                    | InputPropSemiMt
                    | InputPropTopbuttonpad
                    | InputPropPointingStick
                    | InputPropAccelerometer
  deriving (Bounded,Eq,Ord,Read,Show)
instance Enum DeviceProperty where
  succ InputPropPointer = InputPropDirect
  succ InputPropDirect = InputPropButtonpad
  succ InputPropButtonpad = InputPropSemiMt
  succ InputPropSemiMt = InputPropTopbuttonpad
  succ InputPropTopbuttonpad = InputPropPointingStick
  succ InputPropPointingStick = InputPropAccelerometer
  succ InputPropAccelerometer = error "DeviceProperty.succ: InputPropAccelerometer has no successor"

  pred InputPropDirect = InputPropPointer
  pred InputPropButtonpad = InputPropDirect
  pred InputPropSemiMt = InputPropButtonpad
  pred InputPropTopbuttonpad = InputPropSemiMt
  pred InputPropPointingStick = InputPropTopbuttonpad
  pred InputPropAccelerometer = InputPropPointingStick
  pred InputPropPointer = error "DeviceProperty.pred: InputPropPointer has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from InputPropAccelerometer

  fromEnum InputPropPointer = 0
  fromEnum InputPropDirect = 1
  fromEnum InputPropButtonpad = 2
  fromEnum InputPropSemiMt = 3
  fromEnum InputPropTopbuttonpad = 4
  fromEnum InputPropPointingStick = 5
  fromEnum InputPropAccelerometer = 6

  toEnum 0 = InputPropPointer
  toEnum 1 = InputPropDirect
  toEnum 2 = InputPropButtonpad
  toEnum 3 = InputPropSemiMt
  toEnum 4 = InputPropTopbuttonpad
  toEnum 5 = InputPropPointingStick
  toEnum 6 = InputPropAccelerometer
  toEnum unmatched = error ("DeviceProperty.toEnum: Cannot match " ++ show unmatched)

{-# LINE 730 "src/Evdev/Codes.chs" #-}