Safe Haskell | None |
---|---|
Language | Haskell2010 |
Contains TOML-specific combinators for converting between TOML and user data types.
- type BiToml a = Bi Env St a
- type Env = ExceptT DecodeException (Reader TOML)
- type St = State TOML
- data DecodeException
- decode :: BiToml a -> Text -> Either DecodeException a
- encode :: BiToml a -> a -> Text
- bijectionMaker :: forall a t. Text -> (forall f. Value f -> Maybe a) -> (a -> Value t) -> Key -> BiToml a
- dimapNum :: forall n r w. (Integral n, Functor r, Functor w) => Bi r w Integer -> Bi r w n
- mdimap :: (Monad r, Monad w, MonadError DecodeException r) => (c -> d) -> (a -> Maybe b) -> Bijection r w d a -> Bijection r w c b
- bool :: Key -> BiToml Bool
- int :: Key -> BiToml Int
- integer :: Key -> BiToml Integer
- double :: Key -> BiToml Double
- str :: Key -> BiToml Text
- arrayOf :: forall a t. Valuer t a -> Key -> BiToml [a]
- maybeP :: forall a. (Key -> BiToml a) -> Key -> BiToml (Maybe a)
- table :: forall a. BiToml a -> Key -> BiToml a
- data Valuer (tag :: ValueType) a = Valuer {}
- boolV :: Valuer TBool Bool
- integerV :: Valuer TInt Integer
- doubleV :: Valuer TFloat Double
- strV :: Valuer TString Text
- arrV :: forall a t. Valuer t a -> Valuer TArray [a]
Types
type Env = ExceptT DecodeException (Reader TOML) Source #
Immutable environment for Toml
conversion.
This is r
type variable in Bijection
data type.
Mutable context for Toml
conversion.
This is w
type variable in Bijection
data type.
Exceptions
data DecodeException Source #
Type of exception for converting from Toml
to user custom data type.
Encode/Decode
decode :: BiToml a -> Text -> Either DecodeException a Source #
Convert textual representation of toml into user data type.
Converters
:: Text | Name of expected type |
-> (forall f. Value f -> Maybe a) | How to convert from |
-> (a -> Value t) | Convert |
-> Key | Key of the value |
-> BiToml a |
General function to create bidirectional converters for values.
:: (Monad r, Monad w, MonadError DecodeException r) | |
=> (c -> d) | Convert from safe to unsafe value |
-> (a -> Maybe b) | Parser for more type safe value |
-> Bijection r w d a | Source |
-> Bijection r w c b |
Almost same as dimap
. Useful when you want to have fields like this
inside your configuration:
data GhcVer = Ghc7103 | Ghc802 | Ghc822 | Ghc842 showGhcVer :: GhcVer -> Text parseGhcVer :: Text -> Maybe GhcVer
When you specify couple of functions of the following types:
show :: a -> Text parse :: Text -> Maybe a
they should satisfy property parse . show == Just
if you want to use your
converter for pretty-printing.
Toml parsers
arrayOf :: forall a t. Valuer t a -> Key -> BiToml [a] Source #
Parser for array of values. Takes converter for single array element and returns list of values.
maybeP :: forall a. (Key -> BiToml a) -> Key -> BiToml (Maybe a) Source #
Bidirectional converter for Maybe smth
values.
table :: forall a. BiToml a -> Key -> BiToml a Source #
Parser for tables. Use it when when you have nested objects.