boopadoop-0.0.0.2: Mathematically sound sound synthesis

Safe HaskellNone
LanguageHaskell2010

Boopadoop

Description

A music theory library for just intonation and other mathematically pure ideas.

Synopsis

Documentation

data CompactWavetable Source #

A data structure for storing the results of a Wavetable on some subset of its domain. Used internally.

Constructors

CompactWavetable 

type Wavetable = Waveform Tick Discrete Source #

A domain- and codomain-discretized Waveform suitable for writing to a WAVE file. See waveformToWAVE.

type DWave = Waveform Double Double Source #

A Double valued wave with time also in terms of Double. This models a real-valued waveform which typically has values in [-1,1] and is typically supported on either the entire real line (sinWave) or on a compact subset (compactWave)

newtype Waveform t a Source #

A Waveform is a function (of time) that we can later sample.

Constructors

Waveform 

Fields

Instances
Functor (Waveform t) Source # 
Instance details

Defined in Boopadoop

Methods

fmap :: (a -> b) -> Waveform t a -> Waveform t b #

(<$) :: a -> Waveform t b -> Waveform t a #

Show (Waveform Double Double) Source #

Show a waveform by pretty printing some of the actual waveform in dot matrix form.

Instance details

Defined in Boopadoop

Show (Waveform Double Discrete) Source # 
Instance details

Defined in Boopadoop

Show (Waveform Tick Discrete) Source # 
Instance details

Defined in Boopadoop

quotRoundUp :: Int -> Int -> Int Source #

A version of quot that rounds away from zero instead of towards it.

sampleFrom :: (t -> a) -> Waveform t a Source #

Build a Waveform by sampling the given function.

sampleAt :: t -> Waveform t a -> a Source #

Sample a Waveform at specified time. sampleAt = flip sample

sinWave :: Floating a => a -> Waveform a a Source #

Pure sine wave of the given frequency

fastSin :: Double -> Double -> Wavetable Source #

Sine wave that is optimized to store only a small CompactWavetable. Frequency given in

compactWave :: (Ord t, Num t) => (t, t) -> Waveform t Bool Source #

compactWave (l,h) is a wave which is True on [l,h) and False elsewhere

muting :: Num a => Bool -> a -> a Source #

muting True is id while muting False is const 0.

modulate :: (a -> b -> c) -> Waveform t a -> Waveform t b -> Waveform t c Source #

Modulate one wave with another according to the given function pointwise. This means you can't implement phaseModulate using only this combinator because phase modulation requires information about the target wave at times other than the current time.

amplitudeModulate :: Num a => Waveform t a -> Waveform t a -> Waveform t a Source #

Modulate the amplitude of one wave with another. This is simply pointwise multiplication: amplitudeModulate = modulate (*)

phaseModulate Source #

Arguments

:: Num t 
=> t

Tuning parameter. Modulation signal is amplitudeModulated by (const beta)

-> Waveform t t

Modulation signal. Outputs the phase shift to apply

-> Waveform t a

Target wave to be modulated

-> Waveform t a 

Modulate the phase of one wave with another. Used in synthesis. phaseModulate beta (setVolume 0.2 $ sinWave concertA) (setVolume 0.38 $ triWave concertA) (try beta=0.0005)

changeSpeed :: (Ord a, Fractional a) => a -> a -> a -> Waveform a a -> Waveform a a Source #

Smoothly transition to playing a wave back at a different speed after some time

balanceChord :: Fractional a => [Waveform t a] -> Waveform t a Source #

Play several waves on top of each other, normalizing so that e.g. playing three notes together doesn't triple the volume.

mergeWaves :: Num a => [Waveform t a] -> Waveform t a Source #

Play several waves on top of each other, without worrying about the volume. See balanceChord for a normalized version.

waveformToWAVE :: Tick -> Int -> Wavetable -> WAVE Source #

waveformToWAVE outputLength gives a WAVE file object by sampling the given DWave at 44100Hz. May disbehave or clip based on behavior of doubleToSample if the DWave takes values outside of [-1,1].

triWave :: (Ord a, RealFrac a) => a -> Waveform a a Source #

Triangle wave of the given frequency

stdtr :: Num a => a Source #

Arbitrarily chosen standard tick rate, used in testWave

testWave :: String -> Wavetable -> IO () Source #

Output the first ten seconds of the given DWave to the file test.wav for testing. The volume is also attenuated by 50% to not blow out your eardrums. Also pretty prints the wave.

testDiagram :: PitchFactorDiagram -> IO () Source #

Outputs a sound test of the given PitchFactorDiagram as an interval above concertA as a sinWave to the file diag.wav for testing.

sequenceToBeat :: Double -> Double -> Beat DWave -> DWave Source #

