{-# LINE 1 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}
--------------------------------------------------------------------------------
{-# LINE 2 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}
-- |
-- Module    : Sound.ALSA.Sequencer.Marshal.Queue
-- 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.Queue where


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

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

import qualified Sound.ALSA.Sequencer.Utility as U

import qualified Foreign.C.Types as C
import Foreign.Storable (Storable, sizeOf, alignment, peek, peekByteOff, poke, pokeByteOff, )

import Data.Array (Ix, )

import qualified Data.Word as Word




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

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

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

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

direct  :: T
direct  = Cons 253

{-# LINE 58 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}


data Skew =
   Skew {
      skewValue :: ! Word.Word32,
{-# LINE 63 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}
      skewBase  :: ! Word.Word32
{-# LINE 64 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}
   } deriving (Show, Eq)

instance Storable Skew where
  sizeOf _    = (8)
{-# LINE 68 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}
  alignment _ = (4)
{-# LINE 69 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}
  peek p      = do v <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 70 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}
                   b <- (\hsc_ptr -> peekByteOff hsc_ptr 4)  p
{-# LINE 71 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}
                   return Skew { skewValue = v
                               , skewBase  = b
                               }
  poke p v    = (\hsc_ptr -> pokeByteOff hsc_ptr 0) p (skewValue v)
{-# LINE 75 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}
             >> (\hsc_ptr -> pokeByteOff hsc_ptr 4)  p (skewBase  v)
{-# LINE 76 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}


newtype Position = Position { unPosition :: Word.Word32 }
 deriving (Show, Eq, Ord, Ix, Storable)

{-# LINE 79 "src/Sound/ALSA/Sequencer/Marshal/Queue.hsc" #-}