hsc3-0.20: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Sc3.Common.Math

Description

Common math functions.

Synopsis

Documentation

half_pi :: Floating a => a Source #

Half pi.

half_pi == 1.5707963267948966

two_pi :: Floating n => n Source #

Two pi.

two_pi == 6.283185307179586

absdif :: Num a => a -> a -> a Source #

abs of (-).

type SC3_MulAdd t = t -> t -> t -> t Source #

SC3 MulAdd type signature, arguments in SC3 order of input, multiply, add.

sc3_mul_add :: Num t => SC3_MulAdd t Source #

Ordinary (un-optimised) multiply-add, see also mulAdd Ugen.

sc3_mul_add 2 3 4 == 2 * 3 + 4
map (\x -> sc3_mul_add x 2 3) [1,5] == [5,13] && map (\x -> sc3_mul_add x 3 2) [1,5] == [5,17]

mul_add :: Num t => t -> t -> t -> t Source #

Ordinary Haskell order (un-optimised) multiply-add.

mul_add 3 4 2 == 2 * 3 + 4
map (mul_add 2 3) [1,5] == [5,13] && map (mul_add 3 4) [1,5] == [7,19]

mul_add_hs :: Num t => (t, t) -> t -> t Source #

uncurry mul_add

mul_add_hs (3,4) 2 == 2 * 3 + 4

sc3_round_to :: RealFrac n => n -> n -> n Source #

Variant of SC3 roundTo function.

sc3_round_to (2/3) 0.25 == 0.75
let r = [0,0,0.25,0.25,0.5,0.5,0.5,0.75,0.75,1,1]
map (`sc3_round_to` 0.25) [0,0.1 .. 1] == r
map (`sc3_round_to` 5.0) [100.0 .. 110.0]

sc3_idiv :: RealFrac n => n -> n -> n Source #

sc3_lcm :: t -> t -> t Source #

sc3_lcm

Least common multiple. This definition extends the usual definition and returns a negative number if any of the operands is negative. This makes it consistent with the lattice-theoretical interpretation and its idempotency, commutative, associative, absorption laws.

lcm 4 6 == 12
lcm 1 1 == 1
lcm 1624 26 == 21112
lcm 1624 (-26) /= (-21112)
lcm (-1624) (-26) /= (-21112)
lcm 513 (gcd 513 44) == 513

sc3_gcd :: t -> t -> t Source #

sc3_gcd

Greatest common divisor. This definition extends the usual definition and returns a negative number if both operands are negative. This makes it consistent with the lattice-theoretical interpretation and its idempotency, commutative, associative, absorption laws. https://www.jsoftware.com/papers/eem/gcd.htm

gcd 4 6 == 2
gcd 0 1 == 1
gcd 1024 256 == 256
gcd 1024 (-256) == 256
gcd (-1024) (-256) /= (-256)
gcd (-1024) (lcm (-1024) 256) /= (-1024)
gcd 66 54 * lcm 66 54 == 66 * 54

sc3_mod :: RealFrac n => n -> n -> n Source #

The SC3 % Ugen operator is the mod' function.

> 1.5 % 1.2 // ~= 0.3
> -1.5 % 1.2 // ~= 0.9
> 1.5 % -1.2 // ~= -0.9
> -1.5 % -1.2 // ~= -0.3
let (%) = sc3_mod
1.5 % 1.2 ~= 0.3
(-1.5) % 1.2 ~= 0.9
1.5 % (-1.2) ~= -0.9
(-1.5) % (-1.2) ~= -0.3
> 1.2 % 1.5 // ~= 1.2
> -1.2 % 1.5 // ~= 0.3
> 1.2 % -1.5 // ~= -0.3
> -1.2 % -1.5 // ~= -1.2
1.2 % 1.5 ~= 1.2
(-1.2) % 1.5 ~= 0.3
1.2 % (-1.5) ~= -0.3
(-1.2) % (-1.5) ~= -1.2
map (\n -> sc3_mod n 12.0) [-1.0,12.25,15.0] == [11.0,0.25,3.0]

