Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Note = Note {}
- type ValueMap = Map String Value
- class Valuable a where
- data Value
- type Event a = EventF (ArcF Time) a
- data EventF a b = Event {}
- data Context = Context {
- contextPosition :: [((Int, Int), (Int, Int))]
- class Stringy a where
- deltaContext :: Int -> Int -> a -> a
- class Moddable a where
- gmod :: a -> a -> a
- type ControlPattern = Pattern ValueMap
- data Pattern a = Pattern {}
- data State = State {}
- (<*) :: Pattern (a -> b) -> Pattern a -> Pattern b
- (*>) :: Pattern (a -> b) -> Pattern a -> Pattern b
- (<<*) :: Pattern (a -> b) -> Pattern a -> Pattern b
- applyPatToPat :: (Maybe Arc -> Maybe Arc -> Maybe (Maybe Arc)) -> Pattern (a -> b) -> Pattern a -> Pattern b
- applyPatToPatBoth :: Pattern (a -> b) -> Pattern a -> Pattern b
- applyPatToPatLeft :: Pattern (a -> b) -> Pattern a -> Pattern b
- applyPatToPatRight :: Pattern (a -> b) -> Pattern a -> Pattern b
- applyPatToPatSqueeze :: 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
- empty :: Pattern a
- silence :: Pattern a
- 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
- extractI :: String -> ControlPattern -> Pattern Int
- extractF :: String -> ControlPattern -> Pattern Double
- extractS :: String -> ControlPattern -> Pattern String
- extractB :: String -> ControlPattern -> Pattern Bool
- extractR :: String -> ControlPattern -> Pattern Rational
- compressArc :: Arc -> Pattern a -> Pattern a
- compressArcTo :: Arc -> Pattern a -> Pattern a
- focusArc :: Arc -> Pattern a -> Pattern a
- fast :: Pattern Time -> Pattern a -> Pattern a
- fastSqueeze :: Pattern Time -> Pattern a -> Pattern a
- density :: Pattern Time -> Pattern a -> Pattern a
- _fast :: Time -> Pattern a -> Pattern a
- slow :: Pattern Time -> Pattern a -> Pattern a
- _slow :: Time -> Pattern a -> Pattern a
- _fastGap :: Time -> Pattern a -> Pattern a
- rotL :: Time -> Pattern a -> Pattern a
- rotR :: Time -> Pattern a -> Pattern a
- rev :: Pattern a -> Pattern a
- matchManyToOne :: (b -> a -> Bool) -> Pattern a -> Pattern b -> Pattern (Bool, b)
- 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
- filterEvents :: (Event a -> Bool) -> Pattern a -> Pattern a
- filterDigital :: Pattern a -> Pattern a
- filterAnalog :: 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
- combineContexts :: [Context] -> Context
- setContext :: Context -> Pattern a -> Pattern a
- withContext :: (Context -> Context) -> Pattern a -> Pattern a
- deltaMini :: String -> String
- isAnalog :: Event a -> Bool
- isDigital :: Event a -> Bool
- onsetIn :: Arc -> Event a -> Bool
- defragParts :: Eq a => [Event a] -> [Event a]
- isAdjacent :: Eq a => Event a -> Event a -> Bool
- wholeOrPart :: Event a -> Arc
- 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
- resolveState :: ValueMap -> [Event ValueMap] -> (ValueMap, [Event ValueMap])
- 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
- getN :: Value -> Maybe Note
- getS :: Value -> Maybe String
- getB :: Value -> Maybe Bool
- getR :: Value -> Maybe Rational
- 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
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.3-4wLLA8UaySH4WUbCORe3eb" '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)))) |
Some context for an event, currently just position within sourcecode
type ControlPattern = Pattern ValueMap Source #
A datatype representing events taking place over time
Instances
(<*) :: 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
(<<*) :: 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 #
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?
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
fastSqueeze :: Pattern Time -> Pattern a -> Pattern a Source #
Slow down a pattern by the factors in the given time pattern, squeezing
the pattern to fit the slot given in the time pattern
slow :: Pattern Time -> Pattern a -> Pattern a Source #
Slow down a pattern by the given time pattern
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
rev :: Pattern a -> Pattern a Source #
rev p
returns p
with the event positions in each cycle
reversed (or mirrored).
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 #
filterDigital :: Pattern a -> Pattern a Source #
filterAnalog :: Pattern a -> Pattern a Source #
tParam3 :: (a -> b -> c -> Pattern d -> Pattern e) -> Pattern a -> Pattern b -> Pattern c -> Pattern d -> Pattern e Source #
combineContexts :: [Context] -> Context 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
wholeOrPart :: Event a -> Arc Source #
eventValue :: Event a -> a Source #
eventHasOnset :: Event a -> Bool Source #
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)
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