Safe Haskell | None |
---|---|
Language | Haskell2010 |
Convert MIDI events of a MIDI controller to a control signal.
- replicateLong :: Write sig y => StrictTime -> y -> sig y
- piecewiseConstant :: Write sig y => T StrictTime y -> sig y
- piecewiseConstantInit :: Write sig y => y -> T StrictTime y -> sig y
- piecewiseConstantInitWith :: Write sig c => (y -> c) -> c -> T StrictTime [y] -> sig c
- type Instrument y signal = y -> y -> LazyTime -> signal
- type Bank y signal = Program -> Instrument y signal
- renderInstrument :: C y => Bank y signal -> Note -> signal
- renderInstrumentIgnoreProgram :: C y => Instrument y signal -> Note -> signal
- flatten :: (Monoid signal, C time) => T time [signal] -> T time signal
- applyModulation :: (Transform signal, NormalForm signal) => signal -> Modulator (signal -> instr, note) (instr, note)
- evaluateVectorHead :: NormalForm signal => signal -> t -> t
- advanceModulation :: (Transform signal, NormalForm signal) => LazyTime -> State signal LazyTime
- advanceModulationChunk :: (Transform signal, NormalForm signal) => StrictTime -> State signal StrictTime
- advanceModulationChunkStrict :: (Transform signal, NormalForm signal) => StrictTime -> State signal StrictTime
- advanceModulationChunkPC :: NFData body => StrictTime -> State (T StrictTime body) StrictTime
- type FilterSequence event signal = Filter event (T ShortStrictTime signal)
- data Modulator note signal = Modulator state (StrictTime -> State state StrictTime) (note -> State state signal)
- applyModulator :: Modulator a b -> T StrictTime [a] -> T StrictTime [b]
- sequenceCore :: (C event, Monoid signal) => Channel -> Program -> Modulator Note signal -> FilterSequence event signal
- errorNoProgram :: Program
- sequence :: (C event, Monoid signal, C y) => Channel -> Instrument y signal -> FilterSequence event signal
- sequenceModulated :: (C event, Transform ctrl, NormalForm ctrl, Monoid signal, C y) => ctrl -> Channel -> (ctrl -> Instrument y signal) -> FilterSequence event signal
- sequenceMultiModulated :: (C event, Monoid signal, C y) => Channel -> instrument -> Modulator (instrument, Note) (Instrument y signal, Note) -> FilterSequence event signal
- sequenceMultiProgram :: (C event, Monoid signal, C y) => Channel -> Program -> [Instrument y signal] -> FilterSequence event signal
- sequenceModulatedMultiProgram :: (Transform ctrl, NormalForm ctrl, C event, Monoid signal, C y) => ctrl -> Channel -> Program -> [ctrl -> Instrument y signal] -> FilterSequence event signal
Documentation
replicateLong :: Write sig y => StrictTime -> y -> sig y Source #
piecewiseConstant :: Write sig y => T StrictTime y -> sig y Source #
piecewiseConstantInit :: Write sig y => y -> T StrictTime y -> sig y Source #
piecewiseConstantInitWith :: Write sig c => (y -> c) -> c -> T StrictTime [y] -> sig c Source #
type Instrument y signal = y -> y -> LazyTime -> signal Source #
type Bank y signal = Program -> Instrument y signal Source #
renderInstrument :: C y => Bank y signal -> Note -> signal 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
renderInstrumentIgnoreProgram :: C y => Instrument y signal -> Note -> signal Source #
flatten :: (Monoid signal, C time) => T time [signal] -> T time signal Source #
Turn an event list with bundles of elements into an event list with single events. ToDo: Move to event-list package?
applyModulation :: (Transform signal, NormalForm signal) => signal -> Modulator (signal -> instr, note) (instr, note) Source #
evaluateVectorHead :: NormalForm signal => signal -> t -> t Source #
We have to evaluate the head value at each drop
in order to avoid growing thunks that lead to a space leak.
advanceModulation :: (Transform signal, NormalForm signal) => LazyTime -> State signal LazyTime Source #
advanceModulationChunk :: (Transform signal, NormalForm signal) => StrictTime -> State signal StrictTime Source #
advanceModulationChunkStrict :: (Transform signal, NormalForm signal) => StrictTime -> State signal StrictTime Source #
advanceModulationChunkPC :: NFData body => StrictTime -> State (T StrictTime body) StrictTime Source #
type FilterSequence event signal = Filter event (T ShortStrictTime signal) Source #
data Modulator note signal Source #
The state action for the time
should just return the argument time.
However we need this time (or alternatively another result type)
for triggering the drop
in advanceModulationChunk
.
Without this strict evaluation,
the drop will be delayed until the control curve is actually needed.
Modulator state (StrictTime -> State state StrictTime) (note -> State state signal) |
applyModulator :: Modulator a b -> T StrictTime [a] -> T StrictTime [b] Source #
sequenceCore :: (C event, Monoid signal) => Channel -> Program -> Modulator Note signal -> FilterSequence event signal Source #
sequence :: (C event, Monoid signal, C y) => Channel -> Instrument y signal -> FilterSequence event signal Source #
sequenceModulated :: (C event, Transform ctrl, NormalForm ctrl, Monoid signal, C y) => ctrl -> Channel -> (ctrl -> Instrument y signal) -> FilterSequence event signal Source #
sequenceMultiModulated :: (C event, Monoid signal, C y) => Channel -> instrument -> Modulator (instrument, Note) (Instrument y signal, Note) -> FilterSequence event signal Source #
sequenceMultiProgram :: (C event, Monoid signal, C y) => Channel -> Program -> [Instrument y signal] -> FilterSequence event signal Source #
sequenceModulatedMultiProgram :: (Transform ctrl, NormalForm ctrl, C event, Monoid signal, C y) => ctrl -> Channel -> Program -> [ctrl -> Instrument y signal] -> FilterSequence event signal Source #