word8set-0.1.1: Word8 set
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Word8Set

Description

The Word8Set type represents a set of elements of type Word8.

The interface of this module mimics the Data.Set and/or Data.IntSet module interfaces from @containers package.

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

import Data.Word8Set (Word8Set)
import qualified Data.Word8Set as W8S

Implementation

The implementation is based on Word256 type. Word8Set is 256 bits.

Synopsis

Set type

data Word8Set Source #

A set of Word8 numbers.

Implemented using Word256.

Instances

Instances details
Arbitrary Word8Set Source # 
Instance details

Defined in Data.Word8Set

CoArbitrary Word8Set Source # 
Instance details

Defined in Data.Word8Set

Methods

coarbitrary :: Word8Set -> Gen b -> Gen b #

Function Word8Set Source # 
Instance details

Defined in Data.Word8Set

Methods

function :: (Word8Set -> b) -> Word8Set :-> b #

IsString Word8Set Source #
fromString = fromASCII

Since: 0.1.1

Instance details

Defined in Data.Word8Set

Monoid Word8Set Source # 
Instance details

Defined in Data.Word8Set

Semigroup Word8Set Source # 
Instance details

Defined in Data.Word8Set

IsList Word8Set Source # 
Instance details

Defined in Data.Word8Set

Associated Types

type Item Word8Set #

Show Word8Set Source # 
Instance details

Defined in Data.Word8Set

NFData Word8Set Source # 
Instance details

Defined in Data.Word8Set

Methods

rnf :: Word8Set -> () #

Eq Word8Set Source # 
Instance details

Defined in Data.Word8Set

Ord Word8Set Source # 
Instance details

Defined in Data.Word8Set

Heyting Word8Set Source #

Since: 0.1.1

Instance details

Defined in Data.Word8Set

BoundedJoinSemiLattice Word8Set Source # 
Instance details

Defined in Data.Word8Set

Methods

bottom :: Word8Set #

BoundedMeetSemiLattice Word8Set Source # 
Instance details

Defined in Data.Word8Set

Methods

top :: Word8Set #

Lattice Word8Set Source # 
Instance details

Defined in Data.Word8Set

PartialOrd Word8Set Source #
leq = isSubsetOf

Since: 0.1.1

Instance details

Defined in Data.Word8Set

Lift Word8Set Source # 
Instance details

Defined in Data.Word8Set

Methods

lift :: Quote m => Word8Set -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word8Set -> Code m Word8Set #

type Item Word8Set Source # 
Instance details

Defined in Data.Word8Set

type Key = Word8 Source #

Key of Word8Set is Word8.

Construction

empty :: Word8Set Source #

The empty set.

>>> empty
fromList []

full :: Word8Set Source #

The full set.

>>> full
fromList [0,1,2,3,4,5,6,7,8,9,10,11,12,...,255]

singleton :: Key -> Word8Set Source #

A set of one element.

>>> singleton 127
fromList [127]

range :: Key -> Key -> Word8Set Source #

A set of inclusive range.

>>> range 10 20
fromList [10,11,12,13,14,15,16,17,18,19,20]

Insertion

insert :: Key -> Word8Set -> Word8Set Source #

Add a value to the set.

>>> insert 10 (range 15 20)
fromList [10,15,16,17,18,19,20]
>>> insert 10 (range 10 15)
fromList [10,11,12,13,14,15]

Deletion

delete :: Key -> Word8Set -> Word8Set Source #

Delete a value in the set. Returns the original set when the value was not present.

>>> delete 10 (range 5 15)
fromList [5,6,7,8,9,11,12,13,14,15]
>>> delete 10 (range 1 10)
fromList [1,2,3,4,5,6,7,8,9]

Generalized insertion/deletion

alterF :: Functor f => (Bool -> f Bool) -> Key -> Word8Set -> f Word8Set Source #

Generalized insetion deletion.

Query

member :: Key -> Word8Set -> Bool Source #

Is the value a member of the set?

