@@ -56,30 +56,30 @@ data State = State
56
56
}
57
57
58
58
-- | A datatype representing events taking place over time
59
- data Pattern a = Pattern { query :: State -> [Event a ], tactus :: Maybe Rational , pureValue :: Maybe a }
59
+ data Pattern a = Pattern { query :: State -> [Event a ], tactus :: Maybe ( Pattern Rational ) , pureValue :: Maybe a }
60
60
deriving (Generic , Functor )
61
61
62
62
instance (NFData a ) => NFData (Pattern a )
63
63
64
64
pattern :: (State -> [Event a ]) -> Pattern a
65
65
pattern f = Pattern f Nothing Nothing
66
66
67
- setTactus :: Rational -> Pattern a -> Pattern a
68
- setTactus r p = p {tactus = Just r}
67
+ setTactus :: Maybe ( Pattern Rational ) -> Pattern a -> Pattern a
68
+ setTactus r p = p {tactus = r}
69
69
70
70
setTactusFrom :: Pattern b -> Pattern a -> Pattern a
71
71
setTactusFrom a b = b {tactus = tactus a}
72
72
73
73
withTactus :: (Rational -> Rational ) -> Pattern a -> Pattern a
74
- withTactus f p = p {tactus = f <$> tactus p}
74
+ withTactus f p = p {tactus = fmap ( fmap f) $ tactus p}
75
75
76
- _steps :: Rational -> Pattern a -> Pattern a
77
- _steps target p@ (Pattern _ (Just t) _) = setTactus target $ _fast (target / t) p
76
+ steps :: Pattern Rational -> Pattern a -> Pattern a
77
+ steps target p@ (Pattern _ (Just t) _) = setTactus ( Just target) $ fast (target / t) p
78
78
-- raise error?
79
- _steps _ p = p
79
+ steps _ p = p
80
80
81
- steps :: Pattern Rational -> Pattern a -> Pattern a
82
- steps = patternify _steps
81
+ -- _steps :: Pattern Rational -> Pattern a -> Pattern a
82
+ -- _steps = patternify _steps
83
83
84
84
keepMeta :: Pattern a -> Pattern a -> Pattern a
85
85
keepMeta from to = to {tactus = tactus from, pureValue = pureValue from}
@@ -131,8 +131,7 @@ instance Applicative Pattern where
131
131
-- > (⅓>½)-⅔|11
132
132
-- > ⅓-(½>⅔)|12
133
133
-- > (⅔>1)|102
134
- (<*>) :: Pattern (a -> b ) -> Pattern a -> Pattern b
135
- (<*>) a b = (applyPatToPatBoth a b) {tactus = lcmr <$> tactus a <*> tactus b}
134
+ (<*>) a b = (applyPatToPatBoth a b) {tactus = (\ a' b' -> lcmr <$> a' <*> b') <$> tactus a <*> tactus b}
136
135
137
136
-- | Like @<*>@, but the "wholes" come from the left
138
137
(<*) :: Pattern (a -> b ) -> Pattern a -> Pattern b
@@ -151,7 +150,7 @@ infixl 4 <*, *>, <<*
151
150
applyPatToPat :: (Maybe Arc -> Maybe Arc -> Maybe (Maybe Arc )) -> Pattern (a -> b ) -> Pattern a -> Pattern b
152
151
applyPatToPat combineWholes pf px = pattern q
153
152
where
154
- q st = concatMap ( catMaybes . match) ( query pf st)
153
+ q st = catMaybes $ concatMap match $ query pf st
155
154
where
156
155
match ef@ (Event (Context c) _ fPart f) =
157
156
map
@@ -166,7 +165,7 @@ applyPatToPat combineWholes pf px = pattern q
166
165
applyPatToPatBoth :: Pattern (a -> b ) -> Pattern a -> Pattern b
167
166
applyPatToPatBoth pf px = pattern q
168
167
where
169
- q st = catMaybes $ concatMap match ( query pf st) ++ concatMap matchX ( query (filterAnalog px) st)
168
+ q st = catMaybes $ ( concatMap match $ query pf st) ++ ( concatMap matchX $ query (filterAnalog px) st)
170
169
where
171
170
-- match analog events from pf with all events from px
172
171
match ef@ (Event _ Nothing fPart _) = map (withFX ef) (query px $ st {arc = fPart}) -- analog
@@ -183,7 +182,7 @@ applyPatToPatBoth pf px = pattern q
183
182
applyPatToPatLeft :: Pattern (a -> b ) -> Pattern a -> Pattern b
184
183
applyPatToPatLeft pf px = pattern q
185
184
where
186
- q st = concatMap ( catMaybes . match) ( query pf st)
185
+ q st = catMaybes $ concatMap match $ query pf st
187
186
where
188
187
match ef = map (withFX ef) (query px $ st {arc = wholeOrPart ef})
189
188
withFX ef ex = do
@@ -194,7 +193,7 @@ applyPatToPatLeft pf px = pattern q
194
193
applyPatToPatRight :: Pattern (a -> b ) -> Pattern a -> Pattern b
195
194
applyPatToPatRight pf px = pattern q
196
195
where
197
- q st = concatMap ( catMaybes . match) ( query px st)
196
+ q st = catMaybes $ concatMap match $ query px st
198
197
where
199
198
match ex = map (`withFX` ex) (query pf $ st {arc = wholeOrPart ex})
200
199
withFX ef ex = do
@@ -246,18 +245,22 @@ unwrap pp = pp {query = q, pureValue = Nothing}
246
245
-- | Turns a pattern of patterns into a single pattern. Like @unwrap@,
247
246
-- but structure only comes from the inner pattern.
248
247
innerJoin :: Pattern (Pattern a ) -> Pattern a
249
- innerJoin pp = pp {query = q, pureValue = Nothing }
248
+ innerJoin pp = setTactus ( Just $ innerJoin' $ filterJust $ tactus <$> pp) $ innerJoin' pp
250
249
where
251
- q st =
252
- concatMap
253
- (\ (Event oc _ op v) -> mapMaybe (munge oc) $ query v st {arc = op})
254
- (query pp st)
250
+ -- \| innerJoin but without tactus manipulation (to avoid recursion)
251
+ innerJoin' :: Pattern (Pattern b ) -> Pattern b
252
+ innerJoin' pp = pp {query = q, pureValue = Nothing }
255
253
where
256
- munge oc (Event ic iw ip v) =
257
- do
258
- p <- subArc (arc st) ip
259
- p' <- subArc p (arc st)
260
- return (Event (combineContexts [ic, oc]) iw p' v)
254
+ q st =
255
+ concatMap
256
+ (\ (Event oc _ op v) -> mapMaybe (munge oc) $ query v st {arc = op})
257
+ (query pp st)
258
+ where
259
+ munge oc (Event ic iw ip v) =
260
+ do
261
+ p <- subArc (arc st) ip
262
+ p' <- subArc p (arc st)
263
+ return (Event (combineContexts [ic, oc]) iw p' v)
261
264
262
265
-- | Turns a pattern of patterns into a single pattern. Like @unwrap@,
263
266
-- but structure only comes from the outer pattern.
@@ -279,6 +282,7 @@ outerJoin pp = pp {query = q, pureValue = Nothing}
279
282
-- | Like @unwrap@, but cycles of the inner patterns are compressed to fit the
280
283
-- timespan of the outer whole (or the original query if it's a continuous pattern?)
281
284
-- TODO - what if a continuous pattern contains a discrete one, or vice-versa?
285
+ -- TODO - tactus
282
286
squeezeJoin :: Pattern (Pattern a ) -> Pattern a
283
287
squeezeJoin pp = pp {query = q, pureValue = Nothing }
284
288
where
0 commit comments