Safe Haskell | None |
---|---|
Language | Haskell2010 |
Implementation of partial bidirectional mapping as a data type.
Synopsis
- data BiMap a b = BiMap {}
- invert :: BiMap a b -> BiMap b a
- iso :: (a -> b) -> (b -> a) -> BiMap a b
- prism :: (field -> object) -> (object -> Maybe field) -> BiMap object field
- mkAnyValueBiMap :: (forall t. Value t -> Maybe a) -> (a -> Value tag) -> BiMap a AnyValue
- _TextBy :: (a -> Text) -> (Text -> Maybe a) -> BiMap a AnyValue
- _NaturalInteger :: BiMap Natural Integer
- _StringText :: BiMap String Text
- _ReadString :: (Show a, Read a) => BiMap a String
- _BoundedInteger :: (Integral a, Bounded a) => BiMap a Integer
- _ByteStringText :: BiMap ByteString Text
- _LByteStringText :: BiMap ByteString Text
- _Array :: BiMap a AnyValue -> BiMap [a] AnyValue
- _Bool :: BiMap Bool AnyValue
- _Double :: BiMap Double AnyValue
- _Integer :: BiMap Integer AnyValue
- _Text :: BiMap Text AnyValue
- _ZonedTime :: BiMap ZonedTime AnyValue
- _LocalTime :: BiMap LocalTime AnyValue
- _Day :: BiMap Day AnyValue
- _TimeOfDay :: BiMap TimeOfDay AnyValue
- _String :: BiMap String AnyValue
- _Read :: (Show a, Read a) => BiMap a AnyValue
- _Natural :: BiMap Natural AnyValue
- _Word :: BiMap Word AnyValue
- _Int :: BiMap Int AnyValue
- _Float :: BiMap Float AnyValue
- _ByteString :: BiMap ByteString AnyValue
- _LByteString :: BiMap ByteString AnyValue
- _Set :: Ord a => BiMap a AnyValue -> BiMap (Set a) AnyValue
- _IntSet :: BiMap IntSet AnyValue
- _HashSet :: (Eq a, Hashable a) => BiMap a AnyValue -> BiMap (HashSet a) AnyValue
- _NonEmpty :: BiMap a AnyValue -> BiMap (NonEmpty a) AnyValue
- _Left :: BiMap (Either l r) l
- _Right :: BiMap (Either l r) r
- _Just :: BiMap (Maybe a) a
- toMArray :: [AnyValue] -> Maybe (Value TArray)
BiMap idea
Partial bidirectional isomorphism. BiMap a b
contains two function:
a -> Maybe b
b -> Maybe a
prism :: (field -> object) -> (object -> Maybe field) -> BiMap object field Source #
Creates BiMap
from prism-like pair of functions.
Helpers for BiMap and AnyValue
mkAnyValueBiMap :: (forall t. Value t -> Maybe a) -> (a -> Value tag) -> BiMap a AnyValue Source #
Creates prism for AnyValue
.
_BoundedInteger :: (Integral a, Bounded a) => BiMap a Integer Source #
Helper bimap for Value
and integral, bounded values.
_ByteStringText :: BiMap ByteString Text Source #
Helper bimap for Value
and strict ByteString
_LByteStringText :: BiMap ByteString Text Source #
Helper bimap for Value
and lazy ByteString
Some predefined bi mappings
_Array :: BiMap a AnyValue -> BiMap [a] AnyValue Source #
Takes a bimap of a value and returns a bimap of a list of values and Anything
as an array. Usually used with arrayOf
combinator.
_ZonedTime :: BiMap ZonedTime AnyValue Source #
Zoned time bimap for AnyValue
. Usually used with zonedTime
combinator.
_LocalTime :: BiMap LocalTime AnyValue Source #
Local time bimap for AnyValue
. Usually used with localTime
combinator.
_TimeOfDay :: BiMap TimeOfDay AnyValue Source #
Time of day bimap for AnyValue
. Usually used with timeOfDay
combinator.
_ByteString :: BiMap ByteString AnyValue Source #
ByteString
bimap for AnyValue
. Usually used with byteString
combinator.
_LByteString :: BiMap ByteString AnyValue Source #
Lazy ByteString
bimap for AnyValue
. Usually used with lazyByteString
combinator.
_Set :: Ord a => BiMap a AnyValue -> BiMap (Set a) AnyValue Source #
Takes a bimap of a value and returns a bimap of a set of values and Anything
as an array. Usually used with setOf
combinator.
_IntSet :: BiMap IntSet AnyValue Source #
Bimap of IntSet
and Anything
as an array. Usually used with
intSet
combinator.
_HashSet :: (Eq a, Hashable a) => BiMap a AnyValue -> BiMap (HashSet a) AnyValue Source #
Takes a bimap of a value and returns a bimap of a has set of values and
Anything
as an array. Usually used with hashSetOf
combinator.
_NonEmpty :: BiMap a AnyValue -> BiMap (NonEmpty a) AnyValue Source #
Takes a bimap of a value and returns a bimap of a non-empty list of values
and Anything
as an array. Usually used with nonEmptyOf
combinator.