Safe Haskell | Safe-Inferred |
---|
Render FAUST instruments.
Synopsis
- type Error = Text
- write :: Config -> FilePath -> Set Id.TrackId -> InstrumentC.Patch -> [Note.Note] -> IO (Either Error (Int, Int))
- checkElements :: (Config.Payload -> IO ()) -> InstrumentC.Patch -> [Note.Note] -> IO ()
- toSpan :: Note.Note -> Checkpoint.Span
- data Config = Config {
- _chunkSize :: !Frames
- _blockSize :: !Frames
- _controlSize :: !Frames
- _controlsPerBlock :: !Frames
- _maxDecay :: !Frames
- _emitProgress :: !Bool
- defaultConfig :: Config
- _controlRate :: Config -> Int
- renderPatch :: (Config.Payload -> IO ()) -> InstrumentC.Patch -> Config -> Maybe Checkpoint.State -> (Checkpoint.State -> IO ()) -> [Note.Note] -> RealTime.RealTime -> AUtil.Audio
- interleave :: AUtil.NAudio -> AUtil.Audio
- _initialize :: Frames -> InstrumentC.Instrument -> Map InstrumentC.Control Float -> IO ()
- render :: (Config.Payload -> IO ()) -> InstrumentC.Patch -> Maybe Checkpoint.State -> (Checkpoint.State -> IO ()) -> Map InstrumentC.Control AUtil.Audio1 -> AUtil.NAudio -> Frames -> Frames -> Config -> AUtil.NAudio
- renderBlock :: MonadIO m => (Config.Payload -> IO ()) -> Config -> (Checkpoint.State -> IO ()) -> InstrumentC.Instrument -> Map InstrumentC.Control Audio.Block -> [Audio.Block] -> Frames -> Frames -> Stream (Of [Audio.Block]) m (Maybe Frames)
- renderControls :: Monad m => Config -> InstrumentC.PatchT ptr cptr -> [Note.Note] -> RealTime.RealTime -> Map InstrumentC.Control (Audio.Audio m rate 1)
- renderInputs :: (Monad m, TypeLits.KnownNat rate) => Config -> Frames -> InstrumentC.PatchT ptr cptr -> [Note.Note] -> RealTime.RealTime -> Audio.NAudio m rate
- renderInput :: (Monad m, TypeLits.KnownNat rate) => RealTime.RealTime -> [(Double, Double)] -> Maybe (Audio.Audio m rate 1)
- inputsBreakpoints :: InstrumentC.PatchT ptr cptr -> [Note.Note] -> [[(Double, Double)]]
- controlsBreakpoints :: Frames -> InstrumentC.PatchT ptr cptr -> [Note.Note] -> Map InstrumentC.Control [(Double, Double)]
- extractControls :: Frames -> Bool -> Set InstrumentC.Control -> [Note.Note] -> Map InstrumentC.Control [(Double, Double)]
- tweakNotes :: Frames -> [Note.Note] -> [Note.Note]
- controlBreakpoints :: Frames -> Bool -> Control.Control -> [Note.Note] -> [(Double, Double)]
- gateBreakpoints :: Frames -> Bool -> [Note.Note] -> [(Double, Double)]
- dropUntil :: (a -> a -> Bool) -> [a] -> [a]
Documentation
write
checkElements :: (Config.Payload -> IO ()) -> InstrumentC.Patch -> [Note.Note] -> IO () Source #
Emit a warning if the patch expects element-address controls and a note doesn't have an element, or vice versa.
toSpan :: Note.Note -> Checkpoint.Span Source #
render
Config | |
|
_controlRate :: Config -> Int Source #
Control signals run at this rate.
This should divide into Config.blockSize, which in turn divides into Config.SamplingRate.
renderPatch :: (Config.Payload -> IO ()) -> InstrumentC.Patch -> Config -> Maybe Checkpoint.State -> (Checkpoint.State -> IO ()) -> [Note.Note] -> RealTime.RealTime -> AUtil.Audio Source #
Render notes belonging to a single FAUST patch. Since they render on a single element, they should either not overlap, or be ok if overlaps cut each other off.
interleave :: AUtil.NAudio -> AUtil.Audio Source #
_initialize :: Frames -> InstrumentC.Instrument -> Map InstrumentC.Control Float -> IO () Source #
Faust has internal state, and it all starts at 0, and because controls are designed for realtime, they interpolate after the value changed instead of before, I have to initialize then render for long enough to avoid attack artifacts.
:: (Config.Payload -> IO ()) | |
-> InstrumentC.Patch | |
-> Maybe Checkpoint.State | |
-> (Checkpoint.State -> IO ()) | notify new state after each audio chunk |
-> Map InstrumentC.Control AUtil.Audio1 | |
-> AUtil.NAudio | |
-> Frames | |
-> Frames | logical end time |
-> Config | |
-> AUtil.NAudio |
Render a FAUST instrument incrementally.
Chunk size is determined by the size of the inputs
chunks, or
Audio.blockSize if they're empty or run out. The inputs will go to zero
if they end before the given time.
renderBlock :: MonadIO m => (Config.Payload -> IO ()) -> Config -> (Checkpoint.State -> IO ()) -> InstrumentC.Instrument -> Map InstrumentC.Control Audio.Block -> [Audio.Block] -> Frames -> Frames -> Stream (Of [Audio.Block]) m (Maybe Frames) Source #
render breakpoints
renderControls :: Monad m => Config -> InstrumentC.PatchT ptr cptr -> [Note.Note] -> RealTime.RealTime -> Map InstrumentC.Control (Audio.Audio m rate 1) Source #
renderInputs :: (Monad m, TypeLits.KnownNat rate) => Config -> Frames -> InstrumentC.PatchT ptr cptr -> [Note.Note] -> RealTime.RealTime -> Audio.NAudio m rate Source #
Render the supported controls down to audio rate signals. This causes the
stream to be synchronized by _blockSize
, which should determine render
chunk sizes, which should be a factor of _chunkSize
.
renderInput :: (Monad m, TypeLits.KnownNat rate) => RealTime.RealTime -> [(Double, Double)] -> Maybe (Audio.Audio m rate 1) Source #
extract breakpoints
inputsBreakpoints :: InstrumentC.PatchT ptr cptr -> [Note.Note] -> [[(Double, Double)]] Source #
controlsBreakpoints :: Frames -> InstrumentC.PatchT ptr cptr -> [Note.Note] -> Map InstrumentC.Control [(Double, Double)] Source #
extractControls :: Frames -> Bool -> Set InstrumentC.Control -> [Note.Note] -> Map InstrumentC.Control [(Double, Double)] Source #
tweakNotes :: Frames -> [Note.Note] -> [Note.Note] Source #
Offset notes <= 0 to controlSize. Otherwise, since rendering starts at 0, the tweak in controlBreakpoints can't move the breakpoints and the first note gets initialization artifacts. TODO implement proper <0 rendering, SamplerIm does it.
controlBreakpoints :: Frames -> Bool -> Control.Control -> [Note.Note] -> [(Double, Double)] Source #
gateBreakpoints :: Frames -> Bool -> [Note.Note] -> [(Double, Double)] Source #
Make a signal with a rising edge on the note attack. The value is from Control.dynamic, which means a note with dyn=0 won't get an attack at all.
If impulseGate=True, it will be a controlSize length impulse. Otherwise, it will stay positive for the duration of the note. If the note is adjacent to another with the same element, the dip to zero likely won't be registered, so presumably the instrument will need some other signal if it cares about attacks of notes that touch.