-------------------------------------------------------------------------------- -- | -- 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. -- -- 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.Queue where #include import qualified Sound.ALSA.Sequencer.Utility as U import Foreign.C.Types (CInt, ) import Foreign.Storable (Storable, ) import Data.Word (Word8, ) -- | The type of queue identifiers. newtype T = Cons Word8 deriving (Eq, Ord, Storable) instance Show T where showsPrec prec (Cons x) = U.showsRecord prec "Queue" [U.showsField x] imp :: CInt -> T imp x = Cons (fromIntegral x) exp :: T -> CInt exp (Cons x) = fromIntegral x #{enum T, Cons , direct = SND_SEQ_QUEUE_DIRECT }