{-# LINE 1 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
--------------------------------------------------------------------------------
{-# LINE 2 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
-- |
-- Module    : Sound.ALSA.Sequencer.Marshal.Event
-- Copyright : (c) Henning Thielemann, 2010
--             (c) Iavor S. Diatchki, 2007
-- License   : BSD3
--
-- Maintainer: Henning Thielemann
-- Stability : provisional
--
-- PRIVATE MODULE.
--
-- Here we have the various types used by the library,
-- and how they are imported\/exported to C.
--
-- NOTE: In the translations bellow we make the following assumptions
-- about the sizes of C types.
-- CChar  = 8 bits
-- CShort = 16 bit
-- CInt   = 32 bits
--------------------------------------------------------------------------------

module Sound.ALSA.Sequencer.Marshal.Event where


{-# LINE 26 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

import qualified Sound.ALSA.Sequencer.Marshal.Address as Addr
import qualified Sound.ALSA.Sequencer.Marshal.Queue as Queue
import qualified Sound.ALSA.Sequencer.Marshal.RealTime as RealTime

import Foreign.C.Types (CUInt, )
import Foreign.Storable
          (Storable, sizeOf, alignment, peek, poke, pokeByteOff, peekByteOff, )
import Foreign.Ptr (Ptr, castPtr, nullPtr, plusPtr, )
import Foreign.Marshal.Alloc (alloca, )
import Data.Bits ((.|.), (.&.), )
import Data.Int (Int16, Int32, )
import Data.Word (Word8, Word16, Word32, )
import Data.Array (Array, (!), accumArray, )


data Connect = Connect
   { connSource :: !Addr.T
   , connDest   :: !Addr.T
   } deriving (Show,Eq,Ord)

instance Storable Connect where
  sizeOf _    = (4)
{-# LINE 49 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  alignment _ = 4 -- XXX
  peek p      = do s <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 51 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   d <- (\hsc_ptr -> peekByteOff hsc_ptr 2) p
{-# LINE 52 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   return Connect { connSource = s, connDest = d }
  poke p v    = (\hsc_ptr -> pokeByteOff hsc_ptr 0) p (connSource v)
{-# LINE 54 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
             >> (\hsc_ptr -> pokeByteOff hsc_ptr 2)   p (connDest v)
{-# LINE 55 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}


data TimeStamp      = TickTime !Word32
                    | RealTime !RealTime.T
                      deriving Show

peekTimestamp :: Word8 -> Ptr TimeStamp -> IO TimeStamp
peekTimestamp flags p =
  case flags .&. 1 of
{-# LINE 64 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    { 0 -> TickTime `fmap` peek (castPtr p)
{-# LINE 65 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ; _                                -> RealTime `fmap` peek (castPtr p)
    }

pokeTimestamp :: Ptr TimeStamp -> TimeStamp -> IO Word8
pokeTimestamp p ts = case ts of
  TickTime t -> poke (castPtr p) t >> return 0
{-# LINE 71 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  RealTime t -> poke (castPtr p) t >> return 1
{-# LINE 72 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}



newtype InstrCluster = InstrCluster CUInt
  deriving (Show,Eq,Ord,Num,Enum,Storable)

data Instr = Instr
   { instrCluster :: !InstrCluster
    -- XXX: perhaps use Sample?
   , instrStd     :: !Word32
   , instrBank    :: !Word16
   , instrPrg     :: !Word16
   } deriving (Show)

{-
instance Storable Instr where
  sizeOf _    = #{size snd_seq_instr_t}
  alignment _ = 4 -- XXX
  peek p      = do cl <- #{peek snd_seq_instr_t, cluster} p
                   st <- #{peek snd_seq_instr_t, std} p
                   ba <- #{peek snd_seq_instr_t, bank} p
                   pr <- #{peek snd_seq_instr_t, prg} p
                   return Instr { instr_cluster = cl
                                , instr_std     = st
                                , instr_bank    = ba
                                , instr_prg     = pr
                                }
  poke p v    = #{poke snd_seq_instr_t, cluster} p (instr_cluster v)
             >> #{poke snd_seq_instr_t, std}     p (instr_std v)
             >> #{poke snd_seq_instr_t, bank}    p (instr_bank v)
             >> #{poke snd_seq_instr_t, prg}     p (instr_prg v)
-}


data Note = Note
   { noteChannel      :: !Word8
   , noteNote         :: !Word8
   , noteVelocity     :: !Word8
   , noteOffVelocity  :: !Word8
   , noteDuration     :: !Word32
   } deriving (Show)


instance Storable Note where
  sizeOf _    = (8)
{-# LINE 117 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  alignment _ = 4 -- XXX
  peek p      = do c  <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 119 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   n  <- (\hsc_ptr -> peekByteOff hsc_ptr 1) p
{-# LINE 120 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   v  <- (\hsc_ptr -> peekByteOff hsc_ptr 2) p
{-# LINE 121 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   ov <- (\hsc_ptr -> peekByteOff hsc_ptr 3) p
{-# LINE 122 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   d  <- (\hsc_ptr -> peekByteOff hsc_ptr 4) p
{-# LINE 123 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   return Note { noteChannel = c
                               , noteNote = n
                               , noteVelocity = v
                               , noteOffVelocity = ov
                               , noteDuration = d
                               }
  poke p v    = (\hsc_ptr -> pokeByteOff hsc_ptr 0)      p (noteChannel v)
{-# LINE 130 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
             >> (\hsc_ptr -> pokeByteOff hsc_ptr 1)         p (noteNote v)
{-# LINE 131 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
             >> (\hsc_ptr -> pokeByteOff hsc_ptr 2)     p (noteVelocity v)
{-# LINE 132 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
             >> (\hsc_ptr -> pokeByteOff hsc_ptr 3) p (noteOffVelocity v)
{-# LINE 133 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
             >> (\hsc_ptr -> pokeByteOff hsc_ptr 4)     p (noteDuration v)
{-# LINE 134 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}


data Ctrl = Ctrl
   { ctrlChannel  :: !Word8
   , ctrlParam    :: !Word32
   , ctrlValue    :: !Int32
   } deriving (Show)

instance Storable Ctrl where
  sizeOf _    = (12)
{-# LINE 144 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  alignment _ = 4 -- XXX
  peek p      = do ct <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 146 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   pa <- (\hsc_ptr -> peekByteOff hsc_ptr 4) p
{-# LINE 147 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   va <- (\hsc_ptr -> peekByteOff hsc_ptr 8) p
{-# LINE 148 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   return Ctrl { ctrlChannel = ct
                               , ctrlParam   = pa
                               , ctrlValue   = va
                               }
  poke p v    = (\hsc_ptr -> pokeByteOff hsc_ptr 0) p (ctrlChannel v)
{-# LINE 153 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
             >> (\hsc_ptr -> pokeByteOff hsc_ptr 4)   p (ctrlParam v)
{-# LINE 154 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
             >> (\hsc_ptr -> pokeByteOff hsc_ptr 8)   p (ctrlValue v)
{-# LINE 155 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}



data Sample = Sample
   { sampleStd  :: !Word32
   , sampleBank :: !Word16
   , samplePrg  :: !Word16
   } deriving (Show)

{-
instance Storable Sample where
  sizeOf _    = #{size snd_seq_ev_sample_t}
  alignment _ = 4 -- XXX
  peek p      = do st <- #{peek snd_seq_ev_sample_t, std} p
                   ba <- #{peek snd_seq_ev_sample_t, bank} p
                   pr <- #{peek snd_seq_ev_sample_t, prg} p
                   return Sample { sample_std     = st
                                 , sample_bank    = ba
                                 , sample_prg     = pr
                                 }
  poke p v    = #{poke snd_seq_ev_sample_t, std}     p (sampleStd v)
             >> #{poke snd_seq_ev_sample_t, bank}    p (sampleBank v)
             >> #{poke snd_seq_ev_sample_t, prg}     p (samplePrg v)
-}


newtype Cluster = Cluster
   { clusterCluster :: InstrCluster
   } deriving (Show, Eq, Storable)


-- | These are all 14 bit values.
data Volume = Volume
   { volumeVolume  :: !Int16
   , volumeLR      :: !Int16
   , volumeFR      :: !Int16
   , volumeDU      :: !Int16
   } deriving (Show)

{-
instance Storable Volume where
  sizeOf _    = #{size snd_seq_ev_volume_t}
  alignment _ = 4 -- XXX
  peek p      = do v <- #{peek snd_seq_ev_volume_t, volume} p
                   l <- #{peek snd_seq_ev_volume_t, lr} p
                   f <- #{peek snd_seq_ev_volume_t, fr} p
                   d <- #{peek snd_seq_ev_volume_t, du} p
                   return Volume { volume_volume  = v
                                 , volume_lr      = l
                                 , volume_fr      = f
                                 , volume_du      = d
                                 }
  poke p v    = #{poke snd_seq_ev_volume_t, volume} p (volumeVolume v)
             >> #{poke snd_seq_ev_volume_t, lr}     p (volumeLR v)
             >> #{poke snd_seq_ev_volume_t, fr}     p (volumeFR v)
             >> #{poke snd_seq_ev_volume_t, du}     p (volumeDU v)
-}


data Custom = Custom { custom0, custom1, custom2 :: !Word32 }
                      deriving (Show)

instance Storable Custom where
  sizeOf _    = (12)
{-# LINE 219 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  alignment _ = 4 -- XXX
  peek p      = do d0 <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 221 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   d1 <- (\hsc_ptr -> peekByteOff hsc_ptr 4) p
{-# LINE 222 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   d2 <- (\hsc_ptr -> peekByteOff hsc_ptr 8) p
{-# LINE 223 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                   return Custom { custom0 = d0
                                 , custom1 = d1
                                 , custom2 = d2
                                 }
  poke p v    = (\hsc_ptr -> pokeByteOff hsc_ptr 0) p (custom0 v)
{-# LINE 228 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
             >> (\hsc_ptr -> pokeByteOff hsc_ptr 4) p (custom1 v)
{-# LINE 229 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
             >> (\hsc_ptr -> pokeByteOff hsc_ptr 8) p (custom2 v)
{-# LINE 230 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}



data T = Cons
   { highPriority   :: !Bool
   , tag            :: !Word8
   , queue          :: !Queue.T
   , timestamp      :: !TimeStamp
   , source         :: !Addr.T
   , dest           :: !Addr.T
   , body           :: !Data
   } deriving Show

instance Storable T where
  sizeOf _    = (28)
{-# LINE 245 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  alignment _ = 4 -- XXX
  peek p =
    do ty    <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 248 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
       flags <- (\hsc_ptr -> peekByteOff hsc_ptr 1) p
{-# LINE 249 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
       tg    <- (\hsc_ptr -> peekByteOff hsc_ptr 2) p
{-# LINE 250 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
       q     <- (\hsc_ptr -> peekByteOff hsc_ptr 3) p
{-# LINE 251 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
       time  <- peekTimestamp flags ((\hsc_ptr -> hsc_ptr `plusPtr` 4) p)
{-# LINE 252 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
       src   <- (\hsc_ptr -> peekByteOff hsc_ptr 12) p
{-# LINE 253 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
       dst   <- (\hsc_ptr -> peekByteOff hsc_ptr 14) p
{-# LINE 254 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
       d     <- (peekData ! ty) ((\hsc_ptr -> hsc_ptr `plusPtr` 16) p)
{-# LINE 255 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
       return Cons
         { highPriority = (flags .&. 16) /= 0
{-# LINE 257 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
         , tag = tg
         , queue = q
         , timestamp = time
         , source = src
         , dest = dst
         , body = d
         }
  poke p e = do
    { ty <- pokeData ((\hsc_ptr -> hsc_ptr `plusPtr` 16) p) (body e)
{-# LINE 266 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ; (\hsc_ptr -> pokeByteOff hsc_ptr 0) p ty
{-# LINE 267 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ; (\hsc_ptr -> pokeByteOff hsc_ptr 2) p (tag e)
{-# LINE 268 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ; (\hsc_ptr -> pokeByteOff hsc_ptr 3) p (queue e)
{-# LINE 269 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ; real <- pokeTimestamp ((\hsc_ptr -> hsc_ptr `plusPtr` 4) p) (timestamp e)
{-# LINE 270 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ; (\hsc_ptr -> pokeByteOff hsc_ptr 12) p (source e)
{-# LINE 271 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ; (\hsc_ptr -> pokeByteOff hsc_ptr 14) p (dest e)
{-# LINE 272 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ; let flags = (if highPriority e
                     then 16
{-# LINE 274 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
                     else 0)
{-# LINE 275 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
               .|. real
               .|. 0  -- XXX
{-# LINE 277 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ; (\hsc_ptr -> pokeByteOff hsc_ptr 1) p flags
{-# LINE 278 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    }

allocaEv :: T -> (Ptr T -> IO a) -> IO a
allocaEv e h = alloca (\p -> poke p e >> h p)

allocaMaybeEv :: Maybe T -> (Ptr T -> IO a) -> IO a
allocaMaybeEv me h =
  maybe (h nullPtr) (\e -> allocaEv e h) me

pokeData :: Ptr Data -> Data -> IO Word8
pokeData p dt = case dt of
  NoteEv e d  -> poke (castPtr p) d >> return (expNoteEv e)
  CtrlEv e d  -> poke (castPtr p) d >> return (expCtrlEv e)
  AddrEv e d  -> poke (castPtr p) d >> return (expAddrEv e)
  ConnEv e d  -> poke (castPtr p) d >> return (expConnEv e)
  CustomEv e d -> poke (castPtr p) d >> return (expCustomEv e)
  EmptyEv e   -> return (expEmptyEv e)


peekData :: Array Word8 (Ptr Data -> IO Data)
peekData = accumArray (const id) unknown (0,255)
  [ -- result events (2)
    (0, unknown)
{-# LINE 301 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (1, unknown)
{-# LINE 302 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

    -- note events (4)
  , (5,     peekNoteEv ANote)
{-# LINE 305 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (6,   peekNoteEv NoteOn)
{-# LINE 306 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (7,  peekNoteEv NoteOff)
{-# LINE 307 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (8, peekNoteEv KeyPress)
{-# LINE 308 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

    -- control events (12)
  , (10,  peekCtrlEv Controller)
{-# LINE 311 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (11,   peekCtrlEv PgmChange)
{-# LINE 312 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (12,   peekCtrlEv ChanPress)
{-# LINE 313 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (13,   peekCtrlEv PitchBend)
{-# LINE 314 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (14,   peekCtrlEv Control14)
{-# LINE 315 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (15, peekCtrlEv NonRegParam)
{-# LINE 316 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (16,    peekCtrlEv RegParam)
{-# LINE 317 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (20,     peekCtrlEv SongPos)
{-# LINE 318 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (21,     peekCtrlEv SongSel)
{-# LINE 319 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (22,      peekCtrlEv QFrame)
{-# LINE 320 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (23,    peekCtrlEv TimeSign)
{-# LINE 321 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (24,     peekCtrlEv KeySign)
{-# LINE 322 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

  -- queue control (10)
  , (30, unknown)
{-# LINE 325 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (31, unknown)
{-# LINE 326 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (32, unknown)
{-# LINE 327 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (33, unknown)
{-# LINE 328 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (34, unknown)
{-# LINE 329 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (35, unknown)
{-# LINE 330 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (36, unknown)
{-# LINE 331 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (37, unknown)
{-# LINE 332 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (38, unknown)
{-# LINE 333 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (39, unknown)
{-# LINE 334 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

  -- misc (3)
  , (40, peekEmptyEv TuneRequest)
{-# LINE 337 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (41,        peekEmptyEv Reset)
{-# LINE 338 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (42,      peekEmptyEv Sensing)
{-# LINE 339 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

  , (50, peekCustomEv Echo)
{-# LINE 341 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (51,  peekCustomEv OSS)
{-# LINE 342 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

  -- networking (8)
  , (60,  peekAddrEv ClientStart)
{-# LINE 345 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (61,   peekAddrEv ClientExit)
{-# LINE 346 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (62, peekAddrEv ClientChange)
{-# LINE 347 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (63,    peekAddrEv PortStart)
{-# LINE 348 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (64,     peekAddrEv PortExit)
{-# LINE 349 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (65,   peekAddrEv PortChange)
{-# LINE 350 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (66,   peekConnEv PortSubscribed)
{-# LINE 351 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (67, peekConnEv PortUnsubscribed)
{-# LINE 352 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

{-
  , (#{const SND_SEQ_EVENT_SAMPLE}, unknown)
  , (#{const SND_SEQ_EVENT_SAMPLE_CLUSTER}, unknown)
  , (#{const SND_SEQ_EVENT_SAMPLE_START}, unknown)
  , (#{const SND_SEQ_EVENT_SAMPLE_STOP}, unknown)
  , (#{const SND_SEQ_EVENT_SAMPLE_FREQ}, unknown)
  , (#{const SND_SEQ_EVENT_SAMPLE_VOLUME}, unknown)
  , (#{const SND_SEQ_EVENT_SAMPLE_LOOP}, unknown)
  , (#{const SND_SEQ_EVENT_SAMPLE_POSITION}, unknown)
  , (#{const SND_SEQ_EVENT_SAMPLE_PRIVATE1}, unknown)
-}
  , (90, peekCustomEv User0)
{-# LINE 365 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (91, peekCustomEv User1)
{-# LINE 366 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (92, peekCustomEv User2)
{-# LINE 367 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (93, peekCustomEv User3)
{-# LINE 368 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (94, peekCustomEv User4)
{-# LINE 369 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (95, peekCustomEv User5)
{-# LINE 370 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (96, peekCustomEv User6)
{-# LINE 371 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (97, peekCustomEv User7)
{-# LINE 372 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (98, peekCustomEv User8)
{-# LINE 373 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (99, peekCustomEv User9)
{-# LINE 374 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

{-
  , (#{const SND_SEQ_EVENT_INSTR_BEGIN}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_END}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_INFO}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_INFO_RESULT}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_FINFO}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_FINFO_RESULT}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_RESET}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_STATUS}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_STATUS_RESULT}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_PUT}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_GET}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_GET_RESULT}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_FREE}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_LIST}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_LIST_RESULT}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_CLUSTER}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_CLUSTER_GET}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_CLUSTER_RESULT}, unknown)
  , (#{const SND_SEQ_EVENT_INSTR_CHANGE}, unknown)
-}

  , (130, unknown)
{-# LINE 398 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (131, unknown)
{-# LINE 399 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

  , (135, unknown)
{-# LINE 401 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (136, unknown)
{-# LINE 402 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (137, unknown)
{-# LINE 403 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (138, unknown)
{-# LINE 404 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  , (138, unknown)
{-# LINE 405 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

  , (255, peekEmptyEv None)
{-# LINE 407 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  ]

  where unknown = peekEmptyEv Unknown


data NoteEv   = ANote | NoteOn | NoteOff | KeyPress
                deriving Show

data CtrlEv   = Controller | PgmChange | ChanPress
              | PitchBend | Control14
              | NonRegParam | RegParam
              | SongPos | SongSel
              | QFrame
              | TimeSign | KeySign
                deriving Show

data QueueEv  = QueueStart
              | QueueContinue
              | QueueStop
              | QueueSetPosTick
              | QueueSetPosTime
              | QueueTempo
              | QueueClock
              | QueueTick
              | QueueSkew
              | QueueSyncPos
                deriving Show

data EmptyEv  = TuneRequest | Reset | Sensing | None | Unknown
                deriving Show

data CustomEv = Echo | OSS
              | User0 | User1 | User2 | User3 | User4
              | User5 | User6 | User7 | User8 | User9
                deriving Show

data AddrEv   = ClientStart | ClientExit | ClientChange
              | PortStart | PortExit | PortChange
                deriving Show

data ConnEv   = PortSubscribed | PortUnsubscribed
                deriving Show


expNoteEv :: NoteEv -> Word8
expNoteEv e = case e of
  ANote    -> 5
{-# LINE 454 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  NoteOn   -> 6
{-# LINE 455 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  NoteOff  -> 7
{-# LINE 456 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  KeyPress -> 8
{-# LINE 457 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

expCtrlEv :: CtrlEv -> Word8
expCtrlEv e = case e of
  Controller  -> 10
{-# LINE 461 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  PgmChange   -> 11
{-# LINE 462 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  ChanPress   -> 12
{-# LINE 463 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  PitchBend   -> 13
{-# LINE 464 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  Control14   -> 14
{-# LINE 465 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  NonRegParam -> 15
{-# LINE 466 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  RegParam    -> 16
{-# LINE 467 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  SongPos     -> 20
{-# LINE 468 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  SongSel     -> 21
{-# LINE 469 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  QFrame      -> 22
{-# LINE 470 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  TimeSign    -> 23
{-# LINE 471 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  KeySign     -> 24
{-# LINE 472 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

expQueueEv :: QueueEv -> Word8
expQueueEv e = case e of
  QueueStart      -> 30
{-# LINE 476 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  QueueContinue   -> 31
{-# LINE 477 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  QueueStop       -> 32
{-# LINE 478 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  QueueSetPosTick -> 33
{-# LINE 479 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  QueueSetPosTime -> 34
{-# LINE 480 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  QueueTempo      -> 35
{-# LINE 481 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  QueueClock      -> 36
{-# LINE 482 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  QueueTick       -> 37
{-# LINE 483 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  QueueSkew       -> 38
{-# LINE 484 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  QueueSyncPos    -> 39
{-# LINE 485 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

expEmptyEv :: EmptyEv -> Word8
expEmptyEv e = case e of
  TuneRequest -> 40
{-# LINE 489 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  Reset       -> 41
{-# LINE 490 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  Sensing     -> 42
{-# LINE 491 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  None        -> 255
{-# LINE 492 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  Unknown     -> 255
{-# LINE 493 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

expCustomEv :: CustomEv -> Word8
expCustomEv e = case e of
  Echo  -> 50
{-# LINE 497 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  OSS   -> 51
{-# LINE 498 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  User0 -> 90
{-# LINE 499 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  User1 -> 91
{-# LINE 500 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  User2 -> 92
{-# LINE 501 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  User3 -> 93
{-# LINE 502 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  User4 -> 94
{-# LINE 503 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  User5 -> 95
{-# LINE 504 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  User6 -> 96
{-# LINE 505 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  User7 -> 97
{-# LINE 506 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  User8 -> 98
{-# LINE 507 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  User9 -> 99
{-# LINE 508 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

expAddrEv :: AddrEv -> Word8
expAddrEv e = case e of
    ClientStart -> 60
{-# LINE 512 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ClientExit -> 61
{-# LINE 513 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    ClientChange -> 62
{-# LINE 514 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    PortStart -> 63
{-# LINE 515 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    PortExit -> 64
{-# LINE 516 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
    PortChange -> 65
{-# LINE 517 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}

expConnEv :: ConnEv -> Word8
expConnEv e = case e of
  PortSubscribed   -> 66
{-# LINE 521 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}
  PortUnsubscribed -> 67
{-# LINE 522 "src/Sound/ALSA/Sequencer/Marshal/Event.hsc" #-}


peekNoteEv :: NoteEv -> Ptr Data -> IO Data
peekNoteEv e p = NoteEv e `fmap` peek (castPtr p)

peekCtrlEv :: CtrlEv -> Ptr Data -> IO Data
peekCtrlEv e p = CtrlEv e `fmap` peek (castPtr p)

peekAddrEv :: AddrEv -> Ptr Data -> IO Data
peekAddrEv e p = AddrEv e `fmap` peek (castPtr p)

peekConnEv :: ConnEv -> Ptr Data -> IO Data
peekConnEv e p = ConnEv e `fmap` peek (castPtr p)

peekEmptyEv :: EmptyEv -> Ptr Data -> IO Data
peekEmptyEv e _ = return (EmptyEv e)

peekCustomEv :: CustomEv -> Ptr Data -> IO Data
peekCustomEv e p = CustomEv e `fmap` peek (castPtr p)


data Data
  = NoteEv NoteEv Note
  | CtrlEv CtrlEv Ctrl
  | AddrEv AddrEv Addr.T
  | ConnEv ConnEv Connect
  | EmptyEv EmptyEv
  | CustomEv CustomEv Custom
    deriving Show