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

Toml.Syntax

Description

These are the low-level processing functions for transforming concrete TOML syntax into abstract TOML syntax. This module does not do any semantic validation of the parsed TOML.

Synopsis

Parsing

parseRawToml :: Text -> Either (Located String) [Expr Position] Source #

Parse a list of tokens either returning the first unexpected token or a list of the TOML statements in the file to be processed by Toml.Semantics.

type Key a = NonEmpty (a, Text) Source #

Non-empty sequence of dotted simple keys

data Expr a Source #

Headers and assignments corresponding to lines of a TOML file

Constructors

KeyValExpr (Key a) (Val a)

key value assignment: key = value

TableExpr (Key a)

table: [key]

ArrayTableExpr (Key a)

array of tables: [[key]]

Instances

Instances details
Read a => Read (Expr a) Source # 
Instance details

Defined in Toml.Syntax.Types

Show a => Show (Expr a) Source # 
Instance details

Defined in Toml.Syntax.Types

Methods

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

show :: Expr a -> String #

showList :: [Expr a] -> ShowS #

data Val a Source #

Unvalidated TOML values. Table are represented as a list of assignments rather than as resolved maps.

Instances

Instances details
Read a => Read (Val a) Source # 
Instance details

Defined in Toml.Syntax.Types

Show a => Show (Val a) Source # 
Instance details

Defined in Toml.Syntax.Types

Methods

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

show :: Val a -> String #

showList :: [Val a] -> ShowS #

Lexing

scanToken :: Context -> Located Text -> Either (Located String) (Located Token, Located Text) Source #

Get the next token from a located string or a located error message.

data Context Source #

Representation of the current lexer state.

Constructors

TopContext

top-level where [[ and ]] have special meaning

TableContext

inline table - lex key names

ValueContext

value lexer - lex number literals

MlBstrContext Position [Text]

multiline basic string: position of opening delimiter and list of fragments

BstrContext Position [Text]

basic string: position of opening delimiter and list of fragments

MlLstrContext Position [Text]

multiline literal string: position of opening delimiter and list of fragments

LstrContext Position [Text]

literal string: position of opening delimiter and list of fragments

Instances

Instances details
Show Context Source # 
Instance details

Defined in Toml.Syntax.LexerUtils

data Token Source #

Lexical token

Constructors

TokTrue
true
TokFalse
false
TokComma
','
TokEquals
'='
TokNewline
end-of-line
TokPeriod
.
TokSquareO
'['
TokSquareC
']'
Tok2SquareO
'[['
Tok2SquareC
']]'
TokCurlyO
'{'
TokCurlyC
'}'
TokBareKey Text

bare key

TokString Text

string literal

TokMlString Text

multiline string literal

TokInteger !Integer

integer literal

TokFloat !Double

floating-point literal

TokOffsetDateTime !ZonedTime

date-time with timezone offset

TokLocalDateTime !LocalTime

local date-time

TokLocalDate !Day

local date

TokLocalTime !TimeOfDay

local time

TokEOF
end-of-input

Instances

Instances details
Read Token Source # 
Instance details

Defined in Toml.Syntax.Token

Show Token Source # 
Instance details

Defined in Toml.Syntax.Token

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Locations

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

startPos :: Position Source #

The initial Position for the start of a file