toml-reader-0.1.0.0: TOML format parser compliant with v1.0.0.
Safe HaskellNone
LanguageHaskell2010

TOML

Synopsis

Decoding a TOML file

decode :: DecodeTOML a => Text -> Either TOMLError a Source #

Decode the given TOML input.

decodeWith :: Decoder a -> Text -> Either TOMLError a Source #

Decode the given TOML input using the given Decoder.

decodeFile :: DecodeTOML a => FilePath -> IO (Either TOMLError a) Source #

Decode a TOML file at the given file path.

class DecodeTOML a where Source #

A type class containing the default Decoder for the given type.

See the docs for Decoder for examples.

Instances

Instances details
DecodeTOML Bool Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Char Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Double Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Float Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Int Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Int8 Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Int16 Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Int32 Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Int64 Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Integer Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Natural Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Ordering Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Word Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Word8 Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Word16 Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Word32 Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Word64 Source # 
Instance details

Defined in TOML.Decode

DecodeTOML () Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Void Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Version Source # 
Instance details

Defined in TOML.Decode

DecodeTOML String Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Text Source # 
Instance details

Defined in TOML.Decode

DecodeTOML IntSet Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Text Source # 
Instance details

Defined in TOML.Decode

DecodeTOML ZonedTime Source # 
Instance details

Defined in TOML.Decode

DecodeTOML LocalTime Source # 
Instance details

Defined in TOML.Decode

DecodeTOML TimeOfDay Source # 
Instance details

Defined in TOML.Decode

DecodeTOML CalendarDiffTime Source # 
Instance details

Defined in TOML.Decode

DecodeTOML UTCTime Source # 
Instance details

Defined in TOML.Decode

DecodeTOML SystemTime Source # 
Instance details

Defined in TOML.Decode

DecodeTOML NominalDiffTime Source # 
Instance details

Defined in TOML.Decode

DecodeTOML DiffTime Source # 
Instance details

Defined in TOML.Decode

DecodeTOML DayOfWeek Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Day Source # 
Instance details

Defined in TOML.Decode

DecodeTOML CalendarDiffDays Source # 
Instance details

Defined in TOML.Decode

DecodeTOML Value Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML [a] Source # 
Instance details

Defined in TOML.Decode

Methods

tomlDecoder :: Decoder [a] Source #

DecodeTOML a => DecodeTOML (Maybe a) Source #

Since TOML doesn't support literal NULLs, this will only ever return Just. To get the absence of a field, use getFieldOpt or one of its variants.

Instance details

Defined in TOML.Decode

