tidal-1.9.5: Pattern language for improvised music
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Tidal.Pattern

Synopsis

Documentation

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

data State Source #

an Arc and some named control values

Constructors

State 

Fields

data Pattern a Source #

A datatype representing events taking place over time

Constructors

Pattern 

Fields

Instances

Instances details
IsString ControlPattern Source # 
Instance details

Defined in Sound.Tidal.Simple

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 #

Functor Pattern Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

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

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 #

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

Defined in Sound.Tidal.ParseBP

Methods

fromString :: String -> Pattern a #

Monoid (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

mempty :: Pattern a #

mappend :: Pattern a -> Pattern a -> Pattern a #

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

Semigroup (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

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

stimes :: Integral b => b -> Pattern a -> 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] #

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 #

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

Defined in Sound.Tidal.Pattern

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 #

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 #

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, Ord a) => Real (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toRational :: Pattern a -> Rational #

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.Show

Methods

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

show :: Pattern a -> String #

showList :: [Pattern a] -> ShowS #

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

Defined in Sound.Tidal.Pattern

Methods

rnf :: Pattern a -> () #

Eq (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

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

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 #

Stringy (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

type Rep (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

type Rep (Pattern a) = D1 ('MetaData "Pattern" "Sound.Tidal.Pattern" "tidal-1.9.5-7AHiE4IEnHeHqbwX3gka7l" 'False) (C1 ('MetaCons "Pattern" 'PrefixI 'True) (S1 ('MetaSel ('Just "query") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (State -> [Event a]))))

data Context Source #

Some context for an event, currently just position within sourcecode

Constructors

Context 

Fields

Instances

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

Show Context Source # 
Instance details

Defined in Sound.Tidal.Show

NFData Context Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

rnf :: Context -> () #

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

type Rep Context Source # 
Instance details

Defined in Sound.Tidal.Pattern

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

class Moddable a where Source #

Methods

gmod :: a -> a -> a Source #

Instances

Instances details
Moddable Rational Source # 
Instance details

Defined in Sound.Tidal.Pattern

Moddable Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

gmod :: Note -> Note -> Note Source #

Moddable ValueMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

Moddable Double Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

gmod :: Double -> Double -> Double Source #

Moddable Int Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

gmod :: Int -> Int -> Int Source #

newtype Note Source #

Note is Double, but with a different parser

Constructors

Note 

Fields

Instances

Instances details
Data Note 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) -> Note -> c Note #

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

toConstr :: Note -> Constr #

dataTypeOf :: Note -> DataType #

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

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

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

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

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

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

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

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

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

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

Enum Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

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] #

Floating Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

pi :: Note #

exp :: Note -> Note #

log :: Note -> Note #

sqrt :: Note -> Note #

(**) :: Note -> Note -> Note #

logBase :: Note -> Note -> Note #

sin :: Note -> Note #

cos :: Note -> Note #

tan :: Note -> Note #

asin :: Note -> Note #

acos :: Note -> Note #

atan :: Note -> Note #

sinh :: Note -> Note #

cosh :: Note -> Note #

tanh :: Note -> Note #

asinh :: Note -> Note #

acosh :: Note -> Note #

atanh :: Note -> Note #

log1p :: Note -> Note #

expm1 :: Note -> Note #

log1pexp :: Note -> Note #

log1mexp :: Note -> Note #

Generic Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Associated Types

type Rep Note :: Type -> Type #

Methods

from :: Note -> Rep Note x #

to :: Rep Note x -> Note #

Num Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(+) :: Note -> Note -> Note #

(-) :: Note -> Note -> Note #

(*) :: Note -> Note -> Note #

negate :: Note -> Note #

abs :: Note -> Note #

signum :: Note -> Note #

fromInteger :: Integer -> Note #

Fractional Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

(/) :: Note -> Note -> Note #

recip :: Note -> Note #

fromRational :: Rational -> Note #

Real Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toRational :: Note -> Rational #

RealFrac Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

properFraction :: Integral b => Note -> (b, Note) #

truncate :: Integral b => Note -> b #

round :: Integral b => Note -> b #

ceiling :: Integral b => Note -> b #

floor :: Integral b => Note -> b #

Show Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

NFData Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

rnf :: Note -> () #

Eq Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

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

Ord Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

compare :: Note -> Note -> Ordering #

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

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

(>) :: Note -> Note -> Bool #

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

max :: Note -> Note -> Note #

min :: Note -> Note -> Note #

Enumerable Note Source # 
Instance details

Defined in Sound.Tidal.ParseBP

Parseable Note Source # 
Instance details

Defined in Sound.Tidal.ParseBP

Moddable Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

gmod :: Note -> Note -> Note Source #

Valuable Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: Note -> Value Source #

type Rep Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

type Rep Note = D1 ('MetaData "Note" "Sound.Tidal.Pattern" "tidal-1.9.5-7AHiE4IEnHeHqbwX3gka7l" 'True) (C1 ('MetaCons "Note" 'PrefixI 'True) (S1 ('MetaSel ('Just "unNote") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))

data Value Source #

Polymorphic values

Constructors

VS 

Fields

VF 

Fields

VN 

Fields

VR 

Fields

VI 

Fields

VB 

Fields

VX 

Fields

VPattern 

Fields

VList 

Fields

VState 

Instances

Instances details
IsString ControlPattern Source # 
Instance details

Defined in Sound.Tidal.Simple

Floating ValueMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

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 #

Num ValueMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

Fractional ValueMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

Show Value Source # 
Instance details

Defined in Sound.Tidal.Show

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Show ValueMap Source # 
Instance details

Defined in Sound.Tidal.Show

NFData Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

rnf :: Value -> () #

Eq Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

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

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 #

Unionable ValueMap Source # 
Instance details

Defined in Sound.Tidal.Core

Moddable ValueMap Source # 
Instance details

Defined in Sound.Tidal.Pattern

Valuable [Value] Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: [Value] -> Value Source #

type Rep Value Source # 
Instance details

Defined in Sound.Tidal.Pattern

type Rep Value = D1 ('MetaData "Value" "Sound.Tidal.Pattern" "tidal-1.9.5-7AHiE4IEnHeHqbwX3gka7l" '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 "VN" 'PrefixI 'True) (S1 ('MetaSel ('Just "nvalue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Note)) :+: (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]))) :+: (C1 ('MetaCons "VPattern" 'PrefixI 'True) (S1 ('MetaSel ('Just "pvalue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pattern Value))) :+: (C1 ('MetaCons "VList" 'PrefixI 'True) (S1 ('MetaSel ('Just "lvalue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Value])) :+: C1 ('MetaCons "VState" 'PrefixI 'True) (S1 ('MetaSel ('Just "statevalue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ValueMap -> (ValueMap, Value))))))))

class Stringy a where Source #

Methods

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

Instances

Instances details
Stringy String Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

deltaContext :: Int -> Int -> String -> String Source #

Stringy (Pattern a) Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

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

Defined in Sound.Tidal.Show

Methods

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

show :: Event a -> String #

showList :: [Event a] -> ShowS #

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 -> () #

(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 #

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.9.5-7AHiE4IEnHeHqbwX3gka7l" '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))))

class Valuable a where Source #

Methods

toValue :: a -> Value Source #

Instances

Instances details
Valuable Rational Source # 
Instance details

Defined in Sound.Tidal.Pattern

Valuable Note Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: Note -> Value Source #

Valuable String Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: String -> Value Source #

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 [Word8] Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: [Word8] -> Value Source #

Valuable [Value] Source # 
Instance details

Defined in Sound.Tidal.Pattern

Methods

toValue :: [Value] -> Value Source #

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

Like *, but the "wholes" come from the right

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

Like *, but the "wholes" come from the left

rev :: Pattern a -> Pattern a Source #

rev p returns p with the event positions in each cycle reversed (or mirrored).

For example rev "1 [~ 2] ~ 3" is equivalent to rev "3 ~ [2 ~] 1".

Note that rev reverses on a cycle-by-cycle basis. This means that rev (slow 2 "1 2 3 4") would actually result in (slow 2 "2 1 4 3"). This is because the slow 2 makes the repeating pattern last two cycles, each of which is reversed independently.

In practice rev is generally used with conditionals, for example with every:

d1 $ every 3 rev $ n "0 1 [~ 2] 3" # sound "arpy"

or jux:

d1 $ jux rev $ n (iter 4 "0 1 [~ 2] 3") # sound "arpy"

noOv :: String -> a Source #

  • Patterns as numbers

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

Like *, but the "wholes" come from the left

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

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?

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.

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

Shifts a pattern forward in time by the given amount, expressed in cycles. Opposite of rotL.

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

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

This will skip to the fourth cycle:

do
  resetCycles
  d1 $ rotL 4 $ seqP
    [ (0, 12, sound "bd bd*2")
    , (4, 12, sound "hh*2 [sn cp] cp future*4")
    , (8, 12, sound (samples "arpy*8" (run 16)))
    ]

Useful when building and testing out longer sequences.

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

General utilities..

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 pair of Values, depending on their types (int or float; strings and rationals are ignored)

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

withQueryControls :: (ValueMap -> ValueMap) -> Pattern a -> Pattern a Source #

Apply a function to the control values 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.

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

withEvent f p returns a new Pattern with each value 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.

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

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

extractI :: String -> ControlPattern -> Pattern Int Source #

Extract a pattern of integer values by from a control pattern, given the name of the control

extractF :: String -> ControlPattern -> Pattern Double Source #

Extract a pattern of floating point values by from a control pattern, given the name of the control

extractS :: String -> ControlPattern -> Pattern String Source #

Extract a pattern of string values by from a control pattern, given the name of the control

extractB :: String -> ControlPattern -> Pattern Bool Source #

Extract a pattern of boolean values by from a control pattern, given the name of the control

extractR :: String -> ControlPattern -> Pattern Rational Source #

Extract a pattern of rational values by from a control pattern, given the name of the control

extractN :: String -> ControlPattern -> Pattern Note Source #

Extract a pattern of note values by from a control pattern, given the name of the control

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

Speed up a pattern by the given time pattern.

For example, the following will play the sound pattern "bd sn kurt" twice as fast (i.e., so it repeats twice per cycle), and the vowel pattern three times as fast:

d1 $ sound (fast 2 "bd sn kurt")
   # fast 3 (vowel "a e o")

The first parameter can be patterned to, for example, play the pattern at twice the speed for the first half of each cycle and then four times the speed for the second half:

d1 $ fast "2 4" $ sound "bd sn kurt cp"

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

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

fastSqueeze speeds up a pattern by a time pattern given as input, squeezing the resulting pattern inside one cycle and playing the original pattern at every repetition.

To better understand how it works, compare it with fast:

>>> print $ fast "1 2" $ s "bd sn"
(0>½)|s: "bd"
(½>¾)|s: "bd"
(¾>1)|s: "sn"

This will give bd played in the first half cycle, and bd sn in the second half. On the other hand, using fastSqueeze;

>>> print $ fastSqueeze "1 2" $ s "bd sn"
(0>¼)|s: "bd"
(¼>½)|s: "sn"
(½>⅝)|s: "bd"
(⅝>¾)|s: "sn"
(¾>⅞)|s: "bd"
(⅞>1)|s: "sn"

The original pattern will play in the first half, and two repetitions of the original pattern will play in the second half. That is, every repetition contains the whole pattern.

If the time pattern has a single value, it becomes equivalent to fast:

d1 $ fastSqueeze 2 $ s "bd sn"
d1 $ fast 2 $ s "bd sn"
d1 $ s "[bd sn]*2"

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

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.

For example, the following will play the sound pattern "bd sn kurt" twice as slow (i.e., so it repeats once every two cycles), and the vowel pattern three times as slow:

d1 $ sound (slow 2 "bd sn kurt")
   # slow 3 (vowel "a e o")

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.

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

Remove events from patterns that to not meet the given test

wholeStart :: Event a -> Time Source #

Get the onset of an event's whole

eventPartStart :: Event a -> Time Source #

Get the onset of an event's whole

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 #

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

True if an EventF's starts is within given ArcF

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

wholeStop :: Event a -> Time Source #

Get the offset 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 #

groupEventsBy :: Eq a => (Event a -> Event a -> Bool) -> [Event a] -> [[Event a]] Source #

collectEventsBy :: Eq a => (Event a -> Event a -> Bool) -> [Event a] -> [Event [a]] Source #

collectBy :: Eq a => (Event a -> Event a -> Bool) -> Pattern a -> Pattern [a] Source #

collects all events satisfying the same constraint into a list

collect :: Eq a => Pattern a -> Pattern [a] Source #

collects all events occuring at the exact same time into a list

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

merges all values in a list into one pattern by stacking the values