| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Toml.Bi.Map
Contents
Description
Implementation of tagged partial bidirectional isomorphism.
Synopsis
- data BiMap e a b = BiMap {}
- type TomlBiMap = BiMap TomlBiMapError
- invert :: BiMap e a b -> BiMap e b a
- iso :: (a -> b) -> (b -> a) -> BiMap e a b
- prism :: (field -> object) -> (object -> Either error field) -> BiMap error object field
- data TomlBiMapError
- wrongConstructor :: Show a => Text -> a -> Either TomlBiMapError b
- prettyBiMapError :: TomlBiMapError -> Text
- mkAnyValueBiMap :: forall a (tag :: TValue). (forall (t :: TValue). Value t -> Either MatchError a) -> (a -> Value tag) -> TomlBiMap a AnyValue
- _TextBy :: forall a. (a -> Text) -> (Text -> Either Text a) -> TomlBiMap a AnyValue
- _LTextText :: BiMap e Text Text
- _NaturalInteger :: TomlBiMap Natural Integer
- _StringText :: BiMap e String Text
- _ReadString :: (Show a, Read a) => TomlBiMap a String
- _BoundedInteger :: (Integral a, Bounded a, Show a) => TomlBiMap a Integer
- _ByteStringText :: TomlBiMap ByteString Text
- _LByteStringText :: TomlBiMap ByteString Text
- _Array :: forall a. TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
- _Bool :: TomlBiMap Bool AnyValue
- _Double :: TomlBiMap Double AnyValue
- _Integer :: TomlBiMap Integer AnyValue
- _Text :: TomlBiMap Text AnyValue
- _LText :: TomlBiMap Text AnyValue
- _ZonedTime :: TomlBiMap ZonedTime AnyValue
- _LocalTime :: TomlBiMap LocalTime AnyValue
- _Day :: TomlBiMap Day AnyValue
- _TimeOfDay :: TomlBiMap TimeOfDay AnyValue
- _String :: TomlBiMap String AnyValue
- _Read :: (Show a, Read a) => TomlBiMap a AnyValue
- _Natural :: TomlBiMap Natural AnyValue
- _Word :: TomlBiMap Word AnyValue
- _Int :: TomlBiMap Int AnyValue
- _Float :: TomlBiMap Float AnyValue
- _ByteString :: TomlBiMap ByteString AnyValue
- _LByteString :: TomlBiMap ByteString AnyValue
- _Set :: Ord a => TomlBiMap a AnyValue -> TomlBiMap (Set a) AnyValue
- _IntSet :: TomlBiMap IntSet AnyValue
- _HashSet :: (Eq a, Hashable a) => TomlBiMap a AnyValue -> TomlBiMap (HashSet a) AnyValue
- _NonEmpty :: TomlBiMap a AnyValue -> TomlBiMap (NonEmpty a) AnyValue
- _Left :: (Show l, Show r) => TomlBiMap (Either l r) l
- _Right :: (Show l, Show r) => TomlBiMap (Either l r) r
- _Just :: Show r => TomlBiMap (Maybe r) r
- toMArray :: [AnyValue] -> Either MatchError (Value TArray)
BiMap idea
prism :: (field -> object) -> (object -> Either error field) -> BiMap error object field Source #
Creates BiMap from prism-like pair of functions. This combinator can be
used to create BiMap for custom data types like this:
data User
= Admin Integer -- id of admin
| Client Text -- name of the client
deriving (Show)
_Admin :: TomlBiMap User Integer
_Admin = Toml.prism Admin $ \case
Admin i -> Right i
other -> Toml.wrongConstructor "Admin" other
_Client :: TomlBiMap User Text
_Client = Toml.prism Client $ \case
Client n -> Right n
other -> Toml.wrongConstructor "Client" other
BiMap errors for TOML
data TomlBiMapError Source #
Type of errors for TOML BiMap.
Constructors
| WrongConstructor | Error for cases with wrong constructors. For
example, you're trying to convert |
| WrongValue | Error for cases with wrong values |
Fields
| |
| ArbitraryError | Arbitrary textual error |
Fields
| |
Instances
Arguments
| :: Show a | |
| => Text | Name of the expected constructor |
| -> a | Actual value |
| -> Either TomlBiMapError b |
Helper to construct WrongConstuctor error.
prettyBiMapError :: TomlBiMapError -> Text Source #
Converts TomlBiMapError into pretty human-readable text.
Helpers for BiMap and AnyValue
mkAnyValueBiMap :: forall a (tag :: TValue). (forall (t :: TValue). Value t -> Either MatchError a) -> (a -> Value tag) -> TomlBiMap a AnyValue Source #
Creates prism for AnyValue.
_BoundedInteger :: (Integral a, Bounded a, Show a) => TomlBiMap a Integer Source #
Helper bimap for Integer and integral, bounded values.
_ByteStringText :: TomlBiMap ByteString Text Source #
Helper bimap for Text and strict ByteString
_LByteStringText :: TomlBiMap ByteString Text Source #
Helper bimap for Text and lazy ByteString.
Some predefined bi mappings
_ByteString :: TomlBiMap ByteString AnyValue Source #
UTF8 encoded ByteString bimap for AnyValue.
Usually used as byteString combinator.
_LByteString :: TomlBiMap ByteString AnyValue Source #
UTF8 encoded lazy ByteString bimap for AnyValue.
Usually used as lazyByteString combinator.
_Set :: Ord a => TomlBiMap a AnyValue -> TomlBiMap (Set a) AnyValue Source #
Takes a bimap of a value and returns a bimap between a set of values and AnyValue
as an array. Usually used as arraySetOf combinator.
_IntSet :: TomlBiMap IntSet AnyValue Source #
IntSet bimap for AnyValue. Usually used as
arrayIntSetOf combinator.
_HashSet :: (Eq a, Hashable a) => TomlBiMap a AnyValue -> TomlBiMap (HashSet a) AnyValue Source #
Takes a bimap of a value and returns a bimap between a hash set of values and AnyValue
as an array. Usually used as arrayHashSetOf combinator.

