RtMidi-0.7.0.0: Haskell wrapper for RtMidi, the lightweight, cross-platform MIDI I/O library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.RtMidi

Description

Interface to RtMidi

Synopsis

Documentation

data InputDevice Source #

A handle to a device to be used for input

Instances

Instances details
IsDevice InputDevice Source # 
Instance details

Defined in Sound.RtMidi

Show InputDevice Source # 
Instance details

Defined in Sound.RtMidi

Eq InputDevice Source # 
Instance details

Defined in Sound.RtMidi

data OutputDevice Source #

A handle to a device to be used for input

Instances

Instances details
IsDevice OutputDevice Source # 
Instance details

Defined in Sound.RtMidi

Show OutputDevice Source # 
Instance details

Defined in Sound.RtMidi

Eq OutputDevice Source # 
Instance details

Defined in Sound.RtMidi

class IsDevice d where Source #

Generalizes InputDevice and OutputDevice for use in common functions

Minimal complete definition

toDevice, getDeviceType

Instances

Instances details
IsDevice InputDevice Source # 
Instance details

Defined in Sound.RtMidi

IsDevice OutputDevice Source # 
Instance details

Defined in Sound.RtMidi

data DeviceType Source #

Allows us to discriminate in/out functions in generic contexts

Instances

Instances details
Bounded DeviceType Source # 
Instance details

Defined in Sound.RtMidi

Enum DeviceType Source # 
Instance details

Defined in Sound.RtMidi

Generic DeviceType Source # 
Instance details

Defined in Sound.RtMidi

Associated Types

type Rep DeviceType :: Type -> Type #

Show DeviceType Source # 
Instance details

Defined in Sound.RtMidi

NFData DeviceType Source # 
Instance details

Defined in Sound.RtMidi

Methods

rnf :: DeviceType -> () #

Eq DeviceType Source # 
Instance details

Defined in Sound.RtMidi

Ord DeviceType Source # 
Instance details

Defined in Sound.RtMidi

type Rep DeviceType Source # 
Instance details

Defined in Sound.RtMidi

type Rep DeviceType = D1 ('MetaData "DeviceType" "Sound.RtMidi" "RtMidi-0.7.0.0-1VlS6aMo6PA8QAyCx7TdNZ" 'False) (C1 ('MetaCons "InputDeviceType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OutputDeviceType" 'PrefixI 'False) (U1 :: Type -> Type))

data Api Source #

Enum of RtMidi-supported APIs

Instances

Instances details
Bounded Api Source # 
Instance details

Defined in Sound.RtMidi.Foreign

Methods

minBound :: Api #

maxBound :: Api #

Enum Api Source # 
Instance details

Defined in Sound.RtMidi.Foreign

Methods

succ :: Api -> Api #

pred :: Api -> Api #

toEnum :: Int -> Api #

fromEnum :: Api -> Int #

enumFrom :: Api -> [Api] #

enumFromThen :: Api -> Api -> [Api] #

enumFromTo :: Api -> Api -> [Api] #

enumFromThenTo :: Api -> Api -> Api -> [Api] #

Generic Api Source # 
Instance details

Defined in Sound.RtMidi.Foreign

Associated Types

type Rep Api :: Type -> Type #

Methods

from :: Api -> Rep Api x #

to :: Rep Api x -> Api #

Show Api Source # 
Instance details

Defined in Sound.RtMidi.Foreign

Methods

showsPrec :: Int -> Api -> ShowS #

show :: Api -> String #

showList :: [Api] -> ShowS #

NFData Api Source # 
Instance details

Defined in Sound.RtMidi.Foreign

Methods

rnf :: Api -> () #

Eq Api Source # 
Instance details

Defined in Sound.RtMidi.Foreign

Methods

(==) :: Api -> Api -> Bool #

(/=) :: Api -> Api -> Bool #

Ord Api Source # 
Instance details

Defined in Sound.RtMidi.Foreign

Methods

compare :: Api -> Api -> Ordering #

(<) :: Api -> Api -> Bool #

(<=) :: Api -> Api -> Bool #

(>) :: Api -> Api -> Bool #

(>=) :: Api -> Api -> Bool #

max :: Api -> Api -> Api #

min :: Api -> Api -> Api #

type Rep Api Source # 
Instance details

Defined in Sound.RtMidi.Foreign

type Rep Api = D1 ('MetaData "Api" "Sound.RtMidi.Foreign" "RtMidi-0.7.0.0-1VlS6aMo6PA8QAyCx7TdNZ" '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))))

newtype Error Source #

An internal RtMidi error

Constructors

Error 

Fields

Instances

Instances details
Exception Error Source # 
Instance details

Defined in Sound.RtMidi

Generic Error Source # 
Instance details

Defined in Sound.RtMidi

Associated Types

type Rep Error :: Type -> Type #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

Show Error Source # 
Instance details

Defined in Sound.RtMidi

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

NFData Error Source # 
Instance details

Defined in Sound.RtMidi

Methods

rnf :: Error -> () #

Eq Error Source # 
Instance details

Defined in Sound.RtMidi

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

type Rep Error Source # 
Instance details

Defined in Sound.RtMidi

type Rep Error = D1 ('MetaData "Error" "Sound.RtMidi" "RtMidi-0.7.0.0-1VlS6aMo6PA8QAyCx7TdNZ" 'True) (C1 ('MetaCons "Error" 'PrefixI 'True) (S1 ('MetaSel ('Just "unError") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

apiName :: Api -> IO String Source #

Get the internal name for the given Api.

apiDisplayName :: Api -> IO String Source #

Get the display name for the given Api.

compiledApiByName :: String -> IO Api Source #

Lookup a compiled Api by name.

ready :: IsDevice d => d -> IO Bool Source #

Check if a device is ok

compiledApis :: IO [Api] Source #

A static function to determine MIDI Apis built in.

openPort Source #

Arguments

:: IsDevice d 
=> d 
-> Int

port number

-> String

name for the application port that is used

-> IO () 

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).

closePort :: IsDevice d => d -> IO () Source #

Close an open MIDI connection (if one exists).

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.

createInput Source #

Arguments

:: Api

API to use

-> String

client name

-> Int

size of the MIDI input queue

-> IO InputDevice 

Create a new Device to use for input.

setCallback Source #

Arguments

:: 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.

setForeignCallback Source #

Arguments

:: 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.

ignoreTypes Source #

Arguments

:: 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.

createOutput Source #

Arguments

:: 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.

currentApi :: IsDevice d => d -> IO Api Source #

Returns the specifier for the MIDI Api in use