tidal-1.0.0: Pattern language for improvised music

Safe HaskellSafe
LanguageHaskell2010

Sound.Tidal.Pattern

Contents

Synopsis

Types

type Time = Rational Source #

Time is rational

type Arc = (Time, Time) Source #

A time arc (start and end)

type Part = (Arc, Arc) Source #

The second arc (the part) should be equal to or fit inside the first one (the whole that it's a part of).

type Event a = (Part, a) Source #

An event is a value that's active during a timespan

data State Source #

Constructors

State 

Fields

type Query a = State -> [Event a] Source #

A function that represents events taking place over time

data Nature Source #

Also known as Continuous vs Discrete/Amorphous vs Pulsating etc.

Constructors

Analog 
Digital 
Instances
Eq Nature Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

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

data Pattern a Source #

A datatype that's basically a query, plus a hint about whether its events are Analogue or Digital by nature

Constructors

Pattern 

Fields

Instances
Monad Pattern Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(>>=) :: Pattern a -> (a -> Pattern b) -> Pattern b #

(>>) :: Pattern a -> Pattern b -> Pattern b #

return :: a -> Pattern a #

fail :: String -> Pattern a #

Functor Pattern Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

fmap :: (a -> b) -> Pattern a -> Pattern b #

(<$) :: a -> Pattern b -> Pattern a #

Applicative Pattern Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

pure :: a -> Pattern a #

(<*>) :: Pattern (a -> b) -> Pattern a -> Pattern b #

liftA2 :: (a -> b -> c) -> Pattern a -> Pattern b -> Pattern c #

(*>) :: Pattern a -> Pattern b -> Pattern b #

(<*) :: Pattern a -> Pattern b -> Pattern a #

Enum a => Enum (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

succ :: Pattern a -> Pattern a #

pred :: Pattern a -> Pattern a #

toEnum :: Int -> Pattern a #

fromEnum :: Pattern a -> Int #

enumFrom :: Pattern a -> [Pattern a] #

enumFromThen :: Pattern a -> Pattern a -> [Pattern a] #

enumFromTo :: Pattern a -> Pattern a -> [Pattern a] #

enumFromThenTo :: Pattern a -> Pattern a -> Pattern a -> [Pattern a] #

Eq (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(==) :: Pattern a -> Pattern a -> Bool #

(/=) :: Pattern a -> Pattern a -> Bool #

Floating a => Floating (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

pi :: Pattern a #

exp :: Pattern a -> Pattern a #

log :: Pattern a -> Pattern a #

sqrt :: Pattern a -> Pattern a #

(**) :: Pattern a -> Pattern a -> Pattern a #

logBase :: Pattern a -> Pattern a -> Pattern a #

sin :: Pattern a -> Pattern a #

cos :: Pattern a -> Pattern a #

tan :: Pattern a -> Pattern a #

asin :: Pattern a -> Pattern a #

acos :: Pattern a -> Pattern a #

atan :: Pattern a -> Pattern a #

sinh :: Pattern a -> Pattern a #

cosh :: Pattern a -> Pattern a #

tanh :: Pattern a -> Pattern a #

asinh :: Pattern a -> Pattern a #

acosh :: Pattern a -> Pattern a #

atanh :: Pattern a -> Pattern a #

log1p :: Pattern a -> Pattern a #

expm1 :: Pattern a -> Pattern a #

log1pexp :: Pattern a -> Pattern a #

log1mexp :: Pattern a -> Pattern a #

Fractional a => Fractional (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(/) :: Pattern a -> Pattern a -> Pattern a #

recip :: Pattern a -> Pattern a #

fromRational :: Rational -> Pattern a #

Integral a => Integral (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

quot :: Pattern a -> Pattern a -> Pattern a #

rem :: Pattern a -> Pattern a -> Pattern a #

div :: Pattern a -> Pattern a -> Pattern a #

mod :: Pattern a -> Pattern a -> Pattern a #

quotRem :: Pattern a -> Pattern a -> (Pattern a, Pattern a) #

divMod :: Pattern a -> Pattern a -> (Pattern a, Pattern a) #

toInteger :: Pattern a -> Integer #

Num a => Num (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(+) :: Pattern a -> Pattern a -> Pattern a #

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

(*) :: Pattern a -> Pattern a -> Pattern a #

negate :: Pattern a -> Pattern a #

abs :: Pattern a -> Pattern a #

signum :: Pattern a -> Pattern a #

fromInteger :: Integer -> Pattern a #

Ord a => Ord (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

compare :: Pattern a -> Pattern a -> Ordering #

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

(<=) :: Pattern a -> Pattern a -> Bool #

(>) :: Pattern a -> Pattern a -> Bool #

(>=) :: Pattern a -> Pattern a -> Bool #

max :: Pattern a -> Pattern a -> Pattern a #

min :: Pattern a -> Pattern a -> Pattern a #

(Num a, Ord a) => Real (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toRational :: Pattern a -> Rational #

RealFloat a => RealFloat (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

RealFrac a => RealFrac (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

properFraction :: Integral b => Pattern a -> (b, Pattern a) #

truncate :: Integral b => Pattern a -> b #

round :: Integral b => Pattern a -> b #

ceiling :: Integral b => Pattern a -> b #

floor :: Integral b => Pattern a -> b #

Show a => Show (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

show :: Pattern a -> String #

showList :: [Pattern a] -> ShowS #

(Enumerable a, Parseable a) => IsString (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Parse

Methods

fromString :: String -> Pattern a #

data Value Source #

Constructors

VS 

Fields

VF 

Fields

VI 

Fields

Instances
Eq Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

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

Fractional ControlMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

Data Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value #

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

Num ControlMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

Ord Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

compare :: Value -> Value -> Ordering #

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

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

(>) :: Value -> Value -> Bool #

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

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

Show ControlMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

Show Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

TolerantEq ControlMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

TolerantEq Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(~==) :: Value -> Value -> Bool Source #

Unionable ControlMap Source # 
Instance details

Defined in Sound.Tidal.Core

TolerantEq (Event ControlMap) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Instances

(<*) :: Pattern (a -> b) -> Pattern a -> Pattern b infixl 4 Source #

Like *, but the structure only comes from the left

(*>) :: Pattern (a -> b) -> Pattern a -> Pattern b infixl 4 Source #

Like *, but the structure only comes from the right

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

Turns a pattern of patterns into a single pattern. (this is actually join)

1/ For query arc, get the events from the outer pattern pp 2/ Query the inner pattern using the part of the outer 3/ For each inner event, set the whole and part to be the intersection of the outer whole and part, respectively 4 Concatenate all the events together (discarding wholesparts that didn't intersect)

TODO - what if a continuous pattern contains a discrete one, or vice-versa?

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

Turns a pattern of patterns into a single pattern. Like unwrap, but structure only comes from the inner pattern.

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

Turns a pattern of patterns into a single pattern. Like unwrap, but structure only comes from the outer pattern.

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

Like unwrap, but cycles of the inner patterns are compressed to fit the timespan of the outer whole (or the original query if it's a continuous pattern?) TODO - what if a continuous pattern contains a discrete one, or vice-versa?

class TolerantEq a where Source #

Methods

(~==) :: a -> a -> Bool Source #

Instances
TolerantEq ControlMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

TolerantEq Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(~==) :: Value -> Value -> Bool Source #

TolerantEq a => TolerantEq [a] Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(~==) :: [a] -> [a] -> Bool Source #

TolerantEq (Event ControlMap) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Internal functions

queryArc :: Pattern a -> Arc -> [Event a] Source #

eventWhole :: Event a -> Arc Source #

Get the timespan of an event's whole

eventWholeOnset :: Event a -> Time Source #

Get the onset of an event's whole

eventPart :: Event a -> Arc Source #

Get the timespan of an event's part

arcCycles :: Arc -> [Arc] Source #

Splits the given Arc into a list of Arcs, at cycle boundaries.

arcCyclesZW :: Arc -> [Arc] Source #

Like arcCycles, but returns zero-width arcs

mapArc :: (Time -> Time) -> Arc -> Arc Source #

Map the given function over both the start and end Time values of the given Arc.

mapCycle :: (Time -> Time) -> Arc -> Arc Source #

Similar to mapArc but time is relative to the cycle (i.e. the sam of the start of the arc)

splitQueries :: Pattern a -> Pattern a Source #

Splits queries that span cycles. For example `query p (0.5, 1.5)` would be turned into two queries, `(0.5,1)` and `(1,1.5)`, and the results combined. Being able to assume queries don't span cycles often makes transformations easier to specify.

sam :: Time -> Time Source #

The sam (start of cycle) for the given time value

toTime :: Real a => a -> Rational Source #

Turns a number into a (rational) time value. An alias for toRational.

nextSam :: Time -> Time Source #

The end point of the current cycle (and starting point of the next cycle)

cyclePos :: Time -> Time Source #

The position of a time value relative to the start of its cycle.

isIn :: Arc -> Time -> Bool Source #

isIn a t is True if t is inside the arc represented by a.

onsetIn :: Arc -> Event a -> Bool Source #

True if an Event's starts is within given Arc

subArc :: Arc -> Arc -> Maybe Arc Source #

subArc i j is the timespan that is the intersection of i and j. The definition is a bit fiddly as results might be zero-width, but not at the end of an non-zero-width arc - e.g. (0,1) and (1,2) do not intersect, but (1,1) (1,1) does.

timeToCycleArc :: Time -> Arc Source #

The arc of the whole cycle that the given time value falls within

cyclesInArc :: Integral a => Arc -> [a] Source #

A list of cycle numbers which are included in the given arc

cycleArcsInArc :: Arc -> [Arc] Source #

A list of arcs of the whole cycles which are included in the given arc

withResultArc :: (Arc -> Arc) -> Pattern a -> Pattern a Source #

Apply a function to the arcs/timespans (both whole and parts) of the result

withResultTime :: (Time -> Time) -> Pattern a -> Pattern a Source #

Apply a function to the time (both start and end of the timespans of both whole and parts) of the result

withQueryArc :: (Arc -> Arc) -> Pattern a -> Pattern a Source #

Apply a function to the timespan of the query

withQueryTime :: (Time -> Time) -> Pattern a -> Pattern a Source #

Apply a function to the time (both start and end) of the query

withEvent :: (Event a -> Event b) -> Pattern a -> Pattern b Source #

withEvent f p returns a new Pattern with each event mapped over function f.

withEvents :: ([Event a] -> [Event b]) -> Pattern a -> Pattern b Source #

withEvent f p returns a new Pattern with f applied to the resulting list of events for each query function f.

withPart :: (Arc -> Arc) -> Pattern a -> Pattern a Source #

withPart f p returns a new Pattern with function f applied to the part.

compareDefrag :: (Eq a, Ord a) => [Event a] -> [Event a] -> Bool Source #

Compares two lists of events, attempting to combine fragmented events in the process for a truer compare

defragParts :: Eq a => [Event a] -> [Event a] Source #

Returns a list of events, with any adjacent parts of the same whole combined

isAdjacent :: Eq a => Event a -> Event a -> Bool Source #

Returns True if the two given events are adjacent parts of the same whole

applyFIS :: (Double -> Double) -> (Int -> Int) -> (String -> String) -> Value -> Value Source #

Apply one of three functions to a Value, depending on its type

fNum2 :: (Int -> Int -> Int) -> (Double -> Double -> Double) -> Value -> Value -> Value Source #

Apply one of two functions to a Value, depending on its type (int or float; strings are ignored)

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

Shifts a pattern back in time by the given amount, expressed in cycles

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

Shifts a pattern forward in time by the given amount, expressed in cycles

Event filters

filterValues :: (a -> Bool) -> Pattern a -> Pattern a Source #

Remove events from patterns that to not meet the given test

filterJust :: Pattern (Maybe a) -> Pattern a Source #

Turns a pattern of Maybe values in to a pattern of values, dropping the events of Nothing.

Temporal parameter helpers

tParam :: (a -> Pattern b -> Pattern c) -> Pattern a -> Pattern b -> Pattern c Source #

tParam2 :: (a -> b -> Pattern c -> Pattern d) -> Pattern a -> Pattern b -> Pattern c -> Pattern d Source #

tParam3 :: (a -> b -> c -> Pattern d -> Pattern e) -> Pattern a -> Pattern b -> Pattern c -> Pattern d -> Pattern e Source #

tParamSqueeze :: (a -> Pattern b -> Pattern c) -> Pattern a -> Pattern b -> Pattern c Source #

Orphan instances

Show Part Source # 
Instance details

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

Show Arc Source # 
Instance details

Methods

showsPrec :: Int -> Arc -> ShowS #

show :: Arc -> String #

showList :: [Arc] -> ShowS #

Show a => Show (Event a) Source # 
Instance details

Methods

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

show :: Event a -> String #

showList :: [Event a] -> ShowS #