bitset-1.4.1: A space-efficient set data structure.

PortabilityGHC
Stabilityexperimental
Maintainersuperbobry@gmail.com
Safe HaskellNone

Data.BitSet.Generic

Contents

Description

A space-efficient implementation of set data structure for enumerated data types.

Note: Read below the synopsis for important notes on the use of this module.

This module is intended to be imported qualified, to avoid name clashes with Prelude functions, e.g.

 import Data.BitSet.Generic (BitSet)
 import qualified Data.BitSet.Generic as BS

The implementation is abstract with respect to container type, so any numeric type with Bits instance can be used as a container. However, independent of container choice, the maximum number of elements in a bit set is bounded by maxBound :: Int.

Synopsis

Bit set type

data GBitSet c a Source

A bit set with unspecified container type.

Instances

Typeable2 GBitSet 
Num c => Foldable (GBitSet c) 
Eq (GBitSet c a) 
Ord (GBitSet c a) 
(Enum a, Read a, Bits c, Num c) => Read (GBitSet c a) 
(Show a, Num c) => Show (GBitSet c a) 
(Enum a, Bits c, Num c) => Monoid (GBitSet c a) 
(Bits c, Enum a, Num c, Storable c) => Storable (GBitSet c a) 
NFData c => NFData (GBitSet c a) 

Operators

(\\) :: GBitSet c a -> GBitSet c a -> GBitSet c aSource

O(max(m, n)). See difference.

Construction

empty :: (Enum a, Bits c, Num c) => GBitSet c aSource

The empty bit set.

singleton :: (Enum a, Bits c, Num c) => a -> GBitSet c aSource

O(1). Create a singleton set.

insert :: a -> GBitSet c a -> GBitSet c aSource

O(d). Insert an item into the bit set.

delete :: a -> GBitSet c a -> GBitSet c aSource

O(d). Delete an item from the bit set.

Query

null :: GBitSet c a -> BoolSource

O(1). Is the bit set empty?

size :: GBitSet c a -> IntSource

O(1). The number of elements in the bit set.

member :: (Enum a, Bits c) => a -> GBitSet c a -> BoolSource

O(d). Ask whether the item is in the bit set.

notMember :: (Enum a, Bits c) => a -> GBitSet c a -> BoolSource

O(d). Ask whether the item is in the bit set.

isSubsetOf :: GBitSet c a -> GBitSet c a -> BoolSource

O(max(n, m)). Is this a subset? (s1 isSubsetOf s2) tells whether s1 is a subset of s2.

isProperSubsetOf :: Eq c => GBitSet c a -> GBitSet c a -> BoolSource

O(max(n, m). Is this a proper subset? (ie. a subset but not equal).

Combine

union :: GBitSet c a -> GBitSet c a -> GBitSet c aSource

O(max(m, n)). The union of two bit sets.

difference :: GBitSet c a -> GBitSet c a -> GBitSet c aSource

O(max(m, n)). Difference of two bit sets.

intersection :: GBitSet c a -> GBitSet c a -> GBitSet c aSource

O(max(m, n)). The intersection of two bit sets.

Transformations

map :: (Enum a, Enum b, Bits c, Num c) => (a -> b) -> GBitSet c a -> GBitSet c bSource

O(d * n) Transform this bit set by applying a function to every value. Resulting bit set may be smaller then the original.

Folds

foldl' :: (b -> a -> b) -> b -> GBitSet c a -> bSource

O(d * n) Reduce this bit set by applying a binary function to all elements, using the given starting value. Each application of the operator is evaluated before before using the result in the next application. This function is strict in the starting value.

foldr :: (a -> b -> b) -> b -> GBitSet c a -> bSource

O(d * n) Reduce this bit set by applying a binary function to all elements, using the given starting value.

Filter

filter :: (Enum a, Bits c, Num c) => (a -> Bool) -> GBitSet c a -> GBitSet c aSource

O(d * n) Filter this bit set by retaining only elements satisfying predicate.

Lists

toList :: Num c => GBitSet c a -> [a]Source

O(d * n). Convert this bit set set to a list of elements.

fromList :: (Enum a, Bits c, Num c) => [a] -> GBitSet c aSource

O(d * n). Make a bit set from a list of elements.

Internal

toBits :: GBitSet c a -> cSource

O(1). Internal function, which extracts the underlying container from the bit set.

unsafeFromBits :: (Enum a, Bits c, Num c) => c -> GBitSet c aSource

O(1). Internal function, which constructs a bit set, using a given container value. Highly unsafe, because we don't check if bits in the given value correspond to valid instances of type a.