module Examples.Effects.ShiftByOneOctave where import qualified Prelude import Feldspar import Feldspar.Wrap import Feldspar.Vector import Feldspar.Compiler -- | Generic (not compilable) algorithm to double the frequency of a signal. -- This is an approximate solution without using FFT. shiftByOneOctave :: (Fraction a) => Vector1 a -> Vector1 a shiftByOneOctave inp = half ++ half where half = everySecond $ map avg $ zip inp $ tail inp everySecond xs = indexed (length xs `div` 2) $ \idx -> xs ! (2*idx) avg (x,y) = (x + y) / 2 -- | Wrapper to fix the type and size of the vectors in shiftByOneOctave. shiftByOneOctaveInstance :: Data [Float] -> Data [Float] shiftByOneOctaveInstance input = desugar $ shiftByOneOctave input' where input' = thawVector' 256 input -- | Wrapper to fix the type and size of the vectors in shiftByOneOctave. shiftByOneOctave_wrapped :: Data' D256 [Float] -> Data [Float] shiftByOneOctave_wrapped = wrap (shiftByOneOctave :: Vector1 Float -> Vector1 Float)