diff --git a/bench/Memory/Tidal/Inputs.hs b/bench/Memory/Tidal/Inputs.hs index 59a3b786..245fe7f1 100644 --- a/bench/Memory/Tidal/Inputs.hs +++ b/bench/Memory/Tidal/Inputs.hs @@ -2,9 +2,9 @@ module Tidal.Inputs where -import Sound.Tidal.Control import Sound.Tidal.Core import Sound.Tidal.Params +import Sound.Tidal.Control import Sound.Tidal.ParseBP () import Sound.Tidal.Pattern import Sound.Tidal.UI @@ -73,7 +73,7 @@ fixArg1 = pF "cc64" 1 fixArg2 :: ControlPattern fixArg2 = fix (# crush 4) (pF "cc65" 1) $ - fix (stut' 4 (0.125 / 4) (+ up "1")) (pF "cc66" 1) $ + fix (echoWith 4 (0.125 / 4) (+ up "1")) (pF "cc66" 1) $ fix (|*| speed "-1") (pF "cc67" 1) $ fix ((# delaytime 0.125) . (# delay 0.5)) (pF "cc68" 1) $ fix (# coarse 12) (pF "cc69" 1) $ diff --git a/src/Sound/Tidal/Control.hs b/src/Sound/Tidal/Control.hs index b6c36cbe..559adfdf 100644 --- a/src/Sound/Tidal/Control.hs +++ b/src/Sound/Tidal/Control.hs @@ -170,10 +170,6 @@ mergePlayRange (b, e) cm = Map.insert "begin" (VF ((b * d') + b')) $ Map.insert striateBy :: Pattern Int -> Pattern Double -> ControlPattern -> ControlPattern striateBy = patternify2 _striateBy --- | DEPRECATED, use 'striateBy' instead. -striate' :: Pattern Int -> Pattern Double -> ControlPattern -> ControlPattern -striate' = striateBy - _striateBy :: Int -> Double -> ControlPattern -> ControlPattern _striateBy n f p = keepTactus (withTactus (* toRational n) p) $ fastcat $ map (offset . fromIntegral) [0 .. n - 1] where @@ -223,7 +219,7 @@ _gap n p = _fast (toRational n) (cat [pure 1, silence]) |>| _chop n p -- > , speed "1 2 3" -- > ] weave :: Time -> ControlPattern -> [ControlPattern] -> ControlPattern -weave t p ps = weave' t p (map (#) ps) +weave t p ps = weaveWith t p (map (#) ps) -- | -- @weaveWith@ is similar to the above, but weaves with a list of functions, rather @@ -241,10 +237,6 @@ weaveWith t p fs where l = fromIntegral $ length fs --- | An old alias for 'weaveWith'. -weave' :: Time -> Pattern a -> [Pattern a -> Pattern a] -> Pattern a -weave' = weaveWith - -- | -- (A function that takes two ControlPatterns, and blends them together into -- a new ControlPattern. An ControlPattern is basically a pattern of messages to @@ -449,29 +441,17 @@ _echoWith count time f p | count <= 1 = p | otherwise = overlay (f (time `rotR` _echoWith (count - 1) time f p)) p --- | DEPRECATED, use 'echo' instead -stut :: Pattern Integer -> Pattern Double -> Pattern Rational -> ControlPattern -> ControlPattern -stut = patternify3' _stut - _stut :: Integer -> Double -> Rational -> ControlPattern -> ControlPattern _stut count feedback steptime p = stack (p : map (\x -> ((x % 1) * steptime) `rotR` (p |* P.gain (pure $ scalegain (fromIntegral x)))) [1 .. (count - 1)]) where scalegain = (+ feedback) . (* (1 - feedback)) . (/ fromIntegral count) . (fromIntegral count -) --- | DEPRECATED, use 'echoWith' instead -stutWith :: Pattern Int -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a -stutWith n t f p = innerJoin $ (\a b -> _stutWith a b f p) <$> n <* t - _stutWith :: (Num n, Ord n) => n -> Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a _stutWith count steptime f p | count <= 1 = p | otherwise = overlay (f (steptime `rotR` _stutWith (count - 1) steptime f p)) p --- | DEPRECATED, use 'echoWith' instead -stut' :: Pattern Int -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a -stut' = stutWith - -- | Turns a pattern of seconds into a pattern of (rational) cycle durations sec :: (Fractional a) => Pattern a -> Pattern a sec p = (realToFrac <$> cF 1 "_cps") *| p diff --git a/src/Sound/Tidal/UI.hs b/src/Sound/Tidal/UI.hs index f433f9d3..987a3bdd 100644 --- a/src/Sound/Tidal/UI.hs +++ b/src/Sound/Tidal/UI.hs @@ -1187,10 +1187,6 @@ segment = patternify _segment _segment :: Time -> Pattern a -> Pattern a _segment n p = setTactus (Just $ pure n) $ _fast n (pure id) <* p --- | @discretise@: the old (deprecated) name for 'segment' -discretise :: Pattern Time -> Pattern a -> Pattern a -discretise = segment - -- @fromNote p@: converts a pattern of human-readable pitch names -- into pitch numbers. For example, @"cs2"@ will be parsed as C Sharp -- in the 2nd octave with the result of @11@, and @"b-3"@ as @@ -1595,14 +1591,6 @@ _chunk n f p i <- _slow (toRational (-n)) $ rev $ run (fromIntegral (-n)) withinArc (Arc (i % fromIntegral (-n)) ((i + 1) % fromIntegral (-n))) f p --- | DEPRECATED, use 'chunk' with negative numbers instead -chunk' :: (Integral a1) => Pattern a1 -> (Pattern a2 -> Pattern a2) -> Pattern a2 -> Pattern a2 -chunk' npat f p = innerJoin $ (\n -> _chunk' n f p) <$> npat - --- | DEPRECATED, use '_chunk' with negative numbers instead -_chunk' :: (Integral a) => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b -_chunk' n f p = _chunk (-n) f p - -- | -- @inside@ carries out an operation /inside/ a cycle. -- For example, while @rev "0 1 2 3 4 5 6 7"@ is the same as @"7 6 5 4 3 2 1 0"@, @@ -2513,10 +2501,6 @@ sseq' ss cs = fastcat $ map f cs | isDigit c = pure $ ss !! digitToInt c | otherwise = silence --- | Deprecated backwards-compatible alias for 'ghostWith'. -ghost'' :: Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a -ghost'' = ghostWith - -- | Like 'ghost'', but a user-supplied function describes how to alter the pattern. -- -- In this example, ghost notes are applied to the snare hit, but these notes will diff --git a/test/Sound/Tidal/ControlTest.hs b/test/Sound/Tidal/ControlTest.hs index a6f0e52a..37ecd83c 100644 --- a/test/Sound/Tidal/ControlTest.hs +++ b/test/Sound/Tidal/ControlTest.hs @@ -37,12 +37,12 @@ run = ] ) - describe "stutWith" $ do - it "can mimic stut" $ do + describe "echoWith" $ do + it "can mimic echo" $ do comparePD (Arc 0 1) - (filterOnsets $ stutWith 4 0.25 (# gain 1) $ sound "bd") - (filterOnsets $ stut 4 1 0.25 $ sound "bd") + (filterOnsets $ echoWith 1 0.25 (# gain 1) $ sound "bd") + (filterOnsets $ echo 1 0.25 4 $ sound "bd") describe "splice" $ do it "can beatslice" $ do diff --git a/tidal-parse/src/Sound/Tidal/Parse.hs b/tidal-parse/src/Sound/Tidal/Parse.hs index 4a5aea52..8371bd3f 100644 --- a/tidal-parse/src/Sound/Tidal/Parse.hs +++ b/tidal-parse/src/Sound/Tidal/Parse.hs @@ -718,7 +718,6 @@ pTime_p_p = <|> $(fromTidal "sparsity") <|> $(fromTidal "linger") <|> $(fromTidal "segment") - <|> $(fromTidal "discretise") <|> $(fromTidal "timeLoop") <|> $(fromTidal "swing") <|> $(fromTidal "<~") @@ -807,7 +806,6 @@ instance Parse (Pattern Time -> ControlPattern -> ControlPattern) where parser = $(fromTidal "hurry") <|> $(fromTidal "loopAt") - <|> (parser :: H (Pattern Double -> Pattern Time -> ControlPattern -> ControlPattern)) <*!> parser instance Parse ((ControlPattern -> ControlPattern) -> ControlPattern -> ControlPattern) where parser = @@ -975,10 +973,7 @@ pBool_p_p_p :: H (Pattern Bool -> Pattern a -> Pattern a -> Pattern a) pBool_p_p_p = $(fromTidal "stitch") instance Parse (Pattern Int -> Pattern Double -> ControlPattern -> ControlPattern) where - parser = $(fromTidal "striate'") <|> $(fromTidal "striateBy") - -instance Parse (Pattern Double -> Pattern Time -> ControlPattern -> ControlPattern) where - parser = (parser :: H (Pattern Integer -> Pattern Double -> Pattern Time -> ControlPattern -> ControlPattern)) <*!> parser + parser = $(fromTidal "striateBy") instance Parse (Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a) where parser = @@ -997,8 +992,7 @@ instance Parse (Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern $(fromTidal "every") <|> $(fromTidal "plyWith") <|> $(fromTidal "chunk") - <|> $(fromTidal "chunk'") - <|> (parser :: H (Pattern Int -> Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a)) <*!> parser -- note: chunk' is actually generalized to Integral, but not clear what non-Int cases would be + <|> (parser :: H (Pattern Int -> Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a)) <*!> parser instance Parse (Pattern Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a) where parser = @@ -1062,9 +1056,6 @@ instance Parse (Pattern Int -> Pattern Int -> Pattern a -> Pattern a -> Pattern instance Parse (Int -> Pattern Int -> Pattern Int -> Pattern a -> Pattern a) where parser = (parser :: H (Pattern Time -> Int -> Pattern Int -> Pattern Int -> Pattern a -> Pattern a)) <*!> parser -instance Parse (Pattern Integer -> Pattern Double -> Pattern Time -> ControlPattern -> ControlPattern) where - parser = $(fromTidal "stut") - instance Parse (Pattern Integer -> Pattern Rational -> Pattern Double -> ControlPattern -> ControlPattern) where parser = $(fromTidal "echo") @@ -1072,9 +1063,7 @@ instance Parse (Pattern Int -> Pattern Int -> (Pattern a -> Pattern a) -> Patter parser = $(fromTidal "every'") instance Parse (Pattern Int -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a) where - parser = - $(fromTidal "stutWith") - <|> $(fromTidal "echoWith") + parser = $(fromTidal "echoWith") instance Parse (Pattern Time -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a) where parser = $(fromTidal "whenmod") diff --git a/tidal-parse/test/Sound/Tidal/TidalParseTest.hs b/tidal-parse/test/Sound/Tidal/TidalParseTest.hs index ec60b1bd..59b629e5 100644 --- a/tidal-parse/test/Sound/Tidal/TidalParseTest.hs +++ b/tidal-parse/test/Sound/Tidal/TidalParseTest.hs @@ -272,9 +272,9 @@ run = "sound \"cp*16\" |+| gain (sew \"t(3,8)\" \"1*8\" \"0.75*8\")" `parsesTo` (sound "cp*16" |+| gain (sew "t(3,8)" "1*8" "0.75*8")) - it "parses an example with stutWith" $ - "stutWith 16 0.125 (|* gain 0.9) $ s \"bass:2/2\"" - `parsesTo` (stutWith 16 0.125 (|* gain 0.9) $ s "bass:2/2") + it "parses an example with echoWith" $ + "echoWith 16 0.125 (|* gain 0.9) $ s \"bass:2/2\"" + `parsesTo` (echoWith 16 0.125 (|* gain 0.9) $ s "bass:2/2") it "parses an example with choose and a chords from Sound.Tidal.Chords" $ "s \"arpy*8\" # note (choose major)"