Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A lowest common denominator interface to the Win32 and MacOSX MIDI bindings.
Error handling is via fail
-s in the IO monad. .
Always link with the threaded runtime! (use the -threaded GHC option)
Synopsis
- module System.MIDI.Base
- type Source = Source
- type Destination = Destination
- type Connection = Connection
- enumerateSources :: IO [Source]
- enumerateDestinations :: IO [Destination]
- class MIDIHasName c
- getName :: MIDIHasName a => a -> IO String
- getModel :: MIDIHasName a => a -> IO String
- getManufacturer :: MIDIHasName a => a -> IO String
- openSource :: Source -> Maybe ClientCallback -> IO Connection
- openDestination :: Destination -> IO Connection
- start :: Connection -> IO ()
- stop :: Connection -> IO ()
- close :: Connection -> IO ()
- send :: Connection -> MidiMessage -> IO ()
- sendSysEx :: Connection -> [Word8] -> IO ()
- getNextEvent :: Connection -> IO (Maybe MidiEvent)
- checkNextEvent :: Connection -> IO (Maybe MidiEvent)
- getEvents :: Connection -> IO [MidiEvent]
- getEventsUntil :: Connection -> TimeStamp -> IO [MidiEvent]
- currentTime :: Connection -> IO Word32
Documentation
module System.MIDI.Base
MIDI sources and destionations
type Destination = Destination Source #
The opaque data type representing a MIDI destination.
type Connection = Connection Source #
The opaque data type representing a MIDI connection.
enumerateSources :: IO [Source] Source #
Enumerates the MIDI sources present in the system.
enumerateDestinations :: IO [Destination] Source #
Enumerates the MIDI destinations present in the system.
names of MIDI devices
class MIDIHasName c Source #
getName :: MIDIHasName a => a -> IO String Source #
These functions return the name, model and manufacturer of a MIDI source / destination.
Note: On Win32, only getName
returns a somewhat meaningful string at the moment.
getManufacturer :: MIDIHasName a => a -> IO String Source #
connecting to a MIDI source or destination
openSource :: Source -> Maybe ClientCallback -> IO Connection Source #
Opens a MIDI Source. There are two possibilites to receive MIDI messages. The user can either supply a callback function, or get the messages from an asynchronous buffer. However, mixing the two approaches is not allowed.
openDestination :: Destination -> IO Connection Source #
Opens a MIDI Destination.
start :: Connection -> IO () Source #
Starts a connection. This is required for receiving MIDI messages, and also for starting the clock.
stop :: Connection -> IO () Source #
Stops a connection.
close :: Connection -> IO () Source #
Closes a MIDI Connection.
sending messages
send :: Connection -> MidiMessage -> IO () Source #
Sends a short message. The connection must be a Destination
.
sendSysEx :: Connection -> [Word8] -> IO () Source #
Sends a system exclusive message. You should not include the starting / trailing bytes 0xF0 and 0xF7.
Note: On Win32, the connection must be a Destination
manual polling of events
getNextEvent :: Connection -> IO (Maybe MidiEvent) Source #
Gets the next event from a buffered connection (see also openSource
)
checkNextEvent :: Connection -> IO (Maybe MidiEvent) Source #
Checks the next event from a buffered connection, but does not remove it from the buffer.
getEvents :: Connection -> IO [MidiEvent] Source #
Gets all the events from the buffer (see also openSource
)
getEventsUntil :: Connection -> TimeStamp -> IO [MidiEvent] Source #
Gets all the events with timestamp less than the specified from the buffer.
querying time
currentTime :: Connection -> IO Word32 Source #
Returns the time elapsed since the last start
call, in milisecs.