portaudio-0.0.1: Haskell bindings for the PortAudio library.Source codeContentsIndex
Sound.PortAudio
Description
PortAudio is a cross platform audio library which supports many different operatings systems.
Synopsis
data ErrorCode
= NoError
| 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
data HostApiTypeId
= InDevelopment
| DirectSound
| MME
| ASIO
| SoundManager
| CoreAudio
| OSS
| ALSA
| AL
| BeOS
| WDMKS
| JACK
| WASAPI
| AudioScienceHPI
data SampleFormat
= PaFloat32
| PaInt32
| PaInt24
| PaInt16
| PaInt8
| PaUInt8
| PaCustomFormat
| PaNonInterleaved
data HostApiInfo = HostApiInfo {
hostApiInfoStructVersion :: Int
hostApiInfoApiType :: HostApiTypeId
hostApiInfoName :: String
hostApiInfoDeviceCount :: Int
hostApiInfoDefaultInputDevice :: DeviceIndex
hostApiInfoDefaultOutputDevice :: DeviceIndex
}
data HostErrorInfo = HostErrorInfo {
hostErrorInfoHostApiType :: HostApiTypeId
hostErrorInfoErrorCode :: Int
hostErrorInfoErrorText :: String
}
data DeviceInfo = DeviceInfo {
deviceInfoStructVersion :: Int
deviceInfoName :: String
deviceInfoHostApi :: HostApiIndex
deviceInfoMaxInputChannels :: Int
deviceInfoMaxOutputChannels :: Int
deviceInfoDefaultLowInputLatency :: PaTime
deviceInfoDefaultLowOutputLatency :: PaTime
deviceInfoDefaultHighInputLatency :: PaTime
deviceInfoDefaultHighOutputLatency :: PaTime
deviceInfoDefaultSampleRate :: Double
}
data StreamParameters = StreamParameters {
streamParametersDevice :: DeviceIndex
streamParametersChannelCount :: Int
streamParametersSampleFormat :: SampleFormat
streamParametersSuggestedLatency :: PaTime
streamParametersHostApiSpecificStreamInfo :: Ptr ()
}
data StreamInfo = StreamInfo {
streamInfoStructVersion :: Int
streamInfoInputLatency :: PaTime
streamInfoOutputLatency :: PaTime
streamInfoSampleRate :: Double
}
type PaFloat32 = Float
paFloat32 :: PaFloat32
type PaInt32 = Int32
paInt32 :: PaInt32
type PaInt16 = Int16
paInt16 :: PaInt16
type PaInt8 = Int8
paInt8 :: PaInt8
type PaUInt8 = Word8
paUInt8 :: PaUInt8
type PaTime = Double
data PaStream a
paNullPtr
type HostApiIndex = Int
type DeviceIndex = Int
paNoDevice :: DeviceIndex
paUseHostApiSpecificDeviceSpecification :: DeviceIndex
getVersion :: Int
getVersionText :: IO String
withPortAudio :: IO a -> IO (Either String a)
initialize :: IO (Either String ErrorCode)
terminate :: IO (Either String ErrorCode)
withStream :: (PaStream a -> IO a) -> PaStream a -> IO (Either String a)
withDefaultStream :: PortAudioFormat a => Int -> Int -> a -> Double -> Int -> (PaStream a -> (Int, Int, Double, Int) -> IO b) -> IO (Either String b)
openDefaultStream :: PortAudioFormat a => Int -> Int -> a -> Double -> Int -> IO (Either String (PaStream a))
openStream :: Maybe StreamParameters -> Maybe StreamParameters -> Double -> Int -> IO (Either String (PaStream a))
closeStream :: PaStream a -> IO (Either String ErrorCode)
startStream :: PaStream a -> IO (Either String ErrorCode)
stopStream :: PaStream a -> IO (Either String ErrorCode)
abortStream :: PaStream a -> IO (Either String ErrorCode)
readStream :: Storable a => PaStream a -> Int -> Int -> IO (Either String [[a]])
writeStream :: Storable a => PaStream a -> [[a]] -> Int -> IO (Either String ErrorCode)
getStreamInfo :: PaStream a -> IO (Maybe StreamInfo)
getStreamTime :: PaStream a -> IO (Maybe PaTime)
getStreamCpuLoad :: PaStream a -> IO Double
getStreamReadAvailable :: PaStream a -> IO (Either String Int)
getStreamWriteAvailable :: PaStream a -> IO (Either String Int)
getHostApiCount :: IO (Either String Int)
getDefaultHostApi :: IO (Either String Int)
getHostApiInfo :: HostApiIndex -> IO (Maybe HostApiInfo)
getDeviceCount :: IO (Either ErrorCode DeviceIndex)
getDefaultInputDevice :: IO (Maybe DeviceIndex)
getDefaultOutputDevice :: IO (Maybe DeviceIndex)
getDeviceInfo :: DeviceIndex -> IO (Maybe DeviceInfo)
getSampleSize :: SampleFormat -> IO (Either String Int)
hostApiTypeIdToHostApiIndex :: HostApiTypeId -> IO HostApiIndex
hostApiDeviceIndexToDeviceIndex :: HostApiIndex -> Int -> IO DeviceIndex
isFormatSupported :: Maybe StreamParameters -> Maybe StreamParameters -> Double -> IO (Either String Int)
isStreamStopped :: PaStream a -> IO (Either String Bool)
isStreamActive :: PaStream a -> IO (Either String Bool)
paSleep :: Int -> IO ()
chunk :: Int -> [a] -> [[a]]
standardSampleRates :: [Double]
Documentation
data ErrorCode Source
Constructors
NoError
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
show/hide Instances
data HostApiTypeId Source
Unchanging uniqe identifiers for each supported host API. The values are guaranteed to be unique and will never change. This allows code to be written which conditionally uses host API specific extensions.
Constructors
InDevelopment
DirectSound
MME
ASIO
SoundManager
CoreAudio
OSS
ALSA
AL
BeOS
WDMKS
JACK
WASAPI
AudioScienceHPI
show/hide Instances
data SampleFormat Source

