{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveTraversable #-} -- | Diagnostics - errors, warnings, and the result of interpreting a -- program. module Descript.Misc.Build.Process.Diagnose ( DiagType (..) , Diagnostic (..) , getDiagType ) where import Descript.Misc.Build.Process.Validate import Descript.Misc.Ann import Descript.Misc.Summary import Data.Text (Text) import qualified Data.Text as Text -- | What type of diagnostic this is. data DiagType = DiagProblemType | DiagEvalType deriving (Eq, Ord, Read, Show) -- | Describes a piece of source - whether it's valid, what it -- evaluates into, etc.. data Diagnostic an = DiagProblem (Problem an) | DiagEval an Text deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable) instance Ann Diagnostic where getAnn (DiagProblem prob) = getAnn prob getAnn (DiagEval ann _) = ann instance SummaryWithAnn Diagnostic where baseSummary (DiagProblem prob) = baseSummary prob baseSummary (DiagEval _ x) = Text.unpack x instance (AnnSummary an) => Summary (Diagnostic an) where summary = summaryWithAnn -- | Gets the diagnostic's type. getDiagType :: Diagnostic an -> DiagType getDiagType (DiagProblem _) = DiagProblemType getDiagType (DiagEval _ _) = DiagEvalType