wave-0.2.1: Work with WAVE and RF64 files
Copyright© 2016–present Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Codec.Audio.Wave

Description

This module provides a safe interface that allows us to manipulate WAVE files in their “classic” form as well as files in the RF64 format https://tech.ebu.ch/docs/tech/tech3306-2009.pdf. RF64 adds the ability to store files larger than 4 Gb.

The main feature of the API is that it does not allow the user to duplicate information and introduce errors in that way. For example, the block alignment can be calculated from other parameters of an audio stream, thus we do not store it in the Wave record and do not allow user to specify it. We provide, however, a way to calculate it given a Wave record, see waveBlockAlign. The same is true for the number of channels. The channel mask is a more general means of providing the information about the number of channels and the corresponding speaker positions, thus we only store the channel mask.

Another feature of the library is that it does not dictate how to read or write the audio data. To write the audio data the user passes a callback that receives a Handle as an argument. The size of the written data block is deduced automatically. This makes the library fast and open to different ways of handling the audio data, including via foreign code.

Synopsis

Types

data Wave Source #

Representation of the “essential” information about a WAVE file. Every field in this record is an orthogonal piece of information, so no field can be calculated from other fields. The fields are complemented by the functions that calculate derivative parameters: waveByteRate, waveBitRate, waveBitsPerSample, waveBlockAlign, and waveChannels.

Constructors

Wave 

Fields

Instances

Instances details
Data Wave Source # 
Instance details

Defined in Codec.Audio.Wave

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Wave -> c Wave #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Wave #

toConstr :: Wave -> Constr #

dataTypeOf :: Wave -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Wave) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Wave) #

gmapT :: (forall b. Data b => b -> b) -> Wave -> Wave #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Wave -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Wave -> r #

gmapQ :: (forall d. Data d => d -> u) -> Wave -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Wave -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Wave -> m Wave #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Wave -> m Wave #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Wave -> m Wave #

Read Wave Source # 
Instance details

Defined in Codec.Audio.Wave

Show Wave Source # 
Instance details

Defined in Codec.Audio.Wave

Methods

showsPrec :: Int -> Wave -> ShowS #

show :: Wave -> String #

showList :: [Wave] -> ShowS #

Eq Wave Source # 
Instance details

Defined in Codec.Audio.Wave

Methods

(==) :: Wave -> Wave -> Bool #

(/=) :: Wave -> Wave -> Bool #

Ord Wave Source # 
Instance details

Defined in Codec.Audio.Wave

Methods

compare :: Wave -> Wave -> Ordering #

(<) :: Wave -> Wave -> Bool #

(<=) :: Wave -> Wave -> Bool #

(>) :: Wave -> Wave -> Bool #

(>=) :: Wave -> Wave -> Bool #

max :: Wave -> Wave -> Wave #

min :: Wave -> Wave -> Wave #

data WaveFormat Source #

WaveFormat as a flavor of WAVE file.

Constructors

WaveVanilla

Classic WAVE file, 4 Gb size limitation

WaveRF64

WAVE file with RF64 extension

Instances

Instances details
Data WaveFormat Source # 
Instance details

Defined in Codec.Audio.Wave

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WaveFormat -> c WaveFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WaveFormat #

toConstr :: WaveFormat -> Constr #

dataTypeOf :: WaveFormat -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WaveFormat) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WaveFormat) #

gmapT :: (forall b. Data b => b -> b) -> WaveFormat -> WaveFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WaveFormat -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WaveFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> WaveFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WaveFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WaveFormat -> m WaveFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WaveFormat -> m WaveFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WaveFormat -> m WaveFormat #

Bounded WaveFormat Source # 
Instance details

Defined in Codec.Audio.Wave

Enum WaveFormat Source # 
Instance details

Defined in Codec.Audio.Wave

Read WaveFormat Source # 
Instance details

Defined in Codec.Audio.Wave

Show WaveFormat Source # 
Instance details

Defined in Codec.Audio.Wave

Eq WaveFormat Source # 
Instance details

Defined in Codec.Audio.Wave

Ord WaveFormat Source # 
Instance details

Defined in Codec.Audio.Wave

data SampleFormat Source #

Sample formats with associated bit depth.

Constructors

