tomland-0.5.0: Bidirectional TOML parser

Safe HaskellNone
LanguageHaskell2010

Toml.Bi.Combinators

Contents

Description

Contains TOML-specific combinators for converting between TOML and user data types.

Synopsis

Toml codecs

bool :: Key -> TomlCodec Bool Source #

Parser for boolean values.

int :: Key -> TomlCodec Int Source #

Parser for integer values.

integer :: Key -> TomlCodec Integer Source #

Parser for integer values.

natural :: Key -> TomlCodec Natural Source #

Parser for natural values.

word :: Key -> TomlCodec Word Source #

Parser for word values.

double :: Key -> TomlCodec Double Source #

Parser for floating point values as double.

float :: Key -> TomlCodec Float Source #

Parser for floating point values as float.

text :: Key -> TomlCodec Text Source #

Parser for string values as text.

read :: (Show a, Read a, Typeable a) => Key -> TomlCodec a Source #

Parser for values with a Read and Show instance.

string :: Key -> TomlCodec String Source #

Parser for string values as string.

byteString :: Key -> TomlCodec ByteString Source #

Parser for byte vectors values as strict bytestring.

lazyByteString :: Key -> TomlCodec ByteString Source #

Parser for byte vectors values as lazy bytestring.

zonedTime :: Key -> TomlCodec ZonedTime Source #

Parser for zoned time values.

localTime :: Key -> TomlCodec LocalTime Source #

Parser for local time values.

day :: Key -> TomlCodec Day Source #

Parser for day values.

timeOfDay :: Key -> TomlCodec TimeOfDay Source #

Parser for time of day values.

arrayOf :: Typeable a => BiMap a AnyValue -> Key -> TomlCodec [a] Source #

Parser for list of values. Takes converter for single value and returns a list of values.

arraySetOf :: (Typeable a, Ord a) => BiMap a AnyValue -> Key -> TomlCodec (Set a) Source #

Parser for sets. Takes converter for single value and returns a set of values.

arrayIntSet :: Key -> TomlCodec IntSet Source #

Parser for sets of ints. Takes converter for single value and returns a set of ints.

arrayHashSetOf :: (Typeable a, Hashable a, Eq a) => BiMap a AnyValue -> Key -> TomlCodec (HashSet a) Source #

Parser for hash sets. Takes converter for single hashable value and returns a set of hashable values.

arrayNonEmptyOf :: Typeable a => BiMap a AnyValue -> Key -> TomlCodec (NonEmpty a) Source #

Parser for non- empty lists of values. Takes converter for single value and returns a non-empty list of values.

Combinators

match :: forall a. Typeable a => BiMap a AnyValue -> Key -> TomlCodec a Source #

General function to create bidirectional converters for values.

table :: forall a. TomlCodec a -> Key -> TomlCodec a Source #

Parser for tables. Use it when when you have nested objects.

wrapper :: forall b a. Coercible a b => (Key -> TomlCodec a) -> Key -> TomlCodec b Source #

Used for newtype wrappers.

mdimap Source #

Arguments

:: (Monad r, Monad w, MonadError DecodeException r) 
=> (c -> d)

Convert from safe to unsafe value

-> (a -> Maybe b)

Parser for more type safe value

-> Codec r w d a

Source Codec object

-> Codec 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.