A type used to specify one or more sample formats.

  • The floating point representation (PaFloat32) uses +1.0 and -1.0 as the maximum and minimum.
  • (PaUInt8) considers 128 ground.
  • The (PaNonInterleaved) flag indicates that a multichannel buffer is passed as a set of non-interleaved pointers. (WHAT?) I don't think i want to support this.
Constructors
PaFloat32
PaInt32
PaInt24
PaInt16
PaInt8
PaUInt8
PaCustomFormat
PaNonInterleaved
show/hide Instances
data HostApiInfo Source
A structure containing information about a particular host API.
Constructors
HostApiInfo
hostApiInfoStructVersion :: Int
hostApiInfoApiType :: HostApiTypeId
hostApiInfoName :: String
hostApiInfoDeviceCount :: Int
hostApiInfoDefaultInputDevice :: DeviceIndex
hostApiInfoDefaultOutputDevice :: DeviceIndex
show/hide Instances
data HostErrorInfo Source
Structure used to return information about a host error condition.
Constructors
HostErrorInfo
hostErrorInfoHostApiType :: HostApiTypeId
hostErrorInfoErrorCode :: Int
hostErrorInfoErrorText :: String
show/hide Instances
data DeviceInfo Source
A structure providing information and capabilities of PortAudio devices. Devices may support input, output or both.
Constructors
DeviceInfo
deviceInfoStructVersion :: Int
deviceInfoName :: String
deviceInfoHostApi :: HostApiIndex
deviceInfoMaxInputChannels :: Int
deviceInfoMaxOutputChannels :: Int
deviceInfoDefaultLowInputLatency :: PaTime
deviceInfoDefaultLowOutputLatency :: PaTime
deviceInfoDefaultHighInputLatency :: PaTime
deviceInfoDefaultHighOutputLatency :: PaTime
deviceInfoDefaultSampleRate :: Double
show/hide Instances
data StreamParameters Source
Parameters for one direction (input or output) of a stream.
Constructors
StreamParameters
streamParametersDevice :: DeviceIndex
streamParametersChannelCount :: Int
streamParametersSampleFormat :: SampleFormat
streamParametersSuggestedLatency :: PaTime
streamParametersHostApiSpecificStreamInfo :: Ptr ()
show/hide Instances
data StreamInfo Source
A structure containing unchanging information about an open stream.
Constructors
StreamInfo
streamInfoStructVersion :: Int
streamInfoInputLatency :: PaTime
streamInfoOutputLatency :: PaTime
streamInfoSampleRate :: Double
show/hide Instances
type PaFloat32 = FloatSource
32 bit floating point representation.
paFloat32 :: PaFloat32Source
This is a format specifier to be used with functions like openDefaultStream. It specifies a 32 bit floating point representation.
type PaInt32 = Int32Source
32 bit integer representation.
paInt32 :: PaInt32Source
This is a format specifier to be used with functions like openDefaultStream. It specifies a 32 bit integer representation.
type PaInt16 = Int16Source
16 bit integer representation
paInt16 :: PaInt16Source
This is a format specifier to be used with functions like openDefaultStream. It specifies a 16 bit integer representation.
type PaInt8 = Int8Source
8 bit integer representation
paInt8 :: PaInt8Source
This is a format specifier to be used with functions like openDefaultStream. It specifies a 8 bit integer representation.
type PaUInt8 = Word8Source
8 bit unsigned integer representation
paUInt8 :: PaUInt8Source
This is a format specifier to be used with functions like openDefaultStream. It specifies a 8 bit unsigned integer representation.
type PaTime = DoubleSource
Type to represent the monotonic time in seconds which can be used for synchronisation.
data PaStream a Source
A PaStream can provide multiple channels of real-time streaming audio input and output to a client application. type PaStream = IntPtr
show/hide Instances
paNullPtr
type HostApiIndex = IntSource
Used to enumerate host APIs at runtime. The values of this range from 0 to (getHostApiCount - 1)
type DeviceIndex = IntSource
The index of a PortAudio device.
paNoDevice :: DeviceIndexSource
A special DeviceIndex value indicating that no device is available or should be used.
paUseHostApiSpecificDeviceSpecification :: DeviceIndexSource
A special DeviceIndex value indicating that the device(s) to be used are specified in the host api specific stream info structure.
getVersion :: IntSource
Retrieve the release number of the current PortAudio build.
getVersionText :: IO StringSource
Retrieve the textual version of the current PortAudio build.
withPortAudio :: IO a -> IO (Either String a)Source

