toml-parser-2.0.0.0: TOML 1.0.0 parser
Copyright(c) Eric Mertens 2023
LicenseISC
Maintaineremertens@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Toml

Description

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

Types

type Table = Table' () Source #

A Value' with trivial annotations

type Value = Value' () Source #

A Value' with trivial annotations

Located types

data Located a Source #

A value annotated with its text file position

Constructors

Located 

Fields

Instances

Instances details
Foldable Located Source #

Default instance

Instance details

Defined in Toml.Syntax.Position

Methods

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 #

toList :: Located a -> [a] #

null :: Located a -> Bool #

length :: Located a -> Int #

elem :: Eq a => a -> Located a -> Bool #

maximum :: Ord a => Located a -> a #

minimum :: Ord a => Located a -> a #

sum :: Num a => Located a -> a #

product :: Num a => Located a -> a #

Traversable Located Source #

Default instance

Instance details

Defined in Toml.Syntax.Position

Methods

traverse :: Applicative f => (a -> f b) -> Located a -> f (Located b) #

sequenceA :: Applicative f => Located (f a) -> f (Located a) #

mapM :: Monad m => (a -> m b) -> Located a -> m (Located b) #

sequence :: Monad m => Located (m a) -> m (Located a) #

Functor Located Source #

Default instance

Instance details

Defined in Toml.Syntax.Position

Methods

fmap :: (a -> b) -> Located a -> Located b #

(<$) :: a -> Located b -> Located a #

Read a => Read (Located a) Source #

Default instance

Instance details

Defined in Toml.Syntax.Position

Show a => Show (Located a) Source #

Default instance

Instance details

Defined in Toml.Syntax.Position

Methods

showsPrec :: Int -> Located a -> ShowS #

show :: Located a -> String #

showList :: [Located a] -> ShowS #

data Position Source #

A position in a text file

Constructors

Position 

Fields

Instances

Instances details
Read Position Source #

Default instance

Instance details

Defined in Toml.Syntax.Position

Show Position Source #

Default instance

Instance details

Defined in Toml.Syntax.Position

Eq Position Source #

Default instance

Instance details

Defined in Toml.Syntax.Position

Ord Position Source #

Default instance

Instance details

Defined in Toml.Syntax.Position

newtype Table' a Source #

A table with annotated keys and values.

Constructors

MkTable (Map Text (a, Value' a)) 

Instances

Instances details
Foldable Table' Source #

Derived

Instance details

Defined in Toml.Semantics.Types

Methods

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 #

toList :: Table' a -> [a] #

null :: Table' a -> Bool #

length :: Table' a -> Int #

elem :: Eq a => a -> Table' a -> Bool #

maximum :: Ord a => Table' a -> a #

minimum :: Ord a => Table' a -> a #

sum :: Num a => Table' a -> a #

product :: Num a => Table' a -> a #

Traversable Table' Source #

Derived

Instance details

Defined in Toml.Semantics.Types

Methods

traverse :: Applicative f => (a -> f b) -> Table' a -> f (Table' b) #

sequenceA :: Applicative f => Table' (f a) -> f (Table' a) #

mapM :: Monad m => (a -> m b) -> Table' a -> m (Table' b) #

sequence :: Monad m => Table' (m a) -> m (Table' a) #

Functor Table' Source #

Derived

Instance details

Defined in Toml.Semantics.Types

Methods

fmap :: (a -> b) -> Table' a -> Table' b #

(<$) :: a -> Table' b -> Table' a #

FromValue Table Source # 
Instance details

Defined in Toml.Schema.FromValue

