Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
- Support for PortMidi
With this module, you can add cells which receive and send MIDI events.
You don't need to initialise PortMidi, or open devices,
this is all done by essence-of-live-coding
using the LiveCoding.Handle mechanism.
Synopsis
- newtype PortMidiT m a = PortMidiT {}
- data EOLCPortMidiError
- throwPortMidi :: Monad m => EOLCPortMidiError -> PortMidiT m arbitrary
- throwPortMidiC :: Monad m => Cell (PortMidiT m) EOLCPortMidiError arbitrary
- liftPMError :: Monad m => m (Either PMError a) -> PortMidiT m a
- liftHandlingState :: Monad m => Cell (HandlingStateT m) a b -> Cell (PortMidiT m) a b
- runPortMidiC :: MonadIO m => Cell (PortMidiT m) a b -> CellExcept a b (HandlingStateT m) EOLCPortMidiError
- loopPortMidiC :: MonadIO m => Cell (PortMidiT m) a b -> Cell (HandlingStateT m) a b
- runPortMidiT :: PortMidiT m a -> HandlingStateT m (Either EOLCPortMidiError a)
- newtype PortMidiInputStream = PortMidiInputStream {}
- newtype PortMidiOutputStream = PortMidiOutputStream {}
- data DeviceDirection
- lookupDeviceID :: MonadIO m => String -> DeviceDirection -> m (Either EOLCPortMidiError DeviceID)
- portMidiInputStreamHandle :: MonadIO m => String -> Handle m (Either EOLCPortMidiError PortMidiInputStream)
- readEventsFrom :: MonadIO m => Cell (PortMidiT m) PortMidiInputStream [PMEvent]
- readEventsC :: MonadIO m => String -> Cell (PortMidiT m) arbitrary [PMEvent]
- portMidiOutputStreamHandle :: MonadIO m => String -> Handle m (Either EOLCPortMidiError PortMidiOutputStream)
- writeEventsTo :: MonadIO m => Cell (PortMidiT m) (PortMidiOutputStream, [PMEvent]) ()
- writeEventsC :: MonadIO m => String -> Cell (PortMidiT m) [PMEvent] ()
- data PortMidiDevices = PortMidiDevices {
- inputDevices :: [DeviceInfo]
- outputDevices :: [DeviceInfo]
- getPortMidiDevices :: IO PortMidiDevices
- prettyPrintPortMidiDevices :: PortMidiDevices -> IO ()
The PortMidiT
monad transformer
newtype PortMidiT m a Source #
Monad transformer adding PortMidi-related effects to your monad.
This transformer adds two kinds of effects to your stack:
- PortMidi exceptions (See
EOLCPortMidiError
) - Automatic initialisation of PortMidi devices (using
HandlingStateT
)
Instances
data EOLCPortMidiError Source #
Exceptions that can occur while doing livecoding with PortMidi.
There are two kinds of exceptions:
- Internal PortMidi exceptions (see
EOLCPortMidiError
) - When a device is not correctly specified by name and input/output configuration
PMError PMError | An internal error occurred in the PortMidi library |
NoSuchDevice | There is no device of that name |
NotAnInputDevice | There is a device of that name, but it doesn't support input |
NotAnOutputDevice | There is a device of that name, but it doesn't support output |
MultipleDevices | There are multiple devices of the same name |
Instances
Constructing values in PortMidiT
throwPortMidi :: Monad m => EOLCPortMidiError -> PortMidiT m arbitrary Source #
Given an exception value, throw it immediately.
throwPortMidiC :: Monad m => Cell (PortMidiT m) EOLCPortMidiError arbitrary Source #
Like throwPortMidi
, but as a Cell
.
liftPMError :: Monad m => m (Either PMError a) -> PortMidiT m a Source #
Given a monadic action that produces a value or a EOLCPortMidiError
,
run it as an action in PortMidiT
.
Typically needed to lift PortMidi backend functions.
liftHandlingState :: Monad m => Cell (HandlingStateT m) a b -> Cell (PortMidiT m) a b Source #
Given a cell with existing handles, lift it into PortMidiT
.
Running values in PortMidiT
runPortMidiC :: MonadIO m => Cell (PortMidiT m) a b -> CellExcept a b (HandlingStateT m) EOLCPortMidiError Source #
Run a cell containing PortMidi effects.
goes through the following steps:runPortMidiC
cell
- Initialize the MIDI system
- Run
cell
, until possibly an exception occurs - Shut the MIDI system down
- Throw the exception in
CellExcept
loopPortMidiC :: MonadIO m => Cell (PortMidiT m) a b -> Cell (HandlingStateT m) a b Source #
Repeatedly run a cell containing PortMidi effects.
Effectively loops over runPortMidiC
,
and prints the exception after it occurred.
runPortMidiT :: PortMidiT m a -> HandlingStateT m (Either EOLCPortMidiError a) Source #
Execute the PortMidiT
effects'.
This returns the first occurring exception. For details on how to automatically start and garbage collect handles, such as the PortMidi backend and devices, see LiveCoding.HandlingState.
You will rarely need this function.
Look at runPortMidiC
and loopPortMidiC
instead.
Input- and output streams
newtype PortMidiInputStream Source #
A stream associated to a PortMidi input device
newtype PortMidiOutputStream Source #
A stream associated to a PortMidi output device
lookupDeviceID :: MonadIO m => String -> DeviceDirection -> m (Either EOLCPortMidiError DeviceID) Source #
Look up a PortMidi device by its name and direction.
You will rarely need this function.
Consider readEventsC
and writeEventsC
instead.
portMidiInputStreamHandle :: MonadIO m => String -> Handle m (Either EOLCPortMidiError PortMidiInputStream) Source #
A Handle
that opens a PortMidiInputStream
of the given device name.
readEventsFrom :: MonadIO m => Cell (PortMidiT m) PortMidiInputStream [PMEvent] Source #
Read all events from the PortMidiInputStream
that accumulated since the last tick.
readEventsC :: MonadIO m => String -> Cell (PortMidiT m) arbitrary [PMEvent] Source #
Read all events from the input device of the given name.
Automatically opens the device.
This is basically a convenient combination of portMidiInputStreamHandle
and readEventsFrom
.
portMidiOutputStreamHandle :: MonadIO m => String -> Handle m (Either EOLCPortMidiError PortMidiOutputStream) Source #
A Handle
that opens a PortMidiOutputStream
of the given device name.
writeEventsTo :: MonadIO m => Cell (PortMidiT m) (PortMidiOutputStream, [PMEvent]) () Source #
Write all events to the PortMidiOutputStream
.
writeEventsC :: MonadIO m => String -> Cell (PortMidiT m) [PMEvent] () Source #
Write all events to the output device of the given name.
Automatically opens the device.
This is basically a convenient combination of portMidiOutputStreamHandle
and writeEventsTo
.
data PortMidiDevices Source #
All devices that the PortMidi backend has connected.
getPortMidiDevices :: IO PortMidiDevices Source #
Retrieve all PortMidi devices.
prettyPrintPortMidiDevices :: PortMidiDevices -> IO () Source #
Print input and output devices separately, one device per line.
Orphan instances
Data PMError Source # | |
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PMError -> c PMError # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PMError # toConstr :: PMError -> Constr # dataTypeOf :: PMError -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PMError) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PMError) # gmapT :: (forall b. Data b => b -> b) -> PMError -> PMError # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PMError -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PMError -> r # gmapQ :: (forall d. Data d => d -> u) -> PMError -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PMError -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PMError -> m PMError # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PMError -> m PMError # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PMError -> m PMError # | |
Generic PMError Source # | |
Finite PMError Source # | |