Copyright | (c) Eric Mertens 2024 |
---|---|
License | ISC |
Maintainer | emertens@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- class FromValue a where
- mapOf :: Ord k => (l -> Text -> Matcher l k) -> (Text -> Value' l -> Matcher l v) -> Value' l -> Matcher l (Map k v)
- listOf :: (Int -> Value' l -> Matcher l a) -> Value' l -> Matcher l [a]
- data Matcher l a
- runMatcher :: Matcher l a -> Result (MatchMessage l) a
- runMatcherFatalWarn :: Matcher l a -> Either [MatchMessage l] a
- runMatcherIgnoreWarn :: Matcher l a -> Either [MatchMessage l] a
- data Result e a
- data MatchMessage a = MatchMessage {}
- data Scope
- parseTableFromValue :: ParseTable l a -> Value' l -> Matcher l a
- parseTable :: ParseTable l a -> l -> Table' l -> Matcher l a
- getScope :: Matcher a [Scope]
- warn :: String -> Matcher a ()
- warnAt :: l -> String -> Matcher l ()
- failAt :: l -> String -> Matcher l a
- getTable :: ParseTable l (Table' l)
- setTable :: Table' l -> ParseTable l ()
- data ParseTable l a
- reqKey :: FromValue a => Text -> ParseTable l a
- optKey :: FromValue a => Text -> ParseTable l (Maybe a)
- reqKeyOf :: Text -> (Value' l -> Matcher l a) -> ParseTable l a
- optKeyOf :: Text -> (Value' l -> Matcher l a) -> ParseTable l (Maybe a)
- pickKey :: [KeyAlt l a] -> ParseTable l a
- data KeyAlt l a
- warnTable :: String -> ParseTable l ()
- warnTableAt :: l -> String -> ParseTable l ()
- failTableAt :: l -> String -> ParseTable l a
- liftMatcher :: Matcher l a -> ParseTable l a
- class ToValue a where
- toValue :: a -> Value
- toValueList :: [a] -> Value
- class ToValue a => ToTable a where
- table :: [(Text, Value)] -> Table
- (.=) :: ToValue a => Text -> a -> (Text, Value)
- defaultTableToValue :: ToTable a => a -> Value
- type Value = Value' ()
- data Value' a where
- Integer' a Integer
- Double' a Double
- List' a [Value' a]
- Table' a (Table' a)
- Bool' a Bool
- Text' a Text
- TimeOfDay' a TimeOfDay
- ZonedTime' a ZonedTime
- LocalTime' a LocalTime
- Day' a Day
- pattern Bool :: Bool -> Value
- pattern Double :: Double -> Value
- pattern List :: [Value] -> Value
- pattern Integer :: Integer -> Value
- pattern Text :: Text -> Value
- pattern Table :: Table -> Value
- pattern Day :: Day -> Value
- pattern TimeOfDay :: TimeOfDay -> Value
- pattern LocalTime :: LocalTime -> Value
- pattern ZonedTime :: ZonedTime -> Value
- type Table = Table' ()
- newtype Table' a = MkTable (Map Text (a, Value' a))
- newtype GenericTomlArray a = GenericTomlArray a
- newtype GenericTomlTable a = GenericTomlTable a
- genericFromTable :: (Generic a, GParseTable (Rep a)) => Value' l -> Matcher l a
- genericFromArray :: (Generic a, GFromArray (Rep a)) => Value' l -> Matcher l a
- genericToArray :: (Generic a, GToArray (Rep a)) => a -> Value
- genericToTable :: (Generic a, GToTable (Rep a)) => a -> Table
FromValue
class FromValue a where Source #
Class for types that can be decoded from a TOML value.
fromValue :: Value' l -> Matcher l a Source #
Convert a Value
or report an error message
listFromValue :: Value' l -> Matcher l [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 |
FromValue Text Source # | Matches string literals |
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 Table Source # | |
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. |
Integral a => FromValue (Ratio a) Source # | Matches floating-point and integer values. TOML specifies |
FromValue a => FromValue (Seq a) Source # | Matches arrays |
(Generic a, GFromArray (Rep a)) => FromValue (GenericTomlArray a) Source # | Instance derived using |
Defined in Toml.Schema.Generic fromValue :: Value' l -> Matcher l (GenericTomlArray a) Source # listFromValue :: Value' l -> Matcher l [GenericTomlArray a] Source # | |
(Generic a, GParseTable (Rep a)) => FromValue (GenericTomlTable a) Source # | Instance derived using |
Defined in Toml.Schema.Generic fromValue :: Value' l -> Matcher l (GenericTomlTable a) Source # listFromValue :: Value' l -> Matcher l [GenericTomlTable a] Source # | |
FromValue a => FromValue [a] Source # | Implemented in terms of |
(Ord k, FromKey k, FromValue v) => FromValue (Map k v) Source # | |
:: Ord k | |
=> (l -> Text -> Matcher l k) | key matcher |
-> (Text -> Value' l -> Matcher l v) | value matcher |
-> Value' l | |
-> Matcher l (Map k v) |
Table matching function used to help implement fromValue
for tables.
Key matching function is given the annotation of the key for error reporting.
Value matching function is given the key in case values can depend on their keys.
listOf :: (Int -> Value' l -> Matcher l a) -> Value' l -> Matcher l [a] Source #
List matching function used to help implemented fromValue
for arrays.
The element matching function is given the list index in case values can
depend on their index.
Matcher
Computations that result in a Result
and which track a list
of nested contexts to assist in generating warnings and error
messages.
runMatcher :: Matcher l a -> Result (MatchMessage l) a Source #
Run a Matcher
with an empty scope.
runMatcherFatalWarn :: Matcher l a -> Either [MatchMessage l] a Source #
Run Matcher
and treat warnings as errors.
runMatcherIgnoreWarn :: Matcher l a -> Either [MatchMessage l] a Source #
Run Matcher
and ignore warnings.
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.
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 |
data MatchMessage a 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.
For a convenient way to render these to a string, see prettyMatchMessage
.
Instances
Scopes for TOML message.
ScopeIndex Int | zero-based array index |
ScopeKey Text | key in a table |
parseTableFromValue :: ParseTable l a -> Value' l -> Matcher l a Source #
Used to derive a fromValue
implementation from a ParseTable
matcher.
parseTable :: ParseTable l a -> l -> Table' l -> Matcher l 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.
failAt :: l -> String -> Matcher l a Source #
Terminate the match with an error mentioning the given annotation.
getTable :: ParseTable l (Table' l) Source #
Return the remaining portion of the table being matched.
setTable :: Table' l -> ParseTable l () Source #
Replace the remaining portion of the table being matched.
Tables
data ParseTable l a Source #
Parser 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
:: Text | key |
-> (Value' l -> Matcher l a) | value matcher |
-> ParseTable l a |
Match a table entry by key or report an error if missing.
See pickKey
for more complex cases.
:: Text | key |
-> (Value' l -> Matcher l a) | value matcher |
-> ParseTable l (Maybe a) |
pickKey :: [KeyAlt l a] -> ParseTable l 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 Alternative
which will fall-through as a result of any failure to the next case.
Key and value matching function
warnTable :: String -> ParseTable l () Source #
Emit a warning without an annotation.
warnTableAt :: l -> String -> ParseTable l () Source #
Emit a warning with the given annotation.
failTableAt :: l -> String -> ParseTable l a Source #
Abort the current table matching with an error message at the given annotation.
liftMatcher :: Matcher l a -> ParseTable l a Source #
Lift a matcher into the current table parsing context.
ToValue
class ToValue a where Source #
Class for types that can be embedded into Value
toValue :: a -> Value Source #
Embed a single thing into a TOML value.
toValueList :: [a] -> Value Source #
Helper for converting a list of things into a value. This is typically left to be defined by its default implementation and exists to help define the encoding for TOML arrays.
Instances
class ToValue a => ToTable a where Source #
Class for things that can be embedded into a TOML table.
Implement this for things that always embed into a Value'
and then
the ToValue
instance can be derived with defaultTableToValue
.
instance ToValue Example where toValue = defaultTableToValue -- Option 1: Manual instance instance ToTable Example where toTable x =table
["field1".=
field1 x, "field2".=
field2 x] -- Option 2: GHC.Generics derived instance using Toml.ToValue.Generic instance ToTable Example where toTable = genericToTable
defaultTableToValue :: ToTable a => a -> Value Source #
Convenience function for building ToValue
instances.
Types
Semantic TOML value with all table assignments resolved.
Integer' a Integer | |
Double' a Double | |
List' a [Value' a] | |
Table' a (Table' a) | |
Bool' a Bool | |
Text' a Text | |
TimeOfDay' a TimeOfDay | |
ZonedTime' a ZonedTime | |
LocalTime' a LocalTime | |
Day' a Day |
pattern Bool :: Bool -> Value | |
pattern Double :: Double -> Value | |
pattern List :: [Value] -> Value | |
pattern Integer :: Integer -> Value | |
pattern Text :: Text -> Value | |
pattern Table :: Table -> Value | |
pattern Day :: Day -> Value | |
pattern TimeOfDay :: TimeOfDay -> Value | |
pattern LocalTime :: LocalTime -> Value | |
pattern ZonedTime :: ZonedTime -> Value |
Instances
Foldable Value' Source # | Derived |
Defined in Toml.Semantics.Types fold :: Monoid m => Value' m -> m # foldMap :: Monoid m => (a -> m) -> Value' a -> m # foldMap' :: Monoid m => (a -> m) -> Value' a -> m # foldr :: (a -> b -> b) -> b -> Value' a -> b # foldr' :: (a -> b -> b) -> b -> Value' a -> b # foldl :: (b -> a -> b) -> b -> Value' a -> b # foldl' :: (b -> a -> b) -> b -> Value' a -> b # foldr1 :: (a -> a -> a) -> Value' a -> a # foldl1 :: (a -> a -> a) -> Value' a -> a # elem :: Eq a => a -> Value' a -> Bool # maximum :: Ord a => Value' a -> a # minimum :: Ord a => Value' a -> a # | |
Traversable Value' Source # | Derived |
Functor Value' Source # | Derived |
FromValue Value Source # | Matches all values, used for pass-through |
ToValue Value Source # | Identity function |
() ~ a => IsString (Value' a) Source # | Constructs a TOML string literal. fromString = String |
Defined in Toml.Semantics.Types fromString :: String -> Value' a # | |
Read a => Read (Value' a) Source # | Default instance |
Show a => Show (Value' a) Source # | Default instance |
Eq a => Eq (Value' a) Source # | Nearly default instance except |
A table with annotated keys and values.
Instances
Foldable Table' Source # | Derived |
Defined in Toml.Semantics.Types fold :: Monoid m => Table' m -> m # foldMap :: Monoid m => (a -> m) -> Table' a -> m # foldMap' :: Monoid m => (a -> m) -> Table' a -> m # foldr :: (a -> b -> b) -> b -> Table' a -> b # foldr' :: (a -> b -> b) -> b -> Table' a -> b # foldl :: (b -> a -> b) -> b -> Table' a -> b # foldl' :: (b -> a -> b) -> b -> Table' a -> b # foldr1 :: (a -> a -> a) -> Table' a -> a # foldl1 :: (a -> a -> a) -> Table' a -> a # elem :: Eq a => a -> Table' a -> Bool # maximum :: Ord a => Table' a -> a # minimum :: Ord a => Table' a -> a # | |
Traversable Table' Source # | Derived |
Functor Table' Source # | Derived |
FromValue Table Source # | |
Read a => Read (Table' a) Source # | Default instance |
Show a => Show (Table' a) Source # | Default instance |
Eq a => Eq (Table' a) Source # | Default instance |
ToTable (Table' a) Source # | |
ToValue (Table' a) Source # | |
Generics
newtype GenericTomlArray a Source #
Helper type to use GHC's DerivingVia extension to derive
ToValue
, ToTable
, FromValue
for any product type.
Instances
(Generic a, GFromArray (Rep a)) => FromValue (GenericTomlArray a) Source # | Instance derived using |
Defined in Toml.Schema.Generic fromValue :: Value' l -> Matcher l (GenericTomlArray a) Source # listFromValue :: Value' l -> Matcher l [GenericTomlArray a] Source # | |
(Generic a, GToArray (Rep a)) => ToValue (GenericTomlArray a) Source # | Instance derived using |
Defined in Toml.Schema.Generic toValue :: GenericTomlArray a -> Value Source # toValueList :: [GenericTomlArray a] -> Value Source # |
newtype GenericTomlTable a Source #
Instances
(Generic a, GParseTable (Rep a)) => FromValue (GenericTomlTable a) Source # | Instance derived using |
Defined in Toml.Schema.Generic fromValue :: Value' l -> Matcher l (GenericTomlTable a) Source # listFromValue :: Value' l -> Matcher l [GenericTomlTable a] Source # | |
(Generic a, GToTable (Rep a)) => ToTable (GenericTomlTable a) Source # | Instance derived using |
Defined in Toml.Schema.Generic toTable :: GenericTomlTable a -> Table Source # | |
(Generic a, GToTable (Rep a)) => ToValue (GenericTomlTable a) Source # | Instance derived from |
Defined in Toml.Schema.Generic toValue :: GenericTomlTable a -> Value Source # toValueList :: [GenericTomlTable a] -> Value Source # |
genericFromTable :: (Generic a, GParseTable (Rep a)) => Value' l -> Matcher l a Source #
Implementation of fromValue
using genericParseTable
to derive
a match from the record field names of the target type.
genericFromArray :: (Generic a, GFromArray (Rep a)) => Value' l -> Matcher l a Source #
Match a Value'
as an array positionally matching field fields
of a constructor to the elements of the array.