module Data.Edison.Coll.EnumSet (
Set
, empty
, singleton
, fromSeq
, insert
, insertSeq
, union
, unionSeq
, delete
, deleteAll
, deleteSeq
, null
, size
, member
, count
, strict
, deleteMin
, deleteMax
, unsafeInsertMin
, unsafeInsertMax
, unsafeFromOrdSeq
, unsafeAppend
, filterLT
, filterLE
, filterGT
, filterGE
, partitionLT_GE
, partitionLE_GT
, partitionLT_GT
, intersection
, difference
, symmetricDifference
, properSubset
, subset
, toSeq
, lookup
, lookupM
, lookupAll
, lookupWithDefault
, fold, fold', fold1, fold1'
, filter
, partition
, strictWith
, minView
, minElem
, maxView
, maxElem
, foldr, foldr', foldl, foldl'
, foldr1, foldr1', foldl1, foldl1'
, toOrdSeq
, unsafeMapMonotonic
, fromSeqWith
, fromOrdSeq
, insertWith
, insertSeqWith
, unionl
, unionr
, unionWith
, unionSeqWith
, intersectionWith
, map
, setCoerce
, complement
, toBits
, fromBits
, moduleName
) where
import qualified Prelude
import Prelude hiding (filter,foldl,foldr,null,map,lookup,foldl1,foldr1)
import qualified Data.Bits as Bits
import Data.Bits hiding (complement)
import Data.Word
import Data.Monoid (Monoid(..))
import qualified Data.Edison.Seq as S
import qualified Data.Edison.Coll as C
import Data.Edison.Coll.Defaults
import Test.QuickCheck (Arbitrary(..), CoArbitrary(..))
moduleName :: String
moduleName = "Data.Edison.Coll.EnumSet"
newtype Set a = Set Word deriving (Eq)
wordLength :: Int
wordLength =
#if MIN_VERSION_base(4,7,0)
finiteBitSize
#else
bitSize
#endif
(0::Word)
check :: String -> Int -> Int
check msg x
| x < wordLength = x
| otherwise = error $ "EnumSet."++msg++": element beyond word size."
structuralInvariant :: Set a -> Bool
structuralInvariant = const True
countBits :: Word -> Int
countBits w = w `seq` bitcount 0 w
bitcount :: Int -> Word -> Int
bitcount a 0 = a
bitcount a x = a `seq` bitcount (a+1) (x .&. (x1))
lsb :: Word -> Int
lsb x = countBits ((x1) .&. (Bits.complement x))
msb :: Word -> Int
msb x0 = let
x1 = x0 .|. (x0 `shiftR` 1)
x2 = x1 .|. (x1 `shiftR` 2)
x3 = x2 .|. (x2 `shiftR` 4)
x4 = x3 .|. (x3 `shiftR` 8)
x5 = x4 .|. (x4 `shiftR` 16)
in countBits x5 1
lowMask :: Int -> Word
lowMask x = bit x 1
highMask :: Int -> Word
highMask x = Bits.complement (lowMask x)
null :: Set a -> Bool
null (Set 0) = True
null _ = False
size :: Set a -> Int
size (Set w) = countBits w
member :: (Eq a, Enum a) => a -> Set a -> Bool
member x (Set w) = testBit w $ fromEnum x
count :: (Eq a, Enum a) => a -> Set a -> Int
count = countUsingMember
lookup :: (Eq a, Enum a) => a -> Set a -> a
lookup = lookupUsingLookupAll
lookupM :: (Eq a, Enum a, Monad m) => a -> Set a -> m a
lookupM x s
| member x s = return x
| otherwise = fail (moduleName++".lookupM: lookup failed")
lookupAll :: (Eq a, Enum a, S.Sequence s) => a -> Set a -> s a
lookupAll = lookupAllUsingLookupM
lookupWithDefault :: (Eq a, Enum a) => a -> a -> Set a -> a
lookupWithDefault = lookupWithDefaultUsingLookupM
empty :: Set a
empty = Set 0
singleton :: (Eq a, Enum a) => a -> Set a
singleton x =
Set $ setBit 0 $ check "singleton" $ fromEnum x
insert :: (Eq a, Enum a) => a -> Set a -> Set a
insert x (Set w) =
Set $ setBit w $ check "insert" $ fromEnum x
insertWith :: (Eq a, Enum a) => (a -> a -> a) -> a -> Set a -> Set a
insertWith _ x (Set w) =
Set $ setBit w $ check "insertWith" $ fromEnum x
delete :: (Eq a, Enum a) => a -> Set a -> Set a
delete x (Set w) =
Set $ clearBit w $ fromEnum x
deleteAll :: (Eq a, Enum a) => a -> Set a -> Set a
deleteAll = delete
deleteSeq :: (Eq a, Enum a, S.Sequence s) => s a -> Set a -> Set a
deleteSeq = deleteSeqUsingDelete
properSubset :: Set a -> Set a -> Bool
properSubset x y = (x /= y) && (subset x y)
subset :: Set a -> Set a -> Bool
subset x y = (x `union` y) == y
minElem :: (Enum a) => Set a -> a
minElem (Set w)
| w == 0 = error $ moduleName++".minElem: empty set"
| otherwise = toEnum $ lsb w
maxElem :: (Enum a) => Set a -> a
maxElem (Set w)
| w == 0 = error $ moduleName++".maxElem: empty set"
| otherwise = toEnum $ msb w
deleteMin :: (Enum a) => Set a -> Set a
deleteMin (Set w)
| w == 0 = empty
| otherwise = Set $ clearBit w $ lsb w
deleteMax :: (Enum a) => Set a -> Set a
deleteMax (Set w)
| w == 0 = empty
| otherwise = Set $ clearBit w $ msb w
minView :: (Enum a, Monad m) => Set a -> m (a, Set a)
minView (Set w)
| w == 0 = fail (moduleName++".minView: empty set")
| otherwise = let i = lsb w in return (toEnum i,Set $ clearBit w i)
maxView :: (Enum a, Monad m) => Set a -> m (a, Set a)
maxView (Set w)
| w == 0 = fail (moduleName++".maxView: empty set")
| otherwise = let i = msb w in return (toEnum i, Set $ clearBit w i)
unsafeInsertMin :: (Ord a, Enum a) => a -> Set a -> Set a
unsafeInsertMin = insert
unsafeInsertMax :: (Ord a, Enum a) => a -> Set a -> Set a
unsafeInsertMax = insert
unsafeAppend :: (Ord a, Enum a) => Set a -> Set a -> Set a
unsafeAppend = union
unsafeFromOrdSeq :: (Ord a, Enum a, S.Sequence s) => s a -> Set a
unsafeFromOrdSeq = fromSeq
filterLT :: (Ord a, Enum a) => a -> Set a -> Set a
filterLT x (Set w) = Set (w .&. lowMask (fromEnum x))
filterLE :: (Ord a, Enum a) => a -> Set a -> Set a
filterLE x (Set w) = Set (w .&. lowMask (fromEnum x + 1))
filterGT :: (Ord a, Enum a) => a -> Set a -> Set a
filterGT x (Set w) = Set (w .&. highMask (fromEnum x + 1))
filterGE :: (Ord a, Enum a) => a -> Set a -> Set a
filterGE x (Set w) = Set (w .&. highMask (fromEnum x))
partitionLT_GE :: (Ord a, Enum a) => a -> Set a -> (Set a, Set a)
partitionLT_GE x s = (filterLT x s,filterGE x s)
partitionLE_GT :: (Ord a, Enum a) => a -> Set a -> (Set a, Set a)
partitionLE_GT x s = (filterLE x s,filterGT x s)
partitionLT_GT :: (Ord a, Enum a) => a -> Set a -> (Set a, Set a)
partitionLT_GT x s = (filterLT x s,filterGT x s)
unionSeq :: (Eq a, Enum a, S.Sequence s) => s (Set a) -> Set a
unionSeq = unionSeqUsingFoldl'
union :: Set a -> Set a -> Set a
union (Set x) (Set y) = Set $ x .|. y
unionl :: Set a -> Set a -> Set a
unionl = union
unionr :: Set a -> Set a -> Set a
unionr = union
unionWith :: (a -> a -> a) -> Set a -> Set a -> Set a
unionWith _ = union
unionSeqWith :: (Eq a, Enum a, S.Sequence s) => (a -> a -> a) -> s (Set a) -> Set a
unionSeqWith _ = unionSeq
difference :: Set a -> Set a -> Set a
difference (Set x) (Set y) = Set $ (x .|. y) `xor` y
symmetricDifference :: Set a -> Set a -> Set a
symmetricDifference (Set x) (Set y) = Set $ x `xor` y
intersection :: Set a -> Set a -> Set a
intersection (Set x) (Set y) = Set $ x .&. y
intersectionWith :: (a -> a -> a) -> Set a -> Set a -> Set a
intersectionWith _ = intersection
complement :: (Eq a, Bounded a, Enum a) => Set a -> Set a
complement x = symmetricDifference u x
where u = (fromSeq [minBound .. maxBound]) `asTypeOf` x
filter :: (Eq a, Enum a) => (a -> Bool) -> Set a -> Set a
filter p (Set w) = Set $ foldlBits' f 0 w
where
f z i
| p $ toEnum i = setBit z i
| otherwise = z
partition :: (Eq a, Enum a) => (a -> Bool) -> Set a -> (Set a,Set a)
partition p (Set w) = (Set yay,Set nay)
where
(yay,nay) = foldlBits' f (0,0) w
f (x,y) i
| p $ toEnum i = (setBit x i,y)
| otherwise = (x,setBit y i)
map :: (Enum a,Enum b) => (a -> b) -> Set a -> Set b
map f0 (Set w) = Set $ foldlBits' f 0 w
where
f z i = setBit z $ check "map" $ fromEnum $ f0 (toEnum i)
unsafeMapMonotonic :: (Enum a) => (a -> a) -> Set a -> Set a
unsafeMapMonotonic = map
setCoerce :: (Enum a, Enum b) => Set a -> Set b
setCoerce (Set w) = Set w
toBits :: Set a -> Word
toBits (Set w) = w
fromBits :: Word -> Set a
fromBits w = Set w
fold :: (Eq a, Enum a) => (a -> c -> c) -> c -> Set a -> c
fold f z (Set w) = foldrBits folder z w
where folder i = f (toEnum i)
fold' :: (Eq a, Enum a) => (a -> c -> c) -> c -> Set a -> c
fold' f z (Set w) = foldrBits' folder z w
where folder i = f (toEnum i)
fold1 :: (Eq a, Enum a) => (a -> a -> a) -> Set a -> a
fold1 _ (Set 0) = error (moduleName++".fold1: empty set")
fold1 f (Set w) = foldrBits folder (toEnum maxi) (clearBit w maxi)
where
maxi = msb w
folder i z = f (toEnum i) z
fold1' :: (Eq a, Enum a) => (a -> a -> a) -> Set a -> a
fold1' _ (Set 0) = error (moduleName++".fold1': empty set")
fold1' f (Set w) = foldrBits folder (toEnum maxi) (clearBit w maxi)
where
maxi = msb w
folder i z = f (toEnum i) z
foldr :: (Ord a, Enum a) => (a -> b -> b) -> b -> Set a -> b
foldr f z (Set w) = foldrBits folder z w
where folder i = f (toEnum i)
foldr' :: (Ord a, Enum a) => (a -> b -> b) -> b -> Set a -> b
foldr' f z (Set w) = foldrBits' folder z w
where folder i j = f (toEnum i) j
foldr1 :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> a
foldr1 _ (Set 0) = error (moduleName ++ ".foldr1: empty set")
foldr1 f (Set w) = foldrBits folder (toEnum maxi) (clearBit w maxi)
where
maxi = msb w
folder i z = f (toEnum i) z
foldr1' :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> a
foldr1' _ (Set 0) = error (moduleName++".foldr1': empty set")
foldr1' f (Set w) = foldrBits folder (toEnum maxi) (clearBit w maxi)
where
maxi = msb w
folder i z = f (toEnum i) z
foldl :: (Ord a, Enum a) => (c -> a -> c) -> c -> Set a -> c
foldl f z (Set w) = foldlBits folder z w
where folder h i = f h (toEnum i)
foldl' :: (Ord a, Enum a) => (c -> a -> c) -> c -> Set a -> c
foldl' f z (Set w) = foldlBits' folder z w
where folder h i = f h (toEnum i)
foldl1 :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> a
foldl1 _ (Set 0) = error (moduleName++".foldl1: empty set")
foldl1 f (Set w) = foldlBits folder (toEnum mininum) (clearBit w mininum)
where
mininum = lsb w
folder z i = f z (toEnum i)
foldl1' :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> a
foldl1' _ (Set 0) = error (moduleName++".foldl1': empty set")
foldl1' f (Set w) = foldlBits' folder (toEnum mininum) (clearBit w mininum)
where
mininum = lsb w
folder z i = f z (toEnum i)
fromSeq :: (Eq a, Enum a, S.Sequence s) => s a -> Set a
fromSeq xs = Set $ S.fold' f 0 xs
where f x z = setBit z $ check "fromSeq" $ fromEnum x
fromOrdSeq :: (Ord a, Enum a, S.Sequence s) => s a -> Set a
fromOrdSeq = fromSeq
insertSeq :: (Eq a, Enum a, S.Sequence s) => s a -> Set a -> Set a
insertSeq = insertSeqUsingUnion
insertSeqWith :: (Eq a, Enum a, S.Sequence s) => (a -> a -> a) -> s a -> Set a -> Set a
insertSeqWith _ = insertSeq
toSeq :: (Eq a, Enum a, S.Sequence s) => Set a -> s a
toSeq (Set w) = foldrBits f S.empty w
where f i z = S.lcons (toEnum i) z
toOrdSeq :: (Ord a, Enum a, S.Sequence s) => Set a -> s a
toOrdSeq = toSeq
fromSeqWith :: (Eq a, Enum a, S.Sequence s) => (a -> a -> a) -> s a -> Set a
fromSeqWith = fromSeqWithUsingInsertWith
strict :: Set a -> Set a
strict s@(Set w) = w `seq` s
strictWith :: (a -> b) -> Set a -> Set a
strictWith _ s@(Set w) = w `seq` s
foldrBits :: (Int -> a -> a) -> a -> Word -> a
foldrBits f z w = foldrBits_aux f z 0 w
foldrBits_aux :: (Int -> a -> a) -> a -> Int -> Word -> a
foldrBits_aux _ z _ 0 = z
foldrBits_aux f z i w
| i `seq` w `seq` False = undefined
| otherwise =
case w .&. 0x0F of
0x00 -> a
0x01 -> f i $ a
0x02 -> f (i+1) $ a
0x03 -> f i $ f (i+1) $ a
0x04 -> f (i+2) $ a
0x05 -> f i $ f (i+2) $ a
0x06 -> f (i+1) $ f (i+2) $ a
0x07 -> f i $ f (i+1) $ f (i+2) $ a
0x08 -> f (i+3) $ a
0x09 -> f i $ f (i+3) $ a
0x0A -> f (i+1) $ f (i+3) $ a
0x0B -> f i $ f (i+1) $ f (i+3) $ a
0x0C -> f (i+2) $ f (i+3) $ a
0x0D -> f i $ f (i+2) $ f (i+3) $ a
0x0E -> f (i+1) $ f (i+2) $ f (i+3) $ a
0x0F -> f i $ f (i+1) $ f (i+2) $ f (i+3) $ a
_ -> error "bug in foldrBits_aux"
where a = foldrBits_aux f z (i+4) (Bits.shiftR w 4)
foldrBits' :: (Int -> a -> a) -> a -> Word -> a
foldrBits' f z w = foldrBits_aux' f z 0 w
foldrBits_aux' :: (Int -> a -> a) -> a -> Int -> Word -> a
foldrBits_aux' _ z _ 0 = z
foldrBits_aux' f z i w
| i `seq` w `seq` False = undefined
| otherwise =
case w .&. 0x0F of
0x00 -> a
0x01 -> f i $! a
0x02 -> f (i+1) $! a
0x03 -> f i $! f (i+1) $! a
0x04 -> f (i+2) $! a
0x05 -> f i $! f (i+2) $! a
0x06 -> f (i+1) $! f (i+2) $! a
0x07 -> f i $! f (i+1) $! f (i+2) $! a
0x08 -> f (i+3) $! a
0x09 -> f i $! f (i+3) $! a
0x0A -> f (i+1) $! f (i+3) $! a
0x0B -> f i $! f (i+1) $! f (i+3) $! a
0x0C -> f (i+2) $! f (i+3) $! a
0x0D -> f i $! f (i+2) $! f (i+3) $! a
0x0E -> f (i+1) $! f (i+2) $! f (i+3) $! a
0x0F -> f i $! f (i+1) $! f (i+2) $! f (i+3) $! a
_ -> error "bug in foldrBits_aux'"
where a = foldrBits_aux' f z (i+4) (Bits.shiftR w 4)
foldlBits :: (a -> Int -> a) -> a -> Word -> a
foldlBits f z w = foldlBits_aux f z 0 w
foldlBits_aux :: (a -> Int -> a) -> a -> Int -> Word -> a
foldlBits_aux _ z _ 0 = z
foldlBits_aux f z i w
| i `seq` w `seq` False = undefined
| otherwise =
case w .&. 0x0F of
0x00 -> a $ z
0x01 -> a $ f z i
0x02 -> a $ f z (i+1)
0x03 -> a $ f (f z i) (i+1)
0x04 -> a $ f z (i+2)
0x05 -> a $ f (f z i) (i+2)
0x06 -> a $ f (f z (i+1)) (i+2)
0x07 -> a $ f (f (f z i) (i+1)) (i+2)
0x08 -> a $ f z (i+3)
0x09 -> a $ f (f z i) (i+3)
0x0A -> a $ f (f z (i+1)) (i+3)
0x0B -> a $ f (f (f z i) (i+1)) (i+3)
0x0C -> a $ f (f z (i+2)) (i+3)
0x0D -> a $ f (f (f z i) (i+2)) (i+3)
0x0E -> a $ f (f (f z (i+1)) (i+2)) (i+3)
0x0F -> a $ f (f (f (f z i) (i+1)) (i+2)) (i+3)
_ -> error "bug in foldlBits_aux"
where a b = foldlBits_aux f b (i + 4) (Bits.shiftR w 4)
foldlBits' :: (a -> Int -> a) -> a -> Word -> a
foldlBits' f z w = foldlBits_aux' (\x i -> x `seq` f x i) z 0 w
foldlBits_aux' :: (a -> Int -> a) -> a -> Int -> Word -> a
foldlBits_aux' _ z _ 0 = z
foldlBits_aux' f z i w
| i `seq` w `seq` False = undefined
| otherwise =
case w .&. 0x0F of
0x00 -> a $! z
0x01 -> a $! f z i
0x02 -> a $! f z (i+1)
0x03 -> a $! f (f z i) (i+1)
0x04 -> a $! f z (i+2)
0x05 -> a $! f (f z i) (i+2)
0x06 -> a $! f (f z (i+1)) (i+2)
0x07 -> a $! f (f (f z i) (i+1)) (i+2)
0x08 -> a $! f z (i+3)
0x09 -> a $! f (f z i) (i+3)
0x0A -> a $! f (f z (i+1)) (i+3)
0x0B -> a $! f (f (f z i) (i+1)) (i+3)
0x0C -> a $! f (f z (i+2)) (i+3)
0x0D -> a $! f (f (f z i) (i+2)) (i+3)
0x0E -> a $! f (f (f z (i+1)) (i+2)) (i+3)
0x0F -> a $! f (f (f (f z i) (i+1)) (i+2)) (i+3)
_ -> error "bug in foldlBits_aux"
where a b = foldlBits_aux' f b (i + 4) (Bits.shiftR w 4)
instance (Eq a, Enum a) => C.CollX (Set a) a where
{singleton = singleton; fromSeq = fromSeq; insert = insert;
insertSeq = insertSeq; unionSeq = unionSeq;
delete = delete; deleteAll = deleteAll; deleteSeq = deleteSeq;
null = null; size = size; member = member; count = count;
strict = strict;
structuralInvariant = structuralInvariant; instanceName _ = moduleName}
instance (Ord a, Enum a) => C.OrdCollX (Set a) a where
{deleteMin = deleteMin; deleteMax = deleteMax;
unsafeInsertMin = unsafeInsertMin; unsafeInsertMax = unsafeInsertMax;
unsafeFromOrdSeq = unsafeFromOrdSeq; unsafeAppend = unsafeAppend;
filterLT = filterLT; filterLE = filterLE; filterGT = filterGT;
filterGE = filterGE; partitionLT_GE = partitionLT_GE;
partitionLE_GT = partitionLE_GT; partitionLT_GT = partitionLT_GT}
instance (Eq a, Enum a) => C.SetX (Set a) a where
{intersection = intersection; difference = difference;
symmetricDifference = symmetricDifference;
properSubset = properSubset; subset = subset}
instance (Eq a, Enum a) => C.Coll (Set a) a where
{toSeq = toSeq; lookup = lookup; lookupM = lookupM;
lookupAll = lookupAll; lookupWithDefault = lookupWithDefault;
fold = fold; fold' = fold'; fold1 = fold1; fold1' = fold1';
filter = filter; partition = partition; strictWith = strictWith}
instance (Ord a, Enum a) => C.OrdColl (Set a) a where
{minView = minView; minElem = minElem; maxView = maxView;
maxElem = maxElem; foldr = foldr; foldr' = foldr';
foldl = foldl; foldl' = foldl'; foldr1 = foldr1; foldr1' = foldr1';
foldl1 = foldl1; foldl1' = foldl1'; toOrdSeq = toOrdSeq;
unsafeMapMonotonic = unsafeMapMonotonic}
instance (Eq a, Enum a) => C.Set (Set a) a where
{fromSeqWith = fromSeqWith; insertWith = insertWith;
insertSeqWith = insertSeqWith; unionl = unionl; unionr = unionr;
unionWith = unionWith; unionSeqWith = unionSeqWith;
intersectionWith = intersectionWith}
instance (Ord a, Enum a) => C.OrdSetX (Set a) a
instance (Ord a, Enum a) => C.OrdSet (Set a) a
instance (Eq a, Enum a, Show a) => Show (Set a) where
showsPrec = showsPrecUsingToList
instance (Eq a, Enum a, Read a) => Read (Set a) where
readsPrec = readsPrecUsingFromList
instance (Eq a, Enum a, Arbitrary a) => Arbitrary (Set a) where
arbitrary = do (w::Int) <- arbitrary
return (Set (fromIntegral w))
instance (Eq a, Enum a, CoArbitrary a) => CoArbitrary (Set a) where
coarbitrary (Set w) = coarbitrary (fromIntegral w :: Int)
instance (Eq a, Enum a) => Monoid (Set a) where
mempty = empty
mappend = union
mconcat = unionSeq
instance (Ord a, Enum a) => Ord (Set a) where
compare = compareUsingToOrdList