{-| Enable reading and writing of SoundFiles. This module defines several datatypes for multiple audio file formats. Each datatype is an instance of Data.Binary, enabling lazy conversion to and from Lazy Bytestrings using the decodeSoundFileBS function. The different soundfile datatypes are generally not used directly, but are converted to the generic SoundFile type. -} module Sound.File ( module Sound.Base, -- * Generic functions decodeSoundFileBS, decodeSoundFileHinted, getType, getTypeFromName, -- * Format-specific functions -- ** Wave format WF.toWaveFile ) where import Char (toUpper) import qualified System.FilePath as FP import qualified Data.ByteString.Lazy as L import Data.ByteString.Lazy (ByteString) import Data.Binary (decode) import qualified Control.Monad.Error as Err import Sound.Base import Sound.Codecs.WaveFile (isWaveFile, WaveFile) import qualified Sound.Codecs.WaveFile as WF -- |Decode a Lazy ByteString to a SoundFile. This should be used instead of Data.Binary decode -- to make sure that the correct file format is used. decodeSoundFileBS :: Monad m => ByteString -> AudioMonad m SoundFile decodeSoundFileBS bs = do t <- getType bs case t of WavePCM -> fromSndFileCls (decode bs :: WaveFile) _ -> Err.throwError UnknownFileTypeError -- |Attempt to decode a soundfile as the specified type. Return Nothing on failure. -- This function may be faster than using decodeSoundFileBS if the type is known. decodeSoundFileHinted :: Monad m => SndFileType -> ByteString -> AudioMonad m SoundFile decodeSoundFileHinted hintSf bs = case hintSf of WavePCM -> fromSndFileCls (decode bs :: WaveFile) _ -> decodeSoundFileBS bs -- |Find the SndFileType of a ByteString. -- This function assumes that at most the file will match one format. If more than one format matches, -- the first found will be the format used. getType :: Monad m => ByteString -> AudioMonad m SndFileType getType bs = case (theNum) of 1 -> return WavePCM _ -> Err.throwError UnknownFileTypeError where wave :: (Integer, Bool) wave = (1, isWaveFile bs) matchList = filter (\(_,y) -> y) $ [wave] (theNum, _) = head matchList {-|Attempt to guess the SndFileType from the extension of the file. This does not check that the file actually is valid data. -} getTypeFromName :: (Monad m) => FP.FilePath -> AudioMonad m SndFileType getTypeFromName fName = case (map toUpper (FP.takeExtension fName)) of "WAV" -> return WavePCM "WAVE" -> return WavePCM "AIF" -> return AIFF "AIFF" -> return AIFF _ -> Err.throwError UnknownFileTypeError