| Safe Haskell | None | 
|---|
Sound.File.Sndfile
Contents
Description
Sound.File.Sndfile provides a Haskell interface to the libsndfile library by Erik de Castro Lopo (http://www.mega-nerd.com/libsndfile/).
The API is modeled after the original C API, but type and function identifiers follow Haskell naming conventions.
- type Count = Int
- type Index = Int
- data Format = Format {}
- data  HeaderFormat - = HeaderFormatNone
- | HeaderFormatWav
- | HeaderFormatAiff
- | HeaderFormatAu
- | HeaderFormatRaw
- | HeaderFormatPaf
- | HeaderFormatSvx
- | HeaderFormatNist
- | HeaderFormatVoc
- | HeaderFormatIrcam
- | HeaderFormatW64
- | HeaderFormatMat4
- | HeaderFormatMat5
- | HeaderFormatPvf
- | HeaderFormatXi
- | HeaderFormatHtk
- | HeaderFormatSds
- | HeaderFormatAvr
- | HeaderFormatWavex
- | HeaderFormatSd2
- | HeaderFormatFlac
- | HeaderFormatCaf
- | HeaderFormatWve
- | HeaderFormatOgg
- | HeaderFormatMpc2k
- | HeaderFormatRf64
 
- data  SampleFormat - = SampleFormatNone
- | SampleFormatPcmS8
- | SampleFormatPcm16
- | SampleFormatPcm24
- | SampleFormatPcm32
- | SampleFormatPcmU8
- | SampleFormatFloat
- | SampleFormatDouble
- | SampleFormatUlaw
- | SampleFormatAlaw
- | SampleFormatImaAdpcm
- | SampleFormatMsAdpcm
- | SampleFormatGsm610
- | SampleFormatVoxAdpcm
- | SampleFormatG72132
- | SampleFormatG72324
- | SampleFormatG72340
- | SampleFormatDwvw12
- | SampleFormatDwvw16
- | SampleFormatDwvw24
- | SampleFormatDwvwN
- | SampleFormatFormatDpcm8
- | SampleFormatFormatDpcm16
- | SampleFormatVorbis
 
- data  EndianFormat - = EndianFile
- | EndianLittle
- | EndianBig
- | EndianCpu
 
- defaultFormat :: Format
- data Info = Info {}
- duration :: Info -> Double
- defaultInfo :: Info
- checkFormat :: Info -> Bool
- data Handle
- hInfo :: Handle -> Info
- hIsSeekable :: Handle -> IO Bool
- data  IOMode - = ReadMode
- | WriteMode
- | ReadWriteMode
 
- openFile :: FilePath -> IOMode -> Info -> IO Handle
- getFileInfo :: FilePath -> IO Info
- hFlush :: Handle -> IO ()
- hClose :: Handle -> IO ()
- data SeekMode
- hSeek :: Handle -> SeekMode -> Count -> IO Count
- hSeekRead :: Handle -> SeekMode -> Count -> IO Count
- hSeekWrite :: Handle -> SeekMode -> Count -> IO Count
- class Storable e => Sample e where
- class  Buffer a e  where- fromForeignPtr :: ForeignPtr e -> Int -> Int -> IO (a e)
- toForeignPtr :: a e -> IO (ForeignPtr e, Int, Int)
 
- hGetBuffer :: forall a e. (Sample e, Storable e, Buffer a e) => Handle -> Count -> IO (Maybe (a e))
- hGetContents :: (Sample e, Buffer a e) => Handle -> IO (Info, Maybe (a e))
- readFile :: (Sample e, Buffer a e) => FilePath -> IO (Info, Maybe (a e))
- hPutBuffer :: forall a e. (Sample e, Storable e, Buffer a e) => Handle -> a e -> IO Count
- writeFile :: (Sample e, Buffer a e) => Info -> FilePath -> a e -> IO Count
- data  Exception - = Exception { }
- | UnrecognisedFormat { }
- | SystemError { }
- | MalformedFile { }
- | UnsupportedEncoding { }
 
- data  StringType - = StrTitle
- | StrCopyright
- | StrSoftware
- | StrArtist
- | StrComment
- | StrDate
 
- getString :: Handle -> StringType -> IO (Maybe String)
- setString :: Handle -> StringType -> String -> IO ()
Types
Stream format
Stream format specification, consisting of header, sample and endianness formats.
Not all combinations of header, sample and endianness formats are valid;
 valid combinations can be checked with the checkFormat function.
Constructors
| Format | |
| Fields | |
data HeaderFormat Source
Header format.
Constructors
Instances
data SampleFormat Source
Sample format.
Constructors
Instances
data EndianFormat Source
Endianness.
Constructors
| EndianFile | |
| EndianLittle | |
| EndianBig | |
| EndianCpu | 
Instances
Default 'empty' format, useful when opening files for reading with ReadMode.
Stream info
The Info structure is for passing data between the calling function and
   the library when opening a stream for reading or writing.
Constructors
| Info | |
duration :: Info -> DoubleSource
Return soundfile duration in seconds computed via the Info fields
   frames and samplerate.
Default 'empty' info, useful when opening files for reading with ReadMode.
checkFormat :: Info -> BoolSource
Stream handle operations
hIsSeekable :: Handle -> IO BoolSource
I/O mode.
Constructors
| ReadMode | |
| WriteMode | |
| ReadWriteMode | 
Instances
| Enum IOMode | When opening a file for read ( When opening a file for write ( Every call to  On success, the  | 
| 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.
Constructors
| AbsoluteSeek | |
| RelativeSeek | |
| SeekFromEnd | 
hSeek :: Handle -> SeekMode -> Count -> IO CountSource
The file seek functions work much like 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 Int16 and Int32 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.
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
Values of type Exception are thrown by the library when an error occurs.
Use catch to catch only exceptions of this type.
Constructors
| Exception | |
| Fields | |
| UnrecognisedFormat | |
| Fields | |
| SystemError | |
| Fields | |
| MalformedFile | |
| Fields | |
| UnsupportedEncoding | |
| Fields | |
Header string field access
data StringType Source
Header string field types.
Constructors
| StrTitle | |
| StrCopyright | |
| StrSoftware | |
| StrArtist | |
| StrComment | |
| StrDate | 
Instances
setString :: Handle -> StringType -> String -> IO ()Source
The setString function sets the string data associated with the respective StringType.