Converts a rhythm of DWave notes to a combined DWave according to the timing rules of Beat.

sequenceNotes :: (Ord t, Fractional t, Fractional a) => [((t, t), Waveform t a)] -> Waveform t a Source #

Sequences some waves to play on the given time intervals.

buildChord :: (Num a, RealFrac a) => [a] -> a -> Waveform a a Source #

Builds a chord out of the given ratios relative to the root pitch buildChord ratios root

buildChordNoBalance :: [Double] -> Double -> DWave Source #

Builds a chord out of the given ratios relative to the root pitch, without normalizing the volume. (Warning: may be loud)

majorChordOver :: Double -> DWave Source #

Builds a just-intonated major chord over the given root pitch

minorChordOver :: Double -> DWave Source #

Builds an equal temperament minor chord over the given root pitch

concertA :: Num a => a Source #

Concert A4 frequency is 440Hz

envelope :: Double -> Double -> Double -> Double -> Double -> Double -> DWave Source #

Build an envelope waveform with the given parameters: Predelay Time, Attack Time, Hold Time, Decay Time, Sustain Level, Release Time

timeShift :: Num t => t -> Waveform t a -> Waveform t a Source #

Shift a wave in time to start at the specified time after its old start time

seekTo :: Num t => t -> Waveform t a -> Waveform t a Source #

Shift a wave in time such that the new zero is at the specified position

equalTime :: Double -> [DWave] -> DWave Source #

Play several waves in a row with eqqual time each, using sequenceNotes.

setVolume :: Num a => a -> Waveform t a -> Waveform t a Source #

Modify the amplitude of a wave by a constant multiple

emptyWave :: Num a => Waveform t a Source #

The empty wave that is always zero when sampled

discreteConvolve :: (Num a, Num t) => Waveform t [(t, a)] -> Waveform t a -> Waveform t a Source #

Convolve with explicit discrete filter kernel weights.

wackyNotConvolution :: (a -> b -> c) -> Waveform t (Waveform t a) -> Waveform t b -> Waveform t c Source #

This operation is not convolution, but something kind of like it. Use for creative purposes? Should be fast! wackyNotConvolution modf profile w = sampleFrom $ t -> sample (modulate modf (sample profile t) w) t

tickConvolution Source #

Arguments

:: Fractional a 
=> Tick
tickRadius
-> Tick
skipRate
-> Waveform Tick (Waveform Tick a)

The kernel of the convolution at each Tick

-> Waveform Tick a

w(t)

-> Waveform Tick a 

Perform a discrete convolution. The output waveform is f(t) = int_{t-tickRadius}^{t+tickRadius} (kernel(t))(x) * w(t+x) dx but is discretized such that x is always a multiple of skipRate.

sampledConvolution Source #

Arguments

:: (RealFrac t, Fractional a) 
=> t

convolutionSampleRate, controls sampling for x

-> t

convolutionRadius, continuous analogue of tickRadius

-> Waveform t (Waveform t a)

Kernel of convolution for each time

-> Waveform t a 
-> Waveform t a 

Same as tickConvolution but for arbitarily valued waveforms. Works on DWave for example.

bandpassFilter Source #

Arguments

:: Fractional a 
=> Double
bandCenter
-> Double
bandSize
-> Waveform Double a 

Makes a filter which selects frequencies near bandCenter with tuning parameter bandSize. Try: optimizeFilter 200 . tickTable stdtr $ bandpassFilter concertA 100

discretize :: Waveform t Double -> Waveform t Discrete Source #

Discretize the output of a Double producing waveform

tickTable Source #

Arguments

:: Double

Sample rate. Each tick is 1/sampleRate seconds

-> Waveform Double a 
-> Waveform Tick a 

Discretize the input to a Double consuming waveform

tickTableMemo :: Double -> Waveform Double a -> Waveform Tick a Source #

Tries and fails to optimize a Waveform through memoization but actually hangs and eats all your memory.

solidSlice :: Tick -> Tick -> Wavetable -> Wavetable Source #

Optimize a Wavetable by storing its values in a particular range. Uses (tickEnd - tickStart + 1) * sizeOf (_ :: Discrete) bytes of memory to do this.

optimizeFilter :: Tick -> Wavetable -> Wavetable Source #

Optimize a filter by doing solidSlice around t=0 since those values are sampled repeatedly in a filter

fourierTransform :: Tick -> Double -> Waveform Tick (Complex Double) -> Waveform Double (Complex Double) Source #

Take the Fourier Transform of a complex valued Tick sampled waveform

realDFT Source #

Arguments

:: Tick

Radius of Fourier Transform window in Ticks. Try 200

-> Double

Sampling rate to use for the Fourier transform. Try the sample sample rate as the Wavetable

-> Wavetable 
-> Wavetable 

