Skip to content

Commit

Permalink
Embed JVMSetupError inside TopLevelException datatype.
Browse files Browse the repository at this point in the history
This means that JVMSetupError exceptions can now be caught by
the standard TopLevelException handlers, and get shown with
the expected stack traces in the saw-script REPL.

This is done using a new existentially-typed `SomeTopLevelException`
constructor, as recommended by the Control.Exception documentation.

Fixes #1021.
  • Loading branch information
Brian Huffman committed Feb 23, 2021
1 parent 7b71012 commit 090b21c
Show file tree
Hide file tree
Showing 2 changed files with 27 additions and 1 deletion.
5 changes: 4 additions & 1 deletion src/SAWScript/Crucible/JVM/Builtins.hs
Original file line number Diff line number Diff line change
Expand Up @@ -98,6 +98,7 @@ import Verifier.SAW.TypedTerm

import Verifier.SAW.Simulator.What4.ReturnTrip

import SAWScript.Exceptions
import SAWScript.Proof
import SAWScript.Prover.SolverStats
import SAWScript.TopLevel
Expand Down Expand Up @@ -813,7 +814,9 @@ data JVMSetupError
| JVMReturnUnexpected J.Type -- found
| JVMReturnTypeMismatch J.Type J.Type -- expected, found

instance X.Exception JVMSetupError
instance X.Exception JVMSetupError where
toException = topLevelExceptionToException
fromException = topLevelExceptionFromException

instance Show JVMSetupError where
show err =
Expand Down
23 changes: 23 additions & 0 deletions src/SAWScript/Exceptions.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,16 @@
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}

module SAWScript.Exceptions
( TypeErrors(..), failTypecheck
, TopLevelException(..)
, TraceException(..)
, topLevelExceptionToException
, topLevelExceptionFromException
) where

import Control.Exception
import Data.Typeable (cast)

import What4.ProgramLoc (ProgramLoc)

Expand All @@ -31,13 +36,31 @@ data TopLevelException
| CrucibleSetupException ProgramLoc String
| OverrideMatcherException ProgramLoc String
| LLVMMethodSpecException ProgramLoc String
| forall e. Exception e => SomeTopLevelException e

instance Show TopLevelException where
show (TopLevelException _ msg) = msg
show (JavaException _ msg) = msg
show (CrucibleSetupException _ msg) = msg
show (OverrideMatcherException _ msg) = msg
show (LLVMMethodSpecException _ msg) = msg
show (SomeTopLevelException e) = show e

-- | To use a custom structured exception type that works with the
-- saw-script REPL's exception handlers and stack tracing, define
-- 'toException' as 'topLevelExceptionToException' in the custom
-- exception type's 'Exception' class instance.
topLevelExceptionToException :: Exception e => e -> SomeException
topLevelExceptionToException = toException . SomeTopLevelException

-- | To use a custom structured exception type that works with the
-- saw-script REPL's exception handlers and stack tracing, define
-- 'fromException' as 'topLevelExceptionFromException' in the custom
-- exception type's 'Exception' class instance.
topLevelExceptionFromException :: Exception e => SomeException -> Maybe e
topLevelExceptionFromException x =
do SomeTopLevelException a <- fromException x
cast a

instance Exception TopLevelException

Expand Down

0 comments on commit 090b21c

Please sign in to comment.