{-# LINE 1 "src/Sound/ALSA/Sequencer/Marshal/Client.hsc" #-}
--------------------------------------------------------------------------------
{-# LINE 2 "src/Sound/ALSA/Sequencer/Marshal/Client.hsc" #-}
-- |
-- Module    : Sound.ALSA.Sequencer.Marshal
-- 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.
--
-- We use Hsc for expanding C types to Haskell types like Word32.
-- However if a C type is translated to Word32
-- you should not assume that it is translated to Word32 on every platform.
-- On a 64bit machine it may well be Word64.
-- Thus you should use our wrapper types whereever possible.
--------------------------------------------------------------------------------

module Sound.ALSA.Sequencer.Marshal.Client where


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

{-# LINE 27 "src/Sound/ALSA/Sequencer/Marshal/Client.hsc" #-}

import qualified Sound.ALSA.Sequencer.Utility as U
import qualified Foreign.C.Types as C
import qualified Data.Word as Word
import Foreign.Storable (Storable, )


-- | The type of client identifiers.
newtype T =
   Cons Word.Word8
{-# LINE 37 "src/Sound/ALSA/Sequencer/Marshal/Client.hsc" #-}
      deriving (Eq, Ord, Storable)

instance Show T where
   showsPrec prec (Cons x) =
      U.showsRecord prec "Client" [U.showsField x]


system       :: T
system       = Cons 0
subscribers  :: T
subscribers  = Cons 254
broadcast    :: T
broadcast    = Cons 255
unknown      :: T
unknown      = Cons 253

{-# LINE 50 "src/Sound/ALSA/Sequencer/Marshal/Client.hsc" #-}



exp :: T -> C.CInt
exp (Cons c) = fromIntegral c

imp :: C.CInt -> T
imp p = Cons (fromIntegral p)

-- | The different types of clients.
data Type = User | Kernel

impType :: C.CInt -> Type
impType x =
   if x == 1
{-# LINE 65 "src/Sound/ALSA/Sequencer/Marshal/Client.hsc" #-}
     then User
     else Kernel