{-# LANGUAGE MagicHash, TypeFamilies, FlexibleInstances, BangPatterns, CPP #-}
module Data.Interned.IntSet (
IntSet
, identity
, (\\)
, null
, size
, member
, notMember
, isSubsetOf
, isProperSubsetOf
, empty
, singleton
, insert
, delete
, union, unions
, difference
, intersection
, filter
, partition
, split
, splitMember
, findMin
, findMax
, deleteMin
, deleteMax
, deleteFindMin
, deleteFindMax
, maxView
, minView
, map
, fold
, elems
, toList
, fromList
, toAscList
, fromAscList
, fromDistinctAscList
, showTree
, showTreeWith
) where
import Prelude hiding (lookup,filter,foldr,foldl,null,map)
import qualified Data.List as List
import Data.Maybe (fromMaybe)
import Data.Interned.Internal
import Data.Bits
import Data.Hashable
import Text.Read
import GHC.Exts ( Word(..), Int(..), shiftRL# )
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (Monoid(..))
#endif
#if MIN_VERSION_base(4,9,0) && !(MIN_VERSION_base(4,11,0))
import Data.Semigroup (Semigroup(..))
#endif
infixl 9 \\
type Nat = Word
natFromInt :: Int -> Nat
natFromInt :: Int -> Nat
natFromInt Int
i = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i
intFromNat :: Nat -> Int
intFromNat :: Nat -> Int
intFromNat Nat
w = forall a b. (Integral a, Num b) => a -> b
fromIntegral Nat
w
shiftRL :: Nat -> Int -> Nat
shiftRL :: Nat -> Int -> Nat
shiftRL (W# Word#
x) (I# Int#
i) = Word# -> Nat
W# (Word# -> Int# -> Word#
shiftRL# Word#
x Int#
i)
(\\) :: IntSet -> IntSet -> IntSet
IntSet
m1 \\ :: IntSet -> IntSet -> IntSet
\\ IntSet
m2 = IntSet -> IntSet -> IntSet
difference IntSet
m1 IntSet
m2
data IntSet
= Nil
| Tip {-# UNPACK #-} !Id {-# UNPACK #-} !Int
| Bin {-# UNPACK #-} !Id {-# UNPACK #-} !Int {-# UNPACK #-} !Prefix {-# UNPACK #-} !Mask !IntSet !IntSet
data UninternedIntSet
= UNil
| UTip !Int
| UBin {-# UNPACK #-} !Prefix {-# UNPACK #-} !Mask !IntSet !IntSet
tip :: Int -> IntSet
tip :: Int -> IntSet
tip Int
n = forall t. Interned t => Uninterned t -> t
intern (Int -> UninternedIntSet
UTip Int
n)
bin :: Prefix -> Mask -> IntSet -> IntSet -> IntSet
bin :: Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
_ Int
_ IntSet
l IntSet
Nil = IntSet
l
bin Int
_ Int
_ IntSet
Nil IntSet
r = IntSet
r
bin Int
p Int
m IntSet
l IntSet
r = forall t. Interned t => Uninterned t -> t
intern (Int -> Int -> IntSet -> IntSet -> UninternedIntSet
UBin Int
p Int
m IntSet
l IntSet
r)
bin_ :: Prefix -> Mask -> IntSet -> IntSet -> IntSet
bin_ :: Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p Int
m IntSet
l IntSet
r = forall t. Interned t => Uninterned t -> t
intern (Int -> Int -> IntSet -> IntSet -> UninternedIntSet
UBin Int
p Int
m IntSet
l IntSet
r)
identity :: IntSet -> Id
identity :: IntSet -> Int
identity IntSet
Nil = Int
0
identity (Tip Int
i Int
_) = Int
i
identity (Bin Int
i Int
_ Int
_ Int
_ IntSet
_ IntSet
_) = Int
i
instance Interned IntSet where
type Uninterned IntSet = UninternedIntSet
data Description IntSet
= DNil
| DTip {-# UNPACK #-} !Int
| DBin {-# UNPACK #-} !Prefix {-# UNPACK #-} !Mask {-# UNPACK #-} !Id {-# UNPACK #-} !Id
deriving Description IntSet -> Description IntSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Description IntSet -> Description IntSet -> Bool
$c/= :: Description IntSet -> Description IntSet -> Bool
== :: Description IntSet -> Description IntSet -> Bool
$c== :: Description IntSet -> Description IntSet -> Bool
Eq
describe :: Uninterned IntSet -> Description IntSet
describe Uninterned IntSet
UninternedIntSet
UNil = Description IntSet
DNil
describe (UTip Int
j) = Int -> Description IntSet
DTip Int
j
describe (UBin Int
p Int
m IntSet
l IntSet
r) = Int -> Int -> Int -> Int -> Description IntSet
DBin Int
p Int
m (IntSet -> Int
identity IntSet
l) (IntSet -> Int
identity IntSet
r)
cacheWidth :: forall (p :: * -> *). p IntSet -> Int
cacheWidth p IntSet
_ = Int
16384
seedIdentity :: forall (p :: * -> *). p IntSet -> Int
seedIdentity p IntSet
_ = Int
1
identify :: Int -> Uninterned IntSet -> IntSet
identify Int
_ Uninterned IntSet
UninternedIntSet
UNil = IntSet
Nil
identify Int
i (UTip Int
j) = Int -> Int -> IntSet
Tip Int
i Int
j
identify Int
i (UBin Int
p Int
m IntSet
l IntSet
r) = Int -> Int -> Int -> Int -> IntSet -> IntSet -> IntSet
Bin Int
i (IntSet -> Int
size IntSet
l forall a. Num a => a -> a -> a
+ IntSet -> Int
size IntSet
r) Int
p Int
m IntSet
l IntSet
r
cache :: Cache IntSet
cache = Cache IntSet
intSetCache
instance Hashable (Description IntSet) where
hashWithSalt :: Int -> Description IntSet -> Int
hashWithSalt Int
s Description IntSet
R:DescriptionIntSet
DNil = Int
s forall a. Hashable a => Int -> a -> Int
`hashWithSalt` (Int
0 :: Int)
hashWithSalt Int
s (DTip Int
n) = Int
s forall a. Hashable a => Int -> a -> Int
`hashWithSalt` (Int
1 :: Int) forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
n
hashWithSalt Int
s (DBin Int
p Int
m Int
l Int
r) = Int
s forall a. Hashable a => Int -> a -> Int
`hashWithSalt` (Int
2 :: Int) forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
p forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
m forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
l forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
r
intSetCache :: Cache IntSet
intSetCache :: Cache IntSet
intSetCache = forall t. Interned t => Cache t
mkCache
{-# NOINLINE intSetCache #-}
instance Uninternable IntSet where
unintern :: IntSet -> Uninterned IntSet
unintern IntSet
Nil = UninternedIntSet
UNil
unintern (Tip Int
_ Int
j) = Int -> UninternedIntSet
UTip Int
j
unintern (Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r) = Int -> Int -> IntSet -> IntSet -> UninternedIntSet
UBin Int
p Int
m IntSet
l IntSet
r
type Prefix = Int
type Mask = Int
#if MIN_VERSION_base(4,9,0)
instance Semigroup IntSet where
<> :: IntSet -> IntSet -> IntSet
(<>) = IntSet -> IntSet -> IntSet
union
#endif
instance Monoid IntSet where
mempty :: IntSet
mempty = IntSet
empty
#if !(MIN_VERSION_base(4,11,0))
mappend = union
#endif
mconcat :: [IntSet] -> IntSet
mconcat = [IntSet] -> IntSet
unions
null :: IntSet -> Bool
null :: IntSet -> Bool
null IntSet
Nil = Bool
True
null IntSet
_ = Bool
False
size :: IntSet -> Int
size :: IntSet -> Int
size IntSet
t
= case IntSet
t of
Bin Int
_ Int
s Int
_ Int
_ IntSet
_ IntSet
_ -> Int
s
Tip Int
_ Int
_ -> Int
1
IntSet
Nil -> Int
0
member :: Int -> IntSet -> Bool
member :: Int -> IntSet -> Bool
member Int
x IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r
| Int -> Int -> Int -> Bool
nomatch Int
x Int
p Int
m -> Bool
False
| Int -> Int -> Bool
zero Int
x Int
m -> Int -> IntSet -> Bool
member Int
x IntSet
l
| Bool
otherwise -> Int -> IntSet -> Bool
member Int
x IntSet
r
Tip Int
_ Int
y -> (Int
xforall a. Eq a => a -> a -> Bool
==Int
y)
IntSet
Nil -> Bool
False
notMember :: Int -> IntSet -> Bool
notMember :: Int -> IntSet -> Bool
notMember Int
k = Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> IntSet -> Bool
member Int
k
lookup :: Int -> IntSet -> Maybe Int
lookup :: Int -> IntSet -> Maybe Int
lookup Int
k IntSet
t
= let nk :: Nat
nk = Int -> Nat
natFromInt Int
k in seq :: forall a b. a -> b -> b
seq Nat
nk (Nat -> IntSet -> Maybe Int
lookupN Nat
nk IntSet
t)
lookupN :: Nat -> IntSet -> Maybe Int
lookupN :: Nat -> IntSet -> Maybe Int
lookupN Nat
k IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
_ Int
m IntSet
l IntSet
r
| Nat -> Nat -> Bool
zeroN Nat
k (Int -> Nat
natFromInt Int
m) -> Nat -> IntSet -> Maybe Int
lookupN Nat
k IntSet
l
| Bool
otherwise -> Nat -> IntSet -> Maybe Int
lookupN Nat
k IntSet
r
Tip Int
_ Int
kx
| (Nat
k forall a. Eq a => a -> a -> Bool
== Int -> Nat
natFromInt Int
kx) -> forall a. a -> Maybe a
Just Int
kx
| Bool
otherwise -> forall a. Maybe a
Nothing
IntSet
Nil -> forall a. Maybe a
Nothing
empty :: IntSet
empty :: IntSet
empty = IntSet
Nil
singleton :: Int -> IntSet
singleton :: Int -> IntSet
singleton Int
x = Int -> IntSet
tip Int
x
insert :: Int -> IntSet -> IntSet
insert :: Int -> IntSet -> IntSet
insert Int
x IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r
| Int -> Int -> Int -> Bool
nomatch Int
x Int
p Int
m -> Int -> IntSet -> Int -> IntSet -> IntSet
join Int
x (Int -> IntSet
tip Int
x) Int
p IntSet
t
| Int -> Int -> Bool
zero Int
x Int
m -> Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p Int
m (Int -> IntSet -> IntSet
insert Int
x IntSet
l) IntSet
r
| Bool
otherwise -> Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p Int
m IntSet
l (Int -> IntSet -> IntSet
insert Int
x IntSet
r)
Tip Int
_ Int
y
| Int
xforall a. Eq a => a -> a -> Bool
==Int
y -> Int -> IntSet
tip Int
x
| Bool
otherwise -> Int -> IntSet -> Int -> IntSet -> IntSet
join Int
x (Int -> IntSet
tip Int
x) Int
y IntSet
t
IntSet
Nil -> Int -> IntSet
tip Int
x
insertR :: Int -> IntSet -> IntSet
insertR :: Int -> IntSet -> IntSet
insertR Int
x IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r
| Int -> Int -> Int -> Bool
nomatch Int
x Int
p Int
m -> Int -> IntSet -> Int -> IntSet -> IntSet
join Int
x (Int -> IntSet
tip Int
x) Int
p IntSet
t
| Int -> Int -> Bool
zero Int
x Int
m -> Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p Int
m (Int -> IntSet -> IntSet
insert Int
x IntSet
l) IntSet
r
| Bool
otherwise -> Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p Int
m IntSet
l (Int -> IntSet -> IntSet
insert Int
x IntSet
r)
Tip Int
_ Int
y
| Int
xforall a. Eq a => a -> a -> Bool
==Int
y -> IntSet
t
| Bool
otherwise -> Int -> IntSet -> Int -> IntSet -> IntSet
join Int
x (Int -> IntSet
tip Int
x) Int
y IntSet
t
IntSet
Nil -> Int -> IntSet
tip Int
x
delete :: Int -> IntSet -> IntSet
delete :: Int -> IntSet -> IntSet
delete Int
x IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r
| Int -> Int -> Int -> Bool
nomatch Int
x Int
p Int
m -> IntSet
t
| Int -> Int -> Bool
zero Int
x Int
m -> Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m (Int -> IntSet -> IntSet
delete Int
x IntSet
l) IntSet
r
| Bool
otherwise -> Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
l (Int -> IntSet -> IntSet
delete Int
x IntSet
r)
Tip Int
_ Int
y
| Int
xforall a. Eq a => a -> a -> Bool
==Int
y -> IntSet
Nil
| Bool
otherwise -> IntSet
t
IntSet
Nil -> IntSet
Nil
unions :: [IntSet] -> IntSet
unions :: [IntSet] -> IntSet
unions [IntSet]
xs = forall a b. (a -> b -> a) -> a -> [b] -> a
foldlStrict IntSet -> IntSet -> IntSet
union IntSet
empty [IntSet]
xs
union :: IntSet -> IntSet -> IntSet
union :: IntSet -> IntSet -> IntSet
union t1 :: IntSet
t1@(Bin Int
_ Int
_ Int
p1 Int
m1 IntSet
l1 IntSet
r1) t2 :: IntSet
t2@(Bin Int
_ Int
_ Int
p2 Int
m2 IntSet
l2 IntSet
r2)
| Int -> Int -> Bool
shorter Int
m1 Int
m2 = IntSet
union1
| Int -> Int -> Bool
shorter Int
m2 Int
m1 = IntSet
union2
| Int
p1 forall a. Eq a => a -> a -> Bool
== Int
p2 = Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p1 Int
m1 (IntSet -> IntSet -> IntSet
union IntSet
l1 IntSet
l2) (IntSet -> IntSet -> IntSet
union IntSet
r1 IntSet
r2)
| Bool
otherwise = Int -> IntSet -> Int -> IntSet -> IntSet
join Int
p1 IntSet
t1 Int
p2 IntSet
t2
where
union1 :: IntSet
union1 | Int -> Int -> Int -> Bool
nomatch Int
p2 Int
p1 Int
m1 = Int -> IntSet -> Int -> IntSet -> IntSet
join Int
p1 IntSet
t1 Int
p2 IntSet
t2
| Int -> Int -> Bool
zero Int
p2 Int
m1 = Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p1 Int
m1 (IntSet -> IntSet -> IntSet
union IntSet
l1 IntSet
t2) IntSet
r1
| Bool
otherwise = Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p1 Int
m1 IntSet
l1 (IntSet -> IntSet -> IntSet
union IntSet
r1 IntSet
t2)
union2 :: IntSet
union2 | Int -> Int -> Int -> Bool
nomatch Int
p1 Int
p2 Int
m2 = Int -> IntSet -> Int -> IntSet -> IntSet
join Int
p1 IntSet
t1 Int
p2 IntSet
t2
| Int -> Int -> Bool
zero Int
p1 Int
m2 = Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p2 Int
m2 (IntSet -> IntSet -> IntSet
union IntSet
t1 IntSet
l2) IntSet
r2
| Bool
otherwise = Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p2 Int
m2 IntSet
l2 (IntSet -> IntSet -> IntSet
union IntSet
t1 IntSet
r2)
union (Tip Int
_ Int
x) IntSet
t = Int -> IntSet -> IntSet
insert Int
x IntSet
t
union IntSet
t (Tip Int
_ Int
x) = Int -> IntSet -> IntSet
insertR Int
x IntSet
t
union IntSet
Nil IntSet
t = IntSet
t
union IntSet
t IntSet
Nil = IntSet
t
difference :: IntSet -> IntSet -> IntSet
difference :: IntSet -> IntSet -> IntSet
difference t1 :: IntSet
t1@(Bin Int
_ Int
_ Int
p1 Int
m1 IntSet
l1 IntSet
r1) t2 :: IntSet
t2@(Bin Int
_ Int
_ Int
p2 Int
m2 IntSet
l2 IntSet
r2)
| Int -> Int -> Bool
shorter Int
m1 Int
m2 = IntSet
difference1
| Int -> Int -> Bool
shorter Int
m2 Int
m1 = IntSet
difference2
| Int
p1 forall a. Eq a => a -> a -> Bool
== Int
p2 = Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p1 Int
m1 (IntSet -> IntSet -> IntSet
difference IntSet
l1 IntSet
l2) (IntSet -> IntSet -> IntSet
difference IntSet
r1 IntSet
r2)
| Bool
otherwise = IntSet
t1
where
difference1 :: IntSet
difference1 | Int -> Int -> Int -> Bool
nomatch Int
p2 Int
p1 Int
m1 = IntSet
t1
| Int -> Int -> Bool
zero Int
p2 Int
m1 = Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p1 Int
m1 (IntSet -> IntSet -> IntSet
difference IntSet
l1 IntSet
t2) IntSet
r1
| Bool
otherwise = Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p1 Int
m1 IntSet
l1 (IntSet -> IntSet -> IntSet
difference IntSet
r1 IntSet
t2)
difference2 :: IntSet
difference2 | Int -> Int -> Int -> Bool
nomatch Int
p1 Int
p2 Int
m2 = IntSet
t1
| Int -> Int -> Bool
zero Int
p1 Int
m2 = IntSet -> IntSet -> IntSet
difference IntSet
t1 IntSet
l2
| Bool
otherwise = IntSet -> IntSet -> IntSet
difference IntSet
t1 IntSet
r2
difference t1 :: IntSet
t1@(Tip Int
_ Int
x) IntSet
t2
| Int -> IntSet -> Bool
member Int
x IntSet
t2 = IntSet
Nil
| Bool
otherwise = IntSet
t1
difference IntSet
Nil IntSet
_ = IntSet
Nil
difference IntSet
t (Tip Int
_ Int
x) = Int -> IntSet -> IntSet
delete Int
x IntSet
t
difference IntSet
t IntSet
Nil = IntSet
t
intersection :: IntSet -> IntSet -> IntSet
intersection :: IntSet -> IntSet -> IntSet
intersection t1 :: IntSet
t1@(Bin Int
_ Int
_ Int
p1 Int
m1 IntSet
l1 IntSet
r1) t2 :: IntSet
t2@(Bin Int
_ Int
_ Int
p2 Int
m2 IntSet
l2 IntSet
r2)
| Int -> Int -> Bool
shorter Int
m1 Int
m2 = IntSet
intersection1
| Int -> Int -> Bool
shorter Int
m2 Int
m1 = IntSet
intersection2
| Int
p1 forall a. Eq a => a -> a -> Bool
== Int
p2 = Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p1 Int
m1 (IntSet -> IntSet -> IntSet
intersection IntSet
l1 IntSet
l2) (IntSet -> IntSet -> IntSet
intersection IntSet
r1 IntSet
r2)
| Bool
otherwise = IntSet
Nil
where
intersection1 :: IntSet
intersection1 | Int -> Int -> Int -> Bool
nomatch Int
p2 Int
p1 Int
m1 = IntSet
Nil
| Int -> Int -> Bool
zero Int
p2 Int
m1 = IntSet -> IntSet -> IntSet
intersection IntSet
l1 IntSet
t2
| Bool
otherwise = IntSet -> IntSet -> IntSet
intersection IntSet
r1 IntSet
t2
intersection2 :: IntSet
intersection2 | Int -> Int -> Int -> Bool
nomatch Int
p1 Int
p2 Int
m2 = IntSet
Nil
| Int -> Int -> Bool
zero Int
p1 Int
m2 = IntSet -> IntSet -> IntSet
intersection IntSet
t1 IntSet
l2
| Bool
otherwise = IntSet -> IntSet -> IntSet
intersection IntSet
t1 IntSet
r2
intersection t1 :: IntSet
t1@(Tip Int
_ Int
x) IntSet
t2
| Int -> IntSet -> Bool
member Int
x IntSet
t2 = IntSet
t1
| Bool
otherwise = IntSet
Nil
intersection IntSet
t (Tip Int
_ Int
x)
= case Int -> IntSet -> Maybe Int
lookup Int
x IntSet
t of
Just Int
y -> Int -> IntSet
tip Int
y
Maybe Int
Nothing -> IntSet
Nil
intersection IntSet
Nil IntSet
_ = IntSet
Nil
intersection IntSet
_ IntSet
Nil = IntSet
Nil
isProperSubsetOf :: IntSet -> IntSet -> Bool
isProperSubsetOf :: IntSet -> IntSet -> Bool
isProperSubsetOf IntSet
t1 IntSet
t2
= case IntSet -> IntSet -> Ordering
subsetCmp IntSet
t1 IntSet
t2 of
Ordering
LT -> Bool
True
Ordering
_ -> Bool
False
subsetCmp :: IntSet -> IntSet -> Ordering
subsetCmp :: IntSet -> IntSet -> Ordering
subsetCmp t1 :: IntSet
t1@(Bin Int
_ Int
_ Int
p1 Int
m1 IntSet
l1 IntSet
r1) (Bin Int
_ Int
_ Int
p2 Int
m2 IntSet
l2 IntSet
r2)
| Int -> Int -> Bool
shorter Int
m1 Int
m2 = Ordering
GT
| Int -> Int -> Bool
shorter Int
m2 Int
m1 = case Ordering
subsetCmpLt of
Ordering
GT -> Ordering
GT
Ordering
_ -> Ordering
LT
| Int
p1 forall a. Eq a => a -> a -> Bool
== Int
p2 = Ordering
subsetCmpEq
| Bool
otherwise = Ordering
GT
where
subsetCmpLt :: Ordering
subsetCmpLt | Int -> Int -> Int -> Bool
nomatch Int
p1 Int
p2 Int
m2 = Ordering
GT
| Int -> Int -> Bool
zero Int
p1 Int
m2 = IntSet -> IntSet -> Ordering
subsetCmp IntSet
t1 IntSet
l2
| Bool
otherwise = IntSet -> IntSet -> Ordering
subsetCmp IntSet
t1 IntSet
r2
subsetCmpEq :: Ordering
subsetCmpEq = case (IntSet -> IntSet -> Ordering
subsetCmp IntSet
l1 IntSet
l2, IntSet -> IntSet -> Ordering
subsetCmp IntSet
r1 IntSet
r2) of
(Ordering
GT,Ordering
_ ) -> Ordering
GT
(Ordering
_ ,Ordering
GT) -> Ordering
GT
(Ordering
EQ,Ordering
EQ) -> Ordering
EQ
(Ordering, Ordering)
_ -> Ordering
LT
subsetCmp (Bin Int
_ Int
_ Int
_ Int
_ IntSet
_ IntSet
_) IntSet
_ = Ordering
GT
subsetCmp (Tip Int
_ Int
x) (Tip Int
_ Int
y)
| Int
xforall a. Eq a => a -> a -> Bool
==Int
y = Ordering
EQ
| Bool
otherwise = Ordering
GT
subsetCmp (Tip Int
_ Int
x) IntSet
t
| Int -> IntSet -> Bool
member Int
x IntSet
t = Ordering
LT
| Bool
otherwise = Ordering
GT
subsetCmp IntSet
Nil IntSet
Nil = Ordering
EQ
subsetCmp IntSet
Nil IntSet
_ = Ordering
LT
isSubsetOf :: IntSet -> IntSet -> Bool
isSubsetOf :: IntSet -> IntSet -> Bool
isSubsetOf t1 :: IntSet
t1@(Bin Int
_ Int
_ Int
p1 Int
m1 IntSet
l1 IntSet
r1) (Bin Int
_ Int
_ Int
p2 Int
m2 IntSet
l2 IntSet
r2)
| Int -> Int -> Bool
shorter Int
m1 Int
m2 = Bool
False
| Int -> Int -> Bool
shorter Int
m2 Int
m1 = Int -> Int -> Int -> Bool
match Int
p1 Int
p2 Int
m2 Bool -> Bool -> Bool
&& (if Int -> Int -> Bool
zero Int
p1 Int
m2 then IntSet -> IntSet -> Bool
isSubsetOf IntSet
t1 IntSet
l2
else IntSet -> IntSet -> Bool
isSubsetOf IntSet
t1 IntSet
r2)
| Bool
otherwise = (Int
p1forall a. Eq a => a -> a -> Bool
==Int
p2) Bool -> Bool -> Bool
&& IntSet -> IntSet -> Bool
isSubsetOf IntSet
l1 IntSet
l2 Bool -> Bool -> Bool
&& IntSet -> IntSet -> Bool
isSubsetOf IntSet
r1 IntSet
r2
isSubsetOf (Bin Int
_ Int
_ Int
_ Int
_ IntSet
_ IntSet
_) IntSet
_ = Bool
False
isSubsetOf (Tip Int
_ Int
x) IntSet
t = Int -> IntSet -> Bool
member Int
x IntSet
t
isSubsetOf IntSet
Nil IntSet
_ = Bool
True
filter :: (Int -> Bool) -> IntSet -> IntSet
filter :: (Int -> Bool) -> IntSet -> IntSet
filter Int -> Bool
predicate IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r
-> Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m ((Int -> Bool) -> IntSet -> IntSet
filter Int -> Bool
predicate IntSet
l) ((Int -> Bool) -> IntSet -> IntSet
filter Int -> Bool
predicate IntSet
r)
Tip Int
_ Int
x
| Int -> Bool
predicate Int
x -> IntSet
t
| Bool
otherwise -> IntSet
Nil
IntSet
Nil -> IntSet
Nil
partition :: (Int -> Bool) -> IntSet -> (IntSet,IntSet)
partition :: (Int -> Bool) -> IntSet -> (IntSet, IntSet)
partition Int -> Bool
predicate IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r
-> let (IntSet
l1,IntSet
l2) = (Int -> Bool) -> IntSet -> (IntSet, IntSet)
partition Int -> Bool
predicate IntSet
l
(IntSet
r1,IntSet
r2) = (Int -> Bool) -> IntSet -> (IntSet, IntSet)
partition Int -> Bool
predicate IntSet
r
in (Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
l1 IntSet
r1, Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
l2 IntSet
r2)
Tip Int
_ Int
x
| Int -> Bool
predicate Int
x -> (IntSet
t,IntSet
Nil)
| Bool
otherwise -> (IntSet
Nil,IntSet
t)
IntSet
Nil -> (IntSet
Nil,IntSet
Nil)
split :: Int -> IntSet -> (IntSet,IntSet)
split :: Int -> IntSet -> (IntSet, IntSet)
split Int
x IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
_ Int
m IntSet
l IntSet
r
| Int
m forall a. Ord a => a -> a -> Bool
< Int
0 -> if Int
x forall a. Ord a => a -> a -> Bool
>= Int
0 then let (IntSet
lt,IntSet
gt) = Int -> IntSet -> (IntSet, IntSet)
split' Int
x IntSet
l in (IntSet -> IntSet -> IntSet
union IntSet
r IntSet
lt, IntSet
gt)
else let (IntSet
lt,IntSet
gt) = Int -> IntSet -> (IntSet, IntSet)
split' Int
x IntSet
r in (IntSet
lt, IntSet -> IntSet -> IntSet
union IntSet
gt IntSet
l)
| Bool
otherwise -> Int -> IntSet -> (IntSet, IntSet)
split' Int
x IntSet
t
Tip Int
_ Int
y
| Int
xforall a. Ord a => a -> a -> Bool
>Int
y -> (IntSet
t,IntSet
Nil)
| Int
xforall a. Ord a => a -> a -> Bool
<Int
y -> (IntSet
Nil,IntSet
t)
| Bool
otherwise -> (IntSet
Nil,IntSet
Nil)
IntSet
Nil -> (IntSet
Nil, IntSet
Nil)
split' :: Int -> IntSet -> (IntSet,IntSet)
split' :: Int -> IntSet -> (IntSet, IntSet)
split' Int
x IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r
| Int -> Int -> Int -> Bool
match Int
x Int
p Int
m -> if Int -> Int -> Bool
zero Int
x Int
m then let (IntSet
lt,IntSet
gt) = Int -> IntSet -> (IntSet, IntSet)
split' Int
x IntSet
l in (IntSet
lt,IntSet -> IntSet -> IntSet
union IntSet
gt IntSet
r)
else let (IntSet
lt,IntSet
gt) = Int -> IntSet -> (IntSet, IntSet)
split' Int
x IntSet
r in (IntSet -> IntSet -> IntSet
union IntSet
l IntSet
lt,IntSet
gt)
| Bool
otherwise -> if Int
x forall a. Ord a => a -> a -> Bool
< Int
p then (IntSet
Nil, IntSet
t)
else (IntSet
t, IntSet
Nil)
Tip Int
_ Int
y
| Int
xforall a. Ord a => a -> a -> Bool
>Int
y -> (IntSet
t,IntSet
Nil)
| Int
xforall a. Ord a => a -> a -> Bool
<Int
y -> (IntSet
Nil,IntSet
t)
| Bool
otherwise -> (IntSet
Nil,IntSet
Nil)
IntSet
Nil -> (IntSet
Nil,IntSet
Nil)
splitMember :: Int -> IntSet -> (IntSet,Bool,IntSet)
splitMember :: Int -> IntSet -> (IntSet, Bool, IntSet)
splitMember Int
x IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
_ Int
m IntSet
l IntSet
r
| Int
m forall a. Ord a => a -> a -> Bool
< Int
0 -> if Int
x forall a. Ord a => a -> a -> Bool
>= Int
0 then let (IntSet
lt,Bool
found,IntSet
gt) = Int -> IntSet -> (IntSet, Bool, IntSet)
splitMember' Int
x IntSet
l in (IntSet -> IntSet -> IntSet
union IntSet
r IntSet
lt, Bool
found, IntSet
gt)
else let (IntSet
lt,Bool
found,IntSet
gt) = Int -> IntSet -> (IntSet, Bool, IntSet)
splitMember' Int
x IntSet
r in (IntSet
lt, Bool
found, IntSet -> IntSet -> IntSet
union IntSet
gt IntSet
l)
| Bool
otherwise -> Int -> IntSet -> (IntSet, Bool, IntSet)
splitMember' Int
x IntSet
t
Tip Int
_ Int
y
| Int
xforall a. Ord a => a -> a -> Bool
>Int
y -> (IntSet
t,Bool
False,IntSet
Nil)
| Int
xforall a. Ord a => a -> a -> Bool
<Int
y -> (IntSet
Nil,Bool
False,IntSet
t)
| Bool
otherwise -> (IntSet
Nil,Bool
True,IntSet
Nil)
IntSet
Nil -> (IntSet
Nil,Bool
False,IntSet
Nil)
splitMember' :: Int -> IntSet -> (IntSet,Bool,IntSet)
splitMember' :: Int -> IntSet -> (IntSet, Bool, IntSet)
splitMember' Int
x IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r
| Int -> Int -> Int -> Bool
match Int
x Int
p Int
m -> if Int -> Int -> Bool
zero Int
x Int
m then let (IntSet
lt,Bool
found,IntSet
gt) = Int -> IntSet -> (IntSet, Bool, IntSet)
splitMember Int
x IntSet
l in (IntSet
lt,Bool
found,IntSet -> IntSet -> IntSet
union IntSet
gt IntSet
r)
else let (IntSet
lt,Bool
found,IntSet
gt) = Int -> IntSet -> (IntSet, Bool, IntSet)
splitMember Int
x IntSet
r in (IntSet -> IntSet -> IntSet
union IntSet
l IntSet
lt,Bool
found,IntSet
gt)
| Bool
otherwise -> if Int
x forall a. Ord a => a -> a -> Bool
< Int
p then (IntSet
Nil, Bool
False, IntSet
t)
else (IntSet
t, Bool
False, IntSet
Nil)
Tip Int
_ Int
y
| Int
xforall a. Ord a => a -> a -> Bool
>Int
y -> (IntSet
t,Bool
False,IntSet
Nil)
| Int
xforall a. Ord a => a -> a -> Bool
<Int
y -> (IntSet
Nil,Bool
False,IntSet
t)
| Bool
otherwise -> (IntSet
Nil,Bool
True,IntSet
Nil)
IntSet
Nil -> (IntSet
Nil,Bool
False,IntSet
Nil)
maxView :: IntSet -> Maybe (Int, IntSet)
maxView :: IntSet -> Maybe (Int, IntSet)
maxView IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r | Int
m forall a. Ord a => a -> a -> Bool
< Int
0 -> let (Int
result,IntSet
t') = IntSet -> (Int, IntSet)
maxViewUnsigned IntSet
l in forall a. a -> Maybe a
Just (Int
result, Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
t' IntSet
r)
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r -> let (Int
result,IntSet
t') = IntSet -> (Int, IntSet)
maxViewUnsigned IntSet
r in forall a. a -> Maybe a
Just (Int
result, Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
l IntSet
t')
Tip Int
_ Int
y -> forall a. a -> Maybe a
Just (Int
y,IntSet
Nil)
IntSet
Nil -> forall a. Maybe a
Nothing
maxViewUnsigned :: IntSet -> (Int, IntSet)
maxViewUnsigned :: IntSet -> (Int, IntSet)
maxViewUnsigned IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r -> let (Int
result,IntSet
t') = IntSet -> (Int, IntSet)
maxViewUnsigned IntSet
r in (Int
result, Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
l IntSet
t')
Tip Int
_ Int
y -> (Int
y, IntSet
Nil)
IntSet
Nil -> forall a. HasCallStack => [Char] -> a
error [Char]
"maxViewUnsigned Nil"
minView :: IntSet -> Maybe (Int, IntSet)
minView :: IntSet -> Maybe (Int, IntSet)
minView IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r | Int
m forall a. Ord a => a -> a -> Bool
< Int
0 -> let (Int
result,IntSet
t') = IntSet -> (Int, IntSet)
minViewUnsigned IntSet
r in forall a. a -> Maybe a
Just (Int
result, Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
l IntSet
t')
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r -> let (Int
result,IntSet
t') = IntSet -> (Int, IntSet)
minViewUnsigned IntSet
l in forall a. a -> Maybe a
Just (Int
result, Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
t' IntSet
r)
Tip Int
_ Int
y -> forall a. a -> Maybe a
Just (Int
y, IntSet
Nil)
IntSet
Nil -> forall a. Maybe a
Nothing
minViewUnsigned :: IntSet -> (Int, IntSet)
minViewUnsigned :: IntSet -> (Int, IntSet)
minViewUnsigned IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r -> let (Int
result,IntSet
t') = IntSet -> (Int, IntSet)
minViewUnsigned IntSet
l in (Int
result, Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
t' IntSet
r)
Tip Int
_ Int
y -> (Int
y, IntSet
Nil)
IntSet
Nil -> forall a. HasCallStack => [Char] -> a
error [Char]
"minViewUnsigned Nil"
deleteFindMin :: IntSet -> (Int, IntSet)
deleteFindMin :: IntSet -> (Int, IntSet)
deleteFindMin = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"deleteFindMin: empty set has no minimal element") forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntSet -> Maybe (Int, IntSet)
minView
deleteFindMax :: IntSet -> (Int, IntSet)
deleteFindMax :: IntSet -> (Int, IntSet)
deleteFindMax = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"deleteFindMax: empty set has no maximal element") forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntSet -> Maybe (Int, IntSet)
maxView
findMin :: IntSet -> Int
findMin :: IntSet -> Int
findMin IntSet
Nil = forall a. HasCallStack => [Char] -> a
error [Char]
"findMin: empty set has no minimal element"
findMin (Tip Int
_ Int
x) = Int
x
findMin (Bin Int
_ Int
_ Int
_ Int
m IntSet
l IntSet
r)
| Int
m forall a. Ord a => a -> a -> Bool
< Int
0 = IntSet -> Int
find IntSet
r
| Bool
otherwise = IntSet -> Int
find IntSet
l
where find :: IntSet -> Int
find (Tip Int
_ Int
x) = Int
x
find (Bin Int
_ Int
_ Int
_ Int
_ IntSet
l' IntSet
_) = IntSet -> Int
find IntSet
l'
find IntSet
Nil = forall a. HasCallStack => [Char] -> a
error [Char]
"findMin Nil"
findMax :: IntSet -> Int
findMax :: IntSet -> Int
findMax IntSet
Nil = forall a. HasCallStack => [Char] -> a
error [Char]
"findMax: empty set has no maximal element"
findMax (Tip Int
_ Int
x) = Int
x
findMax (Bin Int
_ Int
_ Int
_ Int
m IntSet
l IntSet
r)
| Int
m forall a. Ord a => a -> a -> Bool
< Int
0 = IntSet -> Int
find IntSet
l
| Bool
otherwise = IntSet -> Int
find IntSet
r
where find :: IntSet -> Int
find (Tip Int
_ Int
x) = Int
x
find (Bin Int
_ Int
_ Int
_ Int
_ IntSet
_ IntSet
r') = IntSet -> Int
find IntSet
r'
find IntSet
Nil = forall a. HasCallStack => [Char] -> a
error [Char]
"findMax Nil"
deleteMin :: IntSet -> IntSet
deleteMin :: IntSet -> IntSet
deleteMin = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. HasCallStack => [Char] -> a
error [Char]
"deleteMin: empty set has no minimal element") forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntSet -> Maybe (Int, IntSet)
minView
deleteMax :: IntSet -> IntSet
deleteMax :: IntSet -> IntSet
deleteMax = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. HasCallStack => [Char] -> a
error [Char]
"deleteMax: empty set has no maximal element") forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntSet -> Maybe (Int, IntSet)
maxView
map :: (Int->Int) -> IntSet -> IntSet
map :: (Int -> Int) -> IntSet -> IntSet
map Int -> Int
f = [Int] -> IntSet
fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
List.map Int -> Int
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntSet -> [Int]
toList
fold :: (Int -> b -> b) -> b -> IntSet -> b
fold :: forall b. (Int -> b -> b) -> b -> IntSet -> b
fold Int -> b -> b
f b
z IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
0 Int
m IntSet
l IntSet
r | Int
m forall a. Ord a => a -> a -> Bool
< Int
0 -> forall b. (Int -> b -> b) -> b -> IntSet -> b
foldr Int -> b -> b
f (forall b. (Int -> b -> b) -> b -> IntSet -> b
foldr Int -> b -> b
f b
z IntSet
l) IntSet
r
Bin Int
_ Int
_ Int
_ Int
_ IntSet
_ IntSet
_ -> forall b. (Int -> b -> b) -> b -> IntSet -> b
foldr Int -> b -> b
f b
z IntSet
t
Tip Int
_ Int
x -> Int -> b -> b
f Int
x b
z
IntSet
Nil -> b
z
foldr :: (Int -> b -> b) -> b -> IntSet -> b
foldr :: forall b. (Int -> b -> b) -> b -> IntSet -> b
foldr Int -> b -> b
f b
z IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
_ Int
_ IntSet
l IntSet
r -> forall b. (Int -> b -> b) -> b -> IntSet -> b
foldr Int -> b -> b
f (forall b. (Int -> b -> b) -> b -> IntSet -> b
foldr Int -> b -> b
f b
z IntSet
r) IntSet
l
Tip Int
_ Int
x -> Int -> b -> b
f Int
x b
z
IntSet
Nil -> b
z
elems :: IntSet -> [Int]
elems :: IntSet -> [Int]
elems IntSet
s = IntSet -> [Int]
toList IntSet
s
toList :: IntSet -> [Int]
toList :: IntSet -> [Int]
toList IntSet
t = forall b. (Int -> b -> b) -> b -> IntSet -> b
fold (:) [] IntSet
t
toAscList :: IntSet -> [Int]
toAscList :: IntSet -> [Int]
toAscList IntSet
t = IntSet -> [Int]
toList IntSet
t
fromList :: [Int] -> IntSet
fromList :: [Int] -> IntSet
fromList [Int]
xs = forall a b. (a -> b -> a) -> a -> [b] -> a
foldlStrict IntSet -> Int -> IntSet
ins IntSet
empty [Int]
xs
where
ins :: IntSet -> Int -> IntSet
ins IntSet
t Int
x = Int -> IntSet -> IntSet
insert Int
x IntSet
t
fromAscList :: [Int] -> IntSet
fromAscList :: [Int] -> IntSet
fromAscList [] = IntSet
Nil
fromAscList (Int
x0 : [Int]
xs0) = [Int] -> IntSet
fromDistinctAscList (forall {t}. Eq t => t -> [t] -> [t]
combineEq Int
x0 [Int]
xs0)
where
combineEq :: t -> [t] -> [t]
combineEq t
x' [] = [t
x']
combineEq t
x' (t
x:[t]
xs)
| t
xforall a. Eq a => a -> a -> Bool
==t
x' = t -> [t] -> [t]
combineEq t
x' [t]
xs
| Bool
otherwise = t
x' forall a. a -> [a] -> [a]
: t -> [t] -> [t]
combineEq t
x [t]
xs
fromDistinctAscList :: [Int] -> IntSet
fromDistinctAscList :: [Int] -> IntSet
fromDistinctAscList [] = IntSet
Nil
fromDistinctAscList (Int
z0 : [Int]
zs0) = Int -> [Int] -> Stack -> IntSet
work Int
z0 [Int]
zs0 Stack
Nada
where
work :: Int -> [Int] -> Stack -> IntSet
work Int
x [] Stack
stk = Int -> IntSet -> Stack -> IntSet
finish Int
x (Int -> IntSet
tip Int
x) Stack
stk
work Int
x (Int
z:[Int]
zs) Stack
stk = Int -> [Int] -> Int -> Int -> IntSet -> Stack -> IntSet
reduce Int
z [Int]
zs (Int -> Int -> Int
branchMask Int
z Int
x) Int
x (Int -> IntSet
tip Int
x) Stack
stk
reduce :: Int -> [Int] -> Int -> Int -> IntSet -> Stack -> IntSet
reduce Int
z [Int]
zs Int
_ Int
px IntSet
tx Stack
Nada = Int -> [Int] -> Stack -> IntSet
work Int
z [Int]
zs (Int -> IntSet -> Stack -> Stack
Push Int
px IntSet
tx Stack
Nada)
reduce Int
z [Int]
zs Int
m Int
px IntSet
tx stk :: Stack
stk@(Push Int
py IntSet
ty Stack
stk') =
let mxy :: Int
mxy = Int -> Int -> Int
branchMask Int
px Int
py
pxy :: Int
pxy = Int -> Int -> Int
mask Int
px Int
mxy
in if Int -> Int -> Bool
shorter Int
m Int
mxy
then Int -> [Int] -> Int -> Int -> IntSet -> Stack -> IntSet
reduce Int
z [Int]
zs Int
m Int
pxy (Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
pxy Int
mxy IntSet
ty IntSet
tx) Stack
stk'
else Int -> [Int] -> Stack -> IntSet
work Int
z [Int]
zs (Int -> IntSet -> Stack -> Stack
Push Int
px IntSet
tx Stack
stk)
finish :: Int -> IntSet -> Stack -> IntSet
finish Int
_ IntSet
t Stack
Nada = IntSet
t
finish Int
px IntSet
tx (Push Int
py IntSet
ty Stack
stk) = Int -> IntSet -> Stack -> IntSet
finish Int
p (Int -> IntSet -> Int -> IntSet -> IntSet
join Int
py IntSet
ty Int
px IntSet
tx) Stack
stk
where m :: Int
m = Int -> Int -> Int
branchMask Int
px Int
py
p :: Int
p = Int -> Int -> Int
mask Int
px Int
m
data Stack = Push {-# UNPACK #-} !Prefix !IntSet !Stack | Nada
showTree :: IntSet -> String
showTree :: IntSet -> [Char]
showTree IntSet
s
= Bool -> Bool -> IntSet -> [Char]
showTreeWith Bool
True Bool
False IntSet
s
showTreeWith :: Bool -> Bool -> IntSet -> String
showTreeWith :: Bool -> Bool -> IntSet -> [Char]
showTreeWith Bool
hang Bool
wide IntSet
t
| Bool
hang = (Bool -> [[Char]] -> IntSet -> ShowS
showsTreeHang Bool
wide [] IntSet
t) [Char]
""
| Bool
otherwise = (Bool -> [[Char]] -> [[Char]] -> IntSet -> ShowS
showsTree Bool
wide [] [] IntSet
t) [Char]
""
showsTree :: Bool -> [String] -> [String] -> IntSet -> ShowS
showsTree :: Bool -> [[Char]] -> [[Char]] -> IntSet -> ShowS
showsTree Bool
wide [[Char]]
lbars [[Char]]
rbars IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r
-> Bool -> [[Char]] -> [[Char]] -> IntSet -> ShowS
showsTree Bool
wide ([[Char]] -> [[Char]]
withBar [[Char]]
rbars) ([[Char]] -> [[Char]]
withEmpty [[Char]]
rbars) IntSet
r forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> ShowS
showWide Bool
wide [[Char]]
rbars forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[[Char]] -> ShowS
showsBars [[Char]]
lbars forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString (Int -> Int -> [Char]
showBin Int
p Int
m) forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> ShowS
showWide Bool
wide [[Char]]
lbars forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> [[Char]] -> IntSet -> ShowS
showsTree Bool
wide ([[Char]] -> [[Char]]
withEmpty [[Char]]
lbars) ([[Char]] -> [[Char]]
withBar [[Char]]
lbars) IntSet
l
Tip Int
_ Int
x
-> [[Char]] -> ShowS
showsBars [[Char]]
lbars forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
" " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> ShowS
shows Int
x forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
"\n"
IntSet
Nil -> [[Char]] -> ShowS
showsBars [[Char]]
lbars forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
"|\n"
showsTreeHang :: Bool -> [String] -> IntSet -> ShowS
showsTreeHang :: Bool -> [[Char]] -> IntSet -> ShowS
showsTreeHang Bool
wide [[Char]]
bars IntSet
t
= case IntSet
t of
Bin Int
_ Int
_ Int
p Int
m IntSet
l IntSet
r
-> [[Char]] -> ShowS
showsBars [[Char]]
bars forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString (Int -> Int -> [Char]
showBin Int
p Int
m) forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> ShowS
showWide Bool
wide [[Char]]
bars forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> IntSet -> ShowS
showsTreeHang Bool
wide ([[Char]] -> [[Char]]
withBar [[Char]]
bars) IntSet
l forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> ShowS
showWide Bool
wide [[Char]]
bars forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> IntSet -> ShowS
showsTreeHang Bool
wide ([[Char]] -> [[Char]]
withEmpty [[Char]]
bars) IntSet
r
Tip Int
_ Int
x
-> [[Char]] -> ShowS
showsBars [[Char]]
bars forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
" " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> ShowS
shows Int
x forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
"\n"
IntSet
Nil -> [[Char]] -> ShowS
showsBars [[Char]]
bars forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
"|\n"
showBin :: Prefix -> Mask -> String
showBin :: Int -> Int -> [Char]
showBin Int
_ Int
_
= [Char]
"*"
showWide :: Bool -> [String] -> String -> String
showWide :: Bool -> [[Char]] -> ShowS
showWide Bool
wide [[Char]]
bars
| Bool
wide = [Char] -> ShowS
showString (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (forall a. [a] -> [a]
reverse [[Char]]
bars)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
"|\n"
| Bool
otherwise = forall a. a -> a
id
showsBars :: [String] -> ShowS
showsBars :: [[Char]] -> ShowS
showsBars [[Char]]
bars
= case [[Char]]
bars of
[] -> forall a. a -> a
id
[Char]
_:[[Char]]
bars' -> [Char] -> ShowS
showString (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (forall a. [a] -> [a]
reverse [[Char]]
bars')) forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
node
node :: String
node :: [Char]
node = [Char]
"+--"
withBar, withEmpty :: [String] -> [String]
withBar :: [[Char]] -> [[Char]]
withBar [[Char]]
bars = [Char]
"| "forall a. a -> [a] -> [a]
:[[Char]]
bars
withEmpty :: [[Char]] -> [[Char]]
withEmpty [[Char]]
bars = [Char]
" "forall a. a -> [a] -> [a]
:[[Char]]
bars
instance Eq IntSet where
IntSet
Nil == :: IntSet -> IntSet -> Bool
== IntSet
Nil = Bool
True
Tip Int
i Int
_ == Tip Int
j Int
_ = Int
i forall a. Eq a => a -> a -> Bool
== Int
j
Bin Int
i Int
_ Int
_ Int
_ IntSet
_ IntSet
_ == Bin Int
j Int
_ Int
_ Int
_ IntSet
_ IntSet
_ = Int
i forall a. Eq a => a -> a -> Bool
== Int
j
IntSet
_ == IntSet
_ = Bool
False
instance Ord IntSet where
IntSet
Nil compare :: IntSet -> IntSet -> Ordering
`compare` IntSet
Nil = Ordering
EQ
IntSet
Nil `compare` Tip Int
_ Int
_ = Ordering
LT
IntSet
Nil `compare` Bin Int
_ Int
_ Int
_ Int
_ IntSet
_ IntSet
_ = Ordering
LT
Tip Int
_ Int
_ `compare` IntSet
Nil = Ordering
GT
Tip Int
i Int
_ `compare` Tip Int
j Int
_ = forall a. Ord a => a -> a -> Ordering
compare Int
i Int
j
Tip Int
i Int
_ `compare` Bin Int
j Int
_ Int
_ Int
_ IntSet
_ IntSet
_ = forall a. Ord a => a -> a -> Ordering
compare Int
i Int
j
Bin Int
_ Int
_ Int
_ Int
_ IntSet
_ IntSet
_ `compare` IntSet
Nil = Ordering
GT
Bin Int
i Int
_ Int
_ Int
_ IntSet
_ IntSet
_ `compare` Tip Int
j Int
_ = forall a. Ord a => a -> a -> Ordering
compare Int
i Int
j
Bin Int
i Int
_ Int
_ Int
_ IntSet
_ IntSet
_ `compare` Bin Int
j Int
_ Int
_ Int
_ IntSet
_ IntSet
_ = forall a. Ord a => a -> a -> Ordering
compare Int
i Int
j
instance Show IntSet where
showsPrec :: Int -> IntSet -> ShowS
showsPrec Int
p IntSet
xs = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$
[Char] -> ShowS
showString [Char]
"fromList " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> ShowS
shows (IntSet -> [Int]
toList IntSet
xs)
instance Hashable IntSet where
hashWithSalt :: Int -> IntSet -> Int
hashWithSalt Int
s IntSet
x = forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
s forall a b. (a -> b) -> a -> b
$ IntSet -> Int
identity IntSet
x
instance Read IntSet where
readPrec :: ReadPrec IntSet
readPrec = forall a. ReadPrec a -> ReadPrec a
parens forall a b. (a -> b) -> a -> b
$ forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 forall a b. (a -> b) -> a -> b
$ do
Ident [Char]
"fromList" <- ReadPrec Lexeme
lexP
[Int]
xs <- forall a. Read a => ReadPrec a
readPrec
forall (m :: * -> *) a. Monad m => a -> m a
return ([Int] -> IntSet
fromList [Int]
xs)
readListPrec :: ReadPrec [IntSet]
readListPrec = forall a. Read a => ReadPrec [a]
readListPrecDefault
join :: Prefix -> IntSet -> Prefix -> IntSet -> IntSet
join :: Int -> IntSet -> Int -> IntSet -> IntSet
join Int
p1 IntSet
t1 Int
p2 IntSet
t2
| Int -> Int -> Bool
zero Int
p1 Int
m = Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p Int
m IntSet
t1 IntSet
t2
| Bool
otherwise = Int -> Int -> IntSet -> IntSet -> IntSet
bin_ Int
p Int
m IntSet
t2 IntSet
t1
where
m :: Int
m = Int -> Int -> Int
branchMask Int
p1 Int
p2
p :: Int
p = Int -> Int -> Int
mask Int
p1 Int
m
zero :: Int -> Mask -> Bool
zero :: Int -> Int -> Bool
zero Int
i Int
m
= (Int -> Nat
natFromInt Int
i) forall a. Bits a => a -> a -> a
.&. (Int -> Nat
natFromInt Int
m) forall a. Eq a => a -> a -> Bool
== Nat
0
nomatch,match :: Int -> Prefix -> Mask -> Bool
nomatch :: Int -> Int -> Int -> Bool
nomatch Int
i Int
p Int
m
= (Int -> Int -> Int
mask Int
i Int
m) forall a. Eq a => a -> a -> Bool
/= Int
p
match :: Int -> Int -> Int -> Bool
match Int
i Int
p Int
m
= (Int -> Int -> Int
mask Int
i Int
m) forall a. Eq a => a -> a -> Bool
== Int
p
mask :: Int -> Mask -> Prefix
mask :: Int -> Int -> Int
mask Int
i Int
m
= Nat -> Nat -> Int
maskW (Int -> Nat
natFromInt Int
i) (Int -> Nat
natFromInt Int
m)
zeroN :: Nat -> Nat -> Bool
zeroN :: Nat -> Nat -> Bool
zeroN Nat
i Nat
m = (Nat
i forall a. Bits a => a -> a -> a
.&. Nat
m) forall a. Eq a => a -> a -> Bool
== Nat
0
maskW :: Nat -> Nat -> Prefix
maskW :: Nat -> Nat -> Int
maskW Nat
i Nat
m
= Nat -> Int
intFromNat (Nat
i forall a. Bits a => a -> a -> a
.&. (forall a. Bits a => a -> a
complement (Nat
mforall a. Num a => a -> a -> a
-Nat
1) forall a. Bits a => a -> a -> a
`xor` Nat
m))
shorter :: Mask -> Mask -> Bool
shorter :: Int -> Int -> Bool
shorter Int
m1 Int
m2
= (Int -> Nat
natFromInt Int
m1) forall a. Ord a => a -> a -> Bool
> (Int -> Nat
natFromInt Int
m2)
branchMask :: Prefix -> Prefix -> Mask
branchMask :: Int -> Int -> Int
branchMask Int
p1 Int
p2
= Nat -> Int
intFromNat (Nat -> Nat
highestBitMask (Int -> Nat
natFromInt Int
p1 forall a. Bits a => a -> a -> a
`xor` Int -> Nat
natFromInt Int
p2))
highestBitMask :: Nat -> Nat
highestBitMask :: Nat -> Nat
highestBitMask Nat
x0
= case (Nat
x0 forall a. Bits a => a -> a -> a
.|. Nat -> Int -> Nat
shiftRL Nat
x0 Int
1) of
Nat
x1 -> case (Nat
x1 forall a. Bits a => a -> a -> a
.|. Nat -> Int -> Nat
shiftRL Nat
x1 Int
2) of
Nat
x2 -> case (Nat
x2 forall a. Bits a => a -> a -> a
.|. Nat -> Int -> Nat
shiftRL Nat
x2 Int
4) of
Nat
x3 -> case (Nat
x3 forall a. Bits a => a -> a -> a
.|. Nat -> Int -> Nat
shiftRL Nat
x3 Int
8) of
Nat
x4 -> case (Nat
x4 forall a. Bits a => a -> a -> a
.|. Nat -> Int -> Nat
shiftRL Nat
x4 Int
16) of
Nat
x5 -> case (Nat
x5 forall a. Bits a => a -> a -> a
.|. Nat -> Int -> Nat
shiftRL Nat
x5 Int
32) of
Nat
x6 -> (Nat
x6 forall a. Bits a => a -> a -> a
`xor` (Nat -> Int -> Nat
shiftRL Nat
x6 Int
1))
foldlStrict :: (a -> b -> a) -> a -> [b] -> a
foldlStrict :: forall a b. (a -> b -> a) -> a -> [b] -> a
foldlStrict a -> b -> a
f a
z [b]
xs
= case [b]
xs of
[] -> a
z
(b
x:[b]
xx) -> let z' :: a
z' = a -> b -> a
f a
z b
x in seq :: forall a b. a -> b -> b
seq a
z' (forall a b. (a -> b -> a) -> a -> [b] -> a
foldlStrict a -> b -> a
f a
z' [b]
xx)