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

Description

 
Synopsis

FromValue

class FromValue a where Source #

Class for types that can be decoded from a TOML value.

Minimal complete definition

fromValue

Methods

fromValue :: Value' l -> Matcher l a Source #

Convert a Value or report an error message

listFromValue :: Value' l -> Matcher l [a] Source #

Used to implement instance for []. Most implementations rely on the default implementation.

Instances

Instances details
FromValue Int16 Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue Int32 Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue Int64 Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue Int8 Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue Word16 Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue Word32 Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue Word64 Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue Word8 Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue Text Source #

Matches string literals

Instance details

Defined in Toml.Schema.FromValue

FromValue Text Source #

Matches string literals

Instance details

Defined in Toml.Schema.FromValue

FromValue Day Source #

Matches local date literals

Instance details

Defined in Toml.Schema.FromValue

FromValue LocalTime Source #

Matches local date-time literals

Instance details

Defined in Toml.Schema.FromValue

FromValue TimeOfDay Source #

Matches local time literals

Instance details

Defined in Toml.Schema.FromValue

FromValue ZonedTime Source #

Matches offset date-time literals

Instance details

Defined in Toml.Schema.FromValue

FromValue Table Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue Value Source #

Matches all values, used for pass-through

Instance details

Defined in Toml.Schema.FromValue

FromValue Integer Source #

Matches integer values

Instance details

Defined in Toml.Schema.FromValue

FromValue Natural Source #

Matches non-negative integer values

Instance details

Defined in Toml.Schema.FromValue

FromValue Bool Source #

Matches true and false

Instance details

Defined in Toml.Schema.FromValue

FromValue Char Source #

Matches single-character strings with fromValue and arbitrary strings with listFromValue to support String

Instance details

Defined in Toml.Schema.FromValue

FromValue Double Source #

Matches floating-point and integer values

Instance details

Defined in Toml.Schema.FromValue

FromValue Float Source #

Matches floating-point and integer values

Instance details

Defined in Toml.Schema.FromValue

FromValue Int Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue Word Source # 
Instance details

Defined in Toml.Schema.FromValue

FromValue a => FromValue (NonEmpty a) Source #

Matches non-empty arrays or reports an error.

Instance details

Defined in Toml.Schema.FromValue

Integral a => FromValue (Ratio a) Source #

Matches floating-point and integer values.

TOML specifies Floats should be implemented as IEEE 754 binary64 values. so note that the given Rational will be converted from a double representation and will often be an approximation rather than the exact value.

Instance details

Defined in Toml.Schema.FromValue

FromValue a => FromValue (Seq a) Source #

Matches arrays

Instance details

Defined in Toml.Schema.FromValue

(Generic a, GFromArray (Rep a)) => FromValue (GenericTomlArray a) Source #

Instance derived using genericFromArray

Instance details

Defined in Toml.Schema.Generic

(Generic a, GParseTable (Rep a)) => FromValue (GenericTomlTable a) Source #

Instance derived using genericParseTable

Instance details

Defined in Toml.Schema.Generic

FromValue a => FromValue [a] Source #

Implemented in terms of listFromValue

Instance details

Defined in Toml.Schema.FromValue

Methods

fromValue :: Value' l -> Matcher l [a] Source #

listFromValue :: Value' l -> Matcher l [[a]] Source #

(Ord k, FromKey k, FromValue v) => FromValue (Map k v) Source # 
Instance details

Defined in Toml.Schema.FromValue

Methods

fromValue :: Value' l -> Matcher l (Map k v) Source #

listFromValue :: Value' l -> Matcher l [Map k v] Source #

mapOf Source #

Arguments

:: Ord k 
=> (l -> Text -> Matcher l k)

key matcher

