module Sound.Sc3.Common.Math.Window where
type Window x = x -> x
type Table x = [x]
data TableFormat = TableClosed | TableOpen | TableGuarded deriving (TableFormat -> TableFormat -> Bool
(TableFormat -> TableFormat -> Bool)
-> (TableFormat -> TableFormat -> Bool) -> Eq TableFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TableFormat -> TableFormat -> Bool
== :: TableFormat -> TableFormat -> Bool
$c/= :: TableFormat -> TableFormat -> Bool
/= :: TableFormat -> TableFormat -> Bool
Eq, Int -> TableFormat -> ShowS
[TableFormat] -> ShowS
TableFormat -> String
(Int -> TableFormat -> ShowS)
-> (TableFormat -> String)
-> ([TableFormat] -> ShowS)
-> Show TableFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TableFormat -> ShowS
showsPrec :: Int -> TableFormat -> ShowS
$cshow :: TableFormat -> String
show :: TableFormat -> String
$cshowList :: [TableFormat] -> ShowS
showList :: [TableFormat] -> ShowS
Show)
window_table :: (Integral n, Fractional a, Enum a) => TableFormat -> n -> Window a -> Table a
window_table :: forall n a.
(Integral n, Fractional a, Enum a) =>
TableFormat -> n -> Window a -> Table a
window_table TableFormat
fmt n
n Window a
f =
let k :: a
k = a
1 a -> Window a
forall a. Fractional a => a -> a -> a
/ (n -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
n a -> Window a
forall a. Num a => a -> a -> a
- (if TableFormat
fmt TableFormat -> TableFormat -> Bool
forall a. Eq a => a -> a -> Bool
== TableFormat
TableClosed then a
1 else a
0))
in Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take (n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (if TableFormat
fmt TableFormat -> TableFormat -> Bool
forall a. Eq a => a -> a -> Bool
== TableFormat
TableGuarded then n
n n -> n -> n
forall a. Num a => a -> a -> a
+ n
1 else n
n)) (Window a -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map Window a
f [a
0, a
k ..])
window_table_closed :: (Integral n, Fractional a, Enum a) => n -> Window a -> Table a
window_table_closed :: forall n a.
(Integral n, Fractional a, Enum a) =>
n -> Window a -> Table a
window_table_closed = TableFormat -> n -> Window a -> Table a
forall n a.
(Integral n, Fractional a, Enum a) =>
TableFormat -> n -> Window a -> Table a
window_table TableFormat
TableClosed
square :: Num a => a -> a
square :: forall a. Num a => a -> a
square a
x = a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x
gaussian :: Floating a => a -> Window a
gaussian :: forall a. Floating a => a -> Window a
gaussian a
theta a
i = a -> a
forall a. Floating a => a -> a
exp (-(a
0.5 a -> a -> a
forall a. Num a => a -> a -> a
* a -> a
forall a. Num a => a -> a
square ((a
i a -> a -> a
forall a. Num a => a -> a -> a
- a
0.5) a -> a -> a
forall a. Fractional a => a -> a -> a
/ (a
theta a -> a -> a
forall a. Num a => a -> a -> a
* a
0.5))))
hann :: Floating a => Window a
hann :: forall a. Floating a => a -> a
hann a
i = a
0.5 a -> a -> a
forall a. Num a => a -> a -> a
* (a
1 a -> a -> a
forall a. Num a => a -> a -> a
- a -> a
forall a. Floating a => a -> a
cos (a
2 a -> a -> a
forall a. Num a => a -> a -> a
* a
forall a. Floating a => a
pi a -> a -> a
forall a. Num a => a -> a -> a
* a
i))
hamming :: Floating a => Window a
hamming :: forall a. Floating a => a -> a
hamming a
i = a
0.54 a -> a -> a
forall a. Num a => a -> a -> a
- a
0.46 a -> a -> a
forall a. Num a => a -> a -> a
* a -> a
forall a. Floating a => a -> a
cos (a
2 a -> a -> a
forall a. Num a => a -> a -> a
* a
forall a. Floating a => a
pi a -> a -> a
forall a. Num a => a -> a -> a
* a
i)
rectangular :: Window a
rectangular :: forall a. Window a
rectangular = a -> a
forall a. Window a
id
sine :: Floating a => Window a
sine :: forall a. Floating a => a -> a
sine a
i = a -> a
forall a. Floating a => a -> a
sin (a
i a -> a -> a
forall a. Num a => a -> a -> a
* a
forall a. Floating a => a
pi)
triangular :: Fractional a => Window a
triangular :: forall a. Fractional a => Window a
triangular a
i = a
2 a -> a -> a
forall a. Num a => a -> a -> a
* (a
0.5 a -> a -> a
forall a. Num a => a -> a -> a
- a -> a
forall a. Num a => a -> a
abs (a
i a -> a -> a
forall a. Num a => a -> a -> a
- a
0.5))
gaussian_table :: (Integral n, Floating b, Enum b) => n -> b -> [b]
gaussian_table :: forall n b. (Integral n, Floating b, Enum b) => n -> b -> [b]
gaussian_table n
n = n -> Window b -> Table b
forall n a.
(Integral n, Fractional a, Enum a) =>
n -> Window a -> Table a
window_table_closed n
n (Window b -> Table b) -> (b -> Window b) -> b -> Table b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Window b
forall a. Floating a => a -> Window a
gaussian
hamming_table :: Int -> [Double]
hamming_table :: Int -> [Double]
hamming_table Int
n = Int -> Window Double -> [Double]
forall n a.
(Integral n, Fractional a, Enum a) =>
n -> Window a -> Table a
window_table_closed Int
n Window Double
forall a. Floating a => a -> a
hamming
hann_table :: Int -> [Double]
hann_table :: Int -> [Double]
hann_table Int
n = Int -> Window Double -> [Double]
forall n a.
(Integral n, Fractional a, Enum a) =>
n -> Window a -> Table a
window_table_closed Int
n Window Double
forall a. Floating a => a -> a
hann
sine_table :: (Integral n, Floating b, Enum b) => n -> [b]
sine_table :: forall n b. (Integral n, Floating b, Enum b) => n -> [b]
sine_table n
n = n -> Window b -> Table b
forall n a.
(Integral n, Fractional a, Enum a) =>
n -> Window a -> Table a
window_table_closed n
n Window b
forall a. Floating a => a -> a
sine
triangular_table :: (Integral n, Fractional b, Enum b) => n -> [b]
triangular_table :: forall n b. (Integral n, Fractional b, Enum b) => n -> [b]
triangular_table n
n = n -> Window b -> Table b
forall n a.
(Integral n, Fractional a, Enum a) =>
n -> Window a -> Table a
window_table_closed n
n Window b
forall a. Fractional a => Window a
triangular