Skip to content

Commit

Permalink
add stepalt, steptaper, steptaperlist, stepfirstof/steplastof/stepevery
Browse files Browse the repository at this point in the history
  • Loading branch information
yaxu committed Apr 11, 2024
1 parent 323dfb7 commit b5ac6f7
Showing 1 changed file with 28 additions and 0 deletions.
28 changes: 28 additions & 0 deletions src/Sound/Tidal/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ module Sound.Tidal.Core where
import Prelude hiding ((*>), (<*))

import Data.Fixed (mod')
import Data.List (transpose)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe)
import Sound.Tidal.Pattern
Expand Down Expand Up @@ -457,6 +458,33 @@ steplastof :: Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
steplastof (Pattern _ _ (Just i)) f pat = _steplastof i f pat
steplastof tp f p = innerJoin $ (\t -> _steplastof t f p) <$> tp

_stepfirstof :: Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
_stepfirstof i f pat | i <= 1 = pat
| otherwise = stepcat $ f pat : (take (i-1) $ repeat pat)

stepfirstof :: Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
stepfirstof (Pattern _ _ (Just i)) f pat = _stepfirstof i f pat
stepfirstof tp f p = innerJoin $ (\t -> _steplastof t f p) <$> tp

stepevery :: Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
stepevery = stepfirstof

-- | Like @steptaper@, but returns a list of repetitions
steptaperlist :: Pattern a -> [Pattern a]
steptaperlist pat@(Pattern _ (Just t) _) = pat : map (\r -> _stepsub r pat) [1 .. t]
-- TODO exception?
steptaperlist pat = [pat]

-- | Plays one fewer step from the pattern each repetition, down to nothing
steptaper :: Pattern a -> Pattern a
steptaper = stepcat . steptaperlist

-- | Successively plays a pattern from each group in turn
stepalt :: [[Pattern a]] -> Pattern a
stepalt groups = stepcat $ concat $ take (c * length groups) $ transpose $ map cycle groups
where c = foldl1 lcm $ map length groups


-- ** Manipulating time

-- | Shifts a pattern back in time by the given amount, expressed in cycles
Expand Down

0 comments on commit b5ac6f7

Please sign in to comment.