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

Toml.Codec.Di

Description

Forward and backward mapping functions and combinators (similar to profunctors).

Since: 1.3.0.0

Synopsis

Documentation

dimap Source #

Arguments

:: (b -> a)

Mapper for consumer

-> (a -> b)

Mapper for producer

-> TomlCodec a

Source Codec object

-> TomlCodec b

Target Codec object

This is an instance of Profunctor for Codec. But since there's no Profunctor type class in base or package with no dependencies (and we don't want to bring extra dependencies) this instance is implemented as a single top-level function.

Useful when you want to parse newtypes. For example, if you had data type like this:

data Example = Example
    { foo :: Bool
    , bar :: Text
    }

Bidirectional TOML converter for this type will look like this:

exampleCodec :: TomlCodec Example
exampleCodec = Example
    <$> Toml.bool "foo" .= foo
    <*> Toml.text "bar" .= bar

Now if you change your type in the following way:

newtype Email = Email { unEmail :: Text }

data Example = Example
    { foo :: Bool
    , bar :: Email
    }

you need to patch your TOML codec like this:

exampleCodec :: TomlCodec Example
exampleCodec = Example
    <$> Toml.bool "foo" .= foo
    <*> dimap unEmail Email (Toml.text "bar") .= bar

Since: 0.2.0

dioptional :: TomlCodec a -> TomlCodec (Maybe a) Source #

Bidirectional converter for Maybe a values. For example, given the data type:

data Example = Example
    { foo :: Bool
    , bar :: Maybe Int
    }

the TOML codec will look like

exampleCodec :: TomlCodec Example
exampleCodec = Example
    <$> Toml.bool "foo" .= foo
    <*> dioptional (Toml.int "bar") .= bar

Since: 0.5.0

diwrap :: forall b a. Coercible a b => TomlCodec a -> TomlCodec b Source #

Combinator used for newtype wrappers. For example, given the data types:

newtype N = N Int

data Example = Example
    { foo :: Bool
    , bar :: N
    }

the TOML codec can look like

exampleCodec :: TomlCodec Example
exampleCodec = Example
    <$> Toml.bool "foo" .= foo
    <*> diwrap (Toml.int "bar") .= bar

Since: 1.0.0

dimatch Source #

Arguments

:: (b -> Maybe a)

Mapper for consumer

-> (a -> b)

Mapper for producer

-> TomlCodec a

Source Codec object

-> TomlCodec b

Target Codec object

Bidirectional converter for sum types. For example, given the data type:

data Example
    = Foo Int
    | Bar Bool Int

the TOML codec will look like

matchFoo :: Example -> Maybe Int
matchFoo (Foo num) = Just num
matchFoo _         = Nothing

matchBar :: Example -> Maybe (Bool, Int)
matchBar (Bar b num) = Just (b, num)
matchBar _           = Nothing

barCodec :: TomlCodec (Bool, Int)
barCodec = Toml.pair
    (Toml.bool "a")
    (Toml.int "b")

exampleCodec :: TomlCodec Example
exampleCodec =
    dimatch matchFoo Foo (Toml.int "foo")
    <|> dimatch matchBar (uncurry Bar) (Toml.table barCodec "bar")

Since: 1.2.0.0

(.=) :: Codec field a -> (object -> field) -> Codec object a infixl 5 Source #

Operator to connect two operations:

  1. How to get field from object?
  2. How to write this field to toml?

In code this should be used like this:

data Foo = Foo
    { fooBar :: Int
    , fooBaz :: String
    }

fooCodec :: TomlCodec Foo
fooCodec = Foo
    <$> Toml.int "bar" .= fooBar
    <*> Toml.str "baz" .= fooBaz