| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Enumerate.Map
Description
converting between partial functions and maps.
-- doctest
>>>:set +m>>>:set -XLambdaCase>>>:{let uppercasePartial :: (MonadThrow m) => Char -> m Char -- Partial Char Char uppercasePartial = \case 'a' -> return 'A' 'b' -> return 'B' 'z' -> return 'Z' _ -> failed "uppercasePartial" :}
a (safely-)partial function is isomorphic with a Map:
fromFunctionM.toFunctionM=idtoFunctionM.fromFunctionM=id
modulo the error thrown.
- fromFunction :: (Enumerable a, Ord a) => (a -> b) -> Map a b
- fromFunctionM :: (Enumerable a, Ord a) => Partial a b -> Map a b
- toFunction :: (Enumerable a, Ord a) => Map a b -> Maybe (a -> b)
- toFunctionM :: (Enumerable a, Ord a) => Map a b -> Partial a b
- unsafeToFunction :: Ord a => Map a b -> a -> b
- isMapTotal :: (Enumerable a, Ord a) => Map a b -> Bool
- invertMap :: (Ord a, Ord b) => Map a b -> Map b (NonEmpty a)
- isTotalM :: (Enumerable a, Ord a) => Partial a b -> Maybe (a -> b)
- domainM :: Enumerable a => Partial a b -> [a]
- corange :: Enumerable a => (a -> b) -> [a]
- corangeM :: Enumerable a => Partial a b -> [a]
- image :: Enumerable a => (a -> b) -> [b]
- imageM :: Enumerable a => Partial a b -> [b]
- codomain :: Enumerable b => (a -> b) -> [b]
- codomainM :: Enumerable b => Partial a b -> [b]
- invert :: (Enumerable a, Ord a, Ord b) => (a -> b) -> b -> [a]
- invertM :: (Enumerable a, Ord a, Ord b) => Partial a b -> b -> [a]
- getJectivityM :: (Enumerable a, Enumerable b, Ord a, Ord b) => Partial a b -> Maybe Jectivity
- isInjective :: (Enumerable a, Ord a, Ord b) => (a -> b) -> Maybe (b -> Maybe a)
- isInjectiveM :: (Enumerable a, Ord a, Ord b) => Partial a b -> Maybe (b -> Maybe a)
- isUnique :: Ord a => [a] -> Maybe (Set a)
- isSurjective :: (Enumerable a, Enumerable b, Ord a, Ord b) => (a -> b) -> Maybe (b -> NonEmpty a)
- isSurjectiveM :: (Enumerable a, Enumerable b, Ord a, Ord b) => Partial a b -> Maybe (b -> NonEmpty a)
- isBijective :: (Enumerable a, Enumerable b, Ord a, Ord b) => (a -> b) -> Maybe (b -> a)
- isBijectiveM :: (Enumerable a, Enumerable b, Ord a, Ord b) => Partial a b -> Maybe (b -> a)
Documentation
fromFunction :: (Enumerable a, Ord a) => (a -> b) -> Map a b Source
convert a total function to a map.
>>> fromFunction not
fromList [(False,True),(True,False)]
fromFunctionM :: (Enumerable a, Ord a) => Partial a b -> Map a b Source
convert a (safely-)partial function to a map.
wraps reifyFunctionM.
toFunction :: (Enumerable a, Ord a) => Map a b -> Maybe (a -> b) Source
convert a map to a function, if the map is total.
>>> let Just not' = toFunction (Map.fromList [(False,True),(True,False)]) >>> not' False True
toFunctionM :: (Enumerable a, Ord a) => Map a b -> Partial a b Source
convert a (safely-)partial function to a map.
lookup failures are throwMn as a PatternMatchFail.
>>> let idPartial = toFunctionM (Map.fromList [(True,True)]) >>> idPartial True True >>> idPartial False *** Exception: toFunctionM
unsafeToFunction :: Ord a => Map a b -> a -> b Source
wraps lookup
isMapTotal :: (Enumerable a, Ord a) => Map a b -> Bool Source
does the map contain every key in its domain?
>>>isMapTotal (Map.fromList [(False,True),(True,False)])True
>>>isMapTotal (Map.fromList [('a',0)])False
isTotalM :: (Enumerable a, Ord a) => Partial a b -> Maybe (a -> b) Source
refines the partial function, if total.
>>>:{let myNotM :: Monad m => Bool -> m Bool myNotM False = return True myNotM True = return False :}>>>let Just myNot = isTotalM myNotM>>>myNot FalseTrue
domainM :: Enumerable a => Partial a b -> [a] Source
the domain of a partial function
is the subset of the enumerated input where it's defined.
i.e. when x `member` (domainM f) then fromJust (f x) is defined.
>>>domainM uppercasePartial['a','b','z']
corange :: Enumerable a => (a -> b) -> [a] Source
(right name?)
corange _ = enumerated
corangeM :: Enumerable a => Partial a b -> [a] Source
corangeM _ = enumerated
image :: Enumerable a => (a -> b) -> [b] Source
imageM :: Enumerable a => Partial a b -> [b] Source
the image (not the codomain) of a partial function.
imageM f = mapMaybe f enumeratedincludes duplicates.
codomain :: Enumerable b => (a -> b) -> [b] Source
the codomain of a function. it contains the image.
codomain _ = enumerated
codomainM :: Enumerable b => Partial a b -> [b] Source
invert :: (Enumerable a, Ord a, Ord b) => (a -> b) -> b -> [a] Source
invert a total function.
(invert f) b is:
[]whereverfis not surjective[y]whereverfis uniquely defined(_:_)whereverfis not injective
invert f = invertM (return.f)invertM :: (Enumerable a, Ord a, Ord b) => Partial a b -> b -> [a] Source
invert a partial function.
(invertM f) b is:
[]whereverfis partial[]whereverfis not surjective[y]whereverfis uniquely defined(_:_)whereverfis not injective
a Map is stored internally, with as many keys as the image of f.
see also isBijectiveM.
getJectivityM :: (Enumerable a, Enumerable b, Ord a, Ord b) => Partial a b -> Maybe Jectivity Source
isInjective :: (Enumerable a, Ord a, Ord b) => (a -> b) -> Maybe (b -> Maybe a) Source
isInjectiveM :: (Enumerable a, Ord a, Ord b) => Partial a b -> Maybe (b -> Maybe a) Source
returns the inverse of the injection, if injective.
refines (b -> [a]) (i.e. the type of invertM) to (b -> Maybe a).
unlike isBijectiveM, doesn't need an (Enumerable b) constraint. this helps when you want to ensure a function into an infinite type (e.g. show) is injective. and still reasonably efficient, given the (Ord b) constraint.
isUnique :: Ord a => [a] -> Maybe (Set a) Source
converts the list into a set, if it has no duplicates.
isSurjective :: (Enumerable a, Enumerable b, Ord a, Ord b) => (a -> b) -> Maybe (b -> NonEmpty a) Source
isSurjectiveM :: (Enumerable a, Enumerable b, Ord a, Ord b) => Partial a b -> Maybe (b -> NonEmpty a) Source
isBijective :: (Enumerable a, Enumerable b, Ord a, Ord b) => (a -> b) -> Maybe (b -> a) Source
isBijectiveM :: (Enumerable a, Enumerable b, Ord a, Ord b) => Partial a b -> Maybe (b -> a) Source
returns the inverse of the bijection, if bijective.
refines (b -> [a]) (i.e. the type of invertM) to (b -> a).
can short-circuit.