X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FGHC.hs;h=82a5adc3a03fd06bf405e65d3229655e0a439d09;hp=f5320613ff753262e5b92a1b796dc056856f414e;hb=a6f2d598e1e7760d334d1b5ea0b7745e66835e11;hpb=d529d596a1256bb48bda45ec343631c879c8d56d diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index f532061..82a5adc 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -98,7 +98,7 @@ module GHC ( typeKind, parseName, RunResult(..), - runStmt, SingleStep(..), + runStmt, parseImportDecl, SingleStep(..), resume, Resume(resumeStmt, resumeThreadId, resumeBreakInfo, resumeSpan, resumeHistory, resumeHistoryIx), @@ -111,13 +111,13 @@ module GHC ( showModule, isModuleInterpreted, InteractiveEval.compileExpr, HValue, dynCompileExpr, - lookupName, GHC.obtainTermFromId, GHC.obtainTermFromVal, reconstructType, modInfoModBreaks, ModBreaks(..), BreakIndex, BreakInfo(breakInfo_number, breakInfo_module), BreakArray, setBreakOn, setBreakOff, getBreak, #endif + lookupName, -- * Abstract syntax elements @@ -148,7 +148,7 @@ module GHC ( TyCon, tyConTyVars, tyConDataCons, tyConArity, isClassTyCon, isSynTyCon, isNewTyCon, isPrimTyCon, isFunTyCon, - isOpenTyCon, + isFamilyTyCon, synTyConDefn, synTyConType, synTyConResKind, -- ** Type variables @@ -243,11 +243,11 @@ import Linker ( HValue ) import ByteCodeInstr import BreakArray import InteractiveEval -import TcRnDriver #endif +import TcRnDriver import TcIface -import TcRnTypes hiding (LIE) +import TcRnTypes import TcRnMonad ( initIfaceCheck ) import Packages import NameSet @@ -255,6 +255,7 @@ import RdrName import qualified HsSyn -- hack as we want to reexport the whole module import HsSyn hiding ((<.>)) import Type +import Coercion ( synTyConResKind ) import TcType hiding( typeKind ) import Id import Var @@ -285,7 +286,6 @@ import SysTools ( initSysTools, cleanTempFiles, cleanTempFilesExcept, import Annotations import Module import UniqFM -import FiniteMap import Panic import Digraph import Bag ( unitBag, listToBag, emptyBag, isEmptyBag ) @@ -302,6 +302,9 @@ import Lexer import System.Directory ( getModificationTime, doesFileExist, getCurrentDirectory ) import Data.Maybe +import Data.Map (Map) +import qualified Data.Map as Map +import qualified FiniteMap as Map import Data.List import qualified Data.List as List import Data.Typeable ( Typeable ) @@ -1826,14 +1829,14 @@ moduleGraphNodes drop_hs_boot_nodes summaries = (graphFromEdgedVertices nodes, l numbered_summaries = zip summaries [1..] lookup_node :: HscSource -> ModuleName -> Maybe SummaryNode - lookup_node hs_src mod = lookupFM node_map (mod, hs_src) + lookup_node hs_src mod = Map.lookup (mod, hs_src) node_map lookup_key :: HscSource -> ModuleName -> Maybe Int lookup_key hs_src mod = fmap summaryNodeKey (lookup_node hs_src mod) node_map :: NodeMap SummaryNode - node_map = listToFM [ ((moduleName (ms_mod s), ms_hsc_src s), node) - | node@(s, _, _) <- nodes ] + node_map = Map.fromList [ ((moduleName (ms_mod s), ms_hsc_src s), node) + | node@(s, _, _) <- nodes ] -- We use integers as the keys for the SCC algorithm nodes :: [SummaryNode] @@ -1869,16 +1872,16 @@ moduleGraphNodes drop_hs_boot_nodes summaries = (graphFromEdgedVertices nodes, l type NodeKey = (ModuleName, HscSource) -- The nodes of the graph are -type NodeMap a = FiniteMap NodeKey a -- keyed by (mod, src_file_type) pairs +type NodeMap a = Map NodeKey a -- keyed by (mod, src_file_type) pairs msKey :: ModSummary -> NodeKey msKey (ModSummary { ms_mod = mod, ms_hsc_src = boot }) = (moduleName mod,boot) mkNodeMap :: [ModSummary] -> NodeMap ModSummary -mkNodeMap summaries = listToFM [ (msKey s, s) | s <- summaries] +mkNodeMap summaries = Map.fromList [ (msKey s, s) | s <- summaries] nodeMapElts :: NodeMap a -> [a] -nodeMapElts = eltsFM +nodeMapElts = Map.elems -- | If there are {-# SOURCE #-} imports between strongly connected -- components in the topological sort, then those imports can @@ -1983,7 +1986,7 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots -- for those mentioned in the visited set loop [] done = return (concat (nodeMapElts done)) loop ((wanted_mod, is_boot) : ss) done - | Just summs <- lookupFM done key + | Just summs <- Map.lookup key done = if isSingleton summs then loop ss done else @@ -1994,13 +1997,15 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots Nothing excl_mods case mb_s of Nothing -> loop ss done - Just s -> loop (msDeps s ++ ss) (addToFM done key [s]) + Just s -> loop (msDeps s ++ ss) (Map.insert key [s] done) where key = (unLoc wanted_mod, if is_boot then HsBootFile else HsSrcFile) +-- XXX Does the (++) here need to be flipped? mkRootMap :: [ModSummary] -> NodeMap [ModSummary] -mkRootMap summaries = addListToFM_C (++) emptyFM - [ (msKey s, [s]) | s <- summaries ] +mkRootMap summaries = Map.insertListWith (flip (++)) + [ (msKey s, [s]) | s <- summaries ] + Map.empty msDeps :: ModSummary -> [(Located ModuleName, IsBootInterface)] -- (msDeps s) returns the dependencies of the ModSummary s. @@ -2016,7 +2021,10 @@ msDeps s = ++ [ (m,False) | m <- ms_home_imps s ] home_imps :: [Located (ImportDecl RdrName)] -> [Located ModuleName] -home_imps imps = [ ideclName i | L _ i <- imps, isNothing (ideclPkgQual i) ] +home_imps imps = [ ideclName i | L _ i <- imps, isLocal (ideclPkgQual i) ] + where isLocal Nothing = True + isLocal (Just pkg) | pkg == fsLit "this" = True -- "this" is special + isLocal _ = False ms_home_allimps :: ModSummary -> [ModuleName] ms_home_allimps ms = map unLoc (ms_home_srcimps ms ++ ms_home_imps ms) @@ -2142,7 +2150,7 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod) | wanted_mod `elem` excl_mods = return Nothing - | Just old_summary <- lookupFM old_summary_map (wanted_mod, hsc_src) + | Just old_summary <- Map.lookup (wanted_mod, hsc_src) old_summary_map = do -- Find its new timestamp; all the -- ModSummaries in the old map have valid ml_hs_files let location = ms_location old_summary @@ -2281,7 +2289,7 @@ preprocessFile hsc_env src_fn mb_phase (Just (buf, _time)) | Just (Unlit _) <- mb_phase = True | Nothing <- mb_phase, Unlit _ <- startPhase src_fn = True -- note: local_opts is only required if there's no Unlit phase - | dopt Opt_Cpp dflags' = True + | xopt Opt_Cpp dflags' = True | dopt Opt_Pp dflags' = True | otherwise = False @@ -2364,7 +2372,7 @@ getModuleGraph = liftM hsc_mod_graph getSession -- have Template Haskell enabled whether it is actually needed or not. needsTemplateHaskell :: ModuleGraph -> Bool needsTemplateHaskell ms = - any (dopt Opt_TemplateHaskell . ms_hspp_opts) ms + any (xopt Opt_TemplateHaskell . ms_hspp_opts) ms -- | Return @True@ <==> module is loaded. isLoaded :: GhcMonad m => ModuleName -> m Bool @@ -2432,7 +2440,7 @@ getPackageModuleInfo hsc_env mdl = do return (Just (ModuleInfo { minf_type_env = mkTypeEnv tys, minf_exports = names, - minf_rdr_env = Just $! nameSetToGlobalRdrEnv names (moduleName mdl), + minf_rdr_env = Just $! availsToGlobalRdrEnv (moduleName mdl) avails, minf_instances = error "getModuleInfo: instances for package module unimplemented", minf_modBreaks = emptyModBreaks })) @@ -2720,3 +2728,12 @@ obtainTermFromId bound force id = liftIO $ InteractiveEval.obtainTermFromId hsc_env bound force id #endif + +-- | Returns the 'TyThing' for a 'Name'. The 'Name' may refer to any +-- entity known to GHC, including 'Name's defined using 'runStmt'. +lookupName :: GhcMonad m => Name -> m (Maybe TyThing) +lookupName name = withSession $ \hsc_env -> do + mb_tything <- ioMsg $ tcRnLookupName hsc_env name + return mb_tything + -- XXX: calls panic in some circumstances; is that ok? +