-- | Read and write sound files using hsndfile. module Sound.File.HSndFile where import qualified Data.Vector.Storable as V import Prelude hiding (read) import qualified Sound.File.Decode as D import qualified Sound.File.Sndfile as F import qualified Sound.File.Sndfile.Buffer.Vector as F -- | Sound file meta data. data Header = Header { channelCount :: Int , frameCount :: Int , sampleRate :: Double } deriving (Eq, Show) -- | Duration of sound file in seconds. duration :: Header -> Double duration (Header _ nf sr) = fromIntegral nf / sr -- | Read 'Header' of sound file. header :: FilePath -> IO Header header fn = do h <- F.openFile fn F.ReadMode F.defaultInfo let i = F.hInfo h nc = F.channels i nf = F.frames i sr = F.samplerate i F.hClose h return (Header nc (fromIntegral nf) (fromIntegral sr)) -- | Read 'Header' and audio channel data from sound file. read :: FilePath -> IO (Header, [[Double]]) read fn = do hd <- header fn h <- F.openFile fn F.ReadMode F.defaultInfo let Header nc nf _ = hd ns = nc * nf b <- F.hGetBuffer h ns case b of Just b' -> let e = V.toList (F.fromBuffer b') in return (hd, D.deinterleave nc e) Nothing -> return (hd, [])