SampleFormatPcmInt Word16

Unsigned/signed integers, the argument is the number of bits per sample (8 bit and less are encoded as unsigned integers).

SampleFormatIeeeFloat32Bit

Samples are 32 bit floating point numbers.

SampleFormatIeeeFloat64Bit

Samples are 64 bit floating point numbers.

Instances

Instances details
Data SampleFormat Source # 
Instance details

Defined in Codec.Audio.Wave

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SampleFormat -> c SampleFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SampleFormat #

toConstr :: SampleFormat -> Constr #

dataTypeOf :: SampleFormat -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SampleFormat) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SampleFormat) #

gmapT :: (forall b. Data b => b -> b) -> SampleFormat -> SampleFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SampleFormat -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SampleFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> SampleFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SampleFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SampleFormat -> m SampleFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SampleFormat -> m SampleFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SampleFormat -> m SampleFormat #

Read SampleFormat Source # 
Instance details

Defined in Codec.Audio.Wave

Show SampleFormat Source # 
Instance details

Defined in Codec.Audio.Wave

Eq SampleFormat Source # 
Instance details

Defined in Codec.Audio.Wave

Ord SampleFormat Source # 
Instance details

Defined in Codec.Audio.Wave

data SpeakerPosition Source #

Speaker positions clarifying which exactly channels are packed in the WAVE file.

Constructors

SpeakerFrontLeft

Front left

SpeakerFrontRight

Front right

SpeakerFrontCenter

Front center

SpeakerLowFrequency

Sub-woofer

SpeakerBackLeft

Back left

SpeakerBackRight

Back right

SpeakerFrontLeftOfCenter

Front left of center

SpeakerFrontRightOfCenter

Front right of center

SpeakerBackCenter

Back center

SpeakerSideLeft

Side left

SpeakerSideRight

Side right

SpeakerTopCenter

Top center

SpeakerTopFrontLeft

Top front left

SpeakerTopFrontCenter

Top front center

SpeakerTopFrontRight

Top front right

SpeakerTopBackLeft

Top back left

SpeakerTopBackCenter

Top back center

SpeakerTopBackRight

Top back right

Instances

Instances details
Data SpeakerPosition Source # 
Instance details

Defined in Codec.Audio.Wave

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpeakerPosition -> c SpeakerPosition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpeakerPosition #

toConstr :: SpeakerPosition -> Constr #

dataTypeOf :: SpeakerPosition -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SpeakerPosition) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpeakerPosition) #

gmapT :: (forall b. Data b => b -> b) -> SpeakerPosition -> SpeakerPosition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpeakerPosition -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpeakerPosition -> r #

gmapQ :: (forall d. Data d => d -> u) -> SpeakerPosition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpeakerPosition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpeakerPosition -> m SpeakerPosition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpeakerPosition -> m SpeakerPosition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpeakerPosition -> m SpeakerPosition #

Bounded SpeakerPosition Source # 
Instance details

Defined in Codec.Audio.Wave

Enum SpeakerPosition Source # 
Instance details

Defined in Codec.Audio.Wave

Read SpeakerPosition Source # 
Instance details

Defined in Codec.Audio.Wave

Show SpeakerPosition Source # 
Instance details

Defined in Codec.Audio.Wave

Eq SpeakerPosition Source # 
Instance details

Defined in Codec.Audio.Wave

Ord SpeakerPosition Source # 
Instance details

Defined in Codec.Audio.Wave

data WaveException Source #

Exceptions the library can throw.

Constructors

BadFileFormat String FilePath

Format of the given file doesn't look like anything familiar. The first argument is a message explaining what's wrong and the second argument is the file name.

NonDataChunkIsTooLong ByteString FilePath

The library found a chunk which is not a data chunk but is way too long. The first argument is the tag of the chunk and the second argument is the file name.

NonPcmFormatButMissingFact FilePath

The specified format is non-PCM, it's vanilla WAVE, but the “fact” chunk is missing.

Instances

Instances details
Data WaveException Source # 
Instance details

Defined in Codec.Audio.Wave

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WaveException -> c WaveException #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WaveException #

toConstr :: WaveException -> Constr #

dataTypeOf :: WaveException -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WaveException) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WaveException) #

