Skip to content

Commit

Permalink
stepJoin experiment
Browse files Browse the repository at this point in the history
  • Loading branch information
yaxu committed Apr 17, 2024
1 parent 5dae76f commit e6c05de
Show file tree
Hide file tree
Showing 3 changed files with 36 additions and 5 deletions.
4 changes: 3 additions & 1 deletion src/Sound/Tidal/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -422,7 +422,9 @@ pattern to multiple patterns at once:
> ] # speed "[[1 0.8], [1.5 2]*2]/3"
-}
stack :: [Pattern a] -> Pattern a
stack = foldr overlay silence
stack pats = (foldr overlay silence pats) {tactus = t}
where t | length pats == 0 = Nothing
| otherwise = foldl1 lcmr <$> (sequence $ map tactus pats)

-- ** Manipulating time

Expand Down
33 changes: 29 additions & 4 deletions src/Sound/Tidal/Stepwise.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,13 +19,17 @@

module Sound.Tidal.Stepwise where

import Data.List (transpose)
import Data.Maybe (fromMaybe)
import Data.Containers.ListUtils (nubOrd)

Check failure on line 22 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.4.4

Could not find module ‘Data.Containers.ListUtils’

Check failure on line 22 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.4.4

Could not find module ‘Data.Containers.ListUtils’
import Data.List (sort, transpose)
import Data.Maybe (catMaybes, fromMaybe, isJust)

import Sound.Tidal.Core
import Sound.Tidal.Pattern
import Sound.Tidal.UI (while)
import Sound.Tidal.Utils (applyWhen)
import Sound.Tidal.UI (while)
import Sound.Tidal.Utils (applyWhen, pairs)

_lcmtactus :: [Pattern a] -> Maybe Time
_lcmtactus pats = foldl1 lcmr <$> (sequence $ map tactus pats)

s_cat :: [Pattern a] -> Pattern a
s_cat pats = timecat $ map (\pat -> (fromMaybe 1 $ tactus pat, pat)) pats
Expand Down Expand Up @@ -111,3 +115,24 @@ s_expand = patternify _s_expand

s_contract :: Pattern Rational -> Pattern a -> Pattern a
s_contract = patternify _s_contract

stepJoin :: Pattern (Pattern a) -> Pattern a
stepJoin pp = Pattern q Nothing Nothing
where q st@(State a c) = query (timecat $ retime $ slices $ query (rotL (sam $ start a) pp) (st {arc = Arc 0 1})) st

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.10.1

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.6.5

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.8.3

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal latest - ghc latest

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.8.3

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 9.0.1

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.10.1

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 9.0.1

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.6.5

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal latest - ghc latest

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘c’

Check warning on line 121 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘c’
retime :: [(Time, Pattern a)] -> [(Time, Pattern a)]
retime xs = map (\(dur, pat) -> adjust dur pat) xs
where occupied_perc = sum $ map fst $ filter (isJust . tactus . snd) xs
occupied_tactus = sum $ catMaybes $ map (tactus . snd) xs
total_tactus = occupied_tactus / occupied_perc
adjust dur pat@(Pattern {tactus = Just t}) = (t, pat)

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.10.1

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.6.5

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.8.3

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal latest - ghc latest

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.8.3

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 9.0.1

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.10.1

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 9.0.1

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal 3.4.0.0 - ghc 8.6.5

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / cabal latest - ghc latest

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘dur’

Check warning on line 127 in src/Sound/Tidal/Stepwise.hs

View workflow job for this annotation

GitHub Actions / build (9.0.1, 3.4.0.0)

Defined but not used: ‘dur’
adjust dur pat = (dur*total_tactus, pat)
-- break up events at all start/end points, into groups, including empty ones.
slices :: [Event (Pattern a)] -> [(Time, Pattern a)]
slices evs = map (\s -> ((snd s - fst s), stack $ map value $ fit s evs)) $ pairs $ sort $ nubOrd $ 0:1:concatMap (\ev -> start (part ev):stop (part ev):[]) evs
-- list of slices of events within the given range
fit :: (Rational, Rational) -> [Event (Pattern a)] -> [Event (Pattern a)]
fit (b,e) evs = catMaybes $ map (match (b,e)) evs
-- slice of event within the given range
match :: (Rational, Rational) -> Event (Pattern a) -> Maybe (Event (Pattern a))
match (b,e) ev = do a <- subArc (Arc b e) $ part ev
return ev {part = a}
4 changes: 4 additions & 0 deletions src/Sound/Tidal/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -106,3 +106,7 @@ fromRight b _ = b
applyWhen :: Bool -> (a -> a) -> a -> a
applyWhen True f x = f x
applyWhen False _ x = x

-- pair up neighbours in list
pairs :: [a] -> [(a,a)]
pairs rs = zip rs (tail rs)

0 comments on commit e6c05de

Please sign in to comment.