| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Toml.Bi.Monad
Description
Contains general underlying monad for bidirectional conversion.
Synopsis
- data Codec r w c a = Codec {
- codecRead :: r a
- codecWrite :: c -> w a
- type BiCodec r w a = Codec r w a a
- dimap :: (Functor r, Functor w) => (c -> d) -> (a -> b) -> Codec r w d a -> Codec r w c b
- dioptional :: (Alternative r, Applicative w) => Codec r w c a -> Codec r w (Maybe c) (Maybe a)
- diwrap :: forall b a r w. (Coercible a b, Functor r, Functor w) => BiCodec r w a -> BiCodec r w b
- (<!>) :: Alternative f => (a -> f x) -> (a -> f x) -> a -> f x
- (.=) :: Codec r w field a -> (object -> field) -> Codec r w object a
Documentation
Monad for bidirectional conversion. Contains pair of functions:
- How to read value of type
afrom immutable environment contextr? - How to store value of type
ain stateful contextw?
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:
typeBiCodecr w a =Codecr w a a
Type parameter c if fictional. Here some trick is used. This trick is
implemented in the codec package and
described in more details in related blog post:
https://blog.poisson.chat/posts/2016-10-12-bidirectional-serialization.html.
Constructors
| Codec | |
Fields
| |
Instances
| (Monad r, Monad w) => Monad (Codec r w c) Source # | |
| (Functor r, Functor w) => Functor (Codec r w c) Source # | |
| (Applicative r, Applicative w) => Applicative (Codec r w c) Source # | |
Defined in Toml.Bi.Monad | |
| (Alternative r, Alternative w) => Alternative (Codec r w c) Source # | |
| (MonadPlus r, MonadPlus w) => MonadPlus (Codec r w c) Source # | |
type BiCodec r w a = Codec r w a a Source #
Specialized version of Codec data type. This type alias is used in practice.
Arguments
| :: (Functor r, Functor w) | |
| => (c -> d) | Mapper for consumer |
| -> (a -> b) | Mapper for producer |
| -> Codec r w d a | Source |
| -> Codec r w c b | Target |
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
dioptional :: (Alternative r, Applicative w) => Codec r w c a -> Codec r w (Maybe c) (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
diwrap :: forall b a r w. (Coercible a b, Functor r, Functor w) => BiCodec r w a -> BiCodec r w b Source #
(<!>) :: Alternative f => (a -> f x) -> (a -> f x) -> a -> f x infixl 3 Source #
Alternative instance for function arrow but without empty.