Copyright | (c) Eric Mertens 2023 |
---|---|
License | ISC |
Maintainer | emertens@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This is the high-level interface to the toml-parser library. It enables parsing, printing, and conversion into and out of application-specific representations.
This parser implements TOML 1.0.0 https://toml.io/en/v1.0.0 as carefully as possible.
Use Toml.Schema to implement functions mapping between TOML values and your application types.
Use Toml.Syntax and Toml.Semantics for low-level TOML syntax processing and semantic validation. Most applications will not need to use these modules directly unless the application is about TOML itself.
The types and functions of this package are parameterized over an annotation type in order to allow applications to provide detailed feedback messages tracked back to specific source locations in an original TOML file. While the default annotation is a simple file position, some applications might upgrade this annotation to track multiple file names or synthetically generated sources. Other applications won't need source location and can replace annotations with a simple unit type.
Synopsis
- type Table = Table' ()
- type Value = Value' ()
- data Located a = Located {
- locPosition :: !Position
- locThing :: !a
- data Position = Position {}
- newtype Table' a = MkTable (Map Text (a, Value' a))
- 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
- valueAnn :: Value' a -> a
- valueType :: Value' l -> String
- forgetTableAnns :: Table' a -> Table
- forgetValueAnns :: Value' a -> Value
- decode' :: FromValue a => Text -> Result DecodeError a
- decode :: FromValue a => Text -> Result String a
- parse :: Text -> Either String (Table' Position)
- data DecodeError
- data Result e a
- encode :: ToTable a => a -> TomlDoc
- prettyToml :: Table' a -> TomlDoc
- data DocClass
- prettyDecodeError :: DecodeError -> String
- prettyLocated :: Located String -> String
- prettyMatchMessage :: MatchMessage Position -> String
- prettySemanticError :: SemanticError Position -> String
Types
Located types
A value annotated with its text file position
Located | |
|
Instances
Foldable Located Source # | Default instance |
Defined in Toml.Syntax.Position fold :: Monoid m => Located m -> m # foldMap :: Monoid m => (a -> m) -> Located a -> m # foldMap' :: Monoid m => (a -> m) -> Located a -> m # foldr :: (a -> b -> b) -> b -> Located a -> b # foldr' :: (a -> b -> b) -> b -> Located a -> b # foldl :: (b -> a -> b) -> b -> Located a -> b # foldl' :: (b -> a -> b) -> b -> Located a -> b # foldr1 :: (a -> a -> a) -> Located a -> a # foldl1 :: (a -> a -> a) -> Located a -> a # elem :: Eq a => a -> Located a -> Bool # maximum :: Ord a => Located a -> a # minimum :: Ord a => Located a -> a # | |
Traversable Located Source # | Default instance |
Functor Located Source # | Default instance |
Read a => Read (Located a) Source # | Default instance |
Show a => Show (Located a) Source # | Default instance |
A position in a text file
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 # | |
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 |
valueType :: Value' l -> String Source #
String representation of the kind of value using TOML vocabulary
forgetTableAnns :: Table' a -> Table Source #
Replaces annotations with a unit.
forgetValueAnns :: Value' a -> Value Source #
Replaces annotations with a unit.
Parsing
decode' :: FromValue a => Text -> Result DecodeError a Source #
Decode TOML syntax into an application value.
decode :: FromValue a => Text -> Result String a Source #
Wrapper rending error and warning messages into human-readable strings.
parse :: Text -> Either String (Table' Position) Source #
Parse a TOML formatted String
or report a human-readable error message.
data DecodeError Source #
Sum of errors that can occur during TOML decoding
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 |
Printing
encode :: ToTable a => a -> TomlDoc Source #
Use the ToTable
instance to encode a value to a TOML string.
Render a complete TOML document using top-level table and array of table sections where possible.
Keys are sorted alphabetically. To provide a custom ordering, see
prettyTomlOrdered
.
Annotation used to enable styling pretty-printed TOML
TableClass | top-level |
KeyClass | dotted keys, left-hand side of assignments |
StringClass | string literals |
NumberClass | number literals |
DateClass | date and time literals |
BoolClass | boolean literals |
Error rendering
prettyDecodeError :: DecodeError -> String Source #
Human-readable representation of a DecodeError
prettyMatchMessage :: MatchMessage Position -> String Source #
Render a TOML decoding error as a human-readable string.
prettySemanticError :: SemanticError Position -> String Source #
Render a semantic TOML error in a human-readable string.