fmod_f32 :: Float -> Float -> Float Source #

Type specialised sc3_mod.

fmod_f64 :: Double -> Double -> Double Source #

Type specialised sc3_mod.

sc3_clip :: Ord a => a -> a -> a -> a Source #

SC3 clip function. Clip n to within range (i,j). clip is a Ugen.

map (\n -> sc3_clip n 5 10) [3..12] == [5,5,5,6,7,8,9,10,10,10]

clip_hs :: Ord a => (a, a) -> a -> a Source #

Variant of sc3_clip with haskell argument structure.

map (clip_hs (5,10)) [3..12] == [5,5,5,6,7,8,9,10,10,10]

sc3_mod_alt :: RealFrac a => a -> a -> a Source #

Fractional modulo, alternate implementation.

map (\n -> sc3_mod_alt n 12.0) [-1.0,12.25,15.0] == [11.0,0.25,3.0]

sc3_wrap_ni :: RealFrac a => a -> a -> a -> a Source #

Wrap function that is non-inclusive at right edge, ie. the Wrap Ugen rule.

map (sc3_wrap_ni 0 5) [4,5,6] == [4,0,1]
map (sc3_wrap_ni 5 10) [3..12] == [8,9,5,6,7,8,9,5,6,7]
Sound.Sc3.Plot.plot_fn_r1_ln (sc3_wrap_ni (-1) 1) (-2,2)

wrap_hs_int :: Integral a => (a, a) -> a -> a Source #

sc_wrap::int

> [5,6].wrap(0,5) == [5,0]
map (wrap_hs_int (0,5)) [5,6] == [5,0]
> [9,10,5,6,7,8,9,10,5,6].wrap(5,10) == [9,10,5,6,7,8,9,10,5,6]
map (wrap_hs_int (5,10)) [3..12] == [9,10,5,6,7,8,9,10,5,6]

wrap_hs :: RealFrac n => (n, n) -> n -> n Source #

Wrap n to within range (i,j), ie. AbstractFunction.wrap, ie. inclusive at right edge. wrap is a Ugen, hence prime.

> [5.0,6.0].wrap(0.0,5.0) == [0.0,1.0]
map (wrap_hs (0,5)) [5,6] == [0,1]
map (wrap_hs (5,10)) [3..12] == [8,9,5,6,7,8,9,5,6,7]
Sound.Sc3.Plot.plot_fn_r1_ln (wrap_hs (-1,1)) (-2,2)

sc3_wrap :: RealFrac n => n -> n -> n -> n Source #

Variant of wrap_hs with SC3 argument ordering.

map (\n -> sc3_wrap n 5 10) [3..12] == map (wrap_hs (5,10)) [3..12]

generic_wrap :: (Ord a, Num a) => (a, a) -> a -> a Source #

Generic variant of wrap'.

> [5,6].wrap(0,5) == [5,0]
map (generic_wrap (0,5)) [5,6] == [5,0]
> [9,10,5,6,7,8,9,10,5,6].wrap(5,10) == [9,10,5,6,7,8,9,10,5,6]
map (generic_wrap (5::Integer,10)) [3..12] == [9,10,5,6,7,8,9,10,5,6]

bin_to_freq :: (Fractional n, Integral i) => n -> i -> i -> n Source #

Given sample-rate sr and bin-count n calculate frequency of ith bin.

bin_to_freq 44100 2048 32 == 689.0625

midi_to_cps :: Floating a => a -> a Source #

Fractional midi note number to cycles per second.

map (floor . midi_to_cps) [0,24,69,120,127] == [8,32,440,8372,12543]
map (floor . midi_to_cps) [-36,138] == [1,23679]
map (floor . midi_to_cps) [69.0,69.25 .. 70.0] == [440,446,452,459,466]

cps_to_midi :: Floating a => a -> a Source #

