module Sound.Sc3.Common.Math.Interpolate where
import Sound.Sc3.Common.Math
type Interpolation_f t = t -> t -> t -> t
interpolate :: (Num t,Ord t) => Interpolation_f t -> (t,t) -> t -> t
interpolate :: forall t. (Num t, Ord t) => Interpolation_f t -> (t, t) -> t -> t
interpolate Interpolation_f t
f (t
l,t
r) t
x = if t
x forall a. Ord a => a -> a -> Bool
< t
0 then t
l else if t
x forall a. Ord a => a -> a -> Bool
> t
1 then t
r else Interpolation_f t
f t
l t
r t
x
step :: Interpolation_f t
step :: forall t. Interpolation_f t
step t
_ t
x1 t
_ = t
x1
linear :: Num t => Interpolation_f t
linear :: forall t. Num t => Interpolation_f t
linear t
x0 t
x1 t
t = t
t forall a. Num a => a -> a -> a
* (t
x1 forall a. Num a => a -> a -> a
- t
x0) forall a. Num a => a -> a -> a
+ t
x0
exponential :: Floating t => Interpolation_f t
exponential :: forall t. Floating t => Interpolation_f t
exponential t
x0 t
x1 t
t = t
x0 forall a. Num a => a -> a -> a
* ((t
x1 forall a. Fractional a => a -> a -> a
/ t
x0) forall a. Floating a => a -> a -> a
** t
t)
exponential_0 :: (Eq t,Floating t) => Interpolation_f t
exponential_0 :: forall t. (Eq t, Floating t) => Interpolation_f t
exponential_0 t
x0 t
x1 =
let epsilon :: t
epsilon = t
1e-6
x0' :: t
x0' = if t
x0 forall a. Eq a => a -> a -> Bool
== t
0 then t
epsilon forall a. Num a => a -> a -> a
* forall a. Num a => a -> a
signum t
x1 else t
x0
in forall t. Floating t => Interpolation_f t
exponential t
x0' t
x1
exponential_lin :: (Eq t,Floating t) => Interpolation_f t
exponential_lin :: forall t. (Eq t, Floating t) => Interpolation_f t
exponential_lin t
x0 t
x1 t
t = forall t. Num t => Interpolation_f t
linear t
x0 t
x1 (forall t. (Eq t, Floating t) => Interpolation_f t
exponential_0 t
0 t
1 t
t)
sine :: Floating t => Interpolation_f t
sine :: forall t. Floating t => Interpolation_f t
sine t
x0 t
x1 t
t =
let t' :: t
t' = - forall a. Floating a => a -> a
cos (forall a. Floating a => a
pi forall a. Num a => a -> a -> a
* t
t) forall a. Num a => a -> a -> a
* t
0.5 forall a. Num a => a -> a -> a
+ t
0.5
in forall t. Num t => Interpolation_f t
linear t
x0 t
x1 t
t'
welch :: (Ord t, Floating t) => Interpolation_f t
welch :: forall t. (Ord t, Floating t) => Interpolation_f t
welch t
x0 t
x1 t
t =
if t
x0 forall a. Ord a => a -> a -> Bool
< t
x1
then t
x0 forall a. Num a => a -> a -> a
+ (t
x1 forall a. Num a => a -> a -> a
- t
x0) forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
sin (forall a. Floating a => a
half_pi forall a. Num a => a -> a -> a
* t
t)
else t
x1 forall a. Num a => a -> a -> a
- (t
x1 forall a. Num a => a -> a -> a
- t
x0) forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
sin (forall a. Floating a => a
half_pi forall a. Num a => a -> a -> a
- (forall a. Floating a => a
half_pi forall a. Num a => a -> a -> a
* t
t))
curve :: (Ord t, Floating t) => t -> Interpolation_f t
curve :: forall t. (Ord t, Floating t) => t -> Interpolation_f t
curve t
c t
x0 t
x1 t
t =
if forall a. Num a => a -> a
abs t
c forall a. Ord a => a -> a -> Bool
< t
0.0001
then forall t. Num t => Interpolation_f t
linear t
x0 t
x1 t
t
else let d :: t
d = t
1 forall a. Num a => a -> a -> a
- forall a. Floating a => a -> a
exp t
c
n :: t
n = t
1 forall a. Num a => a -> a -> a
- forall a. Floating a => a -> a
exp (t
t forall a. Num a => a -> a -> a
* t
c)
in t
x0 forall a. Num a => a -> a -> a
+ (t
x1 forall a. Num a => a -> a -> a
- t
x0) forall a. Num a => a -> a -> a
* (t
nforall a. Fractional a => a -> a -> a
/t
d)
squared :: Floating t => Interpolation_f t
squared :: forall t. Floating t => Interpolation_f t
squared t
x0 t
x1 t
t =
let x0' :: t
x0' = forall a. Floating a => a -> a
sqrt t
x0
x1' :: t
x1' = forall a. Floating a => a -> a
sqrt t
x1
l :: t
l = forall t. Num t => Interpolation_f t
linear t
x0' t
x1' t
t
in t
l forall a. Num a => a -> a -> a
* t
l
cubed :: Floating t => Interpolation_f t
cubed :: forall t. Floating t => Interpolation_f t
cubed t
x0 t
x1 t
t =
let x0' :: t
x0' = t
x0 forall a. Floating a => a -> a -> a
** (t
1forall a. Fractional a => a -> a -> a
/t
3)
x1' :: t
x1' = t
x1 forall a. Floating a => a -> a -> a
** (t
1forall a. Fractional a => a -> a -> a
/t
3)
l :: t
l = forall t. Num t => Interpolation_f t
linear t
x0' t
x1' t
t
in t
l forall a. Num a => a -> a -> a
* t
l forall a. Num a => a -> a -> a
* t
l
hold :: (Num t,Ord t) => Interpolation_f t
hold :: forall t. (Num t, Ord t) => Interpolation_f t
hold t
x0 t
x1 t
t = if t
t forall a. Ord a => a -> a -> Bool
>= t
1 then t
x1 else t
x0
fader :: (Num t,Ord t) => Interpolation_f t
fader :: forall t. (Num t, Ord t) => Interpolation_f t
fader t
x0 t
x1 t
t =
let rng :: t
rng = t
x1 forall a. Num a => a -> a -> a
- t
x0
sqr :: a -> a
sqr a
i = a
i forall a. Num a => a -> a -> a
* a
i
in forall a. Num a => a -> a
sqr (if t
rng forall a. Ord a => a -> a -> Bool
> t
0 then t
t else t
1 forall a. Num a => a -> a -> a
- (t
1 forall a. Num a => a -> a -> a
- t
t)) forall a. Num a => a -> a -> a
* t
rng forall a. Num a => a -> a -> a
+ t
x0