A simple example showing usage of hsoundfile and AudioMonad. > module Main where > import Prelude > import qualified Sound.File as SF > import qualified Data.ByteString.Lazy as L > import qualified Sound.Codecs.WaveFile as WF > import qualified Control.Monad.Error as Err > import Data.Binary (encode, decode) > import System.Environment > import Data.List (foldl', transpose) > import Control.Monad.State (execState, evalState) > main = do myArgs <- getArgs This program takes two arguments - the name of an input file and the name of an output file. > let (fName: outName: xs) = myArgs First open the file as a bytestring, then calculate the peak value within it. Err.runErrorT strips the AudioMonad (which is just a Control.Monad.ErrorT) from the computation, leaving just an IO (Either AudioError SF.SoundData), which is ignored > bs <- L.readFile fName > Err.runErrorT $ getMax bs We're re-opening the file to re-process it. This is to allow the GC to collect the [SoundFrame] produced within the getMax function. If we reference the same SndFileCls instance, the entire [SoundFrame] will stay in memory. For small files this isn't an issue, but with large files it can induce thrashing, so it's good practice to re-read the file for each operation (on the audio data). Some knowledge of laziness is required to know when this will help and when it doesn't matter. > bs' <- L.readFile fName > r <- Err.runErrorT $ rewrite bs outName Here, we process the result of runErrorT. If there was some problem with reading the file, it will be reported. > case r of > Right _ -> print "Done" > Left err -> print . show $ err getMax calculates the maximum value within an AudioMonad > getMax :: L.ByteString -> SF.AudioMonad IO SF.SoundData > getMax bs = do First, decode the ByteString to a SndFileCls instance using SF.decodeSoundFileBS We pattern match the output of this function in order to have easy access to the sfInfo in order to display it > sf@(SF.SoundFile sfInfo sfData) <- SF.decodeSoundFileBS bs print the header information > Err.liftIO $ print sfInfo decode the audio data from the sound file and calculate the peak amplitude within it. > as <- SF.getAudioData sf > let maxamp = findMaxAmplitude as display the length of the file (in frames) and the peak amplitude. > Err.liftIO $ print $ (++) "frames of data: " $ show $ SF.lengthInFrames sfData > Err.liftIO $ print $ (++) "Max amplitude is: " $ show maxamp > return maxamp > findMaxAmplitude :: SF.AudioSig -> SF.SoundData > findMaxAmplitude asig = foldl' (foldl' (max . abs)) 0 . SF.audioData $ asig rewrite takes an input ByteString and copies the soundfile to the output filename Although the ByteString could just be copied directly, I am forcing the conversion to demonstrate the functions, as well as test the performance of the codec. At this time, metadata (Author, title, etc.) within the wave file is lost upon conversion, since it's not referenced within the SndFileCls class. > rewrite :: L.ByteString -> String -> SF.AudioMonad IO () > rewrite inBs o = do > sf@(SF.SoundFile sfInfo sfData) <- SF.decodeSoundFileBS inBs > oF <- SF.toWaveFile sf > Err.liftIO $ L.writeFile o . encode $ oF