summaryrefslogtreecommitdiff
path: root/compiler/GHC/Driver
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Driver')
-rw-r--r--compiler/GHC/Driver/Backpack.hs59
-rw-r--r--compiler/GHC/Driver/Backpack/Syntax.hs7
-rw-r--r--compiler/GHC/Driver/CodeOutput.hs15
-rw-r--r--compiler/GHC/Driver/Env.hs375
-rw-r--r--compiler/GHC/Driver/Finder.hs858
-rw-r--r--compiler/GHC/Driver/Hooks.hs34
-rw-r--r--compiler/GHC/Driver/Main.hs146
-rw-r--r--compiler/GHC/Driver/Make.hs45
-rw-r--r--compiler/GHC/Driver/MakeFile.hs10
-rw-r--r--compiler/GHC/Driver/Monad.hs7
-rw-r--r--compiler/GHC/Driver/Phases.hs93
-rw-r--r--compiler/GHC/Driver/Pipeline.hs73
-rw-r--r--compiler/GHC/Driver/Pipeline/Monad.hs12
-rw-r--r--compiler/GHC/Driver/Plugins.hs20
-rw-r--r--compiler/GHC/Driver/Session.hs32
-rw-r--r--compiler/GHC/Driver/Types.hs3340
16 files changed, 680 insertions, 4446 deletions
diff --git a/compiler/GHC/Driver/Backpack.hs b/compiler/GHC/Driver/Backpack.hs
index cd9cb8672b..54961066d8 100644
--- a/compiler/GHC/Driver/Backpack.hs
+++ b/compiler/GHC/Driver/Backpack.hs
@@ -23,43 +23,54 @@ import GHC.Prelude
-- In a separate module because it hooks into the parser.
import GHC.Driver.Backpack.Syntax
-
-import GHC.Parser.Annotation
-import GHC.Parser.Errors.Ppr
-import GHC hiding (Failed, Succeeded)
-import GHC.Parser
-import GHC.Parser.Lexer
import GHC.Driver.Config
import GHC.Driver.Monad
import GHC.Driver.Session
import GHC.Driver.Ppr
+import GHC.Driver.Main
+import GHC.Driver.Make
+import GHC.Driver.Env
+
+import GHC.Parser
+import GHC.Parser.Header
+import GHC.Parser.Lexer
+import GHC.Parser.Annotation
+import GHC.Parser.Errors.Ppr
+
+import GHC hiding (Failed, Succeeded)
import GHC.Tc.Utils.Monad
-import GHC.Tc.Module
-import GHC.Unit
-import GHC.Unit.State
-import GHC.Driver.Types
-import GHC.Data.StringBuffer
-import GHC.Data.FastString
-import qualified GHC.Data.ShortText as ST
-import GHC.Utils.Error
+import GHC.Iface.Recomp
+import GHC.Builtin.Names
+
import GHC.Types.SrcLoc
-import GHC.Driver.Main
+import GHC.Types.SourceError
+import GHC.Types.SourceText
+import GHC.Types.SourceFile
import GHC.Types.Unique.FM
import GHC.Types.Unique.DFM
-import GHC.Utils.Outputable
-import GHC.Data.Maybe
-import GHC.Parser.Header
-import GHC.Iface.Recomp
-import GHC.Driver.Make
import GHC.Types.Unique.DSet
-import GHC.Builtin.Names
-import GHC.Types.Basic hiding (SuccessFlag(..))
-import GHC.Driver.Finder
+
+import GHC.Utils.Outputable
import GHC.Utils.Misc
+import GHC.Utils.Panic
+import GHC.Utils.Error
+
+import GHC.Unit
+import GHC.Unit.External
+import GHC.Unit.State
+import GHC.Unit.Finder
+import GHC.Unit.Module.ModSummary (showModMsg)
+import GHC.Unit.Home.ModInfo
+
+import GHC.Runtime.Linker.Types
import qualified GHC.LanguageExtensions as LangExt
-import GHC.Utils.Panic
+import GHC.Data.Maybe
+import GHC.Data.StringBuffer
+import GHC.Data.FastString
+import qualified GHC.Data.ShortText as ST
+
import Data.List ( partition )
import System.Exit
import Control.Monad
diff --git a/compiler/GHC/Driver/Backpack/Syntax.hs b/compiler/GHC/Driver/Backpack/Syntax.hs
index e7e73b6cae..edaf5200d3 100644
--- a/compiler/GHC/Driver/Backpack/Syntax.hs
+++ b/compiler/GHC/Driver/Backpack/Syntax.hs
@@ -18,14 +18,17 @@ module GHC.Driver.Backpack.Syntax (
import GHC.Prelude
-import GHC.Driver.Phases
import GHC.Hs
+
import GHC.Types.SrcLoc
-import GHC.Utils.Outputable
+import GHC.Types.SourceFile
+
import GHC.Unit.Module.Name
import GHC.Unit.Types
import GHC.Unit.Info
+import GHC.Utils.Outputable
+
{-
************************************************************************
* *
diff --git a/compiler/GHC/Driver/CodeOutput.hs b/compiler/GHC/Driver/CodeOutput.hs
index cee81b900e..f9912ee303 100644
--- a/compiler/GHC/Driver/CodeOutput.hs
+++ b/compiler/GHC/Driver/CodeOutput.hs
@@ -17,33 +17,38 @@ where
import GHC.Prelude
import GHC.Platform
+import GHC.ForeignSrcLang
import GHC.CmmToAsm ( nativeCodeGen )
import GHC.CmmToLlvm ( llvmCodeGen )
-import GHC.Types.Unique.Supply ( mkSplitUniqSupply )
-
-import GHC.Driver.Finder ( mkStubPaths )
-import GHC.Driver.Backend
import GHC.CmmToC ( cmmToC )
import GHC.Cmm.Lint ( cmmLint )
import GHC.Cmm ( RawCmmGroup )
import GHC.Cmm.CLabel
-import GHC.Driver.Types
+
import GHC.Driver.Session
import GHC.Driver.Ppr
+import GHC.Driver.Backend
+
import qualified GHC.Data.ShortText as ST
import GHC.Data.Stream ( Stream )
import qualified GHC.Data.Stream as Stream
+
import GHC.SysTools.FileCleanup
import GHC.Utils.Error
import GHC.Utils.Outputable
import GHC.Utils.Panic
+
import GHC.Unit
import GHC.Unit.State
+import GHC.Unit.Finder ( mkStubPaths )
+
import GHC.Types.SrcLoc
import GHC.Types.CostCentre
+import GHC.Types.ForeignStubs
+import GHC.Types.Unique.Supply ( mkSplitUniqSupply )
import Control.Exception
import System.Directory
diff --git a/compiler/GHC/Driver/Env.hs b/compiler/GHC/Driver/Env.hs
new file mode 100644
index 0000000000..324177ac0f
--- /dev/null
+++ b/compiler/GHC/Driver/Env.hs
@@ -0,0 +1,375 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveFunctor #-}
+
+module GHC.Driver.Env
+ ( Hsc(..)
+ , HscEnv (..)
+ , runHsc
+ , mkInteractiveHscEnv
+ , runInteractiveHsc
+ , hscEPS
+ , hptCompleteSigs
+ , hptInstances
+ , hptAnns
+ , hptAllThings
+ , hptSomeThingsBelowUs
+ , hptRules
+ , prepareAnnotations
+ , lookupType
+ , lookupIfaceByModule
+ )
+where
+
+#include "HsVersions.h"
+
+import GHC.Prelude
+
+import GHC.Driver.Ppr
+import GHC.Driver.Session
+import GHC.Unit.Finder.Types
+
+import GHC.Runtime.Context
+import GHC.Runtime.Interpreter.Types (Interp)
+import GHC.Runtime.Linker.Types ( DynLinker )
+
+import GHC.Unit
+import GHC.Unit.Module.ModGuts
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.ModDetails
+import GHC.Unit.Module.Deps
+import GHC.Unit.Home.ModInfo
+import GHC.Unit.External
+
+import GHC.Core ( CoreRule )
+import GHC.Core.FamInstEnv
+import GHC.Core.InstEnv ( ClsInst )
+
+import GHC.Types.Annotations ( Annotation, AnnEnv, mkAnnEnv, plusAnnEnv )
+import GHC.Types.CompleteMatch
+import GHC.Types.Name
+import GHC.Types.Name.Cache
+import GHC.Types.Name.Env
+import GHC.Types.Target
+import GHC.Types.TypeEnv
+import GHC.Types.TyThing
+
+import GHC.Builtin.Names ( gHC_PRIM )
+
+import GHC.Data.Maybe
+import GHC.Data.Bag
+
+import GHC.Unit.Module.Graph
+
+import GHC.Utils.Outputable
+import GHC.Utils.Monad
+import GHC.Utils.Error
+import GHC.Utils.Panic
+import GHC.Utils.Misc
+
+import Control.Monad ( guard, ap )
+import Data.IORef
+
+-- | The Hsc monad: Passing an environment and warning state
+newtype Hsc a = Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages))
+ deriving (Functor)
+
+instance Applicative Hsc where
+ pure a = Hsc $ \_ w -> return (a, w)
+ (<*>) = ap
+
+instance Monad Hsc where
+ Hsc m >>= k = Hsc $ \e w -> do (a, w1) <- m e w
+ case k a of
+ Hsc k' -> k' e w1
+
+instance MonadIO Hsc where
+ liftIO io = Hsc $ \_ w -> do a <- io; return (a, w)
+
+instance HasDynFlags Hsc where
+ getDynFlags = Hsc $ \e w -> return (hsc_dflags e, w)
+
+runHsc :: HscEnv -> Hsc a -> IO a
+runHsc hsc_env (Hsc hsc) = do
+ (a, w) <- hsc hsc_env emptyBag
+ printOrThrowWarnings (hsc_dflags hsc_env) w
+ return a
+
+mkInteractiveHscEnv :: HscEnv -> HscEnv
+mkInteractiveHscEnv hsc_env = hsc_env{ hsc_dflags = interactive_dflags }
+ where
+ interactive_dflags = ic_dflags (hsc_IC hsc_env)
+
+runInteractiveHsc :: HscEnv -> Hsc a -> IO a
+-- A variant of runHsc that switches in the DynFlags from the
+-- InteractiveContext before running the Hsc computation.
+runInteractiveHsc hsc_env = runHsc (mkInteractiveHscEnv hsc_env)
+
+-- | HscEnv is like 'GHC.Driver.Monad.Session', except that some of the fields are immutable.
+-- An HscEnv is used to compile a single module from plain Haskell source
+-- code (after preprocessing) to either C, assembly or C--. It's also used
+-- to store the dynamic linker state to allow for multiple linkers in the
+-- same address space.
+-- Things like the module graph don't change during a single compilation.
+--
+-- Historical note: \"hsc\" used to be the name of the compiler binary,
+-- when there was a separate driver and compiler. To compile a single
+-- module, the driver would invoke hsc on the source code... so nowadays
+-- we think of hsc as the layer of the compiler that deals with compiling
+-- a single module.
+data HscEnv
+ = HscEnv {
+ hsc_dflags :: DynFlags,
+ -- ^ The dynamic flag settings
+
+ hsc_targets :: [Target],
+ -- ^ The targets (or roots) of the current session
+
+ hsc_mod_graph :: ModuleGraph,
+ -- ^ The module graph of the current session
+
+ hsc_IC :: InteractiveContext,
+ -- ^ The context for evaluating interactive statements
+
+ hsc_HPT :: HomePackageTable,
+ -- ^ The home package table describes already-compiled
+ -- home-package modules, /excluding/ the module we
+ -- are compiling right now.
+ -- (In one-shot mode the current module is the only
+ -- home-package module, so hsc_HPT is empty. All other
+ -- modules count as \"external-package\" modules.
+ -- However, even in GHCi mode, hi-boot interfaces are
+ -- demand-loaded into the external-package table.)
+ --
+ -- 'hsc_HPT' is not mutable because we only demand-load
+ -- external packages; the home package is eagerly
+ -- loaded, module by module, by the compilation manager.
+ --
+ -- The HPT may contain modules compiled earlier by @--make@
+ -- but not actually below the current module in the dependency
+ -- graph.
+ --
+ -- (This changes a previous invariant: changed Jan 05.)
+
+ hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
+ -- ^ Information about the currently loaded external packages.
+ -- This is mutable because packages will be demand-loaded during
+ -- a compilation run as required.
+
+ hsc_NC :: {-# UNPACK #-} !(IORef NameCache),
+ -- ^ As with 'hsc_EPS', this is side-effected by compiling to
+ -- reflect sucking in interface files. They cache the state of
+ -- external interface files, in effect.
+
+ hsc_FC :: {-# UNPACK #-} !(IORef FinderCache),
+ -- ^ The cached result of performing finding in the file system
+
+ hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
+ -- ^ Used for one-shot compilation only, to initialise
+ -- the 'IfGblEnv'. See 'GHC.Tc.Utils.tcg_type_env_var' for
+ -- 'GHC.Tc.Utils.TcGblEnv'. See also Note [hsc_type_env_var hack]
+
+ , hsc_interp :: Maybe Interp
+ -- ^ target code interpreter (if any) to use for TH and GHCi.
+ -- See Note [Target code interpreter]
+
+ , hsc_dynLinker :: DynLinker
+ -- ^ dynamic linker.
+
+ , hsc_home_unit :: !HomeUnit
+ -- ^ Home-unit
+
+ }
+
+{-
+
+Note [Target code interpreter]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+Template Haskell and GHCi use an interpreter to execute code that is built for
+the compiler target platform (= code host platform) on the compiler host
+platform (= code build platform).
+
+The internal interpreter can be used when both platforms are the same and when
+the built code is compatible with the compiler itself (same way, etc.). This
+interpreter is not always available: for instance stage1 compiler doesn't have
+it because there might be an ABI mismatch between the code objects (built by
+stage1 compiler) and the stage1 compiler itself (built by stage0 compiler).
+
+In most cases, an external interpreter can be used instead: it runs in a
+separate process and it communicates with the compiler via a two-way message
+passing channel. The process is lazily spawned to avoid overhead when it is not
+used.
+
+The target code interpreter to use can be selected per session via the
+`hsc_interp` field of `HscEnv`. There may be no interpreter available at all, in
+which case Template Haskell and GHCi will fail to run. The interpreter to use is
+configured via command-line flags (in `GHC.setSessionDynFlags`).
+
+
+-}
+
+-- Note [hsc_type_env_var hack]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- hsc_type_env_var is used to initialize tcg_type_env_var, and
+-- eventually it is the mutable variable that is queried from
+-- if_rec_types to get a TypeEnv. So, clearly, it's something
+-- related to knot-tying (see Note [Tying the knot]).
+-- hsc_type_env_var is used in two places: initTcRn (where
+-- it initializes tcg_type_env_var) and initIfaceCheck
+-- (where it initializes if_rec_types).
+--
+-- But why do we need a way to feed a mutable variable in? Why
+-- can't we just initialize tcg_type_env_var when we start
+-- typechecking? The problem is we need to knot-tie the
+-- EPS, and we may start adding things to the EPS before type
+-- checking starts.
+--
+-- Here is a concrete example. Suppose we are running
+-- "ghc -c A.hs", and we have this file system state:
+--
+-- A.hs-boot A.hi-boot **up to date**
+-- B.hs B.hi **up to date**
+-- A.hs A.hi **stale**
+--
+-- The first thing we do is run checkOldIface on A.hi.
+-- checkOldIface will call loadInterface on B.hi so it can
+-- get its hands on the fingerprints, to find out if A.hi
+-- needs recompilation. But loadInterface also populates
+-- the EPS! And so if compilation turns out to be necessary,
+-- as it is in this case, the thunks we put into the EPS for
+-- B.hi need to have the correct if_rec_types mutable variable
+-- to query.
+--
+-- If the mutable variable is only allocated WHEN we start
+-- typechecking, then that's too late: we can't get the
+-- information to the thunks. So we need to pre-commit
+-- to a type variable in 'hscIncrementalCompile' BEFORE we
+-- check the old interface.
+--
+-- This is all a massive hack because arguably checkOldIface
+-- should not populate the EPS. But that's a refactor for
+-- another day.
+
+-- | Retrieve the ExternalPackageState cache.
+hscEPS :: HscEnv -> IO ExternalPackageState
+hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
+
+hptCompleteSigs :: HscEnv -> [CompleteMatch]
+hptCompleteSigs = hptAllThings (md_complete_matches . hm_details)
+
+-- | Find all the instance declarations (of classes and families) from
+-- the Home Package Table filtered by the provided predicate function.
+-- Used in @tcRnImports@, to select the instances that are in the
+-- transitive closure of imports from the currently compiled module.
+hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst])
+hptInstances hsc_env want_this_module
+ = let (insts, famInsts) = unzip $ flip hptAllThings hsc_env $ \mod_info -> do
+ guard (want_this_module (moduleName (mi_module (hm_iface mod_info))))
+ let details = hm_details mod_info
+ return (md_insts details, md_fam_insts details)
+ in (concat insts, concat famInsts)
+
+-- | Get rules from modules "below" this one (in the dependency sense)
+hptRules :: HscEnv -> [ModuleNameWithIsBoot] -> [CoreRule]
+hptRules = hptSomeThingsBelowUs (md_rules . hm_details) False
+
+
+-- | Get annotations from modules "below" this one (in the dependency sense)
+hptAnns :: HscEnv -> Maybe [ModuleNameWithIsBoot] -> [Annotation]
+hptAnns hsc_env (Just deps) = hptSomeThingsBelowUs (md_anns . hm_details) False hsc_env deps
+hptAnns hsc_env Nothing = hptAllThings (md_anns . hm_details) hsc_env
+
+hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
+hptAllThings extract hsc_env = concatMap extract (eltsHpt (hsc_HPT hsc_env))
+
+-- | Get things from modules "below" this one (in the dependency sense)
+-- C.f Inst.hptInstances
+hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> [ModuleNameWithIsBoot] -> [a]
+hptSomeThingsBelowUs extract include_hi_boot hsc_env deps
+ | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
+
+ | otherwise
+ = let hpt = hsc_HPT hsc_env
+ in
+ [ thing
+ | -- Find each non-hi-boot module below me
+ GWIB { gwib_mod = mod, gwib_isBoot = is_boot } <- deps
+ , include_hi_boot || (is_boot == NotBoot)
+
+ -- unsavoury: when compiling the base package with --make, we
+ -- sometimes try to look up RULES etc for GHC.Prim. GHC.Prim won't
+ -- be in the HPT, because we never compile it; it's in the EPT
+ -- instead. ToDo: clean up, and remove this slightly bogus filter:
+ , mod /= moduleName gHC_PRIM
+
+ -- Look it up in the HPT
+ , let things = case lookupHpt hpt mod of
+ Just info -> extract info
+ Nothing -> pprTrace "WARNING in hptSomeThingsBelowUs" msg []
+ msg = vcat [text "missing module" <+> ppr mod,
+ text "Probable cause: out-of-date interface files"]
+ -- This really shouldn't happen, but see #962
+
+ -- And get its dfuns
+ , thing <- things ]
+
+
+-- | Deal with gathering annotations in from all possible places
+-- and combining them into a single 'AnnEnv'
+prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
+prepareAnnotations hsc_env mb_guts = do
+ eps <- hscEPS hsc_env
+ let -- Extract annotations from the module being compiled if supplied one
+ mb_this_module_anns = fmap (mkAnnEnv . mg_anns) mb_guts
+ -- Extract dependencies of the module if we are supplied one,
+ -- otherwise load annotations from all home package table
+ -- entries regardless of dependency ordering.
+ home_pkg_anns = (mkAnnEnv . hptAnns hsc_env) $ fmap (dep_mods . mg_deps) mb_guts
+ other_pkg_anns = eps_ann_env eps
+ ann_env = foldl1' plusAnnEnv $ catMaybes [mb_this_module_anns,
+ Just home_pkg_anns,
+ Just other_pkg_anns]
+ return ann_env
+
+-- | Find the 'TyThing' for the given 'Name' by using all the resources
+-- at our disposal: the compiled modules in the 'HomePackageTable' and the
+-- compiled modules in other packages that live in 'PackageTypeEnv'. Note
+-- that this does NOT look up the 'TyThing' in the module being compiled: you
+-- have to do that yourself, if desired
+lookupType :: HscEnv -> Name -> IO (Maybe TyThing)
+lookupType hsc_env name = do
+ eps <- liftIO $ readIORef (hsc_EPS hsc_env)
+ let pte = eps_PTE eps
+ hpt = hsc_HPT hsc_env
+
+ mod = ASSERT2( isExternalName name, ppr name )
+ if isHoleName name
+ then mkHomeModule (hsc_home_unit hsc_env) (moduleName (nameModule name))
+ else nameModule name
+
+ !ty = if isOneShot (ghcMode (hsc_dflags hsc_env))
+ -- in one-shot, we don't use the HPT
+ then lookupNameEnv pte name
+ else case lookupHptByModule hpt mod of
+ Just hm -> lookupNameEnv (md_types (hm_details hm)) name
+ Nothing -> lookupNameEnv pte name
+ pure ty
+
+-- | Find the 'ModIface' for a 'Module', searching in both the loaded home
+-- and external package module information
+lookupIfaceByModule
+ :: HomePackageTable
+ -> PackageIfaceTable
+ -> Module
+ -> Maybe ModIface
+lookupIfaceByModule hpt pit mod
+ = case lookupHptByModule hpt mod of
+ Just hm -> Just (hm_iface hm)
+ Nothing -> lookupModuleEnv pit mod
+ -- If the module does come from the home package, why do we look in the PIT as well?
+ -- (a) In OneShot mode, even home-package modules accumulate in the PIT
+ -- (b) Even in Batch (--make) mode, there is *one* case where a home-package
+ -- module is in the PIT, namely GHC.Prim when compiling the base package.
+ -- We could eliminate (b) if we wanted, by making GHC.Prim belong to a package
+ -- of its own, but it doesn't seem worth the bother.
+
diff --git a/compiler/GHC/Driver/Finder.hs b/compiler/GHC/Driver/Finder.hs
deleted file mode 100644
index 57a9551b0f..0000000000
--- a/compiler/GHC/Driver/Finder.hs
+++ /dev/null
@@ -1,858 +0,0 @@
-{-
-(c) The University of Glasgow, 2000-2006
-
-\section[Finder]{Module Finder}
--}
-
-{-# LANGUAGE CPP #-}
-{-# LANGUAGE FlexibleContexts #-}
-
-module GHC.Driver.Finder (
- flushFinderCaches,
- FindResult(..),
- findImportedModule,
- findPluginModule,
- findExactModule,
- findHomeModule,
- findExposedPackageModule,
- mkHomeModLocation,
- mkHomeModLocation2,
- mkHiOnlyModLocation,
- mkHiPath,
- mkObjPath,
- addHomeModuleToFinder,
- uncacheModule,
- mkStubPaths,
-
- findObjectLinkableMaybe,
- findObjectLinkable,
-
- cannotFindModule,
- cannotFindInterface,
-
- ) where
-
-#include "HsVersions.h"
-
-import GHC.Prelude
-
-import GHC.Unit.Types
-import GHC.Unit.Module
-import GHC.Unit.Home
-import GHC.Unit.State
-
-import GHC.Driver.Types
-import GHC.Data.FastString
-import qualified GHC.Data.ShortText as ST
-import GHC.Utils.Misc
-import GHC.Builtin.Names ( gHC_PRIM )
-import GHC.Driver.Session
-import GHC.Platform.Ways
-import GHC.Utils.Outputable as Outputable
-import GHC.Utils.Panic
-import GHC.Data.Maybe ( expectJust )
-
-import Data.IORef ( IORef, readIORef, atomicModifyIORef' )
-import System.Directory
-import System.FilePath
-import Control.Monad
-import Data.Time
-
-
-type FileExt = String -- Filename extension
-type BaseName = String -- Basename of file
-
--- -----------------------------------------------------------------------------
--- The Finder
-
--- The Finder provides a thin filesystem abstraction to the rest of
--- the compiler. For a given module, it can tell you where the
--- source, interface, and object files for that module live.
-
--- It does *not* know which particular package a module lives in. Use
--- Packages.lookupModuleInAllUnits for that.
-
--- -----------------------------------------------------------------------------
--- The finder's cache
-
--- remove all the home modules from the cache; package modules are
--- assumed to not move around during a session.
-flushFinderCaches :: HscEnv -> IO ()
-flushFinderCaches hsc_env =
- atomicModifyIORef' fc_ref $ \fm -> (filterInstalledModuleEnv is_ext fm, ())
- where
- fc_ref = hsc_FC hsc_env
- home_unit = hsc_home_unit hsc_env
- is_ext mod _ = not (isHomeInstalledModule home_unit mod)
-
-addToFinderCache :: IORef FinderCache -> InstalledModule -> InstalledFindResult -> IO ()
-addToFinderCache ref key val =
- atomicModifyIORef' ref $ \c -> (extendInstalledModuleEnv c key val, ())
-
-removeFromFinderCache :: IORef FinderCache -> InstalledModule -> IO ()
-removeFromFinderCache ref key =
- atomicModifyIORef' ref $ \c -> (delInstalledModuleEnv c key, ())
-
-lookupFinderCache :: IORef FinderCache -> InstalledModule -> IO (Maybe InstalledFindResult)
-lookupFinderCache ref key = do
- c <- readIORef ref
- return $! lookupInstalledModuleEnv c key
-
--- -----------------------------------------------------------------------------
--- The three external entry points
-
--- | Locate a module that was imported by the user. We have the
--- module's name, and possibly a package name. Without a package
--- name, this function will use the search path and the known exposed
--- packages to find the module, if a package is specified then only
--- that package is searched for the module.
-
-findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
-findImportedModule hsc_env mod_name mb_pkg =
- case mb_pkg of
- Nothing -> unqual_import
- Just pkg | pkg == fsLit "this" -> home_import -- "this" is special
- | otherwise -> pkg_import
- where
- home_import = findHomeModule hsc_env mod_name
-
- pkg_import = findExposedPackageModule hsc_env mod_name mb_pkg
-
- unqual_import = home_import
- `orIfNotFound`
- findExposedPackageModule hsc_env mod_name Nothing
-
--- | Locate a plugin module requested by the user, for a compiler
--- plugin. This consults the same set of exposed packages as
--- 'findImportedModule', unless @-hide-all-plugin-packages@ or
--- @-plugin-package@ are specified.
-findPluginModule :: HscEnv -> ModuleName -> IO FindResult
-findPluginModule hsc_env mod_name =
- findHomeModule hsc_env mod_name
- `orIfNotFound`
- findExposedPluginPackageModule hsc_env mod_name
-
--- | Locate a specific 'Module'. The purpose of this function is to
--- create a 'ModLocation' for a given 'Module', that is to find out
--- where the files associated with this module live. It is used when
--- reading the interface for a module mentioned by another interface,
--- for example (a "system import").
-
-findExactModule :: HscEnv -> InstalledModule -> IO InstalledFindResult
-findExactModule hsc_env mod =
- let home_unit = hsc_home_unit hsc_env
- in if isHomeInstalledModule home_unit mod
- then findInstalledHomeModule hsc_env (moduleName mod)
- else findPackageModule hsc_env mod
-
--- -----------------------------------------------------------------------------
--- Helpers
-
--- | Given a monadic actions @this@ and @or_this@, first execute
--- @this@. If the returned 'FindResult' is successful, return
--- it; otherwise, execute @or_this@. If both failed, this function
--- also combines their failure messages in a reasonable way.
-orIfNotFound :: Monad m => m FindResult -> m FindResult -> m FindResult
-orIfNotFound this or_this = do
- res <- this
- case res of
- NotFound { fr_paths = paths1, fr_mods_hidden = mh1
- , fr_pkgs_hidden = ph1, fr_unusables = u1, fr_suggestions = s1 }
- -> do res2 <- or_this
- case res2 of
- NotFound { fr_paths = paths2, fr_pkg = mb_pkg2, fr_mods_hidden = mh2
- , fr_pkgs_hidden = ph2, fr_unusables = u2
- , fr_suggestions = s2 }
- -> return (NotFound { fr_paths = paths1 ++ paths2
- , fr_pkg = mb_pkg2 -- snd arg is the package search
- , fr_mods_hidden = mh1 ++ mh2
- , fr_pkgs_hidden = ph1 ++ ph2
- , fr_unusables = u1 ++ u2
- , fr_suggestions = s1 ++ s2 })
- _other -> return res2
- _other -> return res
-
--- | Helper function for 'findHomeModule': this function wraps an IO action
--- which would look up @mod_name@ in the file system (the home package),
--- and first consults the 'hsc_FC' cache to see if the lookup has already
--- been done. Otherwise, do the lookup (with the IO action) and save
--- the result in the finder cache and the module location cache (if it
--- was successful.)
-homeSearchCache :: HscEnv -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
-homeSearchCache hsc_env mod_name do_this = do
- let home_unit = hsc_home_unit hsc_env
- mod = mkHomeInstalledModule home_unit mod_name
- modLocationCache hsc_env mod do_this
-
-findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString
- -> IO FindResult
-findExposedPackageModule hsc_env mod_name mb_pkg
- = findLookupResult hsc_env
- $ lookupModuleWithSuggestions
- (unitState (hsc_dflags hsc_env)) mod_name mb_pkg
-
-findExposedPluginPackageModule :: HscEnv -> ModuleName
- -> IO FindResult
-findExposedPluginPackageModule hsc_env mod_name
- = findLookupResult hsc_env
- $ lookupPluginModuleWithSuggestions
- (unitState (hsc_dflags hsc_env)) mod_name Nothing
-
-findLookupResult :: HscEnv -> LookupResult -> IO FindResult
-findLookupResult hsc_env r = case r of
- LookupFound m pkg_conf -> do
- let im = fst (getModuleInstantiation m)
- r' <- findPackageModule_ hsc_env im pkg_conf
- case r' of
- -- TODO: ghc -M is unlikely to do the right thing
- -- with just the location of the thing that was
- -- instantiated; you probably also need all of the
- -- implicit locations from the instances
- InstalledFound loc _ -> return (Found loc m)
- InstalledNoPackage _ -> return (NoPackage (moduleUnit m))
- InstalledNotFound fp _ -> return (NotFound{ fr_paths = fp, fr_pkg = Just (moduleUnit m)
- , fr_pkgs_hidden = []
- , fr_mods_hidden = []
- , fr_unusables = []
- , fr_suggestions = []})
- LookupMultiple rs ->
- return (FoundMultiple rs)
- LookupHidden pkg_hiddens mod_hiddens ->
- return (NotFound{ fr_paths = [], fr_pkg = Nothing
- , fr_pkgs_hidden = map (moduleUnit.fst) pkg_hiddens
- , fr_mods_hidden = map (moduleUnit.fst) mod_hiddens
- , fr_unusables = []
- , fr_suggestions = [] })
- LookupUnusable unusable ->
- let unusables' = map get_unusable unusable
- get_unusable (m, ModUnusable r) = (moduleUnit m, r)
- get_unusable (_, r) =
- pprPanic "findLookupResult: unexpected origin" (ppr r)
- in return (NotFound{ fr_paths = [], fr_pkg = Nothing
- , fr_pkgs_hidden = []
- , fr_mods_hidden = []
- , fr_unusables = unusables'
- , fr_suggestions = [] })
- LookupNotFound suggest -> do
- let suggest'
- | gopt Opt_HelpfulErrors (hsc_dflags hsc_env) = suggest
- | otherwise = []
- return (NotFound{ fr_paths = [], fr_pkg = Nothing
- , fr_pkgs_hidden = []
- , fr_mods_hidden = []
- , fr_unusables = []
- , fr_suggestions = suggest' })
-
-modLocationCache :: HscEnv -> InstalledModule -> IO InstalledFindResult -> IO InstalledFindResult
-modLocationCache hsc_env mod do_this = do
- m <- lookupFinderCache (hsc_FC hsc_env) mod
- case m of
- Just result -> return result
- Nothing -> do
- result <- do_this
- addToFinderCache (hsc_FC hsc_env) mod result
- return result
-
--- This returns a module because it's more convenient for users
-addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO Module
-addHomeModuleToFinder hsc_env mod_name loc = do
- let home_unit = hsc_home_unit hsc_env
- mod = mkHomeInstalledModule home_unit mod_name
- addToFinderCache (hsc_FC hsc_env) mod (InstalledFound loc mod)
- return (mkHomeModule home_unit mod_name)
-
-uncacheModule :: HscEnv -> ModuleName -> IO ()
-uncacheModule hsc_env mod_name = do
- let home_unit = hsc_home_unit hsc_env
- mod = mkHomeInstalledModule home_unit mod_name
- removeFromFinderCache (hsc_FC hsc_env) mod
-
--- -----------------------------------------------------------------------------
--- The internal workers
-
-findHomeModule :: HscEnv -> ModuleName -> IO FindResult
-findHomeModule hsc_env mod_name = do
- r <- findInstalledHomeModule hsc_env mod_name
- return $ case r of
- InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name)
- InstalledNoPackage _ -> NoPackage uid -- impossible
- InstalledNotFound fps _ -> NotFound {
- fr_paths = fps,
- fr_pkg = Just uid,
- fr_mods_hidden = [],
- fr_pkgs_hidden = [],
- fr_unusables = [],
- fr_suggestions = []
- }
- where
- home_unit = hsc_home_unit hsc_env
- uid = homeUnitAsUnit home_unit
-
--- | Implements the search for a module name in the home package only. Calling
--- this function directly is usually *not* what you want; currently, it's used
--- as a building block for the following operations:
---
--- 1. When you do a normal package lookup, we first check if the module
--- is available in the home module, before looking it up in the package
--- database.
---
--- 2. When you have a package qualified import with package name "this",
--- we shortcut to the home module.
---
--- 3. When we look up an exact 'Module', if the unit id associated with
--- the module is the current home module do a look up in the home module.
---
--- 4. Some special-case code in GHCi (ToDo: Figure out why that needs to
--- call this.)
-findInstalledHomeModule :: HscEnv -> ModuleName -> IO InstalledFindResult
-findInstalledHomeModule hsc_env mod_name =
- homeSearchCache hsc_env mod_name $
- let
- dflags = hsc_dflags hsc_env
- home_unit = hsc_home_unit hsc_env
- home_path = importPaths dflags
- hisuf = hiSuf dflags
- mod = mkHomeInstalledModule home_unit mod_name
-
- source_exts =
- [ ("hs", mkHomeModLocationSearched dflags mod_name "hs")
- , ("lhs", mkHomeModLocationSearched dflags mod_name "lhs")
- , ("hsig", mkHomeModLocationSearched dflags mod_name "hsig")
- , ("lhsig", mkHomeModLocationSearched dflags mod_name "lhsig")
- ]
-
- -- we use mkHomeModHiOnlyLocation instead of mkHiOnlyModLocation so that
- -- when hiDir field is set in dflags, we know to look there (see #16500)
- hi_exts = [ (hisuf, mkHomeModHiOnlyLocation dflags mod_name)
- , (addBootSuffix hisuf, mkHomeModHiOnlyLocation dflags mod_name)
- ]
-
- -- In compilation manager modes, we look for source files in the home
- -- package because we can compile these automatically. In one-shot
- -- compilation mode we look for .hi and .hi-boot files only.
- exts | isOneShot (ghcMode dflags) = hi_exts
- | otherwise = source_exts
- in
-
- -- special case for GHC.Prim; we won't find it in the filesystem.
- -- This is important only when compiling the base package (where GHC.Prim
- -- is a home module).
- if mod `installedModuleEq` gHC_PRIM
- then return (InstalledFound (error "GHC.Prim ModLocation") mod)
- else searchPathExts home_path mod exts
-
-
--- | Search for a module in external packages only.
-findPackageModule :: HscEnv -> InstalledModule -> IO InstalledFindResult
-findPackageModule hsc_env mod = do
- let
- dflags = hsc_dflags hsc_env
- pkg_id = moduleUnit mod
- pkgstate = unitState dflags
- --
- case lookupUnitId pkgstate pkg_id of
- Nothing -> return (InstalledNoPackage pkg_id)
- Just pkg_conf -> findPackageModule_ hsc_env mod pkg_conf
-
--- | Look up the interface file associated with module @mod@. This function
--- requires a few invariants to be upheld: (1) the 'Module' in question must
--- be the module identifier of the *original* implementation of a module,
--- not a reexport (this invariant is upheld by "GHC.Unit.State") and (2)
--- the 'UnitInfo' must be consistent with the unit id in the 'Module'.
--- The redundancy is to avoid an extra lookup in the package state
--- for the appropriate config.
-findPackageModule_ :: HscEnv -> InstalledModule -> UnitInfo -> IO InstalledFindResult
-findPackageModule_ hsc_env mod pkg_conf =
- ASSERT2( moduleUnit mod == unitId pkg_conf, ppr (moduleUnit mod) <+> ppr (unitId pkg_conf) )
- modLocationCache hsc_env mod $
-
- -- special case for GHC.Prim; we won't find it in the filesystem.
- if mod `installedModuleEq` gHC_PRIM
- then return (InstalledFound (error "GHC.Prim ModLocation") mod)
- else
-
- let
- dflags = hsc_dflags hsc_env
- tag = waysBuildTag (ways dflags)
-
- -- hi-suffix for packages depends on the build tag.
- package_hisuf | null tag = "hi"
- | otherwise = tag ++ "_hi"
-
- mk_hi_loc = mkHiOnlyModLocation dflags package_hisuf
-
- import_dirs = map ST.unpack $ unitImportDirs pkg_conf
- -- we never look for a .hi-boot file in an external package;
- -- .hi-boot files only make sense for the home package.
- in
- case import_dirs of
- [one] | MkDepend <- ghcMode dflags -> do
- -- there's only one place that this .hi file can be, so
- -- don't bother looking for it.
- let basename = moduleNameSlashes (moduleName mod)
- loc <- mk_hi_loc one basename
- return (InstalledFound loc mod)
- _otherwise ->
- searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
-
--- -----------------------------------------------------------------------------
--- General path searching
-
-searchPathExts
- :: [FilePath] -- paths to search
- -> InstalledModule -- module name
- -> [ (
- FileExt, -- suffix
- FilePath -> BaseName -> IO ModLocation -- action
- )
- ]
- -> IO InstalledFindResult
-
-searchPathExts paths mod exts
- = do result <- search to_search
-{-
- hPutStrLn stderr (showSDoc $
- vcat [text "Search" <+> ppr mod <+> sep (map (text. fst) exts)
- , nest 2 (vcat (map text paths))
- , case result of
- Succeeded (loc, p) -> text "Found" <+> ppr loc
- Failed fs -> text "not found"])
--}
- return result
-
- where
- basename = moduleNameSlashes (moduleName mod)
-
- to_search :: [(FilePath, IO ModLocation)]
- to_search = [ (file, fn path basename)
- | path <- paths,
- (ext,fn) <- exts,
- let base | path == "." = basename
- | otherwise = path </> basename
- file = base <.> ext
- ]
-
- search [] = return (InstalledNotFound (map fst to_search) (Just (moduleUnit mod)))
-
- search ((file, mk_result) : rest) = do
- b <- doesFileExist file
- if b
- then do { loc <- mk_result; return (InstalledFound loc mod) }
- else search rest
-
-mkHomeModLocationSearched :: DynFlags -> ModuleName -> FileExt
- -> FilePath -> BaseName -> IO ModLocation
-mkHomeModLocationSearched dflags mod suff path basename = do
- mkHomeModLocation2 dflags mod (path </> basename) suff
-
--- -----------------------------------------------------------------------------
--- Constructing a home module location
-
--- This is where we construct the ModLocation for a module in the home
--- package, for which we have a source file. It is called from three
--- places:
---
--- (a) Here in the finder, when we are searching for a module to import,
--- using the search path (-i option).
---
--- (b) The compilation manager, when constructing the ModLocation for
--- a "root" module (a source file named explicitly on the command line
--- or in a :load command in GHCi).
---
--- (c) The driver in one-shot mode, when we need to construct a
--- ModLocation for a source file named on the command-line.
---
--- Parameters are:
---
--- mod
--- The name of the module
---
--- path
--- (a): The search path component where the source file was found.
--- (b) and (c): "."
---
--- src_basename
--- (a): (moduleNameSlashes mod)
--- (b) and (c): The filename of the source file, minus its extension
---
--- ext
--- The filename extension of the source file (usually "hs" or "lhs").
-
-mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation
-mkHomeModLocation dflags mod src_filename = do
- let (basename,extension) = splitExtension src_filename
- mkHomeModLocation2 dflags mod basename extension
-
-mkHomeModLocation2 :: DynFlags
- -> ModuleName
- -> FilePath -- Of source module, without suffix
- -> String -- Suffix
- -> IO ModLocation
-mkHomeModLocation2 dflags mod src_basename ext = do
- let mod_basename = moduleNameSlashes mod
-
- obj_fn = mkObjPath dflags src_basename mod_basename
- hi_fn = mkHiPath dflags src_basename mod_basename
- hie_fn = mkHiePath dflags src_basename mod_basename
-
- return (ModLocation{ ml_hs_file = Just (src_basename <.> ext),
- ml_hi_file = hi_fn,
- ml_obj_file = obj_fn,
- ml_hie_file = hie_fn })
-
-mkHomeModHiOnlyLocation :: DynFlags
- -> ModuleName
- -> FilePath
- -> BaseName
- -> IO ModLocation
-mkHomeModHiOnlyLocation dflags mod path basename = do
- loc <- mkHomeModLocation2 dflags mod (path </> basename) ""
- return loc { ml_hs_file = Nothing }
-
-mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String
- -> IO ModLocation
-mkHiOnlyModLocation dflags hisuf path basename
- = do let full_basename = path </> basename
- obj_fn = mkObjPath dflags full_basename basename
- hie_fn = mkHiePath dflags full_basename basename
- return ModLocation{ ml_hs_file = Nothing,
- ml_hi_file = full_basename <.> hisuf,
- -- Remove the .hi-boot suffix from
- -- hi_file, if it had one. We always
- -- want the name of the real .hi file
- -- in the ml_hi_file field.
- ml_obj_file = obj_fn,
- ml_hie_file = hie_fn
- }
-
--- | Constructs the filename of a .o file for a given source file.
--- Does /not/ check whether the .o file exists
-mkObjPath
- :: DynFlags
- -> FilePath -- the filename of the source file, minus the extension
- -> String -- the module name with dots replaced by slashes
- -> FilePath
-mkObjPath dflags basename mod_basename = obj_basename <.> osuf
- where
- odir = objectDir dflags
- osuf = objectSuf dflags
-
- obj_basename | Just dir <- odir = dir </> mod_basename
- | otherwise = basename
-
-
--- | Constructs the filename of a .hi file for a given source file.
--- Does /not/ check whether the .hi file exists
-mkHiPath
- :: DynFlags
- -> FilePath -- the filename of the source file, minus the extension
- -> String -- the module name with dots replaced by slashes
- -> FilePath
-mkHiPath dflags basename mod_basename = hi_basename <.> hisuf
- where
- hidir = hiDir dflags
- hisuf = hiSuf dflags
-
- hi_basename | Just dir <- hidir = dir </> mod_basename
- | otherwise = basename
-
--- | Constructs the filename of a .hie file for a given source file.
--- Does /not/ check whether the .hie file exists
-mkHiePath
- :: DynFlags
- -> FilePath -- the filename of the source file, minus the extension
- -> String -- the module name with dots replaced by slashes
- -> FilePath
-mkHiePath dflags basename mod_basename = hie_basename <.> hiesuf
- where
- hiedir = hieDir dflags
- hiesuf = hieSuf dflags
-
- hie_basename | Just dir <- hiedir = dir </> mod_basename
- | otherwise = basename
-
-
-
--- -----------------------------------------------------------------------------
--- Filenames of the stub files
-
--- We don't have to store these in ModLocations, because they can be derived
--- from other available information, and they're only rarely needed.
-
-mkStubPaths
- :: DynFlags
- -> ModuleName
- -> ModLocation
- -> FilePath
-
-mkStubPaths dflags mod location
- = let
- stubdir = stubDir dflags
-
- mod_basename = moduleNameSlashes mod
- src_basename = dropExtension $ expectJust "mkStubPaths"
- (ml_hs_file location)
-
- stub_basename0
- | Just dir <- stubdir = dir </> mod_basename
- | otherwise = src_basename
-
- stub_basename = stub_basename0 ++ "_stub"
- in
- stub_basename <.> "h"
-
--- -----------------------------------------------------------------------------
--- findLinkable isn't related to the other stuff in here,
--- but there's no other obvious place for it
-
-findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)
-findObjectLinkableMaybe mod locn
- = do let obj_fn = ml_obj_file locn
- maybe_obj_time <- modificationTimeIfExists obj_fn
- case maybe_obj_time of
- Nothing -> return Nothing
- Just obj_time -> liftM Just (findObjectLinkable mod obj_fn obj_time)
-
--- Make an object linkable when we know the object file exists, and we know
--- its modification time.
-findObjectLinkable :: Module -> FilePath -> UTCTime -> IO Linkable
-findObjectLinkable mod obj_fn obj_time = return (LM obj_time mod [DotO obj_fn])
- -- We used to look for _stub.o files here, but that was a bug (#706)
- -- Now GHC merges the stub.o into the main .o (#3687)
-
--- -----------------------------------------------------------------------------
--- Error messages
-
-cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc
-cannotFindModule dflags mod res = pprWithUnitState unit_state $
- cantFindErr (sLit cannotFindMsg)
- (sLit "Ambiguous module name")
- dflags mod res
- where
- unit_state = unitState dflags
- cannotFindMsg =
- case res of
- NotFound { fr_mods_hidden = hidden_mods
- , fr_pkgs_hidden = hidden_pkgs
- , fr_unusables = unusables }
- | not (null hidden_mods && null hidden_pkgs && null unusables)
- -> "Could not load module"
- _ -> "Could not find module"
-
-cannotFindInterface :: DynFlags -> ModuleName -> InstalledFindResult -> SDoc
-cannotFindInterface = cantFindInstalledErr (sLit "Failed to load interface for")
- (sLit "Ambiguous interface for")
-
-cantFindErr :: PtrString -> PtrString -> DynFlags -> ModuleName -> FindResult
- -> SDoc
-cantFindErr _ multiple_found _ mod_name (FoundMultiple mods)
- | Just pkgs <- unambiguousPackages
- = hang (ptext multiple_found <+> quotes (ppr mod_name) <> colon) 2 (
- sep [text "it was found in multiple packages:",
- hsep (map ppr pkgs) ]
- )
- | otherwise
- = hang (ptext multiple_found <+> quotes (ppr mod_name) <> colon) 2 (
- vcat (map pprMod mods)
- )
- where
- unambiguousPackages = foldl' unambiguousPackage (Just []) mods
- unambiguousPackage (Just xs) (m, ModOrigin (Just _) _ _ _)
- = Just (moduleUnit m : xs)
- unambiguousPackage _ _ = Nothing
-
- pprMod (m, o) = text "it is bound as" <+> ppr m <+>
- text "by" <+> pprOrigin m o
- pprOrigin _ ModHidden = panic "cantFindErr: bound by mod hidden"
- pprOrigin _ (ModUnusable _) = panic "cantFindErr: bound by mod unusable"
- pprOrigin m (ModOrigin e res _ f) = sep $ punctuate comma (
- if e == Just True
- then [text "package" <+> ppr (moduleUnit m)]
- else [] ++
- map ((text "a reexport in package" <+>)
- .ppr.mkUnit) res ++
- if f then [text "a package flag"] else []
- )
-
-cantFindErr cannot_find _ dflags mod_name find_result
- = ptext cannot_find <+> quotes (ppr mod_name)
- $$ more_info
- where
- pkgs = unitState dflags
- home_unit = mkHomeUnitFromFlags dflags
- more_info
- = case find_result of
- NoPackage pkg
- -> text "no unit id matching" <+> quotes (ppr pkg) <+>
- text "was found"
-
- NotFound { fr_paths = files, fr_pkg = mb_pkg
- , fr_mods_hidden = mod_hiddens, fr_pkgs_hidden = pkg_hiddens
- , fr_unusables = unusables, fr_suggestions = suggest }
- | Just pkg <- mb_pkg, not (isHomeUnit home_unit pkg)
- -> not_found_in_package pkg files
-
- | not (null suggest)
- -> pp_suggestions suggest $$ tried_these files dflags
-
- | null files && null mod_hiddens &&
- null pkg_hiddens && null unusables
- -> text "It is not a module in the current program, or in any known package."
-
- | otherwise
- -> vcat (map pkg_hidden pkg_hiddens) $$
- vcat (map mod_hidden mod_hiddens) $$
- vcat (map unusable unusables) $$
- tried_these files dflags
-
- _ -> panic "cantFindErr"
-
- build_tag = waysBuildTag (ways dflags)
-
- not_found_in_package pkg files
- | build_tag /= ""
- = let
- build = if build_tag == "p" then "profiling"
- else "\"" ++ build_tag ++ "\""
- in
- text "Perhaps you haven't installed the " <> text build <>
- text " libraries for package " <> quotes (ppr pkg) <> char '?' $$
- tried_these files dflags
-
- | otherwise
- = text "There are files missing in the " <> quotes (ppr pkg) <>
- text " package," $$
- text "try running 'ghc-pkg check'." $$
- tried_these files dflags
-
- pkg_hidden :: Unit -> SDoc
- pkg_hidden uid =
- text "It is a member of the hidden package"
- <+> quotes (ppr uid)
- --FIXME: we don't really want to show the unit id here we should
- -- show the source package id or installed package id if it's ambiguous
- <> dot $$ pkg_hidden_hint uid
- pkg_hidden_hint uid
- | gopt Opt_BuildingCabalPackage dflags
- = let pkg = expectJust "pkg_hidden" (lookupUnit pkgs uid)
- in text "Perhaps you need to add" <+>
- quotes (ppr (unitPackageName pkg)) <+>
- text "to the build-depends in your .cabal file."
- | Just pkg <- lookupUnit pkgs uid
- = text "You can run" <+>
- quotes (text ":set -package " <> ppr (unitPackageName pkg)) <+>
- text "to expose it." $$
- text "(Note: this unloads all the modules in the current scope.)"
- | otherwise = Outputable.empty
-
- mod_hidden pkg =
- text "it is a hidden module in the package" <+> quotes (ppr pkg)
-
- unusable (pkg, reason)
- = text "It is a member of the package"
- <+> quotes (ppr pkg)
- $$ pprReason (text "which is") reason
-
- pp_suggestions :: [ModuleSuggestion] -> SDoc
- pp_suggestions sugs
- | null sugs = Outputable.empty
- | otherwise = hang (text "Perhaps you meant")
- 2 (vcat (map pp_sugg sugs))
-
- -- NB: Prefer the *original* location, and then reexports, and then
- -- package flags when making suggestions. ToDo: if the original package
- -- also has a reexport, prefer that one
- pp_sugg (SuggestVisible m mod o) = ppr m <+> provenance o
- where provenance ModHidden = Outputable.empty
- provenance (ModUnusable _) = Outputable.empty
- provenance (ModOrigin{ fromOrigUnit = e,
- fromExposedReexport = res,
- fromPackageFlag = f })
- | Just True <- e
- = parens (text "from" <+> ppr (moduleUnit mod))
- | f && moduleName mod == m
- = parens (text "from" <+> ppr (moduleUnit mod))
- | (pkg:_) <- res
- = parens (text "from" <+> ppr (mkUnit pkg)
- <> comma <+> text "reexporting" <+> ppr mod)
- | f
- = parens (text "defined via package flags to be"
- <+> ppr mod)
- | otherwise = Outputable.empty
- pp_sugg (SuggestHidden m mod o) = ppr m <+> provenance o
- where provenance ModHidden = Outputable.empty
- provenance (ModUnusable _) = Outputable.empty
- provenance (ModOrigin{ fromOrigUnit = e,
- fromHiddenReexport = rhs })
- | Just False <- e
- = parens (text "needs flag -package-id"
- <+> ppr (moduleUnit mod))
- | (pkg:_) <- rhs
- = parens (text "needs flag -package-id"
- <+> ppr (mkUnit pkg))
- | otherwise = Outputable.empty
-
-cantFindInstalledErr :: PtrString -> PtrString -> DynFlags -> ModuleName
- -> InstalledFindResult -> SDoc
-cantFindInstalledErr cannot_find _ dflags mod_name find_result
- = ptext cannot_find <+> quotes (ppr mod_name)
- $$ more_info
- where
- home_unit = mkHomeUnitFromFlags dflags
- unit_state = unitState dflags
- build_tag = waysBuildTag (ways dflags)
-
- more_info
- = case find_result of
- InstalledNoPackage pkg
- -> text "no unit id matching" <+> quotes (ppr pkg) <+>
- text "was found" $$ looks_like_srcpkgid pkg
-
- InstalledNotFound files mb_pkg
- | Just pkg <- mb_pkg, not (isHomeUnitId home_unit pkg)
- -> not_found_in_package pkg files
-
- | null files
- -> text "It is not a module in the current program, or in any known package."
-
- | otherwise
- -> tried_these files dflags
-
- _ -> panic "cantFindInstalledErr"
-
- looks_like_srcpkgid :: UnitId -> SDoc
- looks_like_srcpkgid pk
- -- Unsafely coerce a unit id (i.e. an installed package component
- -- identifier) into a PackageId and see if it means anything.
- | (pkg:pkgs) <- searchPackageId unit_state (PackageId (unitIdFS pk))
- = parens (text "This unit ID looks like the source package ID;" $$
- text "the real unit ID is" <+> quotes (ftext (unitIdFS (unitId pkg))) $$
- (if null pkgs then Outputable.empty
- else text "and" <+> int (length pkgs) <+> text "other candidates"))
- -- Todo: also check if it looks like a package name!
- | otherwise = Outputable.empty
-
- not_found_in_package pkg files
- | build_tag /= ""
- = let
- build = if build_tag == "p" then "profiling"
- else "\"" ++ build_tag ++ "\""
- in
- text "Perhaps you haven't installed the " <> text build <>
- text " libraries for package " <> quotes (ppr pkg) <> char '?' $$
- tried_these files dflags
-
- | otherwise
- = text "There are files missing in the " <> quotes (ppr pkg) <>
- text " package," $$
- text "try running 'ghc-pkg check'." $$
- tried_these files dflags
-
-tried_these :: [FilePath] -> DynFlags -> SDoc
-tried_these files dflags
- | null files = Outputable.empty
- | verbosity dflags < 3 =
- text "Use -v (or `:set -v` in ghci) " <>
- text "to see a list of the files searched for."
- | otherwise =
- hang (text "Locations searched:") 2 $ vcat (map text files)
diff --git a/compiler/GHC/Driver/Hooks.hs b/compiler/GHC/Driver/Hooks.hs
index 36b97502cb..25e6530eef 100644
--- a/compiler/GHC/Driver/Hooks.hs
+++ b/compiler/GHC/Driver/Hooks.hs
@@ -31,34 +31,46 @@ where
import GHC.Prelude
+import GHC.Driver.Env
import GHC.Driver.Session
import GHC.Driver.Pipeline.Monad
-import GHC.Driver.Types
+
import GHC.Hs.Decls
import GHC.Hs.Binds
import GHC.Hs.Expr
-import GHC.Tc.Types
-import GHC.Data.Bag
+import GHC.Hs.Extension
+
import GHC.Types.Name.Reader
import GHC.Types.Name
import GHC.Types.Id
-import GHC.Core
-import GHCi.RemoteTypes
import GHC.Types.SrcLoc
-import GHC.Core.Type
-import System.Process
import GHC.Types.Basic
+import GHC.Types.CostCentre
+import GHC.Types.Meta
+import GHC.Types.HpcInfo
+
import GHC.Unit.Module
+import GHC.Unit.Module.ModSummary
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Home.ModInfo
+
+import GHC.Core
import GHC.Core.TyCon
-import GHC.Types.CostCentre
+import GHC.Core.Type
+
+import GHC.Tc.Types
import GHC.Stg.Syntax
-import GHC.Data.Stream
-import GHC.Cmm
-import GHC.Hs.Extension
import GHC.StgToCmm.Types (ModuleLFInfos)
+import GHC.Cmm
+
+import GHCi.RemoteTypes
+
+import GHC.Data.Stream
+import GHC.Data.Bag
import Data.Maybe
import qualified Data.Kind
+import System.Process
{-
************************************************************************
diff --git a/compiler/GHC/Driver/Main.hs b/compiler/GHC/Driver/Main.hs
index 827855a519..143b1f5ccd 100644
--- a/compiler/GHC/Driver/Main.hs
+++ b/compiler/GHC/Driver/Main.hs
@@ -88,88 +88,127 @@ module GHC.Driver.Main
import GHC.Prelude
-import Data.Data hiding (Fixity, TyCon)
-import Data.Maybe ( fromJust )
-import GHC.Types.Id
+import GHC.Driver.Plugins
+import GHC.Driver.Session
+import GHC.Driver.Backend
+import GHC.Driver.Env
+import GHC.Driver.CodeOutput
+import GHC.Driver.Config
+import GHC.Driver.Hooks
+
+import GHC.Runtime.Context
+import GHC.Runtime.Linker
+import GHC.Runtime.Linker.Types
import GHC.Runtime.Interpreter ( addSptEntry )
+import GHC.Runtime.Loader ( initializePlugins )
import GHCi.RemoteTypes ( ForeignHValue )
+import GHC.ByteCode.Types
+
+import GHC.Hs
+import GHC.Hs.Dump
+import GHC.Hs.Stats ( ppSourceStats )
+
+import GHC.HsToCore
+
import GHC.CoreToByteCode ( byteCodeGen, coreExprToBCOs )
-import GHC.Runtime.Linker
+
+import GHC.IfaceToCore ( typecheckIface )
+
+import GHC.Iface.Load ( ifaceStats, initExternalPackageState, writeIface )
+import GHC.Iface.Make
+import GHC.Iface.Recomp
+import GHC.Iface.Tidy
+import GHC.Iface.Ext.Ast ( mkHieFile )
+import GHC.Iface.Ext.Types ( getAsts, hie_asts, hie_module )
+import GHC.Iface.Ext.Binary ( readHieFile, writeHieFile , hie_file_result, NameCacheUpdater(..))
+import GHC.Iface.Ext.Debug ( diffFile, validateScopes )
+import GHC.Iface.Env ( updNameCache )
+
+import GHC.Core
import GHC.Core.Tidy ( tidyExpr )
import GHC.Core.Type ( Type, Kind )
import GHC.Core.Lint ( lintInteractiveExpr )
-import GHC.Types.Var.Env ( emptyTidyEnv )
-import GHC.Utils.Panic
import GHC.Core.ConLike
+import GHC.Core.Opt.Pipeline
+import GHC.Core.TyCon
+import GHC.Core.InstEnv
+import GHC.Core.FamInstEnv
+
+import GHC.CoreToStg.Prep
+import GHC.CoreToStg ( coreToStg )
import GHC.Parser.Annotation
import GHC.Parser.Errors
import GHC.Parser.Errors.Ppr
-import GHC.Unit
-import GHC.Unit.State
-import GHC.Types.Name.Reader
-import GHC.Hs
-import GHC.Hs.Dump
-import GHC.Core
-import GHC.Data.StringBuffer
import GHC.Parser
import GHC.Parser.Lexer as Lexer
-import GHC.Types.SrcLoc
+
import GHC.Tc.Module
-import GHC.IfaceToCore ( typecheckIface )
import GHC.Tc.Utils.Monad
import GHC.Tc.Utils.Zonk ( ZonkFlexi (DefaultFlexi) )
-import GHC.Types.Name.Cache ( initNameCache )
-import GHC.Builtin.Utils
-import GHC.Core.Opt.Pipeline
-import GHC.HsToCore
-import GHC.Iface.Load ( ifaceStats, initExternalPackageState, writeIface )
-import GHC.Iface.Make
-import GHC.Iface.Recomp
-import GHC.Iface.Tidy
-import GHC.CoreToStg.Prep
-import GHC.CoreToStg ( coreToStg )
+
import GHC.Stg.Syntax
import GHC.Stg.FVs ( annTopBindingsFreeVars )
import GHC.Stg.Pipeline ( stg2stg )
+
+import GHC.Builtin.Utils
+import GHC.Builtin.Names
+
import qualified GHC.StgToCmm as StgToCmm ( codeGen )
-import GHC.Types.CostCentre
-import GHC.Core.TyCon
-import GHC.Types.Name
+import GHC.StgToCmm.Types (CgInfos (..), ModuleLFInfos)
+
import GHC.Cmm
import GHC.Cmm.Parser ( parseCmmFile )
import GHC.Cmm.Info.Build
import GHC.Cmm.Pipeline
import GHC.Cmm.Info
-import GHC.Driver.CodeOutput
-import GHC.Driver.Config
-import GHC.Core.InstEnv
-import GHC.Core.FamInstEnv
-import GHC.Utils.Fingerprint ( Fingerprint )
-import GHC.Driver.Hooks
-import GHC.Tc.Utils.Env
-import GHC.Builtin.Names
-import GHC.Driver.Plugins
-import GHC.Runtime.Loader ( initializePlugins )
-import GHC.StgToCmm.Types (CgInfos (..), ModuleLFInfos)
-import GHC.Driver.Session
-import GHC.Driver.Backend
-import GHC.Utils.Error
+import GHC.Unit
+import GHC.Unit.External
+import GHC.Unit.State
+import GHC.Unit.Module.ModDetails
+import GHC.Unit.Module.ModGuts
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.ModSummary
+import GHC.Unit.Module.Graph
+import GHC.Unit.Module.Imported
+import GHC.Unit.Module.Deps
+import GHC.Unit.Module.Status
+import GHC.Unit.Home.ModInfo
-import GHC.Utils.Outputable
+import GHC.Types.Id
+import GHC.Types.SourceError
+import GHC.Types.SafeHaskell
+import GHC.Types.ForeignStubs
+import GHC.Types.Var.Env ( emptyTidyEnv )
+import GHC.Types.Fixity.Env
+import GHC.Types.CostCentre
+import GHC.Types.Unique.Supply
+import GHC.Types.SourceFile
+import GHC.Types.SrcLoc
+import GHC.Types.Name
import GHC.Types.Name.Env
-import GHC.Hs.Stats ( ppSourceStats )
-import GHC.Driver.Types
+import GHC.Types.Name.Cache ( initNameCache )
+import GHC.Types.Name.Reader
+import GHC.Types.Name.Ppr
+import GHC.Types.TyThing
+import GHC.Types.HpcInfo
+
+import GHC.Utils.Fingerprint ( Fingerprint )
+import GHC.Utils.Panic
+import GHC.Utils.Error
+import GHC.Utils.Outputable
+import GHC.Utils.Exception
+import GHC.Utils.Misc
+
import GHC.Data.FastString
-import GHC.Types.Unique.Supply
import GHC.Data.Bag
-import GHC.Utils.Exception
+import GHC.Data.StringBuffer
import qualified GHC.Data.Stream as Stream
import GHC.Data.Stream (Stream)
-import GHC.Utils.Misc
-
+import Data.Data hiding (Fixity, TyCon)
+import Data.Maybe ( fromJust )
import Data.List ( nub, isPrefixOf, partition )
import Control.Monad
import Data.IORef
@@ -183,11 +222,6 @@ import Data.Functor
import Control.DeepSeq (force)
import Data.Bifunctor (first, bimap)
-import GHC.Iface.Ext.Ast ( mkHieFile )
-import GHC.Iface.Ext.Types ( getAsts, hie_asts, hie_module )
-import GHC.Iface.Ext.Binary ( readHieFile, writeHieFile , hie_file_result, NameCacheUpdater(..))
-import GHC.Iface.Ext.Debug ( diffFile, validateScopes )
-
#include "HsVersions.h"
@@ -1639,7 +1673,7 @@ you run it you get a list of HValues that should be the same length as the list
of names; add them to the ClosureEnv.
A naked expression returns a singleton Name [it]. The stmt is lifted into the
-IO monad as explained in Note [Interactively-bound Ids in GHCi] in GHC.Driver.Types
+IO monad as explained in Note [Interactively-bound Ids in GHCi] in GHC.Runtime.Context
-}
-- | Compile a stmt all the way to an HValue, but don't run it
@@ -1781,7 +1815,7 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do
-- We only need to keep around the external bindings
-- (as decided by GHC.Iface.Tidy), since those are the only ones
-- that might later be looked up by name. But we can exclude
- -- - DFunIds, which are in 'cls_insts' (see Note [ic_tythings] in GHC.Driver.Types
+ -- - DFunIds, which are in 'cls_insts' (see Note [ic_tythings] in GHC.Runtime.Context
-- - Implicit Ids, which are implicit in tcs
-- c.f. GHC.Tc.Module.runTcInteractive, which reconstructs the TypeEnv
diff --git a/compiler/GHC/Driver/Make.hs b/compiler/GHC/Driver/Make.hs
index 5c955749a3..5023eacdc7 100644
--- a/compiler/GHC/Driver/Make.hs
+++ b/compiler/GHC/Driver/Make.hs
@@ -35,45 +35,62 @@ module GHC.Driver.Make (
import GHC.Prelude
+import GHC.Tc.Utils.Backpack
+
import qualified GHC.Runtime.Linker as Linker
+import GHC.Runtime.Linker.Types
+import GHC.Runtime.Context
import GHC.Driver.Config
import GHC.Driver.Phases
import GHC.Driver.Pipeline
import GHC.Driver.Session
import GHC.Driver.Backend
-import GHC.Utils.Error
-import GHC.Driver.Finder
import GHC.Driver.Monad
+import GHC.Driver.Env
+import GHC.Driver.Main
+
import GHC.Parser.Header
import GHC.Parser.Errors.Ppr
-import GHC.Driver.Types
-import GHC.Unit
-import GHC.Unit.State
+
+import GHC.Utils.Error
import GHC.IfaceToCore ( typecheckIface )
import GHC.Tc.Utils.Monad ( initIfaceCheck )
-import GHC.Driver.Main
import GHC.Data.Bag ( unitBag, listToBag, unionManyBags, isEmptyBag )
-import GHC.Types.Basic
import GHC.Data.Graph.Directed
-import GHC.Utils.Exception ( tryIO )
import GHC.Data.FastString
import GHC.Data.Maybe ( expectJust )
-import GHC.Types.Name
+import GHC.Data.StringBuffer
+import qualified GHC.LanguageExtensions as LangExt
+import GHC.SysTools.FileCleanup
+
+import GHC.Utils.Exception ( tryIO )
import GHC.Utils.Monad ( allM )
import GHC.Utils.Outputable
import GHC.Utils.Panic
+import GHC.Utils.Misc
+
+import GHC.Types.Basic
+import GHC.Types.Target
+import GHC.Types.SourceFile
+import GHC.Types.SourceError
import GHC.Types.SrcLoc
-import GHC.Data.StringBuffer
import GHC.Types.Unique.FM
import GHC.Types.Unique.DSet
-import GHC.Tc.Utils.Backpack
import GHC.Types.Unique.Set
-import GHC.Utils.Misc
-import qualified GHC.LanguageExtensions as LangExt
+import GHC.Types.Name
import GHC.Types.Name.Env
-import GHC.SysTools.FileCleanup
+
+import GHC.Unit
+import GHC.Unit.External
+import GHC.Unit.State
+import GHC.Unit.Finder
+import GHC.Unit.Module.ModSummary
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.ModDetails
+import GHC.Unit.Module.Graph
+import GHC.Unit.Home.ModInfo
import Data.Either ( rights, partitionEithers )
import qualified Data.Map as Map
diff --git a/compiler/GHC/Driver/MakeFile.hs b/compiler/GHC/Driver/MakeFile.hs
index a393bdbba4..81408ab7c9 100644
--- a/compiler/GHC/Driver/MakeFile.hs
+++ b/compiler/GHC/Driver/MakeFile.hs
@@ -22,18 +22,22 @@ import GHC.Driver.Monad
import GHC.Driver.Session
import GHC.Driver.Ppr
import GHC.Utils.Misc
-import GHC.Driver.Types
+import GHC.Driver.Env
import qualified GHC.SysTools as SysTools
-import GHC.Unit.Module
import GHC.Data.Graph.Directed ( SCC(..) )
-import GHC.Driver.Finder
import GHC.Utils.Outputable
import GHC.Utils.Panic
+import GHC.Types.SourceError
import GHC.Types.SrcLoc
import Data.List
import GHC.Data.FastString
import GHC.SysTools.FileCleanup
+import GHC.Unit.Module
+import GHC.Unit.Module.ModSummary
+import GHC.Unit.Module.Graph
+import GHC.Unit.Finder
+
import GHC.Utils.Exception
import GHC.Utils.Error
diff --git a/compiler/GHC/Driver/Monad.hs b/compiler/GHC/Driver/Monad.hs
index 72dc3b9800..4787574465 100644
--- a/compiler/GHC/Driver/Monad.hs
+++ b/compiler/GHC/Driver/Monad.hs
@@ -25,12 +25,15 @@ module GHC.Driver.Monad (
import GHC.Prelude
-import GHC.Utils.Monad
-import GHC.Driver.Types
import GHC.Driver.Session
+import GHC.Driver.Env
+
+import GHC.Utils.Monad
import GHC.Utils.Exception
import GHC.Utils.Error
+import GHC.Types.SourceError
+
import Control.Monad
import Control.Monad.Catch as MC
import Control.Monad.Trans.Reader
diff --git a/compiler/GHC/Driver/Phases.hs b/compiler/GHC/Driver/Phases.hs
index 4892b20c60..40aa2055c3 100644
--- a/compiler/GHC/Driver/Phases.hs
+++ b/compiler/GHC/Driver/Phases.hs
@@ -9,7 +9,6 @@
-----------------------------------------------------------------------------
module GHC.Driver.Phases (
- HscSource(..), isHsBootOrSig, isHsigFile, hscSourceString,
Phase(..),
happensBefore, eqPhase, anyHsc, isStopLn,
startPhase,
@@ -34,20 +33,27 @@ module GHC.Driver.Phases (
isCishFilename,
isDynLibFilename,
isHaskellUserSrcFilename,
- isSourceFilename
+ isSourceFilename,
+
+ phaseForeignLanguage
) where
#include "HsVersions.h"
import GHC.Prelude
+import GHC.Platform
+
+import GHC.ForeignSrcLang
+
+import GHC.Types.SourceFile
+
import GHC.Utils.Outputable
import GHC.Utils.Panic
-import GHC.Platform
-import System.FilePath
-import GHC.Utils.Binary
import GHC.Utils.Misc
+import System.FilePath
+
-----------------------------------------------------------------------------
-- Phases
@@ -63,70 +69,6 @@ import GHC.Utils.Misc
linker | other | - | a.out
-}
--- Note [HscSource types]
--- ~~~~~~~~~~~~~~~~~~~~~~
--- There are three types of source file for Haskell code:
---
--- * HsSrcFile is an ordinary hs file which contains code,
---
--- * HsBootFile is an hs-boot file, which is used to break
--- recursive module imports (there will always be an
--- HsSrcFile associated with it), and
---
--- * HsigFile is an hsig file, which contains only type
--- signatures and is used to specify signatures for
--- modules.
---
--- Syntactically, hs-boot files and hsig files are quite similar: they
--- only include type signatures and must be associated with an
--- actual HsSrcFile. isHsBootOrSig allows us to abstract over code
--- which is indifferent to which. However, there are some important
--- differences, mostly owing to the fact that hsigs are proper
--- modules (you `import Sig` directly) whereas HsBootFiles are
--- temporary placeholders (you `import {-# SOURCE #-} Mod).
--- When we finish compiling the true implementation of an hs-boot,
--- we replace the HomeModInfo with the real HsSrcFile. An HsigFile, on the
--- other hand, is never replaced (in particular, we *cannot* use the
--- HomeModInfo of the original HsSrcFile backing the signature, since it
--- will export too many symbols.)
---
--- Additionally, while HsSrcFile is the only Haskell file
--- which has *code*, we do generate .o files for HsigFile, because
--- this is how the recompilation checker figures out if a file
--- needs to be recompiled. These are fake object files which
--- should NOT be linked against.
-
-data HscSource
- = HsSrcFile | HsBootFile | HsigFile
- deriving( Eq, Ord, Show )
- -- Ord needed for the finite maps we build in CompManager
-
-instance Binary HscSource where
- put_ bh HsSrcFile = putByte bh 0
- put_ bh HsBootFile = putByte bh 1
- put_ bh HsigFile = putByte bh 2
- get bh = do
- h <- getByte bh
- case h of
- 0 -> return HsSrcFile
- 1 -> return HsBootFile
- _ -> return HsigFile
-
-hscSourceString :: HscSource -> String
-hscSourceString HsSrcFile = ""
-hscSourceString HsBootFile = "[boot]"
-hscSourceString HsigFile = "[sig]"
-
--- See Note [isHsBootOrSig]
-isHsBootOrSig :: HscSource -> Bool
-isHsBootOrSig HsBootFile = True
-isHsBootOrSig HsigFile = True
-isHsBootOrSig _ = False
-
-isHsigFile :: HscSource -> Bool
-isHsigFile HsigFile = True
-isHsigFile _ = False
-
data Phase
= Unlit HscSource
| Cpp HscSource
@@ -368,3 +310,16 @@ isHaskellSigFilename f = isHaskellSigSuffix (drop 1 $ takeExtension f)
isObjectFilename, isDynLibFilename :: Platform -> FilePath -> Bool
isObjectFilename platform f = isObjectSuffix platform (drop 1 $ takeExtension f)
isDynLibFilename platform f = isDynLibSuffix platform (drop 1 $ takeExtension f)
+
+-- | Foreign language of the phase if the phase deals with a foreign code
+phaseForeignLanguage :: Phase -> Maybe ForeignSrcLang
+phaseForeignLanguage phase = case phase of
+ Cc -> Just LangC
+ Ccxx -> Just LangCxx
+ Cobjc -> Just LangObjc
+ Cobjcxx -> Just LangObjcxx
+ HCc -> Just LangC
+ As _ -> Just LangAsm
+ MergeForeign -> Just RawObject
+ _ -> Nothing
+
diff --git a/compiler/GHC/Driver/Pipeline.hs b/compiler/GHC/Driver/Pipeline.hs
index 7ca219bc48..5428c83b99 100644
--- a/compiler/GHC/Driver/Pipeline.hs
+++ b/compiler/GHC/Driver/Pipeline.hs
@@ -39,46 +39,67 @@ module GHC.Driver.Pipeline (
import GHC.Prelude
+import GHC.Platform
+
+import GHC.Tc.Types
+
+import GHC.Driver.Main
+import GHC.Driver.Env hiding ( Hsc )
import GHC.Driver.Pipeline.Monad
-import GHC.Unit
-import GHC.Unit.State
+import GHC.Driver.Config
+import GHC.Driver.Phases
+import GHC.Driver.Session
+import GHC.Driver.Backend
+import GHC.Driver.Ppr
+import GHC.Driver.Hooks
+
import GHC.Platform.Ways
import GHC.Platform.ArchOS
-import GHC.Driver.Config
+
import GHC.Parser.Header
import GHC.Parser.Errors.Ppr
-import GHC.Driver.Phases
+
import GHC.SysTools
import GHC.SysTools.ExtraObj
-import GHC.Driver.Main
-import GHC.Driver.Finder
-import GHC.Driver.Types hiding ( Hsc )
+import GHC.SysTools.FileCleanup
+import GHC.SysTools.Ar
+
import GHC.Utils.Outputable
import GHC.Utils.Error
-import GHC.Driver.Session
-import GHC.Driver.Backend
-import GHC.Driver.Ppr
import GHC.Utils.Panic
import GHC.Utils.Misc
-import GHC.Data.StringBuffer ( hGetStringBuffer, hPutStringBuffer )
-import GHC.Types.Basic ( SuccessFlag(..) )
-import GHC.Data.Maybe ( expectJust )
-import GHC.Types.SrcLoc
-import GHC.CmmToLlvm ( llvmFixupAsm, llvmVersionList )
import GHC.Utils.Monad
-import GHC.Platform
-import GHC.Tc.Types
-import GHC.Driver.Hooks
+import GHC.Utils.Exception as Exception
+
+import GHC.CmmToLlvm ( llvmFixupAsm, llvmVersionList )
import qualified GHC.LanguageExtensions as LangExt
-import GHC.SysTools.FileCleanup
-import GHC.SysTools.Ar
import GHC.Settings
-import GHC.Data.Bag ( unitBag )
-import GHC.Data.FastString ( mkFastString )
-import GHC.Iface.Make ( mkFullIface )
-import GHC.Iface.UpdateIdInfos ( updateModDetailsIdInfos )
+import GHC.Runtime.Linker.Types
+
+import GHC.Data.Bag ( unitBag )
+import GHC.Data.FastString ( mkFastString )
+import GHC.Data.StringBuffer ( hGetStringBuffer, hPutStringBuffer )
+import GHC.Data.Maybe ( expectJust )
+
+import GHC.Iface.Make ( mkFullIface )
+import GHC.Iface.UpdateIdInfos ( updateModDetailsIdInfos )
+
+import GHC.Types.Basic ( SuccessFlag(..) )
+import GHC.Types.Target
+import GHC.Types.SrcLoc
+import GHC.Types.SourceFile
+import GHC.Types.SourceError
+
+import GHC.Unit
+import GHC.Unit.State
+import GHC.Unit.Finder
+import GHC.Unit.Module.ModSummary
+import GHC.Unit.Module.ModDetails
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.Graph (needsTemplateHaskellOrQQ)
+import GHC.Unit.Module.Deps
+import GHC.Unit.Home.ModInfo
-import GHC.Utils.Exception as Exception
import System.Directory
import System.FilePath
import System.IO
@@ -594,7 +615,7 @@ findHSLib :: DynFlags -> [String] -> String -> IO (Maybe FilePath)
findHSLib dflags dirs lib = do
let batch_lib_file = if WayDyn `notElem` ways dflags
then "lib" ++ lib <.> "a"
- else mkSOName (targetPlatform dflags) lib
+ else platformSOName (targetPlatform dflags) lib
found <- filterM doesFileExist (map (</> batch_lib_file) dirs)
case found of
[] -> return Nothing
diff --git a/compiler/GHC/Driver/Pipeline/Monad.hs b/compiler/GHC/Driver/Pipeline/Monad.hs
index 2fcf24e85d..b2db6170ec 100644
--- a/compiler/GHC/Driver/Pipeline/Monad.hs
+++ b/compiler/GHC/Driver/Pipeline/Monad.hs
@@ -14,12 +14,20 @@ import GHC.Prelude
import GHC.Utils.Monad
import GHC.Utils.Outputable
+
import GHC.Driver.Session
import GHC.Driver.Phases
-import GHC.Driver.Types
-import GHC.Unit.Module
+import GHC.Driver.Env
+
import GHC.SysTools.FileCleanup (TempFileLifetime)
+import GHC.Types.SourceFile
+
+import GHC.Unit.Module
+import GHC.Unit.Module.ModDetails
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.Status
+
import Control.Monad
newtype CompPipeline a = P { unP :: PipeEnv -> PipeState -> IO (PipeState, a) }
diff --git a/compiler/GHC/Driver/Plugins.hs b/compiler/GHC/Driver/Plugins.hs
index 6d6a976856..3436cc34a6 100644
--- a/compiler/GHC/Driver/Plugins.hs
+++ b/compiler/GHC/Driver/Plugins.hs
@@ -49,20 +49,26 @@ module GHC.Driver.Plugins (
import GHC.Prelude
-import GHC.Core.Opt.Monad ( CoreToDo, CoreM )
-import qualified GHC.Tc.Types
-import GHC.Tc.Types ( TcGblEnv, IfM, TcM, tcg_rn_decls, tcg_rn_exports )
-import GHC.Tc.Errors.Hole.FitTypes ( HoleFitPluginR )
-import GHC.Hs
+import GHC.Driver.Env
import GHC.Driver.Session
-import GHC.Driver.Types
import GHC.Driver.Monad
import GHC.Driver.Phases
+
import GHC.Unit.Module
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.ModSummary
+
+import qualified GHC.Tc.Types
+import GHC.Tc.Types ( TcGblEnv, IfM, TcM, tcg_rn_decls, tcg_rn_exports )
+import GHC.Tc.Errors.Hole.FitTypes ( HoleFitPluginR )
+
+import GHC.Core.Opt.Monad ( CoreToDo, CoreM )
+import GHC.Hs
import GHC.Utils.Fingerprint
-import Data.List (sort)
import GHC.Utils.Outputable (Outputable(..), text, (<+>))
+import Data.List (sort)
+
--Qualified import so we can define a Semigroup instance
-- but it doesn't clash with Outputable.<>
import qualified Data.Semigroup
diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs
index ccc7d2b8a3..20fd137ea7 100644
--- a/compiler/GHC/Driver/Session.hs
+++ b/compiler/GHC/Driver/Session.hs
@@ -69,7 +69,6 @@ module GHC.Driver.Session (
putLogMsg,
-- ** Safe Haskell
- SafeHaskellMode(..),
safeHaskellOn, safeHaskellModeEnabled,
safeImportsOn, safeLanguageOn, safeInferOn,
packageTrustOn,
@@ -257,6 +256,7 @@ import GHC.Data.Maybe
import GHC.Utils.Monad
import qualified GHC.Utils.Ppr as Pretty
import GHC.Types.SrcLoc
+import GHC.Types.SafeHaskell
import GHC.Types.Basic ( Alignment, alignmentOf, IntWithInf, treatZeroAsInf )
import GHC.Data.FastString
import GHC.Utils.Fingerprint
@@ -264,9 +264,9 @@ import GHC.Utils.Outputable
import GHC.Settings
import GHC.CmmToAsm.CFG.Weight
+import GHC.Types.Error
import {-# SOURCE #-} GHC.Utils.Error
- ( Severity(..), MsgDoc, mkLocMessageAnn
- , getCaretDiagnostic, DumpAction, TraceAction
+ ( DumpAction, TraceAction
, defaultDumpAction, defaultTraceAction )
import GHC.Utils.Json
import GHC.SysTools.Terminal ( stderrSupportsAnsiColors )
@@ -404,27 +404,6 @@ addQuoteInclude spec paths = let f = includePathsQuote spec
flattenIncludes :: IncludeSpecs -> [String]
flattenIncludes specs = includePathsQuote specs ++ includePathsGlobal specs
--- | The various Safe Haskell modes
-data SafeHaskellMode
- = Sf_None -- ^ inferred unsafe
- | Sf_Unsafe -- ^ declared and checked
- | Sf_Trustworthy -- ^ declared and checked
- | Sf_Safe -- ^ declared and checked
- | Sf_SafeInferred -- ^ inferred as safe
- | Sf_Ignore -- ^ @-fno-safe-haskell@ state
- deriving (Eq)
-
-instance Show SafeHaskellMode where
- show Sf_None = "None"
- show Sf_Unsafe = "Unsafe"
- show Sf_Trustworthy = "Trustworthy"
- show Sf_Safe = "Safe"
- show Sf_SafeInferred = "Safe-Inferred"
- show Sf_Ignore = "Ignore"
-
-instance Outputable SafeHaskellMode where
- ppr = text . show
-
-- | Contains not only a collection of 'GeneralFlag's but also a plethora of
-- information relating to the compilation of a single file or GHC session
data DynFlags = DynFlags {
@@ -937,13 +916,13 @@ versionedFilePath platform = uniqueSubdir platform
-- | The 'GhcMode' tells us whether we're doing multi-module
-- compilation (controlled via the "GHC" API) or one-shot
-- (single-module) compilation. This makes a difference primarily to
--- the "GHC.Driver.Finder": in one-shot mode we look for interface files for
+-- the "GHC.Unit.Finder": in one-shot mode we look for interface files for
-- imported modules, but in multi-module mode we look for source files
-- in order to check whether they need to be recompiled.
data GhcMode
= CompManager -- ^ @\-\-make@, GHCi, etc.
| OneShot -- ^ @ghc -c Foo.hs@
- | MkDepend -- ^ @ghc -M@, see "GHC.Driver.Finder" for why we need this
+ | MkDepend -- ^ @ghc -M@, see "GHC.Unit.Finder" for why we need this
deriving Eq
instance Outputable GhcMode where
@@ -5080,4 +5059,3 @@ initSDocContext dflags style = SDC
-- | Initialize the pretty-printing options using the default user style
initDefaultSDocContext :: DynFlags -> SDocContext
initDefaultSDocContext dflags = initSDocContext dflags defaultUserStyle
-
diff --git a/compiler/GHC/Driver/Types.hs b/compiler/GHC/Driver/Types.hs
deleted file mode 100644
index 3bc3167031..0000000000
--- a/compiler/GHC/Driver/Types.hs
+++ /dev/null
@@ -1,3340 +0,0 @@
-{-# LANGUAGE CPP #-}
-{-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveFunctor #-}
-{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE RecordWildCards #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE UndecidableInstances #-}
-
-{-
-(c) The University of Glasgow, 2006
-
-\section[GHC.Driver.Types]{Types for the per-module compiler}
--}
-
--- | Types for the per-module compiler
-module GHC.Driver.Types (
- -- * compilation state
- HscEnv(..), hscEPS,
- FinderCache, FindResult(..), InstalledFindResult(..),
- Target(..), TargetId(..), InputFileBuffer, pprTarget, pprTargetId, findTarget,
- HscStatus(..),
-
- -- * ModuleGraph
- ModuleGraph, emptyMG, mkModuleGraph, extendMG, mapMG,
- mgModSummaries, mgElemModule, mgLookupModule,
- needsTemplateHaskellOrQQ, mgBootModules,
-
- -- * Hsc monad
- Hsc(..), runHsc, mkInteractiveHscEnv, runInteractiveHsc,
-
- -- * Information about modules
- ModDetails(..), emptyModDetails,
- ModGuts(..), CgGuts(..), ForeignStubs(..), appendStubC,
- ImportedMods, ImportedBy(..), importedByUser, ImportedModsVal(..), SptEntry(..),
- ForeignSrcLang(..),
- phaseForeignLanguage,
-
- ModSummary(..), ms_imps, ms_installed_mod, ms_mod_name, ms_home_imps,
- home_imps, ms_home_allimps, ms_home_srcimps, showModMsg, isBootSummary,
- msHsFilePath, msHiFilePath, msObjFilePath,
- SourceModified(..), isTemplateHaskellOrQQNonBoot,
-
- -- * Information about the module being compiled
- -- (re-exported from GHC.Driver.Phases)
- HscSource(..), isHsBootOrSig, isHsigFile, hscSourceString,
-
-
- -- * State relating to modules in this package
- HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
- lookupHpt, eltsHpt, filterHpt, allHpt, mapHpt, delFromHpt,
- addToHpt, addListToHpt, lookupHptDirectly, listToHpt,
- hptCompleteSigs,
- hptInstances, hptRules, pprHPT,
-
- -- * State relating to known packages
- ExternalPackageState(..), EpsStats(..), addEpsInStats,
- PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
- lookupIfaceByModule, emptyPartialModIface, emptyFullModIface, lookupHptByModule,
-
- PackageInstEnv, PackageFamInstEnv, PackageRuleBase,
- PackageCompleteMatches,
-
- mkSOName, mkHsSOName, soExt,
-
- -- * Metaprogramming
- MetaRequest(..),
- MetaResult, -- data constructors not exported to ensure correct response type
- metaRequestE, metaRequestP, metaRequestT, metaRequestD, metaRequestAW,
- MetaHook,
-
- -- * Annotations
- prepareAnnotations,
-
- -- * Interactive context
- InteractiveContext(..), emptyInteractiveContext,
- icPrintUnqual, icInScopeTTs, icExtendGblRdrEnv,
- extendInteractiveContext, extendInteractiveContextWithIds,
- substInteractiveContext,
- setInteractivePrintName, icInteractiveModule,
- InteractiveImport(..),
- mkPrintUnqualified, pprModulePrefix,
- mkQualPackage, mkQualModule, pkgQual,
-
- -- * Interfaces
- ModIface, PartialModIface, ModIface_(..), ModIfaceBackend(..),
- mkIfaceWarnCache, mkIfaceHashCache, mkIfaceFixCache,
- emptyIfaceWarnCache, mi_boot, mi_fix,
- mi_semantic_module,
- mi_free_holes,
- renameFreeHoles,
-
- -- * Fixity
- FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
-
- -- * TyThings and type environments
- TyThing(..), tyThingAvailInfo,
- tyThingTyCon, tyThingDataCon, tyThingConLike,
- tyThingId, tyThingCoAxiom, tyThingParent_maybe, tyThingsTyCoVars,
- implicitTyThings, implicitTyConThings, implicitClassThings,
- isImplicitTyThing,
-
- TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
- typeEnvFromEntities, mkTypeEnvWithImplicits,
- extendTypeEnv, extendTypeEnvList,
- extendTypeEnvWithIds, plusTypeEnv,
- lookupTypeEnv,
- typeEnvElts, typeEnvTyCons, typeEnvIds, typeEnvPatSyns,
- typeEnvDataCons, typeEnvCoAxioms, typeEnvClasses,
-
- -- * MonadThings
- MonadThings(..),
-
- -- * Information on imports and exports
- WhetherHasOrphans, IsBootInterface(..), Usage(..),
- Dependencies(..), noDependencies,
- updNameCache,
- IfaceExport,
-
- -- * Warnings
- Warnings(..), WarningTxt(..), plusWarns,
-
- -- * Linker stuff
- Linkable(..), isObjectLinkable, linkableObjs,
- Unlinked(..), CompiledByteCode,
- isObject, nameOfObject, isInterpretable, byteCodeOfObject,
-
- -- * Program coverage
- HpcInfo(..), emptyHpcInfo, isHpcUsed, AnyHpcUsage,
-
- -- * Breakpoints
- ModBreaks (..), emptyModBreaks,
-
- -- * Safe Haskell information
- IfaceTrustInfo, getSafeMode, setSafeMode, noIfaceTrustInfo,
- trustInfoToNum, numToTrustInfo, IsSafeImport,
-
- -- * result of the parser
- HsParsedModule(..),
-
- -- * Compilation errors and warnings
- SourceError, GhcApiError, mkSrcErr, srcErrorMessages, mkApiErr,
- throwOneError, throwErrors, handleSourceError,
- handleFlagWarnings, printOrThrowWarnings,
-
- -- * COMPLETE signature
- ConLikeSet, CompleteMatch, CompleteMatches,
-
- -- * Exstensible Iface fields
- ExtensibleFields(..), FieldName,
- emptyExtensibleFields,
- readField, readIfaceField, readIfaceFieldWith,
- writeField, writeIfaceField, writeIfaceFieldWith,
- deleteField, deleteIfaceField,
- ) where
-
-#include "HsVersions.h"
-
-import GHC.Prelude
-
-import GHC.Driver.Ppr
-import GHC.Driver.CmdLine
-import GHC.Driver.Session
-
-import GHC.ByteCode.Types
-import GHC.Runtime.Eval.Types ( Resume )
-import GHC.Runtime.Interpreter.Types (Interp)
-import GHC.ForeignSrcLang
-
-import GHC.Types.Unique.FM
-import GHC.Hs
-import GHC.Types.Name.Reader
-import GHC.Types.Avail
-import GHC.Unit
-import GHC.Unit.State
-import GHC.Core.InstEnv ( InstEnv, ClsInst, identicalClsInstHead )
-import GHC.Core.FamInstEnv
-import GHC.Core ( CoreProgram, RuleBase, CoreRule )
-import GHC.Types.Name
-import GHC.Types.Name.Env
-import GHC.Types.Var.Set
-import GHC.Types.Var
-import GHC.Types.Id
-import GHC.Types.Id.Info ( IdDetails(..), RecSelParent(..))
-import GHC.Core.Type
-
-import GHC.Parser.Annotation ( ApiAnns )
-import GHC.Types.Annotations ( Annotation, AnnEnv, mkAnnEnv, plusAnnEnv )
-import GHC.Core.Class
-import GHC.Core.TyCon
-import GHC.Core.Coercion.Axiom
-import GHC.Core.ConLike
-import GHC.Core.DataCon
-import GHC.Core.PatSyn
-import GHC.Builtin.Names ( gHC_PRIM, ioTyConName, printName, mkInteractiveModule )
-import GHC.Builtin.Types
-import GHC.Driver.Backend
-import GHC.Runtime.Linker.Types ( DynLinker, Linkable(..), Unlinked(..), SptEntry(..) )
-import GHC.Driver.Phases
- ( Phase, HscSource(..), hscSourceString
- , isHsBootOrSig, isHsigFile )
-import qualified GHC.Driver.Phases as Phase
-import GHC.Types.Basic
-import GHC.Iface.Syntax
-import GHC.Data.Maybe
-import GHC.Utils.Outputable
-import GHC.Types.SrcLoc
-import GHC.Types.Unique
-import GHC.Types.Unique.DFM
-import GHC.Data.FastString
-import GHC.Data.StringBuffer ( StringBuffer )
-import GHC.Utils.Fingerprint
-import GHC.Utils.Monad
-import GHC.Data.Bag
-import GHC.Utils.Binary
-import GHC.Utils.Error
-import GHC.Utils.Panic
-import GHC.Types.Name.Cache
-import GHC.Platform
-import GHC.Utils.Misc
-import GHC.Types.Unique.DSet
-import GHC.Serialized ( Serialized )
-import qualified GHC.LanguageExtensions as LangExt
-
-import Foreign
-import Control.Monad ( guard, liftM, ap, forM, forM_, replicateM )
-import Data.IORef
-import Data.Map ( Map )
-import qualified Data.Map as Map
-import Data.Time
-import GHC.Utils.Exception
-import System.FilePath
-import Control.DeepSeq
-import Control.Monad.Trans.Reader
-import Control.Monad.Trans.Class
-import Control.Monad.Catch as MC (MonadCatch, catch)
-
--- -----------------------------------------------------------------------------
--- Compilation state
--- -----------------------------------------------------------------------------
-
--- | Status of a compilation to hard-code
-data HscStatus
- -- | Nothing to do.
- = HscNotGeneratingCode ModIface ModDetails
- -- | Nothing to do because code already exists.
- | HscUpToDate ModIface ModDetails
- -- | Update boot file result.
- | HscUpdateBoot ModIface ModDetails
- -- | Generate signature file (backpack)
- | HscUpdateSig ModIface ModDetails
- -- | Recompile this module.
- | HscRecomp
- { hscs_guts :: CgGuts
- -- ^ Information for the code generator.
- , hscs_mod_location :: !ModLocation
- -- ^ Module info
- , hscs_mod_details :: !ModDetails
- , hscs_partial_iface :: !PartialModIface
- -- ^ Partial interface
- , hscs_old_iface_hash :: !(Maybe Fingerprint)
- -- ^ Old interface hash for this compilation, if an old interface file
- -- exists. Pass to `hscMaybeWriteIface` when writing the interface to
- -- avoid updating the existing interface when the interface isn't
- -- changed.
- , hscs_iface_dflags :: !DynFlags
- -- ^ Generate final iface using this DynFlags.
- -- FIXME (osa): I don't understand why this is necessary, but I spent
- -- almost two days trying to figure this out and I couldn't .. perhaps
- -- someone who understands this code better will remove this later.
- }
--- Should HscStatus contain the HomeModInfo?
--- All places where we return a status we also return a HomeModInfo.
-
--- -----------------------------------------------------------------------------
--- The Hsc monad: Passing an environment and warning state
-
-newtype Hsc a = Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages))
- deriving (Functor)
-
-instance Applicative Hsc where
- pure a = Hsc $ \_ w -> return (a, w)
- (<*>) = ap
-
-instance Monad Hsc where
- Hsc m >>= k = Hsc $ \e w -> do (a, w1) <- m e w
- case k a of
- Hsc k' -> k' e w1
-
-instance MonadIO Hsc where
- liftIO io = Hsc $ \_ w -> do a <- io; return (a, w)
-
-instance HasDynFlags Hsc where
- getDynFlags = Hsc $ \e w -> return (hsc_dflags e, w)
-
-runHsc :: HscEnv -> Hsc a -> IO a
-runHsc hsc_env (Hsc hsc) = do
- (a, w) <- hsc hsc_env emptyBag
- printOrThrowWarnings (hsc_dflags hsc_env) w
- return a
-
-mkInteractiveHscEnv :: HscEnv -> HscEnv
-mkInteractiveHscEnv hsc_env = hsc_env{ hsc_dflags = interactive_dflags }
- where
- interactive_dflags = ic_dflags (hsc_IC hsc_env)
-
-runInteractiveHsc :: HscEnv -> Hsc a -> IO a
--- A variant of runHsc that switches in the DynFlags from the
--- InteractiveContext before running the Hsc computation.
-runInteractiveHsc hsc_env = runHsc (mkInteractiveHscEnv hsc_env)
-
--- -----------------------------------------------------------------------------
--- Source Errors
-
--- When the compiler (GHC.Driver.Main) discovers errors, it throws an
--- exception in the IO monad.
-
-mkSrcErr :: ErrorMessages -> SourceError
-mkSrcErr = SourceError
-
-srcErrorMessages :: SourceError -> ErrorMessages
-srcErrorMessages (SourceError msgs) = msgs
-
-mkApiErr :: DynFlags -> SDoc -> GhcApiError
-mkApiErr dflags msg = GhcApiError (showSDoc dflags msg)
-
-throwErrors :: MonadIO io => ErrorMessages -> io a
-throwErrors = liftIO . throwIO . mkSrcErr
-
-throwOneError :: MonadIO io => ErrMsg -> io a
-throwOneError = throwErrors . unitBag
-
--- | A source error is an error that is caused by one or more errors in the
--- source code. A 'SourceError' is thrown by many functions in the
--- compilation pipeline. Inside GHC these errors are merely printed via
--- 'log_action', but API clients may treat them differently, for example,
--- insert them into a list box. If you want the default behaviour, use the
--- idiom:
---
--- > handleSourceError printExceptionAndWarnings $ do
--- > ... api calls that may fail ...
---
--- The 'SourceError's error messages can be accessed via 'srcErrorMessages'.
--- This list may be empty if the compiler failed due to @-Werror@
--- ('Opt_WarnIsError').
---
--- See 'printExceptionAndWarnings' for more information on what to take care
--- of when writing a custom error handler.
-newtype SourceError = SourceError ErrorMessages
-
-instance Show SourceError where
- show (SourceError msgs) = unlines . map show . bagToList $ msgs
-
-instance Exception SourceError
-
--- | Perform the given action and call the exception handler if the action
--- throws a 'SourceError'. See 'SourceError' for more information.
-handleSourceError :: (MonadCatch m) =>
- (SourceError -> m a) -- ^ exception handler
- -> m a -- ^ action to perform
- -> m a
-handleSourceError handler act =
- MC.catch act (\(e :: SourceError) -> handler e)
-
--- | An error thrown if the GHC API is used in an incorrect fashion.
-newtype GhcApiError = GhcApiError String
-
-instance Show GhcApiError where
- show (GhcApiError msg) = msg
-
-instance Exception GhcApiError
-
--- | Given a bag of warnings, turn them into an exception if
--- -Werror is enabled, or print them out otherwise.
-printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO ()
-printOrThrowWarnings dflags warns = do
- let (make_error, warns') =
- mapAccumBagL
- (\make_err warn ->
- case isWarnMsgFatal dflags warn of
- Nothing ->
- (make_err, warn)
- Just err_reason ->
- (True, warn{ errMsgSeverity = SevError
- , errMsgReason = ErrReason err_reason
- }))
- False warns
- if make_error
- then throwIO (mkSrcErr warns')
- else printBagOfErrors dflags warns
-
-handleFlagWarnings :: DynFlags -> [Warn] -> IO ()
-handleFlagWarnings dflags warns = do
- let warns' = filter (shouldPrintWarning dflags . warnReason) warns
-
- -- It would be nicer if warns :: [Located MsgDoc], but that
- -- has circular import problems.
- bag = listToBag [ mkPlainWarnMsg dflags loc (text warn)
- | Warn _ (L loc warn) <- warns' ]
-
- printOrThrowWarnings dflags bag
-
--- Given a warn reason, check to see if it's associated -W opt is enabled
-shouldPrintWarning :: DynFlags -> GHC.Driver.CmdLine.WarnReason -> Bool
-shouldPrintWarning dflags ReasonDeprecatedFlag
- = wopt Opt_WarnDeprecatedFlags dflags
-shouldPrintWarning dflags ReasonUnrecognisedFlag
- = wopt Opt_WarnUnrecognisedWarningFlags dflags
-shouldPrintWarning _ _
- = True
-
-{-
-************************************************************************
-* *
-\subsection{HscEnv}
-* *
-************************************************************************
--}
-
--- | HscEnv is like 'Session', except that some of the fields are immutable.
--- An HscEnv is used to compile a single module from plain Haskell source
--- code (after preprocessing) to either C, assembly or C--. It's also used
--- to store the dynamic linker state to allow for multiple linkers in the
--- same address space.
--- Things like the module graph don't change during a single compilation.
---
--- Historical note: \"hsc\" used to be the name of the compiler binary,
--- when there was a separate driver and compiler. To compile a single
--- module, the driver would invoke hsc on the source code... so nowadays
--- we think of hsc as the layer of the compiler that deals with compiling
--- a single module.
-data HscEnv
- = HscEnv {
- hsc_dflags :: DynFlags,
- -- ^ The dynamic flag settings
-
- hsc_targets :: [Target],
- -- ^ The targets (or roots) of the current session
-
- hsc_mod_graph :: ModuleGraph,
- -- ^ The module graph of the current session
-
- hsc_IC :: InteractiveContext,
- -- ^ The context for evaluating interactive statements
-
- hsc_HPT :: HomePackageTable,
- -- ^ The home package table describes already-compiled
- -- home-package modules, /excluding/ the module we
- -- are compiling right now.
- -- (In one-shot mode the current module is the only
- -- home-package module, so hsc_HPT is empty. All other
- -- modules count as \"external-package\" modules.
- -- However, even in GHCi mode, hi-boot interfaces are
- -- demand-loaded into the external-package table.)
- --
- -- 'hsc_HPT' is not mutable because we only demand-load
- -- external packages; the home package is eagerly
- -- loaded, module by module, by the compilation manager.
- --
- -- The HPT may contain modules compiled earlier by @--make@
- -- but not actually below the current module in the dependency
- -- graph.
- --
- -- (This changes a previous invariant: changed Jan 05.)
-
- hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
- -- ^ Information about the currently loaded external packages.
- -- This is mutable because packages will be demand-loaded during
- -- a compilation run as required.
-
- hsc_NC :: {-# UNPACK #-} !(IORef NameCache),
- -- ^ As with 'hsc_EPS', this is side-effected by compiling to
- -- reflect sucking in interface files. They cache the state of
- -- external interface files, in effect.
-
- hsc_FC :: {-# UNPACK #-} !(IORef FinderCache),
- -- ^ The cached result of performing finding in the file system
-
- hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
- -- ^ Used for one-shot compilation only, to initialise
- -- the 'IfGblEnv'. See 'GHC.Tc.Utils.tcg_type_env_var' for
- -- 'GHC.Tc.Utils.TcGblEnv'. See also Note [hsc_type_env_var hack]
-
- , hsc_interp :: Maybe Interp
- -- ^ target code interpreter (if any) to use for TH and GHCi.
- -- See Note [Target code interpreter]
-
- , hsc_dynLinker :: DynLinker
- -- ^ dynamic linker.
-
- , hsc_home_unit :: !HomeUnit
- -- ^ Home-unit
-
- }
-
-{-
-
-Note [Target code interpreter]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
-Template Haskell and GHCi use an interpreter to execute code that is built for
-the compiler target platform (= code host platform) on the compiler host
-platform (= code build platform).
-
-The internal interpreter can be used when both platforms are the same and when
-the built code is compatible with the compiler itself (same way, etc.). This
-interpreter is not always available: for instance stage1 compiler doesn't have
-it because there might be an ABI mismatch between the code objects (built by
-stage1 compiler) and the stage1 compiler itself (built by stage0 compiler).
-
-In most cases, an external interpreter can be used instead: it runs in a
-separate process and it communicates with the compiler via a two-way message
-passing channel. The process is lazily spawned to avoid overhead when it is not
-used.
-
-The target code interpreter to use can be selected per session via the
-`hsc_interp` field of `HscEnv`. There may be no interpreter available at all, in
-which case Template Haskell and GHCi will fail to run. The interpreter to use is
-configured via command-line flags (in `GHC.setSessionDynFlags`).
-
-
--}
-
--- Note [hsc_type_env_var hack]
--- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--- hsc_type_env_var is used to initialize tcg_type_env_var, and
--- eventually it is the mutable variable that is queried from
--- if_rec_types to get a TypeEnv. So, clearly, it's something
--- related to knot-tying (see Note [Tying the knot]).
--- hsc_type_env_var is used in two places: initTcRn (where
--- it initializes tcg_type_env_var) and initIfaceCheck
--- (where it initializes if_rec_types).
---
--- But why do we need a way to feed a mutable variable in? Why
--- can't we just initialize tcg_type_env_var when we start
--- typechecking? The problem is we need to knot-tie the
--- EPS, and we may start adding things to the EPS before type
--- checking starts.
---
--- Here is a concrete example. Suppose we are running
--- "ghc -c A.hs", and we have this file system state:
---
--- A.hs-boot A.hi-boot **up to date**
--- B.hs B.hi **up to date**
--- A.hs A.hi **stale**
---
--- The first thing we do is run checkOldIface on A.hi.
--- checkOldIface will call loadInterface on B.hi so it can
--- get its hands on the fingerprints, to find out if A.hi
--- needs recompilation. But loadInterface also populates
--- the EPS! And so if compilation turns out to be necessary,
--- as it is in this case, the thunks we put into the EPS for
--- B.hi need to have the correct if_rec_types mutable variable
--- to query.
---
--- If the mutable variable is only allocated WHEN we start
--- typechecking, then that's too late: we can't get the
--- information to the thunks. So we need to pre-commit
--- to a type variable in 'hscIncrementalCompile' BEFORE we
--- check the old interface.
---
--- This is all a massive hack because arguably checkOldIface
--- should not populate the EPS. But that's a refactor for
--- another day.
-
--- | Retrieve the ExternalPackageState cache.
-hscEPS :: HscEnv -> IO ExternalPackageState
-hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
-
--- | A compilation target.
---
--- A target may be supplied with the actual text of the
--- module. If so, use this instead of the file contents (this
--- is for use in an IDE where the file hasn't been saved by
--- the user yet).
-data Target
- = Target {
- targetId :: TargetId, -- ^ module or filename
- targetAllowObjCode :: Bool, -- ^ object code allowed?
- targetContents :: Maybe (InputFileBuffer, UTCTime)
- -- ^ Optional in-memory buffer containing the source code GHC should
- -- use for this target instead of reading it from disk.
- --
- -- Since GHC version 8.10 modules which require preprocessors such as
- -- Literate Haskell or CPP to run are also supported.
- --
- -- If a corresponding source file does not exist on disk this will
- -- result in a 'SourceError' exception if @targetId = TargetModule _@
- -- is used. However together with @targetId = TargetFile _@ GHC will
- -- not complain about the file missing.
- }
-
-data TargetId
- = TargetModule ModuleName
- -- ^ A module name: search for the file
- | TargetFile FilePath (Maybe Phase)
- -- ^ A filename: preprocess & parse it to find the module name.
- -- If specified, the Phase indicates how to compile this file
- -- (which phase to start from). Nothing indicates the starting phase
- -- should be determined from the suffix of the filename.
- deriving Eq
-
-type InputFileBuffer = StringBuffer
-
-pprTarget :: Target -> SDoc
-pprTarget (Target id obj _) =
- (if obj then empty else char '*') <> pprTargetId id
-
-instance Outputable Target where
- ppr = pprTarget
-
-pprTargetId :: TargetId -> SDoc
-pprTargetId (TargetModule m) = ppr m
-pprTargetId (TargetFile f _) = text f
-
-instance Outputable TargetId where
- ppr = pprTargetId
-
-findTarget :: ModSummary -> [Target] -> Maybe Target
-findTarget ms ts =
- case filter (matches ms) ts of
- [] -> Nothing
- (t:_) -> Just t
- where
- summary `matches` Target (TargetModule m) _ _
- = ms_mod_name summary == m
- summary `matches` Target (TargetFile f _) _ _
- | Just f' <- ml_hs_file (ms_location summary)
- = f == f'
- _ `matches` _
- = False
-
-{-
-************************************************************************
-* *
-\subsection{Package and Module Tables}
-* *
-************************************************************************
--}
-
--- | Helps us find information about modules in the home package
-type HomePackageTable = DModuleNameEnv HomeModInfo
- -- Domain = modules in the home package that have been fully compiled
- -- "home" unit id cached here for convenience
-
--- | Helps us find information about modules in the imported packages
-type PackageIfaceTable = ModuleEnv ModIface
- -- Domain = modules in the imported packages
-
--- | Constructs an empty HomePackageTable
-emptyHomePackageTable :: HomePackageTable
-emptyHomePackageTable = emptyUDFM
-
--- | Constructs an empty PackageIfaceTable
-emptyPackageIfaceTable :: PackageIfaceTable
-emptyPackageIfaceTable = emptyModuleEnv
-
-pprHPT :: HomePackageTable -> SDoc
--- A bit arbitrary for now
-pprHPT hpt = pprUDFM hpt $ \hms ->
- vcat [ hang (ppr (mi_module (hm_iface hm)))
- 2 (ppr (md_types (hm_details hm)))
- | hm <- hms ]
-
-lookupHpt :: HomePackageTable -> ModuleName -> Maybe HomeModInfo
-lookupHpt = lookupUDFM
-
-lookupHptDirectly :: HomePackageTable -> Unique -> Maybe HomeModInfo
-lookupHptDirectly = lookupUDFM_Directly
-
-eltsHpt :: HomePackageTable -> [HomeModInfo]
-eltsHpt = eltsUDFM
-
-filterHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> HomePackageTable
-filterHpt = filterUDFM
-
-allHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> Bool
-allHpt = allUDFM
-
-mapHpt :: (HomeModInfo -> HomeModInfo) -> HomePackageTable -> HomePackageTable
-mapHpt = mapUDFM
-
-delFromHpt :: HomePackageTable -> ModuleName -> HomePackageTable
-delFromHpt = delFromUDFM
-
-addToHpt :: HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable
-addToHpt = addToUDFM
-
-addListToHpt
- :: HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable
-addListToHpt = addListToUDFM
-
-listToHpt :: [(ModuleName, HomeModInfo)] -> HomePackageTable
-listToHpt = listToUDFM
-
-lookupHptByModule :: HomePackageTable -> Module -> Maybe HomeModInfo
--- The HPT is indexed by ModuleName, not Module,
--- we must check for a hit on the right Module
-lookupHptByModule hpt mod
- = case lookupHpt hpt (moduleName mod) of
- Just hm | mi_module (hm_iface hm) == mod -> Just hm
- _otherwise -> Nothing
-
--- | Information about modules in the package being compiled
-data HomeModInfo
- = HomeModInfo {
- hm_iface :: !ModIface,
- -- ^ The basic loaded interface file: every loaded module has one of
- -- these, even if it is imported from another package
- hm_details :: !ModDetails,
- -- ^ Extra information that has been created from the 'ModIface' for
- -- the module, typically during typechecking
- hm_linkable :: !(Maybe Linkable)
- -- ^ The actual artifact we would like to link to access things in
- -- this module.
- --
- -- 'hm_linkable' might be Nothing:
- --
- -- 1. If this is an .hs-boot module
- --
- -- 2. Temporarily during compilation if we pruned away
- -- the old linkable because it was out of date.
- --
- -- After a complete compilation ('GHC.load'), all 'hm_linkable' fields
- -- in the 'HomePackageTable' will be @Just@.
- --
- -- When re-linking a module ('GHC.Driver.Main.HscNoRecomp'), we construct the
- -- 'HomeModInfo' by building a new 'ModDetails' from the old
- -- 'ModIface' (only).
- }
-
--- | Find the 'ModIface' for a 'Module', searching in both the loaded home
--- and external package module information
-lookupIfaceByModule
- :: HomePackageTable
- -> PackageIfaceTable
- -> Module
- -> Maybe ModIface
-lookupIfaceByModule hpt pit mod
- = case lookupHptByModule hpt mod of
- Just hm -> Just (hm_iface hm)
- Nothing -> lookupModuleEnv pit mod
-
--- If the module does come from the home package, why do we look in the PIT as well?
--- (a) In OneShot mode, even home-package modules accumulate in the PIT
--- (b) Even in Batch (--make) mode, there is *one* case where a home-package
--- module is in the PIT, namely GHC.Prim when compiling the base package.
--- We could eliminate (b) if we wanted, by making GHC.Prim belong to a package
--- of its own, but it doesn't seem worth the bother.
-
-hptCompleteSigs :: HscEnv -> [CompleteMatch]
-hptCompleteSigs = hptAllThings (md_complete_matches . hm_details)
-
--- | Find all the instance declarations (of classes and families) from
--- the Home Package Table filtered by the provided predicate function.
--- Used in @tcRnImports@, to select the instances that are in the
--- transitive closure of imports from the currently compiled module.
-hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst])
-hptInstances hsc_env want_this_module
- = let (insts, famInsts) = unzip $ flip hptAllThings hsc_env $ \mod_info -> do
- guard (want_this_module (moduleName (mi_module (hm_iface mod_info))))
- let details = hm_details mod_info
- return (md_insts details, md_fam_insts details)
- in (concat insts, concat famInsts)
-
--- | Get rules from modules "below" this one (in the dependency sense)
-hptRules :: HscEnv -> [ModuleNameWithIsBoot] -> [CoreRule]
-hptRules = hptSomeThingsBelowUs (md_rules . hm_details) False
-
-
--- | Get annotations from modules "below" this one (in the dependency sense)
-hptAnns :: HscEnv -> Maybe [ModuleNameWithIsBoot] -> [Annotation]
-hptAnns hsc_env (Just deps) = hptSomeThingsBelowUs (md_anns . hm_details) False hsc_env deps
-hptAnns hsc_env Nothing = hptAllThings (md_anns . hm_details) hsc_env
-
-hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
-hptAllThings extract hsc_env = concatMap extract (eltsHpt (hsc_HPT hsc_env))
-
--- | Get things from modules "below" this one (in the dependency sense)
--- C.f Inst.hptInstances
-hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> [ModuleNameWithIsBoot] -> [a]
-hptSomeThingsBelowUs extract include_hi_boot hsc_env deps
- | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
-
- | otherwise
- = let hpt = hsc_HPT hsc_env
- in
- [ thing
- | -- Find each non-hi-boot module below me
- GWIB { gwib_mod = mod, gwib_isBoot = is_boot } <- deps
- , include_hi_boot || (is_boot == NotBoot)
-
- -- unsavoury: when compiling the base package with --make, we
- -- sometimes try to look up RULES etc for GHC.Prim. GHC.Prim won't
- -- be in the HPT, because we never compile it; it's in the EPT
- -- instead. ToDo: clean up, and remove this slightly bogus filter:
- , mod /= moduleName gHC_PRIM
-
- -- Look it up in the HPT
- , let things = case lookupHpt hpt mod of
- Just info -> extract info
- Nothing -> pprTrace "WARNING in hptSomeThingsBelowUs" msg []
- msg = vcat [text "missing module" <+> ppr mod,
- text "Probable cause: out-of-date interface files"]
- -- This really shouldn't happen, but see #962
-
- -- And get its dfuns
- , thing <- things ]
-
-
-{-
-************************************************************************
-* *
-\subsection{Metaprogramming}
-* *
-************************************************************************
--}
-
--- | The supported metaprogramming result types
-data MetaRequest
- = MetaE (LHsExpr GhcPs -> MetaResult)
- | MetaP (LPat GhcPs -> MetaResult)
- | MetaT (LHsType GhcPs -> MetaResult)
- | MetaD ([LHsDecl GhcPs] -> MetaResult)
- | MetaAW (Serialized -> MetaResult)
-
--- | data constructors not exported to ensure correct result type
-data MetaResult
- = MetaResE { unMetaResE :: LHsExpr GhcPs }
- | MetaResP { unMetaResP :: LPat GhcPs }
- | MetaResT { unMetaResT :: LHsType GhcPs }
- | MetaResD { unMetaResD :: [LHsDecl GhcPs] }
- | MetaResAW { unMetaResAW :: Serialized }
-
-type MetaHook f = MetaRequest -> LHsExpr GhcTc -> f MetaResult
-
-metaRequestE :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsExpr GhcPs)
-metaRequestE h = fmap unMetaResE . h (MetaE MetaResE)
-
-metaRequestP :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LPat GhcPs)
-metaRequestP h = fmap unMetaResP . h (MetaP MetaResP)
-
-metaRequestT :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsType GhcPs)
-metaRequestT h = fmap unMetaResT . h (MetaT MetaResT)
-
-metaRequestD :: Functor f => MetaHook f -> LHsExpr GhcTc -> f [LHsDecl GhcPs]
-metaRequestD h = fmap unMetaResD . h (MetaD MetaResD)
-
-metaRequestAW :: Functor f => MetaHook f -> LHsExpr GhcTc -> f Serialized
-metaRequestAW h = fmap unMetaResAW . h (MetaAW MetaResAW)
-
-{-
-************************************************************************
-* *
-\subsection{Dealing with Annotations}
-* *
-************************************************************************
--}
-
--- | Deal with gathering annotations in from all possible places
--- and combining them into a single 'AnnEnv'
-prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
-prepareAnnotations hsc_env mb_guts = do
- eps <- hscEPS hsc_env
- let -- Extract annotations from the module being compiled if supplied one
- mb_this_module_anns = fmap (mkAnnEnv . mg_anns) mb_guts
- -- Extract dependencies of the module if we are supplied one,
- -- otherwise load annotations from all home package table
- -- entries regardless of dependency ordering.
- home_pkg_anns = (mkAnnEnv . hptAnns hsc_env) $ fmap (dep_mods . mg_deps) mb_guts
- other_pkg_anns = eps_ann_env eps
- ann_env = foldl1' plusAnnEnv $ catMaybes [mb_this_module_anns,
- Just home_pkg_anns,
- Just other_pkg_anns]
- return ann_env
-
-{-
-************************************************************************
-* *
-\subsection{The Finder cache}
-* *
-************************************************************************
--}
-
--- | The 'FinderCache' maps modules to the result of
--- searching for that module. It records the results of searching for
--- modules along the search path. On @:load@, we flush the entire
--- contents of this cache.
---
-type FinderCache = InstalledModuleEnv InstalledFindResult
-
-data InstalledFindResult
- = InstalledFound ModLocation InstalledModule
- | InstalledNoPackage UnitId
- | InstalledNotFound [FilePath] (Maybe UnitId)
-
--- | The result of searching for an imported module.
---
--- NB: FindResult manages both user source-import lookups
--- (which can result in 'Module') as well as direct imports
--- for interfaces (which always result in 'InstalledModule').
-data FindResult
- = Found ModLocation Module
- -- ^ The module was found
- | NoPackage Unit
- -- ^ The requested unit was not found
- | FoundMultiple [(Module, ModuleOrigin)]
- -- ^ _Error_: both in multiple packages
-
- -- | Not found
- | NotFound
- { fr_paths :: [FilePath] -- ^ Places where I looked
-
- , fr_pkg :: Maybe Unit -- ^ Just p => module is in this unit's
- -- manifest, but couldn't find the
- -- .hi file
-
- , fr_mods_hidden :: [Unit] -- ^ Module is in these units,
- -- but the *module* is hidden
-
- , fr_pkgs_hidden :: [Unit] -- ^ Module is in these units,
- -- but the *unit* is hidden
-
- -- | Module is in these units, but it is unusable
- , fr_unusables :: [(Unit, UnusableUnitReason)]
-
- , fr_suggestions :: [ModuleSuggestion] -- ^ Possible mis-spelled modules
- }
-
-{-
-************************************************************************
-* *
-\subsection{Symbol tables and Module details}
-* *
-************************************************************************
--}
-
-{- Note [Interface file stages]
- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
-Interface files have two possible stages.
-
-* A partial stage built from the result of the core pipeline.
-* A fully instantiated form. Which also includes fingerprints and
- potentially information provided by backends.
-
-We can build a full interface file two ways:
-* Directly from a partial one:
- Then we omit backend information and mostly compute fingerprints.
-* From a partial one + information produced by a backend.
- Then we store the provided information and fingerprint both.
--}
-
-type PartialModIface = ModIface_ 'ModIfaceCore
-type ModIface = ModIface_ 'ModIfaceFinal
-
--- | Extends a PartialModIface with information which is either:
--- * Computed after codegen
--- * Or computed just before writing the iface to disk. (Hashes)
--- In order to fully instantiate it.
-data ModIfaceBackend = ModIfaceBackend
- { mi_iface_hash :: !Fingerprint
- -- ^ Hash of the whole interface
- , mi_mod_hash :: !Fingerprint
- -- ^ Hash of the ABI only
- , mi_flag_hash :: !Fingerprint
- -- ^ Hash of the important flags used when compiling the module, excluding
- -- optimisation flags
- , mi_opt_hash :: !Fingerprint
- -- ^ Hash of optimisation flags
- , mi_hpc_hash :: !Fingerprint
- -- ^ Hash of hpc flags
- , mi_plugin_hash :: !Fingerprint
- -- ^ Hash of plugins
- , mi_orphan :: !WhetherHasOrphans
- -- ^ Whether this module has orphans
- , mi_finsts :: !WhetherHasFamInst
- -- ^ Whether this module has family instances. See Note [The type family
- -- instance consistency story].
- , mi_exp_hash :: !Fingerprint
- -- ^ Hash of export list
- , mi_orphan_hash :: !Fingerprint
- -- ^ Hash for orphan rules, class and family instances combined
-
- -- Cached environments for easy lookup. These are computed (lazily) from
- -- other fields and are not put into the interface file.
- -- Not really produced by the backend but there is no need to create them
- -- any earlier.
- , mi_warn_fn :: !(OccName -> Maybe WarningTxt)
- -- ^ Cached lookup for 'mi_warns'
- , mi_fix_fn :: !(OccName -> Maybe Fixity)
- -- ^ Cached lookup for 'mi_fixities'
- , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
- -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that
- -- the thing isn't in decls. It's useful to know that when seeing if we are
- -- up to date wrt. the old interface. The 'OccName' is the parent of the
- -- name, if it has one.
- }
-
-data ModIfacePhase
- = ModIfaceCore
- -- ^ Partial interface built based on output of core pipeline.
- | ModIfaceFinal
-
--- | Selects a IfaceDecl representation.
--- For fully instantiated interfaces we also maintain
--- a fingerprint, which is used for recompilation checks.
-type family IfaceDeclExts (phase :: ModIfacePhase) where
- IfaceDeclExts 'ModIfaceCore = IfaceDecl
- IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl)
-
-type family IfaceBackendExts (phase :: ModIfacePhase) where
- IfaceBackendExts 'ModIfaceCore = ()
- IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend
-
-
-
--- | A 'ModIface' plus a 'ModDetails' summarises everything we know
--- about a compiled module. The 'ModIface' is the stuff *before* linking,
--- and can be written out to an interface file. The 'ModDetails is after
--- linking and can be completely recovered from just the 'ModIface'.
---
--- When we read an interface file, we also construct a 'ModIface' from it,
--- except that we explicitly make the 'mi_decls' and a few other fields empty;
--- as when reading we consolidate the declarations etc. into a number of indexed
--- maps and environments in the 'ExternalPackageState'.
-data ModIface_ (phase :: ModIfacePhase)
- = ModIface {
- mi_module :: !Module, -- ^ Name of the module we are for
- mi_sig_of :: !(Maybe Module), -- ^ Are we a sig of another mod?
-
- mi_hsc_src :: !HscSource, -- ^ Boot? Signature?
-
- mi_deps :: Dependencies,
- -- ^ The dependencies of the module. This is
- -- consulted for directly-imported modules, but not
- -- for anything else (hence lazy)
-
- mi_usages :: [Usage],
- -- ^ Usages; kept sorted so that it's easy to decide
- -- whether to write a new iface file (changing usages
- -- doesn't affect the hash of this module)
- -- NOT STRICT! we read this field lazily from the interface file
- -- It is *only* consulted by the recompilation checker
-
- mi_exports :: ![IfaceExport],
- -- ^ Exports
- -- Kept sorted by (mod,occ), to make version comparisons easier
- -- Records the modules that are the declaration points for things
- -- exported by this module, and the 'OccName's of those things
-
-
- mi_used_th :: !Bool,
- -- ^ Module required TH splices when it was compiled.
- -- This disables recompilation avoidance (see #481).
-
- mi_fixities :: [(OccName,Fixity)],
- -- ^ Fixities
- -- NOT STRICT! we read this field lazily from the interface file
-
- mi_warns :: Warnings,
- -- ^ Warnings
- -- NOT STRICT! we read this field lazily from the interface file
-
- mi_anns :: [IfaceAnnotation],
- -- ^ Annotations
- -- NOT STRICT! we read this field lazily from the interface file
-
-
- mi_decls :: [IfaceDeclExts phase],
- -- ^ Type, class and variable declarations
- -- The hash of an Id changes if its fixity or deprecations change
- -- (as well as its type of course)
- -- Ditto data constructors, class operations, except that
- -- the hash of the parent class/tycon changes
-
- mi_globals :: !(Maybe GlobalRdrEnv),
- -- ^ Binds all the things defined at the top level in
- -- the /original source/ code for this module. which
- -- is NOT the same as mi_exports, nor mi_decls (which
- -- may contains declarations for things not actually
- -- defined by the user). Used for GHCi and for inspecting
- -- the contents of modules via the GHC API only.
- --
- -- (We need the source file to figure out the
- -- top-level environment, if we didn't compile this module
- -- from source then this field contains @Nothing@).
- --
- -- Strictly speaking this field should live in the
- -- 'HomeModInfo', but that leads to more plumbing.
-
- -- Instance declarations and rules
- mi_insts :: [IfaceClsInst], -- ^ Sorted class instance
- mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances
- mi_rules :: [IfaceRule], -- ^ Sorted rules
-
- mi_hpc :: !AnyHpcUsage,
- -- ^ True if this program uses Hpc at any point in the program.
-
- mi_trust :: !IfaceTrustInfo,
- -- ^ Safe Haskell Trust information for this module.
-
- mi_trust_pkg :: !Bool,
- -- ^ Do we require the package this module resides in be trusted
- -- to trust this module? This is used for the situation where a
- -- module is Safe (so doesn't require the package be trusted
- -- itself) but imports some trustworthy modules from its own
- -- package (which does require its own package be trusted).
- -- See Note [Trust Own Package] in GHC.Rename.Names
- mi_complete_matches :: [IfaceCompleteMatch],
-
- mi_doc_hdr :: Maybe HsDocString,
- -- ^ Module header.
-
- mi_decl_docs :: DeclDocMap,
- -- ^ Docs on declarations.
-
- mi_arg_docs :: ArgDocMap,
- -- ^ Docs on arguments.
-
- mi_final_exts :: !(IfaceBackendExts phase),
- -- ^ Either `()` or `ModIfaceBackend` for
- -- a fully instantiated interface.
-
- mi_ext_fields :: ExtensibleFields
- -- ^ Additional optional fields, where the Map key represents
- -- the field name, resulting in a (size, serialized data) pair.
- -- Because the data is intended to be serialized through the
- -- internal `Binary` class (increasing compatibility with types
- -- using `Name` and `FastString`, such as HIE), this format is
- -- chosen over `ByteString`s.
- }
-
--- | Old-style accessor for whether or not the ModIface came from an hs-boot
--- file.
-mi_boot :: ModIface -> IsBootInterface
-mi_boot iface = if mi_hsc_src iface == HsBootFile
- then IsBoot
- else NotBoot
-
--- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be
--- found, 'defaultFixity' is returned instead.
-mi_fix :: ModIface -> OccName -> Fixity
-mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity
-
--- | The semantic module for this interface; e.g., if it's a interface
--- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module'
--- will be @<A>@.
-mi_semantic_module :: ModIface_ a -> Module
-mi_semantic_module iface = case mi_sig_of iface of
- Nothing -> mi_module iface
- Just mod -> mod
-
--- | The "precise" free holes, e.g., the signatures that this
--- 'ModIface' depends on.
-mi_free_holes :: ModIface -> UniqDSet ModuleName
-mi_free_holes iface =
- case getModuleInstantiation (mi_module iface) of
- (_, Just indef)
- -- A mini-hack: we rely on the fact that 'renameFreeHoles'
- -- drops things that aren't holes.
- -> renameFreeHoles (mkUniqDSet cands) (instUnitInsts (moduleUnit indef))
- _ -> emptyUniqDSet
- where
- cands = map gwib_mod $ dep_mods $ mi_deps iface
-
--- | Given a set of free holes, and a unit identifier, rename
--- the free holes according to the instantiation of the unit
--- identifier. For example, if we have A and B free, and
--- our unit identity is @p[A=<C>,B=impl:B]@, the renamed free
--- holes are just C.
-renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName
-renameFreeHoles fhs insts =
- unionManyUniqDSets (map lookup_impl (uniqDSetToList fhs))
- where
- hmap = listToUFM insts
- lookup_impl mod_name
- | Just mod <- lookupUFM hmap mod_name = moduleFreeHoles mod
- -- It wasn't actually a hole
- | otherwise = emptyUniqDSet
-
-instance Binary ModIface where
- put_ bh (ModIface {
- mi_module = mod,
- mi_sig_of = sig_of,
- mi_hsc_src = hsc_src,
- mi_deps = deps,
- mi_usages = usages,
- mi_exports = exports,
- mi_used_th = used_th,
- mi_fixities = fixities,
- mi_warns = warns,
- mi_anns = anns,
- mi_decls = decls,
- mi_insts = insts,
- mi_fam_insts = fam_insts,
- mi_rules = rules,
- mi_hpc = hpc_info,
- mi_trust = trust,
- mi_trust_pkg = trust_pkg,
- mi_complete_matches = complete_matches,
- mi_doc_hdr = doc_hdr,
- mi_decl_docs = decl_docs,
- mi_arg_docs = arg_docs,
- mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we
- -- can deal with it's pointer in the header
- -- when we write the actual file
- mi_final_exts = ModIfaceBackend {
- mi_iface_hash = iface_hash,
- mi_mod_hash = mod_hash,
- mi_flag_hash = flag_hash,
- mi_opt_hash = opt_hash,
- mi_hpc_hash = hpc_hash,
- mi_plugin_hash = plugin_hash,
- mi_orphan = orphan,
- mi_finsts = hasFamInsts,
- mi_exp_hash = exp_hash,
- mi_orphan_hash = orphan_hash
- }}) = do
- put_ bh mod
- put_ bh sig_of
- put_ bh hsc_src
- put_ bh iface_hash
- put_ bh mod_hash
- put_ bh flag_hash
- put_ bh opt_hash
- put_ bh hpc_hash
- put_ bh plugin_hash
- put_ bh orphan
- put_ bh hasFamInsts
- lazyPut bh deps
- lazyPut bh usages
- put_ bh exports
- put_ bh exp_hash
- put_ bh used_th
- put_ bh fixities
- lazyPut bh warns
- lazyPut bh anns
- put_ bh decls
- put_ bh insts
- put_ bh fam_insts
- lazyPut bh rules
- put_ bh orphan_hash
- put_ bh hpc_info
- put_ bh trust
- put_ bh trust_pkg
- put_ bh complete_matches
- lazyPut bh doc_hdr
- lazyPut bh decl_docs
- lazyPut bh arg_docs
-
- get bh = do
- mod <- get bh
- sig_of <- get bh
- hsc_src <- get bh
- iface_hash <- get bh
- mod_hash <- get bh
- flag_hash <- get bh
- opt_hash <- get bh
- hpc_hash <- get bh
- plugin_hash <- get bh
- orphan <- get bh
- hasFamInsts <- get bh
- deps <- lazyGet bh
- usages <- {-# SCC "bin_usages" #-} lazyGet bh
- exports <- {-# SCC "bin_exports" #-} get bh
- exp_hash <- get bh
- used_th <- get bh
- fixities <- {-# SCC "bin_fixities" #-} get bh
- warns <- {-# SCC "bin_warns" #-} lazyGet bh
- anns <- {-# SCC "bin_anns" #-} lazyGet bh
- decls <- {-# SCC "bin_tycldecls" #-} get bh
- insts <- {-# SCC "bin_insts" #-} get bh
- fam_insts <- {-# SCC "bin_fam_insts" #-} get bh
- rules <- {-# SCC "bin_rules" #-} lazyGet bh
- orphan_hash <- get bh
- hpc_info <- get bh
- trust <- get bh
- trust_pkg <- get bh
- complete_matches <- get bh
- doc_hdr <- lazyGet bh
- decl_docs <- lazyGet bh
- arg_docs <- lazyGet bh
- return (ModIface {
- mi_module = mod,
- mi_sig_of = sig_of,
- mi_hsc_src = hsc_src,
- mi_deps = deps,
- mi_usages = usages,
- mi_exports = exports,
- mi_used_th = used_th,
- mi_anns = anns,
- mi_fixities = fixities,
- mi_warns = warns,
- mi_decls = decls,
- mi_globals = Nothing,
- mi_insts = insts,
- mi_fam_insts = fam_insts,
- mi_rules = rules,
- mi_hpc = hpc_info,
- mi_trust = trust,
- mi_trust_pkg = trust_pkg,
- -- And build the cached values
- mi_complete_matches = complete_matches,
- mi_doc_hdr = doc_hdr,
- mi_decl_docs = decl_docs,
- mi_arg_docs = arg_docs,
- mi_ext_fields = emptyExtensibleFields, -- placeholder because this is dealt
- -- with specially when the file is read
- mi_final_exts = ModIfaceBackend {
- mi_iface_hash = iface_hash,
- mi_mod_hash = mod_hash,
- mi_flag_hash = flag_hash,
- mi_opt_hash = opt_hash,
- mi_hpc_hash = hpc_hash,
- mi_plugin_hash = plugin_hash,
- mi_orphan = orphan,
- mi_finsts = hasFamInsts,
- mi_exp_hash = exp_hash,
- mi_orphan_hash = orphan_hash,
- mi_warn_fn = mkIfaceWarnCache warns,
- mi_fix_fn = mkIfaceFixCache fixities,
- mi_hash_fn = mkIfaceHashCache decls
- }})
-
--- | The original names declared of a certain module that are exported
-type IfaceExport = AvailInfo
-
-emptyPartialModIface :: Module -> PartialModIface
-emptyPartialModIface mod
- = ModIface { mi_module = mod,
- mi_sig_of = Nothing,
- mi_hsc_src = HsSrcFile,
- mi_deps = noDependencies,
- mi_usages = [],
- mi_exports = [],
- mi_used_th = False,
- mi_fixities = [],
- mi_warns = NoWarnings,
- mi_anns = [],
- mi_insts = [],
- mi_fam_insts = [],
- mi_rules = [],
- mi_decls = [],
- mi_globals = Nothing,
- mi_hpc = False,
- mi_trust = noIfaceTrustInfo,
- mi_trust_pkg = False,
- mi_complete_matches = [],
- mi_doc_hdr = Nothing,
- mi_decl_docs = emptyDeclDocMap,
- mi_arg_docs = emptyArgDocMap,
- mi_final_exts = (),
- mi_ext_fields = emptyExtensibleFields
- }
-
-emptyFullModIface :: Module -> ModIface
-emptyFullModIface mod =
- (emptyPartialModIface mod)
- { mi_decls = []
- , mi_final_exts = ModIfaceBackend
- { mi_iface_hash = fingerprint0,
- mi_mod_hash = fingerprint0,
- mi_flag_hash = fingerprint0,
- mi_opt_hash = fingerprint0,
- mi_hpc_hash = fingerprint0,
- mi_plugin_hash = fingerprint0,
- mi_orphan = False,
- mi_finsts = False,
- mi_exp_hash = fingerprint0,
- mi_orphan_hash = fingerprint0,
- mi_warn_fn = emptyIfaceWarnCache,
- mi_fix_fn = emptyIfaceFixCache,
- mi_hash_fn = emptyIfaceHashCache } }
-
--- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface'
-mkIfaceHashCache :: [(Fingerprint,IfaceDecl)]
- -> (OccName -> Maybe (OccName, Fingerprint))
-mkIfaceHashCache pairs
- = \occ -> lookupOccEnv env occ
- where
- env = foldl' add_decl emptyOccEnv pairs
- add_decl env0 (v,d) = foldl' add env0 (ifaceDeclFingerprints v d)
- where
- add env0 (occ,hash) = extendOccEnv env0 occ (occ,hash)
-
-emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
-emptyIfaceHashCache _occ = Nothing
-
-
--- | The 'ModDetails' is essentially a cache for information in the 'ModIface'
--- for home modules only. Information relating to packages will be loaded into
--- global environments in 'ExternalPackageState'.
-data ModDetails
- = ModDetails {
- -- The next two fields are created by the typechecker
- md_exports :: [AvailInfo],
- md_types :: !TypeEnv, -- ^ Local type environment for this particular module
- -- Includes Ids, TyCons, PatSyns
- md_insts :: ![ClsInst], -- ^ 'DFunId's for the instances in this module
- md_fam_insts :: ![FamInst],
- md_rules :: ![CoreRule], -- ^ Domain may include 'Id's from other modules
- md_anns :: ![Annotation], -- ^ Annotations present in this module: currently
- -- they only annotate things also declared in this module
- md_complete_matches :: [CompleteMatch]
- -- ^ Complete match pragmas for this module
- }
-
--- | Constructs an empty ModDetails
-emptyModDetails :: ModDetails
-emptyModDetails
- = ModDetails { md_types = emptyTypeEnv,
- md_exports = [],
- md_insts = [],
- md_rules = [],
- md_fam_insts = [],
- md_anns = [],
- md_complete_matches = [] }
-
--- | Records the modules directly imported by a module for extracting e.g.
--- usage information, and also to give better error message
-type ImportedMods = ModuleEnv [ImportedBy]
-
--- | If a module was "imported" by the user, we associate it with
--- more detailed usage information 'ImportedModsVal'; a module
--- imported by the system only gets used for usage information.
-data ImportedBy
- = ImportedByUser ImportedModsVal
- | ImportedBySystem
-
-importedByUser :: [ImportedBy] -> [ImportedModsVal]
-importedByUser (ImportedByUser imv : bys) = imv : importedByUser bys
-importedByUser (ImportedBySystem : bys) = importedByUser bys
-importedByUser [] = []
-
-data ImportedModsVal
- = ImportedModsVal {
- imv_name :: ModuleName, -- ^ The name the module is imported with
- imv_span :: SrcSpan, -- ^ the source span of the whole import
- imv_is_safe :: IsSafeImport, -- ^ whether this is a safe import
- imv_is_hiding :: Bool, -- ^ whether this is an "hiding" import
- imv_all_exports :: !GlobalRdrEnv, -- ^ all the things the module could provide
- -- NB. BangPattern here: otherwise this leaks. (#15111)
- imv_qualified :: Bool -- ^ whether this is a qualified import
- }
-
--- | A ModGuts is carried through the compiler, accumulating stuff as it goes
--- There is only one ModGuts at any time, the one for the module
--- being compiled right now. Once it is compiled, a 'ModIface' and
--- 'ModDetails' are extracted and the ModGuts is discarded.
-data ModGuts
- = ModGuts {
- mg_module :: !Module, -- ^ Module being compiled
- mg_hsc_src :: HscSource, -- ^ Whether it's an hs-boot module
- mg_loc :: SrcSpan, -- ^ For error messages from inner passes
- mg_exports :: ![AvailInfo], -- ^ What it exports
- mg_deps :: !Dependencies, -- ^ What it depends on, directly or
- -- otherwise
- mg_usages :: ![Usage], -- ^ What was used? Used for interfaces.
-
- mg_used_th :: !Bool, -- ^ Did we run a TH splice?
- mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment
-
- -- These fields all describe the things **declared in this module**
- mg_fix_env :: !FixityEnv, -- ^ Fixities declared in this module.
- -- Used for creating interface files.
- mg_tcs :: ![TyCon], -- ^ TyCons declared in this module
- -- (includes TyCons for classes)
- mg_insts :: ![ClsInst], -- ^ Class instances declared in this module
- mg_fam_insts :: ![FamInst],
- -- ^ Family instances declared in this module
- mg_patsyns :: ![PatSyn], -- ^ Pattern synonyms declared in this module
- mg_rules :: ![CoreRule], -- ^ Before the core pipeline starts, contains
- -- See Note [Overall plumbing for rules] in "GHC.Core.Rules"
- mg_binds :: !CoreProgram, -- ^ Bindings for this module
- mg_foreign :: !ForeignStubs, -- ^ Foreign exports declared in this module
- mg_foreign_files :: ![(ForeignSrcLang, FilePath)],
- -- ^ Files to be compiled with the C compiler
- mg_warns :: !Warnings, -- ^ Warnings declared in the module
- mg_anns :: [Annotation], -- ^ Annotations declared in this module
- mg_complete_matches :: [CompleteMatch], -- ^ Complete Matches
- mg_hpc_info :: !HpcInfo, -- ^ Coverage tick boxes in the module
- mg_modBreaks :: !(Maybe ModBreaks), -- ^ Breakpoints for the module
-
- -- The next two fields are unusual, because they give instance
- -- environments for *all* modules in the home package, including
- -- this module, rather than for *just* this module.
- -- Reason: when looking up an instance we don't want to have to
- -- look at each module in the home package in turn
- mg_inst_env :: InstEnv, -- ^ Class instance environment for
- -- /home-package/ modules (including this
- -- one); c.f. 'tcg_inst_env'
- mg_fam_inst_env :: FamInstEnv, -- ^ Type-family instance environment for
- -- /home-package/ modules (including this
- -- one); c.f. 'tcg_fam_inst_env'
-
- mg_safe_haskell :: SafeHaskellMode, -- ^ Safe Haskell mode
- mg_trust_pkg :: Bool, -- ^ Do we need to trust our
- -- own package for Safe Haskell?
- -- See Note [Trust Own Package]
- -- in "GHC.Rename.Names"
-
- mg_doc_hdr :: !(Maybe HsDocString), -- ^ Module header.
- mg_decl_docs :: !DeclDocMap, -- ^ Docs on declarations.
- mg_arg_docs :: !ArgDocMap -- ^ Docs on arguments.
- }
-
--- The ModGuts takes on several slightly different forms:
---
--- After simplification, the following fields change slightly:
--- mg_rules Orphan rules only (local ones now attached to binds)
--- mg_binds With rules attached
-
----------------------------------------------------------
--- The Tidy pass forks the information about this module:
--- * one lot goes to interface file generation (ModIface)
--- and later compilations (ModDetails)
--- * the other lot goes to code generation (CgGuts)
-
--- | A restricted form of 'ModGuts' for code generation purposes
-data CgGuts
- = CgGuts {
- cg_module :: !Module,
- -- ^ Module being compiled
-
- cg_tycons :: [TyCon],
- -- ^ Algebraic data types (including ones that started
- -- life as classes); generate constructors and info
- -- tables. Includes newtypes, just for the benefit of
- -- External Core
-
- cg_binds :: CoreProgram,
- -- ^ The tidied main bindings, including
- -- previously-implicit bindings for record and class
- -- selectors, and data constructor wrappers. But *not*
- -- data constructor workers; reason: we regard them
- -- as part of the code-gen of tycons
-
- cg_foreign :: !ForeignStubs, -- ^ Foreign export stubs
- cg_foreign_files :: ![(ForeignSrcLang, FilePath)],
- cg_dep_pkgs :: ![UnitId], -- ^ Dependent packages, used to
- -- generate #includes for C code gen
- cg_hpc_info :: !HpcInfo, -- ^ Program coverage tick box information
- cg_modBreaks :: !(Maybe ModBreaks), -- ^ Module breakpoints
- cg_spt_entries :: [SptEntry]
- -- ^ Static pointer table entries for static forms defined in
- -- the module.
- -- See Note [Grand plan for static forms] in "GHC.Iface.Tidy.StaticPtrTable"
- }
-
------------------------------------
--- | Foreign export stubs
-data ForeignStubs
- = NoStubs
- -- ^ We don't have any stubs
- | ForeignStubs SDoc SDoc
- -- ^ There are some stubs. Parameters:
- --
- -- 1) Header file prototypes for
- -- "foreign exported" functions
- --
- -- 2) C stubs to use when calling
- -- "foreign exported" functions
-
-appendStubC :: ForeignStubs -> SDoc -> ForeignStubs
-appendStubC NoStubs c_code = ForeignStubs empty c_code
-appendStubC (ForeignStubs h c) c_code = ForeignStubs h (c $$ c_code)
-
-{-
-************************************************************************
-* *
- The interactive context
-* *
-************************************************************************
-
-Note [The interactive package]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Type, class, and value declarations at the command prompt are treated
-as if they were defined in modules
- interactive:Ghci1
- interactive:Ghci2
- ...etc...
-with each bunch of declarations using a new module, all sharing a
-common package 'interactive' (see Module.interactiveUnitId, and
-GHC.Builtin.Names.mkInteractiveModule).
-
-This scheme deals well with shadowing. For example:
-
- ghci> data T = A
- ghci> data T = B
- ghci> :i A
- data Ghci1.T = A -- Defined at <interactive>:2:10
-
-Here we must display info about constructor A, but its type T has been
-shadowed by the second declaration. But it has a respectable
-qualified name (Ghci1.T), and its source location says where it was
-defined.
-
-So the main invariant continues to hold, that in any session an
-original name M.T only refers to one unique thing. (In a previous
-iteration both the T's above were called :Interactive.T, albeit with
-different uniques, which gave rise to all sorts of trouble.)
-
-The details are a bit tricky though:
-
- * The field ic_mod_index counts which Ghci module we've got up to.
- It is incremented when extending ic_tythings
-
- * ic_tythings contains only things from the 'interactive' package.
-
- * Module from the 'interactive' package (Ghci1, Ghci2 etc) never go
- in the Home Package Table (HPT). When you say :load, that's when we
- extend the HPT.
-
- * The 'homeUnitId' field of DynFlags is *not* set to 'interactive'.
- It stays as 'main' (or whatever -this-unit-id says), and is the
- package to which :load'ed modules are added to.
-
- * So how do we arrange that declarations at the command prompt get to
- be in the 'interactive' package? Simply by setting the tcg_mod
- field of the TcGblEnv to "interactive:Ghci1". This is done by the
- call to initTc in initTcInteractive, which in turn get the module
- from it 'icInteractiveModule' field of the interactive context.
-
- The 'homeUnitId' field stays as 'main' (or whatever -this-unit-id says.
-
- * The main trickiness is that the type environment (tcg_type_env) and
- fixity envt (tcg_fix_env), now contain entities from all the
- interactive-package modules (Ghci1, Ghci2, ...) together, rather
- than just a single module as is usually the case. So you can't use
- "nameIsLocalOrFrom" to decide whether to look in the TcGblEnv vs
- the HPT/PTE. This is a change, but not a problem provided you
- know.
-
-* However, the tcg_binds, tcg_sigs, tcg_insts, tcg_fam_insts, etc fields
- of the TcGblEnv, which collect "things defined in this module", all
- refer to stuff define in a single GHCi command, *not* all the commands
- so far.
-
- In contrast, tcg_inst_env, tcg_fam_inst_env, have instances from
- all GhciN modules, which makes sense -- they are all "home package"
- modules.
-
-
-Note [Interactively-bound Ids in GHCi]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-The Ids bound by previous Stmts in GHCi are currently
- a) GlobalIds, with
- b) An External Name, like Ghci4.foo
- See Note [The interactive package] above
- c) A tidied type
-
- (a) They must be GlobalIds (not LocalIds) otherwise when we come to
- compile an expression using these ids later, the byte code
- generator will consider the occurrences to be free rather than
- global.
-
- (b) Having an External Name is important because of Note
- [GlobalRdrEnv shadowing] in GHC.Types.Names.RdrName
-
- (c) Their types are tidied. This is important, because :info may ask
- to look at them, and :info expects the things it looks up to have
- tidy types
-
-Where do interactively-bound Ids come from?
-
- - GHCi REPL Stmts e.g.
- ghci> let foo x = x+1
- These start with an Internal Name because a Stmt is a local
- construct, so the renamer naturally builds an Internal name for
- each of its binders. Then in tcRnStmt they are externalised via
- GHC.Tc.Module.externaliseAndTidyId, so they get Names like Ghic4.foo.
-
- - Ids bound by the debugger etc have Names constructed by
- GHC.Iface.Env.newInteractiveBinder; at the call sites it is followed by
- mkVanillaGlobal or mkVanillaGlobalWithInfo. So again, they are
- all Global, External.
-
- - TyCons, Classes, and Ids bound by other top-level declarations in
- GHCi (eg foreign import, record selectors) also get External
- Names, with Ghci9 (or 8, or 7, etc) as the module name.
-
-
-Note [ic_tythings]
-~~~~~~~~~~~~~~~~~~
-The ic_tythings field contains
- * The TyThings declared by the user at the command prompt
- (eg Ids, TyCons, Classes)
-
- * The user-visible Ids that arise from such things, which
- *don't* come from 'implicitTyThings', notably:
- - record selectors
- - class ops
- The implicitTyThings are readily obtained from the TyThings
- but record selectors etc are not
-
-It does *not* contain
- * DFunIds (they can be gotten from ic_instances)
- * CoAxioms (ditto)
-
-See also Note [Interactively-bound Ids in GHCi]
-
-Note [Override identical instances in GHCi]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-If you declare a new instance in GHCi that is identical to a previous one,
-we simply override the previous one; we don't regard it as overlapping.
-e.g. Prelude> data T = A | B
- Prelude> instance Eq T where ...
- Prelude> instance Eq T where ... -- This one overrides
-
-It's exactly the same for type-family instances. See #7102
--}
-
--- | Interactive context, recording information about the state of the
--- context in which statements are executed in a GHCi session.
-data InteractiveContext
- = InteractiveContext {
- ic_dflags :: DynFlags,
- -- ^ The 'DynFlags' used to evaluate interactive expressions
- -- and statements.
-
- ic_mod_index :: Int,
- -- ^ Each GHCi stmt or declaration brings some new things into
- -- scope. We give them names like interactive:Ghci9.T,
- -- where the ic_index is the '9'. The ic_mod_index is
- -- incremented whenever we add something to ic_tythings
- -- See Note [The interactive package]
-
- ic_imports :: [InteractiveImport],
- -- ^ The GHCi top-level scope (ic_rn_gbl_env) is extended with
- -- these imports
- --
- -- This field is only stored here so that the client
- -- can retrieve it with GHC.getContext. GHC itself doesn't
- -- use it, but does reset it to empty sometimes (such
- -- as before a GHC.load). The context is set with GHC.setContext.
-
- ic_tythings :: [TyThing],
- -- ^ TyThings defined by the user, in reverse order of
- -- definition (ie most recent at the front)
- -- See Note [ic_tythings]
-
- ic_rn_gbl_env :: GlobalRdrEnv,
- -- ^ The cached 'GlobalRdrEnv', built by
- -- 'GHC.Runtime.Eval.setContext' and updated regularly
- -- It contains everything in scope at the command line,
- -- including everything in ic_tythings
-
- ic_instances :: ([ClsInst], [FamInst]),
- -- ^ All instances and family instances created during
- -- this session. These are grabbed en masse after each
- -- update to be sure that proper overlapping is retained.
- -- That is, rather than re-check the overlapping each
- -- time we update the context, we just take the results
- -- from the instance code that already does that.
-
- ic_fix_env :: FixityEnv,
- -- ^ Fixities declared in let statements
-
- ic_default :: Maybe [Type],
- -- ^ The current default types, set by a 'default' declaration
-
- ic_resume :: [Resume],
- -- ^ The stack of breakpoint contexts
-
- ic_monad :: Name,
- -- ^ The monad that GHCi is executing in
-
- ic_int_print :: Name,
- -- ^ The function that is used for printing results
- -- of expressions in ghci and -e mode.
-
- ic_cwd :: Maybe FilePath
- -- virtual CWD of the program
- }
-
-data InteractiveImport
- = IIDecl (ImportDecl GhcPs)
- -- ^ Bring the exports of a particular module
- -- (filtered by an import decl) into scope
-
- | IIModule ModuleName
- -- ^ Bring into scope the entire top-level envt of
- -- of this module, including the things imported
- -- into it.
-
-
--- | Constructs an empty InteractiveContext.
-emptyInteractiveContext :: DynFlags -> InteractiveContext
-emptyInteractiveContext dflags
- = InteractiveContext {
- ic_dflags = dflags,
- ic_imports = [],
- ic_rn_gbl_env = emptyGlobalRdrEnv,
- ic_mod_index = 1,
- ic_tythings = [],
- ic_instances = ([],[]),
- ic_fix_env = emptyNameEnv,
- ic_monad = ioTyConName, -- IO monad by default
- ic_int_print = printName, -- System.IO.print by default
- ic_default = Nothing,
- ic_resume = [],
- ic_cwd = Nothing }
-
-icInteractiveModule :: InteractiveContext -> Module
-icInteractiveModule (InteractiveContext { ic_mod_index = index })
- = mkInteractiveModule index
-
--- | This function returns the list of visible TyThings (useful for
--- e.g. showBindings)
-icInScopeTTs :: InteractiveContext -> [TyThing]
-icInScopeTTs = ic_tythings
-
--- | Get the PrintUnqualified function based on the flags and this InteractiveContext
-icPrintUnqual :: UnitState -> HomeUnit -> InteractiveContext -> PrintUnqualified
-icPrintUnqual unit_state home_unit InteractiveContext{ ic_rn_gbl_env = grenv } =
- mkPrintUnqualified unit_state home_unit grenv
-
--- | extendInteractiveContext is called with new TyThings recently defined to update the
--- InteractiveContext to include them. Ids are easily removed when shadowed,
--- but Classes and TyCons are not. Some work could be done to determine
--- whether they are entirely shadowed, but as you could still have references
--- to them (e.g. instances for classes or values of the type for TyCons), it's
--- not clear whether removing them is even the appropriate behavior.
-extendInteractiveContext :: InteractiveContext
- -> [TyThing]
- -> [ClsInst] -> [FamInst]
- -> Maybe [Type]
- -> FixityEnv
- -> InteractiveContext
-extendInteractiveContext ictxt new_tythings new_cls_insts new_fam_insts defaults fix_env
- = ictxt { ic_mod_index = ic_mod_index ictxt + 1
- -- Always bump this; even instances should create
- -- a new mod_index (#9426)
- , ic_tythings = new_tythings ++ old_tythings
- , ic_rn_gbl_env = ic_rn_gbl_env ictxt `icExtendGblRdrEnv` new_tythings
- , ic_instances = ( new_cls_insts ++ old_cls_insts
- , new_fam_insts ++ fam_insts )
- -- we don't shadow old family instances (#7102),
- -- so don't need to remove them here
- , ic_default = defaults
- , ic_fix_env = fix_env -- See Note [Fixity declarations in GHCi]
- }
- where
- new_ids = [id | AnId id <- new_tythings]
- old_tythings = filterOut (shadowed_by new_ids) (ic_tythings ictxt)
-
- -- Discard old instances that have been fully overridden
- -- See Note [Override identical instances in GHCi]
- (cls_insts, fam_insts) = ic_instances ictxt
- old_cls_insts = filterOut (\i -> any (identicalClsInstHead i) new_cls_insts) cls_insts
-
-extendInteractiveContextWithIds :: InteractiveContext -> [Id] -> InteractiveContext
--- Just a specialised version
-extendInteractiveContextWithIds ictxt new_ids
- | null new_ids = ictxt
- | otherwise = ictxt { ic_mod_index = ic_mod_index ictxt + 1
- , ic_tythings = new_tythings ++ old_tythings
- , ic_rn_gbl_env = ic_rn_gbl_env ictxt `icExtendGblRdrEnv` new_tythings }
- where
- new_tythings = map AnId new_ids
- old_tythings = filterOut (shadowed_by new_ids) (ic_tythings ictxt)
-
-shadowed_by :: [Id] -> TyThing -> Bool
-shadowed_by ids = shadowed
- where
- shadowed id = getOccName id `elemOccSet` new_occs
- new_occs = mkOccSet (map getOccName ids)
-
-setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
-setInteractivePrintName ic n = ic{ic_int_print = n}
-
- -- ToDo: should not add Ids to the gbl env here
-
--- | Add TyThings to the GlobalRdrEnv, earlier ones in the list shadowing
--- later ones, and shadowing existing entries in the GlobalRdrEnv.
-icExtendGblRdrEnv :: GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv
-icExtendGblRdrEnv env tythings
- = foldr add env tythings -- Foldr makes things in the front of
- -- the list shadow things at the back
- where
- -- One at a time, to ensure each shadows the previous ones
- add thing env
- | is_sub_bndr thing
- = env
- | otherwise
- = foldl' extendGlobalRdrEnv env1 (concatMap localGREsFromAvail avail)
- where
- env1 = shadowNames env (concatMap availNames avail)
- avail = tyThingAvailInfo thing
-
- -- Ugh! The new_tythings may include record selectors, since they
- -- are not implicit-ids, and must appear in the TypeEnv. But they
- -- will also be brought into scope by the corresponding (ATyCon
- -- tc). And we want the latter, because that has the correct
- -- parent (#10520)
- is_sub_bndr (AnId f) = case idDetails f of
- RecSelId {} -> True
- ClassOpId {} -> True
- _ -> False
- is_sub_bndr _ = False
-
-substInteractiveContext :: InteractiveContext -> TCvSubst -> InteractiveContext
-substInteractiveContext ictxt@InteractiveContext{ ic_tythings = tts } subst
- | isEmptyTCvSubst subst = ictxt
- | otherwise = ictxt { ic_tythings = map subst_ty tts }
- where
- subst_ty (AnId id)
- = AnId $ updateIdTypeAndMult (substTyAddInScope subst) id
- -- Variables in the interactive context *can* mention free type variables
- -- because of the runtime debugger. Otherwise you'd expect all
- -- variables bound in the interactive context to be closed.
- subst_ty tt
- = tt
-
-instance Outputable InteractiveImport where
- ppr (IIModule m) = char '*' <> ppr m
- ppr (IIDecl d) = ppr d
-
-{-
-************************************************************************
-* *
- Building a PrintUnqualified
-* *
-************************************************************************
-
-Note [Printing original names]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Deciding how to print names is pretty tricky. We are given a name
-P:M.T, where P is the package name, M is the defining module, and T is
-the occurrence name, and we have to decide in which form to display
-the name given a GlobalRdrEnv describing the current scope.
-
-Ideally we want to display the name in the form in which it is in
-scope. However, the name might not be in scope at all, and that's
-where it gets tricky. Here are the cases:
-
- 1. T uniquely maps to P:M.T ---> "T" NameUnqual
- 2. There is an X for which X.T
- uniquely maps to P:M.T ---> "X.T" NameQual X
- 3. There is no binding for "M.T" ---> "M.T" NameNotInScope1
- 4. Otherwise ---> "P:M.T" NameNotInScope2
-
-(3) and (4) apply when the entity P:M.T is not in the GlobalRdrEnv at
-all. In these cases we still want to refer to the name as "M.T", *but*
-"M.T" might mean something else in the current scope (e.g. if there's
-an "import X as M"), so to avoid confusion we avoid using "M.T" if
-there's already a binding for it. Instead we write P:M.T.
-
-There's one further subtlety: in case (3), what if there are two
-things around, P1:M.T and P2:M.T? Then we don't want to print both of
-them as M.T! However only one of the modules P1:M and P2:M can be
-exposed (say P2), so we use M.T for that, and P1:M.T for the other one.
-This is handled by the qual_mod component of PrintUnqualified, inside
-the (ppr mod) of case (3), in Name.pprModulePrefix
-
-Note [Printing unit ids]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-In the old days, original names were tied to PackageIds, which directly
-corresponded to the entities that users wrote in Cabal files, and were perfectly
-suitable for printing when we need to disambiguate packages. However, with
-instantiated units, the situation can be different: if the key is instantiated
-with some holes, we should try to give the user some more useful information.
--}
-
--- | Creates some functions that work out the best ways to format
--- names for the user according to a set of heuristics.
-mkPrintUnqualified :: UnitState -> HomeUnit -> GlobalRdrEnv -> PrintUnqualified
-mkPrintUnqualified unit_state home_unit env
- = QueryQualify qual_name
- (mkQualModule unit_state home_unit)
- (mkQualPackage unit_state)
- where
- qual_name mod occ
- | [gre] <- unqual_gres
- , right_name gre
- = NameUnqual -- If there's a unique entity that's in scope
- -- unqualified with 'occ' AND that entity is
- -- the right one, then we can use the unqualified name
-
- | [] <- unqual_gres
- , any is_name forceUnqualNames
- , not (isDerivedOccName occ)
- = NameUnqual -- Don't qualify names that come from modules
- -- that come with GHC, often appear in error messages,
- -- but aren't typically in scope. Doing this does not
- -- cause ambiguity, and it reduces the amount of
- -- qualification in error messages thus improving
- -- readability.
- --
- -- A motivating example is 'Constraint'. It's often not
- -- in scope, but printing GHC.Prim.Constraint seems
- -- overkill.
-
- | [gre] <- qual_gres
- = NameQual (greQualModName gre)
-
- | null qual_gres
- = if null (lookupGRE_RdrName (mkRdrQual (moduleName mod) occ) env)
- then NameNotInScope1
- else NameNotInScope2
-
- | otherwise
- = NameNotInScope1 -- Can happen if 'f' is bound twice in the module
- -- Eg f = True; g = 0; f = False
- where
- is_name :: Name -> Bool
- is_name name = ASSERT2( isExternalName name, ppr name )
- nameModule name == mod && nameOccName name == occ
-
- forceUnqualNames :: [Name]
- forceUnqualNames =
- map tyConName [ constraintKindTyCon, heqTyCon, coercibleTyCon ]
- ++ [ eqTyConName ]
-
- right_name gre = nameModule_maybe (gre_name gre) == Just mod
-
- unqual_gres = lookupGRE_RdrName (mkRdrUnqual occ) env
- qual_gres = filter right_name (lookupGlobalRdrEnv env occ)
-
- -- we can mention a module P:M without the P: qualifier iff
- -- "import M" would resolve unambiguously to P:M. (if P is the
- -- current package we can just assume it is unqualified).
-
--- | Creates a function for formatting modules based on two heuristics:
--- (1) if the module is the current module, don't qualify, and (2) if there
--- is only one exposed package which exports this module, don't qualify.
-mkQualModule :: UnitState -> HomeUnit -> QueryQualifyModule
-mkQualModule unit_state home_unit mod
- | isHomeModule home_unit mod = False
-
- | [(_, pkgconfig)] <- lookup,
- mkUnit pkgconfig == moduleUnit mod
- -- this says: we are given a module P:M, is there just one exposed package
- -- that exposes a module M, and is it package P?
- = False
-
- | otherwise = True
- where lookup = lookupModuleInAllUnits unit_state (moduleName mod)
-
--- | Creates a function for formatting packages based on two heuristics:
--- (1) don't qualify if the package in question is "main", and (2) only qualify
--- with a unit id if the package ID would be ambiguous.
-mkQualPackage :: UnitState -> QueryQualifyPackage
-mkQualPackage pkgs uid
- | uid == mainUnit || uid == interactiveUnit
- -- Skip the lookup if it's main, since it won't be in the package
- -- database!
- = False
- | Just pkgid <- mb_pkgid
- , searchPackageId pkgs pkgid `lengthIs` 1
- -- this says: we are given a package pkg-0.1@MMM, are there only one
- -- exposed packages whose package ID is pkg-0.1?
- = False
- | otherwise
- = True
- where mb_pkgid = fmap unitPackageId (lookupUnit pkgs uid)
-
--- | A function which only qualifies package names if necessary; but
--- qualifies all other identifiers.
-pkgQual :: UnitState -> PrintUnqualified
-pkgQual pkgs = alwaysQualify { queryQualifyPackage = mkQualPackage pkgs }
-
-{-
-************************************************************************
-* *
- Implicit TyThings
-* *
-************************************************************************
-
-Note [Implicit TyThings]
-~~~~~~~~~~~~~~~~~~~~~~~~
- DEFINITION: An "implicit" TyThing is one that does not have its own
- IfaceDecl in an interface file. Instead, its binding in the type
- environment is created as part of typechecking the IfaceDecl for
- some other thing.
-
-Examples:
- * All DataCons are implicit, because they are generated from the
- IfaceDecl for the data/newtype. Ditto class methods.
-
- * Record selectors are *not* implicit, because they get their own
- free-standing IfaceDecl.
-
- * Associated data/type families are implicit because they are
- included in the IfaceDecl of the parent class. (NB: the
- IfaceClass decl happens to use IfaceDecl recursively for the
- associated types, but that's irrelevant here.)
-
- * Dictionary function Ids are not implicit.
-
- * Axioms for newtypes are implicit (same as above), but axioms
- for data/type family instances are *not* implicit (like DFunIds).
--}
-
--- | Determine the 'TyThing's brought into scope by another 'TyThing'
--- /other/ than itself. For example, Id's don't have any implicit TyThings
--- as they just bring themselves into scope, but classes bring their
--- dictionary datatype, type constructor and some selector functions into
--- scope, just for a start!
-
--- N.B. the set of TyThings returned here *must* match the set of
--- names returned by 'GHC.Iface.Load.ifaceDeclImplicitBndrs', in the sense that
--- TyThing.getOccName should define a bijection between the two lists.
--- This invariant is used in 'GHC.Iface.Load.loadDecl' (see note [Tricky iface loop])
--- The order of the list does not matter.
-implicitTyThings :: TyThing -> [TyThing]
-implicitTyThings (AnId _) = []
-implicitTyThings (ACoAxiom _cc) = []
-implicitTyThings (ATyCon tc) = implicitTyConThings tc
-implicitTyThings (AConLike cl) = implicitConLikeThings cl
-
-implicitConLikeThings :: ConLike -> [TyThing]
-implicitConLikeThings (RealDataCon dc)
- = dataConImplicitTyThings dc
-
-implicitConLikeThings (PatSynCon {})
- = [] -- Pattern synonyms have no implicit Ids; the wrapper and matcher
- -- are not "implicit"; they are simply new top-level bindings,
- -- and they have their own declaration in an interface file
- -- Unless a record pat syn when there are implicit selectors
- -- They are still not included here as `implicitConLikeThings` is
- -- used by `tcTyClsDecls` whilst pattern synonyms are typed checked
- -- by `tcTopValBinds`.
-
-implicitClassThings :: Class -> [TyThing]
-implicitClassThings cl
- = -- Does not include default methods, because those Ids may have
- -- their own pragmas, unfoldings etc, not derived from the Class object
-
- -- associated types
- -- No recursive call for the classATs, because they
- -- are only the family decls; they have no implicit things
- map ATyCon (classATs cl) ++
-
- -- superclass and operation selectors
- map AnId (classAllSelIds cl)
-
-implicitTyConThings :: TyCon -> [TyThing]
-implicitTyConThings tc
- = class_stuff ++
- -- fields (names of selectors)
-
- -- (possibly) implicit newtype axioms
- -- or type family axioms
- implicitCoTyCon tc ++
-
- -- for each data constructor in order,
- -- the constructor, worker, and (possibly) wrapper
- [ thing | dc <- tyConDataCons tc
- , thing <- AConLike (RealDataCon dc) : dataConImplicitTyThings dc ]
- -- NB. record selectors are *not* implicit, they have fully-fledged
- -- bindings that pass through the compilation pipeline as normal.
- where
- class_stuff = case tyConClass_maybe tc of
- Nothing -> []
- Just cl -> implicitClassThings cl
-
--- For newtypes and closed type families (only) add the implicit coercion tycon
-implicitCoTyCon :: TyCon -> [TyThing]
-implicitCoTyCon tc
- | Just co <- newTyConCo_maybe tc = [ACoAxiom $ toBranchedAxiom co]
- | Just co <- isClosedSynFamilyTyConWithAxiom_maybe tc
- = [ACoAxiom co]
- | otherwise = []
-
--- | Returns @True@ if there should be no interface-file declaration
--- for this thing on its own: either it is built-in, or it is part
--- of some other declaration, or it is generated implicitly by some
--- other declaration.
-isImplicitTyThing :: TyThing -> Bool
-isImplicitTyThing (AConLike cl) = case cl of
- RealDataCon {} -> True
- PatSynCon {} -> False
-isImplicitTyThing (AnId id) = isImplicitId id
-isImplicitTyThing (ATyCon tc) = isImplicitTyCon tc
-isImplicitTyThing (ACoAxiom ax) = isImplicitCoAxiom ax
-
--- | tyThingParent_maybe x returns (Just p)
--- when pprTyThingInContext should print a declaration for p
--- (albeit with some "..." in it) when asked to show x
--- It returns the *immediate* parent. So a datacon returns its tycon
--- but the tycon could be the associated type of a class, so it in turn
--- might have a parent.
-tyThingParent_maybe :: TyThing -> Maybe TyThing
-tyThingParent_maybe (AConLike cl) = case cl of
- RealDataCon dc -> Just (ATyCon (dataConTyCon dc))
- PatSynCon{} -> Nothing
-tyThingParent_maybe (ATyCon tc) = case tyConAssoc_maybe tc of
- Just tc -> Just (ATyCon tc)
- Nothing -> Nothing
-tyThingParent_maybe (AnId id) = case idDetails id of
- RecSelId { sel_tycon = RecSelData tc } ->
- Just (ATyCon tc)
- ClassOpId cls ->
- Just (ATyCon (classTyCon cls))
- _other -> Nothing
-tyThingParent_maybe _other = Nothing
-
-tyThingsTyCoVars :: [TyThing] -> TyCoVarSet
-tyThingsTyCoVars tts =
- unionVarSets $ map ttToVarSet tts
- where
- ttToVarSet (AnId id) = tyCoVarsOfType $ idType id
- ttToVarSet (AConLike cl) = case cl of
- RealDataCon dc -> tyCoVarsOfType $ dataConRepType dc
- PatSynCon{} -> emptyVarSet
- ttToVarSet (ATyCon tc)
- = case tyConClass_maybe tc of
- Just cls -> (mkVarSet . fst . classTvsFds) cls
- Nothing -> tyCoVarsOfType $ tyConKind tc
- ttToVarSet (ACoAxiom _) = emptyVarSet
-
--- | The Names that a TyThing should bring into scope. Used to build
--- the GlobalRdrEnv for the InteractiveContext.
-tyThingAvailInfo :: TyThing -> [AvailInfo]
-tyThingAvailInfo (ATyCon t)
- = case tyConClass_maybe t of
- Just c -> [AvailTC n (n : map getName (classMethods c)
- ++ map getName (classATs c))
- [] ]
- where n = getName c
- Nothing -> [AvailTC n (n : map getName dcs) flds]
- where n = getName t
- dcs = tyConDataCons t
- flds = tyConFieldLabels t
-tyThingAvailInfo (AConLike (PatSynCon p))
- = map avail ((getName p) : map flSelector (patSynFieldLabels p))
-tyThingAvailInfo t
- = [avail (getName t)]
-
-{-
-************************************************************************
-* *
- TypeEnv
-* *
-************************************************************************
--}
-
--- | A map from 'Name's to 'TyThing's, constructed by typechecking
--- local declarations or interface files
-type TypeEnv = NameEnv TyThing
-
-emptyTypeEnv :: TypeEnv
-typeEnvElts :: TypeEnv -> [TyThing]
-typeEnvTyCons :: TypeEnv -> [TyCon]
-typeEnvCoAxioms :: TypeEnv -> [CoAxiom Branched]
-typeEnvIds :: TypeEnv -> [Id]
-typeEnvPatSyns :: TypeEnv -> [PatSyn]
-typeEnvDataCons :: TypeEnv -> [DataCon]
-typeEnvClasses :: TypeEnv -> [Class]
-lookupTypeEnv :: TypeEnv -> Name -> Maybe TyThing
-
-emptyTypeEnv = emptyNameEnv
-typeEnvElts env = nameEnvElts env
-typeEnvTyCons env = [tc | ATyCon tc <- typeEnvElts env]
-typeEnvCoAxioms env = [ax | ACoAxiom ax <- typeEnvElts env]
-typeEnvIds env = [id | AnId id <- typeEnvElts env]
-typeEnvPatSyns env = [ps | AConLike (PatSynCon ps) <- typeEnvElts env]
-typeEnvDataCons env = [dc | AConLike (RealDataCon dc) <- typeEnvElts env]
-typeEnvClasses env = [cl | tc <- typeEnvTyCons env,
- Just cl <- [tyConClass_maybe tc]]
-
-mkTypeEnv :: [TyThing] -> TypeEnv
-mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
-
-mkTypeEnvWithImplicits :: [TyThing] -> TypeEnv
-mkTypeEnvWithImplicits things =
- mkTypeEnv things
- `plusNameEnv`
- mkTypeEnv (concatMap implicitTyThings things)
-
-typeEnvFromEntities :: [Id] -> [TyCon] -> [FamInst] -> TypeEnv
-typeEnvFromEntities ids tcs famInsts =
- mkTypeEnv ( map AnId ids
- ++ map ATyCon all_tcs
- ++ concatMap implicitTyConThings all_tcs
- ++ map (ACoAxiom . toBranchedAxiom . famInstAxiom) famInsts
- )
- where
- all_tcs = tcs ++ famInstsRepTyCons famInsts
-
-lookupTypeEnv = lookupNameEnv
-
--- Extend the type environment
-extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
-extendTypeEnv env thing = extendNameEnv env (getName thing) thing
-
-extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
-extendTypeEnvList env things = foldl' extendTypeEnv env things
-
-extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
-extendTypeEnvWithIds env ids
- = extendNameEnvList env [(getName id, AnId id) | id <- ids]
-
-plusTypeEnv :: TypeEnv -> TypeEnv -> TypeEnv
-plusTypeEnv env1 env2 = plusNameEnv env1 env2
-
--- | Find the 'TyThing' for the given 'Name' by using all the resources
--- at our disposal: the compiled modules in the 'HomePackageTable' and the
--- compiled modules in other packages that live in 'PackageTypeEnv'. Note
--- that this does NOT look up the 'TyThing' in the module being compiled: you
--- have to do that yourself, if desired
-lookupType :: HscEnv -> Name -> IO (Maybe TyThing)
-lookupType hsc_env name = do
- eps <- liftIO $ readIORef (hsc_EPS hsc_env)
- let pte = eps_PTE eps
- hpt = hsc_HPT hsc_env
-
- mod = ASSERT2( isExternalName name, ppr name )
- if isHoleName name
- then mkHomeModule (hsc_home_unit hsc_env) (moduleName (nameModule name))
- else nameModule name
-
- !ty = if isOneShot (ghcMode (hsc_dflags hsc_env))
- -- in one-shot, we don't use the HPT
- then lookupNameEnv pte name
- else case lookupHptByModule hpt mod of
- Just hm -> lookupNameEnv (md_types (hm_details hm)) name
- Nothing -> lookupNameEnv pte name
- pure ty
-
--- | Get the 'TyCon' from a 'TyThing' if it is a type constructor thing. Panics otherwise
-tyThingTyCon :: HasDebugCallStack => TyThing -> TyCon
-tyThingTyCon (ATyCon tc) = tc
-tyThingTyCon other = pprPanic "tyThingTyCon" (ppr other)
-
--- | Get the 'CoAxiom' from a 'TyThing' if it is a coercion axiom thing. Panics otherwise
-tyThingCoAxiom :: HasDebugCallStack => TyThing -> CoAxiom Branched
-tyThingCoAxiom (ACoAxiom ax) = ax
-tyThingCoAxiom other = pprPanic "tyThingCoAxiom" (ppr other)
-
--- | Get the 'DataCon' from a 'TyThing' if it is a data constructor thing. Panics otherwise
-tyThingDataCon :: HasDebugCallStack => TyThing -> DataCon
-tyThingDataCon (AConLike (RealDataCon dc)) = dc
-tyThingDataCon other = pprPanic "tyThingDataCon" (ppr other)
-
--- | Get the 'ConLike' from a 'TyThing' if it is a data constructor thing.
--- Panics otherwise
-tyThingConLike :: HasDebugCallStack => TyThing -> ConLike
-tyThingConLike (AConLike dc) = dc
-tyThingConLike other = pprPanic "tyThingConLike" (ppr other)
-
--- | Get the 'Id' from a 'TyThing' if it is a id *or* data constructor thing. Panics otherwise
-tyThingId :: HasDebugCallStack => TyThing -> Id
-tyThingId (AnId id) = id
-tyThingId (AConLike (RealDataCon dc)) = dataConWrapId dc
-tyThingId other = pprPanic "tyThingId" (ppr other)
-
-{-
-************************************************************************
-* *
-\subsection{MonadThings and friends}
-* *
-************************************************************************
--}
-
--- | Class that abstracts out the common ability of the monads in GHC
--- to lookup a 'TyThing' in the monadic environment by 'Name'. Provides
--- a number of related convenience functions for accessing particular
--- kinds of 'TyThing'
-class Monad m => MonadThings m where
- lookupThing :: Name -> m TyThing
-
- lookupId :: Name -> m Id
- lookupId = liftM tyThingId . lookupThing
-
- lookupDataCon :: Name -> m DataCon
- lookupDataCon = liftM tyThingDataCon . lookupThing
-
- lookupTyCon :: Name -> m TyCon
- lookupTyCon = liftM tyThingTyCon . lookupThing
-
--- Instance used in GHC.HsToCore.Quote
-instance MonadThings m => MonadThings (ReaderT s m) where
- lookupThing = lift . lookupThing
-
-{-
-************************************************************************
-* *
-\subsection{Auxiliary types}
-* *
-************************************************************************
-
-These types are defined here because they are mentioned in ModDetails,
-but they are mostly elaborated elsewhere
--}
-
------------------- Warnings -------------------------
--- | Warning information for a module
-data Warnings
- = NoWarnings -- ^ Nothing deprecated
- | WarnAll WarningTxt -- ^ Whole module deprecated
- | WarnSome [(OccName,WarningTxt)] -- ^ Some specific things deprecated
-
- -- Only an OccName is needed because
- -- (1) a deprecation always applies to a binding
- -- defined in the module in which the deprecation appears.
- -- (2) deprecations are only reported outside the defining module.
- -- this is important because, otherwise, if we saw something like
- --
- -- {-# DEPRECATED f "" #-}
- -- f = ...
- -- h = f
- -- g = let f = undefined in f
- --
- -- we'd need more information than an OccName to know to say something
- -- about the use of f in h but not the use of the locally bound f in g
- --
- -- however, because we only report about deprecations from the outside,
- -- and a module can only export one value called f,
- -- an OccName suffices.
- --
- -- this is in contrast with fixity declarations, where we need to map
- -- a Name to its fixity declaration.
- deriving( Eq )
-
-instance Binary Warnings where
- put_ bh NoWarnings = putByte bh 0
- put_ bh (WarnAll t) = do
- putByte bh 1
- put_ bh t
- put_ bh (WarnSome ts) = do
- putByte bh 2
- put_ bh ts
-
- get bh = do
- h <- getByte bh
- case h of
- 0 -> return NoWarnings
- 1 -> do aa <- get bh
- return (WarnAll aa)
- _ -> do aa <- get bh
- return (WarnSome aa)
-
--- | Constructs the cache for the 'mi_warn_fn' field of a 'ModIface'
-mkIfaceWarnCache :: Warnings -> OccName -> Maybe WarningTxt
-mkIfaceWarnCache NoWarnings = \_ -> Nothing
-mkIfaceWarnCache (WarnAll t) = \_ -> Just t
-mkIfaceWarnCache (WarnSome pairs) = lookupOccEnv (mkOccEnv pairs)
-
-emptyIfaceWarnCache :: OccName -> Maybe WarningTxt
-emptyIfaceWarnCache _ = Nothing
-
-plusWarns :: Warnings -> Warnings -> Warnings
-plusWarns d NoWarnings = d
-plusWarns NoWarnings d = d
-plusWarns _ (WarnAll t) = WarnAll t
-plusWarns (WarnAll t) _ = WarnAll t
-plusWarns (WarnSome v1) (WarnSome v2) = WarnSome (v1 ++ v2)
-
--- | Creates cached lookup for the 'mi_fix_fn' field of 'ModIface'
-mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Maybe Fixity
-mkIfaceFixCache pairs
- = \n -> lookupOccEnv env n
- where
- env = mkOccEnv pairs
-
-emptyIfaceFixCache :: OccName -> Maybe Fixity
-emptyIfaceFixCache _ = Nothing
-
--- | Fixity environment mapping names to their fixities
-type FixityEnv = NameEnv FixItem
-
--- | Fixity information for an 'Name'. We keep the OccName in the range
--- so that we can generate an interface from it
-data FixItem = FixItem OccName Fixity
-
-instance Outputable FixItem where
- ppr (FixItem occ fix) = ppr fix <+> ppr occ
-
-emptyFixityEnv :: FixityEnv
-emptyFixityEnv = emptyNameEnv
-
-lookupFixity :: FixityEnv -> Name -> Fixity
-lookupFixity env n = case lookupNameEnv env n of
- Just (FixItem _ fix) -> fix
- Nothing -> defaultFixity
-
-{-
-************************************************************************
-* *
-\subsection{WhatsImported}
-* *
-************************************************************************
--}
-
--- | Records whether a module has orphans. An \"orphan\" is one of:
---
--- * An instance declaration in a module other than the definition
--- module for one of the type constructors or classes in the instance head
---
--- * A rewrite rule in a module other than the one defining
--- the function in the head of the rule
---
-type WhetherHasOrphans = Bool
-
--- | Does this module define family instances?
-type WhetherHasFamInst = Bool
-
--- | Dependency information about ALL modules and packages below this one
--- in the import hierarchy.
---
--- Invariant: the dependencies of a module @M@ never includes @M@.
---
--- Invariant: none of the lists contain duplicates.
-data Dependencies
- = Deps { dep_mods :: [ModuleNameWithIsBoot]
- -- ^ All home-package modules transitively below this one
- -- I.e. modules that this one imports, or that are in the
- -- dep_mods of those directly-imported modules
-
- , dep_pkgs :: [(UnitId, Bool)]
- -- ^ All packages transitively below this module
- -- I.e. packages to which this module's direct imports belong,
- -- or that are in the dep_pkgs of those modules
- -- The bool indicates if the package is required to be
- -- trusted when the module is imported as a safe import
- -- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names
-
- , dep_orphs :: [Module]
- -- ^ Transitive closure of orphan modules (whether
- -- home or external pkg).
- --
- -- (Possible optimization: don't include family
- -- instance orphans as they are anyway included in
- -- 'dep_finsts'. But then be careful about code
- -- which relies on dep_orphs having the complete list!)
- -- This does NOT include us, unlike 'imp_orphs'.
-
- , dep_finsts :: [Module]
- -- ^ Transitive closure of depended upon modules which
- -- contain family instances (whether home or external).
- -- This is used by 'checkFamInstConsistency'. This
- -- does NOT include us, unlike 'imp_finsts'. See Note
- -- [The type family instance consistency story].
-
- , dep_plgins :: [ModuleName]
- -- ^ All the plugins used while compiling this module.
- }
- deriving( Eq )
- -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints
- -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies.
-
-instance Binary Dependencies where
- put_ bh deps = do put_ bh (dep_mods deps)
- put_ bh (dep_pkgs deps)
- put_ bh (dep_orphs deps)
- put_ bh (dep_finsts deps)
- put_ bh (dep_plgins deps)
-
- get bh = do ms <- get bh
- ps <- get bh
- os <- get bh
- fis <- get bh
- pl <- get bh
- return (Deps { dep_mods = ms, dep_pkgs = ps, dep_orphs = os,
- dep_finsts = fis, dep_plgins = pl })
-
-noDependencies :: Dependencies
-noDependencies = Deps [] [] [] [] []
-
--- | Records modules for which changes may force recompilation of this module
--- See wiki: https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/recompilation-avoidance
---
--- This differs from Dependencies. A module X may be in the dep_mods of this
--- module (via an import chain) but if we don't use anything from X it won't
--- appear in our Usage
-data Usage
- -- | Module from another package
- = UsagePackageModule {
- usg_mod :: Module,
- -- ^ External package module depended on
- usg_mod_hash :: Fingerprint,
- -- ^ Cached module fingerprint
- usg_safe :: IsSafeImport
- -- ^ Was this module imported as a safe import
- }
- -- | Module from the current package
- | UsageHomeModule {
- usg_mod_name :: ModuleName,
- -- ^ Name of the module
- usg_mod_hash :: Fingerprint,
- -- ^ Cached module fingerprint
- usg_entities :: [(OccName,Fingerprint)],
- -- ^ Entities we depend on, sorted by occurrence name and fingerprinted.
- -- NB: usages are for parent names only, e.g. type constructors
- -- but not the associated data constructors.
- usg_exports :: Maybe Fingerprint,
- -- ^ Fingerprint for the export list of this module,
- -- if we directly imported it (and hence we depend on its export list)
- usg_safe :: IsSafeImport
- -- ^ Was this module imported as a safe import
- } -- ^ Module from the current package
- -- | A file upon which the module depends, e.g. a CPP #include, or using TH's
- -- 'addDependentFile'
- | UsageFile {
- usg_file_path :: FilePath,
- -- ^ External file dependency. From a CPP #include or TH
- -- addDependentFile. Should be absolute.
- usg_file_hash :: Fingerprint
- -- ^ 'Fingerprint' of the file contents.
-
- -- Note: We don't consider things like modification timestamps
- -- here, because there's no reason to recompile if the actual
- -- contents don't change. This previously lead to odd
- -- recompilation behaviors; see #8114
- }
- -- | A requirement which was merged into this one.
- | UsageMergedRequirement {
- usg_mod :: Module,
- usg_mod_hash :: Fingerprint
- }
- deriving( Eq )
- -- The export list field is (Just v) if we depend on the export list:
- -- i.e. we imported the module directly, whether or not we
- -- enumerated the things we imported, or just imported
- -- everything
- -- We need to recompile if M's exports change, because
- -- if the import was import M, we might now have a name clash
- -- in the importing module.
- -- if the import was import M(x) M might no longer export x
- -- The only way we don't depend on the export list is if we have
- -- import M()
- -- And of course, for modules that aren't imported directly we don't
- -- depend on their export lists
-
-instance Binary Usage where
- put_ bh usg@UsagePackageModule{} = do
- putByte bh 0
- put_ bh (usg_mod usg)
- put_ bh (usg_mod_hash usg)
- put_ bh (usg_safe usg)
-
- put_ bh usg@UsageHomeModule{} = do
- putByte bh 1
- put_ bh (usg_mod_name usg)
- put_ bh (usg_mod_hash usg)
- put_ bh (usg_exports usg)
- put_ bh (usg_entities usg)
- put_ bh (usg_safe usg)
-
- put_ bh usg@UsageFile{} = do
- putByte bh 2
- put_ bh (usg_file_path usg)
- put_ bh (usg_file_hash usg)
-
- put_ bh usg@UsageMergedRequirement{} = do
- putByte bh 3
- put_ bh (usg_mod usg)
- put_ bh (usg_mod_hash usg)
-
- get bh = do
- h <- getByte bh
- case h of
- 0 -> do
- nm <- get bh
- mod <- get bh
- safe <- get bh
- return UsagePackageModule { usg_mod = nm, usg_mod_hash = mod, usg_safe = safe }
- 1 -> do
- nm <- get bh
- mod <- get bh
- exps <- get bh
- ents <- get bh
- safe <- get bh
- return UsageHomeModule { usg_mod_name = nm, usg_mod_hash = mod,
- usg_exports = exps, usg_entities = ents, usg_safe = safe }
- 2 -> do
- fp <- get bh
- hash <- get bh
- return UsageFile { usg_file_path = fp, usg_file_hash = hash }
- 3 -> do
- mod <- get bh
- hash <- get bh
- return UsageMergedRequirement { usg_mod = mod, usg_mod_hash = hash }
- i -> error ("Binary.get(Usage): " ++ show i)
-
-{-
-************************************************************************
-* *
- The External Package State
-* *
-************************************************************************
--}
-
-type PackageTypeEnv = TypeEnv
-type PackageRuleBase = RuleBase
-type PackageInstEnv = InstEnv
-type PackageFamInstEnv = FamInstEnv
-type PackageAnnEnv = AnnEnv
-type PackageCompleteMatches = CompleteMatches
-
--- | Information about other packages that we have slurped in by reading
--- their interface files
-data ExternalPackageState
- = EPS {
- eps_is_boot :: !(ModuleNameEnv ModuleNameWithIsBoot),
- -- ^ In OneShot mode (only), home-package modules
- -- accumulate in the external package state, and are
- -- sucked in lazily. For these home-pkg modules
- -- (only) we need to record which are boot modules.
- -- We set this field after loading all the
- -- explicitly-imported interfaces, but before doing
- -- anything else
- --
- -- The 'ModuleName' part is not necessary, but it's useful for
- -- debug prints, and it's convenient because this field comes
- -- direct from 'GHC.Tc.Utils.imp_dep_mods'
-
- eps_PIT :: !PackageIfaceTable,
- -- ^ The 'ModIface's for modules in external packages
- -- whose interfaces we have opened.
- -- The declarations in these interface files are held in the
- -- 'eps_decls', 'eps_inst_env', 'eps_fam_inst_env' and 'eps_rules'
- -- fields of this record, not in the 'mi_decls' fields of the
- -- interface we have sucked in.
- --
- -- What /is/ in the PIT is:
- --
- -- * The Module
- --
- -- * Fingerprint info
- --
- -- * Its exports
- --
- -- * Fixities
- --
- -- * Deprecations and warnings
-
- eps_free_holes :: InstalledModuleEnv (UniqDSet ModuleName),
- -- ^ Cache for 'mi_free_holes'. Ordinarily, we can rely on
- -- the 'eps_PIT' for this information, EXCEPT that when
- -- we do dependency analysis, we need to look at the
- -- 'Dependencies' of our imports to determine what their
- -- precise free holes are ('moduleFreeHolesPrecise'). We
- -- don't want to repeatedly reread in the interface
- -- for every import, so cache it here. When the PIT
- -- gets filled in we can drop these entries.
-
- eps_PTE :: !PackageTypeEnv,
- -- ^ Result of typechecking all the external package
- -- interface files we have sucked in. The domain of
- -- the mapping is external-package modules
-
- eps_inst_env :: !PackageInstEnv, -- ^ The total 'InstEnv' accumulated
- -- from all the external-package modules
- eps_fam_inst_env :: !PackageFamInstEnv,-- ^ The total 'FamInstEnv' accumulated
- -- from all the external-package modules
- eps_rule_base :: !PackageRuleBase, -- ^ The total 'RuleEnv' accumulated
- -- from all the external-package modules
- eps_ann_env :: !PackageAnnEnv, -- ^ The total 'AnnEnv' accumulated
- -- from all the external-package modules
- eps_complete_matches :: !PackageCompleteMatches,
- -- ^ The total 'CompleteMatches' accumulated
- -- from all the external-package modules
-
- eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv), -- ^ The family instances accumulated from external
- -- packages, keyed off the module that declared them
-
- eps_stats :: !EpsStats -- ^ Stastics about what was loaded from external packages
- }
-
--- | Accumulated statistics about what we are putting into the 'ExternalPackageState'.
--- \"In\" means stuff that is just /read/ from interface files,
--- \"Out\" means actually sucked in and type-checked
-data EpsStats = EpsStats { n_ifaces_in
- , n_decls_in, n_decls_out
- , n_rules_in, n_rules_out
- , n_insts_in, n_insts_out :: !Int }
-
-addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
--- ^ Add stats for one newly-read interface
-addEpsInStats stats n_decls n_insts n_rules
- = stats { n_ifaces_in = n_ifaces_in stats + 1
- , n_decls_in = n_decls_in stats + n_decls
- , n_insts_in = n_insts_in stats + n_insts
- , n_rules_in = n_rules_in stats + n_rules }
-
-{-
-Names in a NameCache are always stored as a Global, and have the SrcLoc
-of their binding locations.
-
-Actually that's not quite right. When we first encounter the original
-name, we might not be at its binding site (e.g. we are reading an
-interface file); so we give it 'noSrcLoc' then. Later, when we find
-its binding site, we fix it up.
--}
-
-updNameCache :: IORef NameCache
- -> (NameCache -> (NameCache, c)) -- The updating function
- -> IO c
-updNameCache ncRef upd_fn
- = atomicModifyIORef' ncRef upd_fn
-
-mkSOName :: Platform -> FilePath -> FilePath
-mkSOName platform root
- = case platformOS platform of
- OSMinGW32 -> root <.> soExt platform
- _ -> ("lib" ++ root) <.> soExt platform
-
-mkHsSOName :: Platform -> FilePath -> FilePath
-mkHsSOName platform root = ("lib" ++ root) <.> soExt platform
-
-soExt :: Platform -> FilePath
-soExt platform
- = case platformOS platform of
- OSDarwin -> "dylib"
- OSMinGW32 -> "dll"
- _ -> "so"
-
-{-
-************************************************************************
-* *
- The module graph and ModSummary type
- A ModSummary is a node in the compilation manager's
- dependency graph, and it's also passed to hscMain
-* *
-************************************************************************
--}
-
--- | A ModuleGraph contains all the nodes from the home package (only).
--- There will be a node for each source module, plus a node for each hi-boot
--- module.
---
--- The graph is not necessarily stored in topologically-sorted order. Use
--- 'GHC.topSortModuleGraph' and 'GHC.Data.Graph.Directed.flattenSCC' to achieve this.
-data ModuleGraph = ModuleGraph
- { mg_mss :: [ModSummary]
- , mg_non_boot :: ModuleEnv ModSummary
- -- a map of all non-boot ModSummaries keyed by Modules
- , mg_boot :: ModuleSet
- -- a set of boot Modules
- , mg_needs_th_or_qq :: !Bool
- -- does any of the modules in mg_mss require TemplateHaskell or
- -- QuasiQuotes?
- }
-
--- | Determines whether a set of modules requires Template Haskell or
--- Quasi Quotes
---
--- Note that if the session's 'DynFlags' enabled Template Haskell when
--- 'depanal' was called, then each module in the returned module graph will
--- have Template Haskell enabled whether it is actually needed or not.
-needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
-needsTemplateHaskellOrQQ mg = mg_needs_th_or_qq mg
-
--- | Map a function 'f' over all the 'ModSummaries'.
--- To preserve invariants 'f' can't change the isBoot status.
-mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
-mapMG f mg@ModuleGraph{..} = mg
- { mg_mss = map f mg_mss
- , mg_non_boot = mapModuleEnv f mg_non_boot
- }
-
-mgBootModules :: ModuleGraph -> ModuleSet
-mgBootModules ModuleGraph{..} = mg_boot
-
-mgModSummaries :: ModuleGraph -> [ModSummary]
-mgModSummaries = mg_mss
-
-mgElemModule :: ModuleGraph -> Module -> Bool
-mgElemModule ModuleGraph{..} m = elemModuleEnv m mg_non_boot
-
--- | Look up a ModSummary in the ModuleGraph
-mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
-mgLookupModule ModuleGraph{..} m = lookupModuleEnv mg_non_boot m
-
-emptyMG :: ModuleGraph
-emptyMG = ModuleGraph [] emptyModuleEnv emptyModuleSet False
-
-isTemplateHaskellOrQQNonBoot :: ModSummary -> Bool
-isTemplateHaskellOrQQNonBoot ms =
- (xopt LangExt.TemplateHaskell (ms_hspp_opts ms)
- || xopt LangExt.QuasiQuotes (ms_hspp_opts ms)) &&
- (isBootSummary ms == NotBoot)
-
--- | Add a ModSummary to ModuleGraph. Assumes that the new ModSummary is
--- not an element of the ModuleGraph.
-extendMG :: ModuleGraph -> ModSummary -> ModuleGraph
-extendMG ModuleGraph{..} ms = ModuleGraph
- { mg_mss = ms:mg_mss
- , mg_non_boot = case isBootSummary ms of
- IsBoot -> mg_non_boot
- NotBoot -> extendModuleEnv mg_non_boot (ms_mod ms) ms
- , mg_boot = case isBootSummary ms of
- NotBoot -> mg_boot
- IsBoot -> extendModuleSet mg_boot (ms_mod ms)
- , mg_needs_th_or_qq = mg_needs_th_or_qq || isTemplateHaskellOrQQNonBoot ms
- }
-
-mkModuleGraph :: [ModSummary] -> ModuleGraph
-mkModuleGraph = foldr (flip extendMG) emptyMG
-
--- | A single node in a 'ModuleGraph'. The nodes of the module graph
--- are one of:
---
--- * A regular Haskell source module
--- * A hi-boot source module
---
-data ModSummary
- = ModSummary {
- ms_mod :: Module,
- -- ^ Identity of the module
- ms_hsc_src :: HscSource,
- -- ^ The module source either plain Haskell or hs-boot
- ms_location :: ModLocation,
- -- ^ Location of the various files belonging to the module
- ms_hs_date :: UTCTime,
- -- ^ Timestamp of source file
- ms_obj_date :: Maybe UTCTime,
- -- ^ Timestamp of object, if we have one
- ms_iface_date :: Maybe UTCTime,
- -- ^ Timestamp of hi file, if we *only* are typechecking (it is
- -- 'Nothing' otherwise.
- -- See Note [Recompilation checking in -fno-code mode] and #9243
- ms_hie_date :: Maybe UTCTime,
- -- ^ Timestamp of hie file, if we have one
- ms_srcimps :: [(Maybe FastString, Located ModuleName)],
- -- ^ Source imports of the module
- ms_textual_imps :: [(Maybe FastString, Located ModuleName)],
- -- ^ Non-source imports of the module from the module *text*
- ms_parsed_mod :: Maybe HsParsedModule,
- -- ^ The parsed, nonrenamed source, if we have it. This is also
- -- used to support "inline module syntax" in Backpack files.
- ms_hspp_file :: FilePath,
- -- ^ Filename of preprocessed source file
- ms_hspp_opts :: DynFlags,
- -- ^ Cached flags from @OPTIONS@, @INCLUDE@ and @LANGUAGE@
- -- pragmas in the modules source code
- ms_hspp_buf :: Maybe StringBuffer
- -- ^ The actual preprocessed source, if we have it
- }
-
-ms_installed_mod :: ModSummary -> InstalledModule
-ms_installed_mod = fst . getModuleInstantiation . ms_mod
-
-ms_mod_name :: ModSummary -> ModuleName
-ms_mod_name = moduleName . ms_mod
-
-ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
-ms_imps ms =
- ms_textual_imps ms ++
- map mk_additional_import (dynFlagDependencies (ms_hspp_opts ms))
- where
- mk_additional_import mod_nm = (Nothing, noLoc mod_nm)
-
-home_imps :: [(Maybe FastString, Located ModuleName)] -> [Located ModuleName]
-home_imps imps = [ lmodname | (mb_pkg, lmodname) <- imps,
- isLocal mb_pkg ]
- 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)
-
--- | Like 'ms_home_imps', but for SOURCE imports.
-ms_home_srcimps :: ModSummary -> [Located ModuleName]
-ms_home_srcimps = home_imps . ms_srcimps
-
--- | All of the (possibly) home module imports from a
--- 'ModSummary'; that is to say, each of these module names
--- could be a home import if an appropriately named file
--- existed. (This is in contrast to package qualified
--- imports, which are guaranteed not to be home imports.)
-ms_home_imps :: ModSummary -> [Located ModuleName]
-ms_home_imps = home_imps . ms_imps
-
--- The ModLocation contains both the original source filename and the
--- filename of the cleaned-up source file after all preprocessing has been
--- done. The point is that the summariser will have to cpp/unlit/whatever
--- all files anyway, and there's no point in doing this twice -- just
--- park the result in a temp file, put the name of it in the location,
--- and let @compile@ read from that file on the way back up.
-
--- The ModLocation is stable over successive up-sweeps in GHCi, wheres
--- the ms_hs_date and imports can, of course, change
-
-msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
-msHsFilePath ms = expectJust "msHsFilePath" (ml_hs_file (ms_location ms))
-msHiFilePath ms = ml_hi_file (ms_location ms)
-msObjFilePath ms = ml_obj_file (ms_location ms)
-
-msDynObjFilePath :: ModSummary -> DynFlags -> FilePath
-msDynObjFilePath ms dflags = dynamicOutputFile dflags (msObjFilePath ms)
-
--- | Did this 'ModSummary' originate from a hs-boot file?
-isBootSummary :: ModSummary -> IsBootInterface
-isBootSummary ms = if ms_hsc_src ms == HsBootFile then IsBoot else NotBoot
-
-instance Outputable ModSummary where
- ppr ms
- = sep [text "ModSummary {",
- nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
- text "ms_mod =" <+> ppr (ms_mod ms)
- <> text (hscSourceString (ms_hsc_src ms)) <> comma,
- text "ms_textual_imps =" <+> ppr (ms_textual_imps ms),
- text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
- char '}'
- ]
-
-showModMsg :: DynFlags -> Bool -> ModSummary -> SDoc
-showModMsg dflags recomp mod_summary =
- if gopt Opt_HideSourcePaths dflags
- then text mod_str
- else hsep $
- [ text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' ')
- , char '('
- , text (op $ msHsFilePath mod_summary) <> char ','
- ] ++
- if gopt Opt_BuildDynamicToo dflags
- then [ text obj_file <> char ','
- , text dyn_file
- , char ')'
- ]
- else [ text obj_file, char ')' ]
- where
- op = normalise
- mod = moduleName (ms_mod mod_summary)
- mod_str = showPpr dflags mod ++ hscSourceString (ms_hsc_src mod_summary)
- dyn_file = op $ msDynObjFilePath mod_summary dflags
- obj_file = case backend dflags of
- Interpreter | recomp -> "interpreted"
- NoBackend -> "nothing"
- _ -> (op $ msObjFilePath mod_summary)
-
-{-
-************************************************************************
-* *
-\subsection{Recompilation}
-* *
-************************************************************************
--}
-
--- | Indicates whether a given module's source has been modified since it
--- was last compiled.
-data SourceModified
- = SourceModified
- -- ^ the source has been modified
- | SourceUnmodified
- -- ^ the source has not been modified. Compilation may or may
- -- not be necessary, depending on whether any dependencies have
- -- changed since we last compiled.
- | SourceUnmodifiedAndStable
- -- ^ the source has not been modified, and furthermore all of
- -- its (transitive) dependencies are up to date; it definitely
- -- does not need to be recompiled. This is important for two
- -- reasons: (a) we can omit the version check in checkOldIface,
- -- and (b) if the module used TH splices we don't need to force
- -- recompilation.
-
-{-
-************************************************************************
-* *
-\subsection{Hpc Support}
-* *
-************************************************************************
--}
-
--- | Information about a modules use of Haskell Program Coverage
-data HpcInfo
- = HpcInfo
- { hpcInfoTickCount :: Int
- , hpcInfoHash :: Int
- }
- | NoHpcInfo
- { hpcUsed :: AnyHpcUsage -- ^ Is hpc used anywhere on the module \*tree\*?
- }
-
--- | This is used to signal if one of my imports used HPC instrumentation
--- even if there is no module-local HPC usage
-type AnyHpcUsage = Bool
-
-emptyHpcInfo :: AnyHpcUsage -> HpcInfo
-emptyHpcInfo = NoHpcInfo
-
--- | Find out if HPC is used by this module or any of the modules
--- it depends upon
-isHpcUsed :: HpcInfo -> AnyHpcUsage
-isHpcUsed (HpcInfo {}) = True
-isHpcUsed (NoHpcInfo { hpcUsed = used }) = used
-
-{-
-************************************************************************
-* *
-\subsection{Safe Haskell Support}
-* *
-************************************************************************
-
-This stuff here is related to supporting the Safe Haskell extension,
-primarily about storing under what trust type a module has been compiled.
--}
-
--- | Is an import a safe import?
-type IsSafeImport = Bool
-
--- | Safe Haskell information for 'ModIface'
--- Simply a wrapper around SafeHaskellMode to sepperate iface and flags
-newtype IfaceTrustInfo = TrustInfo SafeHaskellMode
-
-getSafeMode :: IfaceTrustInfo -> SafeHaskellMode
-getSafeMode (TrustInfo x) = x
-
-setSafeMode :: SafeHaskellMode -> IfaceTrustInfo
-setSafeMode = TrustInfo
-
-noIfaceTrustInfo :: IfaceTrustInfo
-noIfaceTrustInfo = setSafeMode Sf_None
-
-trustInfoToNum :: IfaceTrustInfo -> Word8
-trustInfoToNum it
- = case getSafeMode it of
- Sf_None -> 0
- Sf_Unsafe -> 1
- Sf_Trustworthy -> 2
- Sf_Safe -> 3
- Sf_SafeInferred -> 4
- Sf_Ignore -> 0
-
-numToTrustInfo :: Word8 -> IfaceTrustInfo
-numToTrustInfo 0 = setSafeMode Sf_None
-numToTrustInfo 1 = setSafeMode Sf_Unsafe
-numToTrustInfo 2 = setSafeMode Sf_Trustworthy
-numToTrustInfo 3 = setSafeMode Sf_Safe
-numToTrustInfo 4 = setSafeMode Sf_SafeInferred
-numToTrustInfo n = error $ "numToTrustInfo: bad input number! (" ++ show n ++ ")"
-
-instance Outputable IfaceTrustInfo where
- ppr (TrustInfo Sf_None) = text "none"
- ppr (TrustInfo Sf_Ignore) = text "none"
- ppr (TrustInfo Sf_Unsafe) = text "unsafe"
- ppr (TrustInfo Sf_Trustworthy) = text "trustworthy"
- ppr (TrustInfo Sf_Safe) = text "safe"
- ppr (TrustInfo Sf_SafeInferred) = text "safe-inferred"
-
-instance Binary IfaceTrustInfo where
- put_ bh iftrust = putByte bh $ trustInfoToNum iftrust
- get bh = getByte bh >>= (return . numToTrustInfo)
-
-{-
-************************************************************************
-* *
-\subsection{Parser result}
-* *
-************************************************************************
--}
-
-data HsParsedModule = HsParsedModule {
- hpm_module :: Located HsModule,
- hpm_src_files :: [FilePath],
- -- ^ extra source files (e.g. from #includes). The lexer collects
- -- these from '# <file> <line>' pragmas, which the C preprocessor
- -- leaves behind. These files and their timestamps are stored in
- -- the .hi file, so that we can force recompilation if any of
- -- them change (#3589)
- hpm_annotations :: ApiAnns
- -- See note [Api annotations] in GHC.Parser.Annotation
- }
-
-{-
-************************************************************************
-* *
-\subsection{Linkable stuff}
-* *
-************************************************************************
-
-This stuff is in here, rather than (say) in "GHC.Runtime.Linker", because the "GHC.Runtime.Linker"
-stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
--}
-
-isObjectLinkable :: Linkable -> Bool
-isObjectLinkable l = not (null unlinked) && all isObject unlinked
- where unlinked = linkableUnlinked l
- -- A linkable with no Unlinked's is treated as a BCO. We can
- -- generate a linkable with no Unlinked's as a result of
- -- compiling a module in NoBackend mode, and this choice
- -- happens to work well with checkStability in module GHC.
-
-linkableObjs :: Linkable -> [FilePath]
-linkableObjs l = [ f | DotO f <- linkableUnlinked l ]
-
--------------------------------------------
-
--- | Is this an actual file on disk we can link in somehow?
-isObject :: Unlinked -> Bool
-isObject (DotO _) = True
-isObject (DotA _) = True
-isObject (DotDLL _) = True
-isObject _ = False
-
--- | Is this a bytecode linkable with no file on disk?
-isInterpretable :: Unlinked -> Bool
-isInterpretable = not . isObject
-
--- | Retrieve the filename of the linkable if possible. Panic if it is a byte-code object
-nameOfObject :: Unlinked -> FilePath
-nameOfObject (DotO fn) = fn
-nameOfObject (DotA fn) = fn
-nameOfObject (DotDLL fn) = fn
-nameOfObject other = pprPanic "nameOfObject" (ppr other)
-
--- | Retrieve the compiled byte-code if possible. Panic if it is a file-based linkable
-byteCodeOfObject :: Unlinked -> CompiledByteCode
-byteCodeOfObject (BCOs bc _) = bc
-byteCodeOfObject other = pprPanic "byteCodeOfObject" (ppr other)
-
-
--------------------------------------------
-
-type ConLikeSet = UniqDSet ConLike
-
--- | A list of conlikes which represents a complete pattern match.
--- These arise from @COMPLETE@ signatures.
--- See also Note [Implementation of COMPLETE pragmas].
-type CompleteMatch = ConLikeSet
-
-type CompleteMatches = [CompleteMatch]
-
--- | Foreign language of the phase if the phase deals with a foreign code
-phaseForeignLanguage :: Phase -> Maybe ForeignSrcLang
-phaseForeignLanguage phase = case phase of
- Phase.Cc -> Just LangC
- Phase.Ccxx -> Just LangCxx
- Phase.Cobjc -> Just LangObjc
- Phase.Cobjcxx -> Just LangObjcxx
- Phase.HCc -> Just LangC
- Phase.As _ -> Just LangAsm
- Phase.MergeForeign -> Just RawObject
- _ -> Nothing
-
--------------------------------------------
-
--- Take care, this instance only forces to the degree necessary to
--- avoid major space leaks.
-instance (NFData (IfaceBackendExts (phase :: ModIfacePhase)), NFData (IfaceDeclExts (phase :: ModIfacePhase))) => NFData (ModIface_ phase) where
- rnf (ModIface f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 f12
- f13 f14 f15 f16 f17 f18 f19 f20 f21 f22 f23 f24) =
- rnf f1 `seq` rnf f2 `seq` f3 `seq` f4 `seq` f5 `seq` f6 `seq` rnf f7 `seq` f8 `seq`
- f9 `seq` rnf f10 `seq` rnf f11 `seq` f12 `seq` rnf f13 `seq` rnf f14 `seq` rnf f15 `seq`
- rnf f16 `seq` f17 `seq` rnf f18 `seq` rnf f19 `seq` f20 `seq` f21 `seq` f22 `seq` rnf f23
- `seq` rnf f24
-
-{-
-************************************************************************
-* *
-\subsection{Extensible Iface Fields}
-* *
-************************************************************************
--}
-
-type FieldName = String
-
-newtype ExtensibleFields = ExtensibleFields { getExtensibleFields :: (Map FieldName BinData) }
-
-instance Binary ExtensibleFields where
- put_ bh (ExtensibleFields fs) = do
- put_ bh (Map.size fs :: Int)
-
- -- Put the names of each field, and reserve a space
- -- for a payload pointer after each name:
- header_entries <- forM (Map.toList fs) $ \(name, dat) -> do
- put_ bh name
- field_p_p <- tellBin bh
- put_ bh field_p_p
- return (field_p_p, dat)
-
- -- Now put the payloads and use the reserved space
- -- to point to the start of each payload:
- forM_ header_entries $ \(field_p_p, dat) -> do
- field_p <- tellBin bh
- putAt bh field_p_p field_p
- seekBin bh field_p
- put_ bh dat
-
- get bh = do
- n <- get bh :: IO Int
-
- -- Get the names and field pointers:
- header_entries <- replicateM n $ do
- (,) <$> get bh <*> get bh
-
- -- Seek to and get each field's payload:
- fields <- forM header_entries $ \(name, field_p) -> do
- seekBin bh field_p
- dat <- get bh
- return (name, dat)
-
- return . ExtensibleFields . Map.fromList $ fields
-
-instance NFData ExtensibleFields where
- rnf (ExtensibleFields fs) = rnf fs
-
-emptyExtensibleFields :: ExtensibleFields
-emptyExtensibleFields = ExtensibleFields Map.empty
-
---------------------------------------------------------------------------------
--- | Reading
-
-readIfaceField :: Binary a => FieldName -> ModIface -> IO (Maybe a)
-readIfaceField name = readIfaceFieldWith name get
-
-readField :: Binary a => FieldName -> ExtensibleFields -> IO (Maybe a)
-readField name = readFieldWith name get
-
-readIfaceFieldWith :: FieldName -> (BinHandle -> IO a) -> ModIface -> IO (Maybe a)
-readIfaceFieldWith name read iface = readFieldWith name read (mi_ext_fields iface)
-
-readFieldWith :: FieldName -> (BinHandle -> IO a) -> ExtensibleFields -> IO (Maybe a)
-readFieldWith name read fields = sequence $ ((read =<<) . dataHandle) <$>
- Map.lookup name (getExtensibleFields fields)
-
---------------------------------------------------------------------------------
--- | Writing
-
-writeIfaceField :: Binary a => FieldName -> a -> ModIface -> IO ModIface
-writeIfaceField name x = writeIfaceFieldWith name (`put_` x)
-
-writeField :: Binary a => FieldName -> a -> ExtensibleFields -> IO ExtensibleFields
-writeField name x = writeFieldWith name (`put_` x)
-
-writeIfaceFieldWith :: FieldName -> (BinHandle -> IO ()) -> ModIface -> IO ModIface
-writeIfaceFieldWith name write iface = do
- fields <- writeFieldWith name write (mi_ext_fields iface)
- return iface{ mi_ext_fields = fields }
-
-writeFieldWith :: FieldName -> (BinHandle -> IO ()) -> ExtensibleFields -> IO ExtensibleFields
-writeFieldWith name write fields = do
- bh <- openBinMem (1024 * 1024)
- write bh
- --
- bd <- handleData bh
- return $ ExtensibleFields (Map.insert name bd $ getExtensibleFields fields)
-
-deleteField :: FieldName -> ExtensibleFields -> ExtensibleFields
-deleteField name (ExtensibleFields fs) = ExtensibleFields $ Map.delete name fs
-
-deleteIfaceField :: FieldName -> ModIface -> ModIface
-deleteIfaceField name iface = iface { mi_ext_fields = deleteField name (mi_ext_fields iface) }