Skip to content

Instantly share code, notes, and snippets.

@ion1
Last active October 10, 2016 21:10
Show Gist options
  • Save ion1/96c8a9652d1bffa74846f30c41925ab8 to your computer and use it in GitHub Desktop.
Save ion1/96c8a9652d1bffa74846f30c41925ab8 to your computer and use it in GitHub Desktop.
Biquad
{-# LANGUAGE FlexibleContexts #-}
import Control.Monad.State
import Test.QuickCheck
main = do
print $ runBiquad' 1 0 0 (-1) (-1) [1,0,0,0,0,0,0,0,0,0,0,0]
quickCheck $ \xs -> (dif . int) xs == xs
&& (int . dif) xs == xs
&& dif2 xs == (dif . dif) xs
&& int2 xs == (int . int) xs
`const` (xs :: [Integer])
print $ dif [0..10]
print $ (int . dif) [0..10]
print $ dif2 [0..10]
print $ (int2 . dif2) [0..10]
quickCheck $ \a b c d e xs ->
runBiquad' a b c d e xs == runBiquad a b c d e xs
`const` (xs :: [Integer])
dif, dif2, int, int2 :: Num n => [n] -> [n]
dif = runBiquad' 1 (-1) 0 0 0
dif2 = runBiquad' 1 (-2) 1 0 0
int = runBiquad' 1 0 0 (-1) 0
int2 = runBiquad' 1 0 0 (-2) 1
runBiquad a b c d e = flip evalState (0,0,0,0) . traverse (biquad a b c d e)
biquad a b c d e x0 = do
(x1,x2,y1,y2) <- get
let y0 = a*x0 + b*x1 + c*x2 - d*y1 - e*y2
y0 <$ put (x0,x1,y0,y1)
-- Equivalent, less state to store.
runBiquad' a b c d e = flip evalState (0,0) . traverse (biquad' a b c d e)
biquad' a b c d e x0 = do
(w1,w2) <- get
let w0 = x0 - d*w1 - e*w2
a*w0 + b*w1 + c*w2 <$ put (w0,w1)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment