tomland-0.5.0: Bidirectional TOML parser

Safe HaskellSafe
LanguageHaskell2010

Toml.Bi.Monad

Description

Contains general underlying monad for bidirectional TOML converion.

Synopsis

Documentation

data Codec r w c a Source #

Monad for bidirectional conversion. Contains pair of functions:

  1. How to read value of type a from immutable environment context r?
  2. How to store value of type a in stateful context w?

In practice instead of r we will use some Reader Toml and instead of w we will use State Toml. This approach with the bunch of utility functions allows to have single description for from/to Toml conversion.

In practice this type will always be used in the following way:

type BiCodec r w a = Codec r w a a

Type parameter c if fictional. Here some trick is used. This trick is implemented in codec and described in more details in related blog post.

Constructors

Codec 

Fields

  • codecRead :: r a

    Extract value of type a from monadic context r.

  • codecWrite :: c -> w a

    Store value of type c inside monadic context w and returning value of type a. Type of this function actually should be a -> w () but with such type it's impossible to have Monad and other instances.

Instances
(Monad r, Monad w) => Monad (Codec r w c) Source # 
Instance details

Defined in Toml.Bi.Monad

Methods

(>>=) :: Codec r w c a -> (a -> Codec r w c b) -> Codec r w c b #

(>>) :: Codec r w c a -> Codec r w c b -> Codec r w c b #

return :: a -> Codec r w c a #

fail :: String -> Codec r w c a #

(Functor r, Functor w) => Functor (Codec r w c) Source # 
Instance details

Defined in Toml.Bi.Monad

Methods

fmap :: (a -> b) -> Codec r w c a -> Codec r w c b #

(<$) :: a -> Codec r w c b -> Codec r w c a #

(Applicative r, Applicative w) => Applicative (Codec r w c) Source # 
Instance details

Defined in Toml.Bi.Monad

Methods

pure :: a -> Codec r w c a #

(<*>) :: Codec r w c (a -> b) -> Codec r w c a -> Codec r w c b #

liftA2 :: (a -> b -> c0) -> Codec r w c a -> Codec r w c b -> Codec r w c c0 #

(*>) :: Codec r w c a -> Codec r w c b -> Codec r w c b #

(<*) :: Codec r w c a -> Codec r w c b -> Codec r w c a #

(Alternative r, Alternative w) => Alternative (Codec r w c) Source # 
Instance details

Defined in Toml.Bi.Monad

Methods

empty :: Codec r w c a #

(<|>) :: Codec r w c a -> Codec r w c a -> Codec r w c a #

some :: Codec r w c a -> Codec r w c [a] #

many :: Codec r w c a -> Codec r w c [a] #

(MonadPlus r, MonadPlus w) => MonadPlus (Codec r w c) Source # 
Instance details

Defined in Toml.Bi.Monad

Methods

mzero :: Codec r w c a #

mplus :: Codec r w c a -> Codec r w c a -> Codec r w c a #

type BiCodec r w a = Codec r w a a Source #

Specialized version of Codec data type. This type alias is used in practice.

dimap Source #

Arguments

:: (Functor r, Functor w) 
=> (c -> d)

Mapper for consumer

-> (a -> b)

Mapper for producer

-> Codec r w d a

Source Codec object

-> Codec r w c b 

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
    }

toml bidirectional converter for this type will look like this:

exampleT :: TomlCodec Example
exampleT = Example
    $ bool "foo" .= foo
    * str  "bar" .= bar

Now if you change your time in the following way:

newtype Email = Email { unEmail :: Text }

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

you need to patch your toml parser like this:

exampleT :: TomlCodec Example
exampleT = Example
    $ bool "foo" .= foo
    * dimap unEmail Email (str "bar") .= bar

dioptional :: (Alternative r, Applicative w) => Codec r w c a -> Codec r w (Maybe c) (Maybe a) Source #

Bidirectional converter for Maybe smth values.

(<!>) :: Alternative f => (a -> f x) -> (a -> f x) -> a -> f x infixl 3 Source #

Alternative instance for function arrow but without empty.

(.=) :: Codec r w field a -> (object -> field) -> Codec r w 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 }

foo :: TomlCodec Foo
foo = Foo
 $ int "bar" .= fooBar
 * str "baz" .= fooBaz