hsndfile-0.5.0: Haskell bindings for libsndfile

Sound.File.Sndfile

Contents

Description

Sound.File.Sndfile provides a Haskell interface to the libsndfile library by Erik de Castro Lopo (visit the libraries's website at http://www.mega-nerd.com/libsndfile/). The API is modeled after the original C API, but type and function identifiers follow Haskell naming conventions.

Synopsis

Types

type Count = IntSource

Type for expressing sample counts.

type Index = IntSource

Type for expressing sample indices.

Stream format

data Format Source

Stream format specification, consisting of header, sample and endianness formats.

Not all combinations of header, sample and endianness formats are valid; valid combinamtions can be checked with the checkFormat function.

Instances

defaultFormat :: FormatSource

Default 'empty' format, useful when opening files for reading with ReadMode.

Stream info

data Info Source

The Info structure is for passing data between the calling function and the library when opening a stream for reading or writing.

Constructors

Info 

Fields

frames :: Count

Number of frames in file

samplerate :: Int

Audio sample rate

channels :: Int

Number of channels

format :: Format

Header and sample format

sections :: Int

Number of sections

seekable :: Bool

True when stream is seekable (e.g. local files)

Instances

duration :: Info -> DoubleSource

Return soundfile duration in seconds computed via the Info fields frames and samplerate.

defaultInfo :: InfoSource

Default 'empty' info, useful when opening files for reading with ReadMode.

checkFormat :: Info -> BoolSource

This function allows the caller to check if a set of parameters in the Info struct is valid before calling openFile (WriteMode).

checkFormat returns True if the parameters are valid and False otherwise.

Stream handle operations

data Handle Source

Abstract file handle.

hInfo :: Handle -> InfoSource

Return the stream Info associated with the Handle.

data IOMode Source

I/O mode.

Instances

Enum IOMode

When opening a file for read (ReadMode), the format field should be set to defaultFormat before calling openFile. The only exception to this is the case of RAW files, where the caller has to set the samplerate, channels and format fields to valid values. All other fields of the structure are filled in by the library.

When opening a file for write (WriteMode), the caller must fill in the structure members samplerate, channels, and format.

Every call to openFile should be matched with a call to hClose to free up memory allocated during the call to openFile.

On success, the openFile function returns a Handle which should be passed as the first parameter to all subsequent libsndfile calls dealing with that audio stream. On fail, the openFile function signals an Exception.

Eq IOMode 
Show IOMode 

getFileInfo :: FilePath -> IO InfoSource

Get header format information associated with file.

hFlush :: Handle -> IO ()Source

If the stream is opened with WriteMode or ReadWriteMode, call the operating system's function to force the writing of all file cache buffers to disk. If the file is opened with ReadMode no action is taken.

hClose :: Handle -> IO ()Source

The hClose function closes the stream, deallocates its internal buffers and returns () on success or signals an Exception otherwise.

hSeek :: Handle -> SeekMode -> Count -> IO CountSource

The file seek functions work much like System.IO.hseek with the exception that the non-audio data is ignored and the seek only moves within the audio data section of the file. In addition, seeks are defined in number of (multichannel) frames. Therefore, a seek in a stereo file from the current position forward with an offset of 1 would skip forward by one sample of both channels.

like lseek(), the whence parameter can be any one of the following three values:

  • AbsoluteSeek - The offset is set to the start of the audio data plus offset (multichannel) frames.
  • RelativeSeek - The offset is set to its current location plus offset (multichannel) frames.
  • SeekFromEnd - The offset is set to the end of the data plus offset (multichannel) frames.

Internally, libsndfile keeps track of the read and write locations using separate read and write pointers. If a file has been opened with a mode of ReadWriteMode, calling either hSeekRead or hSeekWrite allows the read and write pointers to be modified separately. hSeek modifies both the read and the write pointer.

Note that the frames offset can be negative and in fact should be when SeekFromEnd is used for the whence parameter.

hSeek will return the offset in (multichannel) frames from the start of the audio data, or signal an error when an attempt is made to seek beyond the start or end of the file.

hSeekRead :: Handle -> SeekMode -> Count -> IO CountSource

Like hSeek, but only the read pointer is modified.

hSeekWrite :: Handle -> SeekMode -> Count -> IO CountSource

Like hSeek, but only the write pointer is modified.

I/O functions

class Storable e => Sample e whereSource

The class Sample is used for polymorphic I/O on a Handle, and is parameterized with the element type that is to be read from a file.

It is important to note that the data type used by the calling program and the data format of the file do not need to be the same. For instance, it is possible to open a 16 bit PCM encoded WAV file and read the data in floating point format. The library seamlessly converts between the two formats on-the-fly; the Haskell interface currently supports reading and writing Double or Float floating point values, as well as Word16 and Word32 integer values.

When converting between integer data and floating point data, the following rules apply: The default behaviour when reading floating point data from a file with integer data is normalisation. Regardless of whether data in the file is 8, 16, 24 or 32 bit wide, the data will be read as floating point data in the range [-1.0, 1.0]. Similarly, data in the range [-1.0, 1.0] will be written to an integer PCM file so that a data value of 1.0 will be the largest allowable integer for the given bit width. This normalisation can be turned on or off using the command interface (implementation missing in Haskell).

hGetSamples and hGetFrames return the number of items read. Unless the end of the file was reached during the read, the return value should equal the number of items requested. Attempts to read beyond the end of the file will not result in an error but will cause the read functions to return less than the number of items requested or 0 if already at the end of the file.

Methods

hGetBuf :: Handle -> Ptr e -> Count -> IO CountSource

Read a buffer of frames.

hPutBuf :: Handle -> Ptr e -> Count -> IO CountSource

Write a buffer of frames.

class Buffer a e whereSource

Buffer class for I/O on soundfile handles.

Methods

fromForeignPtr :: ForeignPtr e -> Int -> Int -> IO (a e)Source

Construct a buffer from a ForeignPtr, a start index and the element count.

toForeignPtr :: a e -> IO (ForeignPtr e, Int, Int)Source

Retrieve from a buffer a ForeignPtr pointing to its data, a start index and an element count.

hGetBuffer :: forall a e. (Sample e, Storable e, Buffer a e) => Handle -> Count -> IO (Maybe (a e))Source

Return an buffer with the requested number of frames of data. The resulting buffer size is equal to the product of the number of frames n and the number of channels in the soundfile.

hGetContents :: (Sample e, Buffer a e) => Handle -> IO (Info, Maybe (a e))Source

Return the contents of a handle open for reading in a single buffer.

readFile :: (Sample e, Buffer a e) => FilePath -> IO (Info, Maybe (a e))Source

Return the contents of a file in a single buffer.

hPutBuffer :: forall a e. (Sample e, Storable e, Buffer a e) => Handle -> a e -> IO CountSource

Write the contents of a buffer to a handle open for writing. Return the number of frames written.

writeFile :: (Sample e, Buffer a e) => Info -> FilePath -> a e -> IO CountSource

Write the contents of a buffer to a file. Return the number of frames written.

Exception handling

data Exception Source

Values of type Exception are thrown by the library when an error occurs.

Use catch to catch only exceptions of this type.

catch

Arguments

:: Exception e 
=> IO a

The computation to run

-> (e -> IO a)

Handler to invoke if an exception is raised

-> IO a 

This is the simplest of the exception-catching functions. It takes a single argument, runs it, and if an exception is raised the "handler" is executed, with the value of the exception passed as an argument. Otherwise, the result is returned as normal. For example:

   catch (readFile f)
         (\e -> do let err = show (e :: IOException)
                   hPutStr stderr ("Warning: Couldn't open " ++ f ++ ": " ++ err)
                   return "")

Note that we have to give a type signature to e, or the program will not typecheck as the type is ambiguous. While it is possible to catch exceptions of any type, see the previous section "Catching all exceptions" for an explanation of the problems with doing so.

For catching exceptions in pure (non-IO) expressions, see the function evaluate.

Note that due to Haskell's unspecified evaluation order, an expression may throw one of several possible exceptions: consider the expression (error "urk") + (1 `div` 0). Does the expression throw ErrorCall "urk", or DivideByZero?

The answer is "it might throw either"; the choice is non-deterministic. If you are catching any type of exception then you might catch either. If you are calling catch with type IO Int -> (ArithException -> IO Int) -> IO Int then the handler may get run with DivideByZero as an argument, or an ErrorCall "urk" exception may be propogated further up. If you call it again, you might get a the opposite behaviour. This is ok, because catch is an IO computation.

Note that the Prelude also exports a function called Prelude.catch with a similar type to Control.Exception.catch, except that the Prelude version only catches the IO and user families of exceptions (as required by Haskell 98).

We recommend either hiding the Prelude version of Prelude.catch when importing Control.Exception:

 import Prelude hiding (catch)

or importing Control.Exception qualified, to avoid name-clashes:

 import qualified Control.Exception as C

and then using C.catch

Header string field access

getString :: Handle -> StringType -> IO (Maybe String)Source

The getString function returns the specificed string from the stream header in the Maybe monad if it exists and Nothing otherwise.

setString :: Handle -> StringType -> String -> IO ()Source

The setString function sets the string data associated with the respective StringType.