{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, OverloadedStrings #-}
module Sound.Tidal.Control where
import Prelude hiding ((<*), (*>))
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe, isJust, fromJust)
import Data.Ratio
import Sound.Tidal.Pattern
import Sound.Tidal.Core
import Sound.Tidal.UI
import qualified Sound.Tidal.Params as P
import Sound.Tidal.Utils
import Sound.Tidal.ParseBP (Parseable, Enumerable, parseBP_E)
spin :: Pattern Int -> ControlPattern -> ControlPattern
spin = tParam _spin
_spin :: Int -> ControlPattern -> ControlPattern
_spin copies p =
stack $ map (\i -> let offset = toInteger i % toInteger copies in
offset `rotL` p
# P.pan (pure $ fromRational offset)
)
[0 .. (copies - 1)]
chop :: Pattern Int -> ControlPattern -> ControlPattern
chop = tParam _chop
chopArc :: Arc -> Int -> [Arc]
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]
_chop :: Int -> ControlPattern -> ControlPattern
_chop n p = withEvents (concatMap chopEvent) p
where
chopEvent :: Event ControlMap -> [Event ControlMap]
chopEvent (Event w p' v) = map (\a -> chomp v (length $ chopArc w n) a) $ arcs w p'
arcs w' p' = numberedArcs p' $ chopArc w' n
numberedArcs :: Arc -> [Arc] -> [(Int, (Arc, Arc))]
numberedArcs p' as = map ((fromJust <$>) <$>) $ filter (isJust . snd . snd) $ enumerate $ map (\a -> (a, subArc p' a)) as
chomp :: ControlMap -> Int -> (Int, (Arc, Arc)) -> Event ControlMap
chomp v n' (i, (w,p')) = Event w p' (Map.insert "begin" (VF b') $ Map.insert "end" (VF e') v)
where b = fromMaybe 0 $ do v' <- Map.lookup "begin" v
getF v'
e = fromMaybe 1 $ do v' <- Map.lookup "end" v
getF v'
d = e-b
b' = (((fromIntegral i)/(fromIntegral n')) * d) + b
e' = (((fromIntegral $ i+1)/(fromIntegral n')) * d) + b
striate :: Pattern Int -> ControlPattern -> ControlPattern
striate = tParam _striate
_striate :: Int -> ControlPattern -> ControlPattern
_striate n p = fastcat $ map (\i -> offset i) [0 .. n-1]
where offset i = (mergePlayRange ((fromIntegral i / fromIntegral n), (fromIntegral (i+1) / fromIntegral n))) <$> p
mergePlayRange :: (Double, Double) -> ControlMap -> ControlMap
mergePlayRange (b,e) cm = Map.insert "begin" (VF $ (b*d')+b') $ Map.insert "end" (VF $ (e*d')+b') $ cm
where b' = fromMaybe 0 $ Map.lookup "begin" cm >>= getF
e' = fromMaybe 1 $ Map.lookup "end" cm >>= getF
d' = e' - b'
striateBy :: Pattern Int -> Pattern Double -> ControlPattern -> ControlPattern
striateBy = tParam2 _striateBy
striate' :: Pattern Int -> Pattern Double -> ControlPattern -> ControlPattern
striate' = striateBy
_striateBy :: Int -> Double -> ControlPattern -> ControlPattern
_striateBy n f p = fastcat $ map (\i -> offset (fromIntegral i)) [0 .. n-1]
where offset i = p # P.begin (pure (slot * i) :: Pattern Double) # P.end (pure ((slot * i) + f) :: Pattern Double)
slot = (1 - f) / (fromIntegral n)
gap :: Pattern Int -> ControlPattern -> ControlPattern
gap = tParam _gap
_gap :: Int -> ControlPattern -> ControlPattern
_gap n p = (_fast (toRational n) $ cat [pure 1, silence]) |>| ( _chop n p)
weave :: Time -> ControlPattern -> [ControlPattern] -> ControlPattern
weave t p ps = weave' t p (map (\x -> (x #)) ps)
weaveWith :: Time -> Pattern a -> [Pattern a -> Pattern a] -> Pattern a
weaveWith t p fs | l == 0 = silence
| otherwise = _slow t $ stack $ map (\(i, f) -> (fromIntegral i % l) `rotL` (_fast t $ f (_slow t p))) (zip [0 :: Int ..] fs)
where l = fromIntegral $ length fs
weave' :: Time -> Pattern a -> [Pattern a -> Pattern a] -> Pattern a
weave' = weaveWith
interlace :: ControlPattern -> ControlPattern -> ControlPattern
interlace a b = weave 16 (P.shape $ (sine * 0.9)) [a, b]
slice :: Pattern Int -> Pattern Int -> ControlPattern -> ControlPattern
slice pN pI p = P.begin b # P.end e # p
where b = (\i n -> (div' i n)) <$> pI <* pN
e = (\i n -> (div' i n) + (div' 1 n)) <$> pI <* pN
div' num den = fromIntegral (num `mod` den) / fromIntegral den
_slice :: Int -> Int -> ControlPattern -> ControlPattern
_slice n i p =
p
# P.begin (pure $ fromIntegral i / fromIntegral n)
# P.end (pure $ fromIntegral (i+1) / fromIntegral n)
randslice :: Pattern Int -> ControlPattern -> ControlPattern
randslice = tParam $ \n p -> innerJoin $ (\i -> _slice n i p) <$> irand n
loopAt :: Pattern Time -> ControlPattern -> ControlPattern
loopAt n p = slow n p |* P.speed (fromRational <$> (1/n)) # P.unit (pure "c")
hurry :: Pattern Rational -> ControlPattern -> ControlPattern
hurry x = (|* P.speed (fromRational <$> x)) . fast x
smash :: Pattern Int -> [Pattern Time] -> ControlPattern -> Pattern ControlMap
smash n xs p = slowcat $ map (\x -> slow x p') xs
where p' = striate n p
smash' :: Int -> [Pattern Time] -> ControlPattern -> Pattern ControlMap
smash' n xs p = slowcat $ map (\x -> slow x p') xs
where p' = _chop n p
stut :: Pattern Integer -> Pattern Double -> Pattern Rational -> ControlPattern -> ControlPattern
stut = tParam3 _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 x
= ((+feedback) . (*(1-feedback)) . (/(fromIntegral count)) . ((fromIntegral count)-)) x
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
stut' :: Pattern Int -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
stut' = stutWith
cI :: String -> Pattern Int
cI s = Pattern Analog $ \(State a m) -> maybe [] (f a) $ Map.lookup s m
where f a (VI v) = [Event a a v]
f a (VF v) = [Event a a (floor v)]
f a (VS v) = maybe [] (\v' -> [Event a a v']) (readMaybe v)
_cX :: (Arc -> Value -> [Event a]) -> [a] -> String -> Pattern a
_cX f ds s = Pattern Analog $
\(State a m) -> maybe (map (\d -> (Event a a d)) ds) (f a) $ Map.lookup s m
_cF :: [Double] -> String -> Pattern Double
_cF = _cX f
where f a (VI v) = [Event a a (fromIntegral v)]
f a (VF v) = [Event a a v]
f a (VS v) = maybe [] (\v' -> [Event a a v']) (readMaybe v)
cF :: Double -> String -> Pattern Double
cF d = _cF [d]
cF0 :: String -> Pattern Double
cF0 = _cF [0]
cF_ :: String -> Pattern Double
cF_ = _cF []
cT :: Time -> String -> Pattern Time
cT d = (toRational <$>) . cF (fromRational d)
cT0 :: String -> Pattern Time
cT0 = (toRational <$>) . cF0
cT_ :: String -> Pattern Time
cT_ = (toRational <$>) . cF_
cR :: Time -> String -> Pattern Rational
cR = cT
cR0 :: String -> Pattern Time
cR0 = cT0
cR_ :: String -> Pattern Time
cR_ = cT_
_cS :: [String] -> String -> Pattern String
_cS = _cX f
where f a (VI v) = [Event a a (show v)]
f a (VF v) = [Event a a (show v)]
f a (VS v) = [Event a a v]
cS :: String -> String -> Pattern String
cS d = _cS [d]
cS_ :: String -> Pattern String
cS_ = _cS []
_cP :: (Enumerable a, Parseable a) => [Pattern a] -> String -> Pattern a
_cP ds s = innerJoin $ _cX f ds s
where f a (VI v) = [Event a a (parseBP_E $ show v)]
f a (VF v) = [Event a a (parseBP_E $ show v)]
f a (VS v) = [Event a a (parseBP_E $ v)]
cP :: (Enumerable a, Parseable a) => Pattern a -> String -> Pattern a
cP d = _cP [d]
cP_ :: (Enumerable a, Parseable a) => String -> Pattern a
cP_ = _cP []
in0 :: Pattern Double
in0 = cF 0 "0"
in1 :: Pattern Double
in1 = cF 0 "1"
in2 :: Pattern Double
in2 = cF 0 "2"
in3 :: Pattern Double
in3 = cF 0 "3"
in4 :: Pattern Double
in4 = cF 0 "4"
in5 :: Pattern Double
in5 = cF 0 "5"
in6 :: Pattern Double
in6 = cF 0 "6"
in7 :: Pattern Double
in7 = cF 0 "7"
in8 :: Pattern Double
in8 = cF 0 "8"
in9 :: Pattern Double
in9 = cF 0 "9"
in10 :: Pattern Double
in10 = cF 0 "10"
in11 :: Pattern Double
in11 = cF 0 "11"
in12 :: Pattern Double
in12 = cF 0 "12"
in13 :: Pattern Double
in13 = cF 0 "13"
in14 :: Pattern Double
in14 = cF 0 "14"
in15 :: Pattern Double
in15 = cF 0 "15"
in16 :: Pattern Double
in16 = cF 0 "16"
in17 :: Pattern Double
in17 = cF 0 "17"
in18 :: Pattern Double
in18 = cF 0 "18"
in19 :: Pattern Double
in19 = cF 0 "19"
in20 :: Pattern Double
in20 = cF 0 "20"
in21 :: Pattern Double
in21 = cF 0 "21"
in22 :: Pattern Double
in22 = cF 0 "22"
in23 :: Pattern Double
in23 = cF 0 "23"
in24 :: Pattern Double
in24 = cF 0 "24"
in25 :: Pattern Double
in25 = cF 0 "25"
in26 :: Pattern Double
in26 = cF 0 "26"
in27 :: Pattern Double
in27 = cF 0 "27"
in28 :: Pattern Double
in28 = cF 0 "28"
in29 :: Pattern Double
in29 = cF 0 "29"
in30 :: Pattern Double
in30 = cF 0 "30"
in31 :: Pattern Double
in31 = cF 0 "31"
in32 :: Pattern Double
in32 = cF 0 "32"
in33 :: Pattern Double
in33 = cF 0 "33"
in34 :: Pattern Double
in34 = cF 0 "34"
in35 :: Pattern Double
in35 = cF 0 "35"
in36 :: Pattern Double
in36 = cF 0 "36"
in37 :: Pattern Double
in37 = cF 0 "37"
in38 :: Pattern Double
in38 = cF 0 "38"
in39 :: Pattern Double
in39 = cF 0 "39"
in40 :: Pattern Double
in40 = cF 0 "40"
in41 :: Pattern Double
in41 = cF 0 "41"
in42 :: Pattern Double
in42 = cF 0 "42"
in43 :: Pattern Double
in43 = cF 0 "43"
in44 :: Pattern Double
in44 = cF 0 "44"
in45 :: Pattern Double
in45 = cF 0 "45"
in46 :: Pattern Double
in46 = cF 0 "46"
in47 :: Pattern Double
in47 = cF 0 "47"
in48 :: Pattern Double
in48 = cF 0 "48"
in49 :: Pattern Double
in49 = cF 0 "49"
in50 :: Pattern Double
in50 = cF 0 "50"
in51 :: Pattern Double
in51 = cF 0 "51"
in52 :: Pattern Double
in52 = cF 0 "52"
in53 :: Pattern Double
in53 = cF 0 "53"
in54 :: Pattern Double
in54 = cF 0 "54"
in55 :: Pattern Double
in55 = cF 0 "55"
in56 :: Pattern Double
in56 = cF 0 "56"
in57 :: Pattern Double
in57 = cF 0 "57"
in58 :: Pattern Double
in58 = cF 0 "58"
in59 :: Pattern Double
in59 = cF 0 "59"
in60 :: Pattern Double
in60 = cF 0 "60"
in61 :: Pattern Double
in61 = cF 0 "61"
in62 :: Pattern Double
in62 = cF 0 "62"
in63 :: Pattern Double
in63 = cF 0 "63"
in64 :: Pattern Double
in64 = cF 0 "64"
in65 :: Pattern Double
in65 = cF 0 "65"
in66 :: Pattern Double
in66 = cF 0 "66"
in67 :: Pattern Double
in67 = cF 0 "67"
in68 :: Pattern Double
in68 = cF 0 "68"
in69 :: Pattern Double
in69 = cF 0 "69"
in70 :: Pattern Double
in70 = cF 0 "70"
in71 :: Pattern Double
in71 = cF 0 "71"
in72 :: Pattern Double
in72 = cF 0 "72"
in73 :: Pattern Double
in73 = cF 0 "73"
in74 :: Pattern Double
in74 = cF 0 "74"
in75 :: Pattern Double
in75 = cF 0 "75"
in76 :: Pattern Double
in76 = cF 0 "76"
in77 :: Pattern Double
in77 = cF 0 "77"
in78 :: Pattern Double
in78 = cF 0 "78"
in79 :: Pattern Double
in79 = cF 0 "79"
in80 :: Pattern Double
in80 = cF 0 "80"
in81 :: Pattern Double
in81 = cF 0 "81"
in82 :: Pattern Double
in82 = cF 0 "82"
in83 :: Pattern Double
in83 = cF 0 "83"
in84 :: Pattern Double
in84 = cF 0 "84"
in85 :: Pattern Double
in85 = cF 0 "85"
in86 :: Pattern Double
in86 = cF 0 "86"
in87 :: Pattern Double
in87 = cF 0 "87"
in88 :: Pattern Double
in88 = cF 0 "88"
in89 :: Pattern Double
in89 = cF 0 "89"
in90 :: Pattern Double
in90 = cF 0 "90"
in91 :: Pattern Double
in91 = cF 0 "91"
in92 :: Pattern Double
in92 = cF 0 "92"
in93 :: Pattern Double
in93 = cF 0 "93"
in94 :: Pattern Double
in94 = cF 0 "94"
in95 :: Pattern Double
in95 = cF 0 "95"
in96 :: Pattern Double
in96 = cF 0 "96"
in97 :: Pattern Double
in97 = cF 0 "97"
in98 :: Pattern Double
in98 = cF 0 "98"
in99 :: Pattern Double
in99 = cF 0 "99"
in100 :: Pattern Double
in100 = cF 0 "100"
in101 :: Pattern Double
in101 = cF 0 "101"
in102 :: Pattern Double
in102 = cF 0 "102"
in103 :: Pattern Double
in103 = cF 0 "103"
in104 :: Pattern Double
in104 = cF 0 "104"
in105 :: Pattern Double
in105 = cF 0 "105"
in106 :: Pattern Double
in106 = cF 0 "106"
in107 :: Pattern Double
in107 = cF 0 "107"
in108 :: Pattern Double
in108 = cF 0 "108"
in109 :: Pattern Double
in109 = cF 0 "109"
in110 :: Pattern Double
in110 = cF 0 "110"
in111 :: Pattern Double
in111 = cF 0 "111"
in112 :: Pattern Double
in112 = cF 0 "112"
in113 :: Pattern Double
in113 = cF 0 "113"
in114 :: Pattern Double
in114 = cF 0 "114"
in115 :: Pattern Double
in115 = cF 0 "115"
in116 :: Pattern Double
in116 = cF 0 "116"
in117 :: Pattern Double
in117 = cF 0 "117"
in118 :: Pattern Double
in118 = cF 0 "118"
in119 :: Pattern Double
in119 = cF 0 "119"
in120 :: Pattern Double
in120 = cF 0 "120"
in121 :: Pattern Double
in121 = cF 0 "121"
in122 :: Pattern Double
in122 = cF 0 "122"
in123 :: Pattern Double
in123 = cF 0 "123"
in124 :: Pattern Double
in124 = cF 0 "124"
in125 :: Pattern Double
in125 = cF 0 "125"
in126 :: Pattern Double
in126 = cF 0 "126"
in127 :: Pattern Double
in127 = cF 0 "127"