Cycles per second to fractional midi note number.

map (round . cps_to_midi) [8,32,440,8372,12543] == [0,24,69,120,127]
map (round . cps_to_midi) [1,24000] == [-36,138]

cps_to_oct :: Floating a => a -> a Source #

Cycles per second to linear octave (4.75 = A4 = 440).

map (cps_to_oct . midi_to_cps) [60,63,69] == [4.0,4.25,4.75]

oct_to_cps :: Floating a => a -> a Source #

Linear octave to cycles per second.

> [4.0,4.25,4.75].octcps.cpsmidi == [60,63,69]
map (cps_to_midi . oct_to_cps) [4.0,4.25,4.75] == [60,63,69]

degree_to_key :: RealFrac a => [a] -> a -> a -> a Source #

Degree, scale and steps per octave to key.

pianokey_to_midi :: Num n => n -> n Source #

One-indexed piano key number (for standard 88 key piano) to midi note number.

map pianokey_to_midi [1,49,88] == [21,69,108]

pianokey_to_cps :: Floating n => n -> n Source #

Piano key to hertz (ba.pianokey2hz in Faust). This is useful as a more musical gamut than midi note numbers. Ie. if x is in (0,1) then pianokey_to_cps of (x * 88) is in (26,4168)

map (round . pianokey_to_cps) [0,1,40,49,88] == [26,28,262,440,4186]
map (round . midi_to_cps) [0,60,69,127] == [8,262,440,12544]

amp_to_db :: Floating a => a -> a Source #

Linear amplitude to decibels.

map (round . amp_to_db) [0.01,0.05,0.0625,0.125,0.25,0.5] == [-40,-26,-24,-18,-12,-6]

db_to_amp :: Floating a => a -> a Source #

Decibels to linear amplitude.

map (floor . (* 100). db_to_amp) [-40,-26,-24,-18,-12,-6] == [01,05,06,12,25,50]

let amp = map (2 **) [0 .. 15] let db = [0,-6 .. -90] map (round . ampDb . (/) 1) amp == db map (round . amp_to_db . (/) 1) amp == db zip amp db

db_to_amp (-3) == 0.7079457843841379 amp_to_db 0.7079457843841379 == -3

midi_to_ratio :: Floating a => a -> a Source #

Fractional midi note interval to frequency multiplier.

map midi_to_ratio [-12,0,7,12] == [0.5,1,1.4983070768766815,2]

ratio_to_midi :: Floating a => a -> a Source #

Inverse of midi_to_ratio.

map ratio_to_midi [3/2,2] == [7.019550008653875,12]

cps_to_incr :: Fractional a => a -> a -> a -> a Source #

sr = sample rate, r = cycle (two-pi), cps = frequency

cps_to_incr 48000 128 375 == 1
cps_to_incr 48000 two_pi 458.3662361046586 == 6e-2

incr_to_cps :: Fractional a => a -> a -> a -> a Source #

Inverse of cps_to_incr.

incr_to_cps 48000 128 1 == 375

pan2_f :: Fractional t => (t -> t) -> t -> t -> (t, t) Source #

Pan2 function, identity is linear, sqrt is equal power.

lin_pan2 :: Fractional t => t -> t -> (t, t) Source #

Linear pan.

map (lin_pan2 1) [-1,-0.5,0,0.5,1] == [(1,0),(0.75,0.25),(0.5,0.5),(0.25,0.75),(0,1)]

eq_pan2 :: Floating t => t -> t -> (t, t) Source #

Equal power pan.

map (eq_pan2 1) [-1,-0.5,0,0.5,1]

sc3_dif_sqr :: Num a => a -> a -> a Source #

a^2 - b^2.

sc3_hypot :: Floating a => a -> a -> a Source #

Euclidean distance function (sqrt of sum of squares).

sc3_hypotx :: (Ord a, Floating a) => a -> a -> a Source #

Sc3 hypotenuse approximation function.

