tomland-1.3.3.0: Bidirectional TOML serialization
Copyright(c) 2018-2021 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Toml.Codec.BiMap

Description

Implementation of Tagged Partial Bidirectional Isomorphism. This module contains the BiMap type that represents conversion between two types with the possibility of failure.

See Toml.Codec.BiMap.Conversion for examples of BiMap with specific types. The BiMap concept is general and is not specific to TOML, but in this package most usages of BiMap are between TOML values and Haskell values.

Synopsis

BiMap concept

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:

Since: 0.4.0

Constructors

BiMap 

Fields

Instances

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

Since: 0.4.0

Instance details

Defined in Toml.Codec.BiMap

Methods

id :: forall (a :: k). BiMap e a a #

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

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

Inverts bidirectional mapping.

Since: 0.4.0

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

Since: 0.4.0

prism Source #

Arguments

:: (field -> object)

Constructor

-> (object -> Either error field)

Match object to either error or field

-> BiMap error object field 

Creates BiMap from prism-like pair of functions. This combinator can be used to create BiMap for custom sum 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

Since: 0.4.0

TOML BiMap

Type

type TomlBiMap = BiMap TomlBiMapError Source #

BiMap specialized to TOML error.

Since: 1.0.0

Error

data TomlBiMapError Source #

Type of errors for TOML BiMap.

Since: 1.0.0

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

Instances

Instances details
Eq TomlBiMapError Source # 
Instance details

Defined in Toml.Codec.BiMap

Show TomlBiMapError Source # 
Instance details

Defined in Toml.Codec.BiMap

Generic TomlBiMapError Source # 
Instance details

Defined in Toml.Codec.BiMap

Associated Types

type Rep TomlBiMapError :: Type -> Type #

NFData TomlBiMapError Source # 
Instance details

Defined in Toml.Codec.BiMap

Methods

rnf :: TomlBiMapError -> () #

type Rep TomlBiMapError Source # 
Instance details

Defined in Toml.Codec.BiMap

wrongConstructor Source #

Arguments

:: Show a 
=> Text

Name of the expected constructor

-> a

Actual value

-> Either TomlBiMapError b 

Helper to construct WrongConstuctor error.

Since: 1.0.0

prettyBiMapError :: TomlBiMapError -> Text Source #

Converts TomlBiMapError into pretty human-readable text.

Since: 1.0.0

Smart constructors

mkAnyValueBiMap Source #

Arguments

:: forall a (tag :: TValue). (forall (t :: TValue). Value t -> Either MatchError a)

Haskell type exctractor from Value

-> (a -> Value tag)

Convert Haskell type back to Value

-> TomlBiMap a AnyValue 

Smart constructor for BiMap from a Haskell value (some primitive like Int or Text) to AnyValue.

Since: 0.4.0

Internals

tShow :: Show a => a -> Text Source #