Custom printer for the Term datatype that won't output TypeRep values
[ghc-hetmet.git] / compiler / ghci / Debugger.hs
1 -----------------------------------------------------------------------------
2 --
3 -- GHCi Interactive debugging commands 
4 --
5 -- Pepe Iborra (supported by Google SoC) 2006
6 --
7 -- ToDo: lots of violation of layering here.  This module should
8 -- decide whether it is above the GHC API (import GHC and nothing
9 -- else) or below it.
10 -- 
11 -----------------------------------------------------------------------------
12
13 module Debugger (pprintClosureCommand, showTerm) where
14
15 import Linker
16 import RtClosureInspect
17
18 import HscTypes
19 import IdInfo
20 --import Id
21 import Name
22 import Var hiding ( varName )
23 import VarSet
24 import Name 
25 import UniqSupply
26 import Type
27 import GHC
28 import InteractiveEval
29 import Outputable
30 import Pretty                    ( Mode(..), showDocWith )
31 import SrcLoc
32
33 import Control.Exception
34 import Control.Monad
35 import Data.List
36 import Data.Maybe
37 import Data.IORef
38
39 import System.IO
40 import GHC.Exts
41
42 -------------------------------------
43 -- | The :print & friends commands
44 -------------------------------------
45 pprintClosureCommand :: Session -> Bool -> Bool -> String -> IO ()
46 pprintClosureCommand session bindThings force str = do
47   tythings <- (catMaybes . concat) `liftM`
48                  mapM (\w -> GHC.parseName session w >>=
49                                 mapM (GHC.lookupName session))
50                       (words str)
51   let ids = [id | AnId id <- tythings]
52
53   -- Obtain the terms and the recovered type information
54   (terms, substs) <- unzip `liftM` mapM (go session) ids
55   
56   -- Apply the substitutions obtained after recovering the types
57   modifySession session $ \hsc_env ->
58          hsc_env{hsc_IC = foldr (flip substInteractiveContext)
59                                 (hsc_IC hsc_env)
60                                 (map skolemiseSubst substs)}
61   -- Finally, print the Terms
62   unqual  <- GHC.getPrintUnqual session
63   let showSDocForUserOneLine unqual doc =
64                showDocWith LeftMode (doc (mkErrStyle unqual))
65   docterms <- mapM (showTerm session) terms
66   (putStrLn . showSDocForUserOneLine unqual . vcat)
67         (zipWith (\id docterm -> ppr id <+> char '=' <+> docterm)
68                  ids
69                  docterms)
70  where
71
72    -- Do the obtainTerm--bindSuspensions-computeSubstitution dance
73    go :: Session -> Id -> IO (Term, TvSubst)
74    go cms id = do
75        term_    <- GHC.obtainTerm cms force id
76        term     <- tidyTermTyVars cms term_
77        term'    <- if not bindThings then return term
78                      else bindSuspensions cms term                       
79      -- Before leaving, we compare the type obtained to see if it's more specific
80      --  Then, we extract a substitution,
81      --  mapping the old tyvars to the reconstructed types.
82        let Just reconstructed_type = termType term
83            Just subst = computeRTTIsubst (idType id) (reconstructed_type)
84        return (term',subst)
85
86    tidyTermTyVars :: Session -> Term -> IO Term
87    tidyTermTyVars (Session ref) t = do
88      hsc_env <- readIORef ref
89      let env_tvs      = ic_tyvars (hsc_IC hsc_env)
90          my_tvs       = termTyVars t
91          tvs          = env_tvs `minusVarSet` my_tvs
92          tyvarOccName = nameOccName . tyVarName
93          tidyEnv      = (initTidyOccEnv (map tyvarOccName (varSetElems tvs))
94                         , env_tvs `intersectVarSet` my_tvs)
95      return$ mapTermType (snd . tidyOpenType tidyEnv) t
96
97 -- | Give names, and bind in the interactive environment, to all the suspensions
98 --   included (inductively) in a term
99 bindSuspensions :: Session -> Term -> IO Term
100 bindSuspensions cms@(Session ref) t = do
101       hsc_env <- readIORef ref
102       inScope <- GHC.getBindings cms
103       let ictxt        = hsc_IC hsc_env
104           prefix       = "_t"
105           alreadyUsedNames = map (occNameString . nameOccName . getName) inScope
106           availNames   = map ((prefix++) . show) [(1::Int)..] \\ alreadyUsedNames
107       availNames_var  <- newIORef availNames
108       (t', stuff)     <- foldTerm (nameSuspensionsAndGetInfos availNames_var) t
109       let (names, tys, hvals) = unzip3 stuff
110       let tys' = map (fst.skolemiseTy) tys
111       let ids = [ mkGlobalId VanillaGlobal name ty vanillaIdInfo
112                 | (name,ty) <- zip names tys']
113           new_tyvars   = tyVarsOfTypes tys'
114           new_ic       = extendInteractiveContext ictxt ids new_tyvars
115       extendLinkEnv (zip names hvals)
116       writeIORef ref (hsc_env {hsc_IC = new_ic })
117       return t'
118      where
119
120 --    Processing suspensions. Give names and recopilate info
121         nameSuspensionsAndGetInfos :: IORef [String] ->
122                                        TermFold (IO (Term, [(Name,Type,HValue)]))
123         nameSuspensionsAndGetInfos freeNames = TermFold
124                       {
125                         fSuspension = doSuspension freeNames
126                       , fTerm = \ty dc v tt -> do
127                                     tt' <- sequence tt
128                                     let (terms,names) = unzip tt'
129                                     return (Term ty dc v terms, concat names)
130                       , fPrim    = \ty n ->return (Prim ty n,[])
131                       }
132         doSuspension freeNames ct mb_ty hval _name = do
133           name <- atomicModifyIORef freeNames (\x->(tail x, head x))
134           n <- newGrimName name
135           let ty' = fromMaybe (error "unexpected") mb_ty
136           return (Suspension ct mb_ty hval (Just n), [(n,ty',hval)])
137
138
139 --  A custom Term printer to enable the use of Show instances
140 showTerm :: Session -> Term -> IO SDoc
141 showTerm cms@(Session ref) term = do
142     cPprExtended <- cPprTermExtended cms
143     cPprTerm (liftM2 (++) cPprShowable cPprExtended) term
144  where
145   cPprShowable _y = [\prec ty _ val tt ->
146     if not (all isFullyEvaluatedTerm tt)
147      then return Nothing
148      else do
149         hsc_env <- readIORef ref
150         dflags  <- GHC.getSessionDynFlags cms
151         do
152            (new_env, bname) <- bindToFreshName hsc_env ty "showme"
153            writeIORef ref (new_env)
154            let noop_log _ _ _ _ = return ()
155                expr = "show " ++ showSDoc (ppr bname)
156            GHC.setSessionDynFlags cms dflags{log_action=noop_log}
157            mb_txt <- withExtendedLinkEnv [(bname, val)]
158                                          (GHC.compileExpr cms expr)
159            let myprec = 10 -- application precedence. TODO Infix constructors
160            case mb_txt of
161              Just txt_ | txt <- unsafeCoerce# txt_, not (null txt)
162                        -> return $ Just$ cparen (prec >= myprec &&
163                                                       needsParens txt)
164                                                 (text txt)
165              _  -> return Nothing
166          `finally` do
167            writeIORef ref hsc_env
168            GHC.setSessionDynFlags cms dflags]
169   needsParens ('"':_) = False   -- some simple heuristics to see whether parens
170                                 -- are redundant in an arbitrary Show output
171   needsParens ('(':_) = False
172   needsParens txt = ' ' `elem` txt
173
174
175   bindToFreshName hsc_env ty userName = do
176     name <- newGrimName userName
177     let ictxt    = hsc_IC hsc_env
178         tmp_ids  = ic_tmp_ids ictxt
179         id       = mkGlobalId VanillaGlobal name (sigmaType ty) vanillaIdInfo
180         new_ic   = ictxt { ic_tmp_ids = id : tmp_ids }
181     return (hsc_env {hsc_IC = new_ic }, name)
182
183 {- | A custom Term printer to handle some types that 
184      we may not want to show, such as Data.Typeable.TypeRep -}
185 cPprTermExtended :: Monad m => Session -> IO (CustomTermPrinter m)
186 cPprTermExtended session = liftM22 (++) (return cPprTermBase) extended
187   where 
188    extended = do
189      [typerep_name]        <- parseName session "Data.Typeable.TypeRep"
190      Just (ATyCon typerep) <- lookupName session typerep_name 
191
192      return (\_y -> 
193         [ ifType (isTyCon typerep) (\_val _prec -> return (text "<typerep>")) ])
194
195    ifType pred f prec ty _ val _tt
196       | pred ty   = Just `liftM` f prec val
197       | otherwise = return Nothing
198    isTyCon a_tc ty = fromMaybe False $ do 
199              (tc,_) <- splitTyConApp_maybe ty
200              return (a_tc == tc)
201    liftM22 f x y = do x' <- x; y' <- y
202                       return$ do x'' <- x';y'' <- y';return (f x'' y'')
203
204 --    Create new uniques and give them sequentially numbered names
205 newGrimName :: String -> IO Name
206 newGrimName userName  = do
207     us <- mkSplitUniqSupply 'b'
208     let unique  = uniqFromSupply us
209         occname = mkOccName varName userName
210         name    = mkInternalName unique occname noSrcSpan
211     return name