{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module TOML.Error (
TOMLError (..),
NormalizeError (..),
DecodeContext,
ContextItem (..),
DecodeError (..),
renderTOMLError,
) where
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NonEmpty
import Data.Text (Text)
import qualified Data.Text as Text
import TOML.Value (Table, Value (..), renderValue)
data TOMLError
= ParseError Text
| NormalizeError NormalizeError
| DecodeError DecodeContext DecodeError
deriving (Int -> TOMLError -> ShowS
[TOMLError] -> ShowS
TOMLError -> String
(Int -> TOMLError -> ShowS)
-> (TOMLError -> String)
-> ([TOMLError] -> ShowS)
-> Show TOMLError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TOMLError] -> ShowS
$cshowList :: [TOMLError] -> ShowS
show :: TOMLError -> String
$cshow :: TOMLError -> String
showsPrec :: Int -> TOMLError -> ShowS
$cshowsPrec :: Int -> TOMLError -> ShowS
Show, TOMLError -> TOMLError -> Bool
(TOMLError -> TOMLError -> Bool)
-> (TOMLError -> TOMLError -> Bool) -> Eq TOMLError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TOMLError -> TOMLError -> Bool
$c/= :: TOMLError -> TOMLError -> Bool
== :: TOMLError -> TOMLError -> Bool
$c== :: TOMLError -> TOMLError -> Bool
Eq)
data NormalizeError
=
DuplicateKeyError
{ NormalizeError -> NonEmpty Text
_path :: NonEmpty Text
, NormalizeError -> Value
_existingValue :: Value
, NormalizeError -> Value
_valueToSet :: Value
}
|
DuplicateSectionError
{ NormalizeError -> NonEmpty Text
_sectionKey :: NonEmpty Text
}
|
ExtendTableError
{ _path :: NonEmpty Text
, NormalizeError -> NonEmpty Text
_originalKey :: NonEmpty Text
}
|
ExtendTableInInlineArrayError
{ _path :: NonEmpty Text
, _originalKey :: NonEmpty Text
}
|
ImplicitArrayForDefinedKeyError
{ _path :: NonEmpty Text
, _existingValue :: Value
, NormalizeError -> Table
_tableSection :: Table
}
|
NonTableInNestedKeyError
{ _path :: NonEmpty Text
, _existingValue :: Value
, _originalKey :: NonEmpty Text
, NormalizeError -> Value
_originalValue :: Value
}
|
NonTableInNestedImplicitArrayError
{ _path :: NonEmpty Text
, _existingValue :: Value
, _sectionKey :: NonEmpty Text
, _tableSection :: Table
}
deriving (Int -> NormalizeError -> ShowS
[NormalizeError] -> ShowS
NormalizeError -> String
(Int -> NormalizeError -> ShowS)
-> (NormalizeError -> String)
-> ([NormalizeError] -> ShowS)
-> Show NormalizeError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NormalizeError] -> ShowS
$cshowList :: [NormalizeError] -> ShowS
show :: NormalizeError -> String
$cshow :: NormalizeError -> String
showsPrec :: Int -> NormalizeError -> ShowS
$cshowsPrec :: Int -> NormalizeError -> ShowS
Show, NormalizeError -> NormalizeError -> Bool
(NormalizeError -> NormalizeError -> Bool)
-> (NormalizeError -> NormalizeError -> Bool) -> Eq NormalizeError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NormalizeError -> NormalizeError -> Bool
$c/= :: NormalizeError -> NormalizeError -> Bool
== :: NormalizeError -> NormalizeError -> Bool
$c== :: NormalizeError -> NormalizeError -> Bool
Eq)
type DecodeContext = [ContextItem]
data ContextItem = Key Text | Index Int
deriving (Int -> ContextItem -> ShowS
[ContextItem] -> ShowS
ContextItem -> String
(Int -> ContextItem -> ShowS)
-> (ContextItem -> String)
-> ([ContextItem] -> ShowS)
-> Show ContextItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContextItem] -> ShowS
$cshowList :: [ContextItem] -> ShowS
show :: ContextItem -> String
$cshow :: ContextItem -> String
showsPrec :: Int -> ContextItem -> ShowS
$cshowsPrec :: Int -> ContextItem -> ShowS
Show, ContextItem -> ContextItem -> Bool
(ContextItem -> ContextItem -> Bool)
-> (ContextItem -> ContextItem -> Bool) -> Eq ContextItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContextItem -> ContextItem -> Bool
$c/= :: ContextItem -> ContextItem -> Bool
== :: ContextItem -> ContextItem -> Bool
$c== :: ContextItem -> ContextItem -> Bool
Eq)
data DecodeError
= MissingField
| InvalidValue Text Value
| TypeMismatch Value
| OtherDecodeError Text
deriving (Int -> DecodeError -> ShowS
[DecodeError] -> ShowS
DecodeError -> String
(Int -> DecodeError -> ShowS)
-> (DecodeError -> String)
-> ([DecodeError] -> ShowS)
-> Show DecodeError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodeError] -> ShowS
$cshowList :: [DecodeError] -> ShowS
show :: DecodeError -> String
$cshow :: DecodeError -> String
showsPrec :: Int -> DecodeError -> ShowS
$cshowsPrec :: Int -> DecodeError -> ShowS
Show, DecodeError -> DecodeError -> Bool
(DecodeError -> DecodeError -> Bool)
-> (DecodeError -> DecodeError -> Bool) -> Eq DecodeError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodeError -> DecodeError -> Bool
$c/= :: DecodeError -> DecodeError -> Bool
== :: DecodeError -> DecodeError -> Bool
$c== :: DecodeError -> DecodeError -> Bool
Eq)
renderTOMLError :: TOMLError -> Text
renderTOMLError :: TOMLError -> Text
renderTOMLError = \case
ParseError Text
s -> Text
s
NormalizeError DuplicateKeyError{NonEmpty Text
Value
_valueToSet :: Value
_existingValue :: Value
_path :: NonEmpty Text
_valueToSet :: NormalizeError -> Value
_existingValue :: NormalizeError -> Value
_path :: NormalizeError -> NonEmpty Text
..} ->
[Text] -> Text
Text.unlines
[ Text
"Could not add value to path " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_path Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":"
, Text
" Existing value: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue Value
_existingValue
, Text
" Value to set: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue Value
_valueToSet
]
NormalizeError DuplicateSectionError{NonEmpty Text
_sectionKey :: NonEmpty Text
_sectionKey :: NormalizeError -> NonEmpty Text
..} -> Text
"Found duplicate section: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_sectionKey
NormalizeError ExtendTableError{NonEmpty Text
_originalKey :: NonEmpty Text
_path :: NonEmpty Text
_originalKey :: NormalizeError -> NonEmpty Text
_path :: NormalizeError -> NonEmpty Text
..} ->
[Text] -> Text
Text.unlines
[ Text
"Invalid table key: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_originalKey
, Text
" Table already statically defined at " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_path
]
NormalizeError ExtendTableInInlineArrayError{NonEmpty Text
_originalKey :: NonEmpty Text
_path :: NonEmpty Text
_originalKey :: NormalizeError -> NonEmpty Text
_path :: NormalizeError -> NonEmpty Text
..} ->
[Text] -> Text
Text.unlines
[ Text
"Invalid table key: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_originalKey
, Text
" Table defined in inline array at " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_path
]
NormalizeError ImplicitArrayForDefinedKeyError{NonEmpty Text
Table
Value
_tableSection :: Table
_existingValue :: Value
_path :: NonEmpty Text
_tableSection :: NormalizeError -> Table
_existingValue :: NormalizeError -> Value
_path :: NormalizeError -> NonEmpty Text
..} ->
[Text] -> Text
Text.unlines
[ Text
"Could not create implicit array at path " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_path Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":"
, Text
" Existing value: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue Value
_existingValue
, Text
" Array table section: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue (Table -> Value
Table Table
_tableSection)
]
NormalizeError NonTableInNestedKeyError{NonEmpty Text
Value
_originalValue :: Value
_originalKey :: NonEmpty Text
_existingValue :: Value
_path :: NonEmpty Text
_originalValue :: NormalizeError -> Value
_originalKey :: NormalizeError -> NonEmpty Text
_existingValue :: NormalizeError -> Value
_path :: NormalizeError -> NonEmpty Text
..} ->
[Text] -> Text
Text.unlines
[ Text
"Found non-Table at path " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_path Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" when defining nested key " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_originalKey Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":"
, Text
" Existing value: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue Value
_existingValue
, Text
" Original value: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue Value
_originalValue
]
NormalizeError NonTableInNestedImplicitArrayError{NonEmpty Text
Table
Value
_tableSection :: Table
_sectionKey :: NonEmpty Text
_existingValue :: Value
_path :: NonEmpty Text
_tableSection :: NormalizeError -> Table
_sectionKey :: NormalizeError -> NonEmpty Text
_existingValue :: NormalizeError -> Value
_path :: NormalizeError -> NonEmpty Text
..} ->
[Text] -> Text
Text.unlines
[ Text
"Found non-Table at path " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_path Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" when initializing implicit array at path " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NonEmpty Text -> Text
showPath NonEmpty Text
_sectionKey Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":"
, Text
" Existing value: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue Value
_existingValue
, Text
" Array table section: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue (Table -> Value
Table Table
_tableSection)
]
DecodeError [ContextItem]
ctx DecodeError
e -> Text
"Decode error at '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [ContextItem] -> Text
renderDecodeContext [ContextItem]
ctx Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"': " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> DecodeError -> Text
renderDecodeError DecodeError
e
where
showPath :: NonEmpty Text -> Text
showPath NonEmpty Text
path = Text
"\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
Text.intercalate Text
"." (NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
NonEmpty.toList NonEmpty Text
path) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
renderDecodeError :: DecodeError -> Text
renderDecodeError = \case
DecodeError
MissingField -> Text
"Field does not exist"
InvalidValue Text
msg Value
v -> Text
"Invalid value: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
msg Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
": " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue Value
v
TypeMismatch Value
v -> Text
"Type mismatch, got: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue Value
v
OtherDecodeError Text
msg -> Text
msg
renderDecodeContext :: [ContextItem] -> Text
renderDecodeContext = [Text] -> Text
Text.concat ([Text] -> Text)
-> ([ContextItem] -> [Text]) -> [ContextItem] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ContextItem -> Text) -> [ContextItem] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ContextItem -> Text
renderContextItem
renderContextItem :: ContextItem -> Text
renderContextItem = \case
Key Text
k -> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
k
Index Int
i -> Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (Int -> String
forall a. Show a => a -> String
show Int
i) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"