{-# LANGUAGE CPP #-}
module ListSetOps (
unionLists, minusList,
Assoc, assoc, assocMaybe, assocUsing, assocDefault, assocDefaultUsing,
hasNoDups, removeDups, findDupsEq,
equivClasses,
getNth
) where
#include "HsVersions.h"
import GhcPrelude
import Outputable
import Util
import Data.List
import qualified Data.List.NonEmpty as NE
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.Set as S
getNth :: Outputable a => [a] -> Int -> a
getNth xs n = ASSERT2( xs `lengthExceeds` n, ppr n $$ ppr xs )
xs !! n
unionLists :: (Outputable a, Eq a) => [a] -> [a] -> [a]
unionLists xs ys
= WARN(lengthExceeds xs 100 || lengthExceeds ys 100, ppr xs $$ ppr ys)
[x | x <- xs, isn'tIn "unionLists" x ys] ++ ys
minusList :: Ord a => [a] -> [a] -> [a]
minusList [] _ = []
minusList xs@[x] ys
| x `elem` ys = []
| otherwise = xs
minusList xs [] = xs
minusList xs [y] = filter (/= y) xs
minusList xs ys = filter (`S.notMember` yss) xs
where
yss = S.fromList ys
type Assoc a b = [(a,b)]
assoc :: (Eq a) => String -> Assoc a b -> a -> b
assocDefault :: (Eq a) => b -> Assoc a b -> a -> b
assocUsing :: (a -> a -> Bool) -> String -> Assoc a b -> a -> b
assocMaybe :: (Eq a) => Assoc a b -> a -> Maybe b
assocDefaultUsing :: (a -> a -> Bool) -> b -> Assoc a b -> a -> b
assocDefaultUsing _ deflt [] _ = deflt
assocDefaultUsing eq deflt ((k,v) : rest) key
| k `eq` key = v
| otherwise = assocDefaultUsing eq deflt rest key
assoc crash_msg list key = assocDefaultUsing (==) (panic ("Failed in assoc: " ++ crash_msg)) list key
assocDefault deflt list key = assocDefaultUsing (==) deflt list key
assocUsing eq crash_msg list key = assocDefaultUsing eq (panic ("Failed in assoc: " ++ crash_msg)) list key
assocMaybe alist key
= lookup alist
where
lookup [] = Nothing
lookup ((tv,ty):rest) = if key == tv then Just ty else lookup rest
hasNoDups :: (Eq a) => [a] -> Bool
hasNoDups xs = f [] xs
where
f _ [] = True
f seen_so_far (x:xs) = if x `is_elem` seen_so_far
then False
else f (x:seen_so_far) xs
is_elem = isIn "hasNoDups"
equivClasses :: (a -> a -> Ordering)
-> [a]
-> [NonEmpty a]
equivClasses _ [] = []
equivClasses _ [stuff] = [stuff :| []]
equivClasses cmp items = NE.groupBy eq (sortBy cmp items)
where
eq a b = case cmp a b of { EQ -> True; _ -> False }
removeDups :: (a -> a -> Ordering)
-> [a]
-> ([a],
[NonEmpty a])
removeDups _ [] = ([], [])
removeDups _ [x] = ([x],[])
removeDups cmp xs
= case (mapAccumR collect_dups [] (equivClasses cmp xs)) of { (dups, xs') ->
(xs', dups) }
where
collect_dups :: [NonEmpty a] -> NonEmpty a -> ([NonEmpty a], a)
collect_dups dups_so_far (x :| []) = (dups_so_far, x)
collect_dups dups_so_far dups@(x :| _) = (dups:dups_so_far, x)
findDupsEq :: (a->a->Bool) -> [a] -> [NonEmpty a]
findDupsEq _ [] = []
findDupsEq eq (x:xs) | null eq_xs = findDupsEq eq xs
| otherwise = (x :| eq_xs) : findDupsEq eq neq_xs
where (eq_xs, neq_xs) = partition (eq x) xs