hommage-0.0.5: Haskell Offline Music Manipulation And Generation EDSLSource codeContentsIndex
Sound.Hommage.Sample
Contents
Sample Datastructure
File Operations
Pitching, Playing and Scratching
Transforming Samples
Filter and Fourier Coeffs
Playing a Sample
Array functions
Synopsis
data Sample a
arraySample :: Sample a -> IOArray Int a
sizeSample :: Sample a -> Int
newSample :: Int -> a -> IO (Sample a)
newSampleFromList :: [a] -> IO (Sample a)
openWavSample :: FilePath -> IO (Either (Sample Mono) (Sample Stereo))
saveWavSampleMono :: FilePath -> Sample Double -> IO ()
saveWavSampleStereo :: FilePath -> Sample Stereo -> IO ()
pitchWavSignal :: FilePath -> [Double] -> Signal
scratchWavSignal :: FilePath -> [Double] -> Signal
playSample :: Sample a -> [a]
pitchSample :: Fractional a => Sample a -> [Double] -> [a]
scratchSample :: Fractional a => Sample a -> [Double] -> [a]
playCoeffs :: Coeffs -> [Complex Double]
mapSample :: (a -> b) -> Sample a -> IO (Sample b)
foldlSample :: Sample a -> (b -> a -> b) -> b -> IO b
updateSample :: Sample a -> (a -> a) -> IO ()
normaliseSample :: (Ord a, Fractional a) => Sample a -> IO ()
fadeinoutSample :: Fractional a => (Int, Int) -> Sample a -> IO ()
stretchSample :: Fractional a => Int -> Sample a -> IO (Sample a)
data Coeffs
arrayCoeffs :: Coeffs -> IOArray Int CoeffArr
sizeCoeffs :: Coeffs -> Int
wavesizeCoeffs :: Coeffs -> Int
syntheseSample :: Coeffs -> IO (Sample Mono)
analyseSample :: Sample Mono -> IO Coeffs
filterCoeffs :: IO (CoeffMap ()) -> Coeffs -> IO Coeffs
mkPlayCoeffs :: Coeffs -> IO (IO (Maybe (Complex Double)))
readCoeffs :: Coeffs -> Int -> Int -> IO (Complex Double)
writeCoeffs :: Coeffs -> Int -> Int -> Complex Double -> IO ()
mkTriggerSample :: Sample a -> a -> IO (Bool -> IO a)
mkPlaySample :: Sample a -> IO (IO (Maybe a))
mkScratchSample :: Fractional a => Sample a -> IO (Double -> IO a)
mkPitchSample :: Fractional a => Sample a -> IO (Double -> IO (Maybe a))
interpolArray :: (Fractional a, MArray array a IO) => array Int a -> Int -> Double -> IO a
mkLoopArray :: (Fractional a, MArray arr a IO) => arr Int a -> Int -> IO (Double -> IO a)
mkPlayArray :: (Fractional a, MArray arr a IO) => arr Int a -> Int -> IO (Double -> IO (Maybe a))
Sample Datastructure
data Sample a Source
arraySample :: Sample a -> IOArray Int aSource
sizeSample :: Sample a -> IntSource
newSample :: Int -> a -> IO (Sample a)Source
newSampleFromList :: [a] -> IO (Sample a)Source
File Operations
openWavSample :: FilePath -> IO (Either (Sample Mono) (Sample Stereo))Source
saveWavSampleMono :: FilePath -> Sample Double -> IO ()Source
saveWavSampleStereo :: FilePath -> Sample Stereo -> IO ()Source
Pitching, Playing and Scratching
pitchWavSignal :: FilePath -> [Double] -> SignalSource
Open a Wav-File, but play it with variable (positive) speed/ frequency.
scratchWavSignal :: FilePath -> [Double] -> SignalSource
Open a Wav-File, but play it with variable (positive and/or negative) speed/ frequency. Backward playing is possible.
playSample :: Sample a -> [a]Source
Creates a finite list with the content of the Sample.
pitchSample :: Fractional a => Sample a -> [Double] -> [a]Source
Creates a list with the content of the Sample, but played with variable speed/frequency.
scratchSample :: Fractional a => Sample a -> [Double] -> [a]Source
Creates a list with the content of the Sample, but played with variable speed/frequency, backward playing possible.
playCoeffs :: Coeffs -> [Complex Double]Source
Creates a list with the content of Coeffs (a representation of the fourier coefficients of a Sample).
Transforming Samples
mapSample :: (a -> b) -> Sample a -> IO (Sample b)Source
foldlSample :: Sample a -> (b -> a -> b) -> b -> IO bSource
updateSample :: Sample a -> (a -> a) -> IO ()Source
normaliseSample :: (Ord a, Fractional a) => Sample a -> IO ()Source
fadeinoutSample :: Fractional a => (Int, Int) -> Sample a -> IO ()Source
stretchSample :: Fractional a => Int -> Sample a -> IO (Sample a)Source
Filter and Fourier Coeffs
data Coeffs Source
arrayCoeffs :: Coeffs -> IOArray Int CoeffArrSource
sizeCoeffs :: Coeffs -> IntSource
wavesizeCoeffs :: Coeffs -> IntSource
syntheseSample :: Coeffs -> IO (Sample Mono)Source
analyseSample :: Sample Mono -> IO CoeffsSource
filterCoeffs :: IO (CoeffMap ()) -> Coeffs -> IO CoeffsSource
mkPlayCoeffs :: Coeffs -> IO (IO (Maybe (Complex Double)))Source
readCoeffs :: Coeffs -> Int -> Int -> IO (Complex Double)Source
usage: readCoeffs obj nrOfCoeffarr nrOfCoefficient
writeCoeffs :: Coeffs -> Int -> Int -> Complex Double -> IO ()Source
Playing a Sample
mkTriggerSample :: Sample a -> a -> IO (Bool -> IO a)Source
mkPlaySample :: Sample a -> IO (IO (Maybe a))Source
mkScratchSample :: Fractional a => Sample a -> IO (Double -> IO a)Source
mkPitchSample :: Fractional a => Sample a -> IO (Double -> IO (Maybe a))Source
Array functions
interpolArray :: (Fractional a, MArray array a IO) => array Int a -> Int -> Double -> IO aSource
mkLoopArray :: (Fractional a, MArray arr a IO) => arr Int a -> Int -> IO (Double -> IO a)Source
mkPlayArray :: (Fractional a, MArray arr a IO) => arr Int a -> Int -> IO (Double -> IO (Maybe a))Source
Produced by Haddock version 2.4.2