Copyright | (c) Eric Mertens 2023 |
---|---|
License | ISC |
Maintainer | emertens@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module extracts a nested Map representation of a TOML file. It detects invalid key assignments and resolves dotted key assignments.
Synopsis
- 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))
- semantics :: [Expr a] -> Either (SemanticError a) (Table' a)
- data SemanticError a = SemanticError {
- errorAnn :: a
- errorKey :: Text
- errorKind :: SemanticErrorKind
- data SemanticErrorKind
- forgetTableAnns :: Table' a -> Table
- forgetValueAnns :: Value' a -> Value
- valueAnn :: Value' a -> a
- valueType :: Value' l -> String
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 # | |
Validation
semantics :: [Expr a] -> Either (SemanticError a) (Table' a) Source #
Extracts a semantic value from a sequence of raw TOML expressions, or reports a semantic error if one occurs.
data SemanticError a Source #
This type represents errors generated when resolving keys in a TOML document.
Since: 1.3.0.0
SemanticError | |
|
Instances
data SemanticErrorKind Source #
Enumeration of the kinds of conflicts a key can generate.
Since: 1.3.0.0
AlreadyAssigned | Attempted to assign to a key that was already assigned |
ClosedTable | Attempted to open a table already closed |
ImplicitlyTable | Attempted to open a tables as an array of tables that was implicitly defined to be a table |
Instances
Read SemanticErrorKind Source # | Default instance |
Defined in Toml.Semantics | |
Show SemanticErrorKind Source # | Default instance |
Defined in Toml.Semantics showsPrec :: Int -> SemanticErrorKind -> ShowS # show :: SemanticErrorKind -> String # showList :: [SemanticErrorKind] -> ShowS # | |
Eq SemanticErrorKind Source # | Default instance |
Defined in Toml.Semantics (==) :: SemanticErrorKind -> SemanticErrorKind -> Bool # (/=) :: SemanticErrorKind -> SemanticErrorKind -> Bool # | |
Ord SemanticErrorKind Source # | Default instance |
Defined in Toml.Semantics compare :: SemanticErrorKind -> SemanticErrorKind -> Ordering # (<) :: SemanticErrorKind -> SemanticErrorKind -> Bool # (<=) :: SemanticErrorKind -> SemanticErrorKind -> Bool # (>) :: SemanticErrorKind -> SemanticErrorKind -> Bool # (>=) :: SemanticErrorKind -> SemanticErrorKind -> Bool # max :: SemanticErrorKind -> SemanticErrorKind -> SemanticErrorKind # min :: SemanticErrorKind -> SemanticErrorKind -> SemanticErrorKind # |
Annotations
forgetTableAnns :: Table' a -> Table Source #
Replaces annotations with a unit.
forgetValueAnns :: Value' a -> Value Source #
Replaces annotations with a unit.