lambdasound-1.2.0: A libary for generating low-level sounds with high-level combinators
Safe HaskellSafe-Inferred
LanguageGHC2021

LambdaSound.Sound

Description

This module exports all needed datatypes and all the combinators needed to manipulate them.

Synopsis

Sound types

data Sound (d :: SoundDuration) a where Source #

Constructors

TimedSound :: !Duration -> ComputeSound a -> Sound T a 
InfiniteSound :: ComputeSound a -> Sound I a 

Instances

Instances details
Applicative (Sound 'I) Source # 
Instance details

Defined in LambdaSound.Sound

Methods

pure :: a -> Sound 'I a #

(<*>) :: Sound 'I (a -> b) -> Sound 'I a -> Sound 'I b #

liftA2 :: (a -> b -> c) -> Sound 'I a -> Sound 'I b -> Sound 'I c #

(*>) :: Sound 'I a -> Sound 'I b -> Sound 'I b #

(<*) :: Sound 'I a -> Sound 'I b -> Sound 'I a #

Functor (Sound d) Source # 
Instance details

Defined in LambdaSound.Sound

Methods

fmap :: (a -> b) -> Sound d a -> Sound d b #

(<$) :: a -> Sound d b -> Sound d a #

Monoid (Sound 'I Pulse) Source # 
Instance details

Defined in LambdaSound.Sound

Monoid (Sound 'T Pulse) Source # 
Instance details

Defined in LambdaSound.Sound

Semigroup (Sound d Pulse) Source # 
Instance details

Defined in LambdaSound.Sound

Methods

(<>) :: Sound d Pulse -> Sound d Pulse -> Sound d Pulse #

sconcat :: NonEmpty (Sound d Pulse) -> Sound d Pulse #

stimes :: Integral b => b -> Sound d Pulse -> Sound d Pulse #

Num a => Num (Sound 'I a) Source # 
Instance details

Defined in LambdaSound.Sound

Methods

(+) :: Sound 'I a -> Sound 'I a -> Sound 'I a #

(-) :: Sound 'I a -> Sound 'I a -> Sound 'I a #

(*) :: Sound 'I a -> Sound 'I a -> Sound 'I a #

negate :: Sound 'I a -> Sound 'I a #

abs :: Sound 'I a -> Sound 'I a #

signum :: Sound 'I a -> Sound 'I a #

fromInteger :: Integer -> Sound 'I a #

Show (Sound d Pulse) Source # 
Instance details

Defined in LambdaSound.Sound

Methods

showsPrec :: Int -> Sound d Pulse -> ShowS #

show :: Sound d Pulse -> String #

showList :: [Sound d Pulse] -> ShowS #

data SoundDuration Source #

Sounds may have a duration attached to them. Timed Sounds have a duration. Infinite Sounds have no duration.

Constructors

I 
T 

newtype Pulse Source #

An audio sample

Constructors

Pulse Float 

Instances

Instances details
Storable Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

sizeOf :: Pulse -> Int #

alignment :: Pulse -> Int #

peekElemOff :: Ptr Pulse -> Int -> IO Pulse #

pokeElemOff :: Ptr Pulse -> Int -> Pulse -> IO () #

peekByteOff :: Ptr b -> Int -> IO Pulse #

pokeByteOff :: Ptr b -> Int -> Pulse -> IO () #

peek :: Ptr Pulse -> IO Pulse #

poke :: Ptr Pulse -> Pulse -> IO () #

Enum Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Floating Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Num Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Fractional Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Real Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

toRational :: Pulse -> Rational #

RealFrac Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

properFraction :: Integral b => Pulse -> (b, Pulse) #

truncate :: Integral b => Pulse -> b #

round :: Integral b => Pulse -> b #

ceiling :: Integral b => Pulse -> b #

floor :: Integral b => Pulse -> b #

Show Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

showsPrec :: Int -> Pulse -> ShowS #

show :: Pulse -> String #

showList :: [Pulse] -> ShowS #

NFData Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

rnf :: Pulse -> () #

Eq Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

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

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

Ord Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

compare :: Pulse -> Pulse -> Ordering #

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

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

(>) :: Pulse -> Pulse -> Bool #

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

max :: Pulse -> Pulse -> Pulse #

min :: Pulse -> Pulse -> Pulse #

Hashable Pulse Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

hashWithSalt :: Int -> Pulse -> Int #

hash :: Pulse -> Int #

Monoid (Sound 'I Pulse) Source # 
Instance details

Defined in LambdaSound.Sound

Monoid (Sound 'T Pulse) Source # 
Instance details

Defined in LambdaSound.Sound

Semigroup (Sound d Pulse) Source # 
Instance details

Defined in LambdaSound.Sound

Methods

(<>) :: Sound d Pulse -> Sound d Pulse -> Sound d Pulse #

sconcat :: NonEmpty (Sound d Pulse) -> Sound d Pulse #

stimes :: Integral b => b -> Sound d Pulse -> Sound d Pulse #

Show (Sound d Pulse) Source # 
Instance details

Defined in LambdaSound.Sound

Methods

showsPrec :: Int -> Sound d Pulse -> ShowS #

show :: Sound d Pulse -> String #

showList :: [Sound d Pulse] -> ShowS #

newtype Duration Source #

The duration of a Sound

Constructors

Duration Float 

Instances

Instances details
Storable Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

Enum Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

Floating Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

Num Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

Fractional Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

Real Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

RealFrac Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

properFraction :: Integral b => Duration -> (b, Duration) #

truncate :: Integral b => Duration -> b #

round :: Integral b => Duration -> b #

ceiling :: Integral b => Duration -> b #

floor :: Integral b => Duration -> b #

Show Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

NFData Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

rnf :: Duration -> () #

Eq Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

Ord Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

Hashable Duration Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

hashWithSalt :: Int -> Duration -> Int #

hash :: Duration -> Int #

newtype Progress Source #

The progress of a Sound. A sound progresses from '0' to '1' while it plays.

Constructors

Progress Float 

Instances

Instances details
Storable Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

Enum Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

Floating Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

Num Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

Fractional Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

Real Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

RealFrac Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

properFraction :: Integral b => Progress -> (b, Progress) #

truncate :: Integral b => Progress -> b #

round :: Integral b => Progress -> b #

ceiling :: Integral b => Progress -> b #

floor :: Integral b => Progress -> b #

Show Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

NFData Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

rnf :: Progress -> () #

Eq Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

Ord Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

Hashable Progress Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

hashWithSalt :: Int -> Progress -> Int #

hash :: Progress -> Int #

newtype Percentage Source #

The percentage of a Sound. '0.3' corresponds to 30% of a Sound.

Constructors

Percentage Float 

Instances

Instances details
Storable Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

Enum Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

Floating Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

Num Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

Fractional Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

Real Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

RealFrac Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

Show Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

NFData Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

rnf :: Percentage -> () #

Eq Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

Ord Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

Hashable Percentage Source # 
Instance details

Defined in LambdaSound.Sound.Types

data SamplingInfo Source #

Gives information about how many samples are needed during computation

Constructors

SamplingInfo 

Fields

Instances

Instances details
Generic SamplingInfo Source # 
Instance details

Defined in LambdaSound.Sound.Types

Associated Types

type Rep SamplingInfo :: Type -> Type #

Show SamplingInfo Source # 
Instance details

Defined in LambdaSound.Sound.Types

Eq SamplingInfo Source # 
Instance details

Defined in LambdaSound.Sound.Types

Hashable SamplingInfo Source # 
Instance details

Defined in LambdaSound.Sound.Types

type Rep SamplingInfo Source # 
Instance details

Defined in LambdaSound.Sound.Types

type Rep SamplingInfo = D1 ('MetaData "SamplingInfo" "LambdaSound.Sound.Types" "lambdasound-1.2.0-inplace" 'False) (C1 ('MetaCons "SamplingInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "period") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Float) :*: (S1 ('MetaSel ('Just "sampleRate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Hz) :*: S1 ('MetaSel ('Just "samples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

newtype Hz Source #

Hz are the unit for frequencies. 440 Hz means that 440 oscillations happen per second

Constructors

Hz Float 

Instances

Instances details
Enum Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

succ :: Hz -> Hz #

pred :: Hz -> Hz #

toEnum :: Int -> Hz #

fromEnum :: Hz -> Int #

enumFrom :: Hz -> [Hz] #

enumFromThen :: Hz -> Hz -> [Hz] #

enumFromTo :: Hz -> Hz -> [Hz] #

enumFromThenTo :: Hz -> Hz -> Hz -> [Hz] #

Floating Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

pi :: Hz #

exp :: Hz -> Hz #

log :: Hz -> Hz #

sqrt :: Hz -> Hz #

(**) :: Hz -> Hz -> Hz #

logBase :: Hz -> Hz -> Hz #

sin :: Hz -> Hz #

cos :: Hz -> Hz #

tan :: Hz -> Hz #

asin :: Hz -> Hz #

acos :: Hz -> Hz #

atan :: Hz -> Hz #

sinh :: Hz -> Hz #

cosh :: Hz -> Hz #

tanh :: Hz -> Hz #

asinh :: Hz -> Hz #

acosh :: Hz -> Hz #

atanh :: Hz -> Hz #

log1p :: Hz -> Hz #

expm1 :: Hz -> Hz #

log1pexp :: Hz -> Hz #

log1mexp :: Hz -> Hz #

Generic Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Associated Types

type Rep Hz :: Type -> Type #

Methods

from :: Hz -> Rep Hz x #

to :: Rep Hz x -> Hz #

Num Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

(+) :: Hz -> Hz -> Hz #

(-) :: Hz -> Hz -> Hz #

(*) :: Hz -> Hz -> Hz #

negate :: Hz -> Hz #

abs :: Hz -> Hz #

signum :: Hz -> Hz #

fromInteger :: Integer -> Hz #

Fractional Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

(/) :: Hz -> Hz -> Hz #

recip :: Hz -> Hz #

fromRational :: Rational -> Hz #

Real Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

toRational :: Hz -> Rational #

RealFrac Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

properFraction :: Integral b => Hz -> (b, Hz) #

truncate :: Integral b => Hz -> b #

round :: Integral b => Hz -> b #

ceiling :: Integral b => Hz -> b #

floor :: Integral b => Hz -> b #

Show Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

showsPrec :: Int -> Hz -> ShowS #

show :: Hz -> String #

showList :: [Hz] -> ShowS #

Eq Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

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

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

Ord Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

compare :: Hz -> Hz -> Ordering #

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

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

(>) :: Hz -> Hz -> Bool #

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

max :: Hz -> Hz -> Hz #

min :: Hz -> Hz -> Hz #

Hashable Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

hashWithSalt :: Int -> Hz -> Int #

hash :: Hz -> Int #

type Rep Hz Source # 
Instance details

Defined in LambdaSound.Sound.Types

type Rep Hz = D1 ('MetaData "Hz" "LambdaSound.Sound.Types" "lambdasound-1.2.0-inplace" 'True) (C1 ('MetaCons "Hz" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)))

newtype Time Source #

Time progresses while a Sound is playing and is used to create samples. It is not guaranteed that Time will correspond to the real runtime of a Sound

Constructors

Time Float 

Instances

Instances details
Storable Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

sizeOf :: Time -> Int #

alignment :: Time -> Int #

peekElemOff :: Ptr Time -> Int -> IO Time #

pokeElemOff :: Ptr Time -> Int -> Time -> IO () #

peekByteOff :: Ptr b -> Int -> IO Time #

pokeByteOff :: Ptr b -> Int -> Time -> IO () #

peek :: Ptr Time -> IO Time #

poke :: Ptr Time -> Time -> IO () #

Enum Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

succ :: Time -> Time #

pred :: Time -> Time #

toEnum :: Int -> Time #

fromEnum :: Time -> Int #

enumFrom :: Time -> [Time] #

enumFromThen :: Time -> Time -> [Time] #

enumFromTo :: Time -> Time -> [Time] #

enumFromThenTo :: Time -> Time -> Time -> [Time] #

Floating Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

pi :: Time #

exp :: Time -> Time #

log :: Time -> Time #

sqrt :: Time -> Time #

(**) :: Time -> Time -> Time #

logBase :: Time -> Time -> Time #

sin :: Time -> Time #

cos :: Time -> Time #

tan :: Time -> Time #

asin :: Time -> Time #

acos :: Time -> Time #

atan :: Time -> Time #

sinh :: Time -> Time #

cosh :: Time -> Time #

tanh :: Time -> Time #

asinh :: Time -> Time #

acosh :: Time -> Time #

atanh :: Time -> Time #

log1p :: Time -> Time #

expm1 :: Time -> Time #

log1pexp :: Time -> Time #

log1mexp :: Time -> Time #

Num Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

(+) :: Time -> Time -> Time #

(-) :: Time -> Time -> Time #

(*) :: Time -> Time -> Time #

negate :: Time -> Time #

abs :: Time -> Time #

signum :: Time -> Time #

fromInteger :: Integer -> Time #

Fractional Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

(/) :: Time -> Time -> Time #

recip :: Time -> Time #

fromRational :: Rational -> Time #

Real Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

toRational :: Time -> Rational #

RealFrac Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

properFraction :: Integral b => Time -> (b, Time) #

truncate :: Integral b => Time -> b #

round :: Integral b => Time -> b #

ceiling :: Integral b => Time -> b #

floor :: Integral b => Time -> b #

Show Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

NFData Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

rnf :: Time -> () #

Eq Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

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

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

Ord Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

compare :: Time -> Time -> Ordering #

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

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

(>) :: Time -> Time -> Bool #

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

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

Hashable Time Source # 
Instance details

Defined in LambdaSound.Sound.Types

Methods

hashWithSalt :: Int -> Time -> Int #

hash :: Time -> Int #

type family DetermineDuration (d1 :: SoundDuration) (d2 :: SoundDuration) where ... Source #

Determines the duration of two sounds when they are combined

Make new sounds

makeSound :: (SamplingInfo -> Int -> a) -> Sound I a Source #

Calculate sound samples based on their index. Take a look at LambdaSound.Create for other creation functions.

makeSoundVector :: (SamplingInfo -> Vector D a) -> Sound I a Source #

Calculate the samples of the sound as one vector Take a look at LambdaSound.Create for other creation functions.

fillWholeSound :: Load r Ix1 Pulse => (SamplingInfo -> Vector r Pulse) -> Sound I Pulse Source #

Fill a sound with a vector of sound samples. Keep in mind that the vector has the appropriate length!

fillWholeSoundST :: (SamplingInfo -> MVector RealWorld S Pulse -> ST RealWorld ()) -> Sound I Pulse Source #

Fill a sound with a vector of sound samples in a mutable fashion.

computeOnce :: (SamplingInfo -> a) -> Sound d (a -> b) -> Sound d b Source #

Compute a value once and then reuse it while computing all samples

Sounds in sequence

timedSequentially :: Sound T Pulse -> Sound T Pulse -> Sound T Pulse Source #

Append two sounds. This is only possible for sounds with a duration.

sequentially :: [Sound T Pulse] -> Sound T Pulse Source #

Combine a list of sounds in a sequential manner.

infiniteSequentially :: Percentage -> Sound I Pulse -> Sound I Pulse -> Sound I Pulse Source #

Append two infinite sounds where the Percentage in the range [0,1] specifies when the first sound ends and the next begins.

Sounds in parallel

parallel2 :: Sound d Pulse -> Sound d Pulse -> Sound d Pulse Source #

Combine two sounds such that they play in parallel. If one Sound is longer than the other, it will be played without the shorter one for its remaining time

parallel :: Monoid (Sound d Pulse) => [Sound d Pulse] -> Sound d Pulse Source #

Combine a lists of sounds such that they play in parallel

Volume

amplify :: Float -> Sound d Pulse -> Sound d Pulse Source #

Amplifies the volume of the given Sound

reduce :: Float -> Sound d Pulse -> Sound d Pulse Source #

Reduces the volume of the given Sound

Pitch

raise :: Float -> Sound d Pulse -> Sound d Pulse Source #

Raises the frequency of the Sound by the given factor. Only works if the sound is based on some frequency (e.g. sineWave but not noise)

diminish :: Float -> Sound d Pulse -> Sound d Pulse Source #

Diminishes the frequency of the Sound by the given factor. Only works if the sound is based on some frequency (e.g. pulse but not noise)

Duration

setDuration :: Duration -> Sound d a -> Sound T a Source #

Sets the duration of the Sound. The resuling sound is a Timed Sound.

(|->) :: Duration -> Sound d a -> Sound 'T a infix 7 Source #

Same as setDuration but in operator form.

getDuration :: Sound T a -> Duration Source #

Get the duration of a Timed Sound

scaleDuration :: Float -> Sound T a -> Sound T a Source #

Scales the Duration of a Sound. The following makes a sound twice as long:

scaleDuration 2 sound

dropDuration :: Sound d a -> Sound I a Source #

Drop the duration associated with a Sound and get an infinite sound again. If you have combined timed sounds with a sequence combinator and then drop their Duration, the sounds will keep their proportional length to each other. Essentially, the percentage of their play time stays the same.

adoptDuration :: Sound d a -> Sound x b -> Sound d b Source #

Set the Duration of a Sound to the same as another one Sound

Sample order

reverseSound :: Sound d a -> Sound d a Source #

Reverses a Sound similar to reverse for lists

dropSound :: Duration -> Sound T a -> Sound T a Source #

Drop parts of a sound similar to drop for lists

takeSound :: Duration -> Sound T a -> Sound T a Source #

Take parts of a sound similar to take for lists

Zipping

zipSoundWith :: (a -> b -> c) -> Sound d1 a -> Sound d2 b -> Sound (DetermineDuration d1 d2) c Source #

Zip two Sounds. The duration of the resulting Sound is equivalent to the duration of the shorter Sound, cutting away the excess samples from the longer one.

zipSound :: Sound d1 (a -> b) -> Sound d2 a -> Sound (DetermineDuration d1 d2) b Source #

Zip two Sounds. The duration of the resulting Sound is equivalent to the duration of the shorter Sound, cutting away the excess samples from the longer one.

Change play behavior of a sound

changeTempo :: (Progress -> Progress) -> Sound d a -> Sound d a Source #

Change how the Sound progresses. For example, you can slow it down in the beginning and speed it up at the end. However, the total duration stays the same.

Negative Progress is treated as '0' and Progress above '1' is treated as '1'

Modify the samples of a sound

modifyWholeSound :: Load r Ix1 Pulse => (Vector S Pulse -> Vector r Pulse) -> Sound d Pulse -> Sound d Pulse Source #

Modify all samples of a sound so that you can look into the past and future of a sound (e.g. IIR filter).

modifyWholeSoundST :: (Vector S Pulse -> MVector RealWorld S Pulse -> ST RealWorld ()) -> Sound d Pulse -> Sound d Pulse Source #

Modify all samples of a sound so that you can look into the past and future of a sound (e.g. IIR filter).

Access the samples of a sound

withSamplingInfo :: (SamplingInfo -> Sound d a) -> Sound I a Source #

Access the sample rate of an infinite sound

withSampledSound :: Sound T a -> (Vector D a -> Sound I b) -> Sound I b Source #

Access the samples of a sound.

withSampledSoundPulse :: Sound T Pulse -> (Vector S Pulse -> Sound I a) -> Sound I a Source #

Access the samples of a sound.

The pulse version is slightly faster since you get a storable vector

Embed IO

embedIO :: IO (Sound d a) -> Sound I a Source #

Embed an IO calculation when generating an infinite sound.

This IO action will be run each time the sound is used.

embedIOLazily :: IO (Sound d a) -> Sound I a Source #

Embed an IO calculation lazily when generating an infinite sound.

This IO action will not necessarily run each time the sound is used due to memoization. The IO action will run at least once and at most as often as the sound occurs.