Skip to content
Snippets Groups Projects
Commit 57491ab4 authored by Ian Lynagh's avatar Ian Lynagh
Browse files

Follow rename of Instance to ClsInst in GHC

parent 949849c3
No related branches found
No related tags found
No related merge requests found
......@@ -150,7 +150,7 @@ ppClass x = out x{tcdSigs=[]} :
(map (reL . HsTyVar . hsTyVarName . unL) (tcdTyVars x))
ppInstance :: Instance -> [String]
ppInstance :: ClsInst -> [String]
ppInstance x = [dropComment $ out x]
......
......@@ -91,7 +91,7 @@ lookupInstDoc name iface ifaceMap instIfaceMap =
-- | Like GHC's getInfo but doesn't cut things out depending on the
-- interative context, which we don't set sufficiently anyway.
getAllInfo :: GhcMonad m => Name -> m (Maybe (TyThing,Fixity,[Instance]))
getAllInfo :: GhcMonad m => Name -> m (Maybe (TyThing,Fixity,[ClsInst]))
getAllInfo name = withSession $ \hsc_env -> do
(_msgs, r) <- liftIO $ tcRnGetInfo hsc_env name
return r
......
......@@ -160,7 +160,7 @@ parseOption other = tell ["Unrecognised option: " ++ other] >> return Nothing
type Maps = (DocMap Name, ArgMap Name, SubMap, DeclMap)
mkMaps :: DynFlags -> GlobalRdrEnv -> [Instance] -> [Name] -> [(LHsDecl Name, [HsDocString])] -> ErrMsgM Maps
mkMaps :: DynFlags -> GlobalRdrEnv -> [ClsInst] -> [Name] -> [(LHsDecl Name, [HsDocString])] -> ErrMsgM Maps
mkMaps dflags gre instances exports decls = do
maps <- mapM f decls
let mergeMaps (a,b,c,d) (x,y,z,w) =
......@@ -201,10 +201,10 @@ mkMaps dflags gre instances exports decls = do
-- Note [2]:
------------
-- We relate Instances to InstDecls using the SrcSpans buried inside them.
-- We relate ClsInsts to InstDecls using the SrcSpans buried inside them.
-- That should work for normal user-written instances (from looking at GHC
-- sources). We can assume that commented instances are user-written.
-- This lets us relate Names (from Instances) to comments (associated
-- This lets us relate Names (from ClsInsts) to comments (associated
-- with InstDecls).
......@@ -384,7 +384,7 @@ mkExportItems
-> [LHsDecl Name]
-> Maps
-> Maybe [IE Name]
-> [Instance]
-> [ClsInst]
-> InstIfaceMap
-> DynFlags
-> ErrMsgGhc [ExportItem Name]
......
......@@ -105,7 +105,7 @@ data Interface = Interface
, ifaceVisibleExports :: ![Name]
-- | Instances exported by the module.
, ifaceInstances :: ![Instance]
, ifaceInstances :: ![ClsInst]
-- | The number of haddockable and haddocked items in the module, as a
-- tuple. Haddockable items are the exports and the module itself.
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment