tidal-1.7.5: Pattern language for improvised music
Safe HaskellNone
LanguageHaskell2010

Sound.Tidal.Core

Synopsis

Elemental patterns

silence :: Pattern a Source #

An empty pattern

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 - unipolar sinewave. A pattern of continuous values following a sinewave with frequency of one cycle, and amplitude from 0 to 1.

sine2 :: Fractional a => Pattern a Source #

sine2 - bipolar sinewave. A pattern of continuous values following a sinewave with frequency of one cycle, and amplitude from -1 to 1.

cosine :: Fractional a => Pattern a Source #

cosine - unipolar cosine wave. A pattern of continuous values following a cosine with frequency of one cycle, and amplitude from 0 to 1. Equivalent to `0.25 ~> sine`.

cosine2 :: Fractional a => Pattern a Source #

cosine2 - bipolar cosine wave. A pattern of continuous values following a cosine with frequency of one cycle, and amplitude from -1 to 1. Equivalent to `0.25 ~> sine2`.

saw :: (Fractional a, Real a) => Pattern a Source #

saw - unipolar ascending sawtooth wave. A pattern of continuous values following a sawtooth with frequency of one cycle, and amplitude from 0 to 1.

saw2 :: (Fractional a, Real a) => Pattern a Source #

saw2 - bipolar ascending sawtooth wave. A pattern of continuous values following a sawtooth with frequency of one cycle, and amplitude from -1 to 1.

isaw :: (Fractional a, Real a) => Pattern a Source #

isaw like saw, but a descending (inverse) sawtooth.

isaw2 :: (Fractional a, Real a) => Pattern a Source #

isaw2 like saw2, but a descending (inverse) sawtooth.

tri :: (Fractional a, Real a) => Pattern a Source #

tri - unipolar triangle wave. A pattern of continuous values following a triangle wave with frequency of one cycle, and amplitude from 0 to 1.

tri2 :: (Fractional a, Real a) => Pattern a Source #

tri2 - bipolar triangle wave. A pattern of continuous values following a triangle wave with frequency of one cycle, and amplitude from -1 to 1.

square :: Fractional a => Pattern a Source #

square - unipolar square wave. A pattern of continuous values following a square wave with frequency of one cycle, and amplitude from 0 to 1. | square is like sine, for square waves.

square2 :: Fractional a => Pattern a Source #

square2 - bipolar square wave. A pattern of continuous values following a square wave with frequency of one cycle, and amplitude from -1 to 1.

envL :: Pattern Double Source #

envL is a Pattern of continuous Double values, representing a linear interpolation between 0 and 1 during the first cycle, then staying constant at 1 for all following cycles. Possibly only useful if you're using something like the retrig function defined in tidal.el.

envLR :: Pattern Double Source #

like envL but reversed.

envEq :: Pattern Double Source #

'Equal power' version of env, for gain-based transitions

envEqR :: Pattern Double Source #

Equal power reversed

Pattern algebra

class Unionable a where Source #

Methods

union :: a -> a -> a Source #

Instances

Instances details
Unionable a Source # 
Instance details

Defined in Sound.Tidal.Core

Methods

union :: a -> a -> a Source #

Unionable ValueMap Source # 
Instance details

Defined in Sound.Tidal.Core

(|+|) :: (Applicative a, Num b) => a b -> a b -> a b Source #

(|+) :: Num a => Pattern a -> Pattern a -> Pattern a Source #

(+|) :: Num a => Pattern a -> Pattern a -> Pattern a Source #

(|/|) :: (Applicative a, Fractional b) => a b -> a b -> a b Source #

(|*|) :: (Applicative a, Num b) => a b -> a b -> a b Source #

(|*) :: Num a => Pattern a -> Pattern a -> Pattern a Source #

(*|) :: Num a => Pattern a -> Pattern a -> Pattern a Source #

(|-|) :: (Applicative a, Num b) => a b -> a b -> a b Source #

(|-) :: Num a => Pattern a -> Pattern a -> Pattern a Source #

(-|) :: Num a => Pattern a -> Pattern a -> Pattern a Source #

(|%|) :: (Applicative a, Real b) => a b -> a b -> a b Source #

(|%) :: Real a => Pattern a -> Pattern a -> Pattern a Source #

(%|) :: Real a => Pattern a -> Pattern a -> Pattern a 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 all of them per cycle.

listToPat :: [a] -> Pattern a Source #

A synonym for fastFromList

fromMaybes :: [Maybe a] -> Pattern a Source #

'fromMaybes; is similar to fromList, but allows values to be optional using the Maybe type, so that Nothing results in gaps in the pattern.

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.

_run :: (Enum a, Num a) => a -> Pattern a Source #

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

_scan :: (Enum a, Num a) => a -> Pattern a Source #

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.

slowCat :: [Pattern a] -> Pattern a Source #

Alias for cat

slowAppend :: Pattern a -> Pattern a -> Pattern a Source #

Alias for append

fastAppend :: Pattern a -> Pattern a -> Pattern a Source #

Like append, but twice as fast

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

overlay :: Pattern a -> Pattern a -> Pattern a Source #

overlay combines two Patterns into a new pattern, so that their events are combined over time.

(<>) :: Pattern a -> Pattern a -> Pattern a Source #

An infix alias of overlay

stack :: [Pattern a] -> Pattern a Source #

stack combines a list of Patterns into a new pattern, so that their events are combined over time.

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

fast :: Pattern Time -> Pattern a -> Pattern a Source #

Speed up a pattern by the given time pattern

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

density :: Pattern Time -> Pattern a -> Pattern a Source #

An alias for fast

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

sparsity :: Pattern Time -> Pattern a -> Pattern a Source #

An alias for slow

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

densityGap :: Pattern Time -> Pattern a -> Pattern a Source #

An alias for fastGap

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 :: Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

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

_every' :: Int -> Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

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.

whenT :: (Time -> Bool) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

Like when, but works on continuous time values rather than cycle numbers.

_getP :: a -> (Value -> Maybe a) -> Pattern Value -> Pattern a Source #

_cX :: a -> (Value -> Maybe a) -> String -> Pattern a Source #

_cX_ :: (Value -> Maybe a) -> String -> Pattern a Source #