Skip to content
This repository was archived by the owner on Jun 13, 2025. It is now read-only.

Commit 9dacdbc

Browse files
authored
Merge pull request #1111 from tidalcycles/patterned-tactus
Patterned tactus WIP
2 parents 7317563 + 6161c2d commit 9dacdbc

File tree

11 files changed

+356
-134
lines changed

11 files changed

+356
-134
lines changed

cabal.project

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1 +1,2 @@
1+
tests: True
12
packages: ./ tidal-parse tidal-listener tidal-link

src/Sound/Tidal/Control.hs

Lines changed: 16 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -26,14 +26,25 @@ module Sound.Tidal.Control where
2626
-}
2727

2828
import qualified Data.Map.Strict as Map
29-
import Data.Maybe (fromJust, fromMaybe, isJust)
30-
import Data.Ratio
29+
import Data.Maybe (fromMaybe)
30+
import Data.Ratio ((%))
3131
import Sound.Tidal.Core
32+
( cF,
33+
cat,
34+
fastcat,
35+
overlay,
36+
sine,
37+
slowcat,
38+
stack,
39+
(#),
40+
(*|),
41+
(|*),
42+
(|>|),
43+
)
3244
import qualified Sound.Tidal.Params as P
3345
import Sound.Tidal.Pattern
3446
import Sound.Tidal.Stream.Types (patternTimeID)
35-
import Sound.Tidal.UI
36-
import Sound.Tidal.Utils
47+
import Sound.Tidal.UI (bite, _irand)
3748
import Prelude hiding ((*>), (<*))
3849

3950
-- | `spin` will "spin" and layer up a pattern the given number of times,
@@ -95,7 +106,7 @@ chopArc :: Arc -> Int -> [Arc]
95106
chopArc (Arc s e) n = map (\i -> Arc (s + (e - s) * (fromIntegral i / fromIntegral n)) (s + (e - s) * (fromIntegral (i + 1) / fromIntegral n))) [0 .. n - 1]
96107

97108
_chop :: Int -> ControlPattern -> ControlPattern
98-
_chop n pat = squeezeJoin $ f <$> pat
109+
_chop n pat = keepTactus (withTactus (* toRational n) pat) $ squeezeJoin $ f <$> pat
99110
where
100111
f v = fastcat $ map (pure . rangemap v) slices
101112
rangemap v (b, e) = Map.union (fromMaybe (makeMap (b, e)) $ merge v (b, e)) v

src/Sound/Tidal/Core.hs

Lines changed: 32 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -21,8 +21,9 @@
2121
module Sound.Tidal.Core where
2222

2323
import Data.Fixed (mod')
24+
import Data.List (sortOn)
2425
import qualified Data.Map.Strict as Map
25-
import Data.Maybe (fromMaybe)
26+
import Data.Maybe (fromMaybe, mapMaybe)
2627
import Sound.Tidal.Pattern
2728
import Prelude hiding ((*>), (<*))
2829

@@ -379,7 +380,9 @@ fastCat :: [Pattern a] -> Pattern a
379380
fastCat (p : []) = p
380381
fastCat ps = setTactus t $ _fast (toTime $ length ps) $ cat ps
381382
where
382-
t = fromMaybe (toRational $ length ps) $ ((* (toRational $ length ps)) . foldl1 lcmr) <$> (sequence $ map tactus ps)
383+
t = fastCat <$> (sequence $ map tactus ps)
384+
385+
-- where t = fromMaybe (toRational $ length ps) $ ((* (toRational $ length ps)) . foldl1 lcmr) <$> (sequence $ map tactus ps)
383386

384387
-- | Alias for @fastCat@
385388
fastcat :: [Pattern a] -> Pattern a
@@ -400,7 +403,7 @@ fastcat = fastCat
400403
-- > ]
401404
timeCat :: [(Time, Pattern a)] -> Pattern a
402405
timeCat ((_, p) : []) = p
403-
timeCat tps = setTactus total $ stack $ map (\(s, e, p) -> compressArc (Arc (s / total) (e / total)) p) $ arrange 0 $ filter (\(t, _) -> t > 0) $ tps
406+
timeCat tps = setTactus (Just $ pure total) $ stack $ map (\(s, e, p) -> compressArc (Arc (s / total) (e / total)) p) $ arrange 0 $ filter (\(t, _) -> t > 0) $ tps
404407
where
405408
total = sum $ map fst tps
406409
arrange :: Time -> [(Time, Pattern a)] -> [(Time, Time, Pattern a)]
@@ -427,6 +430,25 @@ timecat = timeCat
427430
overlay :: Pattern a -> Pattern a -> Pattern a
428431
overlay = (<>)
429432

433+
-- | Serialises a pattern so there's only one event playing at any one
434+
-- time, making it /monophonic/. Events which start/end earlier are given priority.
435+
mono :: Pattern a -> Pattern a
436+
mono p = pattern $ \(State a cm) -> flatten $ query p (State a cm)
437+
where
438+
flatten :: [Event a] -> [Event a]
439+
flatten = mapMaybe constrainPart . truncateOverlaps . sortOn whole
440+
truncateOverlaps [] = []
441+
truncateOverlaps (e : es) = e : truncateOverlaps (mapMaybe (snip e) es)
442+
-- TODO - decide what to do about analog events..
443+
snip a b
444+
| start (wholeOrPart b) >= stop (wholeOrPart a) = Just b
445+
| stop (wholeOrPart b) <= stop (wholeOrPart a) = Nothing
446+
| otherwise = Just b {whole = Just $ Arc (stop $ wholeOrPart a) (stop $ wholeOrPart b)}
447+
constrainPart :: Event a -> Maybe (Event a)
448+
constrainPart e = do
449+
a <- subArc (wholeOrPart e) (part e)
450+
return $ e {part = a}
451+
430452
-- | 'stack' combines a list of 'Pattern's into a new pattern, so that their
431453
-- events are combined over time, i.e., all of the patterns in the list are played
432454
-- simultaneously.
@@ -450,7 +472,10 @@ stack pats = (foldr overlay silence pats) {tactus = t}
450472
where
451473
t
452474
| length pats == 0 = Nothing
453-
| otherwise = foldl1 lcmr <$> (sequence $ map tactus pats)
475+
-- TODO - something cleverer..
476+
| otherwise = (mono . stack) <$> (sequence $ map tactus pats)
477+
478+
-- | otherwise = foldl1 lcmr <$> (sequence $ map tactus pats)
454479

455480
-- ** Manipulating time
456481

@@ -506,6 +531,9 @@ sparsity = slow
506531
zoom :: (Time, Time) -> Pattern a -> Pattern a
507532
zoom (s, e) = zoomArc (Arc s e)
508533

534+
zoompat :: Pattern Time -> Pattern Time -> Pattern a -> Pattern a
535+
zoompat = patternify2 $ curry zoom
536+
509537
zoomArc :: Arc -> Pattern a -> Pattern a
510538
zoomArc (Arc s e) p
511539
| s >= e = nothing

src/Sound/Tidal/Pattern.hs

Lines changed: 29 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -56,30 +56,30 @@ data State = State
5656
}
5757

