Skip to content

Commit a0aac45

Browse files
ttuegelandreiburdusarv-jenkins
authored
Add context to some error messages (#2017)
* Add Pretty.prettyException * Add ErrorContext * Kore.Internal.Condition.fromNormalizationSimplified: withErrorContext * Kore.Internal.Substitution.unsafeWrap: withErrorContext * Small cleanup * Add HasCallStack to unsafeWrapFromAssignments * Update kore/src/Kore/Internal/Substitution.hs Co-authored-by: andreiburdusa <andrei.burdusa@zoho.com> Co-authored-by: rv-jenkins <admin@runtimeverification.com>
1 parent c41d860 commit a0aac45

File tree

4 files changed

+119
-6
lines changed

4 files changed

+119
-6
lines changed

kore/src/ErrorContext.hs

Lines changed: 61 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,61 @@
1+
{- |
2+
Copyright : (c) Runtime Verification, 2020
3+
License : NCSA
4+
5+
-}
6+
7+
module ErrorContext
8+
( ErrorContext (..)
9+
, withErrorContext
10+
) where
11+
12+
import Prelude
13+
14+
import Control.Exception
15+
( Exception (..)
16+
, SomeException
17+
, mapException
18+
)
19+
import Data.String
20+
( fromString
21+
)
22+
import Data.Typeable
23+
( Typeable
24+
)
25+
26+
import Pretty
27+
( Pretty
28+
)
29+
import qualified Pretty
30+
31+
data ErrorContext where
32+
ErrorContext
33+
:: (Pretty context, Show context)
34+
=> String -- ^ A brief message (one line) introducing the context.
35+
-> context -- ^ Some 'Pretty'-printable data for context.
36+
-> SomeException -- ^ The error itself.
37+
-> ErrorContext
38+
deriving (Typeable)
39+
40+
deriving instance Show ErrorContext
41+
42+
instance Pretty ErrorContext where
43+
pretty (ErrorContext intro context someException) =
44+
Pretty.vsep
45+
[ fromString intro
46+
, Pretty.indent 4 (Pretty.pretty context)
47+
, Pretty.prettyException someException
48+
]
49+
50+
instance Exception ErrorContext where
51+
displayException = show . Pretty.pretty
52+
53+
{- | Compute a value, putting error messages in context.
54+
-}
55+
withErrorContext
56+
:: (Pretty context, Show context)
57+
=> String
58+
-> context
59+
-> a -- ^ The value computed.
60+
-> a
61+
withErrorContext intro context = mapException (ErrorContext intro context)

kore/src/Kore/Internal/Condition.hs

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,7 @@ module Kore.Internal.Condition
3737

3838
import Prelude.Kore
3939

40+
import ErrorContext
4041
import Kore.Attribute.Pattern.FreeVariables
4142
( freeVariables
4243
, isFreeVariable
@@ -182,11 +183,15 @@ The 'normalized' part becomes the normalized 'substitution', while the
182183
183184
-}
184185
fromNormalizationSimplified
185-
:: InternalVariable variable
186+
:: HasCallStack
187+
=> InternalVariable variable
186188
=> Normalization variable
187189
-> Condition variable
188-
fromNormalizationSimplified Normalization { normalized, denormalized } =
190+
fromNormalizationSimplified
191+
normalization@Normalization { normalized, denormalized }
192+
=
189193
predicate' <> substitution'
194+
& withErrorContext "while normalizing substitution" normalization
190195
where
191196
predicate' =
192197
Conditional.fromPredicate
@@ -195,7 +200,7 @@ fromNormalizationSimplified Normalization { normalized, denormalized } =
195200
$ Substitution.wrap denormalized
196201
substitution' =
197202
Conditional.fromSubstitution
198-
$ Substitution.unsafeWrap (Substitution.assignmentToPair <$> normalized)
203+
$ Substitution.unsafeWrapFromAssignments normalized
199204
markSimplifiedIfChildrenSimplified childrenList result =
200205
Predicate.setSimplified childrenSimplified result
201206
where

kore/src/Kore/Internal/Substitution.hs

Lines changed: 37 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,7 @@ import qualified Data.Set as Set
6969
import qualified Generics.SOP as SOP
7070
import qualified GHC.Generics as GHC
7171

72+
import ErrorContext
7273
import Kore.Attribute.Pattern.FreeVariables as FreeVariables
7374
import qualified Kore.Attribute.Pattern.Simplified as Attribute
7475
( Simplified (..)
@@ -92,7 +93,12 @@ import Kore.TopBottom
9293
( TopBottom (..)
9394
)
9495
import Kore.Unparser
95-
( unparseToString
96+
( Unparse
97+
, unparse
98+
, unparseToString
99+
)
100+
import Pretty
101+
( Pretty
96102
)
97103
import qualified Pretty
98104
import qualified SQL
@@ -118,6 +124,14 @@ instance NFData variable => NFData (Assignment variable)
118124

119125
instance Hashable variable => Hashable (Assignment variable)
120126

127+
instance (Ord variable, Unparse variable) => Pretty (Assignment variable) where
128+
pretty Assignment_ { assignedVariable, assignedTerm } =
129+
Pretty.vsep
130+
[ Pretty.hsep ["assigned variable:", unparse assignedVariable]
131+
, "assigned term:"
132+
, Pretty.indent 4 (unparse assignedTerm)
133+
]
134+
121135
-- | Smart constructor for 'Assignment'. It enforces the invariant
122136
-- that for variable renaming, the smaller variable will be on the
123137
-- left of the substitution.
@@ -419,7 +433,7 @@ wrap xs = Substitution xs
419433
-- this unless you are sure you need it.
420434
unsafeWrap
421435
:: HasCallStack
422-
=> Ord variable
436+
=> InternalVariable variable
423437
=> [(SomeVariable variable, TermLike variable)]
424438
-> Substitution variable
425439
unsafeWrap =
@@ -436,15 +450,18 @@ unsafeWrap =
436450
& assert (not $ any depends $ Map.keys subst)
437451
-- and if this is an element variable substitution, the substitution
438452
-- must be defined.
453+
-- TODO (thomas.tuegel): isBottom -> isDefinedPattern
439454
& assert (not $ isElementVariable var && isBottom termLike)
455+
& withErrorContext "while wrapping substitution" (assign var termLike)
440456
where
441457
Variable { variableName } = var
442458
occurs = TermLike.hasFreeVariable variableName
443459
depends Variable { variableName = variableName' } =
444460
TermLike.hasFreeVariable variableName' termLike
445461

446462
unsafeWrapFromAssignments
447-
:: Ord variable
463+
:: HasCallStack
464+
=> InternalVariable variable
448465
=> [Assignment variable]
449466
-> Substitution variable
450467
unsafeWrapFromAssignments =
@@ -678,6 +695,23 @@ instance Semigroup (Normalization variable) where
678695
instance Monoid (Normalization variable) where
679696
mempty = Normalization mempty mempty
680697

698+
instance InternalVariable variable => Pretty (Normalization variable) where
699+
pretty Normalization { normalized, denormalized } =
700+
Pretty.vsep
701+
[ "normalized:"
702+
, (Pretty.indent 4 . Pretty.vsep) (map prettyPair normalized)
703+
, "denormalized:"
704+
, (Pretty.indent 4 . Pretty.vsep) (map prettyPair denormalized)
705+
]
706+
where
707+
prettyPair assignment =
708+
Pretty.vsep
709+
[ "variable:"
710+
, Pretty.indent 4 (unparse $ assignedVariable assignment)
711+
, "term:"
712+
, Pretty.indent 4 (unparse $ assignedTerm assignment)
713+
]
714+
681715
mkNormalization
682716
:: InternalVariable variable
683717
=> [(SomeVariable variable, TermLike variable)]

kore/src/Pretty.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,10 +11,18 @@ module Pretty
1111
, renderString
1212
, renderIO
1313
, hPutDoc, putDoc
14+
, prettyException
1415
) where
1516

1617
import Prelude.Kore
1718

19+
import Control.Exception
20+
( Exception
21+
, displayException
22+
)
23+
import Data.String
24+
( fromString
25+
)
1826
import Data.Text
1927
( Text
2028
)
@@ -52,3 +60,8 @@ flattenSimpleDocStream = worker
5260

5361
renderText :: SimpleDocStream ann -> Text
5462
renderText = renderStrict
63+
64+
{- | Display an 'Exception' nicely for the user.
65+
-}
66+
prettyException :: Exception exn => exn -> Doc ann
67+
prettyException = vsep . map fromString . lines . displayException

0 commit comments

Comments
 (0)