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.Semantics

Description

This module extracts a nested Map representation of a TOML file. It detects invalid key assignments and resolves dotted key assignments.

Synopsis

Types

type Value = Value' () Source #

A Value' with trivial annotations

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 #

type Table = Table' () Source #

A Value' with trivial annotations

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

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

Constructors

SemanticError 

Fields

Instances

Instances details
Foldable SemanticError Source # 
Instance details

Defined in Toml.Semantics

Methods

fold :: Monoid m => SemanticError m -> m #

foldMap :: Monoid m => (a -> m) -> SemanticError a -> m #

foldMap' :: Monoid m => (a -> m) -> SemanticError a -> m #

foldr :: (a -> b -> b) -> b -> SemanticError a -> b #

foldr' :: (a -> b -> b) -> b -> SemanticError a -> b #

foldl :: (b -> a -> b) -> b -> SemanticError a -> b #

foldl' :: (b -> a -> b) -> b -> SemanticError a -> b #

foldr1 :: (a -> a -> a) -> SemanticError a -> a #

foldl1 :: (a -> a -> a) -> SemanticError a -> a #

toList :: SemanticError a -> [a] #

null :: SemanticError a -> Bool #

length :: SemanticError a -> Int #

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

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

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

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

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

Traversable SemanticError Source # 
Instance details

Defined in Toml.Semantics

Methods

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

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

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

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

Functor SemanticError Source # 
Instance details

Defined in Toml.Semantics

Methods

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

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

Read a => Read (SemanticError a) Source #

Default instance

Instance details

Defined in Toml.Semantics

Show a => Show (SemanticError a) Source #

Default instance

Instance details

Defined in Toml.Semantics

Eq a => Eq (SemanticError a) Source #

Default instance

Instance details

Defined in Toml.Semantics

Ord a => Ord (SemanticError a) Source #

Default instance

Instance details

Defined in Toml.Semantics

data SemanticErrorKind Source #

Enumeration of the kinds of conflicts a key can generate.

Since: 1.3.0.0

Constructors

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

Annotations

forgetTableAnns :: Table' a -> Table Source #

Replaces annotations with a unit.

forgetValueAnns :: Value' a -> Value Source #

Replaces annotations with a unit.

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