diff -rN old-ghc/compiler/ghci/InteractiveUI.hs new-ghc/compiler/ghci/InteractiveUI.hs
37c37,38
< import Name
---
> import Name hiding (varName)
> import qualified Var(varName)
113c114,118
<   ("browse",    keepGoing browseCmd,		False, completeModule),
---
> --  :b used to be :browse, and shouldn't be taken over by debugger..
> --  ("b",    keepGoing (browseCmd False),		False, completeModule),
> --  ("b!",    keepGoing (browseCmd True),		False, completeModule),
>   ("browse",    keepGoing (browseCmd False),		False, completeModule),
>   ("browse!",   keepGoing (browseCmd True),		False, completeModule),
162c167
<  "   :browse [*]<module>         display the names defined by <module>\n" ++
---
>  "   :browse[!] [*]<module>      display the names defined by <module>\n" ++
229c234
<  "\n" 
---
>  "\n"
711,714c716,719
< 	     ; session <- getSession
< 	     ; dflags <- getDynFlags
< 	     ; let pefas = dopt Opt_PrintExplicitForalls dflags
< 	     ; mapM_ (infoThing pefas session) names }
---
>              ; session <- getSession
>              ; dflags <- getDynFlags
>              ; let pefas = dopt Opt_PrintExplicitForalls dflags
>              ; mapM_ (infoThing pefas session) names }
717,723c722,728
< 	names     <- GHC.parseName session str
< 	mb_stuffs <- mapM (GHC.getInfo session) names
< 	let filtered = filterOutChildren (\(t,f,i) -> t) (catMaybes mb_stuffs)
< 	unqual <- GHC.getPrintUnqual session
< 	putStrLn (showSDocForUser unqual $
<      		   vcat (intersperse (text "") $
< 		         map (pprInfo pefas) filtered))
---
>         names     <- GHC.parseName session str
>         mb_stuffs <- mapM (GHC.getInfo session) names
>         let filtered = filterOutChildren (\(t,f,i) -> t) (catMaybes mb_stuffs)
>         unqual <- GHC.getPrintUnqual session
>         putStrLn (showSDocForUser unqual $
>                         vcat (intersperse (text "") $
>                          map (pprInfo pefas) filtered))
1014,1015c1019,1020
< browseCmd :: String -> GHCi ()
< browseCmd m = 
---
> browseCmd :: Bool -> String -> GHCi ()
> browseCmd bang m = 
1017,1018c1022,1023
<     ['*':m] | looksLikeModuleName m -> browseModule m False
<     [m]     | looksLikeModuleName m -> browseModule m True
---
>     ['*':m] | looksLikeModuleName m -> browseModule bang m False
>     [m]     | looksLikeModuleName m -> browseModule bang m True
1021c1026,1029
< browseModule m exports_only = do
---
> -- without bang, show items in context of their parents and omit children
> -- with bang, show class methods and data constructors separately, and
> --            indicate import modules, to aid qualifying unqualified names
> browseModule bang m exports_only = do
1031c1039
< 		      else GHC.setContext s [modl] [])
---
>                       else GHC.setContext s [modl] [])
1040,1042c1048,1050
< 	       | exports_only = GHC.modInfoExports mod_info
< 	       | otherwise    = GHC.modInfoTopLevelScope mod_info
< 				`orElse` []
---
>                | exports_only = GHC.modInfoExports mod_info
>                | otherwise    = GHC.modInfoTopLevelScope mod_info
>                                 `orElse` []
1045c1053
<  	let filtered_things = filterOutChildren (\t -> t) (catMaybes mb_things)
---
>         let filtered_things = filterOutChildren (\t -> t) (catMaybes mb_things)
1048,1054c1056,1087
< 	let pefas = dopt Opt_PrintExplicitForalls dflags
< 	io (putStrLn (showSDocForUser unqual (
< 		vcat (map (pprTyThingInContext pefas) filtered_things)
< 	   )))
< 	-- ToDo: modInfoInstances currently throws an exception for
< 	-- package modules.  When it works, we can do this:
< 	--	$$ vcat (map GHC.pprInstance (GHC.modInfoInstances mod_info))
---
>         let pefas              = dopt Opt_PrintExplicitForalls dflags
>             things | bang      = catMaybes mb_things
>                    | otherwise = filtered_things
>             modNames           = map (GHC.moduleNameString . GHC.moduleName 
>                                     . GHC.nameModule . GHC.getName) things
>             -- annotate groups of imports with their import module
>             annotate mg []                      = []
>             annotate mg ((m,t):mts) | mg==m     = t:(annotate m mts)
>             annotate mg ((m,t):mts) | otherwise = 
>               (text $ "-- imported from "++m):t:(annotate m mts)
>         prettyThings <- mapM (pprTyThingOrMethod bang s pefas) things
>         let prettyThings' | bang      = annotate "" (zip modNames prettyThings)
>                           | otherwise = prettyThings
>         io (putStrLn $ showSDocForUser unqual (vcat prettyThings'))
>         -- ToDo: modInfoInstances currently throws an exception for
>         -- package modules.  When it works, we can do this:
>         --        $$ vcat (map GHC.pprInstance (GHC.modInfoInstances mod_info))
> 
> -- need to decode dictionary parameter as class context?
> -- why are class self/other parameters treated differently?
> -- to merge nested foralls, we'd need to avoid name capture?
> -- use exprType as a workaround for now
> pprTyThingOrMethod bang s pefas anid@(AnId id) 
>   | bang, Just cls <- GHC.isClassOpId_maybe id 
>   = do let pid = GHC.pprParenSymName id
>        maybe_ty <- io (GHC.exprType s $ showSDoc pid)
>        case maybe_ty of
>         Nothing -> return $ text "--" <> pid <> text ": no type available?"
>         Just ty -> do ty' <- cleanType ty
>                       return $ pid <> text " :: " <> ppr ty'
> pprTyThingOrMethod bang s pefas id
>   = return $ pprTyThing pefas id
1134,1138c1167,1171
<    	      text "options currently set: " <> 
<    	      if null opts
<    		   then text "none."
<    		   else hsep (map (\o -> char '+' <> text (optToStr o)) opts)
<    	   ))
---
>                  text "options currently set: " <> 
>                  if null opts
>                       then text "none."
>                       else hsep (map (\o -> char '+' <> text (optToStr o)) opts)
>               ))
1141,1142c1174,1175
< 	("args":args) -> setArgs args
< 	("prog":prog) -> setProg prog
---
>         ("args":args) -> setArgs args
>         ("prog":prog) -> setProg prog
1146c1179
< 	wds -> setOptions wds
---
>         wds -> setOptions wds
1278,1280c1311,1313
< 	["modules" ] -> showModules
< 	["bindings"] -> showBindings
< 	["linker"]   -> io showLinkerState
---
>         ["modules" ] -> showModules
>         ["bindings"] -> showBindings
>         ["linker"]   -> io showLinkerState
1283c1316
< 	_ -> throwDyn (CmdLineError "syntax:  :show [args|prog|prompt|editor|stop|modules|bindings|breaks|context]")
---
>         _ -> throwDyn (CmdLineError "syntax:  :show [args|prog|prompt|editor|stop|modules|bindings|breaks|context]")
1288c1321
< 		       io (putStrLn m)
---
>                        io (putStrLn m)
1320,1321c1353,1354
< 	then return ty
< 	else return $! GHC.dropForAlls ty
---
>         then return ty
>         else return $! GHC.dropForAlls ty