>>> member 5 (range 10 20)
False
>>> member 15 (range 10 20)
True

notMember :: Key -> Word8Set -> Bool Source #

Is the element not in the set?

>>> notMember 5 (range 10 20)
True
>>> notMember 15 (range 10 20)
False

lookupLT :: Key -> Word8Set -> Maybe Key Source #

Find largest element smaller than the given one.

>>> lookupLT 3 (fromList [3, 5])
Nothing
>>> lookupLT 5 (fromList [3, 5])
Just 3
>>> lookupLT 0 full
Nothing

lookupGT :: Key -> Word8Set -> Maybe Key Source #

Find smallest element greater than the given one.

>>> lookupGT 4 (fromList [3, 5])
Just 5
>>> lookupGT 5 (fromList [3, 5])
Nothing
>>> lookupGT 255 full
Nothing

lookupLE :: Key -> Word8Set -> Maybe Key Source #

Find largest element smaller or equal to the given one.

>>> lookupLE 2 (fromList [3, 5])
Nothing
>>> lookupLE 4 (fromList [3, 5])
Just 3
>>> lookupLE 5 (fromList [3, 5])
Just 5

lookupGE :: Key -> Word8Set -> Maybe Key Source #

Find smallest element greater or equal to the given one.

>>> lookupGE 3 (fromList [3, 5])
Just 3
>>> lookupGE 4 (fromList [3, 5])
Just 5
>>> lookupGE 6 (fromList [3, 5])
Nothing

null :: Word8Set -> Bool Source #

Is the set empty?

>>> null empty
True
>>> null (range 10 20)
False

isFull :: Word8Set -> Bool Source #

Is the set full?

>>> isFull full
True
>>> isFull (range 1 255)
False

isSingleton :: Word8Set -> Maybe Key Source #

Is set singleton?

>>> isSingleton empty
Nothing
>>> isSingleton full
Nothing
>>> isSingleton (singleton 5)
Just 5
>>> isSingleton (fromList [3, 5])
Nothing

isRange :: Word8Set -> Maybe (Key, Key) Source #

Is set of the form range l r?

>>> isRange empty
Nothing
>>> isRange full
Just (0,255)
>>> isRange (singleton 5)
Just (5,5)
>>> isRange (range 10 20)
Just (10,20)
>>> isRange (fromList [3, 5])
Nothing

size :: Word8Set -> Int Source #

Cardinality of the set.

>>> size empty
0
>>> size (union (range 10 20) (range 30 40))
22

isSubsetOf :: Word8Set -> Word8Set -> Bool Source #

Is this a subset? (s1 isSubsetOf s2) tells whether s1 is a subset of s2.

>>> isSubsetOf (range 10 20) (range 5 25)
True
>>> isSubsetOf (range 10 20) (range 10 20)
True
>>> isSubsetOf (range 5 25) (range 10 20)
False

isProperSubsetOf :: Word8Set -> Word8Set -> Bool Source #

Is this a proper subset? Is this a proper subset? (ie. a subset but not equal).

>>> isProperSubsetOf (range 10 20) (range 5 25)
True
>>> isProperSubsetOf (range 10 20) (range 10 20)
False
>>> isProperSubsetOf (range 5 25) (range 10 20)
False

disjoint :: Word8Set -> Word8Set -> Bool Source #

Check whether two sets are disjoint (i.e. their intersection is empty).

>>> disjoint (range 11 20) (range 21 30)
True

Combine

union :: Word8Set -> Word8Set -> Word8Set Source #

The union of two sets.

unions :: Foldable f => f Word8Set -> Word8Set Source #

The union of a list of sets.

difference :: Word8Set -> Word8Set -> Word8Set Source #

Difference between two sets.

symmetricDifference :: Word8Set -> Word8Set -> Word8Set Source #

Symmetric difference between two sets

symmetricDifference xs ys = difference (union xs ys) (intersection xs ys)
>>> symmetricDifference (range 10 20) (range 15 25)
fromList [10,11,12,13,14,21,22,23,24,25]

