Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Interface to RtMidi
Synopsis
- data InputDevice
- data OutputDevice
- class IsDevice d where
- getDeviceType :: d -> DeviceType
- data DeviceType
- data Api
- newtype Error = Error {}
- apiName :: Api -> IO String
- apiDisplayName :: Api -> IO String
- compiledApiByName :: String -> IO Api
- ready :: IsDevice d => d -> IO Bool
- compiledApis :: IO [Api]
- openPort :: IsDevice d => d -> Int -> String -> IO ()
- openVirtualPort :: IsDevice d => d -> String -> IO ()
- closePort :: IsDevice d => d -> IO ()
- portCount :: IsDevice d => d -> IO Int
- portName :: IsDevice d => d -> Int -> IO (Maybe String)
- listPorts :: IsDevice d => d -> IO [(Int, String)]
- findPort :: IsDevice d => d -> (String -> Bool) -> IO (Maybe Int)
- defaultInput :: IO InputDevice
- createInput :: Api -> String -> Int -> IO InputDevice
- setCallback :: InputDevice -> (Double -> Vector Word8 -> IO ()) -> IO ()
- setUnsafeCallback :: InputDevice -> (Double -> Ptr Word8 -> Int -> IO ()) -> IO ()
- setForeignCallback :: InputDevice -> FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()) -> Ptr () -> IO ()
- cancelCallback :: InputDevice -> IO ()
- ignoreTypes :: InputDevice -> Bool -> Bool -> Bool -> IO ()
- getMessage :: InputDevice -> IO (Double, Vector Word8)
- getMessageSized :: InputDevice -> Int -> IO (Double, Vector Word8)
- getMessageMutable :: InputDevice -> IOVector Word8 -> IO (Double, Int)
- defaultOutput :: IO OutputDevice
- createOutput :: Api -> String -> IO OutputDevice
- sendMessage :: OutputDevice -> Vector Word8 -> IO ()
- sendUnsafeMessage :: OutputDevice -> Ptr Word8 -> Int -> IO ()
- currentApi :: IsDevice d => d -> IO Api
Documentation
data InputDevice Source #
A handle to a device to be used for input
Instances
IsDevice InputDevice Source # | |
Defined in Sound.RtMidi toDevice :: InputDevice -> Device | |
Show InputDevice Source # | |
Defined in Sound.RtMidi showsPrec :: Int -> InputDevice -> ShowS # show :: InputDevice -> String # showList :: [InputDevice] -> ShowS # | |
Eq InputDevice Source # | |
Defined in Sound.RtMidi (==) :: InputDevice -> InputDevice -> Bool # (/=) :: InputDevice -> InputDevice -> Bool # |
data OutputDevice Source #
A handle to a device to be used for input
Instances
IsDevice OutputDevice Source # | |
Defined in Sound.RtMidi toDevice :: OutputDevice -> Device | |
Show OutputDevice Source # | |
Defined in Sound.RtMidi showsPrec :: Int -> OutputDevice -> ShowS # show :: OutputDevice -> String # showList :: [OutputDevice] -> ShowS # | |
Eq OutputDevice Source # | |
Defined in Sound.RtMidi (==) :: OutputDevice -> OutputDevice -> Bool # (/=) :: OutputDevice -> OutputDevice -> Bool # |
class IsDevice d where Source #
Generalizes InputDevice
and OutputDevice
for use in common functions
toDevice, getDeviceType
getDeviceType :: d -> DeviceType Source #
Instances
IsDevice InputDevice Source # | |
Defined in Sound.RtMidi toDevice :: InputDevice -> Device | |
IsDevice OutputDevice Source # | |
Defined in Sound.RtMidi toDevice :: OutputDevice -> Device |
data DeviceType Source #
Allows us to discriminate in/out functions in generic contexts
Instances
Enum of RtMidi-supported APIs
Instances
Bounded Api Source # | |
Enum Api Source # | |
Generic Api Source # | |
Show Api Source # | |
NFData Api Source # | |
Defined in Sound.RtMidi.Foreign | |
Eq Api Source # | |
Ord Api Source # | |
type Rep Api Source # | |
Defined in Sound.RtMidi.Foreign type Rep Api = D1 ('MetaData "Api" "Sound.RtMidi.Foreign" "RtMidi-0.8.0.0-FDDwGzNsMQHA5gKeRo3gjA" 'False) ((C1 ('MetaCons "UnspecifiedApi" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CoreMidiApi" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlsaApi" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "JackApi" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MultimediaApi" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DummyApi" 'PrefixI 'False) (U1 :: Type -> Type)))) |
An internal RtMidi error
Instances
Exception Error Source # | |
Defined in Sound.RtMidi toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # | |
Generic Error Source # | |
Show Error Source # | |
NFData Error Source # | |
Defined in Sound.RtMidi | |
Eq Error Source # | |
type Rep Error Source # | |
Defined in Sound.RtMidi |
Open a MIDI connection
openVirtualPort :: IsDevice d => d -> String -> IO () Source #
This function creates a virtual MIDI output port to which other software applications can connect.
This type of functionality is currently only supported by the Macintosh OS X, Linux ALSA and JACK APIs (the function does nothing with the other APIs).
portCount :: IsDevice d => d -> IO Int Source #
Return the number of MIDI ports available to the Device
.
portName :: IsDevice d => d -> Int -> IO (Maybe String) Source #
Return a string identifier for the specified MIDI port number.
Nothing
is returned if an invalid port specifier is provided.
listPorts :: IsDevice d => d -> IO [(Int, String)] Source #
Convenience function to list ports.
Note that the underlying library does not offer an "atomic" interface for this so results may be inconsistent if you connect/disconnect ports during this call.
findPort :: IsDevice d => d -> (String -> Bool) -> IO (Maybe Int) Source #
Convenience function to lookup the first port satisfying the predicate.
You may want to find an exact name:
findPort d (== name)
Or you may want to match part of a name:
findPort d (isInfixOf name)
Note that if you are performing many lookups, it's better to use listPorts
and
do the lookups yourself (see the caveats there too).
defaultInput :: IO InputDevice Source #
Default constructor for a Device
to use for input.
:: Api | API to use |
-> String | client name |
-> Int | size of the MIDI input queue |
-> IO InputDevice |
Create a new Device
to use for input.
:: InputDevice | |
-> (Double -> Vector Word8 -> IO ()) | Function that takes a timestamp and a MIDI message as arguments |
-> IO () |
Set a callback function to be invoked for incoming MIDI messages.
The callback function will be called whenever an incoming MIDI message is received. While not absolutely necessary, it is best to set the callback function before opening a MIDI port to avoid leaving some messages in the queue.
setUnsafeCallback :: InputDevice -> (Double -> Ptr Word8 -> Int -> IO ()) -> IO () Source #
A variant of setCallback
that takes a raw pointer and length. It is unsafe to share or reference the pointer beyond the
scope of the callback, as the RtMidi-owned memory it references may have been changed or freed.
:: InputDevice | |
-> FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()) | |
-> Ptr () | Pointer to context that will be passed into the callback |
-> IO () |
Set a foreign callback function to be invoked for incoming MIDI messages.
This variant allows you to set the callback to a C function pointer so we're not forced to enter a Haskell wrapper every invocation.
cancelCallback :: InputDevice -> IO () Source #
Cancel use of the current callback function (if one exists).
Subsequent incoming MIDI messages will be written to the queue and can be retrieved with the getMessage
function.
:: InputDevice | |
-> Bool | SysEx messages |
-> Bool | Time messages |
-> Bool | Sense messages |
-> IO () |
Specify whether certain MIDI message types should be queued or ignored during input.
By default, MIDI timing and active sensing messages are ignored during message input because of their
relative high data rates. MIDI sysex messages are ignored by default as well.
Variable values of True
imply that the respective message type will be ignored.
getMessage :: InputDevice -> IO (Double, Vector Word8) Source #
Return data bytes for the next available MIDI message in the input queue and the event delta-time in seconds.
This function returns immediately whether a new message is available or not.
A valid message is indicated by whether the list contains any elements.
Note that large sysex messages will be silently dropped! Use getMessageSized
or use a callback to get these safely.
getMessageSized :: InputDevice -> Int -> IO (Double, Vector Word8) Source #
Variant of getMessage
that allows you to set message buffer size (typically for large sysex messages).
getMessageMutable :: InputDevice -> IOVector Word8 -> IO (Double, Int) Source #
Variant of getMessage
that allows you to fill a shared buffer, returning timestamp and size.
defaultOutput :: IO OutputDevice Source #
Default constructor for a Device
to use for output.
:: Api | API to use |
-> String | client name |
-> IO OutputDevice |
Create a new Device
to use for output.
sendMessage :: OutputDevice -> Vector Word8 -> IO () Source #
Immediately send a single message out an open MIDI output port.
sendUnsafeMessage :: OutputDevice -> Ptr Word8 -> Int -> IO () Source #
A variant of sendMessage
that allows reading directly from pinned memory.