{-# Language GADTs, OverloadedStrings, CPP #-}
module Config.Schema.Load.Error
(
ValueSpecMismatch(..)
, PrimMismatch(..)
, Problem(..)
, ErrorAnnotation(..)
, prettyValueSpecMismatch
, prettyPrimMismatch
, prettyProblem
, describeSpec
, describeValue
, simplifyValueSpecMismatch
) where
import Control.Exception
import Data.Text (Text)
import Data.Foldable (toList)
import qualified Data.Text as Text
import Data.List.NonEmpty (NonEmpty((:|)))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Typeable (Typeable)
import Text.PrettyPrint
(Doc, fsep, ($+$), nest, text, vcat, (<+>), empty,
punctuate, comma, int, colon, hcat)
import Config
import Config.Macro (FilePosition(..))
import Config.Schema.Types
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid ((<>))
#endif
data ValueSpecMismatch p =
ValueSpecMismatch p Text (NonEmpty (PrimMismatch p))
deriving Show
data PrimMismatch p =
PrimMismatch Text (Problem p)
deriving Show
data Problem p
= MissingSection Text
| UnusedSections (NonEmpty Text)
| SubkeyProblem Text (ValueSpecMismatch p)
| ListElementProblem Int (ValueSpecMismatch p)
| NestedProblem (ValueSpecMismatch p)
| TypeMismatch
| CustomProblem Text
| WrongAtom
deriving Show
describeSpec :: PrimValueSpec a -> Text
describeSpec TextSpec = "text"
describeSpec NumberSpec = "number"
describeSpec AnyAtomSpec = "atom"
describeSpec (AtomSpec a) = "atom `" <> a <> "`"
describeSpec (ListSpec _) = "list"
describeSpec (SectionsSpec name _) = name
describeSpec (AssocSpec _) = "sections"
describeSpec (CustomSpec name _) = name
describeSpec (NamedSpec name _) = name
describeValue :: Value p -> Text
describeValue Text{} = "text"
describeValue Number{} = "number"
describeValue (Atom _ a) = "atom `" <> atomName a <> "`"
describeValue Sections{} = "sections"
describeValue List{} = "list"
rewriteMismatch ::
(ValueSpecMismatch p -> ValueSpecMismatch p) ->
ValueSpecMismatch p -> ValueSpecMismatch p
rewriteMismatch f (ValueSpecMismatch p v prims) = f (ValueSpecMismatch p v (fmap aux1 prims))
where
aux1 (PrimMismatch spec prob) = PrimMismatch spec (aux2 prob)
aux2 (SubkeyProblem x y) = SubkeyProblem x (rewriteMismatch f y)
aux2 (ListElementProblem x y) = ListElementProblem x (rewriteMismatch f y)
aux2 (NestedProblem y) = NestedProblem (rewriteMismatch f y)
aux2 prob = prob
removeTypeMismatch1 :: ValueSpecMismatch p -> ValueSpecMismatch p
removeTypeMismatch1 (ValueSpecMismatch p v xs)
| Just xs' <- NonEmpty.nonEmpty (NonEmpty.filter (not . isTypeMismatch) xs)
= ValueSpecMismatch p v xs'
removeTypeMismatch1 v = v
isTypeMismatch :: PrimMismatch p -> Bool
isTypeMismatch (PrimMismatch _ prob) =
case prob of
WrongAtom -> True
TypeMismatch -> True
NestedProblem (ValueSpecMismatch _ _ xs) -> all isTypeMismatch xs
_ -> False
focusMismatch1 :: ValueSpecMismatch p -> ValueSpecMismatch p
focusMismatch1 x@(ValueSpecMismatch _ _ prims)
| PrimMismatch _ problem :| [] <- prims
, Just sub <- simplify1 problem = sub
| otherwise = x
where
simplify1 (SubkeyProblem _ p) = Just p
simplify1 (ListElementProblem _ p) = Just p
simplify1 (NestedProblem p) = Just p
simplify1 _ = Nothing
prettyValueSpecMismatch :: ErrorAnnotation p => ValueSpecMismatch p -> Doc
prettyValueSpecMismatch (ValueSpecMismatch p v es) =
heading $+$ errors
where
heading = displayAnnotation p <> text (Text.unpack v)
errors = vcat (map prettyPrimMismatch (toList es))
prettyPrimMismatch :: ErrorAnnotation p => PrimMismatch p -> Doc
prettyPrimMismatch (PrimMismatch spec problem) =
case prettyProblem problem of
(summary, detail) ->
(text "* expected" <+> text (Text.unpack spec) <+> summary) $+$ nest 4 detail
simplifyValueSpecMismatch :: ValueSpecMismatch p -> ValueSpecMismatch p
simplifyValueSpecMismatch = rewriteMismatch (focusMismatch1 . removeTypeMismatch1)
prettyProblem ::
ErrorAnnotation p =>
Problem p ->
(Doc, Doc)
prettyProblem p =
case p of
TypeMismatch ->
( text "- type mismatch"
, empty)
WrongAtom ->
( text "- wrong atom"
, empty)
MissingSection name ->
( text "- missing section:" <+> text (Text.unpack name)
, empty)
UnusedSections names ->
( text "- unexpected sections:" <+>
fsep (punctuate comma (map (text . Text.unpack) (toList names)))
, empty)
CustomProblem e ->
( text "-" <+> text (Text.unpack e)
, empty)
SubkeyProblem name e ->
( text "- problem in section:" <+> text (Text.unpack name)
, prettyValueSpecMismatch e)
NestedProblem e ->
( empty
, prettyValueSpecMismatch e)
ListElementProblem i e ->
( text "- problem in element:" <+> int i
, prettyValueSpecMismatch e)
class (Typeable a, Show a) => ErrorAnnotation a where
displayAnnotation :: a -> Doc
instance ErrorAnnotation Position where
displayAnnotation pos = hcat [int (posLine pos), colon, int (posColumn pos), colon]
instance ErrorAnnotation FilePosition where
displayAnnotation (FilePosition path pos) = hcat [text path, colon, int (posLine pos), colon, int (posColumn pos), colon]
instance ErrorAnnotation () where
displayAnnotation _ = empty
instance ErrorAnnotation p => Exception (ValueSpecMismatch p) where
displayException = show . prettyValueSpecMismatch . simplifyValueSpecMismatch