Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- silence :: Pattern a
- sig :: (Time -> a) -> Pattern a
- sine :: Fractional a => Pattern a
- cosine :: Fractional a => Pattern a
- saw :: (Fractional a, Real a) => Pattern a
- isaw :: (Fractional a, Real a) => Pattern a
- tri :: (Fractional a, Real a) => Pattern a
- square :: Fractional a => Pattern a
- envL :: Pattern Double
- envLR :: Pattern Double
- envEq :: Pattern Double
- envEqR :: Pattern Double
- class Unionable a where
- union :: a -> a -> a
- (|+|) :: (Applicative a, Num b) => a b -> a b -> a b
- (|+) :: Num a => Pattern a -> Pattern a -> Pattern a
- (+|) :: Num a => Pattern a -> Pattern a -> Pattern a
- (|++|) :: Applicative a => a String -> a String -> a String
- (|++) :: Pattern String -> Pattern String -> Pattern String
- (++|) :: Pattern String -> Pattern String -> Pattern String
- (|/|) :: (Applicative a, Fractional b) => a b -> a b -> a b
- (|/) :: Fractional a => Pattern a -> Pattern a -> Pattern a
- (/|) :: Fractional a => Pattern a -> Pattern a -> Pattern a
- (|*|) :: (Applicative a, Num b) => a b -> a b -> a b
- (|*) :: Num a => Pattern a -> Pattern a -> Pattern a
- (*|) :: Num a => Pattern a -> Pattern a -> Pattern a
- (|-|) :: (Applicative a, Num b) => a b -> a b -> a b
- (|-) :: Num a => Pattern a -> Pattern a -> Pattern a
- (-|) :: Num a => Pattern a -> Pattern a -> Pattern a
- (|%|) :: (Applicative a, Real b) => a b -> a b -> a b
- (|%) :: Real a => Pattern a -> Pattern a -> Pattern a
- (%|) :: Real a => Pattern a -> Pattern a -> Pattern a
- (|**|) :: (Applicative a, Floating b) => a b -> a b -> a b
- (|**) :: Floating a => Pattern a -> Pattern a -> Pattern a
- (**|) :: Floating a => Pattern a -> Pattern a -> Pattern a
- (|>|) :: (Applicative a, Unionable b) => a b -> a b -> a b
- (|>) :: Unionable a => Pattern a -> Pattern a -> Pattern a
- (>|) :: Unionable a => Pattern a -> Pattern a -> Pattern a
- (|<|) :: (Applicative a, Unionable b) => a b -> a b -> a b
- (|<) :: Unionable a => Pattern a -> Pattern a -> Pattern a
- (<|) :: Unionable a => Pattern a -> Pattern a -> Pattern a
- (#) :: Unionable b => Pattern b -> Pattern b -> Pattern b
- fromList :: [a] -> Pattern a
- fastFromList :: [a] -> Pattern a
- listToPat :: [a] -> Pattern a
- fromMaybes :: [Maybe a] -> Pattern a
- run :: (Enum a, Num a) => Pattern a -> Pattern a
- _run :: (Enum a, Num a) => a -> Pattern a
- scan :: (Enum a, Num a) => Pattern a -> Pattern a
- _scan :: (Enum a, Num a) => a -> Pattern a
- append :: Pattern a -> Pattern a -> Pattern a
- cat :: [Pattern a] -> Pattern a
- slowCat :: [Pattern a] -> Pattern a
- slowcat :: [Pattern a] -> Pattern a
- slowAppend :: Pattern a -> Pattern a -> Pattern a
- slowappend :: Pattern a -> Pattern a -> Pattern a
- fastAppend :: Pattern a -> Pattern a -> Pattern a
- fastappend :: Pattern a -> Pattern a -> Pattern a
- fastCat :: [Pattern a] -> Pattern a
- fastcat :: [Pattern a] -> Pattern a
- timeCat :: [(Time, Pattern a)] -> Pattern a
- overlay :: Pattern a -> Pattern a -> Pattern a
- (<>) :: Pattern a -> Pattern a -> Pattern a
- stack :: [Pattern a] -> Pattern a
- (<~) :: Pattern Time -> Pattern a -> Pattern a
- (~>) :: Pattern Time -> Pattern a -> Pattern a
- fast :: Pattern Time -> Pattern a -> Pattern a
- fastSqueeze :: Pattern Time -> Pattern a -> Pattern a
- density :: Pattern Time -> Pattern a -> Pattern a
- _fast :: Time -> Pattern a -> Pattern a
- slow :: Pattern Time -> Pattern a -> Pattern a
- _slow :: Time -> Pattern a -> Pattern a
- slowSqueeze :: Pattern Time -> Pattern a -> Pattern a
- sparsity :: Pattern Time -> Pattern a -> Pattern a
- rev :: Pattern a -> Pattern a
- zoom :: (Time, Time) -> Pattern a -> Pattern a
- zoomArc :: Arc -> Pattern a -> Pattern a
- fastGap :: Pattern Time -> Pattern a -> Pattern a
- densityGap :: Pattern Time -> Pattern a -> Pattern a
- compress :: (Time, Time) -> Pattern a -> Pattern a
- compressTo :: (Time, Time) -> Pattern a -> Pattern a
- repeatCycles :: Int -> Pattern a -> Pattern a
- fastRepeatCycles :: Int -> Pattern a -> Pattern a
- every :: Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- _every :: Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- every' :: Pattern Int -> Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- _every' :: Int -> Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- foldEvery :: [Int] -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- when :: (Int -> Bool) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- whenT :: (Time -> Bool) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
Elemental patterns
sig :: (Time -> a) -> Pattern a Source #
Takes a function from time to values, and turns it into a Pattern
.
sine :: Fractional a => Pattern a Source #
sine
returns a Pattern
of continuous Fractional
values following a
sinewave with frequency of one cycle, and amplitude from 0 to 1.
cosine :: Fractional a => Pattern a Source #
cosine
is a synonym for 0.25 ~> sine
.
saw :: (Fractional a, Real a) => Pattern a Source #
saw
is the equivalent of sine
for (ascending) sawtooth waves.
isaw :: (Fractional a, Real a) => Pattern a Source #
isaw
is the equivalent of sine
for inverse (descending) sawtooth waves.
tri :: (Fractional a, Real a) => Pattern a Source #
tri
is the equivalent of sine
for triangular waves.
Pattern algebra
class Unionable a where Source #
Instances
Unionable a Source # | |
Defined in Sound.Tidal.Core | |
Unionable ControlMap Source # | |
Defined in Sound.Tidal.Core union :: ControlMap -> ControlMap -> ControlMap Source # |
(|+|) :: (Applicative a, Num b) => a b -> a b -> a b Source #
(|/|) :: (Applicative a, Fractional b) => a b -> a b -> a b Source #
(|*|) :: (Applicative a, Num b) => a b -> a b -> a b Source #
(|-|) :: (Applicative a, Num b) => a b -> a b -> a b Source #
(|%|) :: (Applicative a, Real b) => a b -> a b -> a b Source #
(|**|) :: (Applicative a, Floating b) => a b -> a b -> a b Source #
(|>|) :: (Applicative a, Unionable b) => a b -> a b -> a b Source #
(|<|) :: (Applicative a, Unionable b) => a b -> a b -> a b Source #
Constructing patterns
fromList :: [a] -> Pattern a Source #
Turns a list of values into a pattern, playing one of them per cycle.
fastFromList :: [a] -> Pattern a Source #
Turns a list of values into a pattern, playing one of them per cycle.
listToPat :: [a] -> Pattern a Source #
A synonym for fastFromList
fromMaybes :: [Maybe a] -> Pattern a Source #
run :: (Enum a, Num a) => Pattern a -> Pattern a Source #
A pattern of whole numbers from 0 to the given number, in a single cycle.
scan :: (Enum a, Num a) => Pattern a -> Pattern a Source #
From 1
for the first cycle, successively adds a number until it gets up to n
Combining patterns
append :: Pattern a -> Pattern a -> Pattern a Source #
Alternate between cycles of the two given patterns
cat :: [Pattern a] -> Pattern a Source #
Like append
, but for a list of patterns. Interlaces them, playing the first cycle from each
in turn, then the second cycle from each, and so on.
fastCat :: [Pattern a] -> Pattern a Source #
The same as cat
, but speeds up the result by the number of
patterns there are, so the cycles from each are squashed to fit a
single cycle.
timeCat :: [(Time, Pattern a)] -> Pattern a Source #
Similar to fastCat
, but each pattern is given a relative duration
Manipulating time
(<~) :: Pattern Time -> Pattern a -> Pattern a Source #
Shifts a pattern back in time by the given amount, expressed in cycles
(~>) :: Pattern Time -> Pattern a -> Pattern a Source #
Shifts a pattern forward in time by the given amount, expressed in cycles
fastSqueeze :: Pattern Time -> Pattern a -> Pattern a Source #
Slow down a pattern by the factors in the given time pattern, squeezing
the pattern to fit the slot given in the time pattern
slow :: Pattern Time -> Pattern a -> Pattern a Source #
Slow down a pattern by the given time pattern
slowSqueeze :: Pattern Time -> Pattern a -> Pattern a Source #
Slow down a pattern by the factors in the given time pattern, squeezing
the pattern to fit the slot given in the time pattern
rev :: Pattern a -> Pattern a Source #
rev p
returns p
with the event positions in each cycle
reversed (or mirrored).
zoom :: (Time, Time) -> Pattern a -> Pattern a Source #
Plays a portion of a pattern, specified by a time arc (start and end time). The new resulting pattern is played over the time period of the original pattern:
d1 $ zoom (0.25, 0.75) $ sound "bd*2 hh*3 [sn bd]*2 drum"
In the pattern above, zoom
is used with an arc from 25% to 75%. It is equivalent to this pattern:
d1 $ sound "hh*3 [sn bd]*2"
fastGap :: Pattern Time -> Pattern a -> Pattern a Source #
fastGap
is similar to fast
but maintains its cyclic
alignment. For example, fastGap 2 p
would squash the events in
pattern p
into the first half of each cycle (and the second
halves would be empty). The factor should be at least 1
every :: Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
- Higher order functions
Functions which work on other functions (higher order functions)
every n f p
applies the function f
to p
, but only affects
every n
cycles.
every' :: Pattern Int -> Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
every n o f'
is like every n f
with an offset of o
cycles
foldEvery :: [Int] -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
foldEvery ns f p
applies the function f
to p
, and is applied for
each cycle in ns
.
when :: (Int -> Bool) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
Only when
the given test function returns True
the given pattern
transformation is applied. The test function will be called with the
current cycle as a number.
d1 $ when ((elem '4').show) (striate 4) $ sound "hh hc"
The above will only apply `striate 4` to the pattern if the current cycle number contains the number 4. So the fourth cycle will be striated and the fourteenth and so on. Expect lots of striates after cycle number 399.