Perform a port audio action in the context of the PortAudio library.

This initializes the library, performs the supplied actions, and then terminates the library. This is the reccomended way to use the library. withPortAudio :: IO a -> IO (Maybe a) -- ^ Returns (Just a) on success or Nothing on failure.

initializeSource
:: IO (Either String ErrorCode)(Right NoError) on success. (Left err) on failure.
Library initialization function. Call this before using PortAudio. The functions getVersion, getVersionText, and getErrorText may be called before initialize is called.
terminateSource
:: IO (Either String ErrorCode)(Right NoError) on success. (Left err) on failure.)
Library termination function. Call this after PortAudio is no longer needed.
withStream :: (PaStream a -> IO a) -> PaStream a -> IO (Either String a)Source
Perform an action with a stream.
withDefaultStream :: PortAudioFormat a => Int -> Int -> a -> Double -> Int -> (PaStream a -> (Int, Int, Double, Int) -> IO b) -> IO (Either String b)Source
openDefaultStreamSource
:: PortAudioFormat a
=> IntNumber of input channels
-> IntNumber of output channels
-> aSample Format. Should only use one of: paUInt8, paInt8, paInt16, paInt32, or paFloat32.
-> DoubleSample Rate
-> IntFrames Per Buffer
-> IO (Either String (PaStream a))(Right PaStream) on success, (Left err) on failure.
A Simplified version of openStream which opens the default input and/or output device(s).
openStreamSource
::
=> Maybe StreamParametersInput Parameters
-> Maybe StreamParametersOutput Parameters
-> DoubleSample Rate
-> IntFrames Per Buffer
-> IO (Either String (PaStream a))(Right PaStream) on success, (Left err) on failure.
Open a stream for input, output, or both.
closeStream :: PaStream a -> IO (Either String ErrorCode)Source
Close a PortAudio stream. If the audio streem is active, any pending buffers are discarded as if abortStream had been called.
startStream :: PaStream a -> IO (Either String ErrorCode)Source
Commences audio processing.
stopStream :: PaStream a -> IO (Either String ErrorCode)Source
Terminates audio processing. It blocks until all pending audio buffers have been played.
abortStream :: PaStream a -> IO (Either String ErrorCode)Source
Terminates audio processing immediately without waiting for pending buffers to complete.
readStreamSource
:: Storable a
=> PaStream aThe input stream
-> IntThe number of channels
-> IntThe number of frames
-> IO (Either String [[a]])
Read a sample from an input stream.
writeStreamSource
:: Storable a
=> PaStream aThe output stream
-> [[a]]The samples to be played
-> IntNumber of frames
-> IO (Either String ErrorCode)The return status of the write
getStreamInfo :: PaStream a -> IO (Maybe StreamInfo)Source
Retrieve a StreamInfo containing information about the specified stream.
getStreamTime :: PaStream a -> IO (Maybe PaTime)Source
Determine the current time for the stream according to the sample clock used to generate the buffer timestamps.
getStreamCpuLoad :: PaStream a -> IO DoubleSource

