Skip to content

Commit

Permalink
Handle breakpoint jumps while splicing TH functions in ghci
Browse files Browse the repository at this point in the history
The dynamic linker has been modified so that it won't panic if one of the breakpointJump functions fails to resolve.
Now, if the dynamic linker fails to find a HValue for a Name, before looking for a static symbol it will ask to

Breakpoints.lookupBogusBreakpointVal :: Name -> Maybe HValue

which returns an identity function for the Jump names or Nothing else.

A TH function might contain a call to a breakpoint function. So if it is compiled to bytecodes, the breakpoints will be desugared to 'jumps'. Whenever this code is spliced, the linker will fail to find the jumpfunctions unless there is a default.
  • Loading branch information
pepeiborra committed Dec 10, 2006
1 parent 3761010 commit 1df34b3
Show file tree
Hide file tree
Showing 2 changed files with 25 additions and 0 deletions.
3 changes: 3 additions & 0 deletions compiler/ghci/ByteCodeLink.lhs
Expand Up @@ -27,6 +27,7 @@ import Module
import PackageConfig
import FastString
import Panic
import Breakpoints
#ifdef DEBUG
import Outputable
Expand Down Expand Up @@ -211,6 +212,8 @@ lookupName :: ClosureEnv -> Name -> IO HValue
lookupName ce nm
= case lookupNameEnv ce nm of
Just (_,aa) -> return aa
Nothing | Just bk <- lookupBogusBreakpointVal nm
-> return bk
Nothing
-> ASSERT2(isExternalName nm, ppr nm)
do let sym_to_find = nameToCLabel nm "closure"
Expand Down
22 changes: 22 additions & 0 deletions compiler/main/Breakpoints.hs
Expand Up @@ -9,7 +9,16 @@

module Breakpoints where

#ifdef GHCI
import {-#SOURCE#-} ByteCodeLink ( HValue )
#endif

import {-#SOURCE#-} HscTypes ( Session )
import Name
import Var ( Id )
import PrelNames

import GHC.Exts ( unsafeCoerce# )

data BkptHandler a = BkptHandler {
handleBreakpoint :: forall b. Session -> [(Id,HValue)] -> BkptLocation a -> String -> b -> IO b
Expand All @@ -29,3 +38,16 @@ type Coord = (Int, Int)

noDbgSites :: SiteMap
noDbgSites = []

-- | Returns the 'identity' jumps
-- Used to deal with spliced code, where we don't want breakpoints
#ifdef GHCI
lookupBogusBreakpointVal :: Name -> Maybe HValue
lookupBogusBreakpointVal name
| name == breakpointJumpName = Just$ unsafeCoerce# (\_ _ _ _ a->a)
| name == breakpointAutoJumpName = Just$ unsafeCoerce# (\_ _ _ _ a->a)
| name == breakpointCondJumpName = Just$ unsafeCoerce# (\_ _ _ _ _ a->a)
| otherwise = Nothing
#else
lookupBogusBreakpointVal _ = Nothing
#endif //GHCI

0 comments on commit 1df34b3

Please sign in to comment.