toml-parser-1.2.1.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 coversion 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.

Synopsis

Types

type Table = Map String Value Source #

Representation of a TOML key-value table.

data Value Source #

Semantic TOML value with all table assignments resolved.

Instances

Instances details
Data Value Source #

Default instance

Instance details

Defined in Toml.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value #

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

Generic Value Source # 
Instance details

Defined in Toml.Value

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Read Value Source #

Default instance

Instance details

Defined in Toml.Value

Show Value Source #

Default instance

Instance details

Defined in Toml.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Eq Value Source #

Nearly default instance except Value doesn't have an Eq instance. Value values are equal if their times and timezones are both equal.

Instance details

Defined in Toml.Value

Methods

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

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

FromValue Value Source #

Matches all values, used for pass-through

Instance details

Defined in Toml.FromValue

ToValue Value Source #

Identity function

Instance details

Defined in Toml.ToValue

type Rep Value Source #

Default instance

Instance details

Defined in Toml.Value

type Rep Value = D1 ('MetaData "Value" "Toml.Value" "toml-parser-1.2.1.0-93ny6R2gSFGGe7xlzvdeoY" 'False) (((C1 ('MetaCons "Integer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: C1 ('MetaCons "Float" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Value])) :+: (C1 ('MetaCons "Table" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Table)) :+: C1 ('MetaCons "Bool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :+: ((C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "TimeOfDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeOfDay))) :+: (C1 ('MetaCons "ZonedTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ZonedTime)) :+: (C1 ('MetaCons "LocalTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalTime)) :+: C1 ('MetaCons "Day" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day))))))

Parsing

parse :: String -> Either String Table Source #

Parse a TOML formatted Value or report an error message.

Printing

prettyToml Source #

Arguments

:: Table

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

Serialization

decode :: FromValue a => String -> Result a Source #

Use the FromValue instance to decode a value from a TOML string.

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

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

data Result 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 [String]

error messages

Success [String] a

warning messages and result

Instances

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

Default instance

Instance details

Defined in Toml.FromValue.Matcher

Show a => Show (Result a) Source #

Default instance

Instance details

Defined in Toml.FromValue.Matcher

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Eq a => Eq (Result a) Source #

Default instance

Instance details

Defined in Toml.FromValue.Matcher

Methods

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

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

Ord a => Ord (Result a) Source #

Default instance

Instance details

Defined in Toml.FromValue.Matcher

Methods

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

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

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

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

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

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

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