Safe Haskell | None |
---|---|
Language | Haskell2010 |
System.PortAudio
Synopsis
- withPortAudio :: IO a -> IO a
- data Error
- = NotInitialized
- | UnanticipatedHostError
- | InvalidChannelCount
- | InvalidSampleRate
- | InvalidDevice
- | InvalidFlag
- | SampleFormatNotSupported
- | BadIODeviceCombination
- | InsufficientMemory
- | BufferTooBig
- | BufferTooSmall
- | NullCallback
- | BadStreamPtr
- | TimedOut
- | InternalError
- | DeviceUnavailable
- | IncompatibleHostApiSpecificStreamInfo
- | StreamIsStopped
- | StreamIsNotStopped
- | InputOverflowed
- | OutputUnderflowed
- | HostApiNotFound
- | InvalidHostApi
- | CanNotReadFromACallbackStream
- | CanNotWriteToACallbackStream
- | CanNotReadFromAnOutputOnlyStream
- | CanNotWriteToAnInputOnlyStream
- | IncompatibleStreamHostApi
- | BadBufferPtr
- getDevices :: IO ([Device Input], [Device Output])
- data Device t = Device {}
- data Input
- data Output
- data Stream
- withStream :: (Storable i, Storable o) => Double -> Int -> Maybe (StreamParameters Input i) -> Maybe (StreamParameters Output o) -> StreamFlags -> (Status -> Vector i -> IOVector o -> IO StreamCallbackResult) -> (Stream -> IO r) -> IO r
- data StreamCallbackResult
- startStream :: Stream -> IO ()
- stopStream :: Stream -> IO ()
- withStartStream :: Stream -> IO r -> IO r
- isStreamStopped :: Stream -> IO Bool
- setStreamFinishedCallback :: Stream -> IO () -> IO ()
- data StreamParameters t a
- streamParameters :: forall t f a. (Applicative f, Foldable f, PortAudioSample a) => Device t -> Double -> Maybe (StreamParameters t (f a))
- class PortAudioSample a
- noConnection :: Maybe (StreamParameters t ())
- data Status = Status {
- currentTime :: !Double
- inputBufferAdcTime :: !Double
- outputBufferDacTime :: !Double
- inputUnderflow :: !Bool
- inputOverflow :: !Bool
- outputUnderflow :: !Bool
- outputOverflow :: !Bool
- primingOutput :: !Bool
- data StreamFlags
- clipOff :: StreamFlags
- ditherOff :: StreamFlags
- neverDropInput :: StreamFlags
- primeOutputBuffersUsingStreamCallback :: StreamFlags
Initialization
withPortAudio :: IO a -> IO a Source #
Constructors
Instances
Enum Error Source # | |
Defined in System.PortAudio | |
Eq Error Source # | |
Ord Error Source # | |
Show Error Source # | |
Exception Error Source # | |
Defined in System.PortAudio Methods toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # |
Devices
Constructors
Device | |
Fields |
Opening a stream
Arguments
:: (Storable i, Storable o) | |
=> Double | sampling rate |
-> Int | buffer size |
-> Maybe (StreamParameters Input i) | |
-> Maybe (StreamParameters Output o) | |
-> StreamFlags | |
-> (Status -> Vector i -> IOVector o -> IO StreamCallbackResult) | callback |
-> (Stream -> IO r) | |
-> IO r |
data StreamCallbackResult Source #
Instances
startStream :: Stream -> IO () Source #
stopStream :: Stream -> IO () Source #
Stream parameters
data StreamParameters t a Source #
Instances
Storable (StreamParameters t a) Source # | |
Defined in System.PortAudio Methods sizeOf :: StreamParameters t a -> Int # alignment :: StreamParameters t a -> Int # peekElemOff :: Ptr (StreamParameters t a) -> Int -> IO (StreamParameters t a) # pokeElemOff :: Ptr (StreamParameters t a) -> Int -> StreamParameters t a -> IO () # peekByteOff :: Ptr b -> Int -> IO (StreamParameters t a) # pokeByteOff :: Ptr b -> Int -> StreamParameters t a -> IO () # peek :: Ptr (StreamParameters t a) -> IO (StreamParameters t a) # poke :: Ptr (StreamParameters t a) -> StreamParameters t a -> IO () # |
streamParameters :: forall t f a. (Applicative f, Foldable f, PortAudioSample a) => Device t -> Double -> Maybe (StreamParameters t (f a)) Source #
class PortAudioSample a Source #
Minimal complete definition
paSampleFormat
Instances
PortAudioSample Float Source # | |
Defined in System.PortAudio Methods paSampleFormat :: proxy Float -> CULong | |
PortAudioSample Int8 Source # | |
Defined in System.PortAudio Methods paSampleFormat :: proxy Int8 -> CULong | |
PortAudioSample Int16 Source # | |
Defined in System.PortAudio Methods paSampleFormat :: proxy Int16 -> CULong | |
PortAudioSample Int32 Source # | |
Defined in System.PortAudio Methods paSampleFormat :: proxy Int32 -> CULong | |
PortAudioSample Word8 Source # | |
Defined in System.PortAudio Methods paSampleFormat :: proxy Word8 -> CULong |
noConnection :: Maybe (StreamParameters t ()) Source #
This is Nothing
, but it explicitly specifies the stream type with zero-width unit type.
Timestamps and status flags
Constructors
Status | |
Fields
|
Stream flags
data StreamFlags Source #
Instances
Semigroup StreamFlags Source # | |
Defined in System.PortAudio Methods (<>) :: StreamFlags -> StreamFlags -> StreamFlags # sconcat :: NonEmpty StreamFlags -> StreamFlags # stimes :: Integral b => b -> StreamFlags -> StreamFlags # | |
Monoid StreamFlags Source # | |
Defined in System.PortAudio Methods mempty :: StreamFlags # mappend :: StreamFlags -> StreamFlags -> StreamFlags # mconcat :: [StreamFlags] -> StreamFlags # |