hsc3-0.20: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Sc3.Common.Math.Interpolate

Description

Interpolation functions, ie. for envelope segments. Present naming is for qualified import.

Synopsis

Documentation

type Interpolation_f t = t -> t -> t -> t Source #

An interpolation function takes three arguments. x0 is the left or begin value, x1 is the right or end value, t is a (0,1) index.

interpolate :: (Num t, Ord t) => Interpolation_f t -> (t, t) -> t -> t Source #

Clip x to (0,1) and run f.

interpolate linear (-1,1) 0.5 == 0

step :: Interpolation_f t Source #

Step function, ignores t and returns x1.

linear :: Num t => Interpolation_f t Source #

Linear interpolation funtion.

map (linear 1 10) [0,0.25 .. 1] == [1,3.25,5.5,7.75,10]
import Sound.Sc3.Plot 
plot_fn_r1_ln (linear (-1) 1) (0,1)

exponential :: Floating t => Interpolation_f t Source #

Exponential interpolation. x0 must not be zero and (x0,x1) must not span zero.

plot_fn_r1_ln (exponential 0.001 1) (0,1)
plot_fn_r1_ln (exponential 1 2) (0,1)
plot_fn_r1_ln (exponential 20 20000) (0,1)

exponential_0 :: (Eq t, Floating t) => Interpolation_f t Source #

Variant that allows x0 to be zero, though (x0,x1) must not span zero.

plot_fn_r1_ln (exponential_0 0 1) (0,1)
plot_fn_r1_ln (exponential_0 0 (-1)) (0,1)

exponential_lin :: (Eq t, Floating t) => Interpolation_f t Source #

linear of exponential_0 of (0,1), ie. allows (x0,x1) to span zero.

plot_fn_r1_ln (exponential_lin (-1) 1) (0,1)

sine :: Floating t => Interpolation_f t Source #

linear with t transformed by sine function over (-pi2,pi2).

plot_fn_r1_ln (sine (-1) 1) (0,1)

welch :: (Ord t, Floating t) => Interpolation_f t Source #

If x0 < x1 rising sine segment (0,pi2), else falling segment (pi2,pi).

plot_fn_r1_ln (welch (-1) 1) (0,1)
plot_fn_r1_ln (welch 1 (-1)) (0,1)

curve :: (Ord t, Floating t) => t -> Interpolation_f t Source #

Curvature controlled by single parameter c. Zero is linear, increasing c approaches exponential and continues past it. The value for c at which the curve is close to exponential depends on the range.

plot_p1_ln (map (\c-> map (curve c (-1) 1) [0,0.01 .. 1]) [-6,-4 .. 6])
plot_p1_ln (map (\f -> map f [0,0.01 .. 1]) [curve 4.4 1 100,exponential 1 100,curve 4.5 1 100])
plot_p1_ln (map (\f -> map f [0,0.01 .. 1]) [exponential 20 20000,curve 7 20 20000])
plot_p1_ln (map (\f -> map f [0,0.01 .. 1]) [fader 0 2,curve 2 0 2])

squared :: Floating t => Interpolation_f t Source #

Square of linear of sqrt of x0 and x1, therefore neither may be negative.

plot_fn_r1_ln (squared 0 1) (0,1)
plot_p1_ln (map (\f -> map f [0,0.01 .. 1]) [curve 2.05 0 1,squared 0 1])

cubed :: Floating t => Interpolation_f t Source #

Cubic variant of squared.

plot_fn_r1_ln (cubed 0 1) (0,1)
plot_p1_ln (map (\f -> map f [0,0.01 .. 1]) [curve 3.25 0 1,cubed 0 1])

hold :: (Num t, Ord t) => Interpolation_f t Source #

x0 until end, then immediately x1.

plot_fn_r1_ln (hold 0 1) (0,2)

fader :: (Num t, Ord t) => Interpolation_f t Source #

Fader curve, equal to squared when x1 > x0.

plot_p1_ln (map (\f -> map f [0,0.01 .. 1]) [squared 0 1,fader 0 1])
plot_p1_ln (map (\f -> map f [0,0.01 .. 1]) [curve 2 1 0,fader 1 0])