| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Sound.Tidal.Pattern
Synopsis
- type Time = Rational
- sam :: Time -> Time
- toTime :: Real a => a -> Rational
- nextSam :: Time -> Time
- cyclePos :: Time -> Time
- data ArcF a = Arc {}
- type Arc = ArcF Time
- sect :: Arc -> Arc -> Arc
- hull :: Arc -> Arc -> Arc
- subArc :: Arc -> Arc -> Maybe Arc
- timeToCycleArc :: Time -> Arc
- cycleArc :: Arc -> Arc
- cyclesInArc :: Integral a => Arc -> [a]
- cycleArcsInArc :: Arc -> [Arc]
- arcCycles :: Arc -> [Arc]
- arcCyclesZW :: Arc -> [Arc]
- mapCycle :: (Time -> Time) -> Arc -> Arc
- isIn :: Arc -> Time -> Bool
- data EventF a b = Event {}
- type Event a = EventF (ArcF Time) a
- onsetIn :: Arc -> Event a -> Bool
- compareDefrag :: Ord a => [Event a] -> [Event a] -> Bool
- defragParts :: Eq a => [Event a] -> [Event a]
- isAdjacent :: Eq a => Event a -> Event a -> Bool
- wholeStart :: Event a -> Time
- wholeStop :: Event a -> Time
- eventPartStart :: 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
- data State = State {}
- type Query a = State -> [Event a]
- data Nature
- data Pattern a = Pattern {}
- data Value
- class Valuable a where
- type StateMap = Map String (Pattern Value)
- type ControlMap = Map String Value
- type ControlPattern = Pattern ControlMap
- (<*) :: Pattern (a -> b) -> Pattern a -> Pattern b
- (*>) :: Pattern (a -> b) -> Pattern a -> Pattern b
- unwrap :: Pattern (Pattern a) -> Pattern a
- innerJoin :: Pattern (Pattern a) -> Pattern a
- outerJoin :: Pattern (Pattern a) -> Pattern a
- squeezeJoin :: Pattern (Pattern a) -> Pattern a
- noOv :: String -> a
- class TolerantEq a where
- showPattern :: Show a => Arc -> Pattern a -> String
- prettyRat :: Rational -> String
- showFrac :: Integer -> Integer -> String
- empty :: Pattern a
- queryArc :: Pattern a -> Arc -> [Event a]
- isDigital :: Pattern a -> Bool
- isAnalog :: Pattern a -> Bool
- 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
- withEvent :: (Event a -> Event b) -> Pattern a -> Pattern b
- withEvents :: ([Event a] -> [Event b]) -> Pattern a -> Pattern b
- withPart :: (Arc -> Arc) -> Pattern a -> Pattern a
- applyFIS :: (Double -> Double) -> (Int -> Int) -> (String -> String) -> Value -> Value
- fNum2 :: (Int -> Int -> Int) -> (Double -> Double -> Double) -> Value -> Value -> Value
- getI :: Value -> Maybe Int
- getF :: Value -> Maybe Double
- getS :: Value -> Maybe String
- getB :: Value -> Maybe Bool
- getR :: Value -> Maybe Rational
- compressArc :: Arc -> Pattern a -> Pattern a
- compressArcTo :: Arc -> Pattern a -> Pattern a
- _fastGap :: Time -> Pattern a -> Pattern a
- rotL :: Time -> Pattern a -> Pattern a
- rotR :: Time -> Pattern a -> Pattern a
- filterValues :: (a -> Bool) -> Pattern a -> Pattern a
- filterJust :: Pattern (Maybe a) -> Pattern a
- filterWhen :: (Time -> Bool) -> Pattern a -> Pattern a
- filterOnsets :: Pattern a -> Pattern a
- playFor :: Time -> Time -> Pattern a -> Pattern a
- tParam :: (t1 -> t2 -> Pattern a) -> Pattern t1 -> t2 -> 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
- tParamSqueeze :: (a -> Pattern b -> Pattern c) -> Pattern a -> Pattern b -> Pattern c
- matchManyToOne :: (b -> a -> Bool) -> Pattern a -> Pattern b -> Pattern (Bool, b)
Types
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)
An arc of time, with a start time (or onset) and a stop time (or offset)
Instances
| Functor ArcF Source # | |
| Show Arc Source # | |
| Applicative ArcF Source # | |
| Eq a => Eq (ArcF a) Source # | |
| Fractional a => Fractional (ArcF a) Source # | |
| Num a => Num (ArcF a) Source # | |
| Ord a => Ord (ArcF a) Source # | |
| Show a => Show (Event a) Source # | |
| NFData a => NFData (ArcF a) Source # | |
| Defined in Sound.Tidal.Pattern | |
| TolerantEq (Event ControlMap) Source # | |
| Defined in Sound.Tidal.Pattern Methods (~==) :: Event ControlMap -> Event ControlMap -> Bool Source # | |
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.
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
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)
An event is a value that's active during a timespan The part should be equal to or fit inside the whole
Instances
| Bifunctor EventF Source # | |
| Functor (EventF a) Source # | |
| Show a => Show (Event a) Source # | |
| TolerantEq (Event ControlMap) Source # | |
| Defined in Sound.Tidal.Pattern Methods (~==) :: Event ControlMap -> Event ControlMap -> Bool Source # | |
| (Eq a, Eq b) => Eq (EventF a b) Source # | |
| (Ord a, Ord b) => Ord (EventF a b) Source # | |
| Defined in Sound.Tidal.Pattern | |
| (NFData a, NFData b) => NFData (EventF a b) Source # | |
| Defined in Sound.Tidal.Pattern | |
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
eventValue :: Event a -> a Source #
eventHasOnset :: Event a -> Bool Source #
an Arc and some named control values
Also known as Continuous vs Discrete/Amorphous vs Pulsating etc.
A datatype that's basically a query, plus a hint about whether its events are Analogue or Digital by nature
Instances
Instances
type ControlPattern = Pattern ControlMap Source #
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.
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?
class TolerantEq a where Source #
Instances
| TolerantEq ControlMap Source # | |
| Defined in Sound.Tidal.Pattern Methods (~==) :: ControlMap -> ControlMap -> Bool Source # | |
| TolerantEq Value Source # | |
| TolerantEq a => TolerantEq [a] Source # | |
| Defined in Sound.Tidal.Pattern | |
| TolerantEq (Event ControlMap) Source # | |
| Defined in Sound.Tidal.Pattern Methods (~==) :: Event ControlMap -> Event ControlMap -> Bool Source # | |
Internal functions
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)
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
filterOnsets :: Pattern a -> Pattern a Source #