Safe Haskell | None |
---|---|
Language | Haskell2010 |
Contains TOML-specific combinators for converting between TOML and user data types.
Synopsis
- bool :: Key -> TomlCodec Bool
- int :: Key -> TomlCodec Int
- integer :: Key -> TomlCodec Integer
- natural :: Key -> TomlCodec Natural
- word :: Key -> TomlCodec Word
- double :: Key -> TomlCodec Double
- float :: Key -> TomlCodec Float
- text :: Key -> TomlCodec Text
- read :: (Show a, Read a, Typeable a) => Key -> TomlCodec a
- string :: Key -> TomlCodec String
- byteString :: Key -> TomlCodec ByteString
- lazyByteString :: Key -> TomlCodec ByteString
- zonedTime :: Key -> TomlCodec ZonedTime
- localTime :: Key -> TomlCodec LocalTime
- day :: Key -> TomlCodec Day
- timeOfDay :: Key -> TomlCodec TimeOfDay
- arrayOf :: Typeable a => BiMap a AnyValue -> Key -> TomlCodec [a]
- arraySetOf :: (Typeable a, Ord a) => BiMap a AnyValue -> Key -> TomlCodec (Set a)
- arrayIntSet :: Key -> TomlCodec IntSet
- arrayHashSetOf :: (Typeable a, Hashable a, Eq a) => BiMap a AnyValue -> Key -> TomlCodec (HashSet a)
- arrayNonEmptyOf :: Typeable a => BiMap a AnyValue -> Key -> TomlCodec (NonEmpty a)
- match :: forall a. Typeable a => BiMap a AnyValue -> Key -> TomlCodec a
- table :: forall a. TomlCodec a -> Key -> TomlCodec a
- wrapper :: forall b a. Coercible a b => (Key -> TomlCodec a) -> Key -> TomlCodec b
- mdimap :: (Monad r, Monad w, MonadError DecodeException r) => (c -> d) -> (a -> Maybe b) -> Codec r w d a -> Codec r w c b
Toml codecs
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.
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.
:: (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 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.