-- |Datatypes and functions useful for all SoundFile datatypes. module Sound.Base ( -- * Basic Audio data types SampleRate, BitDepth, SoundData, SoundFrame, FrameCount, AudioSig, -- ** SoundFile types and classes SndFileInfo ( .. ), SndFileType ( .. ), SoundFile ( SoundFile ), SndFileCls (getSfInfo, getSfType, fromSndFileCls, getAudioData, getAudioLength), -- * Error handling AudioError (..), AudioMonad, -- * Functions -- ** SoundFile functions lengthInFrames, audioData, makeFrames, interleave, -- ** AudioSig functions makeAudioSignal, appendASig, concatASig ) where import Data.List (transpose) import Control.Parallel.Strategies (rnf, (>|)) import qualified Control.Parallel.Strategies as Strat import qualified Control.Monad.Error as Err -- |The samplerate value, in samples per second. type SampleRate = Integer -- |The bit depth, or word length, of audio data. type BitDepth = Integer -- |A single sample of audio data. Represented normalized to [-1,1] type SoundData = Double -- |One frame of audio data, i.e. the sample value for each channel in the data. type SoundFrame = [SoundData] -- |A position in a data stream, or a length, in frame values. type FrameCount = Integer -- |An audio data stream. This has both the raw audio data (as a list of 'SoundFrame'), -- and the total length, in frames. data AudioSig = AudioSig { -- | The audio data. audioData :: [SoundFrame], -- | length of the audio data. lengthInFrames :: FrameCount } deriving (Eq, Show) -- The total length needs to be passed as well so -- it can be written without forcing all the elements in the list. This is a bit of a -- hack, but I want to see how workable it is. I've also tried it as a monad, which was less successful. -- however, perhaps it should be a tuple. The audioData won't be forced because it's a list, I think... makeAudioSignal :: FrameCount -> [SoundFrame] -> AudioSig makeAudioSignal fc frames = AudioSig frames fc appendASig :: AudioSig -> AudioSig -> AudioSig appendASig a b = AudioSig (concat [audioData a, audioData b]) $ (lengthInFrames a) + (lengthInFrames b) concatASig :: [AudioSig] -> AudioSig concatASig a = AudioSig (concat . map audioData $ a) (sum . map lengthInFrames $ a) {-|Monad to support error handling. -} type AudioMonad m = Err.ErrorT AudioError m data AudioError = NoFormatError -- ^ Audio format information not found in file | UnknownFileTypeError -- ^ File is not in a recognized file format | InvalidBitDepthError BitDepth [BitDepth] -- ^ Specified bit depth is not supported | OtherError String -- ^ unspecified error. instance Err.Error AudioError where noMsg = OtherError "An Audio Error!" strMsg s = OtherError s instance Show AudioError where show (NoFormatError) = "No format information found." show UnknownFileTypeError = "The file does not appear to be a recognized audio file." show (InvalidBitDepthError r vs) = "Requested bit depth " ++ show r ++ " is invalid. Valid bit depths are " ++ show vs show (OtherError s) = s {-|The basic class datatypes that represent soundfiles should support. -} class SndFileCls a where -- | get a 'SndFileInfo' with data for the current SoundFile getSfInfo :: (Monad m) => a -> AudioMonad m SndFileInfo -- | get the type of the underlying instance getSfType :: a -> SndFileType --WavePCM, AIFF, etc -- | Get the AudioSig from the SndFileCls instance. getAudioData :: (Monad m) => a -> AudioMonad m AudioSig -- | convert a SndFileCls instance to the SoundFile type. fromSndFileCls :: (Monad m) => a -> AudioMonad m SoundFile fromSndFileCls sf = do sfi <- getSfInfo sf ad <- getAudioData sf return $ SoundFile sfi ad -- | Get the length of audio data, in frames. getAudioLength :: (Monad m) => a -> AudioMonad m FrameCount getAudioLength a= do ad <- getAudioData a return $ lengthInFrames ad -- | Basic information about the audio data: number of channels, samplerate, and bit depth. data SndFileInfo = SndFileInfo {numChannels :: Int, sr :: SampleRate, bitDepth :: BitDepth} deriving (Eq, Show) instance Strat.NFData SndFileInfo where rnf (SndFileInfo chn sr' bd) = rnf chn >| rnf sr' >| rnf bd {-|The type of the 'SndFileCls' Internal is a special type used for the 'SndFile' class. -} data SndFileType = AIFF | WavePCM | OtherSoundFile String | Internal deriving (Eq, Show) --more to be added as I have time. AIFF not impl. -- |A generic datatype for SoundFile data. data SoundFile = SoundFile { sfFileInfo :: SndFileInfo, sfFileData :: AudioSig } instance SndFileCls SoundFile where getSfInfo = return . sfFileInfo getAudioData = return . sfFileData getSfType _ = Internal instance Eq SoundFile where a == b = sfFileInfo a == sfFileInfo b instance Show SoundFile where show = show . sfFileInfo -- |Convert an interleaved ['SoundData'] (e.g., [l1, r1, l2, r2,...]) to ['SoundFrame'] makeFrames :: Int -> [SoundData] -> [SoundFrame] makeFrames _ [] = [] makeFrames 1 xs = map (:[]) xs makeFrames numChans xs = frames : makeFrames numChans rest where (frames, rest) = splitAt numChans xs -- |Interleave a [['SoundData']] to ['SoundFrame'], e.g. [[l1,l2,l3], [r1,r2,r3]] -> [[l1,r1], [l2,r2], [l3, r3]] interleave :: [[SoundData]] -> [SoundFrame] interleave = transpose