crucible-debug-0.1.0: An interactive debugger for Crucible programs
Copyright(c) Galois Inc. 2025
MaintainerLangston Barrett <langston@galois.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lang.Crucible.Debug

Description

 
Synopsis

Documentation

debugger :: sym ~ ExprBuilder s st fs => IsSymInterface sym => IsSyntaxExtension ext => IsExpr (SymExpr sym) => (?parserHooks :: ParserHooks ext) => Pretty cExt => CommandExt cExt -> ExtImpl cExt p sym ext t -> IntrinsicPrinters sym -> Inputs (CompletionT cExt (StyleT cExt IO)) (Statement cExt) -> Outputs IO (Response cExt) -> TypeRepr t -> IO (ExecutionFeature p sym ext (RegEntry sym t)) Source #

bareDebuggerExt :: IsSyntaxExtension ext => (?parserHooks :: ParserHooks ext) => Pretty cExt => CommandExt cExt -> (forall p sym t. IsSymInterface sym => ExtImpl cExt p sym ext t) -> (forall p sym. IsSymInterface sym => ExtensionImpl p sym ext) -> Inputs (CompletionT cExt (StyleT cExt IO)) (Statement cExt) -> Outputs IO (Response cExt) -> (Text -> IO ()) -> IO () Source #

Like bareDebugger, but with a syntax extension

bareDebugger :: Inputs (CompletionT Void (StyleT Void IO)) (Statement Void) -> Outputs IO (Response Void) -> (Text -> IO ()) -> IO () Source #

Start a debugger instance in an empty Crucible program.

The Crucible program simply returns the unit value. The idea is to use the Load and Call commands to actually run some Crucible CFG(s).

Proves obligations using Z3.

defaultDebuggerInputs :: MonadIO m => CommandExt cExt -> IO (Inputs (CompletionT cExt (StyleT cExt m)) (Statement cExt)) Source #

data Arg cExt i where Source #

Constructors

