module Examples.Effects.Overdrive where import qualified Prelude import Feldspar import Feldspar.Wrap import Feldspar.Vector import Feldspar.Compiler -- | Generic (not compilable) overdrive function overdrive :: (Numeric a, Ord a) => Vector1 a -> Data a -> Data a -> Vector1 a overdrive x mul bound = map (\x -> x * mul) $ map mapFn x where mapFn elem = (?) (elem > bound) (bound, elseBranch) where elseBranch = (?) (elem < - bound) (-bound,elem) -- | Wrapper to fix the type and size of the vectors in overdrive. overdriveInstance :: Data [Float] -> Data Float -> Data Float -> Data [Float] overdriveInstance x mul bound = desugar $ overdrive (thawVector' 256 x) mul bound -- | Wrapper to fix the type and size of the vectors in overdrive. overdrive_wrapped :: Data' D256 [Float] -> Data Float -> Data Float -> Data [Float] overdrive_wrapped = wrap (overdrive :: Vector1 Float -> Data Float -> Data Float -> Vector1 Float)