module Data.IntSet (
#if !defined(TESTING)
IntSet
#else
IntSet(..)
#endif
, (\\)
, null
, size
, member
, notMember
, isSubsetOf
, isProperSubsetOf
, empty
, singleton
, insert
, delete
, union
, unions
, difference
, intersection
, filter
, partition
, split
, splitMember
, map
, fold
, findMin
, findMax
, deleteMin
, deleteMax
, deleteFindMin
, deleteFindMax
, maxView
, minView
, elems
, toList
, fromList
, toAscList
, fromAscList
, fromDistinctAscList
, showTree
, showTreeWith
#if defined(TESTING)
, match
#endif
) where
import Prelude hiding (lookup,filter,foldr,foldl,null,map)
import Data.Bits
import qualified Data.List as List
import Data.Monoid (Monoid(..))
import Data.Maybe (fromMaybe)
import Data.Typeable
#if __GLASGOW_HASKELL__
import Text.Read
import Data.Data (Data(..), mkNoRepType)
#endif
#if __GLASGOW_HASKELL__ >= 503
import GHC.Exts ( Word(..), Int(..), shiftRL# )
#elif __GLASGOW_HASKELL__
import Word
import GlaExts ( Word(..), Int(..), shiftRL# )
#else
import Data.Word
#endif
infixl 9 \\
type Nat = Word
natFromInt :: Int -> Nat
natFromInt i = fromIntegral i
intFromNat :: Nat -> Int
intFromNat w = fromIntegral w
shiftRL :: Nat -> Int -> Nat
#if __GLASGOW_HASKELL__
shiftRL (W# x) (I# i)
= W# (shiftRL# x i)
#else
shiftRL x i = shiftR x i
#endif
(\\) :: IntSet -> IntSet -> IntSet
m1 \\ m2 = difference m1 m2
data IntSet = Nil
| Tip !Int
| Bin !Prefix !Mask !IntSet !IntSet
type Prefix = Int
type Mask = Int
instance Monoid IntSet where
mempty = empty
mappend = union
mconcat = unions
#if __GLASGOW_HASKELL__
instance Data IntSet where
gfoldl f z is = z fromList `f` (toList is)
toConstr _ = error "toConstr"
gunfold _ _ = error "gunfold"
dataTypeOf _ = mkNoRepType "Data.IntSet.IntSet"
#endif
null :: IntSet -> Bool
null Nil = True
null _ = False
size :: IntSet -> Int
size t
= case t of
Bin _ _ l r -> size l + size r
Tip _ -> 1
Nil -> 0
member :: Int -> IntSet -> Bool
member x = x `seq` go
where
go (Bin p m l r)
| nomatch x p m = False
| zero x m = go l
| otherwise = go r
go (Tip y) = x == y
go Nil = False
notMember :: Int -> IntSet -> Bool
notMember k = not . member k
lookup :: Int -> IntSet -> Maybe Int
lookup k = k `seq` go
where
go (Bin _ m l r)
| zero k m = go l
| otherwise = go r
go (Tip kx)
| k == kx = Just kx
| otherwise = Nothing
go Nil = Nothing
empty :: IntSet
empty
= Nil
singleton :: Int -> IntSet
singleton x
= Tip x
insert :: Int -> IntSet -> IntSet
insert x t = x `seq`
case t of
Bin p m l r
| nomatch x p m -> join x (Tip x) p t
| zero x m -> Bin p m (insert x l) r
| otherwise -> Bin p m l (insert x r)
Tip y
| x==y -> Tip x
| otherwise -> join x (Tip x) y t
Nil -> Tip x
insertR :: Int -> IntSet -> IntSet
insertR x t = x `seq`
case t of
Bin p m l r
| nomatch x p m -> join x (Tip x) p t
| zero x m -> Bin p m (insert x l) r
| otherwise -> Bin p m l (insert x r)
Tip y
| x==y -> t
| otherwise -> join x (Tip x) y t
Nil -> Tip x
delete :: Int -> IntSet -> IntSet
delete x t = x `seq`
case t of
Bin p m l r
| nomatch x p m -> t
| zero x m -> bin p m (delete x l) r
| otherwise -> bin p m l (delete x r)
Tip y
| x==y -> Nil
| otherwise -> t
Nil -> Nil
unions :: [IntSet] -> IntSet
unions xs
= foldlStrict union empty xs
union :: IntSet -> IntSet -> IntSet
union t1@(Bin p1 m1 l1 r1) t2@(Bin p2 m2 l2 r2)
| shorter m1 m2 = union1
| shorter m2 m1 = union2
| p1 == p2 = Bin p1 m1 (union l1 l2) (union r1 r2)
| otherwise = join p1 t1 p2 t2
where
union1 | nomatch p2 p1 m1 = join p1 t1 p2 t2
| zero p2 m1 = Bin p1 m1 (union l1 t2) r1
| otherwise = Bin p1 m1 l1 (union r1 t2)
union2 | nomatch p1 p2 m2 = join p1 t1 p2 t2
| zero p1 m2 = Bin p2 m2 (union t1 l2) r2
| otherwise = Bin p2 m2 l2 (union t1 r2)
union (Tip x) t = insert x t
union t (Tip x) = insertR x t
union Nil t = t
union t Nil = t
difference :: IntSet -> IntSet -> IntSet
difference t1@(Bin p1 m1 l1 r1) t2@(Bin p2 m2 l2 r2)
| shorter m1 m2 = difference1
| shorter m2 m1 = difference2
| p1 == p2 = bin p1 m1 (difference l1 l2) (difference r1 r2)
| otherwise = t1
where
difference1 | nomatch p2 p1 m1 = t1
| zero p2 m1 = bin p1 m1 (difference l1 t2) r1
| otherwise = bin p1 m1 l1 (difference r1 t2)
difference2 | nomatch p1 p2 m2 = t1
| zero p1 m2 = difference t1 l2
| otherwise = difference t1 r2
difference t1@(Tip x) t2
| member x t2 = Nil
| otherwise = t1
difference Nil _ = Nil
difference t (Tip x) = delete x t
difference t Nil = t
intersection :: IntSet -> IntSet -> IntSet
intersection t1@(Bin p1 m1 l1 r1) t2@(Bin p2 m2 l2 r2)
| shorter m1 m2 = intersection1
| shorter m2 m1 = intersection2
| p1 == p2 = bin p1 m1 (intersection l1 l2) (intersection r1 r2)
| otherwise = Nil
where
intersection1 | nomatch p2 p1 m1 = Nil
| zero p2 m1 = intersection l1 t2
| otherwise = intersection r1 t2
intersection2 | nomatch p1 p2 m2 = Nil
| zero p1 m2 = intersection t1 l2
| otherwise = intersection t1 r2
intersection t1@(Tip x) t2
| member x t2 = t1
| otherwise = Nil
intersection t (Tip x)
= case lookup x t of
Just y -> Tip y
Nothing -> Nil
intersection Nil _ = Nil
intersection _ Nil = Nil
isProperSubsetOf :: IntSet -> IntSet -> Bool
isProperSubsetOf t1 t2
= case subsetCmp t1 t2 of
LT -> True
_ -> False
subsetCmp :: IntSet -> IntSet -> Ordering
subsetCmp t1@(Bin p1 m1 l1 r1) (Bin p2 m2 l2 r2)
| shorter m1 m2 = GT
| shorter m2 m1 = case subsetCmpLt of
GT -> GT
_ -> LT
| p1 == p2 = subsetCmpEq
| otherwise = GT
where
subsetCmpLt | nomatch p1 p2 m2 = GT
| zero p1 m2 = subsetCmp t1 l2
| otherwise = subsetCmp t1 r2
subsetCmpEq = case (subsetCmp l1 l2, subsetCmp r1 r2) of
(GT,_ ) -> GT
(_ ,GT) -> GT
(EQ,EQ) -> EQ
_ -> LT
subsetCmp (Bin _ _ _ _) _ = GT
subsetCmp (Tip x) (Tip y)
| x==y = EQ
| otherwise = GT
subsetCmp (Tip x) t
| member x t = LT
| otherwise = GT
subsetCmp Nil Nil = EQ
subsetCmp Nil _ = LT
isSubsetOf :: IntSet -> IntSet -> Bool
isSubsetOf t1@(Bin p1 m1 l1 r1) (Bin p2 m2 l2 r2)
| shorter m1 m2 = False
| shorter m2 m1 = match p1 p2 m2 && (if zero p1 m2 then isSubsetOf t1 l2
else isSubsetOf t1 r2)
| otherwise = (p1==p2) && isSubsetOf l1 l2 && isSubsetOf r1 r2
isSubsetOf (Bin _ _ _ _) _ = False
isSubsetOf (Tip x) t = member x t
isSubsetOf Nil _ = True
filter :: (Int -> Bool) -> IntSet -> IntSet
filter predicate t
= case t of
Bin p m l r
-> bin p m (filter predicate l) (filter predicate r)
Tip x
| predicate x -> t
| otherwise -> Nil
Nil -> Nil
partition :: (Int -> Bool) -> IntSet -> (IntSet,IntSet)
partition predicate t
= case t of
Bin p m l r
-> let (l1,l2) = partition predicate l
(r1,r2) = partition predicate r
in (bin p m l1 r1, bin p m l2 r2)
Tip x
| predicate x -> (t,Nil)
| otherwise -> (Nil,t)
Nil -> (Nil,Nil)
split :: Int -> IntSet -> (IntSet,IntSet)
split x t
= case t of
Bin _ m l r
| m < 0 -> if x >= 0 then let (lt,gt) = split' x l in (union r lt, gt)
else let (lt,gt) = split' x r in (lt, union gt l)
| otherwise -> split' x t
Tip y
| x>y -> (t,Nil)
| x<y -> (Nil,t)
| otherwise -> (Nil,Nil)
Nil -> (Nil, Nil)
split' :: Int -> IntSet -> (IntSet,IntSet)
split' x t
= case t of
Bin p m l r
| match x p m -> if zero x m then let (lt,gt) = split' x l in (lt,union gt r)
else let (lt,gt) = split' x r in (union l lt,gt)
| otherwise -> if x < p then (Nil, t)
else (t, Nil)
Tip y
| x>y -> (t,Nil)
| x<y -> (Nil,t)
| otherwise -> (Nil,Nil)
Nil -> (Nil,Nil)
splitMember :: Int -> IntSet -> (IntSet,Bool,IntSet)
splitMember x t
= case t of
Bin _ m l r
| m < 0 -> if x >= 0 then let (lt,found,gt) = splitMember' x l in (union r lt, found, gt)
else let (lt,found,gt) = splitMember' x r in (lt, found, union gt l)
| otherwise -> splitMember' x t
Tip y
| x>y -> (t,False,Nil)
| x<y -> (Nil,False,t)
| otherwise -> (Nil,True,Nil)
Nil -> (Nil,False,Nil)
splitMember' :: Int -> IntSet -> (IntSet,Bool,IntSet)
splitMember' x t
= case t of
Bin p m l r
| match x p m -> if zero x m then let (lt,found,gt) = splitMember x l in (lt,found,union gt r)
else let (lt,found,gt) = splitMember x r in (union l lt,found,gt)
| otherwise -> if x < p then (Nil, False, t)
else (t, False, Nil)
Tip y
| x>y -> (t,False,Nil)
| x<y -> (Nil,False,t)
| otherwise -> (Nil,True,Nil)
Nil -> (Nil,False,Nil)
maxView :: IntSet -> Maybe (Int, IntSet)
maxView t
= case t of
Bin p m l r | m < 0 -> let (result,t') = maxViewUnsigned l in Just (result, bin p m t' r)
Bin p m l r -> let (result,t') = maxViewUnsigned r in Just (result, bin p m l t')
Tip y -> Just (y,Nil)
Nil -> Nothing
maxViewUnsigned :: IntSet -> (Int, IntSet)
maxViewUnsigned t
= case t of
Bin p m l r -> let (result,t') = maxViewUnsigned r in (result, bin p m l t')
Tip y -> (y, Nil)
Nil -> error "maxViewUnsigned Nil"
minView :: IntSet -> Maybe (Int, IntSet)
minView t
= case t of
Bin p m l r | m < 0 -> let (result,t') = minViewUnsigned r in Just (result, bin p m l t')
Bin p m l r -> let (result,t') = minViewUnsigned l in Just (result, bin p m t' r)
Tip y -> Just (y, Nil)
Nil -> Nothing
minViewUnsigned :: IntSet -> (Int, IntSet)
minViewUnsigned t
= case t of
Bin p m l r -> let (result,t') = minViewUnsigned l in (result, bin p m t' r)
Tip y -> (y, Nil)
Nil -> error "minViewUnsigned Nil"
deleteFindMin :: IntSet -> (Int, IntSet)
deleteFindMin = fromMaybe (error "deleteFindMin: empty set has no minimal element") . minView
deleteFindMax :: IntSet -> (Int, IntSet)
deleteFindMax = fromMaybe (error "deleteFindMax: empty set has no maximal element") . maxView
findMin :: IntSet -> Int
findMin Nil = error "findMin: empty set has no minimal element"
findMin (Tip x) = x
findMin (Bin _ m l r)
| m < 0 = find r
| otherwise = find l
where find (Tip x) = x
find (Bin _ _ l' _) = find l'
find Nil = error "findMin Nil"
findMax :: IntSet -> Int
findMax Nil = error "findMax: empty set has no maximal element"
findMax (Tip x) = x
findMax (Bin _ m l r)
| m < 0 = find l
| otherwise = find r
where find (Tip x) = x
find (Bin _ _ _ r') = find r'
find Nil = error "findMax Nil"
deleteMin :: IntSet -> IntSet
deleteMin = maybe (error "deleteMin: empty set has no minimal element") snd . minView
deleteMax :: IntSet -> IntSet
deleteMax = maybe (error "deleteMax: empty set has no maximal element") snd . maxView
map :: (Int->Int) -> IntSet -> IntSet
map f = fromList . List.map f . toList
fold :: (Int -> b -> b) -> b -> IntSet -> b
fold f z t
= case t of
Bin 0 m l r | m < 0 -> go (go z l) r
Bin _ _ _ _ -> go z t
Tip x -> f x z
Nil -> z
where
go z' (Bin _ _ l r) = go (go z' r) l
go z' (Tip x) = f x z'
go z' Nil = z'
elems :: IntSet -> [Int]
elems s
= toList s
toList :: IntSet -> [Int]
toList t
= fold (:) [] t
toAscList :: IntSet -> [Int]
toAscList t = toList t
fromList :: [Int] -> IntSet
fromList xs
= foldlStrict ins empty xs
where
ins t x = insert x t
fromAscList :: [Int] -> IntSet
fromAscList [] = Nil
fromAscList (x0 : xs0) = fromDistinctAscList (combineEq x0 xs0)
where
combineEq x' [] = [x']
combineEq x' (x:xs)
| x==x' = combineEq x' xs
| otherwise = x' : combineEq x xs
fromDistinctAscList :: [Int] -> IntSet
fromDistinctAscList [] = Nil
fromDistinctAscList (z0 : zs0) = work z0 zs0 Nada
where
work x [] stk = finish x (Tip x) stk
work x (z:zs) stk = reduce z zs (branchMask z x) x (Tip x) stk
reduce z zs _ px tx Nada = work z zs (Push px tx Nada)
reduce z zs m px tx stk@(Push py ty stk') =
let mxy = branchMask px py
pxy = mask px mxy
in if shorter m mxy
then reduce z zs m pxy (Bin pxy mxy ty tx) stk'
else work z zs (Push px tx stk)
finish _ t Nada = t
finish px tx (Push py ty stk) = finish p (join py ty px tx) stk
where m = branchMask px py
p = mask px m
data Stack = Push !Prefix !IntSet !Stack | Nada
instance Eq IntSet where
t1 == t2 = equal t1 t2
t1 /= t2 = nequal t1 t2
equal :: IntSet -> IntSet -> Bool
equal (Bin p1 m1 l1 r1) (Bin p2 m2 l2 r2)
= (m1 == m2) && (p1 == p2) && (equal l1 l2) && (equal r1 r2)
equal (Tip x) (Tip y)
= (x==y)
equal Nil Nil = True
equal _ _ = False
nequal :: IntSet -> IntSet -> Bool
nequal (Bin p1 m1 l1 r1) (Bin p2 m2 l2 r2)
= (m1 /= m2) || (p1 /= p2) || (nequal l1 l2) || (nequal r1 r2)
nequal (Tip x) (Tip y)
= (x/=y)
nequal Nil Nil = False
nequal _ _ = True
instance Ord IntSet where
compare s1 s2 = compare (toAscList s1) (toAscList s2)
instance Show IntSet where
showsPrec p xs = showParen (p > 10) $
showString "fromList " . shows (toList xs)
instance Read IntSet where
#ifdef __GLASGOW_HASKELL__
readPrec = parens $ prec 10 $ do
Ident "fromList" <- lexP
xs <- readPrec
return (fromList xs)
readListPrec = readListPrecDefault
#else
readsPrec p = readParen (p > 10) $ \ r -> do
("fromList",s) <- lex r
(xs,t) <- reads s
return (fromList xs,t)
#endif
#include "Typeable.h"
INSTANCE_TYPEABLE0(IntSet,intSetTc,"IntSet")
showTree :: IntSet -> String
showTree s
= showTreeWith True False s
showTreeWith :: Bool -> Bool -> IntSet -> String
showTreeWith hang wide t
| hang = (showsTreeHang wide [] t) ""
| otherwise = (showsTree wide [] [] t) ""
showsTree :: Bool -> [String] -> [String] -> IntSet -> ShowS
showsTree wide lbars rbars t
= case t of
Bin p m l r
-> showsTree wide (withBar rbars) (withEmpty rbars) r .
showWide wide rbars .
showsBars lbars . showString (showBin p m) . showString "\n" .
showWide wide lbars .
showsTree wide (withEmpty lbars) (withBar lbars) l
Tip x
-> showsBars lbars . showString " " . shows x . showString "\n"
Nil -> showsBars lbars . showString "|\n"
showsTreeHang :: Bool -> [String] -> IntSet -> ShowS
showsTreeHang wide bars t
= case t of
Bin p m l r
-> showsBars bars . showString (showBin p m) . showString "\n" .
showWide wide bars .
showsTreeHang wide (withBar bars) l .
showWide wide bars .
showsTreeHang wide (withEmpty bars) r
Tip x
-> showsBars bars . showString " " . shows x . showString "\n"
Nil -> showsBars bars . showString "|\n"
showBin :: Prefix -> Mask -> String
showBin _ _
= "*"
showWide :: Bool -> [String] -> String -> String
showWide wide bars
| wide = showString (concat (reverse bars)) . showString "|\n"
| otherwise = id
showsBars :: [String] -> ShowS
showsBars bars
= case bars of
[] -> id
_ -> showString (concat (reverse (tail bars))) . showString node
node :: String
node = "+--"
withBar, withEmpty :: [String] -> [String]
withBar bars = "| ":bars
withEmpty bars = " ":bars
join :: Prefix -> IntSet -> Prefix -> IntSet -> IntSet
join p1 t1 p2 t2
| zero p1 m = Bin p m t1 t2
| otherwise = Bin p m t2 t1
where
m = branchMask p1 p2
p = mask p1 m
bin :: Prefix -> Mask -> IntSet -> IntSet -> IntSet
bin _ _ l Nil = l
bin _ _ Nil r = r
bin p m l r = Bin p m l r
zero :: Int -> Mask -> Bool
zero i m
= (natFromInt i) .&. (natFromInt m) == 0
nomatch,match :: Int -> Prefix -> Mask -> Bool
nomatch i p m
= (mask i m) /= p
match i p m
= (mask i m) == p
mask :: Int -> Mask -> Prefix
mask i m
= maskW (natFromInt i) (natFromInt m)
maskW :: Nat -> Nat -> Prefix
maskW i m
= intFromNat (i .&. (complement (m1) `xor` m))
shorter :: Mask -> Mask -> Bool
shorter m1 m2
= (natFromInt m1) > (natFromInt m2)
branchMask :: Prefix -> Prefix -> Mask
branchMask p1 p2
= intFromNat (highestBitMask (natFromInt p1 `xor` natFromInt p2))
highestBitMask :: Nat -> Nat
highestBitMask x0
= case (x0 .|. shiftRL x0 1) of
x1 -> case (x1 .|. shiftRL x1 2) of
x2 -> case (x2 .|. shiftRL x2 4) of
x3 -> case (x3 .|. shiftRL x3 8) of
x4 -> case (x4 .|. shiftRL x4 16) of
x5 -> case (x5 .|. shiftRL x5 32) of
x6 -> (x6 `xor` (shiftRL x6 1))
foldlStrict :: (a -> b -> a) -> a -> [b] -> a
foldlStrict f = go
where
go z [] = z
go z (x:xs) = let z' = f z x in z' `seq` go z' xs