foldToRange :: (Ord a, Num a) => a -> a -> a -> a Source #

Fold k to within range (i,j), ie. AbstractFunction.fold

map (foldToRange 5 10) [3..12] == [7,6,5,6,7,8,9,10,9,8]

sc3_fold :: (Ord a, Num a) => a -> a -> a -> a Source #

Variant of foldToRange with SC3 argument ordering.

sc3_distort :: Fractional n => n -> n Source #

SC3 distort operator.

sc3_softclip :: (Ord n, Fractional n) => n -> n Source #

SC3 softclip operator.

Bool

sc3_true :: Num n => n Source #

True is conventionally 1. The test to determine true is > 0.

sc3_false :: Num n => n Source #

False is conventionally 0. The test to determine true is <= 0.

sc3_not :: (Ord n, Num n) => n -> n Source #

Lifted not.

sc3_not sc3_true == sc3_false
sc3_not sc3_false == sc3_true

sc3_bool :: Num n => Bool -> n Source #

Translate Bool to sc3_true and sc3_false.

sc3_comparison :: Num n => (n -> n -> Bool) -> n -> n -> n Source #

Lift comparison function.

Eq

sc3_eq :: (Num n, Eq n) => n -> n -> n Source #

Lifted ==.

sc3_neq :: (Num n, Eq n) => n -> n -> n Source #

Lifted /=.

Ord

sc3_lt :: (Num n, Ord n) => n -> n -> n Source #

Lifted <.

sc3_lte :: (Num n, Ord n) => n -> n -> n Source #

Lifted <=.

sc3_gt :: (Num n, Ord n) => n -> n -> n Source #

Lifted >.

sc3_gte :: (Num n, Ord n) => n -> n -> n Source #

Lifted >=.

Clip Rule

apply_clip_rule :: Ord n => Clip_Rule -> n -> n -> n -> n -> n -> Maybe n Source #

Clip a value that is expected to be within an input range to an output range, according to a rule.

let f r = map (\x -> apply_clip_rule r 0 1 (-1) 1 x) [-1,0,0.5,1,2]
in map f [minBound .. maxBound]

LinLin

urange_ma :: Fractional a => SC3_MulAdd a -> a -> a -> a -> a Source #

Scale uni-polar (0,1) input to linear (l,r) range.

urange :: Fractional a => a -> a -> a -> a Source #

Scale (0,1) input to linear (l,r) range. u = uni-polar.

map (urange 3 4) [0,0.5,1] == [3,3.5,4]

range_muladd :: Fractional t => t -> t -> (t, t) Source #

Calculate multiplier and add values for (-1,1) range transform.

range_muladd 3 4 == (0.5,3.5)

range_ma :: Fractional a => SC3_MulAdd a -> a -> a -> a -> a Source #

Scale bi-polar (-1,1) input to linear (l,r) range. Note that the argument order is not the same as linLin.

range :: Fractional a => a -> a -> a -> a Source #

Scale (-1,1) input to linear (l,r) range. Note that the argument order is not the same as linlin. Note also that the various range Ugen methods at sclang select mul-add values given the output range of the Ugen, ie LFPulse.range selects a (0,1) input range.

map (range 3 4) [-1,0,1] == [3,3.5,4]
map (\x -> let (m,a) = linlin_muladd (-1) 1 3 4 in x * m + a) [-1,0,1] == [3,3.5,4]

range_hs :: Fractional a => (a, a) -> a -> a Source #

in_range :: Fractional a => a -> (a, a) -> a Source #

flip range_hs. This allows cases such as osc in_range (0,1)

linlin_muladd :: Fractional t => t -> t -> t -> t -> (t, t) Source #

Calculate multiplier and add values for linlin transform. Inputs are: input-min input-max output-min output-max

