{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
module SDL.Audio
(
AudioDevice
, openAudioDevice
, closeAudioDevice
, OpenDeviceSpec(..)
, AudioDeviceUsage(..)
, Channels(..)
, Changeable(..)
, setAudioDeviceLocked
, LockState(..)
, PlaybackState(..)
, setAudioDevicePlaybackState
, AudioDeviceStatus(..)
, audioDeviceStatus
, AudioFormat(..)
, getAudioDeviceNames
, AudioSpec(..)
, getAudioDrivers
, currentAudioDriver
, AudioDriver
, audioDriverName
, audioInit
) where
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Bits
import Data.Data (Data)
import Data.IORef (newIORef, writeIORef, readIORef)
import Data.Int (Int8, Int16, Int32)
import Data.Text (Text)
import Data.Traversable (for)
import Data.Typeable
import Data.Word
import Foreign.C.Types
import Foreign.ForeignPtr
import Foreign.Marshal.Alloc
import Foreign.Marshal.Utils
import Foreign.Ptr
import Foreign.Storable
import GHC.Exts (Constraint)
import GHC.Generics (Generic)
import SDL.Internal.Exception
import qualified Data.ByteString as BS
import qualified Data.Text.Encoding as Text
import qualified Data.Vector as V
import qualified Data.Vector.Storable.Mutable as MV
import qualified SDL.Raw.Audio as Raw
import qualified SDL.Raw.Enum as Raw
import qualified SDL.Raw.Types as Raw
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
#endif
#if MIN_VERSION_base(4,12,0)
import Data.Kind (Type)
#else
# define Type *
#endif
data OpenDeviceSpec = forall sampleType. OpenDeviceSpec
{ OpenDeviceSpec -> Changeable CInt
openDeviceFreq :: !(Changeable CInt)
, ()
openDeviceFormat :: !(Changeable (AudioFormat sampleType))
, OpenDeviceSpec -> Changeable Channels
openDeviceChannels :: !(Changeable Channels)
, OpenDeviceSpec -> Word16
openDeviceSamples :: !Word16
, OpenDeviceSpec
-> forall actualSampleType.
AudioFormat actualSampleType -> IOVector actualSampleType -> IO ()
openDeviceCallback :: forall actualSampleType. AudioFormat actualSampleType -> MV.IOVector actualSampleType -> IO ()
, OpenDeviceSpec -> AudioDeviceUsage
openDeviceUsage :: !AudioDeviceUsage
, OpenDeviceSpec -> Maybe Text
openDeviceName :: !(Maybe Text)
} deriving (Typeable)
openAudioDevice :: MonadIO m => OpenDeviceSpec -> m (AudioDevice, AudioSpec)
openAudioDevice :: forall (m :: Type -> Type).
MonadIO m =>
OpenDeviceSpec -> m (AudioDevice, AudioSpec)
openAudioDevice OpenDeviceSpec{Maybe Text
Word16
Changeable CInt
Changeable Channels
Changeable (AudioFormat sampleType)
AudioDeviceUsage
forall actualSampleType.
AudioFormat actualSampleType -> IOVector actualSampleType -> IO ()
openDeviceName :: Maybe Text
openDeviceUsage :: AudioDeviceUsage
openDeviceCallback :: forall actualSampleType.
AudioFormat actualSampleType -> IOVector actualSampleType -> IO ()
openDeviceSamples :: Word16
openDeviceChannels :: Changeable Channels
openDeviceFormat :: Changeable (AudioFormat sampleType)
openDeviceFreq :: Changeable CInt
openDeviceName :: OpenDeviceSpec -> Maybe Text
openDeviceUsage :: OpenDeviceSpec -> AudioDeviceUsage
openDeviceCallback :: OpenDeviceSpec
-> forall actualSampleType.
AudioFormat actualSampleType -> IOVector actualSampleType -> IO ()
openDeviceSamples :: OpenDeviceSpec -> Word16
openDeviceChannels :: OpenDeviceSpec -> Changeable Channels
openDeviceFormat :: ()
openDeviceFreq :: OpenDeviceSpec -> Changeable CInt
..} = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith (forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
BS.useAsCString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8) Maybe Text
openDeviceName forall a b. (a -> b) -> a -> b
$ \Ptr CChar
cDevName -> do
IORef AnAudioFormat
anAudioFormatRef <- forall a. a -> IO (IORef a)
newIORef forall a. HasCallStack => a
undefined
AudioCallback
cb <- (Ptr () -> Ptr Word8 -> CInt -> IO ()) -> IO AudioCallback
Raw.mkAudioCallback forall a b. (a -> b) -> a -> b
$ \Ptr ()
_ Ptr Word8
buffer CInt
len -> do
ForeignPtr Word8
fp <- forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ Ptr Word8
buffer
AnAudioFormat
anAudioFormat <- forall a. IORef a -> IO a
readIORef IORef AnAudioFormat
anAudioFormatRef
case AnAudioFormat
anAudioFormat of
AnAudioFormat AudioFormat sampleType
audioFormat ->
case forall sampleType.
AudioFormat sampleType -> Dict (Storable sampleType)
audioFormatStorable AudioFormat sampleType
audioFormat of
Dict (Storable sampleType)
Dict -> forall actualSampleType.
AudioFormat actualSampleType -> IOVector actualSampleType -> IO ()
openDeviceCallback AudioFormat sampleType
audioFormat
(forall a b s.
(Storable a, Storable b) =>
MVector s a -> MVector s b
MV.unsafeCast (forall a s. ForeignPtr a -> Int -> MVector s a
MV.unsafeFromForeignPtr0 ForeignPtr Word8
fp (forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
len)))
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (AudioCallback -> AudioSpec
desiredSpec AudioCallback
cb) forall a b. (a -> b) -> a -> b
$ \Ptr AudioSpec
desiredSpecPtr ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr AudioSpec
actualSpecPtr -> do
Word32
devId <- forall a (m :: Type -> Type).
(Eq a, MonadIO m, Num a) =>
Text -> Text -> m a -> m a
throwIf0 Text
"SDL.Audio.openAudioDevice" Text
"SDL_OpenAudioDevice" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type).
MonadIO m =>
Ptr CChar
-> CInt -> Ptr AudioSpec -> Ptr AudioSpec -> CInt -> m Word32
Raw.openAudioDevice Ptr CChar
cDevName (forall a. Num a => AudioDeviceUsage -> a
encodeUsage AudioDeviceUsage
openDeviceUsage) Ptr AudioSpec
desiredSpecPtr Ptr AudioSpec
actualSpecPtr CInt
changes
AudioSpec
actual <- forall a. Storable a => Ptr a -> IO a
peek Ptr AudioSpec
actualSpecPtr
let audioDevice :: AudioDevice
audioDevice = Word32 -> AudioDevice
AudioDevice Word32
devId
anAudioFormat :: AnAudioFormat
anAudioFormat = Word16 -> AnAudioFormat
decodeAudioFormat (AudioSpec -> Word16
Raw.audioSpecFormat AudioSpec
actual)
spec :: AudioSpec
spec =
case AnAudioFormat
anAudioFormat of
AnAudioFormat AudioFormat sampleType
audioFormat ->
AudioSpec { audioSpecFreq :: CInt
audioSpecFreq = AudioSpec -> CInt
Raw.audioSpecFreq AudioSpec
actual
, audioSpecFormat :: AudioFormat sampleType
audioSpecFormat = AudioFormat sampleType
audioFormat
, audioSpecChannels :: Channels
audioSpecChannels = forall a b. Show a => Text -> Text -> (a -> Maybe b) -> a -> b
fromC Text
"SDL.Audio.openAudioDevice" Text
"audioSpecChannels" forall {a}. (Eq a, Num a) => a -> Maybe Channels
readChannels (AudioSpec -> Word8
Raw.audioSpecChannels AudioSpec
actual)
, audioSpecSilence :: Word8
audioSpecSilence = AudioSpec -> Word8
Raw.audioSpecSilence AudioSpec
actual
, audioSpecSize :: Word32
audioSpecSize = AudioSpec -> Word32
Raw.audioSpecSize AudioSpec
actual
, audioSpecSamples :: Word16
audioSpecSamples = AudioSpec -> Word16
Raw.audioSpecSamples AudioSpec
actual
, audioSpecCallback :: AudioFormat sampleType -> IOVector sampleType -> IO ()
audioSpecCallback = forall actualSampleType.
AudioFormat actualSampleType -> IOVector actualSampleType -> IO ()
openDeviceCallback
}
forall a. IORef a -> a -> IO ()
writeIORef IORef AnAudioFormat
anAudioFormatRef AnAudioFormat
anAudioFormat
forall (m :: Type -> Type) a. Monad m => a -> m a
return (AudioDevice
audioDevice, AudioSpec
spec)
where
changes :: CInt
changes = forall (t :: Type -> Type) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl forall a. Bits a => a -> a -> a
(.|.) CInt
0 [ forall a b. (a -> b) -> (a -> b) -> Changeable a -> b
foldChangeable (forall a b. a -> b -> a
const CInt
0) (forall a b. a -> b -> a
const forall {a}. (Eq a, Num a) => a
Raw.SDL_AUDIO_ALLOW_FREQUENCY_CHANGE) Changeable CInt
openDeviceFreq
, forall a b. (a -> b) -> (a -> b) -> Changeable a -> b
foldChangeable (forall a b. a -> b -> a
const CInt
0) (forall a b. a -> b -> a
const forall {a}. (Eq a, Num a) => a
Raw.SDL_AUDIO_ALLOW_FORMAT_CHANGE) Changeable (AudioFormat sampleType)
openDeviceFormat
, forall a b. (a -> b) -> (a -> b) -> Changeable a -> b
foldChangeable (forall a b. a -> b -> a
const CInt
0) (forall a b. a -> b -> a
const forall {a}. (Eq a, Num a) => a
Raw.SDL_AUDIO_ALLOW_CHANNELS_CHANGE) Changeable Channels
openDeviceChannels
]
channelsToWord8 :: Channels -> a
channelsToWord8 Channels
Mono = a
1
channelsToWord8 Channels
Stereo = a
2
channelsToWord8 Channels
Quad = a
4
channelsToWord8 Channels
FivePointOne = a
6
readChannels :: a -> Maybe Channels
readChannels a
1 = forall a. a -> Maybe a
Just Channels
Mono
readChannels a
2 = forall a. a -> Maybe a
Just Channels
Stereo
readChannels a
4 = forall a. a -> Maybe a
Just Channels
Quad
readChannels a
6 = forall a. a -> Maybe a
Just Channels
FivePointOne
readChannels a
_ = forall a. Maybe a
Nothing
desiredSpec :: AudioCallback -> AudioSpec
desiredSpec AudioCallback
cb = Raw.AudioSpec
{ audioSpecFreq :: CInt
Raw.audioSpecFreq = forall a. Changeable a -> a
unpackChangeable Changeable CInt
openDeviceFreq
, audioSpecFormat :: Word16
Raw.audioSpecFormat = forall sampleType. AudioFormat sampleType -> Word16
encodeAudioFormat (forall a. Changeable a -> a
unpackChangeable Changeable (AudioFormat sampleType)
openDeviceFormat)
, audioSpecChannels :: Word8
Raw.audioSpecChannels = forall {a}. Num a => Channels -> a
channelsToWord8 (forall a. Changeable a -> a
unpackChangeable Changeable Channels
openDeviceChannels)
, audioSpecSilence :: Word8
Raw.audioSpecSilence = Word8
0
, audioSpecSize :: Word32
Raw.audioSpecSize = Word32
0
, audioSpecSamples :: Word16
Raw.audioSpecSamples = Word16
openDeviceSamples
, audioSpecCallback :: AudioCallback
Raw.audioSpecCallback = AudioCallback
cb
, audioSpecUserdata :: Ptr ()
Raw.audioSpecUserdata = forall a. Ptr a
nullPtr
}
audioFormatStorable :: AudioFormat sampleType -> Dict (Storable sampleType)
audioFormatStorable :: forall sampleType.
AudioFormat sampleType -> Dict (Storable sampleType)
audioFormatStorable AudioFormat sampleType
Signed8BitAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
Unsigned8BitAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
Signed16BitLEAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
Signed16BitBEAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
Signed16BitNativeAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
Unsigned16BitLEAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
Unsigned16BitBEAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
Unsigned16BitNativeAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
Signed32BitLEAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
Signed32BitBEAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
Signed32BitNativeAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
FloatingLEAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
FloatingBEAudio = forall (c :: Constraint). c => Dict c
Dict
audioFormatStorable AudioFormat sampleType
FloatingNativeAudio = forall (c :: Constraint). c => Dict c
Dict
data Dict :: Constraint -> Type where
Dict :: c => Dict c
closeAudioDevice :: MonadIO m => AudioDevice -> m ()
closeAudioDevice :: forall (m :: Type -> Type). MonadIO m => AudioDevice -> m ()
closeAudioDevice (AudioDevice Word32
d) = forall (m :: Type -> Type). MonadIO m => Word32 -> m ()
Raw.closeAudioDevice Word32
d
newtype AudioDevice = AudioDevice (Raw.AudioDeviceID)
deriving (AudioDevice -> AudioDevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AudioDevice -> AudioDevice -> Bool
$c/= :: AudioDevice -> AudioDevice -> Bool
== :: AudioDevice -> AudioDevice -> Bool
$c== :: AudioDevice -> AudioDevice -> Bool
Eq, Typeable)
getAudioDeviceNames :: MonadIO m => AudioDeviceUsage -> m (Maybe (V.Vector Text))
getAudioDeviceNames :: forall (m :: Type -> Type).
MonadIO m =>
AudioDeviceUsage -> m (Maybe (Vector Text))
getAudioDeviceNames AudioDeviceUsage
usage = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
CInt
n <- forall (m :: Type -> Type). MonadIO m => CInt -> m CInt
Raw.getNumAudioDevices CInt
usage'
if CInt
n forall a. Eq a => a -> a -> Bool
== -CInt
1
then forall (m :: Type -> Type) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList) forall a b. (a -> b) -> a -> b
$
forall (t :: Type -> Type) (f :: Type -> Type) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [CInt
0 .. (CInt
n forall a. Num a => a -> a -> a
- CInt
1)] forall a b. (a -> b) -> a -> b
$ \CInt
i -> do
Ptr CChar
cstr <- forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Audio.getAudioDeviceNames" Text
"SDL_GetAudioDeviceName" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type).
MonadIO m =>
CInt -> CInt -> m (Ptr CChar)
Raw.getAudioDeviceName CInt
i CInt
usage'
ByteString -> Text
Text.decodeUtf8 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CChar -> IO ByteString
BS.packCString Ptr CChar
cstr
where usage' :: CInt
usage' = forall a. Num a => AudioDeviceUsage -> a
encodeUsage AudioDeviceUsage
usage
data AudioFormat sampleType where
Signed8BitAudio :: AudioFormat Int8
Unsigned8BitAudio :: AudioFormat Word8
Signed16BitLEAudio :: AudioFormat Int16
Signed16BitBEAudio :: AudioFormat Int16
Signed16BitNativeAudio :: AudioFormat Int16
Unsigned16BitLEAudio :: AudioFormat Word16
Unsigned16BitBEAudio :: AudioFormat Word16
Unsigned16BitNativeAudio :: AudioFormat Word16
Signed32BitLEAudio :: AudioFormat Int32
Signed32BitBEAudio :: AudioFormat Int32
Signed32BitNativeAudio :: AudioFormat Int32
FloatingLEAudio :: AudioFormat Float
FloatingBEAudio :: AudioFormat Float
FloatingNativeAudio :: AudioFormat Float
deriving instance Eq (AudioFormat sampleType)
deriving instance Ord (AudioFormat sampleType)
deriving instance Show (AudioFormat sampleType)
data AnAudioFormat where
AnAudioFormat :: AudioFormat sampleType -> AnAudioFormat
encodeAudioFormat :: AudioFormat sampleType -> Word16
encodeAudioFormat :: forall sampleType. AudioFormat sampleType -> Word16
encodeAudioFormat AudioFormat sampleType
Signed8BitAudio = Word16
Raw.SDL_AUDIO_S8
encodeAudioFormat AudioFormat sampleType
Unsigned8BitAudio = Word16
Raw.SDL_AUDIO_U8
encodeAudioFormat AudioFormat sampleType
Signed16BitLEAudio = Word16
Raw.SDL_AUDIO_S16LSB
encodeAudioFormat AudioFormat sampleType
Signed16BitBEAudio = Word16
Raw.SDL_AUDIO_S16MSB
encodeAudioFormat AudioFormat sampleType
Signed16BitNativeAudio = Word16
Raw.SDL_AUDIO_S16SYS
encodeAudioFormat AudioFormat sampleType
Unsigned16BitLEAudio = Word16
Raw.SDL_AUDIO_U16LSB
encodeAudioFormat AudioFormat sampleType
Unsigned16BitBEAudio = Word16
Raw.SDL_AUDIO_U16MSB
encodeAudioFormat AudioFormat sampleType
Unsigned16BitNativeAudio = Word16
Raw.SDL_AUDIO_U16SYS
encodeAudioFormat AudioFormat sampleType
Signed32BitLEAudio = Word16
Raw.SDL_AUDIO_S32LSB
encodeAudioFormat AudioFormat sampleType
Signed32BitBEAudio = Word16
Raw.SDL_AUDIO_S32MSB
encodeAudioFormat AudioFormat sampleType
Signed32BitNativeAudio = Word16
Raw.SDL_AUDIO_S32SYS
encodeAudioFormat AudioFormat sampleType
FloatingLEAudio = Word16
Raw.SDL_AUDIO_F32LSB
encodeAudioFormat AudioFormat sampleType
FloatingBEAudio = Word16
Raw.SDL_AUDIO_F32MSB
encodeAudioFormat AudioFormat sampleType
FloatingNativeAudio = Word16
Raw.SDL_AUDIO_F32SYS
decodeAudioFormat :: Word16 -> AnAudioFormat
decodeAudioFormat :: Word16 -> AnAudioFormat
decodeAudioFormat Word16
Raw.SDL_AUDIO_S8 = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Int8
Signed8BitAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_U8 = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Word8
Unsigned8BitAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_S16LSB = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Int16
Signed16BitLEAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_S16MSB = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Int16
Signed16BitBEAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_S16SYS = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Int16
Signed16BitNativeAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_U16LSB = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Word16
Unsigned16BitLEAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_U16MSB = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Word16
Unsigned16BitBEAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_U16SYS = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Word16
Unsigned16BitNativeAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_S32LSB = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Int32
Signed32BitLEAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_S32MSB = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Int32
Signed32BitBEAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_S32SYS = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Int32
Signed32BitNativeAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_F32LSB = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Float
FloatingLEAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_F32MSB = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Float
FloatingBEAudio
decodeAudioFormat Word16
Raw.SDL_AUDIO_F32SYS = forall sampleType. AudioFormat sampleType -> AnAudioFormat
AnAudioFormat AudioFormat Float
FloatingNativeAudio
decodeAudioFormat Word16
x = forall a. HasCallStack => [Char] -> a
error ([Char]
"decodeAudioFormat failed: Unknown format " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Word16
x)
data Channels
= Mono
| Stereo
| Quad
| FivePointOne
deriving (Channels
forall a. a -> a -> Bounded a
maxBound :: Channels
$cmaxBound :: Channels
minBound :: Channels
$cminBound :: Channels
Bounded,Typeable Channels
Channels -> DataType
Channels -> Constr
(forall b. Data b => b -> b) -> Channels -> Channels
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Channels -> u
forall u. (forall d. Data d => d -> u) -> Channels -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Channels -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Channels -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Channels -> m Channels
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Channels -> m Channels
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Channels
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Channels -> c Channels
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Channels)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Channels)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Channels -> m Channels
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Channels -> m Channels
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Channels -> m Channels
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Channels -> m Channels
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Channels -> m Channels
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Channels -> m Channels
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Channels -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Channels -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Channels -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Channels -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Channels -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Channels -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Channels -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Channels -> r
gmapT :: (forall b. Data b => b -> b) -> Channels -> Channels
$cgmapT :: (forall b. Data b => b -> b) -> Channels -> Channels
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Channels)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Channels)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Channels)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Channels)
dataTypeOf :: Channels -> DataType
$cdataTypeOf :: Channels -> DataType
toConstr :: Channels -> Constr
$ctoConstr :: Channels -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Channels
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Channels
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Channels -> c Channels
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Channels -> c Channels
Data,Int -> Channels
Channels -> Int
Channels -> [Channels]
Channels -> Channels
Channels -> Channels -> [Channels]
Channels -> Channels -> Channels -> [Channels]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Channels -> Channels -> Channels -> [Channels]
$cenumFromThenTo :: Channels -> Channels -> Channels -> [Channels]
enumFromTo :: Channels -> Channels -> [Channels]
$cenumFromTo :: Channels -> Channels -> [Channels]
enumFromThen :: Channels -> Channels -> [Channels]
$cenumFromThen :: Channels -> Channels -> [Channels]
enumFrom :: Channels -> [Channels]
$cenumFrom :: Channels -> [Channels]
fromEnum :: Channels -> Int
$cfromEnum :: Channels -> Int
toEnum :: Int -> Channels
$ctoEnum :: Int -> Channels
pred :: Channels -> Channels
$cpred :: Channels -> Channels
succ :: Channels -> Channels
$csucc :: Channels -> Channels
Enum,Channels -> Channels -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Channels -> Channels -> Bool
$c/= :: Channels -> Channels -> Bool
== :: Channels -> Channels -> Bool
$c== :: Channels -> Channels -> Bool
Eq,forall x. Rep Channels x -> Channels
forall x. Channels -> Rep Channels x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Channels x -> Channels
$cfrom :: forall x. Channels -> Rep Channels x
Generic,Eq Channels
Channels -> Channels -> Bool
Channels -> Channels -> Ordering
Channels -> Channels -> Channels
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Channels -> Channels -> Channels
$cmin :: Channels -> Channels -> Channels
max :: Channels -> Channels -> Channels
$cmax :: Channels -> Channels -> Channels
>= :: Channels -> Channels -> Bool
$c>= :: Channels -> Channels -> Bool
> :: Channels -> Channels -> Bool
$c> :: Channels -> Channels -> Bool
<= :: Channels -> Channels -> Bool
$c<= :: Channels -> Channels -> Bool
< :: Channels -> Channels -> Bool
$c< :: Channels -> Channels -> Bool
compare :: Channels -> Channels -> Ordering
$ccompare :: Channels -> Channels -> Ordering
Ord,ReadPrec [Channels]
ReadPrec Channels
Int -> ReadS Channels
ReadS [Channels]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Channels]
$creadListPrec :: ReadPrec [Channels]
readPrec :: ReadPrec Channels
$creadPrec :: ReadPrec Channels
readList :: ReadS [Channels]
$creadList :: ReadS [Channels]
readsPrec :: Int -> ReadS Channels
$creadsPrec :: Int -> ReadS Channels
Read,Int -> Channels -> ShowS
[Channels] -> ShowS
Channels -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Channels] -> ShowS
$cshowList :: [Channels] -> ShowS
show :: Channels -> [Char]
$cshow :: Channels -> [Char]
showsPrec :: Int -> Channels -> ShowS
$cshowsPrec :: Int -> Channels -> ShowS
Show,Typeable)
data AudioSpec = forall sampleType. AudioSpec
{ AudioSpec -> CInt
audioSpecFreq :: !CInt
, ()
audioSpecFormat :: !(AudioFormat sampleType)
, AudioSpec -> Channels
audioSpecChannels :: !Channels
, AudioSpec -> Word8
audioSpecSilence :: !Word8
, AudioSpec -> Word16
audioSpecSamples :: !Word16
, AudioSpec -> Word32
audioSpecSize :: !Word32
, ()
audioSpecCallback :: AudioFormat sampleType -> MV.IOVector sampleType -> IO ()
}
deriving (Typeable)
data AudioDeviceUsage
= ForPlayback
| ForCapture
deriving (AudioDeviceUsage
forall a. a -> a -> Bounded a
maxBound :: AudioDeviceUsage
$cmaxBound :: AudioDeviceUsage
minBound :: AudioDeviceUsage
$cminBound :: AudioDeviceUsage
Bounded, Typeable AudioDeviceUsage
AudioDeviceUsage -> DataType
AudioDeviceUsage -> Constr
(forall b. Data b => b -> b)
-> AudioDeviceUsage -> AudioDeviceUsage
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> AudioDeviceUsage -> u
forall u. (forall d. Data d => d -> u) -> AudioDeviceUsage -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceUsage -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceUsage -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> AudioDeviceUsage -> m AudioDeviceUsage
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AudioDeviceUsage -> m AudioDeviceUsage
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AudioDeviceUsage
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AudioDeviceUsage -> c AudioDeviceUsage
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AudioDeviceUsage)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AudioDeviceUsage)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AudioDeviceUsage -> m AudioDeviceUsage
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AudioDeviceUsage -> m AudioDeviceUsage
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AudioDeviceUsage -> m AudioDeviceUsage
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AudioDeviceUsage -> m AudioDeviceUsage
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> AudioDeviceUsage -> m AudioDeviceUsage
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> AudioDeviceUsage -> m AudioDeviceUsage
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AudioDeviceUsage -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AudioDeviceUsage -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> AudioDeviceUsage -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> AudioDeviceUsage -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceUsage -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceUsage -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceUsage -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceUsage -> r
gmapT :: (forall b. Data b => b -> b)
-> AudioDeviceUsage -> AudioDeviceUsage
$cgmapT :: (forall b. Data b => b -> b)
-> AudioDeviceUsage -> AudioDeviceUsage
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AudioDeviceUsage)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AudioDeviceUsage)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AudioDeviceUsage)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AudioDeviceUsage)
dataTypeOf :: AudioDeviceUsage -> DataType
$cdataTypeOf :: AudioDeviceUsage -> DataType
toConstr :: AudioDeviceUsage -> Constr
$ctoConstr :: AudioDeviceUsage -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AudioDeviceUsage
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AudioDeviceUsage
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AudioDeviceUsage -> c AudioDeviceUsage
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AudioDeviceUsage -> c AudioDeviceUsage
Data, Int -> AudioDeviceUsage
AudioDeviceUsage -> Int
AudioDeviceUsage -> [AudioDeviceUsage]
AudioDeviceUsage -> AudioDeviceUsage
AudioDeviceUsage -> AudioDeviceUsage -> [AudioDeviceUsage]
AudioDeviceUsage
-> AudioDeviceUsage -> AudioDeviceUsage -> [AudioDeviceUsage]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: AudioDeviceUsage
-> AudioDeviceUsage -> AudioDeviceUsage -> [AudioDeviceUsage]
$cenumFromThenTo :: AudioDeviceUsage
-> AudioDeviceUsage -> AudioDeviceUsage -> [AudioDeviceUsage]
enumFromTo :: AudioDeviceUsage -> AudioDeviceUsage -> [AudioDeviceUsage]
$cenumFromTo :: AudioDeviceUsage -> AudioDeviceUsage -> [AudioDeviceUsage]
enumFromThen :: AudioDeviceUsage -> AudioDeviceUsage -> [AudioDeviceUsage]
$cenumFromThen :: AudioDeviceUsage -> AudioDeviceUsage -> [AudioDeviceUsage]
enumFrom :: AudioDeviceUsage -> [AudioDeviceUsage]
$cenumFrom :: AudioDeviceUsage -> [AudioDeviceUsage]
fromEnum :: AudioDeviceUsage -> Int
$cfromEnum :: AudioDeviceUsage -> Int
toEnum :: Int -> AudioDeviceUsage
$ctoEnum :: Int -> AudioDeviceUsage
pred :: AudioDeviceUsage -> AudioDeviceUsage
$cpred :: AudioDeviceUsage -> AudioDeviceUsage
succ :: AudioDeviceUsage -> AudioDeviceUsage
$csucc :: AudioDeviceUsage -> AudioDeviceUsage
Enum, AudioDeviceUsage -> AudioDeviceUsage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
$c/= :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
== :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
$c== :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
Eq, forall x. Rep AudioDeviceUsage x -> AudioDeviceUsage
forall x. AudioDeviceUsage -> Rep AudioDeviceUsage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AudioDeviceUsage x -> AudioDeviceUsage
$cfrom :: forall x. AudioDeviceUsage -> Rep AudioDeviceUsage x
Generic, Eq AudioDeviceUsage
AudioDeviceUsage -> AudioDeviceUsage -> Bool
AudioDeviceUsage -> AudioDeviceUsage -> Ordering
AudioDeviceUsage -> AudioDeviceUsage -> AudioDeviceUsage
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AudioDeviceUsage -> AudioDeviceUsage -> AudioDeviceUsage
$cmin :: AudioDeviceUsage -> AudioDeviceUsage -> AudioDeviceUsage
max :: AudioDeviceUsage -> AudioDeviceUsage -> AudioDeviceUsage
$cmax :: AudioDeviceUsage -> AudioDeviceUsage -> AudioDeviceUsage
>= :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
$c>= :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
> :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
$c> :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
<= :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
$c<= :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
< :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
$c< :: AudioDeviceUsage -> AudioDeviceUsage -> Bool
compare :: AudioDeviceUsage -> AudioDeviceUsage -> Ordering
$ccompare :: AudioDeviceUsage -> AudioDeviceUsage -> Ordering
Ord, ReadPrec [AudioDeviceUsage]
ReadPrec AudioDeviceUsage
Int -> ReadS AudioDeviceUsage
ReadS [AudioDeviceUsage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AudioDeviceUsage]
$creadListPrec :: ReadPrec [AudioDeviceUsage]
readPrec :: ReadPrec AudioDeviceUsage
$creadPrec :: ReadPrec AudioDeviceUsage
readList :: ReadS [AudioDeviceUsage]
$creadList :: ReadS [AudioDeviceUsage]
readsPrec :: Int -> ReadS AudioDeviceUsage
$creadsPrec :: Int -> ReadS AudioDeviceUsage
Read, Int -> AudioDeviceUsage -> ShowS
[AudioDeviceUsage] -> ShowS
AudioDeviceUsage -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [AudioDeviceUsage] -> ShowS
$cshowList :: [AudioDeviceUsage] -> ShowS
show :: AudioDeviceUsage -> [Char]
$cshow :: AudioDeviceUsage -> [Char]
showsPrec :: Int -> AudioDeviceUsage -> ShowS
$cshowsPrec :: Int -> AudioDeviceUsage -> ShowS
Show, Typeable)
encodeUsage :: Num a => AudioDeviceUsage -> a
encodeUsage :: forall a. Num a => AudioDeviceUsage -> a
encodeUsage AudioDeviceUsage
usage =
case AudioDeviceUsage
usage of
AudioDeviceUsage
ForPlayback -> a
0
AudioDeviceUsage
ForCapture -> a
1
data Changeable a
= Mandate !a
| Desire !a
deriving (Changeable a -> DataType
Changeable a -> Constr
forall {a}. Data a => Typeable (Changeable a)
forall a. Data a => Changeable a -> DataType
forall a. Data a => Changeable a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> Changeable a -> Changeable a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Changeable a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> Changeable a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Changeable a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Changeable a -> r
forall a (m :: Type -> Type).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)
forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)
forall a (c :: Type -> Type).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Changeable a)
forall a (c :: Type -> Type).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Changeable a -> c (Changeable a)
forall a (t :: Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Changeable a))
forall a (t :: Type -> Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Changeable a))
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Changeable a)
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Changeable a -> c (Changeable a)
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Changeable a))
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)
$cgmapMo :: forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)
$cgmapMp :: forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)
$cgmapM :: forall a (m :: Type -> Type).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Changeable a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Changeable a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Changeable a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> Changeable a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Changeable a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Changeable a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Changeable a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Changeable a -> r
gmapT :: (forall b. Data b => b -> b) -> Changeable a -> Changeable a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Changeable a -> Changeable a
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Changeable a))
$cdataCast2 :: forall a (t :: Type -> Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Changeable a))
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Changeable a))
$cdataCast1 :: forall a (t :: Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Changeable a))
dataTypeOf :: Changeable a -> DataType
$cdataTypeOf :: forall a. Data a => Changeable a -> DataType
toConstr :: Changeable a -> Constr
$ctoConstr :: forall a. Data a => Changeable a -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Changeable a)
$cgunfold :: forall a (c :: Type -> Type).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Changeable a)
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Changeable a -> c (Changeable a)
$cgfoldl :: forall a (c :: Type -> Type).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Changeable a -> c (Changeable a)
Data, forall a. Eq a => a -> Changeable a -> Bool
forall a. Num a => Changeable a -> a
forall a. Ord a => Changeable a -> a
forall m. Monoid m => Changeable m -> m
forall a. Changeable a -> Bool
forall a. Changeable a -> Int
forall a. Changeable a -> [a]
forall a. (a -> a -> a) -> Changeable a -> a
forall m a. Monoid m => (a -> m) -> Changeable a -> m
forall b a. (b -> a -> b) -> b -> Changeable a -> b
forall a b. (a -> b -> b) -> b -> Changeable a -> b
forall (t :: Type -> Type).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => Changeable a -> a
$cproduct :: forall a. Num a => Changeable a -> a
sum :: forall a. Num a => Changeable a -> a
$csum :: forall a. Num a => Changeable a -> a
minimum :: forall a. Ord a => Changeable a -> a
$cminimum :: forall a. Ord a => Changeable a -> a
maximum :: forall a. Ord a => Changeable a -> a
$cmaximum :: forall a. Ord a => Changeable a -> a
elem :: forall a. Eq a => a -> Changeable a -> Bool
$celem :: forall a. Eq a => a -> Changeable a -> Bool
length :: forall a. Changeable a -> Int
$clength :: forall a. Changeable a -> Int
null :: forall a. Changeable a -> Bool
$cnull :: forall a. Changeable a -> Bool
toList :: forall a. Changeable a -> [a]
$ctoList :: forall a. Changeable a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Changeable a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Changeable a -> a
foldr1 :: forall a. (a -> a -> a) -> Changeable a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Changeable a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Changeable a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Changeable a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Changeable a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Changeable a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Changeable a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Changeable a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Changeable a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Changeable a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Changeable a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Changeable a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Changeable a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Changeable a -> m
fold :: forall m. Monoid m => Changeable m -> m
$cfold :: forall m. Monoid m => Changeable m -> m
Foldable, forall a b. a -> Changeable b -> Changeable a
forall a b. (a -> b) -> Changeable a -> Changeable b
forall (f :: Type -> Type).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Changeable b -> Changeable a
$c<$ :: forall a b. a -> Changeable b -> Changeable a
fmap :: forall a b. (a -> b) -> Changeable a -> Changeable b
$cfmap :: forall a b. (a -> b) -> Changeable a -> Changeable b
Functor, Changeable a -> Changeable a -> Bool
forall a. Eq a => Changeable a -> Changeable a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Changeable a -> Changeable a -> Bool
$c/= :: forall a. Eq a => Changeable a -> Changeable a -> Bool
== :: Changeable a -> Changeable a -> Bool
$c== :: forall a. Eq a => Changeable a -> Changeable a -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Changeable a) x -> Changeable a
forall a x. Changeable a -> Rep (Changeable a) x
$cto :: forall a x. Rep (Changeable a) x -> Changeable a
$cfrom :: forall a x. Changeable a -> Rep (Changeable a) x
Generic, ReadPrec [Changeable a]
ReadPrec (Changeable a)
ReadS [Changeable a]
forall a. Read a => ReadPrec [Changeable a]
forall a. Read a => ReadPrec (Changeable a)
forall a. Read a => Int -> ReadS (Changeable a)
forall a. Read a => ReadS [Changeable a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Changeable a]
$creadListPrec :: forall a. Read a => ReadPrec [Changeable a]
readPrec :: ReadPrec (Changeable a)
$creadPrec :: forall a. Read a => ReadPrec (Changeable a)
readList :: ReadS [Changeable a]
$creadList :: forall a. Read a => ReadS [Changeable a]
readsPrec :: Int -> ReadS (Changeable a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Changeable a)
Read, Int -> Changeable a -> ShowS
forall a. Show a => Int -> Changeable a -> ShowS
forall a. Show a => [Changeable a] -> ShowS
forall a. Show a => Changeable a -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Changeable a] -> ShowS
$cshowList :: forall a. Show a => [Changeable a] -> ShowS
show :: Changeable a -> [Char]
$cshow :: forall a. Show a => Changeable a -> [Char]
showsPrec :: Int -> Changeable a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Changeable a -> ShowS
Show, Functor Changeable
Foldable Changeable
forall (t :: Type -> Type).
Functor t
-> Foldable t
-> (forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: Type -> Type) a.
Applicative f =>
t (f a) -> f (t a))
-> (forall (m :: Type -> Type) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: Type -> Type) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: Type -> Type) a.
Monad m =>
Changeable (m a) -> m (Changeable a)
forall (f :: Type -> Type) a.
Applicative f =>
Changeable (f a) -> f (Changeable a)
forall (m :: Type -> Type) a b.
Monad m =>
(a -> m b) -> Changeable a -> m (Changeable b)
forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> Changeable a -> f (Changeable b)
sequence :: forall (m :: Type -> Type) a.
Monad m =>
Changeable (m a) -> m (Changeable a)
$csequence :: forall (m :: Type -> Type) a.
Monad m =>
Changeable (m a) -> m (Changeable a)
mapM :: forall (m :: Type -> Type) a b.
Monad m =>
(a -> m b) -> Changeable a -> m (Changeable b)
$cmapM :: forall (m :: Type -> Type) a b.
Monad m =>
(a -> m b) -> Changeable a -> m (Changeable b)
sequenceA :: forall (f :: Type -> Type) a.
Applicative f =>
Changeable (f a) -> f (Changeable a)
$csequenceA :: forall (f :: Type -> Type) a.
Applicative f =>
Changeable (f a) -> f (Changeable a)
traverse :: forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> Changeable a -> f (Changeable b)
$ctraverse :: forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> Changeable a -> f (Changeable b)
Traversable, Typeable)
foldChangeable :: (a -> b) -> (a -> b) -> Changeable a -> b
foldChangeable :: forall a b. (a -> b) -> (a -> b) -> Changeable a -> b
foldChangeable a -> b
f a -> b
_ (Mandate a
a) = a -> b
f a
a
foldChangeable a -> b
_ a -> b
g (Desire a
a) = a -> b
g a
a
unpackChangeable :: Changeable a -> a
unpackChangeable :: forall a. Changeable a -> a
unpackChangeable = forall a b. (a -> b) -> (a -> b) -> Changeable a -> b
foldChangeable forall a. a -> a
id forall a. a -> a
id
data LockState
= Locked
| Unlocked
deriving (LockState
forall a. a -> a -> Bounded a
maxBound :: LockState
$cmaxBound :: LockState
minBound :: LockState
$cminBound :: LockState
Bounded, Typeable LockState
LockState -> DataType
LockState -> Constr
(forall b. Data b => b -> b) -> LockState -> LockState
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> LockState -> u
forall u. (forall d. Data d => d -> u) -> LockState -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LockState -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LockState -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> LockState -> m LockState
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LockState -> m LockState
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LockState
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LockState -> c LockState
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LockState)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LockState)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LockState -> m LockState
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LockState -> m LockState
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LockState -> m LockState
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LockState -> m LockState
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> LockState -> m LockState
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> LockState -> m LockState
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LockState -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LockState -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> LockState -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LockState -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LockState -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LockState -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LockState -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LockState -> r
gmapT :: (forall b. Data b => b -> b) -> LockState -> LockState
$cgmapT :: (forall b. Data b => b -> b) -> LockState -> LockState
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LockState)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LockState)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LockState)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LockState)
dataTypeOf :: LockState -> DataType
$cdataTypeOf :: LockState -> DataType
toConstr :: LockState -> Constr
$ctoConstr :: LockState -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LockState
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LockState
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LockState -> c LockState
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LockState -> c LockState
Data, Int -> LockState
LockState -> Int
LockState -> [LockState]
LockState -> LockState
LockState -> LockState -> [LockState]
LockState -> LockState -> LockState -> [LockState]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: LockState -> LockState -> LockState -> [LockState]
$cenumFromThenTo :: LockState -> LockState -> LockState -> [LockState]
enumFromTo :: LockState -> LockState -> [LockState]
$cenumFromTo :: LockState -> LockState -> [LockState]
enumFromThen :: LockState -> LockState -> [LockState]
$cenumFromThen :: LockState -> LockState -> [LockState]
enumFrom :: LockState -> [LockState]
$cenumFrom :: LockState -> [LockState]
fromEnum :: LockState -> Int
$cfromEnum :: LockState -> Int
toEnum :: Int -> LockState
$ctoEnum :: Int -> LockState
pred :: LockState -> LockState
$cpred :: LockState -> LockState
succ :: LockState -> LockState
$csucc :: LockState -> LockState
Enum, LockState -> LockState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LockState -> LockState -> Bool
$c/= :: LockState -> LockState -> Bool
== :: LockState -> LockState -> Bool
$c== :: LockState -> LockState -> Bool
Eq, forall x. Rep LockState x -> LockState
forall x. LockState -> Rep LockState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LockState x -> LockState
$cfrom :: forall x. LockState -> Rep LockState x
Generic, Eq LockState
LockState -> LockState -> Bool
LockState -> LockState -> Ordering
LockState -> LockState -> LockState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LockState -> LockState -> LockState
$cmin :: LockState -> LockState -> LockState
max :: LockState -> LockState -> LockState
$cmax :: LockState -> LockState -> LockState
>= :: LockState -> LockState -> Bool
$c>= :: LockState -> LockState -> Bool
> :: LockState -> LockState -> Bool
$c> :: LockState -> LockState -> Bool
<= :: LockState -> LockState -> Bool
$c<= :: LockState -> LockState -> Bool
< :: LockState -> LockState -> Bool
$c< :: LockState -> LockState -> Bool
compare :: LockState -> LockState -> Ordering
$ccompare :: LockState -> LockState -> Ordering
Ord, ReadPrec [LockState]
ReadPrec LockState
Int -> ReadS LockState
ReadS [LockState]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LockState]
$creadListPrec :: ReadPrec [LockState]
readPrec :: ReadPrec LockState
$creadPrec :: ReadPrec LockState
readList :: ReadS [LockState]
$creadList :: ReadS [LockState]
readsPrec :: Int -> ReadS LockState
$creadsPrec :: Int -> ReadS LockState
Read, Int -> LockState -> ShowS
[LockState] -> ShowS
LockState -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [LockState] -> ShowS
$cshowList :: [LockState] -> ShowS
show :: LockState -> [Char]
$cshow :: LockState -> [Char]
showsPrec :: Int -> LockState -> ShowS
$cshowsPrec :: Int -> LockState -> ShowS
Show, Typeable)
setAudioDeviceLocked :: MonadIO m => AudioDevice -> LockState -> m ()
setAudioDeviceLocked :: forall (m :: Type -> Type).
MonadIO m =>
AudioDevice -> LockState -> m ()
setAudioDeviceLocked (AudioDevice Word32
d) LockState
Locked = forall (m :: Type -> Type). MonadIO m => Word32 -> m ()
Raw.lockAudioDevice Word32
d
setAudioDeviceLocked (AudioDevice Word32
d) LockState
Unlocked = forall (m :: Type -> Type). MonadIO m => Word32 -> m ()
Raw.unlockAudioDevice Word32
d
data PlaybackState
= Pause
| Play
deriving (PlaybackState
forall a. a -> a -> Bounded a
maxBound :: PlaybackState
$cmaxBound :: PlaybackState
minBound :: PlaybackState
$cminBound :: PlaybackState
Bounded, Int -> PlaybackState
PlaybackState -> Int
PlaybackState -> [PlaybackState]
PlaybackState -> PlaybackState
PlaybackState -> PlaybackState -> [PlaybackState]
PlaybackState -> PlaybackState -> PlaybackState -> [PlaybackState]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: PlaybackState -> PlaybackState -> PlaybackState -> [PlaybackState]
$cenumFromThenTo :: PlaybackState -> PlaybackState -> PlaybackState -> [PlaybackState]
enumFromTo :: PlaybackState -> PlaybackState -> [PlaybackState]
$cenumFromTo :: PlaybackState -> PlaybackState -> [PlaybackState]
enumFromThen :: PlaybackState -> PlaybackState -> [PlaybackState]
$cenumFromThen :: PlaybackState -> PlaybackState -> [PlaybackState]
enumFrom :: PlaybackState -> [PlaybackState]
$cenumFrom :: PlaybackState -> [PlaybackState]
fromEnum :: PlaybackState -> Int
$cfromEnum :: PlaybackState -> Int
toEnum :: Int -> PlaybackState
$ctoEnum :: Int -> PlaybackState
pred :: PlaybackState -> PlaybackState
$cpred :: PlaybackState -> PlaybackState
succ :: PlaybackState -> PlaybackState
$csucc :: PlaybackState -> PlaybackState
Enum, PlaybackState -> PlaybackState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PlaybackState -> PlaybackState -> Bool
$c/= :: PlaybackState -> PlaybackState -> Bool
== :: PlaybackState -> PlaybackState -> Bool
$c== :: PlaybackState -> PlaybackState -> Bool
Eq, Eq PlaybackState
PlaybackState -> PlaybackState -> Bool
PlaybackState -> PlaybackState -> Ordering
PlaybackState -> PlaybackState -> PlaybackState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PlaybackState -> PlaybackState -> PlaybackState
$cmin :: PlaybackState -> PlaybackState -> PlaybackState
max :: PlaybackState -> PlaybackState -> PlaybackState
$cmax :: PlaybackState -> PlaybackState -> PlaybackState
>= :: PlaybackState -> PlaybackState -> Bool
$c>= :: PlaybackState -> PlaybackState -> Bool
> :: PlaybackState -> PlaybackState -> Bool
$c> :: PlaybackState -> PlaybackState -> Bool
<= :: PlaybackState -> PlaybackState -> Bool
$c<= :: PlaybackState -> PlaybackState -> Bool
< :: PlaybackState -> PlaybackState -> Bool
$c< :: PlaybackState -> PlaybackState -> Bool
compare :: PlaybackState -> PlaybackState -> Ordering
$ccompare :: PlaybackState -> PlaybackState -> Ordering
Ord, ReadPrec [PlaybackState]
ReadPrec PlaybackState
Int -> ReadS PlaybackState
ReadS [PlaybackState]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PlaybackState]
$creadListPrec :: ReadPrec [PlaybackState]
readPrec :: ReadPrec PlaybackState
$creadPrec :: ReadPrec PlaybackState
readList :: ReadS [PlaybackState]
$creadList :: ReadS [PlaybackState]
readsPrec :: Int -> ReadS PlaybackState
$creadsPrec :: Int -> ReadS PlaybackState
Read, Typeable PlaybackState
PlaybackState -> DataType
PlaybackState -> Constr
(forall b. Data b => b -> b) -> PlaybackState -> PlaybackState
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PlaybackState -> u
forall u. (forall d. Data d => d -> u) -> PlaybackState -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PlaybackState -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PlaybackState -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PlaybackState
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PlaybackState -> c PlaybackState
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PlaybackState)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PlaybackState)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PlaybackState -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PlaybackState -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PlaybackState -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PlaybackState -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PlaybackState -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PlaybackState -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PlaybackState -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PlaybackState -> r
gmapT :: (forall b. Data b => b -> b) -> PlaybackState -> PlaybackState
$cgmapT :: (forall b. Data b => b -> b) -> PlaybackState -> PlaybackState
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PlaybackState)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PlaybackState)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PlaybackState)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PlaybackState)
dataTypeOf :: PlaybackState -> DataType
$cdataTypeOf :: PlaybackState -> DataType
toConstr :: PlaybackState -> Constr
$ctoConstr :: PlaybackState -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PlaybackState
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PlaybackState
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PlaybackState -> c PlaybackState
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PlaybackState -> c PlaybackState
Data, forall x. Rep PlaybackState x -> PlaybackState
forall x. PlaybackState -> Rep PlaybackState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PlaybackState x -> PlaybackState
$cfrom :: forall x. PlaybackState -> Rep PlaybackState x
Generic, Int -> PlaybackState -> ShowS
[PlaybackState] -> ShowS
PlaybackState -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [PlaybackState] -> ShowS
$cshowList :: [PlaybackState] -> ShowS
show :: PlaybackState -> [Char]
$cshow :: PlaybackState -> [Char]
showsPrec :: Int -> PlaybackState -> ShowS
$cshowsPrec :: Int -> PlaybackState -> ShowS
Show, Typeable)
setAudioDevicePlaybackState :: MonadIO m => AudioDevice -> PlaybackState -> m ()
setAudioDevicePlaybackState :: forall (m :: Type -> Type).
MonadIO m =>
AudioDevice -> PlaybackState -> m ()
setAudioDevicePlaybackState (AudioDevice Word32
d) PlaybackState
Pause = forall (m :: Type -> Type). MonadIO m => Word32 -> CInt -> m ()
Raw.pauseAudioDevice Word32
d CInt
1
setAudioDevicePlaybackState (AudioDevice Word32
d) PlaybackState
Play = forall (m :: Type -> Type). MonadIO m => Word32 -> CInt -> m ()
Raw.pauseAudioDevice Word32
d CInt
0
data AudioDeviceStatus
= Playing
| Paused
| Stopped
deriving (AudioDeviceStatus
forall a. a -> a -> Bounded a
maxBound :: AudioDeviceStatus
$cmaxBound :: AudioDeviceStatus
minBound :: AudioDeviceStatus
$cminBound :: AudioDeviceStatus
Bounded, Int -> AudioDeviceStatus
AudioDeviceStatus -> Int
AudioDeviceStatus -> [AudioDeviceStatus]
AudioDeviceStatus -> AudioDeviceStatus
AudioDeviceStatus -> AudioDeviceStatus -> [AudioDeviceStatus]
AudioDeviceStatus
-> AudioDeviceStatus -> AudioDeviceStatus -> [AudioDeviceStatus]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: AudioDeviceStatus
-> AudioDeviceStatus -> AudioDeviceStatus -> [AudioDeviceStatus]
$cenumFromThenTo :: AudioDeviceStatus
-> AudioDeviceStatus -> AudioDeviceStatus -> [AudioDeviceStatus]
enumFromTo :: AudioDeviceStatus -> AudioDeviceStatus -> [AudioDeviceStatus]
$cenumFromTo :: AudioDeviceStatus -> AudioDeviceStatus -> [AudioDeviceStatus]
enumFromThen :: AudioDeviceStatus -> AudioDeviceStatus -> [AudioDeviceStatus]
$cenumFromThen :: AudioDeviceStatus -> AudioDeviceStatus -> [AudioDeviceStatus]
enumFrom :: AudioDeviceStatus -> [AudioDeviceStatus]
$cenumFrom :: AudioDeviceStatus -> [AudioDeviceStatus]
fromEnum :: AudioDeviceStatus -> Int
$cfromEnum :: AudioDeviceStatus -> Int
toEnum :: Int -> AudioDeviceStatus
$ctoEnum :: Int -> AudioDeviceStatus
pred :: AudioDeviceStatus -> AudioDeviceStatus
$cpred :: AudioDeviceStatus -> AudioDeviceStatus
succ :: AudioDeviceStatus -> AudioDeviceStatus
$csucc :: AudioDeviceStatus -> AudioDeviceStatus
Enum, AudioDeviceStatus -> AudioDeviceStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
$c/= :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
== :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
$c== :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
Eq, Eq AudioDeviceStatus
AudioDeviceStatus -> AudioDeviceStatus -> Bool
AudioDeviceStatus -> AudioDeviceStatus -> Ordering
AudioDeviceStatus -> AudioDeviceStatus -> AudioDeviceStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AudioDeviceStatus -> AudioDeviceStatus -> AudioDeviceStatus
$cmin :: AudioDeviceStatus -> AudioDeviceStatus -> AudioDeviceStatus
max :: AudioDeviceStatus -> AudioDeviceStatus -> AudioDeviceStatus
$cmax :: AudioDeviceStatus -> AudioDeviceStatus -> AudioDeviceStatus
>= :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
$c>= :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
> :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
$c> :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
<= :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
$c<= :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
< :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
$c< :: AudioDeviceStatus -> AudioDeviceStatus -> Bool
compare :: AudioDeviceStatus -> AudioDeviceStatus -> Ordering
$ccompare :: AudioDeviceStatus -> AudioDeviceStatus -> Ordering
Ord, ReadPrec [AudioDeviceStatus]
ReadPrec AudioDeviceStatus
Int -> ReadS AudioDeviceStatus
ReadS [AudioDeviceStatus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AudioDeviceStatus]
$creadListPrec :: ReadPrec [AudioDeviceStatus]
readPrec :: ReadPrec AudioDeviceStatus
$creadPrec :: ReadPrec AudioDeviceStatus
readList :: ReadS [AudioDeviceStatus]
$creadList :: ReadS [AudioDeviceStatus]
readsPrec :: Int -> ReadS AudioDeviceStatus
$creadsPrec :: Int -> ReadS AudioDeviceStatus
Read, Typeable AudioDeviceStatus
AudioDeviceStatus -> DataType
AudioDeviceStatus -> Constr
(forall b. Data b => b -> b)
-> AudioDeviceStatus -> AudioDeviceStatus
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> AudioDeviceStatus -> u
forall u. (forall d. Data d => d -> u) -> AudioDeviceStatus -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceStatus -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceStatus -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> AudioDeviceStatus -> m AudioDeviceStatus
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AudioDeviceStatus -> m AudioDeviceStatus
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AudioDeviceStatus
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AudioDeviceStatus -> c AudioDeviceStatus
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AudioDeviceStatus)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AudioDeviceStatus)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AudioDeviceStatus -> m AudioDeviceStatus
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AudioDeviceStatus -> m AudioDeviceStatus
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AudioDeviceStatus -> m AudioDeviceStatus
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AudioDeviceStatus -> m AudioDeviceStatus
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> AudioDeviceStatus -> m AudioDeviceStatus
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> AudioDeviceStatus -> m AudioDeviceStatus
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AudioDeviceStatus -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AudioDeviceStatus -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> AudioDeviceStatus -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> AudioDeviceStatus -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceStatus -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceStatus -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceStatus -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AudioDeviceStatus -> r
gmapT :: (forall b. Data b => b -> b)
-> AudioDeviceStatus -> AudioDeviceStatus
$cgmapT :: (forall b. Data b => b -> b)
-> AudioDeviceStatus -> AudioDeviceStatus
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AudioDeviceStatus)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AudioDeviceStatus)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AudioDeviceStatus)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AudioDeviceStatus)
dataTypeOf :: AudioDeviceStatus -> DataType
$cdataTypeOf :: AudioDeviceStatus -> DataType
toConstr :: AudioDeviceStatus -> Constr
$ctoConstr :: AudioDeviceStatus -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AudioDeviceStatus
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AudioDeviceStatus
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AudioDeviceStatus -> c AudioDeviceStatus
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AudioDeviceStatus -> c AudioDeviceStatus
Data, forall x. Rep AudioDeviceStatus x -> AudioDeviceStatus
forall x. AudioDeviceStatus -> Rep AudioDeviceStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AudioDeviceStatus x -> AudioDeviceStatus
$cfrom :: forall x. AudioDeviceStatus -> Rep AudioDeviceStatus x
Generic, Int -> AudioDeviceStatus -> ShowS
[AudioDeviceStatus] -> ShowS
AudioDeviceStatus -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [AudioDeviceStatus] -> ShowS
$cshowList :: [AudioDeviceStatus] -> ShowS
show :: AudioDeviceStatus -> [Char]
$cshow :: AudioDeviceStatus -> [Char]
showsPrec :: Int -> AudioDeviceStatus -> ShowS
$cshowsPrec :: Int -> AudioDeviceStatus -> ShowS
Show, Typeable)
audioDeviceStatus :: MonadIO m => AudioDevice -> m AudioDeviceStatus
audioDeviceStatus :: forall (m :: Type -> Type).
MonadIO m =>
AudioDevice -> m AudioDeviceStatus
audioDeviceStatus (AudioDevice Word32
d) = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b. Show a => Text -> Text -> (a -> Maybe b) -> a -> b
fromC Text
"SDL.Audio.audioDeviceStatus" Text
"SDL_AudioStatus" Word32 -> Maybe AudioDeviceStatus
readStatus forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: Type -> Type). MonadIO m => Word32 -> m Word32
Raw.getAudioDeviceStatus Word32
d
where
readStatus :: Word32 -> Maybe AudioDeviceStatus
readStatus Word32
n = case Word32
n of
Word32
Raw.SDL_AUDIO_PLAYING -> forall a. a -> Maybe a
Just AudioDeviceStatus
Playing
Word32
Raw.SDL_AUDIO_STOPPED -> forall a. a -> Maybe a
Just AudioDeviceStatus
Stopped
Word32
Raw.SDL_AUDIO_PAUSED -> forall a. a -> Maybe a
Just AudioDeviceStatus
Paused
Word32
_ -> forall a. Maybe a
Nothing
newtype AudioDriver = AudioDriver Text
deriving (AudioDriver -> AudioDriver -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AudioDriver -> AudioDriver -> Bool
$c/= :: AudioDriver -> AudioDriver -> Bool
== :: AudioDriver -> AudioDriver -> Bool
$c== :: AudioDriver -> AudioDriver -> Bool
Eq, Int -> AudioDriver -> ShowS
[AudioDriver] -> ShowS
AudioDriver -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [AudioDriver] -> ShowS
$cshowList :: [AudioDriver] -> ShowS
show :: AudioDriver -> [Char]
$cshow :: AudioDriver -> [Char]
showsPrec :: Int -> AudioDriver -> ShowS
$cshowsPrec :: Int -> AudioDriver -> ShowS
Show, Typeable)
audioDriverName :: AudioDriver -> Text
audioDriverName :: AudioDriver -> Text
audioDriverName (AudioDriver Text
t) = Text
t
getAudioDrivers :: MonadIO m => m (V.Vector AudioDriver)
getAudioDrivers :: forall (m :: Type -> Type). MonadIO m => m (Vector AudioDriver)
getAudioDrivers = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
CInt
n <- forall (m :: Type -> Type). MonadIO m => m CInt
Raw.getNumAudioDrivers
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. [a] -> Vector a
V.fromList forall a b. (a -> b) -> a -> b
$
forall (t :: Type -> Type) (f :: Type -> Type) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [CInt
0 .. (CInt
n forall a. Num a => a -> a -> a
- CInt
1)] forall a b. (a -> b) -> a -> b
$ \CInt
i -> do
Ptr CChar
cstr <- forall (m :: Type -> Type). MonadIO m => CInt -> m (Ptr CChar)
Raw.getAudioDriver CInt
i
Text -> AudioDriver
AudioDriver forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Text.decodeUtf8 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CChar -> IO ByteString
BS.packCString Ptr CChar
cstr
audioInit :: MonadIO m => AudioDriver -> m ()
audioInit :: forall (m :: Type -> Type). MonadIO m => AudioDriver -> m ()
audioInit (AudioDriver Text
n) = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
BS.useAsCString (Text -> ByteString
Text.encodeUtf8 Text
n) forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m ()
throwIfNeg_ Text
"SDL.Audio.audioInit" Text
"SDL_AudioInit" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: Type -> Type). MonadIO m => Ptr CChar -> m CInt
Raw.audioInit
currentAudioDriver :: MonadIO m => m (Maybe Text)
currentAudioDriver :: forall (m :: Type -> Type). MonadIO m => m (Maybe Text)
currentAudioDriver =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
Text.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr CChar -> IO ByteString
BS.packCString) forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: Type -> Type). MonadIO m => m (Ptr CChar)
Raw.getCurrentAudioDriver