WeakSets-0.2.0.0: Simple set types. Useful to create sets of arbitrary types and nested sets.
CopyrightGuillaume Sabbagh 2022
LicenseLGPL-3.0-or-later
Maintainerguillaumesabbagh@protonmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

HomogeneousSet

Description

Homogeneous sets are sets which can contain only one type of values.

They are more flexible than Data.Set because they do not require the objects contained to be orderable.

The datatype only assumes its components are equatable, it is therefore slower than the Data.Set datatype.

We use this datatype because most of the datatypes we care about are not orderable.

Inline functions related to homogeneous sets are written between pipes |.

Function names should not collide with Prelude but should collide with Data.Set.

Synopsis

Set datatype and smart constructor

data Set a Source #

A homogeneous set is a list of values.

The only differences are that we don't want duplicate elements and we don't need the order of the list elements.

To force these constraints, the Set constructor is abstract and is not exported. The only way to construct a set is to use the smart constructor set which ensures the previous conditions.

Instances

Instances details
Monad Set Source # 
Instance details

Defined in HomogeneousSet

Methods

(>>=) :: Set a -> (a -> Set b) -> Set b

(>>) :: Set a -> Set b -> Set b

return :: a -> Set a

Functor Set Source # 
Instance details

Defined in HomogeneousSet

Methods

fmap :: (a -> b) -> Set a -> Set b

(<$) :: a -> Set b -> Set a

Applicative Set Source # 
Instance details

Defined in HomogeneousSet

Methods

pure :: a -> Set a

(<*>) :: Set (a -> b) -> Set a -> Set b

liftA2 :: (a -> b -> c) -> Set a -> Set b -> Set c

(*>) :: Set a -> Set b -> Set b

(<*) :: Set a -> Set b -> Set a

Foldable Set Source # 
Instance details

Defined in HomogeneousSet

Methods

fold :: Monoid m => Set m -> m

foldMap :: Monoid m => (a -> m) -> Set a -> m

foldMap' :: Monoid m => (a -> m) -> Set a -> m

foldr :: (a -> b -> b) -> b -> Set a -> b

foldr' :: (a -> b -> b) -> b -> Set a -> b

foldl :: (b -> a -> b) -> b -> Set a -> b

foldl' :: (b -> a -> b) -> b -> Set a -> b

foldr1 :: (a -> a -> a) -> Set a -> a

foldl1 :: (a -> a -> a) -> Set a -> a

toList :: Set a -> [a]

null :: Set a -> Bool

length :: Set a -> Int

elem :: Eq a => a -> Set a -> Bool

maximum :: Ord a => Set a -> a

minimum :: Ord a => Set a -> a

sum :: Num a => Set a -> a

product :: Num a => Set a -> a

Eq a => Eq (Set a) Source # 
Instance details

Defined in HomogeneousSet

Methods

(==) :: Set a -> Set a -> Bool

(/=) :: Set a -> Set a -> Bool

Show a => Show (Set a) Source # 
Instance details

Defined in HomogeneousSet

Methods

showsPrec :: Int -> Set a -> ShowS

show :: Set a -> String

showList :: [Set a] -> ShowS

Eq a => Semigroup (Set a) Source # 
Instance details

Defined in HomogeneousSet

Methods

(<>) :: Set a -> Set a -> Set a

sconcat :: NonEmpty (Set a) -> Set a

stimes :: Integral b => b -> Set a -> Set a

Eq a => Monoid (Set a) Source # 
Instance details

Defined in HomogeneousSet

Methods

mempty :: Set a

mappend :: Set a -> Set a -> Set a

mconcat :: [Set a] -> Set a

set :: [a] -> Set a Source #

The smart constructor of sets. This is the only way of instantiating a Set.

If several elements are equal, they are kept until the user wants a list back.

Set related functions

setToList :: Eq a => Set a -> [a] Source #

Transform a Set back into a list, the list returned does not have duplicate elements, the order of the original list holds.

isIncludedIn :: Eq a => Set a -> Set a -> Bool Source #

Return a boolean indicating if a Set is included in another one.

cardinal :: Eq a => Set a -> Int Source #

Size of a set.

isIn :: Eq a => a -> Set a -> Bool Source #

Return wether an element is in a set.

(|&|) :: Eq a => Set a -> Set a -> Set a Source #

Return the intersection of two sets.

(|||) :: Set a -> Set a -> Set a Source #

Return the union of two sets.

(|*|) :: Set a -> Set b -> Set (a, b) Source #

Return the cartesian product of two sets.

(|+|) :: Set a -> Set b -> Set (Either a b) Source #

Return the disjoint union of two sets.

(|-|) :: Eq a => Set a -> Set a -> Set a Source #

Return the difference of two sets.

(|^|) :: (Num a, Eq a) => Set a -> a -> Set [a] Source #

Returns the cartesian product of a set with itself n times.

powerSet :: Set a -> Set (Set a) Source #

Return the set of all subsets of a given set.

filterSet :: (a -> Bool) -> Set a -> Set a Source #

Filter a set according to a condition.

Functions to work with Maybe

setToMaybe :: Set a -> Maybe a Source #

Set version of listToMaybe.

maybeToSet :: Maybe a -> Set a Source #

Set version of maybeToList.

catMaybesToSet :: Set (Maybe a) -> Set a Source #

Set version of catMaybes.

mapMaybeToSet :: (a -> Maybe b) -> Set a -> Set b Source #

Set version of mapMaybe.

Function datatype and smart constructor

type AssociationList a b = [(a, b)] Source #

An association list is a list of pairs (key,value).

data Function a b Source #

A function of homogeneous sets. It is a set of pairs (key,value) such that their should only be one pair with a given key.

It is an abstract type, the smart constructor is function.

Instances

Instances details
(Eq a, Eq b) => Eq (Function a b) Source # 
Instance details

Defined in HomogeneousSet

Methods

(==) :: Function a b -> Function a b -> Bool

(/=) :: Function a b -> Function a b -> Bool

(Show a, Show b) => Show (Function a b) Source # 
Instance details

Defined in HomogeneousSet

Methods

showsPrec :: Int -> Function a b -> ShowS

show :: Function a b -> String

showList :: [Function a b] -> ShowS

function :: AssociationList a b -> Function a b Source #

The smart constructor of functions. This is the only way of instantiating a Function.

Takes an association list and returns a function which maps to each key the value associated.

If several pairs have the same keys, they are kept until the user wants an association list back.

Function related functions

functionToSet :: Eq a => Function a b -> Set (a, b) Source #

Transform a function back into its underlying association list.

domain :: Function a b -> Set a Source #

Return the domain of a function.

image :: Function a b -> Set b Source #

Return the image of a function. The image of a function is the set of values which are reachable by applying the function.

(|$|) :: Eq a => Function a b -> a -> Maybe b Source #

Apply a function to a given value. If the function is not defined on the given value returns Nothing, otherwise returns Just the image.

This function is like lookup in Data.Map for function (the order of the argument are reversed though).

(|!|) :: Eq a => Function a b -> a -> b Source #

Unsafe version of (|$|).

This function is like (!) in Data.Map for function.

findWithDefault :: Eq a => Function a b -> b -> a -> b Source #

Apply a function to a given value, if the value is in the domain returns the image, otherwise return a default value.

This function is like findWithDefault in Data.Map for function (the order of the argument are reversed though).

(|.|) :: (Eq a, Eq b) => Function b c -> Function a b -> Function a c Source #

Compose two functions. If the two functions are not composable, strips the functions until they can compose.

memorizeFunction :: (a -> b) -> Set a -> Function a b Source #

Memorize a Haskell function on a given finite domain.