gmapT :: (forall b. Data b => b -> b) -> WaveException -> WaveException #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WaveException -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WaveException -> r #

gmapQ :: (forall d. Data d => d -> u) -> WaveException -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WaveException -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WaveException -> m WaveException #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WaveException -> m WaveException #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WaveException -> m WaveException #

Exception WaveException Source # 
Instance details

Defined in Codec.Audio.Wave

Read WaveException Source # 
Instance details

Defined in Codec.Audio.Wave

Show WaveException Source # 
Instance details

Defined in Codec.Audio.Wave

Eq WaveException Source # 
Instance details

Defined in Codec.Audio.Wave

Derived information

waveByteRate :: Wave -> Word32 Source #

The byte rate of a given Wave file. The byte rate is the number of bytes it takes to encode one second of audio.

waveBitRate :: Wave -> Double Source #

The bit rate in kilobits per second.

waveBitsPerSample :: Wave -> Word16 Source #

The number of significant bits in a sample.

waveBlockAlign :: Wave -> Word16 Source #

The block alignment of samples as the number of bits per sample (rounded towards the next multiplier of 8 if necessary) multiplied by the number of channels. This is how many bytes it takes to encode a single multi-channel sample.

waveChannels :: Wave -> Word16 Source #

The total number of channels present in the audio stream.

waveDuration :: Wave -> Double Source #

The duration in seconds.

Common speaker configurations

speakerMono :: Set SpeakerPosition Source #

Front center (C).

speakerStereo :: Set SpeakerPosition Source #

Front left (L), front right (R).

speakerQuad :: Set SpeakerPosition Source #

L, R, back left (Lb), back right (Rb).

speakerSurround :: Set SpeakerPosition Source #

Surround: L, R, front center (C), back center (Cb).

speaker5_1 :: Set SpeakerPosition Source #

L, R, C, Lb, Rb, low frequency (LFE).

speaker7_1 :: Set SpeakerPosition Source #

L, R, C, Lb, Rb, front left-of-center, front right-of-center, LFE.

speaker5_1Surround :: Set SpeakerPosition Source #

L, R, C, side left (Ls), side right (Rs), LFE.

speaker7_1Surround :: Set SpeakerPosition Source #

L, R, C, Lb, Rb, Ls, Rs, LFE.

Reading

readWaveFile Source #

Arguments

:: MonadIO m 
=> FilePath

Location of file to read

-> m Wave 

Read a Wave record from a WAVE file found at given path. This action throws WaveException if the file is malformed and cannot be read.

Vanilla WAVE and RF64 files are supported. The format is detected automatically from the contents of the file, not by extension.

Only PCM with samples in the form of integers or floats are supported, see SampleFormat.

Finally, if “fmt” chunk is not extensible, we try to guess the channel mask from the number of channels alone, here is how:

  • 1 channel: front center (C)
  • 2 channels: front left (L), front right (R)
  • 3 channels: L, R, C
  • 4 channels: L, R, back left (Lb), back right (Rb)
  • 5 channels: L, R, C, Lb, Rb
  • 6 channels: L, R, C, LFE, Lb, Rb
  • 7 channels: L, R, C, LFE, back center (Cb), side left (Ls), side right (Rs)
  • 8 channels: L, R, C, LFE, Lb, Rb, Ls, Rs
  • N channels: first N items are taken from [minBound..maxBound] of SpeakerPositions

Writing

writeWaveFile Source #

Arguments

:: MonadIO m 
=> FilePath

Where to save the file

-> Wave

Parameters of the WAVE file

-> (Handle -> IO ())

Callback that will be used to write WAVE data

-> m () 

Write a WAVE file. The waveFileFormat value specifies in which of the supported formats the file should be written. The action uses the provided callback to write WAVE audio data. waveDataOffset and waveDataSize from Wave are ignored, instead the values are inferred dynamically after using the callback. Further, the function takes care of the requirement that WAVE data should end on an “even byte boundary”. The pad byte is written if necessary and included in the data size.

The waveSamplesTotal field will be inferred, so the provided value is not used.

If Wave specifies the floating point sample format, the “fact” chunk is automatically generated and written (the chunk is required for all non-PCM formats by the spec), but only for vanilla WAVE.