repa-sndfile-3.2.3.3: Reading and writing sound files with repa arrays

Portabilitynon-portable
Stabilityexperimental
Maintainer8c6794b6@gmail.com
Safe HaskellNone

Data.Array.Repa.IO.Sndfile

Contents

Description

Read and write audio file with repa arrays using libsndfile via hsndfile. Note that this module re-exports header related types from hsndfile.

For more info about supported format, visit libsndfile web site:

Synopsis

Examples

Read "in.wav", write to "out.wav" with same format.

 module Main where

 import Data.Array.Repa
   ((:.)(..), Array, Z(..), DIM2, computeP, fromFunction)
 import Data.Array.Repa.Repr.ForeignPtr (F)
 import Data.Array.Repa.IO.Sndfile

 main :: IO ()
 main = do
   (i, a) <- readSF "in.wav" :: IO (Info, Array F DIM2 Double)
   writeSF "out.wav" i a

Write 440hz sine wave for 3 seconds to monaural file "sin440.wav".

 sin440 :: IO ()
 sin440 = do
   let dur = 3; freq = 440; sr = 48000
       hdr = wav16 {samplerate = sr, frames = sr * dur}
       sig = fromFunction (Z :. 1 :. dur * sr) $ \(_ :. _ :. i) ->
         sin (fromIntegral i * freq * pi * 2 / fromIntegral sr)
   sig' <- computeP sig :: IO (Array F DIM2 Double)
   writeSF "sin440.wav" hdr sig'

Write 440hz sine wave to channel 0, 880hz sine wave to channel 1, for 3 seconds to stereo file "sin440and880.wav".

 sin440and880 :: IO ()
 sin440and880 = do
     let dur = 3; freq1 = 440; freq2 = 880; sr = 480000
         hdr = wav16 {samplerate = sr, channels = 2, frames = sr * dur * 2}
         gen f i = sin (fromIntegral i * f * pi * 2 / fromIntegral sr)
         sig = fromFunction (Z :. 2 :. dur * sr) $ \(_ :. c :. i) ->
             case c of
                 0 -> gen freq1 i
                 1 -> gen freq2 i
                 _ -> 0
     sig' <- computeP sig :: IO (Array F DIM2 Double)
     writeSF "sin440and880.wav" hdr sig'

Sound file reader and writer

readSF :: forall a r. (Sample a, Source r a, Target r a, Buffer (Array F DIM1) a) => FilePath -> IO (Info, Array r DIM2 a)Source

Read sound file from given path.

Returns a tuple of Info and array containing the samples of sound file. Returned pair contains sound file information and array which is indexed with channel number and frame. Info could used later for writing sound file.

writeSF :: forall a r. (Sample a, Source r a, Buffer (Array r DIM1) a, Target r a) => FilePath -> Info -> Array r DIM2 a -> IO ()Source

Write array contents to sound file with given header information.

Expecting an array indexed with channel and frame, as returned from readSF. i.e. 2-dimensional array with its contents indexed with channel.

withSF :: forall a b r. (Sample a, Target r a, Source r a) => FilePath -> (Info -> Array r DIM2 a -> IO b) -> IO bSource

Wrapper for invoking array with reading sound file.

Performs given action using sound file info and samples as arguments.

Sound file headers (re-exports from hsndfile)

data 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 

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

data 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.

Instances

type Count = Int

Type for expressing sample counts.

Utils

toMC :: (Monad m, Source r1 e, Source r2 e, Target r2 e) => Int -> Array r1 DIM1 e -> m (Array r2 DIM2 e)Source

Converts vector signal to multi channel signal.

fromMC :: (Source r1 e, Source r2 e, Target r2 e, Monad m) => Array r1 DIM2 e -> m (Array r2 DIM1 e)Source

Converts multi channel signal to vector signal.

wav16 :: InfoSource

16 bit MS wave, single channel, sampling rate = 48000.

wav32 :: InfoSource

32 bit MS wave, single channel, sampling rate = 48000.