WeakSets-0.4.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

Data.WeakSets.HomogeneousFunction

Description

Homogeneous functions are functions between HomogeneousSets.

They are more flexible than Data.Map because they do not require the keys to be orderable.

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

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

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

Function names should not collide with Prelude but may collide with Data.Map.

Synopsis

Function datatype and smart constructor

type AssociationList k v = [(k, v)] Source #

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

data Function k v 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
Functor (Function k) Source # 
Instance details

Defined in Data.WeakSets.HomogeneousFunction

Methods

fmap :: (a -> b) -> Function k a -> Function k b

(<$) :: a -> Function k b -> Function k a

Foldable (Function k) Source # 
Instance details

Defined in Data.WeakSets.HomogeneousFunction

Methods

fold :: Monoid m => Function k m -> m

foldMap :: Monoid m => (a -> m) -> Function k a -> m

foldMap' :: Monoid m => (a -> m) -> Function k a -> m

foldr :: (a -> b -> b) -> b -> Function k a -> b

foldr' :: (a -> b -> b) -> b -> Function k a -> b

foldl :: (b -> a -> b) -> b -> Function k a -> b

foldl' :: (b -> a -> b) -> b -> Function k a -> b

foldr1 :: (a -> a -> a) -> Function k a -> a

foldl1 :: (a -> a -> a) -> Function k a -> a

toList :: Function k a -> [a]

null :: Function k a -> Bool

length :: Function k a -> Int

elem :: Eq a => a -> Function k a -> Bool

maximum :: Ord a => Function k a -> a

minimum :: Ord a => Function k a -> a

sum :: Num a => Function k a -> a

product :: Num a => Function k a -> a

(Eq k, Eq v) => Eq (Function k v) Source # 
Instance details

Defined in Data.WeakSets.HomogeneousFunction

Methods

(==) :: Function k v -> Function k v -> Bool

(/=) :: Function k v -> Function k v -> Bool

(Show k, Show v) => Show (Function k v) Source # 
Instance details

Defined in Data.WeakSets.HomogeneousFunction

Methods

showsPrec :: Int -> Function k v -> ShowS

show :: Function k v -> String

showList :: [Function k v] -> ShowS

Semigroup (Function k v) Source # 
Instance details

Defined in Data.WeakSets.HomogeneousFunction

Methods

(<>) :: Function k v -> Function k v -> Function k v

sconcat :: NonEmpty (Function k v) -> Function k v

stimes :: Integral b => b -> Function k v -> Function k v

Monoid (Function k v) Source # 
Instance details

Defined in Data.WeakSets.HomogeneousFunction

Methods

mempty :: Function k v

mappend :: Function k v -> Function k v -> Function k v

mconcat :: [Function k v] -> Function k v

function :: AssociationList k v -> Function k v Source #

O(1). 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

domain :: Function k v -> Set k Source #

O(n). Return the domain of a function.

image :: Function k v -> Set v Source #

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

idFromSet :: Set a -> Function a a Source #

O(n). Return the identity function associated to a Set.

(|.|) :: (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.

Query

size :: Eq k => Function k v -> Int Source #

O(n). The number of entries in the function.

member :: Eq k => Function k v -> k -> Bool Source #

O(n). Return wether a key is in the function domain or not.

notMember :: Eq k => Function k v -> k -> Bool Source #

O(n). Negation of member.

(|?|) :: Eq k => Function k v -> k -> Maybe v Source #

O(n). 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 k => Function k v -> k -> v Source #

O(n). Unsafe version of (|?|).

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

findWithDefault :: Eq k => Function k v -> v -> k -> v Source #

O(n). 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).

Construction

Insertion

insert :: k -> v -> Function k v -> Function k v Source #

O(1). Insert a new key and value in the function. If the key is already present in the function, the associated value is replaced with the supplied value. insert is equivalent to insertWith const.

insertWith :: Eq k => (v -> v -> v) -> k -> v -> Function k v -> Function k v Source #

O(n). Insert with a function, combining new value and old value. insertWith f key value mp will insert the pair (key, value) into mp if key does not exist in the function. If the key does exist, the function will insert the pair (key, f new_value old_value).

insertWithKey :: Eq k => (k -> a -> a -> a) -> k -> a -> Function k a -> Function k a Source #

O(n). Insert with a function, combining key, new value and old value. insertWithKey f key value mp will insert the pair (key, value) into mp if key does not exist in the function. If the key does exist, the function will insert the pair (key,f key new_value old_value). Note that the key passed to f is the same key passed to insertWithKey.

Delete/Update

delete :: Eq k => k -> Function k a -> Function k a Source #

O(n). Delete a key and its value from the function. When the key is not a member of the function, the original function is returned.

adjust :: Eq k => (a -> a) -> k -> Function k a -> Function k a Source #

O(n). Update a value at a specific key with the result of the provided function. When the key is not a member of the function, the original function is returned.

adjustWithKey :: Eq k => (k -> a -> a) -> k -> Function k a -> Function k a Source #

O(n). Adjust a value at a specific key. When the key is not a member of the function, the original function is returned.

alter :: Eq k => (Maybe a -> Maybe a) -> k -> Function k a -> Function k a Source #

O(n). The expression (alter f k function) alters the value x at k, or absence thereof. alter can be used to insert, delete, or update a value in a Function. In short : lookup k (alter f k m) = f (lookup k m).

Combine

Union

union :: Eq k => Function k a -> Function k a -> Function k a Source #

O(n). The expression (union t1 t2) takes the left-biased union of t1 and t2. It prefers t1 when duplicate keys are encountered.

Traversal

mapKeys :: (k1 -> k2) -> Function k1 v -> Function k2 v Source #

O(n). Map a function over the keys of a function.

Conversion

keys :: Function k v -> Set k Source #

O(n). Alias of domain.

elems :: Function k v -> Set v Source #

O(n). Alias of image.

functionToSet :: Eq k => Function k v -> Set (k, v) Source #

O(n). Transform a function back into its underlying association list.

memorizeFunction :: (k -> v) -> Set k -> Function k v Source #

O(n). Memorize a Haskell function on a given finite domain.