summaryrefslogtreecommitdiff
path: root/ghc/GHCi
diff options
context:
space:
mode:
authorAlan Zimmerman <alan.zimm@gmail.com>2017-05-19 14:56:09 +0200
committerAlan Zimmerman <alan.zimm@gmail.com>2017-06-06 00:16:20 +0200
commit8e6ec0fa7431b0454b09c0011a615f0845df1198 (patch)
treed6b3604e0ceac3d81d0510669f7ccce9a2bf3ae2 /ghc/GHCi
parentc9eb4385aad248118650725b7b699bb97ee21c0d (diff)
downloadhaskell-8e6ec0fa7431b0454b09c0011a615f0845df1198.tar.gz
Udate hsSyn AST to use Trees that Grow
Summary: See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow This commit prepares the ground for a full extensible AST, by replacing the type parameter for the hsSyn data types with a set of indices into type families, data GhcPs -- ^ Index for GHC parser output data GhcRn -- ^ Index for GHC renamer output data GhcTc -- ^ Index for GHC typechecker output These are now used instead of `RdrName`, `Name` and `Id`/`TcId`/`Var` Where the original name type is required in a polymorphic context, this is accessible via the IdP type family, defined as type family IdP p type instance IdP GhcPs = RdrName type instance IdP GhcRn = Name type instance IdP GhcTc = Id These types are declared in the new 'hsSyn/HsExtension.hs' module. To gain a better understanding of the extension mechanism, it has been applied to `HsLit` only, also replacing the `SourceText` fields in them with extension types. To preserve extension generality, a type class is introduced to capture the `SourceText` interface, which must be honoured by all of the extension points which originally had a `SourceText`. The class is defined as class HasSourceText a where -- Provide setters to mimic existing constructors noSourceText :: a sourceText :: String -> a setSourceText :: SourceText -> a getSourceText :: a -> SourceText And the constraint is captured in `SourceTextX`, which is a constraint type listing all the extension points that make use of the class. Updating Haddock submodule to match. Test Plan: ./validate Reviewers: simonpj, shayan-najd, goldfire, austin, bgamari Subscribers: rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3609
Diffstat (limited to 'ghc/GHCi')
-rw-r--r--ghc/GHCi/UI.hs6
-rw-r--r--ghc/GHCi/UI/Info.hs6
-rw-r--r--ghc/GHCi/UI/Monad.hs7
3 files changed, 9 insertions, 10 deletions
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs
index 6954002645..5f81a2ce7c 100644
--- a/ghc/GHCi/UI.hs
+++ b/ghc/GHCi/UI.hs
@@ -59,7 +59,7 @@ import Packages ( trusted, getPackageDetails, getInstalledPackageDetails,
import IfaceSyn ( showToHeader )
import PprTyThing
import PrelNames
-import RdrName ( RdrName, getGRE_NameQualifier_maybes, getRdrName )
+import RdrName ( getGRE_NameQualifier_maybes, getRdrName )
import SrcLoc
import qualified Lexer
@@ -1566,7 +1566,7 @@ cmdCmd str = handleSourceError GHC.printException $ do
-- | Generate a typed ghciStepIO expression
-- @ghciStepIO :: Ty String -> IO String@.
-getGhciStepIO :: GHCi (LHsExpr RdrName)
+getGhciStepIO :: GHCi (LHsExpr GhcPs)
getGhciStepIO = do
ghciTyConName <- GHC.getGHCiMonad
let stringTy = nlHsTyVar stringTy_RDR
@@ -2385,7 +2385,7 @@ iiModuleName (IIDecl d) = unLoc (ideclName d)
preludeModuleName :: ModuleName
preludeModuleName = GHC.mkModuleName "Prelude"
-sameImpModule :: ImportDecl RdrName -> InteractiveImport -> Bool
+sameImpModule :: ImportDecl GhcPs -> InteractiveImport -> Bool
sameImpModule _ (IIModule _) = False -- we only care about imports here
sameImpModule imp (IIDecl d) = unLoc (ideclName d) == unLoc (ideclName imp)
diff --git a/ghc/GHCi/UI/Info.hs b/ghc/GHCi/UI/Info.hs
index ef5e9ef207..a114ebff29 100644
--- a/ghc/GHCi/UI/Info.hs
+++ b/ghc/GHCi/UI/Info.hs
@@ -308,13 +308,13 @@ processAllTypeCheckedModule tcm = do
tcs = tm_typechecked_source tcm
-- | Extract 'Id', 'SrcSpan', and 'Type' for 'LHsBind's
- getTypeLHsBind :: LHsBind Id -> m (Maybe (Maybe Id,SrcSpan,Type))
+ getTypeLHsBind :: LHsBind GhcTc -> m (Maybe (Maybe Id,SrcSpan,Type))
getTypeLHsBind (L _spn FunBind{fun_id = pid,fun_matches = MG _ _ _typ _})
= pure $ Just (Just (unLoc pid),getLoc pid,varType (unLoc pid))
getTypeLHsBind _ = pure Nothing
-- | Extract 'Id', 'SrcSpan', and 'Type' for 'LHsExpr's
- getTypeLHsExpr :: LHsExpr Id -> m (Maybe (Maybe Id,SrcSpan,Type))
+ getTypeLHsExpr :: LHsExpr GhcTc -> m (Maybe (Maybe Id,SrcSpan,Type))
getTypeLHsExpr e = do
hs_env <- getSession
(_,mbe) <- liftIO $ deSugarExpr hs_env e
@@ -328,7 +328,7 @@ processAllTypeCheckedModule tcm = do
unwrapVar e' = e'
-- | Extract 'Id', 'SrcSpan', and 'Type' for 'LPats's
- getTypeLPat :: LPat Id -> m (Maybe (Maybe Id,SrcSpan,Type))
+ getTypeLPat :: LPat GhcTc -> m (Maybe (Maybe Id,SrcSpan,Type))
getTypeLPat (L spn pat) =
pure (Just (getMaybeId pat,spn,hsPatType pat))
where
diff --git a/ghc/GHCi/UI/Monad.hs b/ghc/GHCi/UI/Monad.hs
index bb946cc7b1..46f0860ab9 100644
--- a/ghc/GHCi/UI/Monad.hs
+++ b/ghc/GHCi/UI/Monad.hs
@@ -44,8 +44,7 @@ import SrcLoc
import Module
import GHCi
import GHCi.RemoteTypes
-import HsSyn (ImportDecl)
-import RdrName (RdrName)
+import HsSyn (ImportDecl, GhcPs)
import Util
import Exception
@@ -109,7 +108,7 @@ data GHCiState = GHCiState
-- :load, :reload, and :add. In between it may be modified
-- by :module.
- extra_imports :: [ImportDecl RdrName],
+ extra_imports :: [ImportDecl GhcPs],
-- ^ These are "always-on" imports, added to the
-- context regardless of what other imports we have.
-- This is useful for adding imports that are required
@@ -122,7 +121,7 @@ data GHCiState = GHCiState
-- on the GHCi code. Potentially we could also expose
-- this functionality via GHCi commands.
- prelude_imports :: [ImportDecl RdrName],
+ prelude_imports :: [ImportDecl GhcPs],
-- ^ These imports are added to the context when
-- -XImplicitPrelude is on and we don't have a *-module
-- in the context. They can also be overridden by another