ABreakpoint :: Breakpoint -> Arg cExt 'TBreakpoint 
ACommand :: Command cExt -> Arg cExt 'TCommand 
AExactly :: SymbolRepr s -> Arg cExt ('TExactly s) 
AFunction :: FunctionName -> Arg cExt 'TFunction 
AInt :: Int -> Arg cExt 'TInt 
APath :: Text -> Arg cExt 'TPath 
AText :: Text -> Arg cExt 'TText 

data ArgTypeRepr i where Source #

Value-level representative of ArgType

Constructors

TBreakpointRepr :: ArgTypeRepr 'TBreakpoint 
TCommandRepr :: ArgTypeRepr 'TCommand 
TExactlyRepr :: SymbolRepr s -> ArgTypeRepr ('TExactly s) 
TFunctionRepr :: ArgTypeRepr 'TFunction 
TIntRepr :: ArgTypeRepr 'TInt 
TPathRepr :: ArgTypeRepr 'TPath 
TTextRepr :: ArgTypeRepr 'TText 

Instances

Instances details
Show (ArgTypeRepr t) Source # 
Instance details

Defined in Lang.Crucible.Debug.Arg.Type

Pretty (ArgTypeRepr t) Source # 
Instance details

Defined in Lang.Crucible.Debug.Arg.Type

Methods

pretty :: ArgTypeRepr t -> Doc ann #

prettyList :: [ArgTypeRepr t] -> Doc ann #

type Breakpoint = Lit 'TBreakpoint Source #

type Exactly s = Lit ('TExactly s) Source #

type Function = Lit 'TFunction Source #

type Int = Lit 'TInt Source #

type Path = Lit 'TPath Source #

type Text = Lit 'TText Source #

data Command cExt Source #

Constructors

Base BaseCommand 
Ext cExt 

Instances

Instances details
Functor Command Source # 
Instance details

Defined in Lang.Crucible.Debug.Command

Methods

fmap :: (a -> b) -> Command a -> Command b #

(<$) :: a -> Command b -> Command a #

Show cExt => Show (Command cExt) Source # 
Instance details

Defined in Lang.Crucible.Debug.Command

Methods

showsPrec :: Int -> Command cExt -> ShowS #

show :: Command cExt -> String #

showList :: [Command cExt] -> ShowS #

Pretty cExt => Pretty (Command cExt) Source # 
Instance details

Defined in Lang.Crucible.Debug.Command

Methods

pretty :: Command cExt -> Doc ann #

prettyList :: [Command cExt] -> Doc ann #

data CommandExt cExt Source #

Constructors

CommandExt 

Fields

  • extAbbrev :: cExt -> Text

    Used in abbrev, parse

  • extList :: [cExt]
     
  • extDetail :: cExt -> Maybe Text

    Multi-line help string. Used in detail.

    This is always displayed as a new paragraph following extHelp, so it should not repeat the information there.

    Should be long-form prose, with proper capitalization and punctuation. Should not rely on being shown in monospaced font.

  • extHelp :: cExt -> Text

    Single-line help string. Used in help.

    The first letter should be capitalized, it should not end in a period. It should probably be less than about 70 characters long.

  • extName :: cExt -> Text

    Used in help, parse

  • extRegex :: cExt -> Some (RegexRepr ArgTypeRepr)

    Used in help

data EvalResult cExt p sym ext t Source #

The result of evaluating a Statement

Constructors

EvalResult 

Fields

data Context cExt p sym ext t Source #

Debugger state.

Type parameters:

  • cExt is the command extension type, see CommandExt
  • p, sym, ext are as in OverrideSim
  • t is the Crucible type of the RegValue returned by the program

cExt is different from ext because it's not necessarily true that you would want the debugger command extensions to be tied in a 1:1 fashion with the syntax extension (source language).

Constructors

Context 

Fields

data CommandImpl cExt p sym ext t Source #

Constructors

forall r. CommandImpl 

Fields

newtype ExtImpl cExt p sym ext t Source #

Constructors

ExtImpl 

Fields

voidImpl :: ExtImpl Void p sym ext t Source #

data Response cExt Source #

Constructors

Ok 
UserError (UserError cExt) 
XResponse (ResponseExt cExt) 

Instances

Instances details
(Show (ResponseExt cExt), Show cExt) => Show (Response cExt) Source # 
Instance details

Defined in Lang.Crucible.Debug.Response

Methods

showsPrec :: Int -> Response cExt -> ShowS #

show :: Response cExt -> String #

showList :: [Response cExt] -> ShowS #

(Pretty (ResponseExt cExt), Pretty cExt) => Pretty (Response cExt) Source # 
Instance details

Defined in Lang.Crucible.Debug.Response

Methods

pretty :: Response cExt -> Doc ann #

prettyList :: [Response cExt] -> Doc ann #

data UserError cExt Source #

The command could not be completed successfully for some reason the user should have anticipated.

Instances

Instances details
Show cExt => Show (UserError cExt) Source # 
Instance details

Defined in Lang.Crucible.Debug.Response

Methods

showsPrec :: Int -> UserError cExt -> ShowS #

show :: UserError cExt -> String #

showList :: [UserError cExt] -> ShowS #

Pretty cExt => Pretty (UserError cExt) Source # 
Instance details

Defined in Lang.Crucible.Debug.Response

Methods

pretty :: UserError cExt -> Doc ann #

prettyList :: [UserError cExt] -> Doc ann #

data NotApplicable Source #

The command was not applicable in this state

Instances

Instances details
Show NotApplicable Source # 
Instance details

Defined in Lang.Crucible.Debug.Response

Pretty NotApplicable Source # 
Instance details

Defined in Lang.Crucible.Debug.Response

Methods

pretty :: NotApplicable -> Doc ann #

prettyList :: [NotApplicable] -> Doc ann #

type family ResponseExt cExt :: Type Source #

Instances

Instances details
type ResponseExt Void Source # 
Instance details

Defined in Lang.Crucible.Debug.Response

data Regex a Source #

Type-level only

Instances

Instances details
FoldableFC (RegexRepr :: (k -> Type) -> Regex k -> Type) Source # 
Instance details

Defined in Lang.Crucible.Debug.Regex

Methods

foldMapFC :: forall f m. Monoid m => (forall (x :: k0). f x -> m) -> forall (x :: l). RegexRepr f x -> m #

foldrFC :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> RegexRepr f x -> b #

foldlFC :: forall f b. (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> RegexRepr f x -> b #

foldrFC' :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> RegexRepr f x -> b #

foldlFC' :: forall f b. (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> RegexRepr f x -> b #

toListFC :: (forall (x :: k0). f x -> a) -> forall (x :: l). RegexRepr f x -> [a] #

FunctorFC (RegexRepr :: (k -> Type) -> Regex k -> Type) Source # 
Instance details

Defined in Lang.Crucible.Debug.Regex

Methods

fmapFC :: (forall (x :: k0). f x -> g x) -> forall (x :: l). RegexRepr f x -> RegexRepr g x #

TraversableFC (RegexRepr :: (k -> Type) -> Regex k -> Type) Source # 
Instance details

Defined in Lang.Crucible.Debug.Regex

Methods

traverseFC :: forall f g m. Applicative m => (forall (x :: k0). f x -> m (g x)) -> forall (x :: l). RegexRepr f x -> m (RegexRepr g x) #

TestEquality f => TestEquality (RegexRepr f :: Regex k -> Type) Source # 
Instance details

Defined in Lang.Crucible.Debug.Regex

Methods

testEquality :: forall (a :: k0) (b :: k0). RegexRepr f a -> RegexRepr f b -> Maybe (a :~: b) #

type Empty = 'TEmpty Source #

type Lit = 'TLit Source #

type (:|) a b = 'TOr a b Source #

type Then = 'TThen Source #

type Star = 'TStar Source #

data Match k r where Source #

The result of match, in case of success

Constructors

MEmpty :: Match f 'TEmpty 
MLit :: f t -> Match f ('TLit t) 
MLeft :: Match f l -> Match f ('TOr l r) 
MRight :: Match f r -> Match f ('TOr l r) 
MThen :: Match f l -> Match f r -> Match f ('TThen l r) 
MStar :: [Match f r] -> Match f ('TStar r) 

data RegexRepr f r where Source #

Value-level representative of Regex

The order of the type parameters is a bit arbitrary... This order gives KnownRepr and TestEquality instances but requires flipping the type parameters to get TraversableF.

Constructors

Empty :: RegexRepr f 'TEmpty 
Fail :: RegexRepr f 'TFail 
Lit :: f t -> RegexRepr f ('TLit t) 
Or :: RegexRepr f l -> RegexRepr f r -> RegexRepr f ('TOr l r) 
Star :: RegexRepr f r -> RegexRepr f ('TStar r) 
Then :: RegexRepr f l -> RegexRepr f r -> RegexRepr f ('TThen l r) 

Instances

Instances details
FoldableFC (RegexRepr :: (k -> Type) -> Regex k -> Type) Source # 
Instance details

Defined in Lang.Crucible.Debug.Regex

Methods

foldMapFC :: forall f m. Monoid m => (forall (x :: k0). f x -> m) -> forall (x :: l). RegexRepr f x -> m #

foldrFC :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> RegexRepr f x -> b #

foldlFC :: forall f b. (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> RegexRepr f x -> b #

foldrFC' :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> RegexRepr f x -> b #

foldlFC' :: forall f b. (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> RegexRepr f x -> b #

toListFC :: (forall (x :: k0). f x -> a) -> forall (x :: l). RegexRepr f x -> [a] #

FunctorFC (RegexRepr :: (k -> Type) -> Regex k -> Type) Source # 
Instance details

Defined in Lang.Crucible.Debug.Regex

Methods

fmapFC :: (forall (x :: k0). f x -> g x) -> forall (x :: l). RegexRepr f x -> RegexRepr g x #

TraversableFC (RegexRepr :: (k -> Type) -> Regex k -> Type) Source # 
Instance details

Defined in Lang.Crucible.Debug.Regex

Methods

traverseFC :: forall f g m. Applicative m => (forall (x :: k0). f x -> m (g x)) -> forall (x :: l). RegexRepr f x -> m (RegexRepr g x) #

TestEquality f => TestEquality (RegexRepr f :: Regex k -> Type) Source # 
Instance details

Defined in Lang.Crucible.Debug.Regex

Methods

testEquality :: forall (a :: k0) (b :: k0). RegexRepr f a -> RegexRepr f b -> Maybe (a :~: b) #

data Trace ext Source #

data TraceEntry ext Source #

Constructors

forall blocks init ret. TraceEntry 

Fields

Instances

Instances details
PrettyExt ext => Pretty (TraceEntry ext) Source # 
Instance details

Defined in Lang.Crucible.Debug.Trace

Methods

pretty :: TraceEntry ext -> Doc ann #

prettyList :: [TraceEntry ext] -> Doc ann #

latest :: Trace ext -> Int -> IO [TraceEntry ext] Source #

Get up to the N latest entries