tomland-1.0.0: Bidirectional TOML serialization

Safe HaskellNone
LanguageHaskell2010

Toml.Bi.Map

Contents

Description

Implementation of tagged partial bidirectional isomorphism.

Synopsis

BiMap idea

data BiMap e a b Source #

Partial bidirectional isomorphism. BiMap a b contains two function:

  1. a -> Either e b
  2. b -> Either e a

If you think of types as sets then this data type can be illustrated by the following picture:

BiMap also implements Category typeclass. And this instance can be described clearly by this illustration:

Constructors

BiMap 

Fields

Instances
Category (BiMap e :: Type -> Type -> Type) Source # 
Instance details

Defined in Toml.Bi.Map

Methods

id :: BiMap e a a #

(.) :: BiMap e b c -> BiMap e a b -> BiMap e a c #

type TomlBiMap = BiMap TomlBiMapError Source #

BiMap specialized to TOML error.

invert :: BiMap e a b -> BiMap e b a Source #

Inverts bidirectional mapping.

iso :: (a -> b) -> (b -> a) -> BiMap e a b Source #

Creates BiMap from isomorphism. Can be used in the following way:

newtype Even = Even Integer
newtype Odd  = Odd  Integer

succEven :: Even -> Odd
succEven (Even n) = Odd (n + 1)

predOdd :: Odd -> Even
predOdd (Odd n) = Even (n - 1)

_EvenOdd :: BiMap e Even Odd
_EvenOdd = iso succEven predOdd

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 Left but bidirectional converter expects Right.

Fields

  • Text

    Expected constructor name

  • Text

    Actual value

WrongValue

Error for cases with wrong values

Fields

ArbitraryError

Arbitrary textual error

Fields

wrongConstructor Source #

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.

_TextBy Source #

Arguments

:: (a -> Text)

show function for a

-> (Text -> Either Text a)

Parser of a from Text

-> TomlBiMap a AnyValue 

Creates bimap for Text to AnyValue with custom functions

_LTextText :: BiMap e Text Text Source #

Helper bimap for Text and Text.

_StringText :: BiMap e String Text Source #

Helper bimap for String and Text.

_ReadString :: (Show a, Read a) => TomlBiMap a String Source #

Helper bimap for String and types with Read and Show instances.

_BoundedInteger :: (Integral a, Bounded a, Show a) => TomlBiMap a Integer Source #

Helper bimap for Integer and integral, bounded values.

Some predefined bi mappings

_Array :: forall a. TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue Source #

Takes a bimap of a value and returns a bimap between a list of values and AnyValue as an array. Usually used as arrayOf combinator.

_Bool :: TomlBiMap Bool AnyValue Source #

Bool bimap for AnyValue. Usually used as bool combinator.

_Double :: TomlBiMap Double AnyValue Source #

Double bimap for AnyValue. Usually used as double combinator.

_Integer :: TomlBiMap Integer AnyValue Source #

Integer bimap for AnyValue. Usually used as integer combinator.

_Text :: TomlBiMap Text AnyValue Source #

Text bimap for AnyValue. Usually used as text combinator.

_LText :: TomlBiMap Text AnyValue Source #

Text bimap for AnyValue. Usually used as lazyText combinator.

_ZonedTime :: TomlBiMap ZonedTime AnyValue Source #

ZonedTime bimap for AnyValue. Usually used as zonedTime combinator.

_LocalTime :: TomlBiMap LocalTime AnyValue Source #

LocalTime bimap for AnyValue. Usually used as localTime combinator.

_Day :: TomlBiMap Day AnyValue Source #

Day bimap for AnyValue. Usually used as day combinator.

_TimeOfDay :: TomlBiMap TimeOfDay AnyValue Source #

TimeOfDay bimap for AnyValue. Usually used as timeOfDay combinator.

_String :: TomlBiMap String AnyValue Source #

String bimap for AnyValue. Usually used as string combinator.

_Read :: (Show a, Read a) => TomlBiMap a AnyValue Source #

Bimap for AnyValue and values with a Read and Show instance. Usually used as read combinator.

_Natural :: TomlBiMap Natural AnyValue Source #

String bimap for AnyValue. Usually used as natural combinator.

_Word :: TomlBiMap Word AnyValue Source #

Word bimap for AnyValue. Usually used as word combinator.

_Int :: TomlBiMap Int AnyValue Source #

Int bimap for AnyValue. Usually used as int combinator.

_Float :: TomlBiMap Float AnyValue Source #

Float bimap for AnyValue. Usually used as float combinator.

_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.

_NonEmpty :: TomlBiMap a AnyValue -> TomlBiMap (NonEmpty a) AnyValue Source #

Takes a bimap of a value and returns a bimap between a non-empty list of values and AnyValue as an array. Usually used as nonEmpty combinator.

_Left :: (Show l, Show r) => TomlBiMap (Either l r) l Source #

Bimap for Either and its left type

_Right :: (Show l, Show r) => TomlBiMap (Either l r) r Source #

Bimap for Either and its right type

_Just :: Show r => TomlBiMap (Maybe r) r Source #

Bimap for Maybe

Useful utility functions

toMArray :: [AnyValue] -> Either MatchError (Value TArray) Source #

Function for creating Array from list of AnyValue.