Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type Event a = EventF (ArcF Time) a
- data State = State {}
- data Pattern a = Pattern {}
- data Context = Context {
- contextPosition :: [((Int, Int), (Int, Int))]
- type ControlPattern = Pattern ValueMap
- type ValueMap = Map String Value
- class Moddable a where
- gmod :: a -> a -> a
- newtype Note = Note {}
- data Value
- class Stringy a where
- deltaContext :: Int -> Int -> a -> a
- data EventF a b = Event {}
- class Valuable a where
- (*>) :: Pattern (a -> b) -> Pattern a -> Pattern b
- empty :: Pattern a
- (<*) :: Pattern (a -> b) -> Pattern a -> Pattern b
- reset :: Pattern Bool -> Pattern a -> Pattern a
- silence :: Pattern a
- rev :: Pattern a -> Pattern a
- noOv :: String -> a
- applyPatToPatBoth :: Pattern (a -> b) -> Pattern a -> Pattern b
- applyPatToPatLeft :: Pattern (a -> b) -> Pattern a -> Pattern b
- applyPatToPatRight :: Pattern (a -> b) -> Pattern a -> Pattern b
- (<<*) :: Pattern (a -> b) -> Pattern a -> Pattern b
- applyPatToPatSqueeze :: Pattern (a -> b) -> Pattern a -> Pattern b
- applyPatToPat :: (Maybe Arc -> Maybe Arc -> Maybe (Maybe Arc)) -> Pattern (a -> b) -> Pattern a -> Pattern b
- wholeOrPart :: Event a -> Arc
- filterAnalog :: Pattern a -> Pattern a
- filterDigital :: Pattern a -> Pattern a
- combineContexts :: [Context] -> Context
- squeezeJoin :: Pattern (Pattern a) -> Pattern a
- unwrap :: Pattern (Pattern a) -> Pattern a
- innerJoin :: Pattern (Pattern a) -> Pattern a
- outerJoin :: Pattern (Pattern a) -> Pattern a
- focusArc :: Arc -> Pattern a -> Pattern a
- _trigJoin :: Bool -> Pattern (Pattern a) -> Pattern a
- rotR :: Time -> Pattern a -> Pattern a
- trigJoin :: Pattern (Pattern a) -> Pattern a
- trigZeroJoin :: Pattern (Pattern a) -> Pattern a
- resetTo :: Pattern Rational -> Pattern a -> Pattern a
- rotL :: Time -> Pattern a -> Pattern a
- restart :: Pattern Bool -> Pattern a -> Pattern a
- restartTo :: Pattern Rational -> Pattern a -> Pattern a
- applyFIS :: (Double -> Double) -> (Int -> Int) -> (String -> String) -> Value -> Value
- fNum2 :: (Int -> Int -> Int) -> (Double -> Double -> Double) -> Value -> Value -> Value
- queryArc :: Pattern a -> Arc -> [Event a]
- splitQueries :: Pattern a -> Pattern a
- withResultArc :: (Arc -> Arc) -> Pattern a -> Pattern a
- withResultTime :: (Time -> Time) -> Pattern a -> Pattern a
- withQueryArc :: (Arc -> Arc) -> Pattern a -> Pattern a
- withQueryTime :: (Time -> Time) -> Pattern a -> Pattern a
- withQueryControls :: (ValueMap -> ValueMap) -> Pattern a -> Pattern a
- withEvent :: (Event a -> Event b) -> Pattern a -> Pattern b
- withValue :: (a -> b) -> Pattern a -> Pattern b
- withEvents :: ([Event a] -> [Event b]) -> Pattern a -> Pattern b
- withPart :: (Arc -> Arc) -> Pattern a -> Pattern a
- _extract :: (Value -> Maybe a) -> String -> ControlPattern -> Pattern a
- filterJust :: Pattern (Maybe a) -> Pattern a
- extractI :: String -> ControlPattern -> Pattern Int
- getI :: Value -> Maybe Int
- extractF :: String -> ControlPattern -> Pattern Double
- getF :: Value -> Maybe Double
- extractS :: String -> ControlPattern -> Pattern String
- getS :: Value -> Maybe String
- extractB :: String -> ControlPattern -> Pattern Bool
- getB :: Value -> Maybe Bool
- extractR :: String -> ControlPattern -> Pattern Rational
- getR :: Value -> Maybe Rational
- extractN :: String -> ControlPattern -> Pattern Note
- getN :: Value -> Maybe Note
- compressArc :: Arc -> Pattern a -> Pattern a
- _fastGap :: Time -> Pattern a -> Pattern a
- compressArcTo :: Arc -> Pattern a -> Pattern a
- _fast :: Time -> Pattern a -> Pattern a
- fast :: Pattern Time -> Pattern a -> Pattern a
- tParam :: (t1 -> t2 -> Pattern a) -> Pattern t1 -> t2 -> Pattern a
- fastSqueeze :: Pattern Time -> Pattern a -> Pattern a
- tParamSqueeze :: (a -> Pattern b -> Pattern c) -> Pattern a -> Pattern b -> Pattern c
- density :: Pattern Time -> Pattern a -> Pattern a
- slow :: Pattern Time -> Pattern a -> Pattern a
- _slow :: Time -> Pattern a -> Pattern a
- matchManyToOne :: (b -> a -> Bool) -> Pattern a -> Pattern b -> Pattern (Bool, b)
- filterValues :: (a -> Bool) -> Pattern a -> Pattern a
- filterWhen :: (Time -> Bool) -> Pattern a -> Pattern a
- wholeStart :: Event a -> Time
- filterOnsets :: Pattern a -> Pattern a
- eventPartStart :: Event a -> Time
- filterEvents :: (Event a -> Bool) -> Pattern a -> Pattern a
- isDigital :: Event a -> Bool
- isAnalog :: Event a -> Bool
- playFor :: Time -> Time -> Pattern a -> Pattern a
- tParam2 :: (a -> b -> c -> Pattern d) -> Pattern a -> Pattern b -> c -> Pattern d
- tParam3 :: (a -> b -> c -> Pattern d -> Pattern e) -> Pattern a -> Pattern b -> Pattern c -> Pattern d -> Pattern e
- setContext :: Context -> Pattern a -> Pattern a
- withContext :: (Context -> Context) -> Pattern a -> Pattern a
- deltaMini :: String -> String
- onsetIn :: Arc -> Event a -> Bool
- defragParts :: Eq a => [Event a] -> [Event a]
- isAdjacent :: Eq a => Event a -> Event a -> Bool
- wholeStop :: Event a -> Time
- eventPartStop :: Event a -> Time
- eventPart :: Event a -> Arc
- eventValue :: Event a -> a
- eventHasOnset :: Event a -> Bool
- toEvent :: (((Time, Time), (Time, Time)), a) -> Event a
- resolveState :: ValueMap -> [Event ValueMap] -> (ValueMap, [Event ValueMap])
- getBlob :: Value -> Maybe [Word8]
- getList :: Value -> Maybe [Value]
- valueToPattern :: Value -> Pattern Value
- sameDur :: Event a -> Event a -> Bool
- groupEventsBy :: Eq a => (Event a -> Event a -> Bool) -> [Event a] -> [[Event a]]
- collectEvent :: [Event a] -> Maybe (Event [a])
- collectEventsBy :: Eq a => (Event a -> Event a -> Bool) -> [Event a] -> [Event [a]]
- collectBy :: Eq a => (Event a -> Event a -> Bool) -> Pattern a -> Pattern [a]
- collect :: Eq a => Pattern a -> Pattern [a]
- uncollectEvent :: Event [a] -> [Event a]
- uncollectEvents :: [Event [a]] -> [Event a]
- uncollect :: Pattern [a] -> Pattern a
- module Sound.Tidal.Time
Documentation
A datatype representing events taking place over time
Instances
Some context for an event, currently just position within sourcecode
type ControlPattern = Pattern ValueMap Source #
Note is Double, but with a different parser
Instances
Data Note Source # | |
Defined in Sound.Tidal.Pattern 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 # 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 # | |
Floating Note Source # | |
Generic Note Source # | |
Num Note Source # | |
Fractional Note Source # | |
Real Note Source # | |
Defined in Sound.Tidal.Pattern toRational :: Note -> Rational # | |
RealFrac Note Source # | |
Show Note Source # | |
NFData Note Source # | |
Defined in Sound.Tidal.Pattern | |
Eq Note Source # | |
Ord Note Source # | |
Enumerable Note Source # | |
Parseable Note Source # | |
Moddable Note Source # | |
Valuable Note Source # | |
type Rep Note Source # | |
Defined in Sound.Tidal.Pattern |
Polymorphic values
Instances
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.
Instances
Functor (EventF a) Source # | |
Show a => Show (Event a) Source # | |
Generic (EventF a b) Source # | |
(NFData a, NFData b) => NFData (EventF a b) Source # | |
Defined in Sound.Tidal.Pattern | |
(Eq a, Eq b) => Eq (EventF a b) Source # | |
(Ord a, Ord b) => Ord (EventF a b) Source # | |
type Rep (EventF a b) Source # | |
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)))) |
(*>) :: 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"
(<<*) :: 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 #
wholeOrPart :: Event a -> Arc Source #
filterAnalog :: Pattern a -> Pattern a Source #
filterDigital :: Pattern a -> Pattern a Source #
combineContexts :: [Context] -> Context 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)
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.
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"
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"
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
filterOnsets :: Pattern a -> Pattern a Source #
tParam3 :: (a -> b -> c -> Pattern d -> Pattern e) -> Pattern a -> Pattern b -> Pattern c -> Pattern d -> Pattern e Source #
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
eventValue :: Event a -> a Source #
eventHasOnset :: Event a -> Bool 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
uncollectEvent :: Event [a] -> [Event a] Source #
uncollectEvents :: [Event [a]] -> [Event a] Source #
uncollect :: Pattern [a] -> Pattern a Source #
merges all values in a list into one pattern by stacking the values
module Sound.Tidal.Time