summaryrefslogtreecommitdiff
path: root/ghc/compiler/main
diff options
context:
space:
mode:
authorSimon Marlow <simonmar@microsoft.com>2006-02-06 12:26:54 +0000
committerSimon Marlow <simonmar@microsoft.com>2006-02-06 12:26:54 +0000
commit315a1f6c671b9800909752c702bda347198dd60a (patch)
tree66b81e99e0f9ae7e095aca52c64301cf2138f711 /ghc/compiler/main
parent594aa4967f05341c5a2417881e0abd068ab34e9a (diff)
downloadhaskell-315a1f6c671b9800909752c702bda347198dd60a.tar.gz
Basic completion in GHCi
This patch adds completion support to GHCi when readline is being used. Completion of identifiers (in scope only, but including qualified identifiers) in expressions is provided. Also, completion of commands (:cmd), and special completion for certain commands (eg. module names for the :module command) are also provided.
Diffstat (limited to 'ghc/compiler/main')
-rw-r--r--ghc/compiler/main/GHC.hs25
1 files changed, 23 insertions, 2 deletions
diff --git a/ghc/compiler/main/GHC.hs b/ghc/compiler/main/GHC.hs
index b5707c7886..6f6b7c8e38 100644
--- a/ghc/compiler/main/GHC.hs
+++ b/ghc/compiler/main/GHC.hs
@@ -62,6 +62,7 @@ module GHC (
#ifdef GHCI
setContext, getContext,
getNamesInScope,
+ getRdrNamesInScope,
moduleIsInterpreted,
getInfo,
exprType,
@@ -83,6 +84,7 @@ module GHC (
Name,
nameModule, nameParent_maybe, pprParenSymName, nameSrcLoc,
NamedThing(..),
+ RdrName(Qual,Unqual),
-- ** Identifiers
Id, idType,
@@ -176,7 +178,7 @@ import GHC.Exts ( unsafeCoerce# )
import Packages ( initPackages )
import NameSet ( NameSet, nameSetToList, elemNameSet )
-import RdrName ( GlobalRdrEnv, GlobalRdrElt(..), RdrName,
+import RdrName ( GlobalRdrEnv, GlobalRdrElt(..), RdrName(..),
globalRdrEnvElts )
import HsSyn
import Type ( Kind, Type, dropForAlls, PredType, ThetaType,
@@ -199,7 +201,7 @@ import DataCon ( DataCon, dataConWrapId, dataConSig, dataConTyCon,
dataConFieldLabels, dataConStrictMarks,
dataConIsInfix, isVanillaDataCon )
import Name ( Name, nameModule, NamedThing(..), nameParent_maybe,
- nameSrcLoc )
+ nameSrcLoc, nameOccName )
import OccName ( parenSymOcc )
import NameEnv ( nameEnvElts )
import InstEnv ( Instance, instanceDFunId, pprInstance, pprInstanceHdr )
@@ -1887,6 +1889,25 @@ getNamesInScope :: Session -> IO [Name]
getNamesInScope s = withSession s $ \hsc_env -> do
return (map gre_name (globalRdrEnvElts (ic_rn_gbl_env (hsc_IC hsc_env))))
+getRdrNamesInScope :: Session -> IO [RdrName]
+getRdrNamesInScope s = withSession s $ \hsc_env -> do
+ let env = ic_rn_gbl_env (hsc_IC hsc_env)
+ return (concat (map greToRdrNames (globalRdrEnvElts env)))
+
+-- ToDo: move to RdrName
+greToRdrNames :: GlobalRdrElt -> [RdrName]
+greToRdrNames GRE{ gre_name = name, gre_prov = prov }
+ = case prov of
+ LocalDef -> [unqual]
+ Imported specs -> concat (map do_spec (map is_decl specs))
+ where
+ occ = nameOccName name
+ unqual = Unqual occ
+ do_spec decl_spec
+ | is_qual decl_spec = [qual]
+ | otherwise = [unqual,qual]
+ where qual = Qual (is_as decl_spec) occ
+
-- | Parses a string as an identifier, and returns the list of 'Name's that
-- the identifier can refer to in the current interactive context.
parseName :: Session -> String -> IO [Name]