module Music.Typesetting.Process where import Data.List import Music.Typesetting.Model import Music.Typesetting.Query -- delete persistent annotations or like prune :: (a -> a -> Bool) -> (b -> Maybe a) -> (a -> b -> b) -> [b] -> [b] prune cmp get del = let go _ [] = [] go Nothing (x:xs) = x : go (get x) xs go (Just st) (x:xs) = case get x of Nothing -> x : go (Just st) xs Just y -> if cmp st y then del y x : go (Just st) xs else x : go (Just y) xs in go Nothing m_delete_annotation :: M_Annotation -> Measure -> Measure m_delete_annotation i (Measure a n) = Measure (delete i a) n m_remove_duplicate_ts :: [Measure] -> [Measure] m_remove_duplicate_ts = let get = m_time_signature' del = m_delete_annotation in prune (==) get del