Since: 0.1.1

intersection :: Word8Set -> Word8Set -> Word8Set Source #

The intersection between two sets.

complement :: Word8Set -> Word8Set Source #

The complement of the set.

Filter

filter :: (Key -> Bool) -> Word8Set -> Word8Set Source #

Filter all elements that satisfy some predicate.

>>> filter even (range 10 20)
fromList [10,12,14,16,18,20]

partition :: (Key -> Bool) -> Word8Set -> (Word8Set, Word8Set) Source #

Partition the set according to some predicate.

>>> partition even (range 10 20)
(fromList [10,12,14,16,18,20],fromList [11,13,15,17,19])

Map

map :: (Key -> Key) -> Word8Set -> Word8Set Source #

map f s is the set obtained by applying f to each element of s.

>>> map (+ 1) (fromList [0, 10, 250, 255])
fromList [0,1,11,251]

Folds

foldr :: (Key -> b -> b) -> b -> Word8Set -> b Source #

Lazy right fold.

>>> foldr (:) [] (unions [range 10 20, range 70 73, range 130 132, range 200 202, singleton 255])
[10,11,12,13,14,15,16,17,18,19,20,70,71,72,73,130,131,132,200,201,202,255]

foldl :: (a -> Key -> a) -> a -> Word8Set -> a Source #

Lazy left fold.

>>> foldl (flip (:)) [] (unions [range 10 20, range 70 73, range 130 132, range 200 202, singleton 255])
[255,202,201,200,132,131,130,73,72,71,70,20,19,18,17,16,15,14,13,12,11,10]

Strict folds

foldr' :: (Key -> b -> b) -> b -> Word8Set -> b Source #

Strict right fold.

foldl' :: (a -> Key -> a) -> a -> Word8Set -> a Source #

Strict left fold.

Min/Max

findMin :: Word8Set -> Word8 Source #

The minimal element of the set.

>>> findMin (fromList [3, 5])
3

Returns 0 for empty set.

>>> findMin empty
0

findMax :: Word8Set -> Word8 Source #

The maximal element of the set.

>>> findMax (fromList [3, 5])
5

Returns 255 for empty set.

>>> findMax empty
255

deleteMin :: Word8Set -> Word8Set Source #

Delete the minimal element. Returns an empty set if the set is empty.

deleteMax :: Word8Set -> Word8Set Source #

Delete the maximal element. Returns an empty set if the set is empty.

maxView :: Word8Set -> Maybe (Key, Word8Set) Source #

Retrieves the maximal key of the set, and the set stripped of that element, or Nothing if passed an empty set.

>>> maxView (fromList [3, 5])
Just (5,fromList [3])
>>> maxView empty
Nothing

minView :: Word8Set -> Maybe (Key, Word8Set) Source #

Retrieves the minimal key of the set, and the set stripped of that element, or Nothing if passed an empty set.

>>> minView (fromList [3, 5])
Just (3,fromList [5])
>>> minView empty
Nothing

Conversion

to/fromList

elems :: Word8Set -> [Key] Source #

The elements of a set in ascending order.

toList :: Word8Set -> [Key] Source #

The elements of a set in ascending order.

fromList :: [Key] -> Word8Set Source #

Create a set from a list of Word8s.

fromFoldable :: Foldable f => f Key -> Word8Set Source #

Create a set from a foldable of Word8s.

to/from Word256

toWord256 :: Word8Set -> Word256 Source #

Convert set to Word256.

fromWord256 :: Word256 -> Word8Set Source #

Create set from Word256.

to/from ASCII Strings

toASCII :: Word8Set -> String Source #

Create ASCII string from a set.

>>> toASCII (range 100 120)
"defghijklmnopqrstuvwx"

fromASCII :: String -> Word8Set Source #

Create set from ASCII string.

>>> fromASCII "foobar"
fromList [97,98,102,111,114]

Non-ASCII codepoints are truncated:

>>> fromASCII "\1000"
fromList [232]