-> (Text -> Value' l -> Matcher l v)

value matcher

-> Value' l 
-> Matcher l (Map k v) 

Table matching function used to help implement fromValue for tables. Key matching function is given the annotation of the key for error reporting. Value matching function is given the key in case values can depend on their keys.

listOf :: (Int -> Value' l -> Matcher l a) -> Value' l -> Matcher l [a] Source #

List matching function used to help implemented fromValue for arrays. The element matching function is given the list index in case values can depend on their index.

Matcher

data Matcher l a Source #

Computations that result in a Result and which track a list of nested contexts to assist in generating warnings and error messages.

Use withScope to run a Matcher in a new, nested scope.

Instances

Instances details
MonadFail (Matcher a) Source #

Fail with an error message without an annotation.

Instance details

Defined in Toml.Schema.Matcher

Methods

fail :: String -> Matcher a a0 #

Alternative (Matcher a) Source # 
Instance details

Defined in Toml.Schema.Matcher

Methods

empty :: Matcher a a0 #

(<|>) :: Matcher a a0 -> Matcher a a0 -> Matcher a a0 #

some :: Matcher a a0 -> Matcher a [a0] #

many :: Matcher a a0 -> Matcher a [a0] #

Applicative (Matcher a) Source # 
Instance details

Defined in Toml.Schema.Matcher

Methods

pure :: a0 -> Matcher a a0 #

(<*>) :: Matcher a (a0 -> b) -> Matcher a a0 -> Matcher a b #

liftA2 :: (a0 -> b -> c) -> Matcher a a0 -> Matcher a b -> Matcher a c #

(*>) :: Matcher a a0 -> Matcher a b -> Matcher a b #

(<*) :: Matcher a a0 -> Matcher a b -> Matcher a a0 #

Functor (Matcher a) Source # 
Instance details

Defined in Toml.Schema.Matcher

Methods

fmap :: (a0 -> b) -> Matcher a a0 -> Matcher a b #

(<$) :: a0 -> Matcher a b -> Matcher a a0 #

Monad (Matcher a) Source # 
Instance details

Defined in Toml.Schema.Matcher

Methods

(>>=) :: Matcher a a0 -> (a0 -> Matcher a b) -> Matcher a b #

(>>) :: Matcher a a0 -> Matcher a b -> Matcher a b #

return :: a0 -> Matcher a a0 #

MonadPlus (Matcher a) Source # 
Instance details

Defined in Toml.Schema.Matcher

Methods

mzero :: Matcher a a0 #

mplus :: Matcher a a0 -> Matcher a a0 -> Matcher a a0 #

runMatcher :: Matcher l a -> Result (MatchMessage l) a Source #

Run a Matcher with an empty scope.

runMatcherFatalWarn :: Matcher l a -> Either [MatchMessage l] a Source #

Run Matcher and treat warnings as errors.

runMatcherIgnoreWarn :: Matcher l a -> Either [MatchMessage l] a Source #

Run Matcher and ignore warnings.

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 #

data MatchMessage a Source #

A message emitted while matching a TOML value. The message is paired with the path to the value that was in focus when the message was generated. These message get used for both warnings and errors.

For a convenient way to render these to a string, see prettyMatchMessage.

Constructors

MatchMessage 

Fields

Instances

Instances details
Foldable MatchMessage Source # 
Instance details

Defined in Toml.Schema.Matcher

Methods

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

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

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

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

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

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

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

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

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

toList :: MatchMessage a -> [a] #

null :: MatchMessage a -> Bool #

length :: MatchMessage a -> Int #

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

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

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

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

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

Traversable MatchMessage Source # 
Instance details

Defined in Toml.Schema.Matcher

Methods

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

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

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

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

Functor MatchMessage Source # 
Instance details

Defined in Toml.Schema.Matcher

Methods

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

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

Read a => Read (MatchMessage a) Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

Show a => Show (MatchMessage a) Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

Eq a => Eq (MatchMessage a) Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

Ord a => Ord (MatchMessage a) Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

data Scope Source #

Scopes for TOML message.

Constructors

ScopeIndex Int

zero-based array index

ScopeKey Text

key in a table

Instances

Instances details
Read Scope Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

Show Scope Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

Eq Scope Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

Methods

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

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

Ord Scope Source #

Default instance

Instance details

Defined in Toml.Schema.Matcher

Methods

compare :: Scope -> Scope -> Ordering #

(<) :: Scope -> Scope -> Bool #

(<=) :: Scope -> Scope -> Bool #

(>) :: Scope -> Scope -> Bool #

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

max :: Scope -> Scope -> Scope #

min :: Scope -> Scope -> Scope #

parseTableFromValue :: ParseTable l a -> Value' l -> Matcher l a Source #

Used to derive a fromValue implementation from a ParseTable matcher.

parseTable :: ParseTable l a -> l -> Table' l -> Matcher l a Source #

Run a ParseTable computation with a given starting Table'. Unused tables will generate a warning. To change this behavior getTable and setTable can be used to discard or generate error messages.

getScope :: Matcher a [Scope] Source #

Get the current list of scopes.

warn :: String -> Matcher a () Source #

Emit a warning without an annotation.

warnAt :: l -> String -> Matcher l () Source #

Emit a warning mentioning the given annotation.

failAt :: l -> String -> Matcher l a Source #

Terminate the match with an error mentioning the given annotation.

getTable :: ParseTable l (Table' l) Source #

Return the remaining portion of the table being matched.

setTable :: Table' l -> ParseTable l () Source #

Replace the remaining portion of the table being matched.

Tables

data ParseTable l a Source #

Parser that tracks a current set of unmatched key-value pairs from a table.

Use optKey and reqKey to extract keys.

Use getTable and setTable to override the table and implement other primitives.

Instances

Instances details
MonadFail (ParseTable l) Source #

Implemented in terms of fail on Matcher

Instance details

Defined in Toml.Schema.ParseTable

Methods

fail :: String -> ParseTable l a #

Alternative (ParseTable l) Source # 
Instance details

Defined in Toml.Schema.ParseTable

Methods

empty :: ParseTable l a #

(<|>) :: ParseTable l a -> ParseTable l a -> ParseTable l a #

some :: ParseTable l a -> ParseTable l [a] #

many :: ParseTable l a -> ParseTable l [a] #

Applicative (ParseTable l) Source # 
Instance details

Defined in Toml.Schema.ParseTable

Methods

pure :: a -> ParseTable l a #

(<*>) :: ParseTable l (a -> b) -> ParseTable l a -> ParseTable l b #

liftA2 :: (a -> b -> c) -> ParseTable l a -> ParseTable l b -> ParseTable l c #

(*>) :: ParseTable l a -> ParseTable l b -> ParseTable l b #

(<*) :: ParseTable l a -> ParseTable l b -> ParseTable l a #

Functor (ParseTable l) Source # 
Instance details

Defined in Toml.Schema.ParseTable

Methods

fmap :: (a -> b) -> ParseTable l a -> ParseTable l b #

(<$) :: a -> ParseTable l b -> ParseTable l a #

Monad (ParseTable l) Source # 
Instance details

Defined in Toml.Schema.ParseTable

Methods

(>>=) :: ParseTable l a -> (a -> ParseTable l b) -> ParseTable l b #

(>>) :: ParseTable l a -> ParseTable l b -> ParseTable l b #

return :: a -> ParseTable l a #

MonadPlus (ParseTable l) Source # 
Instance details

Defined in Toml.Schema.ParseTable

Methods

mzero :: ParseTable l a #

mplus :: ParseTable l a -> ParseTable l a -> ParseTable l a #

reqKey :: FromValue a => Text -> ParseTable l a Source #

Convenience function for matching a required key with a FromValue instance.

reqKey key = reqKeyOf key fromValue

optKey :: FromValue a => Text -> ParseTable l (Maybe a) Source #

Convenience function for matching an optional key with a FromValue instance.

optKey key = optKeyOf key fromValue

reqKeyOf Source #

Arguments

:: Text

key

-> (Value' l -> Matcher l a)

value matcher

-> ParseTable l a 

Match a table entry by key or report an error if missing.

See pickKey for more complex cases.

optKeyOf Source #

Arguments

:: Text

key

-> (Value' l -> Matcher l a)

value matcher

-> ParseTable l (Maybe a) 

Match a table entry by key if it exists or return Nothing if not. If the key is defined, it is matched by the given function.

See pickKey for more complex cases.

pickKey :: [KeyAlt l a] -> ParseTable l a Source #

Take the first option from a list of table keys and matcher functions. This operation will commit to the first table key that matches. If the associated matcher fails, only that error will be propagated and the other alternatives will not be matched.

If no keys match, an error message is generated explaining which keys would have been accepted.

This is provided as an alternative to chaining multiple reqKey cases together with Alternative which will fall-through as a result of any failure to the next case.

data KeyAlt l a Source #

Key and value matching function

Constructors

Key Text (Value' l -> Matcher l a)

pick alternative based on key match

Else (Matcher l a)

default case when no previous cases matched

warnTable :: String -> ParseTable l () Source #

Emit a warning without an annotation.

warnTableAt :: l -> String -> ParseTable l () Source #

Emit a warning with the given annotation.

failTableAt :: l -> String -> ParseTable l a Source #

Abort the current table matching with an error message at the given annotation.

liftMatcher :: Matcher l a -> ParseTable l a Source #

Lift a matcher into the current table parsing context.

ToValue

class ToValue a where Source #

Class for types that can be embedded into Value

Minimal complete definition

toValue

Methods

toValue :: a -> Value Source #

Embed a single thing into a TOML value.

toValueList :: [a] -> Value Source #

Helper for converting a list of things into a value. This is typically left to be defined by its default implementation and exists to help define the encoding for TOML arrays.

Instances

Instances details
ToValue Int16 Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Int32 Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Int64 Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Int8 Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Word16 Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Word32 Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Word64 Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Word8 Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Text Source #

Encodes as string literal

Instance details

Defined in Toml.Schema.ToValue

ToValue Text Source #

Encodes as string literal

Instance details

Defined in Toml.Schema.ToValue

ToValue Day Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue LocalTime Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue TimeOfDay Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue ZonedTime Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Value Source #

Identity function

Instance details

Defined in Toml.Schema.ToValue

ToValue Integer Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Natural Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Bool Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Char Source #

Single characters are encoded as singleton strings. Lists of characters are encoded as a single string value.

Instance details

Defined in Toml.Schema.ToValue

ToValue Double Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Float Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Int Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue Word Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue a => ToValue (NonEmpty a) Source #

Converts to list and encodes that to value

Instance details

Defined in Toml.Schema.ToValue

Integral a => ToValue (Ratio a) Source #

TOML represents floating point numbers with Double. This operation lose precision and can overflow to infinity.

Instance details

Defined in Toml.Schema.ToValue

ToValue a => ToValue (Seq a) Source #

Converts to list and encodes that to value

Instance details

Defined in Toml.Schema.ToValue

Methods

toValue :: Seq a -> Value Source #

toValueList :: [Seq a] -> Value Source #

(Generic a, GToArray (Rep a)) => ToValue (GenericTomlArray a) Source #

Instance derived using genericToArray

Instance details

Defined in Toml.Schema.Generic

(Generic a, GToTable (Rep a)) => ToValue (GenericTomlTable a) Source #

Instance derived from ToTable instance using defaultTableToValue

Instance details

Defined in Toml.Schema.Generic

ToValue (Table' a) Source # 
Instance details

Defined in Toml.Schema.ToValue

ToValue a => ToValue [a] Source #

This instance defers to the list element's toValueList implementation.

Instance details

Defined in Toml.Schema.ToValue

Methods

toValue :: [a] -> Value Source #

toValueList :: [[a]] -> Value Source #

(ToKey k, ToValue v) => ToValue (Map k v) Source # 
Instance details

Defined in Toml.Schema.ToValue

Methods

toValue :: Map k v -> Value Source #

toValueList :: [Map k v] -> Value Source #

class ToValue a => ToTable a where Source #

Class for things that can be embedded into a TOML table.

Implement this for things that always embed into a Value' and then the ToValue instance can be derived with defaultTableToValue.

instance ToValue Example where
    toValue = defaultTableToValue

-- Option 1: Manual instance
instance ToTable Example where
    toTable x = table ["field1" .= field1 x, "field2" .= field2 x]

-- Option 2: GHC.Generics derived instance using Toml.ToValue.Generic
instance ToTable Example where
    toTable = genericToTable

Methods

toTable :: a -> Table Source #

Convert a single value into a table

Instances

Instances details
(Generic a, GToTable (Rep a)) => ToTable (GenericTomlTable a) Source #

Instance derived using genericToTable

Instance details

Defined in Toml.Schema.Generic

ToTable (Table' a) Source # 
Instance details

Defined in Toml.Schema.ToValue

Methods

toTable :: Table' a -> Table Source #

(ToKey k, ToValue v) => ToTable (Map k v) Source # 
Instance details

Defined in Toml.Schema.ToValue

Methods

toTable :: Map k v -> Table Source #

table :: [(Text, Value)] -> Table Source #

Build a Value' from a list of key-value pairs.

Use .= for a convenient way to build the pairs.

(.=) :: ToValue a => Text -> a -> (Text, Value) Source #

Convenience function for building key-value pairs while constructing a Value'.

table [a .= b, c .= d]

defaultTableToValue :: ToTable a => a -> Value Source #

Convenience function for building ToValue instances.

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

Generics

newtype GenericTomlArray a Source #

Helper type to use GHC's DerivingVia extension to derive ToValue, ToTable, FromValue for any product type.

Constructors

GenericTomlArray a 

Instances

Instances details
(Generic a, GFromArray (Rep a)) => FromValue (GenericTomlArray a) Source #

Instance derived using genericFromArray

Instance details

Defined in Toml.Schema.Generic

(Generic a, GToArray (Rep a)) => ToValue (GenericTomlArray a) Source #

Instance derived using genericToArray

Instance details

Defined in Toml.Schema.Generic

newtype GenericTomlTable a Source #

Helper type to use GHC's DerivingVia extension to derive ToValue, ToTable, FromValue for records.

Constructors

GenericTomlTable a 

Instances

Instances details
(Generic a, GParseTable (Rep a)) => FromValue (GenericTomlTable a) Source #

Instance derived using genericParseTable

Instance details

Defined in Toml.Schema.Generic

(Generic a, GToTable (Rep a)) => ToTable (GenericTomlTable a) Source #

Instance derived using genericToTable

Instance details

Defined in Toml.Schema.Generic

(Generic a, GToTable (Rep a)) => ToValue (GenericTomlTable a) Source #

Instance derived from ToTable instance using defaultTableToValue

Instance details

Defined in Toml.Schema.Generic

genericFromTable :: (Generic a, GParseTable (Rep a)) => Value' l -> Matcher l a Source #

Implementation of fromValue using genericParseTable to derive a match from the record field names of the target type.

genericFromArray :: (Generic a, GFromArray (Rep a)) => Value' l -> Matcher l a Source #

Match a Value' as an array positionally matching field fields of a constructor to the elements of the array.

genericToArray :: (Generic a, GToArray (Rep a)) => a -> Value Source #

Use a record's field names to generate a Value'

genericToTable :: (Generic a, GToTable (Rep a)) => a -> Table Source #

Use a record's field names to generate a Value'