Skip to content

Commit

Permalink
Audio.Types: added multi-channel and error handling
Browse files Browse the repository at this point in the history
- support for multi-channel audio processing through the `MultiChaextend audio types
- error handling via `AudioError`
- `AudioChannel` class to manage gain and pan operations
  • Loading branch information
Bernardo Barros committed Nov 29, 2024
1 parent 180ff2e commit 953e6c2
Showing 1 changed file with 64 additions and 90 deletions.
154 changes: 64 additions & 90 deletions src/Euterpea/IO/Audio/Types.hs
Original file line number Diff line number Diff line change
@@ -1,56 +1,40 @@
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}

module Euterpea.IO.Audio.Types where

import Control.Arrow.ArrowP
import Control.SF.SF
import Data.Maybe (fromMaybe)

-- | The 'Clock' class is used to define types that can provide a sampling rate.
class Clock p where
-- | Returns the sampling rate for the given clock type.
--
-- Example:
-- >>> rate AudRate
-- 44100.0
rate :: p -> Double

{- | An instance of 'Clock' for 'AudRate', with a fixed sampling rate.
Audio rate often uses a standard of 44100 Hz, suitable for CD-quality audio.
-}
data AudRate
data CtrRate

instance Clock AudRate where
rate :: AudRate -> Double
rate _ = 44100
rate _ = 44100 -- Audio rate (44100 Hz)

{- | An instance of 'Clock' for 'CtrRate', with a lower sampling rate.
Control rate is usually much lower than audio rate; here it is set to 4410 Hz.
-}
instance Clock CtrRate where
rate :: CtrRate -> Double
rate _ = 4410

-- | 'AudRate' represents an audio rate clock, typically used for audio signals.
data AudRate

-- | 'CtrRate' represents a control rate clock, typically used for control signals.
data CtrRate
rate _ = 4410 -- Control rate (4410 Hz)

{- | 'Frequency' is a newtype wrapper for Double, representing frequency values in Hertz.
It derives useful numeric and display properties automatically.
-- | Represents various types of audio processing errors
data AudioError
= InvalidFrequency Double -- ^ Frequency outside valid range (20Hz-20kHz)
| InvalidSampleRate Double -- ^ Sample rate outside valid range (1Hz-192kHz)
| InvalidPan Double -- ^ Pan outside valid range (-1 to 1)
deriving (Show, Eq)

Example:
>>> let f = Frequency 440.0
>>> getFrequency f
440.0
-}
newtype Frequency = Frequency {getFrequency :: Double}
deriving (Show, Eq, Ord, Num, Fractional, Floating)

{- | The 'ToFrequency' class is for types that can be converted to a 'Frequency'.
This allows different representations of frequency to be standardized.
-}
class ToFrequency a where
-- | Converts a value to a 'Frequency'.
toFrequency :: a -> Frequency
Expand All @@ -61,77 +45,67 @@ instance ToFrequency Double where
instance ToFrequency Frequency where
toFrequency = id

{- | 'SampleRate' is a newtype wrapper for Double, representing sample rates in Hertz.
Example:
>>> let sr = SampleRate 48000.0
>>> getSampleRate sr
48000.0
-}
newtype SampleRate = SampleRate {getSampleRate :: Double}
deriving (Show, Eq, Ord, Num)

{- | Type synonym for a signal function with an audio rate clock.
Represents signal processing functions that operate at audio rate.
-}
type AudSF a b = SigFun AudRate a b

{- | Type synonym for a signal function with a control rate clock.
Represents signal processing functions that operate at control rate.
-}
type CtrSF a b = SigFun CtrRate a b

{- | 'Signal' represents a signal with a specified clock and input/output types.
Allows defining complex signal processing pipelines with specific clocking.
-}
type Signal clk a b = ArrowP SF clk a b

{- | 'SigFun' is a type synonym for generalized signal functions using 'ArrowP'.
A key abstraction for creating reusable components in signal processing.
-}
type SigFun clk a b = ArrowP SF clk a b

{- | The 'AudioSample' class defines operations for various audio sample formats.
Supports basic operations like mixing and channel management.
-}
class AudioSample a where
zero ::
-- | Represents silence or zero value for the audio sample.
a
mix ::
a ->
a ->
-- | Combines two audio samples into one.
a
collapse ::
a ->
-- | Converts an audio sample to a list of doubles, typically representing channels.
[Double]
numChans ::
a ->
-- | Returns the number of channels in the audio sample.
Int

-- | An instance of 'AudioSample' for single-channel (mono) audio represented by 'Double'.
zero :: a
mix :: a -> a -> a
collapse :: a -> [Double]
numChans :: a -> Int

instance AudioSample Double where
zero = 0 -- Zero value for mono is 0.
mix = (+) -- Mixes two mono samples by addition.
collapse a = [a] -- Collapse returns a single-element list.
numChans _ = 1 -- Mono has one channel.
zero = 0
mix = (+)
collapse a = [a]
numChans _ = 1

-- | An instance of 'AudioSample' for stereo audio represented by a tuple of 'Double's.
instance AudioSample (Double, Double) where
zero = (0, 0) -- Zero value for stereo is (0, 0).
mix (a, b) (c, d) = (a + c, b + d) -- Mixes two stereo samples by adding corresponding channels.
collapse (a, b) = [a, b] -- Collapse returns a list containing both channels.
numChans _ = 2 -- Stereo has two channels.

{- | Type synonym for mono signals using the generic signal type.
Often used for single-channel (mono) audio processing.
-}
type Mono p = Signal p () Double
zero = (0, 0)
mix (a, b) (c, d) = (a + c, b + d)
collapse (a, b) = [a, b]
numChans _ = 2

class AudioSample a => MultiChannel a where
mapChannels :: (Double -> Double) -> a -> a
channels :: a -> [Double]
channels = collapse
fromChannels :: [Double] -> Maybe a

instance MultiChannel Double where
mapChannels = id
fromChannels [x] = Just x
fromChannels _ = Nothing

instance MultiChannel (Double, Double) where
mapChannels f (l, r) = (f l, f r)
fromChannels [l, r] = Just (l, r)
fromChannels _ = Nothing

class MultiChannel a => AudioChannel a where
gain :: Double -> a -> Either AudioError a
gain g = Right . mapChannels (* g)
pan :: Double -> a -> Either AudioError a

instance AudioChannel Double where
pan _ = Right

instance AudioChannel (Double, Double) where
pan p x
| p < -1 || p > 1 = Left $ InvalidPan p
| otherwise = Right $ fromMaybe (error "Impossible: stereo pan conversion failed") $
fromChannels $ doPan (channels x)
where
doPan [l, r] =
let leftGain = cos ((p + 1) * pi / 4) -- Equal power panning
rightGain = sin ((p + 1) * pi / 4)
in [l * leftGain, r * rightGain]
doPan _ = error "Impossible: stereo channels /= 2"

{- | Type synonym for stereo signals using the generic signal type.
Used for processing two-channel (stereo) audio signals.
-}
type Mono p = Signal p () Double
type Stereo p = Signal p () (Double, Double)

0 comments on commit 953e6c2

Please sign in to comment.