Retrieve CPU usage information (value between 0.0 and 1.0) for the specified stream.

Note: A usage level of 0.0 is potentially an error (no specific error condition is defined by PortAudio).

getStreamReadAvailable :: PaStream a -> IO (Either String Int)Source
Get the number of frames that can be read from the stream without blocking.
getStreamWriteAvailable :: PaStream a -> IO (Either String Int)Source
Get the number of frames which can be written to the stream without blocking.
getHostApiCountSource
:: IO (Either String Int)(Left err) on failure, (Right int) on success.
Retrieve the number of available host APIs. Even if a host API is available it may have no devices available.
getDefaultHostApi :: IO (Either String Int)Source
Returns the index of the default host API.
getHostApiInfo :: HostApiIndex -> IO (Maybe HostApiInfo)Source
Gets a structure containing information about a specific host API. FINISH
getDeviceCount :: IO (Either ErrorCode DeviceIndex)Source
Retrieve the number of available devices or Nothing if there are none.
getDefaultInputDevice :: IO (Maybe DeviceIndex)Source
Retrieve the index of the default input device or Nothing if there are none.
getDefaultOutputDevice :: IO (Maybe DeviceIndex)Source
Retrieve the index of the default output device or Nothing if there are none.
getDeviceInfo :: DeviceIndex -> IO (Maybe DeviceInfo)Source
Retrieve a DeviceInfo structure containing information about the specified device.
getSampleSize :: SampleFormat -> IO (Either String Int)Source
Retrieve the size of a given sample format in bytes.
hostApiTypeIdToHostApiIndex :: HostApiTypeId -> IO HostApiIndexSource
Convert a static host API uniqe identifier to a runtime host API index. FINISH
hostApiDeviceIndexToDeviceIndex :: HostApiIndex -> Int -> IO DeviceIndexSource
Convert a host-API-specific device index to a standard PortAudio device index. FINISH
isFormatSupportedSource
:: Maybe StreamParametersInput Parameters
-> Maybe StreamParametersOutput Parameters
-> DoubleSample Rate
-> IO (Either String Int)(Right 0) on supported format, (Left err) otherwise.
Determines whether it is possible to open a stream with the specified parameters.
isStreamStoppedSource
::
=> PaStream a
-> IO (Either String Bool)(Right bool) on success, (Left err) on failure.
Determines whether the stream is stopped.
isStreamActiveSource
::
=> PaStream a
-> IO (Either String Bool)(Right bool) on success, (Left err) on failure.
Determines whether the stream is active.
paSleep :: Int -> IO ()Source
Put the caller to sleep for at least n milliseconds. The function may sleep longer than requested so don't rely on this for accurate musical timing.
chunk :: Int -> [a] -> [[a]]Source
Split a list into as many at most n-lengthed lists as possible. This is useful for interleaving audio channels.
standardSampleRates :: [Double]Source
Produced by Haddock version 2.4.2