Read a => Read (Table' a) Source #

Default instance

Instance details

Defined in Toml.Semantics.Types

Show a => Show (Table' a) Source #

Default instance

Instance details

Defined in Toml.Semantics.Types

Methods

showsPrec :: Int -> Table' a -> ShowS #

show :: Table' a -> String #

showList :: [Table' a] -> ShowS #

Eq a => Eq (Table' a) Source #

Default instance

Instance details

Defined in Toml.Semantics.Types

Methods

(==) :: Table' a -> Table' a -> Bool #

(/=) :: Table' a -> Table' a -> Bool #

ToTable (Table' a) Source # 
Instance details

Defined in Toml.Schema.ToValue

Methods

toTable :: Table' a -> Table Source #

ToValue (Table' a) Source # 
Instance details

Defined in Toml.Schema.ToValue

data Value' a Source #

Semantic TOML value with all table assignments resolved.

Bundled Patterns

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

Instances details
Foldable Value' Source #

Derived

Instance details

Defined in Toml.Semantics.Types

Methods

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 #

toList :: Value' a -> [a] #

null :: Value' a -> Bool #

length :: Value' a -> Int #

elem :: Eq a => a -> Value' a -> Bool #

maximum :: Ord a => Value' a -> a #

minimum :: Ord a => Value' a -> a #

sum :: Num a => Value' a -> a #

product :: Num a => Value' a -> a #

Traversable Value' Source #

Derived

Instance details

Defined in Toml.Semantics.Types

Methods

traverse :: Applicative f => (a -> f b) -> Value' a -> f (Value' b) #

sequenceA :: Applicative f => Value' (f a) -> f (Value' a) #

mapM :: Monad m => (a -> m b) -> Value' a -> m (Value' b) #

sequence :: Monad m => Value' (m a) -> m (Value' a) #

Functor Value' Source #

Derived

Instance details

Defined in Toml.Semantics.Types

Methods

fmap :: (a -> b) -> Value' a -> Value' b #

(<$) :: a -> Value' b -> Value' a #

FromValue Value Source #

Matches all values, used for pass-through

Instance details

Defined in Toml.Schema.FromValue

ToValue Value Source #

Identity function

Instance details

Defined in Toml.Schema.ToValue

() ~ a => IsString (Value' a) Source #

Constructs a TOML string literal.

fromString = String
Instance details

Defined in Toml.Semantics.Types

Methods

fromString :: String -> Value' a #

Read a => Read (Value' a) Source #

Default instance

Instance details

Defined in Toml.Semantics.Types

Show a => Show (Value' a) Source #

Default instance

Instance details

Defined in Toml.Semantics.Types

Methods

showsPrec :: Int -> Value' a -> ShowS #

show :: Value' a -> String #

showList :: [Value' a] -> ShowS #

Eq a => Eq (Value' a) Source #

Nearly default instance except ZonedTime doesn't have an Eq instance. ZonedTime values are equal if their times and time-zones are both equal.

Instance details

Defined in Toml.Semantics.Types

Methods

(==) :: Value' a -> Value' a -> Bool #

(/=) :: Value' a -> Value' a -> Bool #

valueAnn :: Value' a -> a Source #

Extract the top-level annotation from a value.

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

data Result e a Source #

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.

Constructors

Failure [e]

error messages

Success [e] a

warning messages and result

Instances

Instances details
(Read e, Read a) => Read (Result e a) Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

(Show e, Show a) => Show (Result e a) Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

Methods

showsPrec :: Int -> Result e a -> ShowS #

show :: Result e a -> String #

showList :: [Result e a] -> ShowS #

(Eq e, Eq a) => Eq (Result e a) Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

Methods

(==) :: Result e a -> Result e a -> Bool #

(/=) :: Result e a -> Result e a -> Bool #

(Ord e, Ord a) => Ord (Result e a) Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

Methods

compare :: Result e a -> Result e a -> Ordering #

(<) :: Result e a -> Result e a -> Bool #

(<=) :: Result e a -> Result e a -> Bool #

(>) :: Result e a -> Result e a -> Bool #

(>=) :: Result e a -> Result e a -> Bool #

max :: Result e a -> Result e a -> Result e a #

min :: Result e a -> Result e a -> Result e a #

Printing

encode :: ToTable a => a -> TomlDoc Source #

Use the ToTable instance to encode a value to a TOML string.

prettyToml Source #

Arguments

:: Table' a

table to print

-> TomlDoc

TOML syntax

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.

data DocClass Source #

Annotation used to enable styling pretty-printed TOML

Constructors

TableClass

top-level [key] and [[key]]

KeyClass

dotted keys, left-hand side of assignments

StringClass

string literals

NumberClass

number literals

DateClass

date and time literals

BoolClass

boolean literals

Instances

Instances details
Read DocClass Source # 
Instance details

Defined in Toml.Pretty

Show DocClass Source # 
Instance details

Defined in Toml.Pretty

Eq DocClass Source # 
Instance details

Defined in Toml.Pretty

Ord DocClass Source # 
Instance details

Defined in Toml.Pretty

Error rendering

prettyDecodeError :: DecodeError -> String Source #

Human-readable representation of a DecodeError

prettyLocated :: Located String -> String Source #

Pretty-print as line:col: message

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.