Integral a => DecodeTOML (Ratio a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (Min a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (Max a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (First a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (Last a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (Identity a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (First a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (Last a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (Dual a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (NonEmpty a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (IntMap a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML a => DecodeTOML (Seq a) Source # 
Instance details

Defined in TOML.Decode

(DecodeTOML a, Ord a) => DecodeTOML (Set a) Source # 
Instance details

Defined in TOML.Decode

(DecodeTOML a, DecodeTOML b) => DecodeTOML (Either a b) Source # 
Instance details

Defined in TOML.Decode

(DecodeTOML a, DecodeTOML b) => DecodeTOML (a, b) Source # 
Instance details

Defined in TOML.Decode

Methods

tomlDecoder :: Decoder (a, b) Source #

HasResolution a => DecodeTOML (Fixed a) Source # 
Instance details

Defined in TOML.Decode

DecodeTOML (Proxy a) Source # 
Instance details

Defined in TOML.Decode

(IsString k, Ord k, DecodeTOML v) => DecodeTOML (Map k v) Source # 
Instance details

Defined in TOML.Decode

Methods

tomlDecoder :: Decoder (Map k v) Source #

(DecodeTOML a, DecodeTOML b, DecodeTOML c) => DecodeTOML (a, b, c) Source # 
Instance details

Defined in TOML.Decode

Methods

tomlDecoder :: Decoder (a, b, c) Source #

DecodeTOML a => DecodeTOML (Const a b) Source # 
Instance details

Defined in TOML.Decode

Methods

tomlDecoder :: Decoder (Const a b) Source #

(DecodeTOML a, DecodeTOML b, DecodeTOML c, DecodeTOML d) => DecodeTOML (a, b, c, d) Source # 
Instance details

Defined in TOML.Decode

Methods

tomlDecoder :: Decoder (a, b, c, d) Source #

data Decoder a Source #

A Decoder a represents a function for decoding a TOML value to a value of type a.

Generally, you'd only need to chain the getField* functions together, like

decoder =
  MyConfig
    <$> getField "a"
    <*> getField "b"
    <*> getField "c"

or use interfaces like Monad and Alternative:

decoder = do
  cfgType <- getField "type"
  case cfgType of
    "int" -> MyIntValue <$> (getField "int" <|> getField "integer")
    "bool" -> MyBoolValue <$> getField "bool"
    _ -> fail $ "Invalid type: " <> cfgType

but you can also manually implement a Decoder with makeDecoder.

Instances

Instances details
Monad Decoder Source # 
Instance details

Defined in TOML.Decode

Methods

(>>=) :: Decoder a -> (a -> Decoder b) -> Decoder b #

(>>) :: Decoder a -> Decoder b -> Decoder b #

return :: a -> Decoder a #

Functor Decoder Source # 
Instance details

Defined in TOML.Decode

Methods

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

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

MonadFail Decoder Source # 
Instance details

Defined in TOML.Decode

Methods

fail :: String -> Decoder a #

Applicative Decoder Source # 
Instance details

Defined in TOML.Decode

Methods

pure :: a -> Decoder a #

(<*>) :: Decoder (a -> b) -> Decoder a -> Decoder b #

liftA2 :: (a -> b -> c) -> Decoder a -> Decoder b -> Decoder c #

(*>) :: Decoder a -> Decoder b -> Decoder b #

(<*) :: Decoder a -> Decoder b -> Decoder a #

Alternative Decoder Source # 
Instance details

Defined in TOML.Decode

Methods

empty :: Decoder a #

(<|>) :: Decoder a -> Decoder a -> Decoder a #

some :: Decoder a -> Decoder [a] #

many :: Decoder a -> Decoder [a] #

Decoding getters

getField :: DecodeTOML a => Text -> Decoder a Source #

Decode a field in a TOML Value. Equivalent to getFields with a single-element list.

a = 1
b = asdf
-- MyConfig 1 "asdf"
MyConfig <$> getField "a" <*> getField "b"

getFields :: DecodeTOML a => [Text] -> Decoder a Source #

Decode a nested field in a TOML Value.

a.b = 1
-- MyConfig 1
MyConfig <$> getFields ["a", "b"]

getFieldOpt :: DecodeTOML a => Text -> Decoder (Maybe a) Source #

Decode a field in a TOML Value, or Nothing if the field doesn't exist. Equivalent to getFieldsOpt with a single-element list.

a = 1
-- MyConfig (Just 1) Nothing
MyConfig <$> getFieldOpt "a" <*> getFieldOpt "b"

getFieldsOpt :: DecodeTOML a => [Text] -> Decoder (Maybe a) Source #

Decode a nested field in a TOML Value, or Nothing if any of the fields don't exist.

a.b = 1
-- MyConfig (Just 1) Nothing Nothing
MyConfig
  <$> getFieldsOpt ["a", "b"]
  <*> getFieldsOpt ["a", "c"]
  <*> getFieldsOpt ["b", "c"]

getFieldWith :: Decoder a -> Text -> Decoder a Source #

Same as getField, except with the given Decoder.

getFieldsWith :: Decoder a -> [Text] -> Decoder a Source #

Same as getFields, except with the given Decoder.

getFieldOptWith :: Decoder a -> Text -> Decoder (Maybe a) Source #

Same as getFieldOpt, except with the given Decoder.

getFieldsOptWith :: Decoder a -> [Text] -> Decoder (Maybe a) Source #

Same as getFieldsOpt, except with the given Decoder.

getArrayOf :: Decoder a -> Decoder [a] Source #

Decode a list of values using the given Decoder.

[[a]]
b = 1

[[a]]
b = 2
-- MyConfig [1, 2]
MyConfig
  <$> getFieldWith (getArrayOf (getField "b")) "a"

Build custom Decoder

data DecodeM a Source #

The underlying decoding monad that either returns a value of type a or returns an error.

Instances

Instances details
Monad DecodeM Source # 
Instance details

Defined in TOML.Decode

Methods

(>>=) :: DecodeM a -> (a -> DecodeM b) -> DecodeM b #

(>>) :: DecodeM a -> DecodeM b -> DecodeM b #

return :: a -> DecodeM a #

Functor DecodeM Source # 
Instance details

Defined in TOML.Decode

Methods

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

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

MonadFail DecodeM Source # 
Instance details

Defined in TOML.Decode

Methods

fail :: String -> DecodeM a #

Applicative DecodeM Source # 
Instance details

Defined in TOML.Decode

Methods

pure :: a -> DecodeM a #

(<*>) :: DecodeM (a -> b) -> DecodeM a -> DecodeM b #

liftA2 :: (a -> b -> c) -> DecodeM a -> DecodeM b -> DecodeM c #

(*>) :: DecodeM a -> DecodeM b -> DecodeM b #

(<*) :: DecodeM a -> DecodeM b -> DecodeM a #

Alternative DecodeM Source # 
Instance details

Defined in TOML.Decode

Methods

empty :: DecodeM a #

(<|>) :: DecodeM a -> DecodeM a -> DecodeM a #

some :: DecodeM a -> DecodeM [a] #

many :: DecodeM a -> DecodeM [a] #

makeDecoder :: (Value -> DecodeM a) -> Decoder a Source #

Manually implement a Decoder with the given function.

runDecoder :: Decoder a -> Value -> DecodeM a Source #

Run a Decoder with the given Value.

makeDecoder $ \v -> do
  a <- runDecoder decoder1 v
  b <- runDecoder decoder2 v
  return (a, b)

Satisfies

makeDecoder . runDecoder === id
runDecoder . makeDecoder === id

invalidValue :: Text -> Value -> DecodeM a Source #

Throw an error indicating that the given Value is invalid.

makeDecoder $ \v ->
  case v of
    Integer 42 -> invalidValue "We don't like this number" v
    _ -> runDecoder tomlDecoder v

-- or alternatively,
tomlDecoder >>= case
  42 -> makeDecoder $ invalidValue "We don't like this number"
  v -> pure v

typeMismatch :: Value -> DecodeM a Source #

Throw an error indicating that the given Value isn't the correct type of value.

makeDecoder $ \v ->
  case v of
    String s -> ...
    _ -> typeMismatch v

decodeFail :: Text -> DecodeM a Source #

Throw a generic failure message.

TOML types

data Value Source #

Instances

Instances details
Eq Value Source # 
Instance details

Defined in TOML.Value

Methods

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

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

Show Value Source # 
Instance details

Defined in TOML.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

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 #

NFData Value Source # 
Instance details

Defined in TOML.Value

Methods

rnf :: Value -> () #

DecodeTOML Value Source # 
Instance details

Defined in TOML.Decode

type Rep Value Source # 
Instance details

Defined in TOML.Value

type Rep Value = D1 ('MetaData "Value" "TOML.Value" "toml-reader-0.1.0.0-J2PkHtEIoovITMoD1hWFGz" 'False) (((C1 ('MetaCons "Table" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Table)) :+: C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Value]))) :+: (C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (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 "Boolean" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "OffsetDateTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LocalTime, TimeZone)))) :+: (C1 ('MetaCons "LocalDateTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalTime)) :+: (C1 ('MetaCons "LocalDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :+: C1 ('MetaCons "LocalTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeOfDay))))))

renderValue :: Value -> Text Source #

Render a Value in pseudo-JSON format.

data TOMLError Source #

Instances

Instances details
Eq TOMLError Source # 
Instance details

Defined in TOML.Error

Show TOMLError Source # 
Instance details

Defined in TOML.Error

data NormalizeError Source #

Constructors

DuplicateKeyError

When a key is defined twice, e.g.

name = First
name = Second
DuplicateSectionError

When a section is defined twice, e.g.

[foo]
a = 1

[foo]
b = 2
ExtendTableError

When a key attempts to extend an invalid table

a = {}
[a.b]

b = {}
b.a = 1

c.x.x = 1
[c.a]
ExtendTableInInlineArrayError

When a section attempts to extend a table within an inline array

a = [{ b = 1 }]
[a.c]
ImplicitArrayForDefinedKeyError

When a key is already defined, but attempting to create an implicit array at the same key, e.g.

list = [1, 2, 3]

[[list]]
a = 1
NonTableInNestedKeyError

When a non-table value is already defined in a nested key, e.g.

a.b = 1
a.b.c.d = 2
NonTableInNestedImplicitArrayError

When a non-table value is already defined in a nested implicit array, e.g.

a.b = 1

[[a.b.c]]
d = 2

Instances

Instances details
Eq NormalizeError Source # 
Instance details

Defined in TOML.Error

Show NormalizeError Source # 
Instance details

Defined in TOML.Error

data ContextItem Source #

Constructors

Key Text 
Index Int 

Instances

Instances details
Eq ContextItem Source # 
Instance details

Defined in TOML.Error

Show ContextItem Source # 
Instance details

Defined in TOML.Error

data DecodeError Source #

Instances

Instances details
Eq DecodeError Source # 
Instance details

Defined in TOML.Error

Show DecodeError Source # 
Instance details

Defined in TOML.Error