module Sound.Tidal.Dirt where
import Sound.OSC.FD (Datum)
import qualified Data.Map as Map
import Control.Applicative
import Control.Concurrent.MVar
import Data.Colour.SRGB
import Data.Colour.Names
import Data.Hashable
import Data.Bits
import Data.Maybe
import Data.Fixed
import Data.Ratio
import Data.List (elemIndex)
import Sound.Tidal.Stream
import Sound.Tidal.OscStream
import Sound.Tidal.Pattern
import Sound.Tidal.Parse
import Sound.Tidal.Params
import Sound.Tidal.Time
import Sound.Tidal.Tempo
import Sound.Tidal.Transition (transition, wash)
import Sound.Tidal.Utils (enumerate)
dirt :: Shape
dirt = Shape { params = [ s_p,
offset_p,
begin_p,
end_p,
speed_p,
pan_p,
velocity_p,
vowel_p,
cutoff_p,
resonance_p,
accelerate_p,
shape_p,
kriole_p,
gain_p,
cut_p,
delay_p,
delaytime_p,
delayfeedback_p,
crush_p,
coarse_p,
hcutoff_p,
hresonance_p,
bandf_p,
bandq_p,
unit_p,
loop_p,
n_p,
attack_p,
hold_p,
release_p
],
cpsStamp = True,
latency = 0.3
}
dirtSlang = OscSlang {
path = "/play",
timestamp = MessageStamp,
namedParams = False,
preamble = []
}
superDirtSlang = dirtSlang { timestamp = BundleStamp, path = "/play2", namedParams = True }
superDirtBackend port = do
s <- makeConnection "127.0.0.1" port superDirtSlang
return $ Backend s (\_ _ _ -> return ())
superDirtState port = do
backend <- superDirtBackend port
Sound.Tidal.Stream.state backend dirt
dirtBackend = do
s <- makeConnection "127.0.0.1" 7771 dirtSlang
return $ Backend s (\_ _ _ -> return ())
dirtStream = do
backend <- dirtBackend
stream backend dirt
dirtState = do
backend <- dirtBackend
Sound.Tidal.Stream.state backend dirt
dirtSetters :: IO Time -> IO (ParamPattern -> IO (), (Time -> [ParamPattern] -> ParamPattern) -> ParamPattern -> IO ())
dirtSetters getNow = do ds <- dirtState
return (setter ds, transition getNow ds)
superDirtSetters :: IO Time -> IO (ParamPattern -> IO (), (Time -> [ParamPattern] -> ParamPattern) -> ParamPattern -> IO ())
superDirtSetters getNow = do ds <- superDirtState 57120
return (setter ds, transition getNow ds)
superDirts :: [Int] -> IO [(ParamPattern -> IO (), (Time -> [ParamPattern] -> ParamPattern) -> ParamPattern -> IO ())]
superDirts ports = do (_, getNow) <- cpsUtils
states <- mapM (superDirtState) ports
return $ map (\state -> (setter state, transition getNow state)) states
dirtstream _ = dirtStream
dirtToColour :: ParamPattern -> Pattern ColourD
dirtToColour p = s
where s = fmap (\x -> maybe black (datumToColour) (Map.lookup (param dirt "s") x)) p
showToColour :: Show a => a -> ColourD
showToColour = stringToColour . show
datumToColour :: Value -> ColourD
datumToColour = showToColour
stringToColour :: String -> ColourD
stringToColour s = sRGB (r/256) (g/256) (b/256)
where i = (hash s) `mod` 16777216
r = fromIntegral $ (i .&. 0xFF0000) `shiftR` 16;
g = fromIntegral $ (i .&. 0x00FF00) `shiftR` 8;
b = fromIntegral $ (i .&. 0x0000FF);
pick :: String -> Int -> String
pick name n = name ++ ":" ++ (show n)
striate :: Pattern Int -> ParamPattern -> ParamPattern
striate = temporalParam _striate
_striate :: Int -> ParamPattern -> ParamPattern
_striate n p = fastcat $ map (\x -> off (fromIntegral x) p) [0 .. n1]
where off i p = p
# begin (atom (fromIntegral i / fromIntegral n))
# end (atom (fromIntegral (i+1) / fromIntegral n))
striate' :: Int -> Double -> ParamPattern -> ParamPattern
striate' n f p = fastcat $ map (\x -> off (fromIntegral x) p) [0 .. n1]
where off i p = p # begin (atom (slot * i) :: Pattern Double) # end (atom ((slot * i) + f) :: Pattern Double)
slot = (1 f) / (fromIntegral n)
striateO :: Int -> Double -> ParamPattern -> ParamPattern
striateO n o p = _striate n p |+| begin (atom o :: Pattern Double) |+| end (atom o :: Pattern Double)
striateL :: Int -> Int -> ParamPattern -> ParamPattern
striateL n l p = _striate n p # loop (atom $ fromIntegral l)
striateL' n f l p = striate' n f p # loop (atom $ fromIntegral l)
metronome = _slow 2 $ sound (p "[odx, [hh]*8]")
clutchIn :: Time -> Time -> [Pattern a] -> Pattern a
clutchIn _ _ [] = silence
clutchIn _ _ (p:[]) = p
clutchIn t now (p:p':_) = overlay (fadeOut' now t p') (fadeIn' now t p)
clutch :: Time -> [Pattern a] -> Pattern a
clutch = clutchIn 2
xfadeIn :: Time -> Time -> [ParamPattern] -> ParamPattern
xfadeIn _ _ [] = silence
xfadeIn _ _ (p:[]) = p
xfadeIn t now (p:p':_) = overlay (p |*| gain (now `rotR` (_slow t envEqR))) (p' |*| gain (now `rotR` (_slow t (envEq))))
xfade :: Time -> [ParamPattern] -> ParamPattern
xfade = xfadeIn 2
stut :: Pattern Integer -> Pattern Double -> Pattern Rational -> ParamPattern -> ParamPattern
stut n g t p = unwrap $ (\a b c -> _stut a b c p) <$> n <*> g <*> t
_stut :: Integer -> Double -> Rational -> ParamPattern -> ParamPattern
_stut steps feedback time p = stack (p:(map (\x -> (((x%steps)*time) `rotR` (p |*| gain (pure $ scale (fromIntegral x))))) [1..(steps1)]))
where scale x
= ((+feedback) . (*(1feedback)) . (/(fromIntegral steps)) . ((fromIntegral steps))) x
stut' :: Integer -> Time -> (ParamPattern -> ParamPattern) -> ParamPattern -> ParamPattern
stut' steps steptime f p | steps <= 0 = p
| otherwise = overlay (f (steptime `rotR` stut' (steps1) steptime f p)) p
anticipateIn :: Time -> Time -> [ParamPattern] -> ParamPattern
anticipateIn t now = wash (spread' (_stut 8 0.2) (now `rotR` (_slow t $ (toRational . (1)) <$> envL))) t now
anticipate :: Time -> [ParamPattern] -> ParamPattern
anticipate = anticipateIn 8
nToOrbit = copyParam n_p orbit_p
soundToOrbit :: [String] -> ParamPattern -> ParamPattern
soundToOrbit sounds p = follow s_p orbit_p ((\s -> fromMaybe 0 $ elemIndex s sounds) <$>) p