essence-of-live-coding-pulse-0.2.7: General purpose live coding framework - pulse backend
Safe HaskellSafe-Inferred
LanguageHaskell2010

LiveCoding.Pulse

Synopsis

Documentation

type PulseCell m a b = Cell (PulseT m) a b Source #

addSample :: Monad m => PulseCell m Float () Source #

Compose with this cell to play a sound sample.

sampleRate :: Num a => a Source #

Globally fix the sample rate to 48000 samples per second.

pulseHandle :: Handle IO Simple Source #

Create a pulse server backend handle.

Currently, this is always mono, but with a future release of pulse-simple, this might be configurable.

pulseWrapC Source #

Arguments

:: Int

Specifies how many steps of your PulseCell should be performed in one step of pulseWrapC.

-> PulseCell IO a b

Your cell that produces samples.

-> Cell (HandlingStateT IO) a [b] 

Run a PulseCell with a started pulse backend.

Currently, this is synchronous and blocking, i.e. the resulting cell will block until the backend buffer is nearly empty.

This performs several steps of your cell at a time, replicating the input so many times.

wrapSum :: (Monad m, Data a, RealFloat a) => Cell m a a Source #

Returns the sum of all incoming values, and wraps it between -1 and 1.

This is to prevent floating number imprecision when the sum gets too large.

wrapIntegral :: (Monad m, Data a, RealFloat a) => Cell m a a Source #

Like wrapSum, but as an integral, assuming the PulseAudio sampleRate.

sawtooth :: (Monad m, Data a, RealFloat a) => Cell m a a Source #

A sawtooth, or triangle wave, generator, outputting a sawtooth wave with the given input as frequency.

modSum :: (Monad m, Data a, Integral a) => a -> Cell m a a Source #

clamp :: (Ord a, Num a) => a -> a -> a -> a Source #

osc :: (Data a, RealFloat a, Monad m) => Cell (ReaderT a m) () a Source #

A sine oscillator. Supply the frequency via the ReaderT environment. See osc' and oscAt.

oscAt :: (Data a, RealFloat a, Monad m) => a -> Cell m () a Source #

A sine oscillator, at a fixed frequency.

osc' :: (Data a, RealFloat a, Monad m) => Cell m a a Source #

A sine oscillator, at a frequency that can be specified live.

data Note Source #

A basic musical note (western traditional notation, german nomenclature).

Assumes equal temperament and removes enharmonic equivalents, i.e. there is only Dis (= D sharp) but not Eb (= E flat).

Constructors

A 
Bb 
B 
C 
Cis 
D 
Dis 
E 
F 
Fis 
G 
Gis 

Instances

Instances details
Enum Note Source # 
Instance details

Defined in LiveCoding.Pulse

Methods

succ :: Note -> Note #

pred :: Note -> Note #

toEnum :: Int -> Note #

fromEnum :: Note -> Int #

enumFrom :: Note -> [Note] #

enumFromThen :: Note -> Note -> [Note] #

enumFromTo :: Note -> Note -> [Note] #

enumFromThenTo :: Note -> Note -> Note -> [Note] #

Show Note Source # 
Instance details

Defined in LiveCoding.Pulse

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

f :: Note -> Float Source #

Calculate the frequency of a note, with A corresponding to 220 Hz.

o :: Float -> Float Source #

Transpose a frequency an octave higher, i.e. multiply by 2.

oB :: Float -> Float Source #

Transpose a frequency an octave lower, i.e. divide by 2.