tidal-1.6.1: Pattern language for improvised music
Safe HaskellSafe
LanguageHaskell2010

Sound.Tidal.Pattern

Synopsis

Types

type Time = Rational Source #

Time is rational

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.

data ArcF a Source #

An arc of time, with a start time (or onset) and a stop time (or offset)

Constructors

Arc 

Fields

Instances

Instances details
Functor ArcF Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

fmap :: (a -> b) -> ArcF a -> ArcF b

(<$) :: a -> ArcF b -> ArcF a

Show Arc 
Instance details

Defined in Sound.Tidal.Show

Methods

showsPrec :: Int -> Arc -> ShowS

show :: Arc -> String #

showList :: [Arc] -> ShowS

Applicative ArcF Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

pure :: a -> ArcF a

(<*>) :: ArcF (a -> b) -> ArcF a -> ArcF b

liftA2 :: (a -> b -> c) -> ArcF a -> ArcF b -> ArcF c

(*>) :: ArcF a -> ArcF b -> ArcF b

(<*) :: ArcF a -> ArcF b -> ArcF a

Eq a => Eq (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(==) :: ArcF a -> ArcF a -> Bool

(/=) :: ArcF a -> ArcF a -> Bool

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

Defined in Sound.Tidal.Pattern

Methods

(/) :: ArcF a -> ArcF a -> ArcF a

recip :: ArcF a -> ArcF a

fromRational :: Rational -> ArcF a

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

Defined in Sound.Tidal.Pattern

Methods

(+) :: ArcF a -> ArcF a -> ArcF a

(-) :: ArcF a -> ArcF a -> ArcF a

(*) :: ArcF a -> ArcF a -> ArcF a

negate :: ArcF a -> ArcF a

abs :: ArcF a -> ArcF a

signum :: ArcF a -> ArcF a

fromInteger :: Integer -> ArcF a

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

Defined in Sound.Tidal.Pattern

Methods

compare :: ArcF a -> ArcF a -> Ordering

(<) :: ArcF a -> ArcF a -> Bool

(<=) :: ArcF a -> ArcF a -> Bool

(>) :: ArcF a -> ArcF a -> Bool

(>=) :: ArcF a -> ArcF a -> Bool

max :: ArcF a -> ArcF a -> ArcF a

min :: ArcF a -> ArcF a -> ArcF a

Show a => Show (Event a) 
Instance details

Defined in Sound.Tidal.Show

Methods

showsPrec :: Int -> Event a -> ShowS

show :: Event a -> String #

showList :: [Event a] -> ShowS

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

Defined in Sound.Tidal.Pattern

Methods

showsPrec :: Int -> ArcF a -> ShowS

show :: ArcF a -> String #

showList :: [ArcF a] -> ShowS

Generic (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Associated Types

type Rep (ArcF a) :: Type -> Type

Methods

from :: ArcF a -> Rep (ArcF a) x

to :: Rep (ArcF a) x -> ArcF a

NFData a => NFData (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

rnf :: ArcF a -> ()

TolerantEq (Event ControlMap) Source # 
Instance details

Defined in Sound.Tidal.Pattern

type Rep (ArcF a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

type Rep (ArcF a) = D1 ('MetaData "ArcF" "Sound.Tidal.Pattern" "tidal-1.6.1-ErpW3ZkXJtABh2hIrLNXFQ" 'False) (C1 ('MetaCons "Arc" 'PrefixI 'True) (S1 ('MetaSel ('Just "start") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "stop") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

sect :: Arc -> Arc -> Arc Source #

hull :: Arc -> Arc -> Arc Source #

convex hull union

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

subArc i j is the timespan that is the intersection of i and j. intersection 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.

subMaybeArc :: Maybe Arc -> Maybe Arc -> Maybe (Maybe Arc) Source #

timeToCycleArc :: Time -> Arc Source #

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

cycleArc :: Arc -> Arc Source #

Shifts an arc to the equivalent one that starts during cycle zero

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

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

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

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

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

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

data Context Source #

Constructors

Context 

Fields

Instances

Instances details
Eq Context Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(==) :: Context -> Context -> Bool

(/=) :: Context -> Context -> Bool

Ord Context Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

compare :: Context -> Context -> Ordering

(<) :: Context -> Context -> Bool

(<=) :: Context -> Context -> Bool

(>) :: Context -> Context -> Bool

(>=) :: Context -> Context -> Bool

max :: Context -> Context -> Context

min :: Context -> Context -> Context

Show Context 
Instance details

Defined in Sound.Tidal.Show

Methods

showsPrec :: Int -> Context -> ShowS

show :: Context -> String #

showList :: [Context] -> ShowS

Generic Context Source # 
Instance details

Defined in Sound.Tidal.Pattern

Associated Types

type Rep Context :: Type -> Type

Methods

from :: Context -> Rep Context x

to :: Rep Context x -> Context

NFData Context Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

rnf :: Context -> ()

type Rep Context Source # 
Instance details

Defined in Sound.Tidal.Pattern

type Rep Context = D1 ('MetaData "Context" "Sound.Tidal.Pattern" "tidal-1.6.1-ErpW3ZkXJtABh2hIrLNXFQ" 'False) (C1 ('MetaCons "Context" 'PrefixI 'True) (S1 ('MetaSel ('Just "contextPosition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [((Int, Int), (Int, Int))])))

deltaContext :: Int -> Int -> Pattern a -> Pattern a Source #

data EventF a b Source #

An event is a value that's active during a timespan. If a whole is present, the part should be equal to or fit inside it.

Constructors

Event 

Fields

Instances

Instances details
Functor (EventF a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

fmap :: (a0 -> b) -> EventF a a0 -> EventF a b

(<$) :: a0 -> EventF a b -> EventF a a0

Show a => Show (Event a) 
Instance details

Defined in Sound.Tidal.Show

Methods

showsPrec :: Int -> Event a -> ShowS

show :: Event a -> String #

showList :: [Event a] -> ShowS

TolerantEq (Event ControlMap) Source # 
Instance details

Defined in Sound.Tidal.Pattern

(Eq a, Eq b) => Eq (EventF a b) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(==) :: EventF a b -> EventF a b -> Bool

(/=) :: EventF a b -> EventF a b -> Bool

(Ord a, Ord b) => Ord (EventF a b) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

compare :: EventF a b -> EventF a b -> Ordering

(<) :: EventF a b -> EventF a b -> Bool

(<=) :: EventF a b -> EventF a b -> Bool

(>) :: EventF a b -> EventF a b -> Bool

(>=) :: EventF a b -> EventF a b -> Bool

max :: EventF a b -> EventF a b -> EventF a b

min :: EventF a b -> EventF a b -> EventF a b

Generic (EventF a b) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Associated Types

type Rep (EventF a b) :: Type -> Type

Methods

from :: EventF a b -> Rep (EventF a b) x

to :: Rep (EventF a b) x -> EventF a b

(NFData a, NFData b) => NFData (EventF a b) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

rnf :: EventF a b -> ()

type Rep (EventF a b) Source # 
Instance details

Defined in Sound.Tidal.Pattern

type Rep (EventF a b) = D1 ('MetaData "EventF" "Sound.Tidal.Pattern" "tidal-1.6.1-ErpW3ZkXJtABh2hIrLNXFQ" 'False) (C1 ('MetaCons "Event" 'PrefixI 'True) ((S1 ('MetaSel ('Just "context") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Context) :*: S1 ('MetaSel ('Just "whole") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))) :*: (S1 ('MetaSel ('Just "part") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))))

type Event a = EventF (ArcF Time) a Source #

isAnalog :: Event a -> Bool Source #

isDigital :: Event a -> Bool Source #

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

True if an Event's starts is within given Arc

compareDefrag :: 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

wholeStart :: Event a -> Time Source #

Get the onset of an event's whole

wholeStop :: Event a -> Time Source #

Get the offset of an event's whole

eventPartStart :: Event a -> Time Source #

Get the onset of an event's whole

eventPartStop :: Event a -> Time Source #

Get the offset of an event's part

eventPart :: Event a -> Arc Source #

Get the timespan of an event's part

toEvent :: (((Time, Time), (Time, Time)), a) -> Event a Source #

data State Source #

an Arc and some named control values

Constructors

State 

Fields

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

A function that represents events taking place over time

data Pattern a Source #

A datatype that's basically a query

Constructors

Pattern 

Fields

Instances

Instances details
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

Functor Pattern Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

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

IsString ControlPattern 
Instance details

Defined in Sound.Tidal.Simple

Methods

fromString :: String -> ControlPattern

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

Methods

floatRadix :: Pattern a -> Integer

floatDigits :: Pattern a -> Int

floatRange :: Pattern a -> (Int, Int)

decodeFloat :: Pattern a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Pattern a

exponent :: Pattern a -> Int

significand :: Pattern a -> Pattern a

scaleFloat :: Int -> Pattern a -> Pattern a

isNaN :: Pattern a -> Bool

isInfinite :: Pattern a -> Bool

isDenormalized :: Pattern a -> Bool

isNegativeZero :: Pattern a -> Bool

isIEEE :: Pattern a -> Bool

atan2 :: Pattern a -> Pattern a -> Pattern a

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) 
Instance details

Defined in Sound.Tidal.Show

Methods

showsPrec :: Int -> Pattern a -> ShowS

show :: Pattern a -> String #

showList :: [Pattern a] -> ShowS

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

Defined in Sound.Tidal.ParseBP

Methods

fromString :: String -> Pattern a

Generic (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Associated Types

type Rep (Pattern a) :: Type -> Type

Methods

from :: Pattern a -> Rep (Pattern a) x

to :: Rep (Pattern a) x -> Pattern a

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

Defined in Sound.Tidal.Pattern

Methods

rnf :: Pattern a -> ()

type Rep (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

type Rep (Pattern a) = D1 ('MetaData "Pattern" "Sound.Tidal.Pattern" "tidal-1.6.1-ErpW3ZkXJtABh2hIrLNXFQ" 'False) (C1 ('MetaCons "Pattern" 'PrefixI 'True) (S1 ('MetaSel ('Just "query") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Query a))))

data Value Source #

Constructors

VS 

Fields

VF 

Fields

VR 

Fields

VI 

Fields

VB 

Fields

VX 

Fields

Instances

Instances details
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 :: forall r r'. (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 
Instance details

Defined in Sound.Tidal.Show

Methods

showsPrec :: Int -> ControlMap -> ShowS

show :: ControlMap -> String #

showList :: [ControlMap] -> ShowS

Show Value 
Instance details

Defined in Sound.Tidal.Show

Methods

showsPrec :: Int -> Value -> ShowS

show :: Value -> String #

showList :: [Value] -> ShowS

IsString ControlPattern 
Instance details

Defined in Sound.Tidal.Simple

Methods

fromString :: String -> ControlPattern

Generic Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

Associated Types

type Rep Value :: Type -> Type

Methods

from :: Value -> Rep Value x

to :: Rep Value x -> Value

NFData Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

rnf :: Value -> ()

TolerantEq ControlMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

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

type Rep Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

type Rep Value = D1 ('MetaData "Value" "Sound.Tidal.Pattern" "tidal-1.6.1-ErpW3ZkXJtABh2hIrLNXFQ" 'False) ((C1 ('MetaCons "VS" 'PrefixI 'True) (S1 ('MetaSel ('Just "svalue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "VF" 'PrefixI 'True) (S1 ('MetaSel ('Just "fvalue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "VR" 'PrefixI 'True) (S1 ('MetaSel ('Just "rvalue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)))) :+: (C1 ('MetaCons "VI" 'PrefixI 'True) (S1 ('MetaSel ('Just "ivalue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "VB" 'PrefixI 'True) (S1 ('MetaSel ('Just "bvalue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "VX" 'PrefixI 'True) (S1 ('MetaSel ('Just "xvalue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Word8])))))

class Valuable a where Source #

Methods

toValue :: a -> Value Source #

Instances

Instances details
Valuable Bool Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: Bool -> Value Source #

Valuable Double Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: Double -> Value Source #

Valuable Int Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: Int -> Value Source #

Valuable Rational Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: Rational -> Value Source #

Valuable String Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: String -> Value Source #

Valuable [Word8] Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: [Word8] -> Value Source #

type StateMap = Map String (Pattern Value) Source #

type ControlMap = Map String Value Source #

Instances

applyPatToPat :: (Maybe Arc -> Maybe Arc -> Maybe (Maybe Arc)) -> Pattern (a -> b) -> Pattern a -> Pattern b Source #

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

Like *, but the wholes come from the left

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

Like *, but the wholes come 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.

squeezeJoin :: 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?

noOv :: String -> a Source #

class TolerantEq a where Source #

Methods

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

Instances

Instances details
TolerantEq ControlMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

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 #

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.

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.

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 and rationals are ignored)

getI :: Value -> Maybe Int Source #

getF :: Value -> Maybe Double Source #

getS :: Value -> Maybe String Source #

getB :: Value -> Maybe Bool Source #

getR :: Value -> Maybe Rational Source #

getBlob :: Value -> Maybe [Word8] Source #

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 into a pattern of values, dropping the events of Nothing.

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

filterEvents :: (Event a -> Bool) -> Pattern a -> Pattern a Source #

Temporal parameter helpers

tParam :: (t1 -> t2 -> Pattern a) -> Pattern t1 -> t2 -> Pattern a Source #

tParam2 :: (a -> b -> c -> Pattern d) -> Pattern a -> Pattern b -> 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 #

matchManyToOne :: (b -> a -> Bool) -> Pattern a -> Pattern b -> Pattern (Bool, b) Source #

Mark values in the first pattern which match with at least one value in the second pattern.