Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
A music theory library for just intonation and other mathematically pure ideas.
Synopsis
- type DWave = Waveform Double Double
- newtype Waveform t a = Waveform {
- sample :: t -> a
- sampleFrom :: (t -> a) -> Waveform t a
- sampleAt :: t -> Waveform t a -> a
- sinWave :: Double -> DWave
- compactWave :: (Ord t, Num t) => (t, t) -> Waveform t Bool
- modulateMuting :: Num a => Waveform t Bool -> Waveform t a -> Waveform t a
- modulate :: (a -> b -> c) -> Waveform t a -> Waveform t b -> Waveform t c
- amplitudeModulate :: Num a => Waveform t a -> Waveform t a -> Waveform t a
- phaseModulate :: Num t => t -> Waveform t t -> Waveform t a -> Waveform t a
- changeSpeed :: (Ord a, Fractional a) => a -> a -> a -> Waveform a a -> Waveform a a
- balanceChord :: Fractional a => [Waveform t a] -> Waveform t a
- mergeWaves :: Fractional a => [Waveform t a] -> Waveform t a
- waveformToWAVE :: Double -> DWave -> WAVE
- triWave :: (Ord a, RealFrac a) => a -> Waveform a a
- testWave :: DWave -> IO ()
- testDiagram :: PitchFactorDiagram -> IO ()
- sequenceToBeat :: Double -> Double -> Beat DWave -> DWave
- sequenceNotes :: (Ord t, Fractional t, Fractional a) => [((t, t), Waveform t a)] -> Waveform t a
- buildChord :: [Double] -> Double -> DWave
- buildChordNoBalance :: [Double] -> Double -> DWave
- majorChordOver :: Double -> DWave
- minorChordOver :: Double -> DWave
- concertA :: Num a => a
- envelope :: Double -> Double -> Double -> Double -> Double -> Double -> DWave
- timeShift :: Num t => t -> Waveform t a -> Waveform t a
- equalTime :: Double -> [DWave] -> DWave
- setVolume :: Num a => a -> Waveform t a -> Waveform t a
- emptyWave :: Num a => Waveform t a
- module Boopadoop.Diagram
- module Boopadoop.Rhythm
- module Boopadoop.Interval
Documentation
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
)
A Waveform
is a function (of time) that we can later sample.
sampleFrom :: (t -> a) -> Waveform t a Source #
Build a Waveform
by sampling the given function.
compactWave :: (Ord t, Num t) => (t, t) -> Waveform t Bool Source #
is a wave which is compactWave
(l,h)1
on [l,h)
and 0
elsewhere
modulateMuting :: Num a => Waveform t Bool -> Waveform t a -> Waveform t a Source #
Modulate the muting or non-muting of another wave with a
value wave, such as Bool
.compactWave
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
(*
)
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 :: Fractional 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 :: Double -> DWave -> WAVE Source #
gives a waveformToWAVE
outputLength
file object by sampling the given WAVE
at DWave
44100Hz
.
May disbehave or clip based on behavior of
if the DWave takes values outside of doubleToSample
[-1,1]
.
testWave :: DWave -> IO () Source #
Output the first ten seconds of the given
to the file DWave
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
as an interval above PitchFactorDiagram
as a concertA
to the file sinWave
diag.wav
for testing.
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 :: [Double] -> Double -> DWave 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
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
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
module Boopadoop.Diagram
module Boopadoop.Rhythm
module Boopadoop.Interval