range_muladd 3 4 == (0.5,3.5)
linlin_muladd (-1) 1 3 4 == (0.5,3.5)
linlin_muladd 0 1 3 4 == (1,3)
linlin_muladd (-1) 1 0 1 == (0.5,0.5)
linlin_muladd (-0.3) 1 (-1) 1

linlin_ma :: Fractional a => SC3_MulAdd a -> a -> a -> a -> a -> a -> a Source #

Map from one linear range to another linear range.

linlin_ma hs_muladd 5 0 10 (-1) 1 == 0

linlin_hs :: Fractional a => (a, a) -> (a, a) -> a -> a Source #

linLin with a more typical haskell argument structure, ranges as pairs and input last.

map (linlin_hs (0,127) (-0.5,0.5)) [0,63.5,127] == [-0.5,0.0,0.5]

sc3_linlin :: Fractional a => a -> a -> a -> a -> a -> a Source #

Map from one linear range to another linear range.

r = [0,0.125,0.25,0.375,0.5,0.625,0.75,0.875,1]
map (\i -> sc3_linlin i (-1) 1 0 1) [-1,-0.75 .. 1] == r

linlin_enum_plain :: (Enum t, Enum u) => t -> u -> t -> u Source #

Given enumeration from dst that is in the same relation as n is from src.

linlin _enum_plain 'a' 'A' 'e' == 'E'
linlin_enum_plain 0 (-50) 16 == -34
linlin_enum_plain 0 (-50) (-1) == -51

linlin_enum :: (Enum t, Enum u) => (t, t) -> (u, u) -> t -> Maybe u Source #

Variant of linlin_enum_plain that requires src and dst ranges to be of equal size, and for n to lie in src.

linlin_enum (0,100) (-50,50) 0x10 == Just (-34)
linlin_enum (-50,50) (0,100) (-34) == Just 0x10
linlin_enum (0,100) (-50,50) (-1) == Nothing

linlin_enum_err :: (Enum t, Enum u) => (t, t) -> (u, u) -> t -> u Source #

Erroring variant.

linlin_eq :: (Eq a, Num a) => (a, a) -> (a, a) -> a -> Maybe a Source #

Variant of linlin that requires src and dst ranges to be of equal size, thus with constraint of Num and Eq instead of Fractional.

linlin_eq (0,100) (-50,50) 0x10 == Just (-34)
linlin_eq (-50,50) (0,100) (-34) == Just 0x10

linlin_eq_err :: (Eq a, Num a) => (a, a) -> (a, a) -> a -> a Source #

Erroring variant.

LinExp

linexp_hs :: Floating a => (a, a) -> (a, a) -> a -> a Source #

Linear to exponential range conversion. Rule is as at linExp Ugen, haskell manner argument ordering. Destination values must be nonzero and have the same sign.

map (floor . linexp_hs (1,2) (10,100)) [0,1,1.5,2,3] == [1,10,31,100,1000]
map (floor . linexp_hs (-2,2) (1,100)) [-3,-2,-1,0,1,2,3] == [0,1,3,10,31,100,316]

lin_exp :: Floating a => a -> a -> a -> a -> a -> a Source #

Variant of linexp_hs with argument ordering as at linExp Ugen.

map (\i -> lin_exp i 1 2 1 3) [1,1.1 .. 2]
map (\i -> floor (lin_exp i 1 2 10 100)) [0,1,1.5,2,3]

sc3_linexp :: (Ord a, Floating a) => a -> a -> a -> a -> a -> a Source #

SimpleNumber.linexp shifts from linear to exponential ranges.

map (sc3_linexp 1 2 1 3) [1,1.1 .. 2]
> [1,1.5,2].collect({|i| i.linexp(1,2,10,100).floor}) == [10,31,100]
map (floor . sc3_linexp 1 2 10 100) [0,1,1.5,2,3] == [10,10,31,100,100]

sc3_explin :: (Ord a, Floating a) => a -> a -> a -> a -> a -> a Source #

SimpleNumber.explin is the inverse of linexp.

map (sc3_explin 10 100 1 2) [10,10,31,100,100]

