synthesizer-llvm-1.1.0.1: Efficient signal processing using runtime compilation

Safe HaskellNone
LanguageHaskell98

Synthesizer.LLVM.Causal.Helix

Contents

Description

Synopsis
  • static :: (C nodesStep, C nodesLeap) => (C vh, T vh ~ v) => (C a, Field a, RationalConstant a) => (Fraction a, NativeFloating a ar) => (NativeFloating a ar, T a ~ am) => (forall r. T r nodesLeap am v) -> (forall r. T r nodesStep am v) -> Exp Int -> Exp a -> Exp (StorableVector vh) -> T (am, am) v
  • staticPacked :: (C nodesStep, C nodesLeap) => (C vh, T vh ~ ve, Element v ~ ve) => (Size (nodesLeap (nodesStep v)) ~ n, Write (nodesLeap (nodesStep v)), Element (nodesLeap (nodesStep v)) ~ nodesLeap (nodesStep (Element v))) => Positive n => (C a, Field a, Real a, Fraction a, RationalConstant a, NativeFloating n a ar) => (forall r. T r nodesLeap (Value n a) v) -> (forall r. T r nodesStep (Value n a) v) -> Exp Int -> Exp a -> Exp (StorableVector vh) -> T (Value n a, Value n a) v
  • dynamic :: (C nodesStep, C nodesLeap) => (C a, Field a, Fraction a, Select a, Comparison a, NativeFloating a ar, RationalConstant a, NativeFloating a ar) => T a ~ am => C v => (forall r. T r nodesLeap am v) -> (forall r. T r nodesStep am v) -> Exp Int -> Exp a -> T v -> T (am, am) v
  • dynamicLimited :: (C nodesStep, C nodesLeap) => (C a, Field a, Fraction a, Select a, Comparison a, NativeFloating a ar, RationalConstant a, NativeFloating a ar) => T a ~ am => C v => (forall r. T r nodesLeap am v) -> (forall r. T r nodesStep am v) -> Exp Int -> Exp a -> T v -> T (am, am) v
  • zigZag :: C a => (Select a, Comparison a, Fraction a) => (Field a, RationalConstant a) => Exp a -> MV a a
  • zigZagPacked :: Positive n => C a => (Field a, Fraction a) => RationalConstant a => (Select a, Comparison a) => Exp a -> T (Value n a) (Value n a)
  • zigZagLong :: C a => (Select a, Comparison a, Fraction a) => (Field a, RationalConstant a) => Exp a -> Exp a -> MV a a
  • zigZagLongPacked :: Vector n a => (Field a, Fraction a) => RationalConstant a => (Select a, Comparison a) => Exp a -> Exp a -> T (Value n a) (Value n a)

time and phase control based on the helix model

static :: (C nodesStep, C nodesLeap) => (C vh, T vh ~ v) => (C a, Field a, RationalConstant a) => (Fraction a, NativeFloating a ar) => (NativeFloating a ar, T a ~ am) => (forall r. T r nodesLeap am v) -> (forall r. T r nodesStep am v) -> Exp Int -> Exp a -> Exp (StorableVector vh) -> T (am, am) v Source #

Inputs are (shape, phase).

The shape parameter is limited at the beginning and at the end such that only available data is used for interpolation. Actually, we allow almost one step less than possible, since the right boundary of the interval of admissible shape values is open.

staticPacked :: (C nodesStep, C nodesLeap) => (C vh, T vh ~ ve, Element v ~ ve) => (Size (nodesLeap (nodesStep v)) ~ n, Write (nodesLeap (nodesStep v)), Element (nodesLeap (nodesStep v)) ~ nodesLeap (nodesStep (Element v))) => Positive n => (C a, Field a, Real a, Fraction a, RationalConstant a, NativeFloating n a ar) => (forall r. T r nodesLeap (Value n a) v) -> (forall r. T r nodesStep (Value n a) v) -> Exp Int -> Exp a -> Exp (StorableVector vh) -> T (Value n a, Value n a) v Source #

dynamic :: (C nodesStep, C nodesLeap) => (C a, Field a, Fraction a, Select a, Comparison a, NativeFloating a ar, RationalConstant a, NativeFloating a ar) => T a ~ am => C v => (forall r. T r nodesLeap am v) -> (forall r. T r nodesStep am v) -> Exp Int -> Exp a -> T v -> T (am, am) v Source #

If the time control exceeds the end of the input signal, then the last waveform is locked. This is analogous to static.

dynamicLimited :: (C nodesStep, C nodesLeap) => (C a, Field a, Fraction a, Select a, Comparison a, NativeFloating a ar, RationalConstant a, NativeFloating a ar) => T a ~ am => C v => (forall r. T r nodesLeap am v) -> (forall r. T r nodesStep am v) -> Exp Int -> Exp a -> T v -> T (am, am) v Source #

In contrast to dynamic this one ends when the end of the manipulated signal is reached.

useful control curves

zigZag :: C a => (Select a, Comparison a, Fraction a) => (Field a, RationalConstant a) => Exp a -> MV a a Source #

zigZag start creates a zig-zag curve with values between 0 and 1, inclusively, that is useful as shape control for looping a sound. Input of the causal process is the slope (or frequency) control. Slope values must not be negative. The start value must be at most 2 and may be negative.

zigZagPacked :: Positive n => C a => (Field a, Fraction a) => RationalConstant a => (Select a, Comparison a) => Exp a -> T (Value n a) (Value n a) Source #

zigZagLong :: C a => (Select a, Comparison a, Fraction a) => (Field a, RationalConstant a) => Exp a -> Exp a -> MV a a Source #

zigZagLong loopStart loopLength creates a curve that starts at 0 and is linear until it reaches loopStart+loopLength. Then it begins looping in a ping-pong manner between loopStart+loopLength and loopStart. It is useful as shape control for looping a sound. Input of the causal process is the slope (or frequency) control. Slope values must not be negative.

  • Main> Sig.renderChunky SVL.defaultChunkSize (Causal.take 25 <<< Helix.zigZagLong 6 10 $* 2) () :: SVL.Vector Float VectorLazy.fromChunks [Vector.pack [0.0,1.999999,3.9999995,6.0,8.0,10.0,12.0,14.0,15.999999,14.000001,12.0,10.0,7.999999,6.0,8.0,10.0,12.0,14.0,16.0,14.0,11.999999,9.999998,7.999998,6.0000024,8.000002]]

zigZagLongPacked :: Vector n a => (Field a, Fraction a) => RationalConstant a => (Select a, Comparison a) => Exp a -> Exp a -> T (Value n a) (Value n a) Source #