module Synthesizer.Utility where
import qualified Algebra.Module as Module
import qualified Algebra.RealField as RealField
import qualified Algebra.Field as Field
import System.Random (Random, RandomGen, randomRs, )
import Prelude ()
import PreludeBase
import NumericPrelude
viewListL :: [a] -> Maybe (a, [a])
viewListL [] = Nothing
viewListL (x:xs) = Just (x,xs)
viewListR :: [a] -> Maybe ([a], a)
viewListR =
foldr (\x -> Just . maybe ([],x) (mapFst (x:))) Nothing
nest :: Int -> (a -> a) -> a -> a
nest 0 _ x = x
nest n f x = f (nest (n1) f x)
mapPair :: (a -> c, b -> d) -> (a,b) -> (c,d)
mapPair ~(f,g) ~(x,y) = (f x, g y)
mapFst :: (a -> c) -> (a,b) -> (c,b)
mapFst f ~(x,y) = (f x, y)
mapSnd :: (b -> d) -> (a,b) -> (a,d)
mapSnd g ~(x,y) = (x, g y)
fst3 :: (a,b,c) -> a
fst3 (a,_,_) = a
snd3 :: (a,b,c) -> b
snd3 (_,b,_) = b
thd3 :: (a,b,c) -> c
thd3 (_,_,c) = c
swap :: (a,b) -> (b,a)
swap (x,y) = (y,x)
common :: (Eq a) => String -> a -> a -> a
common errorMsg x y =
if x == y
then x
else error errorMsg
fwrap :: RealField.C a => (a,a) -> a -> a
fwrap (lo,hi) x = lo + fmod (xlo) (hilo)
fmod :: RealField.C a => a -> a -> a
fmod x y = fraction (x/y) * y
fmodAlt :: RealField.C a => a -> a -> a
fmodAlt x y = x fromInteger (floor (x/y)) * y
propFMod :: RealField.C a => a -> a -> Bool
propFMod x y =
fmod x y == fmodAlt x y
affineComb :: (Module.C t y) => t -> (y,y) -> y
affineComb phase (x0,x1) = x0 + phase *> (x1x0)
balanceLevel :: (Field.C y) =>
y -> [y] -> [y]
balanceLevel center xs =
let d = center sum xs / fromIntegral (length xs)
in map (d+) xs
randomRsBalanced :: (RandomGen g, Random y, Field.C y) =>
g -> Int -> y -> y -> [y]
randomRsBalanced g n center width =
balanceLevel center (take n $ randomRs (zero,width) g)
clip :: Ord a => a -> a -> a -> a
clip lower upper = max lower . min upper