Skip to content

Commit

Permalink
simplify definition of chop
Browse files Browse the repository at this point in the history
  • Loading branch information
yaxu committed Apr 27, 2024
1 parent 850fb7a commit a8dc071
Showing 1 changed file with 11 additions and 36 deletions.
47 changes: 11 additions & 36 deletions src/Sound/Tidal/Control.hs
Original file line number Diff line number Diff line change
Expand Up @@ -96,42 +96,17 @@ 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 pat = withTactus (* toRational n) $ withEvents (concatMap chopEvent) pat
where -- for each part,
chopEvent :: Event ValueMap -> [Event ValueMap]
chopEvent (Event c (Just w) p' v) = map (chomp c v (length $ chopArc w n)) $ arcs w p'
-- ignoring 'analog' events (those without wholes),
chopEvent _ = []
-- cut whole into n bits, and number them
arcs w' p' = numberedArcs p' $ chopArc w' n
-- each bit is a new whole, with part that's the intersection of old part and new whole
-- (discard new parts that don't intersect with the old part)
numberedArcs :: Arc -> [Arc] -> [(Int, (Arc, Arc))]
numberedArcs p' as = map ((fromJust <$>) <$>) $ filter (isJust . snd . snd) $ enumerate $ map (\a -> (a, subArc p' a)) as
-- begin set to i/n, end set to i+1/n
-- if the old event had a begin and end, then multiply the new
-- begin and end values by the old difference (end-begin), and
-- add the old begin
chomp :: Context -> ValueMap -> Int -> (Int, (Arc, Arc)) -> Event ValueMap
chomp c v n' (i, (w,p')) = Event c (Just 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

{-
-- A simpler definition than the above, but this version doesn't chop
-- with multiple chops, and only works with a single 'pure' event..
_chop' :: Int -> ControlPattern -> ControlPattern
_chop' n p = begin (fromList begins) # end (fromList ends) # p
where step = 1/(fromIntegral n)
begins = [0,step .. (1-step)]
ends = (tail begins) ++ [1]
-}

_chop n pat = squeezeJoin $ f <$> pat
where f v = fastcat $ map (pure . rangemap v) slices
rangemap v (b, e) = Map.union (fromMaybe (makeMap (b,e)) $ merge v (b,e)) v
merge :: ValueMap -> (Double, Double) -> Maybe ValueMap
merge v (b, e) = do b' <- Map.lookup "begin" v >>= getF
e' <- Map.lookup "end" v >>= getF
let d = e' - b'
return $ makeMap (b' + b*d, b' + e*d)
makeMap (b,e) = Map.fromList [("begin", VF b), ("end", VF $ e)]
slices = map (\i -> (frac i, frac $ i + 1)) [0 .. n-1]
frac i = fromIntegral i / fromIntegral n

{-| Striate is a kind of granulator, cutting samples into bits in a similar to
chop, but the resulting bits are organised differently. For example:
Expand Down

0 comments on commit a8dc071

Please sign in to comment.