Take the Fourier Transform of a Wavetable

skipTicks Source #

Arguments

:: Tick
n
-> Waveform Tick a 
-> Waveform Tick a 

Skip every n ticks in the in the given Waveform. sample (skipTicks n w) k = sample w (n*k)

exploitPeriodicity Source #

Arguments

:: Tick

Period in Ticks of the Wavetable.

-> Wavetable 
-> Wavetable 

Optimize a Wavetable that we know to be periodic by storing it's values on one period. Takes period * sizeOf (_ :: Discrete) bytes of memory to do this.

usingFFT :: Tick -> Wavetable -> Wavetable Source #

Attempts to do a fast fourier transform, but the units of the domain of the output are highly suspect. May be unreliable, use with caution.

fft :: [Complex Double] -> [Complex Double] Source #

Cooley-Tukey fft

semi :: Floating a => a Source #

12 tone equal temperament semitone ratio. Equal to 2 ** (1/12).

allSemis :: Floating a => [a] Source #

12 tone equal temperament ratios for all semitones in an octave.

takeFinAlignments :: Floating a => Int -> [[a]] Source #

List multiples of the single octave semitone ratios upto a certain amount.

newtype PitchFactorDiagram Source #

A pitch factor diagram is a list of prime exponents that represents a rational number via diagramToRatio. These are useful because pitches with few prime factors, that is, small PitchFactorDiagrams with small factors in them, are generally consonant, and many interesting just intonation intervals can be written this way (see perfectFifth and majorThird).

Constructors

Factors 

Fields

diagramToRatio :: Fractional a => PitchFactorDiagram -> a Source #

Convert a factor diagram to the underlying ratio by raising each prime (starting from two) to the power in the factor list. For instance, going up two perfect fifths and down three major thirds yields: diagramToRatio (Factors [4,2,-3]) = (2 ^^ 4) * (3 ^^ 2) * (5 ^^ (-3)) = 144/125

diagramToFloatyRatio :: PitchFactorDiagram -> Rational Source #

Similar to diagramToRatio, but simplifies the resulting ratio to the simplest ratio within 0.05.

diagramToSemi :: Floating a => PitchFactorDiagram -> a Source #

Convert a PFD to its decimal number of semitones. Useful for approximating weird ratios in a twelvetone scale: diagramToSemi (normalizePFD $ Factors [0,0,0,1]) = diagramToSemi (countPFD (7/4)) = 9.688259064691248

normalizePFD :: PitchFactorDiagram -> PitchFactorDiagram Source #

Normalize a PFD by raising or lowering it by octaves until its ratio lies between 1 (unison) and 2 (one octave up). This operation is idempotent.

countPFDFuzzy :: Double -> PitchFactorDiagram Source #

Same as countPFD but makes an effort to simplify the ratio from a Double slightly to the simplest rational number within 0.0001.

countPFD :: Rational -> PitchFactorDiagram Source #

Calculates the PitchFactorDiagram corresponding to a given frequency ratio by finding prime factors of the numerator and denominator.

intervalOf :: PitchFactorDiagram -> Double -> Double Source #

Converts a PFD into an operation on frequencies. intervalOf perfectFifth concertA is the just intonation E5.

scalePFD :: Integer -> PitchFactorDiagram -> PitchFactorDiagram Source #

Scale a PFD by raising the underlying ratio to the given power. scalePFD 2 perfectFifth = addPFD octave majorSecond

addPFD :: PitchFactorDiagram -> PitchFactorDiagram -> PitchFactorDiagram Source #

Adds two PFDs together by multiplying their ratios. addPFD minorThird majorThird = perfectFifth

printTheSequence :: Int -> IO () Source #

Prints the natural numbers from the given value up to 128, highlighting primes and powers of two. Interesting musical intervals are build out of the relative distance of a prime between the two nearest powers of two.

data Beat a Source #

A rhythm is represented as a rose tree where each subtree is given equal amounts of time. Leaves are either a Beat of type a or empty (a rest).

Constructors

RoseBeat [Beat a] 
Beat a 
Rest 
Instances
SummaryChar a => Show (Beat a) Source #

Show the rhythm by printing the summary characters, or . for rests.

Instance details

Defined in Boopadoop.Rhythm

Methods

showsPrec :: Int -> Beat a -> ShowS #

show :: Beat a -> String #

showList :: [Beat a] -> ShowS #

class SummaryChar a where Source #

Class for things that can be summarized in a single character, for use in printing out rhythms.

Methods

sumUp :: a -> Char Source #

Instances
SummaryChar DrumRack Source # 
Instance details

Defined in Boopadoop.Rhythm

Methods

sumUp :: DrumRack -> Char Source #

data DrumRack Source #

A rack of drums. Simple enumeration of the different possible drum types.

