{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
module Haskus.Binary.BitSet
( BitSet
, BitOffset (..)
, null
, empty
, singleton
, insert
, delete
, toBits
, fromBits
, member
, elem
, notMember
, elems
, intersection
, union
, unions
, fromListToBits
, toListFromBits
, enumerateSetBits
, fromList
, toList
)
where
import Prelude hiding (null,elem)
import qualified GHC.Exts as Ext
import Data.Foldable (foldl')
import Haskus.Binary.Bits
import Haskus.Binary.Storable
newtype BitSet b a = BitSet b deriving (Eq,Ord,Storable)
instance
( Show a
, BitOffset a
, FiniteBits b
, IndexableBits b
, Eq b
) => Show (BitSet b a)
where
show b = "fromList " ++ show (toList b)
null ::
( FiniteBits b
, Eq b
) => BitSet b a -> Bool
{-# INLINABLE null #-}
null (BitSet b) = b == zeroBits
empty :: (FiniteBits b) => BitSet b a
{-# INLINABLE empty #-}
empty = BitSet zeroBits
singleton :: (IndexableBits b, BitOffset a) => a -> BitSet b a
{-# INLINABLE singleton #-}
singleton e = BitSet $ bit (toBitOffset e)
insert :: (IndexableBits b, BitOffset a) => BitSet b a -> a -> BitSet b a
{-# INLINABLE insert #-}
insert (BitSet b) e = BitSet $ setBit b (toBitOffset e)
delete :: (IndexableBits b, BitOffset a) => BitSet b a -> a -> BitSet b a
{-# INLINABLE delete #-}
delete (BitSet b) e = BitSet $ clearBit b (toBitOffset e)
toBits :: BitSet b a -> b
toBits (BitSet b) = b
fromBits :: (BitOffset a, FiniteBits b) => b -> BitSet b a
fromBits = BitSet
member ::
( BitOffset a
, FiniteBits b
, IndexableBits b
) => BitSet b a -> a -> Bool
{-# INLINABLE member #-}
member (BitSet b) e = testBit b (toBitOffset e)
elem ::
( BitOffset a
, FiniteBits b
, IndexableBits b
) => a -> BitSet b a -> Bool
{-# INLINABLE elem #-}
elem e (BitSet b) = testBit b (toBitOffset e)
notMember ::
( BitOffset a
, FiniteBits b
, IndexableBits b
) => BitSet b a -> a -> Bool
{-# INLINABLE notMember #-}
notMember b e = not (member b e)
elems ::
( BitOffset a
, FiniteBits b
, IndexableBits b
, Eq b
) => BitSet b a -> [a]
elems (BitSet b) = go b
where
go !c
| c == zeroBits = []
| otherwise = let e = countTrailingZeros c in fromBitOffset e : go (clearBit c e)
intersection ::
( FiniteBits b
, Bitwise b
) => BitSet b a -> BitSet b a -> BitSet b a
{-# INLINABLE intersection #-}
intersection (BitSet b1) (BitSet b2) = BitSet (b1 .&. b2)
union ::
( FiniteBits b
, Bitwise b
) => BitSet b a -> BitSet b a -> BitSet b a
{-# INLINABLE union #-}
union (BitSet b1) (BitSet b2) = BitSet (b1 .|. b2)
unions ::
( FiniteBits b
, Bitwise b
) => [BitSet b a] -> BitSet b a
{-# INLINABLE unions #-}
unions = foldl' union empty
class BitOffset a where
toBitOffset :: a -> Word
default toBitOffset :: Enum a => a -> Word
toBitOffset = fromIntegral . fromEnum
fromBitOffset :: Word -> a
default fromBitOffset :: Enum a => Word -> a
fromBitOffset = toEnum . fromIntegral
instance BitOffset Int where
toBitOffset = fromIntegral
fromBitOffset = fromIntegral
instance BitOffset Word where
toBitOffset = id
fromBitOffset = id
fromListToBits ::
( BitOffset a
, FiniteBits b
, IndexableBits b
, Foldable m
) => m a -> b
fromListToBits = toBits . fromList
toListFromBits ::
( BitOffset a
, FiniteBits b
, IndexableBits b
, Eq b
) => b -> [a]
toListFromBits = toList . BitSet
enumerateSetBits ::
( BitOffset a
, FiniteBits b
, IndexableBits b
, Eq b
, Bounded a
, Enum a
) => b -> [a]
enumerateSetBits b = go [] [minBound..]
where
go rs [] = rs
go rs (x:xs)
| member (BitSet b) x = go (x:rs) xs
| otherwise = go rs xs
toList ::
( BitOffset a
, FiniteBits b
, IndexableBits b
, Eq b
) => BitSet b a -> [a]
toList = elems
fromList ::
( BitOffset a
, IndexableBits b
, FiniteBits b
, Foldable m
) => m a -> BitSet b a
fromList = foldl' insert (BitSet zeroBits)
instance
( FiniteBits b
, IndexableBits b
, BitOffset a
, Eq b
) => Ext.IsList (BitSet b a)
where
type Item (BitSet b a) = a
fromList = fromList
toList = toList