Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- decode :: DecodeTOML a => Text -> Either TOMLError a
- decodeWith :: Decoder a -> Text -> Either TOMLError a
- decodeFile :: DecodeTOML a => FilePath -> IO (Either TOMLError a)
- class DecodeTOML a where
- tomlDecoder :: Decoder a
- data Decoder a
- getField :: DecodeTOML a => Text -> Decoder a
- getFields :: DecodeTOML a => [Text] -> Decoder a
- getFieldOpt :: DecodeTOML a => Text -> Decoder (Maybe a)
- getFieldsOpt :: DecodeTOML a => [Text] -> Decoder (Maybe a)
- getFieldWith :: Decoder a -> Text -> Decoder a
- getFieldsWith :: Decoder a -> [Text] -> Decoder a
- getFieldOptWith :: Decoder a -> Text -> Decoder (Maybe a)
- getFieldsOptWith :: Decoder a -> [Text] -> Decoder (Maybe a)
- getArrayOf :: Decoder a -> Decoder [a]
- data DecodeM a
- makeDecoder :: (Value -> DecodeM a) -> Decoder a
- runDecoder :: Decoder a -> Value -> DecodeM a
- invalidValue :: Text -> Value -> DecodeM a
- typeMismatch :: Value -> DecodeM a
- decodeFail :: Text -> DecodeM a
- data Value
- renderValue :: Value -> Text
- type Table = Map Text Value
- data TOMLError
- data NormalizeError
- = DuplicateKeyError {
- _path :: NonEmpty Text
- _existingValue :: Value
- _valueToSet :: Value
- | DuplicateSectionError { }
- | ExtendTableError { }
- | ExtendTableInInlineArrayError { }
- | ImplicitArrayForDefinedKeyError { }
- | NonTableInNestedKeyError { }
- | NonTableInNestedImplicitArrayError { }
- = DuplicateKeyError {
- type DecodeContext = [ContextItem]
- data ContextItem
- data DecodeError
- renderTOMLError :: TOMLError -> Text
Decoding a TOML file
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.
tomlDecoder :: Decoder a Source #
Instances
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
.
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"]
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
The underlying decoding monad that either returns a value of type a
or returns an error.
makeDecoder :: (Value -> DecodeM a) -> Decoder a Source #
Manually implement a Decoder
with the given function.
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
Table Table | |
Array [Value] | |
String Text | |
Integer Integer | |
Float Double | |
Boolean Bool | |
OffsetDateTime (LocalTime, TimeZone) | |
LocalDateTime LocalTime | |
LocalDate Day | |
LocalTime TimeOfDay |
Instances
renderValue :: Value -> Text Source #
Render a Value in pseudo-JSON format.
data NormalizeError Source #
DuplicateKeyError | When a key is defined twice, e.g. name = |
| |
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
Eq NormalizeError Source # | |
Defined in TOML.Error (==) :: NormalizeError -> NormalizeError -> Bool # (/=) :: NormalizeError -> NormalizeError -> Bool # | |
Show NormalizeError Source # | |
Defined in TOML.Error showsPrec :: Int -> NormalizeError -> ShowS # show :: NormalizeError -> String # showList :: [NormalizeError] -> ShowS # |
type DecodeContext = [ContextItem] Source #
data ContextItem Source #
Instances
Eq ContextItem Source # | |
Defined in TOML.Error (==) :: ContextItem -> ContextItem -> Bool # (/=) :: ContextItem -> ContextItem -> Bool # | |
Show ContextItem Source # | |
Defined in TOML.Error showsPrec :: Int -> ContextItem -> ShowS # show :: ContextItem -> String # showList :: [ContextItem] -> ShowS # |
data DecodeError Source #
Instances
Eq DecodeError Source # | |
Defined in TOML.Error (==) :: DecodeError -> DecodeError -> Bool # (/=) :: DecodeError -> DecodeError -> Bool # | |
Show DecodeError Source # | |
Defined in TOML.Error showsPrec :: Int -> DecodeError -> ShowS # show :: DecodeError -> String # showList :: [DecodeError] -> ShowS # |
renderTOMLError :: TOMLError -> Text Source #