5858
-- | 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}
6060
deriving (Generic, Functor)
6161

6262
instance (NFData a) => NFData (Pattern a)
6363

6464
pattern :: (State -> [Event a]) -> Pattern a
6565
pattern f = Pattern f Nothing Nothing
6666

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}
6969

7070
setTactusFrom :: Pattern b -> Pattern a -> Pattern a
7171
setTactusFrom a b = b {tactus = tactus a}
7272

7373
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}
7575

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
7878
-- raise error?
79-
_steps _ p = p
79+
steps _ p = p
8080

81-
steps :: Pattern Rational -> Pattern a -> Pattern a
82-
steps = patternify _steps
81+
-- _steps :: Pattern Rational -> Pattern a -> Pattern a
82+
-- _steps = patternify _steps
8383

8484
keepMeta :: Pattern a -> Pattern a -> Pattern a
8585
keepMeta from to = to {tactus = tactus from, pureValue = pureValue from}
@@ -131,8 +131,7 @@ instance Applicative Pattern where
131131
-- > (⅓>½)-⅔|11
132132
-- > ⅓-(½>⅔)|12
133133
-- > (⅔>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}
136135

137136
-- | Like @<*>@, but the "wholes" come from the left
138137
(<*) :: Pattern (a -> b) -> Pattern a -> Pattern b
@@ -151,7 +150,7 @@ infixl 4 <*, *>, <<*
151150
applyPatToPat :: (Maybe Arc -> Maybe Arc -> Maybe (Maybe Arc)) -> Pattern (a -> b) -> Pattern a -> Pattern b
152151
applyPatToPat combineWholes pf px = pattern q
153152
where
154-
q st = concatMap (catMaybes . match) (query pf st)
153+
q st = catMaybes $ concatMap match $ query pf st
155154
where
156155
match ef@(Event (Context c) _ fPart f) =
157156
map
@@ -166,7 +165,7 @@ applyPatToPat combineWholes pf px = pattern q
166165
applyPatToPatBoth :: Pattern (a -> b) -> Pattern a -> Pattern b
167166
applyPatToPatBoth pf px = pattern q
168167
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)
170169
where
171170
-- match analog events from pf with all events from px
172171
match ef@(Event _ Nothing fPart _) = map (withFX ef) (query px $ st {arc = fPart}) -- analog
@@ -183,7 +182,7 @@ applyPatToPatBoth pf px = pattern q
183182
applyPatToPatLeft :: Pattern (a -> b) -> Pattern a -> Pattern b
184183
applyPatToPatLeft pf px = pattern q
185184
where
186-
q st = concatMap (catMaybes . match) (query pf st)
185+
q st = catMaybes $ concatMap match $ query pf st
187186
where
188187
match ef = map (withFX ef) (query px $ st {arc = wholeOrPart ef})
189188
withFX ef ex = do
@@ -194,7 +193,7 @@ applyPatToPatLeft pf px = pattern q
194193
applyPatToPatRight :: Pattern (a -> b) -> Pattern a -> Pattern b
195194
applyPatToPatRight pf px = pattern q
196195
where
197-
q st = concatMap (catMaybes . match) (query px st)
196+
q st = catMaybes $ concatMap match $ query px st
198197
where
199198
match ex = map (`withFX` ex) (query pf $ st {arc = wholeOrPart ex})
200199
withFX ef ex = do
@@ -246,18 +245,22 @@ unwrap pp = pp {query = q, pureValue = Nothing}
246245
-- | Turns a pattern of patterns into a single pattern. Like @unwrap@,
247246
-- but structure only comes from the inner pattern.
248247
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
250249
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}
255253
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)
261264

262265
-- | Turns a pattern of patterns into a single pattern. Like @unwrap@,
263266
-- but structure only comes from the outer pattern.
@@ -279,6 +282,7 @@ outerJoin pp = pp {query = q, pureValue = Nothing}
279282
-- | Like @unwrap@, but cycles of the inner patterns are compressed to fit the
280283
-- timespan of the outer whole (or the original query if it's a continuous pattern?)
281284
-- TODO - what if a continuous pattern contains a discrete one, or vice-versa?
285+
-- TODO - tactus
282286
squeezeJoin :: Pattern (Pattern a) -> Pattern a
283287
squeezeJoin pp = pp {query = q, pureValue = Nothing}
284288
where

0 commit comments

Comments
 (0)