Constructors

Kick 
Snare 
Instances
SummaryChar DrumRack Source # 
Instance details

Defined in Boopadoop.Rhythm

Methods

sumUp :: DrumRack -> Char Source #

rockBeat :: Beat DrumRack Source #

The standard rock beat (or half of it) played on the DrumRack

primeBeat :: Beat a -> Beat a Source #

Force there to be only prime divisions of time in the rhythm. This is done without affecting the actual rhythm. This operation is not uniquely valued in any way, and this algorithm prefers small primes first.

octave :: PitchFactorDiagram Source #

Interval of one octave, ratio is 2.

perfectFifth :: PitchFactorDiagram Source #

Interval of a perfect fifth 3:2

majorThird :: PitchFactorDiagram Source #

Interval of a major third 5:4

majorSecond :: PitchFactorDiagram Source #

Interval of a major second 9:8

counterExample :: PitchFactorDiagram Source #

Interval 199:200. Should be mostly consonant to your ear but has non-small PFD: [-3,0,-2,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1]

newtype Discrete Source #

Discrete x represents x/discFactor as a floating point number in [-1,1].

Constructors

Discrete 

Fields

Instances
Bounded Discrete Source # 
Instance details

Defined in Boopadoop.Discrete

Eq Discrete Source # 
Instance details

Defined in Boopadoop.Discrete

Fractional Discrete Source # 
Instance details

Defined in Boopadoop.Discrete

Num Discrete Source # 
Instance details

Defined in Boopadoop.Discrete

Ord Discrete Source # 
Instance details

Defined in Boopadoop.Discrete

Show Discrete Source # 
Instance details

Defined in Boopadoop.Discrete

Show (Waveform Double Discrete) Source # 
Instance details

Defined in Boopadoop

Show (Waveform Tick Discrete) Source # 
Instance details

Defined in Boopadoop

doubleToDiscrete :: Double -> Discrete Source #

Breaks when the double is not in [-1,1]

discreteToDouble :: Discrete -> Double Source #

Convert Discrete to the Double it represents.

discFactor :: Num a => a Source #

This is the conversion factor between the internal value of a Discrete and the value it represents.

properFloor :: RealFrac a => a -> Int32 Source #

Round toward zero

multiplyDiscrete :: Discrete -> Discrete -> Discrete Source #

Perform fast Discrete multiplication.

disguise :: (Double -> Double) -> Discrete -> Discrete Source #

Make a function of doubles a function of discretes

newtype Tick Source #

A discrete representation of time. See tickTable for the sampling rate.

Constructors

Tick 

Fields

Instances
Enum Tick Source # 
Instance details

Defined in Boopadoop.Discrete

Methods

succ :: Tick -> Tick #

pred :: Tick -> Tick #

toEnum :: Int -> Tick #

fromEnum :: Tick -> Int #

enumFrom :: Tick -> [Tick] #

enumFromThen :: Tick -> Tick -> [Tick] #

enumFromTo :: Tick -> Tick -> [Tick] #

enumFromThenTo :: Tick -> Tick -> Tick -> [Tick] #

Eq Tick Source # 
Instance details

Defined in Boopadoop.Discrete

Methods

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

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

Integral Tick Source # 
Instance details

Defined in Boopadoop.Discrete

Methods

quot :: Tick -> Tick -> Tick #

rem :: Tick -> Tick -> Tick #

div :: Tick -> Tick -> Tick #

mod :: Tick -> Tick -> Tick #

quotRem :: Tick -> Tick -> (Tick, Tick) #

divMod :: Tick -> Tick -> (Tick, Tick) #

toInteger :: Tick -> Integer #

Num Tick Source # 
Instance details

Defined in Boopadoop.Discrete

Methods

(+) :: Tick -> Tick -> Tick #

(-) :: Tick -> Tick -> Tick #

(*) :: Tick -> Tick -> Tick #

negate :: Tick -> Tick #

abs :: Tick -> Tick #

signum :: Tick -> Tick #

fromInteger :: Integer -> Tick #

Ord Tick Source # 
Instance details

Defined in Boopadoop.Discrete

Methods

compare :: Tick -> Tick -> Ordering #

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

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

(>) :: Tick -> Tick -> Bool #

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

max :: Tick -> Tick -> Tick #

min :: Tick -> Tick -> Tick #

Real Tick Source # 
Instance details

Defined in Boopadoop.Discrete

Methods

toRational :: Tick -> Rational #

Show Tick Source # 
Instance details

Defined in Boopadoop.Discrete

Methods

showsPrec :: Int -> Tick -> ShowS #

show :: Tick -> String #

showList :: [Tick] -> ShowS #

Show (Waveform Tick Discrete) Source # 
Instance details

Defined in Boopadoop