ExpExp

sc3_expexp :: (Ord a, Floating a) => a -> a -> a -> a -> a -> a Source #

Translate from one exponential range to another.

map (sc3_expexp 0.1 10 4.3 100) [1 .. 10]

LinCurve

sc3_lincurve :: (Ord a, Floating a) => a -> a -> a -> a -> a -> a -> a Source #

Map x from an assumed linear input range (src_l,src_r) to an exponential curve output range (dst_l,dst_r). curve is like the parameter in Env. Unlike with linexp, the output range may include zero.

> (0..10).lincurve(0,10,-4.3,100,-3).round == [-4,24,45,61,72,81,87,92,96,98,100]
let f = round . sc3_lincurve (-3) 0 10 (-4.3) 100
in map f [0 .. 10] == [-4,24,45,61,72,81,87,92,96,98,100]
import Sound.Sc3.Plot 
plotTable (map (\c-> map (sc3_lincurve c 0 1 (-1) 1) [0,0.01 .. 1]) [-6,-4 .. 6])

sc3_curvelin :: (Ord a, Floating a) => a -> a -> a -> a -> a -> a -> a Source #

Inverse of sc3_lincurve.

let f = round . sc3_curvelin (-3) (-4.3) 100 0 10
in map f [-4,24,45,61,72,81,87,92,96,98,100] == [0..10]

PP

double_pp_rm0 :: String -> String Source #

Removes all but the last trailing zero from floating point string.

double_pp :: Int -> Double -> String Source #

The default show is odd, 0.05 shows as 5.0e-2.

unwords (map (double_pp 4) [0.0001,0.001,0.01,0.1,1.0]) == "0.0001 0.001 0.01 0.1 1.0"

real_pp :: Int -> Double -> String Source #

Print as integer if integral, else as real.

unwords (map (real_pp 5) [0.0001,0.001,0.01,0.1,1.0]) == "0.0001 0.001 0.01 0.1 1"

Parser

Optimiser

sum_opt_f :: Num t => (t -> t -> t -> t) -> (t -> t -> t -> t -> t) -> [t] -> t Source #

Non-specialised optimised sum function (3 & 4 element adders).

Sin

sin_taylor_approximation :: Floating a => a -> a Source #

Taylor approximation of sin, (-pi, pi).

import Sound.Sc3.Plot
let xs = [-pi, -pi + 0.05 .. pi] in plot_p1_ln [map sin_taylor_approximation xs, map sin xs]
let xs = [-pi, -pi + 0.05 .. pi] in plot_p1_ln [map (\x -> sin_taylor_approximation x - sin x) xs]

sin_bhaskara_approximation :: Floating a => a -> a Source #

Bhaskara approximation of sin, (0, pi).

import Sound.Sc3.Plot
let xs = [0, 0.05 .. pi] in plot_p1_ln [map sin_bhaskara_approximation xs, map sin xs]
let xs = [0, 0.05 .. pi] in plot_p1_ln [map (\x -> sin_bhaskara_approximation x - sin x) xs]

sin_green_approximation :: Floating a => a -> a Source #

Robin Green, robin_green@playstation.sony.com, (-pi, pi)

import Sound.Sc3.Plot
let xs = [-pi, -pi + 0.05 .. pi] in plot_p1_ln [map sin_green_approximation xs, map sin xs]
let xs = [-pi, -pi + 0.05 .. pi] in plot_p1_ln [map (\x -> sin_green_approximation x - sin x) xs]

sin_adenot_approximation :: Floating a => a -> a Source #

Paul Adenot, (-pi, pi)

import Sound.Sc3.Plot
let xs = [-pi, -pi + 0.05 .. pi] in plot_p1_ln [map sin_adenot_approximation xs, map sin xs]
let xs = [-pi, -pi + 0.05 .. pi] in plot_p1_ln [map (\x -> sin_adenot_approximation x - sin x) xs]