synthesizer-alsa-0.0.3: Control synthesizer effects via ALSA/MIDISource codeContentsIndex
Synthesizer.Storable.ALSA.MIDI
Description
Convert MIDI events of a MIDI controller to a control signal.
Synopsis
getTimeSeconds :: Fractional time => IO time
clockTimeToSeconds :: Fractional time => ClockTime -> time
type ALSAEvent = (Double, Event)
getStampedEvent :: SndSeq -> IO ALSAEvent
getWaitingEvents :: SndSeq -> IO [ALSAEvent]
type StrictTime = Integer
withMIDIEventsNonblock :: Double -> (T StrictTime (Maybe Event) -> IO a) -> IO a
withMIDIEventsNonblockSimple :: Double -> (T StrictTime Event -> IO a) -> IO a
withMIDIEventsBlock :: Double -> (T StrictTime Event -> IO a) -> IO a
withInPort :: BlockMode -> (SndSeq -> Port -> IO t) -> IO t
discretizeTime :: Double -> T Double a -> T StrictTime a
type LazyTime = T Integer
getSlice :: (Event -> Maybe a) -> State (T StrictTime (Maybe Event)) (T LazyTime a)
partitionMaybe :: (a -> Maybe b) -> T StrictTime a -> (T StrictTime b, T StrictTime a)
partitionMaybeBeat :: (a -> Maybe b) -> T StrictTime (Maybe a) -> (T StrictTime (Maybe b), T StrictTime (Maybe a))
maybeController :: Int -> Int -> Event -> Maybe (Int, Int)
getControllerEvents :: Int -> Int -> State (T StrictTime (Maybe Event)) (T LazyTime Int)
controllerValuesToSignal :: Double -> T LazyTime Double -> T Double
chunkSizesFromLazyTime :: LazyTime -> T ChunkSize
controllerValueToSample :: (Double, Double) -> Int -> Double
getControllerSignal :: Int -> Int -> (Double, Double) -> Double -> State (T StrictTime (Maybe Event)) (T Double)
controllerValueToSampleExp :: (Double, Double) -> Int -> Double
getControllerSignalExp :: Int -> Int -> (Double, Double) -> Double -> State (T StrictTime (Maybe Event)) (T Double)
maybePitchBend :: Int -> Event -> Maybe Int
pitchBendValueToSample :: Double -> Double -> Int -> Double
getPitchBendSignal :: Int -> Double -> Double -> State (T StrictTime (Maybe Event)) (T Double)
getNoteEvents :: Int -> State (T StrictTime (Maybe Event)) (T LazyTime (Int, Int, Bool))
matchNoteEventsAlt :: T LazyTime (Int, Int, Bool) -> T LazyTime (Int, Int, LazyTime)
matchNoteEventsMaybe :: T LazyTime (Maybe (Int, Int, Bool)) -> T LazyTime (Maybe (Int, Int, LazyTime))
matchNoteEvents :: T LazyTime (Int, Int, Bool) -> T LazyTime (Int, Int, LazyTime)
appendTTLazy :: T LazyTime body -> T LazyTime body -> T LazyTime body
lazyDuration :: T LazyTime body -> LazyTime
break :: (body -> Bool) -> T LazyTime body -> (T LazyTime body, body, T LazyTime body)
remove :: (body -> Bool) -> T LazyTime body -> (body, T LazyTime body)
type Instrument = LazyTime -> Double -> Double -> T Double
makeInstrumentSounds :: Instrument -> T time (Int, Int, LazyTime) -> T time (T Double)
insertBreaks :: T LazyTime (T Double) -> T StrictTime (T Double)
getNoteSignal :: Int -> Instrument -> State (T StrictTime (Maybe Event)) (T Double)
ioToLazyList :: IO a -> IO [a]
dump :: IO ()
playMonoSox :: (Storable a, C a) => a -> T a -> IO ()
defaultSampleRate :: Num a => a
bufferSize :: Int
defaultChunkSize :: ChunkSize
latency :: Int
playMono :: (Storable a, C a) => a -> T a -> IO ()
Documentation
getTimeSeconds :: Fractional time => IO timeSource
clockTimeToSeconds :: Fractional time => ClockTime -> timeSource
type ALSAEvent = (Double, Event)Source
getStampedEvent :: SndSeq -> IO ALSAEventSource
only use it for non-blocking sequencers
getWaitingEvents :: SndSeq -> IO [ALSAEvent]Source
only use it for non-blocking sequencers
type StrictTime = IntegerSource
withMIDIEventsNonblock :: Double -> (T StrictTime (Maybe Event) -> IO a) -> IO aSource
withMIDIEventsNonblockSimple :: Double -> (T StrictTime Event -> IO a) -> IO aSource
withMIDIEventsBlock :: Double -> (T StrictTime Event -> IO a) -> IO aSource
withInPort :: BlockMode -> (SndSeq -> Port -> IO t) -> IO tSource
discretizeTime :: Double -> T Double a -> T StrictTime aSource
We first discretize the absolute time values, then we compute differences, in order to avoid rounding errors in further computations.
type LazyTime = T IntegerSource
getSlice :: (Event -> Maybe a) -> State (T StrictTime (Maybe Event)) (T LazyTime a)Source
We turn the strict time values into lazy ones according to the breaks by our beat. However for the laziness breaks we ignore the events that are filtered out. That is we loose laziness granularity but hopefully gain efficiency by larger blocks.
partitionMaybe :: (a -> Maybe b) -> T StrictTime a -> (T StrictTime b, T StrictTime a)Source
Move all elements that are mapped to Just into another list.
partitionMaybeBeat :: (a -> Maybe b) -> T StrictTime (Maybe a) -> (T StrictTime (Maybe b), T StrictTime (Maybe a))Source
Move all elements that are mapped to Just into another list. Nothing elements in the source list are maintained in both result lists as laziness breaks.
maybeController :: Int -> Int -> Event -> Maybe (Int, Int)Source
getControllerEvents :: Int -> Int -> State (T StrictTime (Maybe Event)) (T LazyTime Int)Source
controllerValuesToSignal :: Double -> T LazyTime Double -> T DoubleSource
chunkSizesFromLazyTime :: LazyTime -> T ChunkSizeSource
controllerValueToSample :: (Double, Double) -> Int -> DoubleSource
getControllerSignal :: Int -> Int -> (Double, Double) -> Double -> State (T StrictTime (Maybe Event)) (T Double)Source
controllerValueToSampleExp :: (Double, Double) -> Int -> DoubleSource
getControllerSignalExp :: Int -> Int -> (Double, Double) -> Double -> State (T StrictTime (Maybe Event)) (T Double)Source
maybePitchBend :: Int -> Event -> Maybe IntSource
pitchBendValueToSample :: Double -> Double -> Int -> DoubleSource
getPitchBendSignal :: Int -> Double -> Double -> State (T StrictTime (Maybe Event)) (T Double)Source
getPitchBendSignal channel range center: emits frequencies on an exponential scale from center/range to center*range.
getNoteEvents :: Int -> State (T StrictTime (Maybe Event)) (T LazyTime (Int, Int, Bool))Source
matchNoteEventsAlt :: T LazyTime (Int, Int, Bool) -> T LazyTime (Int, Int, LazyTime)Source
matchNoteEventsMaybe :: T LazyTime (Maybe (Int, Int, Bool)) -> T LazyTime (Maybe (Int, Int, LazyTime))Source
matchNoteEvents :: T LazyTime (Int, Int, Bool) -> T LazyTime (Int, Int, LazyTime)Source
appendTTLazy :: T LazyTime body -> T LazyTime body -> T LazyTime bodySource
This is like append but more lazy, because it uses the structure of the time value.
lazyDuration :: T LazyTime body -> LazyTimeSource
break :: (body -> Bool) -> T LazyTime body -> (T LazyTime body, body, T LazyTime body)Source
Find the first matching body element. Event list must be infinite or it must contain a matching body element, otherwise body and the end of the returned list will be undefined.
remove :: (body -> Bool) -> T LazyTime body -> (body, T LazyTime body)Source
Remove the first matching body element. Event list must be infinite or it must contain a matching body element, otherwise body and the end of the returned list will be undefined.
type Instrument = LazyTime -> Double -> Double -> T DoubleSource
makeInstrumentSounds :: Instrument -> T time (Int, Int, LazyTime) -> T time (T Double)Source
Instrument parameters are: velocity from -1 to 1 (0 is the normal pressure, no pressure aka NoteOff is not supported), frequency is given in Hertz
insertBreaks :: T LazyTime (T Double) -> T StrictTime (T Double)Source
Turn an event list with lazy times to an event list with strict times. This is much like the version we started on. We could avoid this function with a more sophisticated version of arrange.
getNoteSignal :: Int -> Instrument -> State (T StrictTime (Maybe Event)) (T Double)Source
ioToLazyList :: IO a -> IO [a]Source
dump :: IO ()Source
playMonoSox :: (Storable a, C a) => a -> T a -> IO ()Source
Latency is high using Sox - Can we achieve better results using ALSA's sound output?
defaultSampleRate :: Num a => aSource
bufferSize :: IntSource
defaultChunkSize :: ChunkSizeSource
latency :: IntSource
playMono :: (Storable a, C a) => a -> T a -> IO ()Source
Produced by Haddock version 2.4.2