-- File created: 2008-02-02 19:40:11 module Coadjute.Util.List( -- * Extensions of standard functions fullGroupBy, -- * Replacing sublists replaceList, replaceListOnce, maxReplaceList, -- * Miscellaneous nubSplitBy, length1 ) where import Data.List -- |(Elements in the list that appear only once, groups of elements which -- appear more than once.) -- -- > nubSplitBy (==) [1,2,3,1,4,5,2] == ([3,4,5],[[1,1],[2,2]]) nubSplitBy :: (a -> a -> Bool) -> [a] -> ([a], [[a]]) nubSplitBy rel xs = ( filter (`notElemm` nubParts) nubs , fullGroupBy rel . filter (`elemm` nubParts) $ xs) where nubs = nubBy rel xs nubParts = xs \\\ nubs elemm = any . rel notElemm x = not . elemm x (\\\) = deleteFirstsBy rel {- prop_nubSplitPreserves :: [Int] -> Bool prop_nubSplitPreserves xs = let (ns,rs) = nubSplitBy (==) xs in sort (ns ++ concat rs) == sort xs -} -- |Like 'groupBy', but makes groups from the whole list, not only consecutive -- elements. Essentially '\f -> groupBy f . sort' but doesn't need an Ord -- instance. -- -- > fullGroupBy (==) [1,2,3,1,4,5] == [[1,1],[2],[3],[4],[5]] -- > fullGroupBy (==) "mississippi" == ["m", "iiii", "ssss", "pp"] fullGroupBy :: (a -> a -> Bool) -> [a] -> [[a]] fullGroupBy rel xs = map (\a -> filter (rel a) xs) (nubBy rel xs) {- prop_groupSorted :: [Int] -> Bool prop_groupSorted xs = sort (fullGroupBy (==) xs ) == sort ( groupBy (==) (sort xs)) -} -- |Returns 'True' for single-element lists and 'False' for all others. length1 :: [a] -> Bool length1 [_] = True length1 _ = False -- |Replaces one list with another as many times as requested. -- -- > maxReplaceList 3 "ab" "--" "|abc1abc2abc3abc|" == "|--c1--c2--c3abc|" maxReplaceList :: Eq a => Int -> [a] -> [a] -> [a] -> [a] maxReplaceList times what with s = if times < 0 then error "maxReplaceList :: negative count" else go times s where len = length what go _ [] = [] go 0 xs = xs go n xs@(c:cs) = let (prefix,rest) = splitAt len xs in if prefix == what then with ++ go (n-1) rest else c : go n cs -- |Performs one replacement of the first sublist with the second. -- -- > replaceListOnce "abc" "-" "abcdefabc" == "-defabc" replaceListOnce :: Eq a => [a] -> [a] -> [a] -> [a] replaceListOnce = maxReplaceList 1 -- |Like 'maxReplaceList', but replaces throughout the list. -- -- > replaceList "abc" "--" "abcdefabc" == "--def--" replaceList :: Eq a => [a] -> [a] -> [a] -> [a] replaceList = maxReplaceList maxBound