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

module Sound.ALSA.Sequencer.Marshal.Sequencer where


import qualified Foreign.C.Types as C
import Foreign.Ptr (Ptr, )


-- | Read\/Write permissions for the sequencer device.
-- This way we prevent the ALSA exception 22 "Invalid argument"
-- when calling @event_output@ on an input-only sequencer.
class OpenMode mode where expOpenMode :: mode -> C.CInt

class OpenMode mode => AllowInput  mode where
class OpenMode mode => AllowOutput mode where

data OutputMode = OutputMode deriving (Int -> OutputMode -> ShowS
[OutputMode] -> ShowS
OutputMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutputMode] -> ShowS
$cshowList :: [OutputMode] -> ShowS
show :: OutputMode -> String
$cshow :: OutputMode -> String
showsPrec :: Int -> OutputMode -> ShowS
$cshowsPrec :: Int -> OutputMode -> ShowS
Show)
data InputMode  = InputMode  deriving (Int -> InputMode -> ShowS
[InputMode] -> ShowS
InputMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputMode] -> ShowS
$cshowList :: [InputMode] -> ShowS
show :: InputMode -> String
$cshow :: InputMode -> String
showsPrec :: Int -> InputMode -> ShowS
$cshowsPrec :: Int -> InputMode -> ShowS
Show)
data DuplexMode = DuplexMode deriving (Int -> DuplexMode -> ShowS
[DuplexMode] -> ShowS
DuplexMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DuplexMode] -> ShowS
$cshowList :: [DuplexMode] -> ShowS
show :: DuplexMode -> String
$cshow :: DuplexMode -> String
showsPrec :: Int -> DuplexMode -> ShowS
$cshowsPrec :: Int -> DuplexMode -> ShowS
Show)

instance OpenMode OutputMode where expOpenMode :: OutputMode -> CInt
expOpenMode OutputMode
_ = CInt
1
{-# LINE 37 "src/Sound/ALSA/Sequencer/Marshal/Sequencer.hsc" #-}
instance OpenMode InputMode  where expOpenMode _ = 2
{-# LINE 38 "src/Sound/ALSA/Sequencer/Marshal/Sequencer.hsc" #-}
instance OpenMode DuplexMode where expOpenMode _ = 3
{-# LINE 39 "src/Sound/ALSA/Sequencer/Marshal/Sequencer.hsc" #-}

instance AllowOutput OutputMode where
instance AllowOutput DuplexMode where
instance AllowInput  InputMode  where
instance AllowInput  DuplexMode where


-- | Blocking behavior of the sequencer device.
data BlockMode      = Block     -- ^ Operations may block.
                    | Nonblock  -- ^ Throw exceptions instead of blocking.
                      deriving (Int -> BlockMode -> ShowS
[BlockMode] -> ShowS
BlockMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockMode] -> ShowS
$cshowList :: [BlockMode] -> ShowS
show :: BlockMode -> String
$cshow :: BlockMode -> String
showsPrec :: Int -> BlockMode -> ShowS
$cshowsPrec :: Int -> BlockMode -> ShowS
Show,BlockMode -> BlockMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockMode -> BlockMode -> Bool
$c/= :: BlockMode -> BlockMode -> Bool
== :: BlockMode -> BlockMode -> Bool
$c== :: BlockMode -> BlockMode -> Bool
Eq)

expBlockMode      :: BlockMode -> C.CInt
expBlockMode :: BlockMode -> CInt
expBlockMode BlockMode
x     = case BlockMode
x of
  BlockMode
Block     -> CInt
0
  BlockMode
Nonblock  -> CInt
1
{-# LINE 55 "src/Sound/ALSA/Sequencer/Marshal/Sequencer.hsc" #-}


-- | The type of sequencer handles.
newtype T mode = Cons (Ptr Core) deriving T mode -> T mode -> Bool
forall mode. T mode -> T mode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: T mode -> T mode -> Bool
$c/= :: forall mode. T mode -> T mode -> Bool
== :: T mode -> T mode -> Bool
$c== :: forall mode. T mode -> T mode -> Bool
Eq
data Core