Copyright | (c) Eric Mertens 2023 |
---|---|
License | ISC |
Maintainer | emertens@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Use FromValue
to define a transformation from some Value
to an application
domain type.
Use ParseTable
to help build FromValue
instances that match tables. It
will make it easy to track which table keys have been used and which are left
over.
Warnings can be emitted using warning
and warnTable
(depending on what)
context you're in. These warnings can provide useful feedback about
problematic decodings or keys that might be unused now but were perhaps
meaningful in an old version of a configuration file.
Toml.FromValue.Generic can be used to derive instances of FromValue
automatically for record types.
Synopsis
- class FromValue a where
- class FromKey a where
- data Matcher a
- data MatchMessage = MatchMessage {
- matchPath :: [Scope]
- matchMessage :: String
- data Result e a
- warning :: String -> Matcher ()
- data ParseTable a
- runParseTable :: ParseTable a -> Table -> Matcher a
- parseTableFromValue :: ParseTable a -> Value -> Matcher a
- reqKey :: FromValue a => String -> ParseTable a
- optKey :: FromValue a => String -> ParseTable (Maybe a)
- reqKeyOf :: String -> (Value -> Matcher a) -> ParseTable a
- optKeyOf :: String -> (Value -> Matcher a) -> ParseTable (Maybe a)
- warnTable :: String -> ParseTable ()
- data KeyAlt a
- pickKey :: [KeyAlt a] -> ParseTable a
- getTable :: ParseTable Table
- setTable :: Table -> ParseTable ()
- liftMatcher :: Matcher a -> ParseTable a
Deserialization classes
class FromValue a where Source #
Class for types that can be decoded from a TOML value.
fromValue :: Value -> Matcher a Source #
Convert a Value
or report an error message
listFromValue :: Value -> Matcher [a] Source #
Used to implement instance for '[]'. Most implementations rely on the default implementation.
Instances
FromValue Int16 Source # | |
FromValue Int32 Source # | |
FromValue Int64 Source # | |
FromValue Int8 Source # | |
FromValue Word16 Source # | |
FromValue Word32 Source # | |
FromValue Word64 Source # | |
FromValue Word8 Source # | |
FromValue Text Source # | Matches string literals Since: 1.2.1.0 |
FromValue Text Source # | Matches string literals Since: 1.2.1.0 |
FromValue Day Source # | Matches local date literals |
FromValue LocalTime Source # | Matches local date-time literals |
FromValue TimeOfDay Source # | Matches local time literals |
FromValue ZonedTime Source # | Matches offset date-time literals |
FromValue Value Source # | Matches all values, used for pass-through |
FromValue Integer Source # | Matches integer values |
FromValue Natural Source # | Matches non-negative integer values |
FromValue Bool Source # | Matches |
FromValue Char Source # | Matches single-character strings with |
FromValue Double Source # | Matches floating-point and integer values |
FromValue Float Source # | Matches floating-point and integer values |
FromValue Int Source # | |
FromValue Word Source # | |
FromValue a => FromValue (NonEmpty a) Source # | Matches non-empty arrays or reports an error. Since: 1.3.0.0 |
Integral a => FromValue (Ratio a) Source # | Matches floating-point and integer values. TOML specifies Since: 1.3.0.0 |
FromValue a => FromValue (Seq a) Source # | Matches arrays Since: 1.3.0.0 |
(Generic a, GFromArray (Rep a)) => FromValue (GenericTomlArray a) Source # | Instance derived using |
Defined in Toml.Generic fromValue :: Value -> Matcher (GenericTomlArray a) Source # listFromValue :: Value -> Matcher [GenericTomlArray a] Source # | |
(Generic a, GParseTable (Rep a)) => FromValue (GenericTomlTable a) Source # | Instance derived using |
Defined in Toml.Generic fromValue :: Value -> Matcher (GenericTomlTable a) Source # listFromValue :: Value -> Matcher [GenericTomlTable a] Source # | |
FromValue a => FromValue [a] Source # | Implemented in terms of |
(Ord k, FromKey k, FromValue v) => FromValue (Map k v) Source # | |
class FromKey a where Source #
Convert from a table key
Since: 1.3.0.0
Matcher
Computations that result in a Result
and which track a list
of nested contexts to assist in generating warnings and error
messages.
data MatchMessage Source #
A message emitted while matching a TOML value. The message is paired with the path to the value that was in focus when the message was generated. These message get used for both warnings and errors.
Since: 1.3.0.0
MatchMessage | |
|
Instances
Read MatchMessage Source # | Default instance |
Defined in Toml.FromValue.Matcher readsPrec :: Int -> ReadS MatchMessage # readList :: ReadS [MatchMessage] # | |
Show MatchMessage Source # | Default instance |
Defined in Toml.FromValue.Matcher showsPrec :: Int -> MatchMessage -> ShowS # show :: MatchMessage -> String # showList :: [MatchMessage] -> ShowS # | |
Eq MatchMessage Source # | Default instance |
Defined in Toml.FromValue.Matcher (==) :: MatchMessage -> MatchMessage -> Bool # (/=) :: MatchMessage -> MatchMessage -> Bool # | |
Ord MatchMessage Source # | Default instance |
Defined in Toml.FromValue.Matcher compare :: MatchMessage -> MatchMessage -> Ordering # (<) :: MatchMessage -> MatchMessage -> Bool # (<=) :: MatchMessage -> MatchMessage -> Bool # (>) :: MatchMessage -> MatchMessage -> Bool # (>=) :: MatchMessage -> MatchMessage -> Bool # max :: MatchMessage -> MatchMessage -> MatchMessage # min :: MatchMessage -> MatchMessage -> MatchMessage # |
Computation outcome with error and warning messages. Multiple error messages can occur when multiple alternatives all fail. Resolving any one of the error messages could allow the computation to succeed.
Since: 1.3.0.0
Instances
(Read e, Read a) => Read (Result e a) Source # | Default instance |
(Show e, Show a) => Show (Result e a) Source # | Default instance |
(Eq e, Eq a) => Eq (Result e a) Source # | Default instance |
(Ord e, Ord a) => Ord (Result e a) Source # | Default instance |
Table matching
data ParseTable a Source #
A Matcher
that tracks a current set of unmatched key-value
pairs from a table.
Use optKey
and reqKey
to extract keys.
Use getTable
and setTable
to override the table and implement
other primitives.
Instances
runParseTable :: ParseTable a -> Table -> Matcher a Source #
Run a ParseTable
computation with a given starting Table
.
Unused tables will generate a warning. To change this behavior
getTable
and setTable
can be used to discard or generate
error messages.
parseTableFromValue :: ParseTable a -> Value -> Matcher a Source #
Used to derive a fromValue
implementation from a ParseTable
matcher.
:: String | key |
-> (Value -> Matcher a) | value matcher |
-> ParseTable a |
Match a table entry by key or report an error if missing.
See pickKey
for more complex cases.
:: String | key |
-> (Value -> Matcher a) | value matcher |
-> ParseTable (Maybe a) |
warnTable :: String -> ParseTable () Source #
Emit a warning at the current location.
Key and value matching function
Since: 1.2.0.0
pickKey :: [KeyAlt a] -> ParseTable a Source #
Take the first option from a list of table keys and matcher functions. This operation will commit to the first table key that matches. If the associated matcher fails, only that error will be propagated and the other alternatives will not be matched.
If no keys match, an error message is generated explaining which keys would have been accepted.
This is provided as an alternative to chaining multiple
reqKey
cases together with (
because that will
generate one error message for each unmatched alternative as well as
the error associate with the matched alternative.<|>
)
Since: 1.2.0.0
Table matching primitives
getTable :: ParseTable Table Source #
Return the remaining portion of the table being matched.
setTable :: Table -> ParseTable () Source #
Replace the remaining portion of the table being matched.
liftMatcher :: Matcher a -> ParseTable a Source #
Lift a matcher into the current table parsing context.