1{-
2(c) The University of Glasgow, 2006
3
4\section[HscTypes]{Types for the per-module compiler}
5-}
6
7{-# LANGUAGE CPP, ScopedTypeVariables #-}
8{-# LANGUAGE DeriveFunctor #-}
9{-# LANGUAGE RecordWildCards #-}
10{-# LANGUAGE ViewPatterns #-}
11{-# LANGUAGE TypeFamilies #-}
12{-# LANGUAGE TypeSynonymInstances #-}
13{-# LANGUAGE FlexibleInstances #-}
14{-# LANGUAGE FlexibleContexts #-}
15{-# LANGUAGE UndecidableInstances #-}
16{-# LANGUAGE DataKinds #-}
17
18-- | Types for the per-module compiler
19module HscTypes (
20        -- * compilation state
21        HscEnv(..), hscEPS,
22        FinderCache, FindResult(..), InstalledFindResult(..),
23        Target(..), TargetId(..), InputFileBuffer, pprTarget, pprTargetId,
24        HscStatus(..),
25        IServ(..),
26
27        -- * ModuleGraph
28        ModuleGraph, emptyMG, mkModuleGraph, extendMG, mapMG,
29        mgModSummaries, mgElemModule, mgLookupModule,
30        needsTemplateHaskellOrQQ, mgBootModules,
31
32        -- * Hsc monad
33        Hsc(..), runHsc, mkInteractiveHscEnv, runInteractiveHsc,
34
35        -- * Information about modules
36        ModDetails(..), emptyModDetails,
37        ModGuts(..), CgGuts(..), ForeignStubs(..), appendStubC,
38        ImportedMods, ImportedBy(..), importedByUser, ImportedModsVal(..), SptEntry(..),
39        ForeignSrcLang(..),
40        phaseForeignLanguage,
41
42        ModSummary(..), ms_imps, ms_installed_mod, ms_mod_name, ms_home_imps,
43        home_imps, ms_home_allimps, ms_home_srcimps, showModMsg, isBootSummary,
44        msHsFilePath, msHiFilePath, msObjFilePath,
45        SourceModified(..), isTemplateHaskellOrQQNonBoot,
46
47        -- * Information about the module being compiled
48        -- (re-exported from DriverPhases)
49        HscSource(..), isHsBootOrSig, isHsigFile, hscSourceString,
50
51
52        -- * State relating to modules in this package
53        HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
54        lookupHpt, eltsHpt, filterHpt, allHpt, mapHpt, delFromHpt,
55        addToHpt, addListToHpt, lookupHptDirectly, listToHpt,
56        hptCompleteSigs,
57        hptInstances, hptRules, pprHPT,
58
59        -- * State relating to known packages
60        ExternalPackageState(..), EpsStats(..), addEpsInStats,
61        PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
62        lookupIfaceByModule, emptyPartialModIface, emptyFullModIface, lookupHptByModule,
63
64        PackageInstEnv, PackageFamInstEnv, PackageRuleBase,
65        PackageCompleteMatchMap,
66
67        mkSOName, mkHsSOName, soExt,
68
69        -- * Metaprogramming
70        MetaRequest(..),
71        MetaResult, -- data constructors not exported to ensure correct response type
72        metaRequestE, metaRequestP, metaRequestT, metaRequestD, metaRequestAW,
73        MetaHook,
74
75        -- * Annotations
76        prepareAnnotations,
77
78        -- * Interactive context
79        InteractiveContext(..), emptyInteractiveContext,
80        icPrintUnqual, icInScopeTTs, icExtendGblRdrEnv,
81        extendInteractiveContext, extendInteractiveContextWithIds,
82        substInteractiveContext,
83        setInteractivePrintName, icInteractiveModule,
84        InteractiveImport(..), setInteractivePackage,
85        mkPrintUnqualified, pprModulePrefix,
86        mkQualPackage, mkQualModule, pkgQual,
87
88        -- * Interfaces
89        ModIface, PartialModIface, ModIface_(..), ModIfaceBackend(..),
90        mkIfaceWarnCache, mkIfaceHashCache, mkIfaceFixCache,
91        emptyIfaceWarnCache, mi_boot, mi_fix,
92        mi_semantic_module,
93        mi_free_holes,
94        renameFreeHoles,
95
96        -- * Fixity
97        FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
98
99        -- * TyThings and type environments
100        TyThing(..),  tyThingAvailInfo,
101        tyThingTyCon, tyThingDataCon, tyThingConLike,
102        tyThingId, tyThingCoAxiom, tyThingParent_maybe, tyThingsTyCoVars,
103        implicitTyThings, implicitTyConThings, implicitClassThings,
104        isImplicitTyThing,
105
106        TypeEnv, lookupType, lookupTypeHscEnv, mkTypeEnv, emptyTypeEnv,
107        typeEnvFromEntities, mkTypeEnvWithImplicits,
108        extendTypeEnv, extendTypeEnvList,
109        extendTypeEnvWithIds, plusTypeEnv,
110        lookupTypeEnv,
111        typeEnvElts, typeEnvTyCons, typeEnvIds, typeEnvPatSyns,
112        typeEnvDataCons, typeEnvCoAxioms, typeEnvClasses,
113
114        -- * MonadThings
115        MonadThings(..),
116
117        -- * Information on imports and exports
118        WhetherHasOrphans, IsBootInterface, Usage(..),
119        Dependencies(..), noDependencies,
120        updNameCache,
121        IfaceExport,
122
123        -- * Warnings
124        Warnings(..), WarningTxt(..), plusWarns,
125
126        -- * Linker stuff
127        Linkable(..), isObjectLinkable, linkableObjs,
128        Unlinked(..), CompiledByteCode,
129        isObject, nameOfObject, isInterpretable, byteCodeOfObject,
130
131        -- * Program coverage
132        HpcInfo(..), emptyHpcInfo, isHpcUsed, AnyHpcUsage,
133
134        -- * Breakpoints
135        ModBreaks (..), emptyModBreaks,
136
137        -- * Safe Haskell information
138        IfaceTrustInfo, getSafeMode, setSafeMode, noIfaceTrustInfo,
139        trustInfoToNum, numToTrustInfo, IsSafeImport,
140
141        -- * result of the parser
142        HsParsedModule(..),
143
144        -- * Compilation errors and warnings
145        SourceError, GhcApiError, mkSrcErr, srcErrorMessages, mkApiErr,
146        throwOneError, throwErrors, handleSourceError,
147        handleFlagWarnings, printOrThrowWarnings,
148
149        -- * COMPLETE signature
150        CompleteMatch(..), CompleteMatchMap,
151        mkCompleteMatchMap, extendCompleteMatchMap
152    ) where
153
154#include "HsVersions.h"
155
156import GhcPrelude
157
158import ByteCodeTypes
159import InteractiveEvalTypes ( Resume )
160import GHCi.Message         ( Pipe )
161import GHCi.RemoteTypes
162import GHC.ForeignSrcLang
163
164import UniqFM
165import GHC.Hs
166import RdrName
167import Avail
168import Module
169import InstEnv          ( InstEnv, ClsInst, identicalClsInstHead )
170import FamInstEnv
171import CoreSyn          ( CoreProgram, RuleBase, CoreRule )
172import Name
173import NameEnv
174import VarSet
175import Var
176import Id
177import IdInfo           ( IdDetails(..), RecSelParent(..))
178import Type
179
180import ApiAnnotation    ( ApiAnns )
181import Annotations      ( Annotation, AnnEnv, mkAnnEnv, plusAnnEnv )
182import Class
183import TyCon
184import CoAxiom
185import ConLike
186import DataCon
187import PatSyn
188import PrelNames        ( gHC_PRIM, ioTyConName, printName, mkInteractiveModule )
189import TysWiredIn
190import Packages hiding  ( Version(..) )
191import CmdLineParser
192import DynFlags
193import LinkerTypes      ( DynLinker, Linkable(..), Unlinked(..), SptEntry(..) )
194import DriverPhases     ( Phase, HscSource(..), hscSourceString
195                        , isHsBootOrSig, isHsigFile )
196import qualified DriverPhases as Phase
197import BasicTypes
198import IfaceSyn
199import Maybes
200import Outputable
201import SrcLoc
202import Unique
203import UniqDFM
204import FastString
205import StringBuffer     ( StringBuffer )
206import Fingerprint
207import MonadUtils
208import Bag
209import Binary
210import ErrUtils
211import NameCache
212import GHC.Platform
213import Util
214import UniqDSet
215import GHC.Serialized   ( Serialized )
216import qualified GHC.LanguageExtensions as LangExt
217
218import Foreign
219import Control.Monad    ( guard, liftM, ap )
220import Data.IORef
221import Data.Time
222import Exception
223import System.FilePath
224import Control.Concurrent
225import System.Process   ( ProcessHandle )
226import Control.DeepSeq
227
228-- -----------------------------------------------------------------------------
229-- Compilation state
230-- -----------------------------------------------------------------------------
231
232-- | Status of a compilation to hard-code
233data HscStatus
234    -- | Nothing to do.
235    = HscNotGeneratingCode ModIface
236    -- | Nothing to do because code already exists.
237    | HscUpToDate ModIface
238    -- | Update boot file result.
239    | HscUpdateBoot ModIface
240    -- | Generate signature file (backpack)
241    | HscUpdateSig ModIface
242    -- | Recompile this module.
243    | HscRecomp
244        { hscs_guts       :: CgGuts
245          -- ^ Information for the code generator.
246        , hscs_mod_location :: !ModLocation
247          -- ^ Module info
248        , hscs_partial_iface  :: !PartialModIface
249          -- ^ Partial interface
250        , hscs_old_iface_hash :: !(Maybe Fingerprint)
251          -- ^ Old interface hash for this compilation, if an old interface file
252          -- exists. Pass to `hscMaybeWriteIface` when writing the interface to
253          -- avoid updating the existing interface when the interface isn't
254          -- changed.
255        , hscs_iface_dflags :: !DynFlags
256          -- ^ Generate final iface using this DynFlags.
257          -- FIXME (osa): I don't understand why this is necessary, but I spent
258          -- almost two days trying to figure this out and I couldn't .. perhaps
259          -- someone who understands this code better will remove this later.
260        }
261-- Should HscStatus contain the HomeModInfo?
262-- All places where we return a status we also return a HomeModInfo.
263
264-- -----------------------------------------------------------------------------
265-- The Hsc monad: Passing an environment and warning state
266
267newtype Hsc a = Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages))
268    deriving (Functor)
269
270instance Applicative Hsc where
271    pure a = Hsc $ \_ w -> return (a, w)
272    (<*>) = ap
273
274instance Monad Hsc where
275    Hsc m >>= k = Hsc $ \e w -> do (a, w1) <- m e w
276                                   case k a of
277                                       Hsc k' -> k' e w1
278
279instance MonadIO Hsc where
280    liftIO io = Hsc $ \_ w -> do a <- io; return (a, w)
281
282instance HasDynFlags Hsc where
283    getDynFlags = Hsc $ \e w -> return (hsc_dflags e, w)
284
285runHsc :: HscEnv -> Hsc a -> IO a
286runHsc hsc_env (Hsc hsc) = do
287    (a, w) <- hsc hsc_env emptyBag
288    printOrThrowWarnings (hsc_dflags hsc_env) w
289    return a
290
291mkInteractiveHscEnv :: HscEnv -> HscEnv
292mkInteractiveHscEnv hsc_env = hsc_env{ hsc_dflags = interactive_dflags }
293  where
294    interactive_dflags = ic_dflags (hsc_IC hsc_env)
295
296runInteractiveHsc :: HscEnv -> Hsc a -> IO a
297-- A variant of runHsc that switches in the DynFlags from the
298-- InteractiveContext before running the Hsc computation.
299runInteractiveHsc hsc_env = runHsc (mkInteractiveHscEnv hsc_env)
300
301-- -----------------------------------------------------------------------------
302-- Source Errors
303
304-- When the compiler (HscMain) discovers errors, it throws an
305-- exception in the IO monad.
306
307mkSrcErr :: ErrorMessages -> SourceError
308mkSrcErr = SourceError
309
310srcErrorMessages :: SourceError -> ErrorMessages
311srcErrorMessages (SourceError msgs) = msgs
312
313mkApiErr :: DynFlags -> SDoc -> GhcApiError
314mkApiErr dflags msg = GhcApiError (showSDoc dflags msg)
315
316throwErrors :: MonadIO io => ErrorMessages -> io a
317throwErrors = liftIO . throwIO . mkSrcErr
318
319throwOneError :: MonadIO io => ErrMsg -> io a
320throwOneError = throwErrors . unitBag
321
322-- | A source error is an error that is caused by one or more errors in the
323-- source code.  A 'SourceError' is thrown by many functions in the
324-- compilation pipeline.  Inside GHC these errors are merely printed via
325-- 'log_action', but API clients may treat them differently, for example,
326-- insert them into a list box.  If you want the default behaviour, use the
327-- idiom:
328--
329-- > handleSourceError printExceptionAndWarnings $ do
330-- >   ... api calls that may fail ...
331--
332-- The 'SourceError's error messages can be accessed via 'srcErrorMessages'.
333-- This list may be empty if the compiler failed due to @-Werror@
334-- ('Opt_WarnIsError').
335--
336-- See 'printExceptionAndWarnings' for more information on what to take care
337-- of when writing a custom error handler.
338newtype SourceError = SourceError ErrorMessages
339
340instance Show SourceError where
341  show (SourceError msgs) = unlines . map show . bagToList $ msgs
342
343instance Exception SourceError
344
345-- | Perform the given action and call the exception handler if the action
346-- throws a 'SourceError'.  See 'SourceError' for more information.
347handleSourceError :: (ExceptionMonad m) =>
348                     (SourceError -> m a) -- ^ exception handler
349                  -> m a -- ^ action to perform
350                  -> m a
351handleSourceError handler act =
352  gcatch act (\(e :: SourceError) -> handler e)
353
354-- | An error thrown if the GHC API is used in an incorrect fashion.
355newtype GhcApiError = GhcApiError String
356
357instance Show GhcApiError where
358  show (GhcApiError msg) = msg
359
360instance Exception GhcApiError
361
362-- | Given a bag of warnings, turn them into an exception if
363-- -Werror is enabled, or print them out otherwise.
364printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO ()
365printOrThrowWarnings dflags warns = do
366  let (make_error, warns') =
367        mapAccumBagL
368          (\make_err warn ->
369            case isWarnMsgFatal dflags warn of
370              Nothing ->
371                (make_err, warn)
372              Just err_reason ->
373                (True, warn{ errMsgSeverity = SevError
374                           , errMsgReason = ErrReason err_reason
375                           }))
376          False warns
377  if make_error
378    then throwIO (mkSrcErr warns')
379    else printBagOfErrors dflags warns
380
381handleFlagWarnings :: DynFlags -> [Warn] -> IO ()
382handleFlagWarnings dflags warns = do
383  let warns' = filter (shouldPrintWarning dflags . warnReason)  warns
384
385      -- It would be nicer if warns :: [Located MsgDoc], but that
386      -- has circular import problems.
387      bag = listToBag [ mkPlainWarnMsg dflags loc (text warn)
388                      | Warn _ (dL->L loc warn) <- warns' ]
389
390  printOrThrowWarnings dflags bag
391
392-- Given a warn reason, check to see if it's associated -W opt is enabled
393shouldPrintWarning :: DynFlags -> CmdLineParser.WarnReason -> Bool
394shouldPrintWarning dflags ReasonDeprecatedFlag
395  = wopt Opt_WarnDeprecatedFlags dflags
396shouldPrintWarning dflags ReasonUnrecognisedFlag
397  = wopt Opt_WarnUnrecognisedWarningFlags dflags
398shouldPrintWarning _ _
399  = True
400
401{-
402************************************************************************
403*                                                                      *
404\subsection{HscEnv}
405*                                                                      *
406************************************************************************
407-}
408
409-- | HscEnv is like 'Session', except that some of the fields are immutable.
410-- An HscEnv is used to compile a single module from plain Haskell source
411-- code (after preprocessing) to either C, assembly or C--. It's also used
412-- to store the dynamic linker state to allow for multiple linkers in the
413-- same address space.
414-- Things like the module graph don't change during a single compilation.
415--
416-- Historical note: \"hsc\" used to be the name of the compiler binary,
417-- when there was a separate driver and compiler.  To compile a single
418-- module, the driver would invoke hsc on the source code... so nowadays
419-- we think of hsc as the layer of the compiler that deals with compiling
420-- a single module.
421data HscEnv
422  = HscEnv {
423        hsc_dflags :: DynFlags,
424                -- ^ The dynamic flag settings
425
426        hsc_targets :: [Target],
427                -- ^ The targets (or roots) of the current session
428
429        hsc_mod_graph :: ModuleGraph,
430                -- ^ The module graph of the current session
431
432        hsc_IC :: InteractiveContext,
433                -- ^ The context for evaluating interactive statements
434
435        hsc_HPT    :: HomePackageTable,
436                -- ^ The home package table describes already-compiled
437                -- home-package modules, /excluding/ the module we
438                -- are compiling right now.
439                -- (In one-shot mode the current module is the only
440                -- home-package module, so hsc_HPT is empty.  All other
441                -- modules count as \"external-package\" modules.
442                -- However, even in GHCi mode, hi-boot interfaces are
443                -- demand-loaded into the external-package table.)
444                --
445                -- 'hsc_HPT' is not mutable because we only demand-load
446                -- external packages; the home package is eagerly
447                -- loaded, module by module, by the compilation manager.
448                --
449                -- The HPT may contain modules compiled earlier by @--make@
450                -- but not actually below the current module in the dependency
451                -- graph.
452                --
453                -- (This changes a previous invariant: changed Jan 05.)
454
455        hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
456                -- ^ Information about the currently loaded external packages.
457                -- This is mutable because packages will be demand-loaded during
458                -- a compilation run as required.
459
460        hsc_NC  :: {-# UNPACK #-} !(IORef NameCache),
461                -- ^ As with 'hsc_EPS', this is side-effected by compiling to
462                -- reflect sucking in interface files.  They cache the state of
463                -- external interface files, in effect.
464
465        hsc_FC   :: {-# UNPACK #-} !(IORef FinderCache),
466                -- ^ The cached result of performing finding in the file system
467
468        hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
469                -- ^ Used for one-shot compilation only, to initialise
470                -- the 'IfGblEnv'. See 'TcRnTypes.tcg_type_env_var' for
471                -- 'TcRnTypes.TcGblEnv'.  See also Note [hsc_type_env_var hack]
472
473        , hsc_iserv :: MVar (Maybe IServ)
474                -- ^ interactive server process.  Created the first
475                -- time it is needed.
476
477        , hsc_dynLinker :: DynLinker
478                -- ^ dynamic linker.
479
480 }
481
482-- Note [hsc_type_env_var hack]
483-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
484-- hsc_type_env_var is used to initialize tcg_type_env_var, and
485-- eventually it is the mutable variable that is queried from
486-- if_rec_types to get a TypeEnv.  So, clearly, it's something
487-- related to knot-tying (see Note [Tying the knot]).
488-- hsc_type_env_var is used in two places: initTcRn (where
489-- it initializes tcg_type_env_var) and initIfaceCheck
490-- (where it initializes if_rec_types).
491--
492-- But why do we need a way to feed a mutable variable in?  Why
493-- can't we just initialize tcg_type_env_var when we start
494-- typechecking?  The problem is we need to knot-tie the
495-- EPS, and we may start adding things to the EPS before type
496-- checking starts.
497--
498-- Here is a concrete example. Suppose we are running
499-- "ghc -c A.hs", and we have this file system state:
500--
501--  A.hs-boot   A.hi-boot **up to date**
502--  B.hs        B.hi      **up to date**
503--  A.hs        A.hi      **stale**
504--
505-- The first thing we do is run checkOldIface on A.hi.
506-- checkOldIface will call loadInterface on B.hi so it can
507-- get its hands on the fingerprints, to find out if A.hi
508-- needs recompilation.  But loadInterface also populates
509-- the EPS!  And so if compilation turns out to be necessary,
510-- as it is in this case, the thunks we put into the EPS for
511-- B.hi need to have the correct if_rec_types mutable variable
512-- to query.
513--
514-- If the mutable variable is only allocated WHEN we start
515-- typechecking, then that's too late: we can't get the
516-- information to the thunks.  So we need to pre-commit
517-- to a type variable in 'hscIncrementalCompile' BEFORE we
518-- check the old interface.
519--
520-- This is all a massive hack because arguably checkOldIface
521-- should not populate the EPS. But that's a refactor for
522-- another day.
523
524
525data IServ = IServ
526  { iservPipe :: Pipe
527  , iservProcess :: ProcessHandle
528  , iservLookupSymbolCache :: IORef (UniqFM (Ptr ()))
529  , iservPendingFrees :: [HValueRef]
530  }
531
532-- | Retrieve the ExternalPackageState cache.
533hscEPS :: HscEnv -> IO ExternalPackageState
534hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
535
536-- | A compilation target.
537--
538-- A target may be supplied with the actual text of the
539-- module.  If so, use this instead of the file contents (this
540-- is for use in an IDE where the file hasn't been saved by
541-- the user yet).
542data Target
543  = Target {
544      targetId           :: TargetId, -- ^ module or filename
545      targetAllowObjCode :: Bool,     -- ^ object code allowed?
546      targetContents     :: Maybe (InputFileBuffer, UTCTime)
547      -- ^ Optional in-memory buffer containing the source code GHC should
548      -- use for this target instead of reading it from disk.
549      --
550      -- Since GHC version 8.10 modules which require preprocessors such as
551      -- Literate Haskell or CPP to run are also supported.
552      --
553      -- If a corresponding source file does not exist on disk this will
554      -- result in a 'SourceError' exception if @targetId = TargetModule _@
555      -- is used. However together with @targetId = TargetFile _@ GHC will
556      -- not complain about the file missing.
557    }
558
559data TargetId
560  = TargetModule ModuleName
561        -- ^ A module name: search for the file
562  | TargetFile FilePath (Maybe Phase)
563        -- ^ A filename: preprocess & parse it to find the module name.
564        -- If specified, the Phase indicates how to compile this file
565        -- (which phase to start from).  Nothing indicates the starting phase
566        -- should be determined from the suffix of the filename.
567  deriving Eq
568
569type InputFileBuffer = StringBuffer
570
571pprTarget :: Target -> SDoc
572pprTarget (Target id obj _) =
573    (if obj then char '*' else empty) <> pprTargetId id
574
575instance Outputable Target where
576    ppr = pprTarget
577
578pprTargetId :: TargetId -> SDoc
579pprTargetId (TargetModule m) = ppr m
580pprTargetId (TargetFile f _) = text f
581
582instance Outputable TargetId where
583    ppr = pprTargetId
584
585{-
586************************************************************************
587*                                                                      *
588\subsection{Package and Module Tables}
589*                                                                      *
590************************************************************************
591-}
592
593-- | Helps us find information about modules in the home package
594type HomePackageTable  = DModuleNameEnv HomeModInfo
595        -- Domain = modules in the home package that have been fully compiled
596        -- "home" unit id cached here for convenience
597
598-- | Helps us find information about modules in the imported packages
599type PackageIfaceTable = ModuleEnv ModIface
600        -- Domain = modules in the imported packages
601
602-- | Constructs an empty HomePackageTable
603emptyHomePackageTable :: HomePackageTable
604emptyHomePackageTable  = emptyUDFM
605
606-- | Constructs an empty PackageIfaceTable
607emptyPackageIfaceTable :: PackageIfaceTable
608emptyPackageIfaceTable = emptyModuleEnv
609
610pprHPT :: HomePackageTable -> SDoc
611-- A bit arbitrary for now
612pprHPT hpt = pprUDFM hpt $ \hms ->
613    vcat [ hang (ppr (mi_module (hm_iface hm)))
614              2 (ppr (md_types (hm_details hm)))
615         | hm <- hms ]
616
617lookupHpt :: HomePackageTable -> ModuleName -> Maybe HomeModInfo
618lookupHpt = lookupUDFM
619
620lookupHptDirectly :: HomePackageTable -> Unique -> Maybe HomeModInfo
621lookupHptDirectly = lookupUDFM_Directly
622
623eltsHpt :: HomePackageTable -> [HomeModInfo]
624eltsHpt = eltsUDFM
625
626filterHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> HomePackageTable
627filterHpt = filterUDFM
628
629allHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> Bool
630allHpt = allUDFM
631
632mapHpt :: (HomeModInfo -> HomeModInfo) -> HomePackageTable -> HomePackageTable
633mapHpt = mapUDFM
634
635delFromHpt :: HomePackageTable -> ModuleName -> HomePackageTable
636delFromHpt = delFromUDFM
637
638addToHpt :: HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable
639addToHpt = addToUDFM
640
641addListToHpt
642  :: HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable
643addListToHpt = addListToUDFM
644
645listToHpt :: [(ModuleName, HomeModInfo)] -> HomePackageTable
646listToHpt = listToUDFM
647
648lookupHptByModule :: HomePackageTable -> Module -> Maybe HomeModInfo
649-- The HPT is indexed by ModuleName, not Module,
650-- we must check for a hit on the right Module
651lookupHptByModule hpt mod
652  = case lookupHpt hpt (moduleName mod) of
653      Just hm | mi_module (hm_iface hm) == mod -> Just hm
654      _otherwise                               -> Nothing
655
656-- | Information about modules in the package being compiled
657data HomeModInfo
658  = HomeModInfo {
659      hm_iface    :: !ModIface,
660        -- ^ The basic loaded interface file: every loaded module has one of
661        -- these, even if it is imported from another package
662      hm_details  :: !ModDetails,
663        -- ^ Extra information that has been created from the 'ModIface' for
664        -- the module, typically during typechecking
665      hm_linkable :: !(Maybe Linkable)
666        -- ^ The actual artifact we would like to link to access things in
667        -- this module.
668        --
669        -- 'hm_linkable' might be Nothing:
670        --
671        --   1. If this is an .hs-boot module
672        --
673        --   2. Temporarily during compilation if we pruned away
674        --      the old linkable because it was out of date.
675        --
676        -- After a complete compilation ('GHC.load'), all 'hm_linkable' fields
677        -- in the 'HomePackageTable' will be @Just@.
678        --
679        -- When re-linking a module ('HscMain.HscNoRecomp'), we construct the
680        -- 'HomeModInfo' by building a new 'ModDetails' from the old
681        -- 'ModIface' (only).
682    }
683
684-- | Find the 'ModIface' for a 'Module', searching in both the loaded home
685-- and external package module information
686lookupIfaceByModule
687        :: HomePackageTable
688        -> PackageIfaceTable
689        -> Module
690        -> Maybe ModIface
691lookupIfaceByModule hpt pit mod
692  = case lookupHptByModule hpt mod of
693       Just hm -> Just (hm_iface hm)
694       Nothing -> lookupModuleEnv pit mod
695
696-- If the module does come from the home package, why do we look in the PIT as well?
697-- (a) In OneShot mode, even home-package modules accumulate in the PIT
698-- (b) Even in Batch (--make) mode, there is *one* case where a home-package
699--     module is in the PIT, namely GHC.Prim when compiling the base package.
700-- We could eliminate (b) if we wanted, by making GHC.Prim belong to a package
701-- of its own, but it doesn't seem worth the bother.
702
703hptCompleteSigs :: HscEnv -> [CompleteMatch]
704hptCompleteSigs = hptAllThings  (md_complete_sigs . hm_details)
705
706-- | Find all the instance declarations (of classes and families) from
707-- the Home Package Table filtered by the provided predicate function.
708-- Used in @tcRnImports@, to select the instances that are in the
709-- transitive closure of imports from the currently compiled module.
710hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst])
711hptInstances hsc_env want_this_module
712  = let (insts, famInsts) = unzip $ flip hptAllThings hsc_env $ \mod_info -> do
713                guard (want_this_module (moduleName (mi_module (hm_iface mod_info))))
714                let details = hm_details mod_info
715                return (md_insts details, md_fam_insts details)
716    in (concat insts, concat famInsts)
717
718-- | Get rules from modules "below" this one (in the dependency sense)
719hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
720hptRules = hptSomeThingsBelowUs (md_rules . hm_details) False
721
722
723-- | Get annotations from modules "below" this one (in the dependency sense)
724hptAnns :: HscEnv -> Maybe [(ModuleName, IsBootInterface)] -> [Annotation]
725hptAnns hsc_env (Just deps) = hptSomeThingsBelowUs (md_anns . hm_details) False hsc_env deps
726hptAnns hsc_env Nothing = hptAllThings (md_anns . hm_details) hsc_env
727
728hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
729hptAllThings extract hsc_env = concatMap extract (eltsHpt (hsc_HPT hsc_env))
730
731-- | Get things from modules "below" this one (in the dependency sense)
732-- C.f Inst.hptInstances
733hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> [(ModuleName, IsBootInterface)] -> [a]
734hptSomeThingsBelowUs extract include_hi_boot hsc_env deps
735  | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
736
737  | otherwise
738  = let hpt = hsc_HPT hsc_env
739    in
740    [ thing
741    |   -- Find each non-hi-boot module below me
742      (mod, is_boot_mod) <- deps
743    , include_hi_boot || not is_boot_mod
744
745        -- unsavoury: when compiling the base package with --make, we
746        -- sometimes try to look up RULES etc for GHC.Prim. GHC.Prim won't
747        -- be in the HPT, because we never compile it; it's in the EPT
748        -- instead. ToDo: clean up, and remove this slightly bogus filter:
749    , mod /= moduleName gHC_PRIM
750
751        -- Look it up in the HPT
752    , let things = case lookupHpt hpt mod of
753                    Just info -> extract info
754                    Nothing -> pprTrace "WARNING in hptSomeThingsBelowUs" msg []
755          msg = vcat [text "missing module" <+> ppr mod,
756                      text "Probable cause: out-of-date interface files"]
757                        -- This really shouldn't happen, but see #962
758
759        -- And get its dfuns
760    , thing <- things ]
761
762
763{-
764************************************************************************
765*                                                                      *
766\subsection{Metaprogramming}
767*                                                                      *
768************************************************************************
769-}
770
771-- | The supported metaprogramming result types
772data MetaRequest
773  = MetaE  (LHsExpr GhcPs   -> MetaResult)
774  | MetaP  (LPat GhcPs      -> MetaResult)
775  | MetaT  (LHsType GhcPs   -> MetaResult)
776  | MetaD  ([LHsDecl GhcPs] -> MetaResult)
777  | MetaAW (Serialized     -> MetaResult)
778
779-- | data constructors not exported to ensure correct result type
780data MetaResult
781  = MetaResE  { unMetaResE  :: LHsExpr GhcPs   }
782  | MetaResP  { unMetaResP  :: LPat GhcPs      }
783  | MetaResT  { unMetaResT  :: LHsType GhcPs   }
784  | MetaResD  { unMetaResD  :: [LHsDecl GhcPs] }
785  | MetaResAW { unMetaResAW :: Serialized        }
786
787type MetaHook f = MetaRequest -> LHsExpr GhcTc -> f MetaResult
788
789metaRequestE :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsExpr GhcPs)
790metaRequestE h = fmap unMetaResE . h (MetaE MetaResE)
791
792metaRequestP :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LPat GhcPs)
793metaRequestP h = fmap unMetaResP . h (MetaP MetaResP)
794
795metaRequestT :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsType GhcPs)
796metaRequestT h = fmap unMetaResT . h (MetaT MetaResT)
797
798metaRequestD :: Functor f => MetaHook f -> LHsExpr GhcTc -> f [LHsDecl GhcPs]
799metaRequestD h = fmap unMetaResD . h (MetaD MetaResD)
800
801metaRequestAW :: Functor f => MetaHook f -> LHsExpr GhcTc -> f Serialized
802metaRequestAW h = fmap unMetaResAW . h (MetaAW MetaResAW)
803
804{-
805************************************************************************
806*                                                                      *
807\subsection{Dealing with Annotations}
808*                                                                      *
809************************************************************************
810-}
811
812-- | Deal with gathering annotations in from all possible places
813--   and combining them into a single 'AnnEnv'
814prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
815prepareAnnotations hsc_env mb_guts = do
816    eps <- hscEPS hsc_env
817    let -- Extract annotations from the module being compiled if supplied one
818        mb_this_module_anns = fmap (mkAnnEnv . mg_anns) mb_guts
819        -- Extract dependencies of the module if we are supplied one,
820        -- otherwise load annotations from all home package table
821        -- entries regardless of dependency ordering.
822        home_pkg_anns  = (mkAnnEnv . hptAnns hsc_env) $ fmap (dep_mods . mg_deps) mb_guts
823        other_pkg_anns = eps_ann_env eps
824        ann_env        = foldl1' plusAnnEnv $ catMaybes [mb_this_module_anns,
825                                                         Just home_pkg_anns,
826                                                         Just other_pkg_anns]
827    return ann_env
828
829{-
830************************************************************************
831*                                                                      *
832\subsection{The Finder cache}
833*                                                                      *
834************************************************************************
835-}
836
837-- | The 'FinderCache' maps modules to the result of
838-- searching for that module. It records the results of searching for
839-- modules along the search path. On @:load@, we flush the entire
840-- contents of this cache.
841--
842type FinderCache = InstalledModuleEnv InstalledFindResult
843
844data InstalledFindResult
845  = InstalledFound ModLocation InstalledModule
846  | InstalledNoPackage InstalledUnitId
847  | InstalledNotFound [FilePath] (Maybe InstalledUnitId)
848
849-- | The result of searching for an imported module.
850--
851-- NB: FindResult manages both user source-import lookups
852-- (which can result in 'Module') as well as direct imports
853-- for interfaces (which always result in 'InstalledModule').
854data FindResult
855  = Found ModLocation Module
856        -- ^ The module was found
857  | NoPackage UnitId
858        -- ^ The requested package was not found
859  | FoundMultiple [(Module, ModuleOrigin)]
860        -- ^ _Error_: both in multiple packages
861
862        -- | Not found
863  | NotFound
864      { fr_paths       :: [FilePath]       -- Places where I looked
865
866      , fr_pkg         :: Maybe UnitId  -- Just p => module is in this package's
867                                           --           manifest, but couldn't find
868                                           --           the .hi file
869
870      , fr_mods_hidden :: [UnitId]      -- Module is in these packages,
871                                           --   but the *module* is hidden
872
873      , fr_pkgs_hidden :: [UnitId]      -- Module is in these packages,
874                                           --   but the *package* is hidden
875
876        -- Modules are in these packages, but it is unusable
877      , fr_unusables   :: [(UnitId, UnusablePackageReason)]
878
879      , fr_suggestions :: [ModuleSuggestion] -- Possible mis-spelled modules
880      }
881
882{-
883************************************************************************
884*                                                                      *
885\subsection{Symbol tables and Module details}
886*                                                                      *
887************************************************************************
888-}
889
890{- Note [Interface file stages]
891   ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
892
893Interface files have two possible stages.
894
895* A partial stage built from the result of the core pipeline.
896* A fully instantiated form. Which also includes fingerprints and
897  potentially information provided by backends.
898
899We can build a full interface file two ways:
900* Directly from a partial one:
901  Then we omit backend information and mostly compute fingerprints.
902* From a partial one + information produced by a backend.
903  Then we store the provided information and fingerprint both.
904-}
905
906type PartialModIface = ModIface_ 'ModIfaceCore
907type ModIface = ModIface_ 'ModIfaceFinal
908
909-- | Extends a PartialModIface with information which is either:
910-- * Computed after codegen
911-- * Or computed just before writing the iface to disk. (Hashes)
912-- In order to fully instantiate it.
913data ModIfaceBackend = ModIfaceBackend
914  { mi_iface_hash :: !Fingerprint
915    -- ^ Hash of the whole interface
916  , mi_mod_hash :: !Fingerprint
917    -- ^ Hash of the ABI only
918  , mi_flag_hash :: !Fingerprint
919    -- ^ Hash of the important flags used when compiling the module, excluding
920    -- optimisation flags
921  , mi_opt_hash :: !Fingerprint
922    -- ^ Hash of optimisation flags
923  , mi_hpc_hash :: !Fingerprint
924    -- ^ Hash of hpc flags
925  , mi_plugin_hash :: !Fingerprint
926    -- ^ Hash of plugins
927  , mi_orphan :: !WhetherHasOrphans
928    -- ^ Whether this module has orphans
929  , mi_finsts :: !WhetherHasFamInst
930    -- ^ Whether this module has family instances. See Note [The type family
931    -- instance consistency story].
932  , mi_exp_hash :: !Fingerprint
933    -- ^ Hash of export list
934  , mi_orphan_hash :: !Fingerprint
935    -- ^ Hash for orphan rules, class and family instances combined
936
937    -- Cached environments for easy lookup. These are computed (lazily) from
938    -- other fields and are not put into the interface file.
939    -- Not really produced by the backend but there is no need to create them
940    -- any earlier.
941  , mi_warn_fn :: !(OccName -> Maybe WarningTxt)
942    -- ^ Cached lookup for 'mi_warns'
943  , mi_fix_fn :: !(OccName -> Maybe Fixity)
944    -- ^ Cached lookup for 'mi_fixities'
945  , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
946    -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that
947    -- the thing isn't in decls. It's useful to know that when seeing if we are
948    -- up to date wrt. the old interface. The 'OccName' is the parent of the
949    -- name, if it has one.
950  }
951
952data ModIfacePhase
953  = ModIfaceCore
954  -- ^ Partial interface built based on output of core pipeline.
955  | ModIfaceFinal
956
957-- | Selects a IfaceDecl representation.
958-- For fully instantiated interfaces we also maintain
959-- a fingerprint, which is used for recompilation checks.
960type family IfaceDeclExts (phase :: ModIfacePhase) where
961  IfaceDeclExts 'ModIfaceCore = IfaceDecl
962  IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl)
963
964type family IfaceBackendExts (phase :: ModIfacePhase) where
965  IfaceBackendExts 'ModIfaceCore = ()
966  IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend
967
968
969
970-- | A 'ModIface' plus a 'ModDetails' summarises everything we know
971-- about a compiled module.  The 'ModIface' is the stuff *before* linking,
972-- and can be written out to an interface file. The 'ModDetails is after
973-- linking and can be completely recovered from just the 'ModIface'.
974--
975-- When we read an interface file, we also construct a 'ModIface' from it,
976-- except that we explicitly make the 'mi_decls' and a few other fields empty;
977-- as when reading we consolidate the declarations etc. into a number of indexed
978-- maps and environments in the 'ExternalPackageState'.
979data ModIface_ (phase :: ModIfacePhase)
980  = ModIface {
981        mi_module     :: !Module,             -- ^ Name of the module we are for
982        mi_sig_of     :: !(Maybe Module),     -- ^ Are we a sig of another mod?
983
984        mi_hsc_src    :: !HscSource,          -- ^ Boot? Signature?
985
986        mi_deps     :: Dependencies,
987                -- ^ The dependencies of the module.  This is
988                -- consulted for directly-imported modules, but not
989                -- for anything else (hence lazy)
990
991        mi_usages   :: [Usage],
992                -- ^ Usages; kept sorted so that it's easy to decide
993                -- whether to write a new iface file (changing usages
994                -- doesn't affect the hash of this module)
995                -- NOT STRICT!  we read this field lazily from the interface file
996                -- It is *only* consulted by the recompilation checker
997
998        mi_exports  :: ![IfaceExport],
999                -- ^ Exports
1000                -- Kept sorted by (mod,occ), to make version comparisons easier
1001                -- Records the modules that are the declaration points for things
1002                -- exported by this module, and the 'OccName's of those things
1003
1004
1005        mi_used_th  :: !Bool,
1006                -- ^ Module required TH splices when it was compiled.
1007                -- This disables recompilation avoidance (see #481).
1008
1009        mi_fixities :: [(OccName,Fixity)],
1010                -- ^ Fixities
1011                -- NOT STRICT!  we read this field lazily from the interface file
1012
1013        mi_warns    :: Warnings,
1014                -- ^ Warnings
1015                -- NOT STRICT!  we read this field lazily from the interface file
1016
1017        mi_anns     :: [IfaceAnnotation],
1018                -- ^ Annotations
1019                -- NOT STRICT!  we read this field lazily from the interface file
1020
1021
1022        mi_decls    :: [IfaceDeclExts phase],
1023                -- ^ Type, class and variable declarations
1024                -- The hash of an Id changes if its fixity or deprecations change
1025                --      (as well as its type of course)
1026                -- Ditto data constructors, class operations, except that
1027                -- the hash of the parent class/tycon changes
1028
1029        mi_globals  :: !(Maybe GlobalRdrEnv),
1030                -- ^ Binds all the things defined at the top level in
1031                -- the /original source/ code for this module. which
1032                -- is NOT the same as mi_exports, nor mi_decls (which
1033                -- may contains declarations for things not actually
1034                -- defined by the user).  Used for GHCi and for inspecting
1035                -- the contents of modules via the GHC API only.
1036                --
1037                -- (We need the source file to figure out the
1038                -- top-level environment, if we didn't compile this module
1039                -- from source then this field contains @Nothing@).
1040                --
1041                -- Strictly speaking this field should live in the
1042                -- 'HomeModInfo', but that leads to more plumbing.
1043
1044                -- Instance declarations and rules
1045        mi_insts       :: [IfaceClsInst],     -- ^ Sorted class instance
1046        mi_fam_insts   :: [IfaceFamInst],  -- ^ Sorted family instances
1047        mi_rules       :: [IfaceRule],     -- ^ Sorted rules
1048
1049        mi_hpc       :: !AnyHpcUsage,
1050                -- ^ True if this program uses Hpc at any point in the program.
1051
1052        mi_trust     :: !IfaceTrustInfo,
1053                -- ^ Safe Haskell Trust information for this module.
1054
1055        mi_trust_pkg :: !Bool,
1056                -- ^ Do we require the package this module resides in be trusted
1057                -- to trust this module? This is used for the situation where a
1058                -- module is Safe (so doesn't require the package be trusted
1059                -- itself) but imports some trustworthy modules from its own
1060                -- package (which does require its own package be trusted).
1061                -- See Note [RnNames . Trust Own Package]
1062        mi_complete_sigs :: [IfaceCompleteMatch],
1063
1064        mi_doc_hdr :: Maybe HsDocString,
1065                -- ^ Module header.
1066
1067        mi_decl_docs :: DeclDocMap,
1068                -- ^ Docs on declarations.
1069
1070        mi_arg_docs :: ArgDocMap,
1071                -- ^ Docs on arguments.
1072
1073        mi_final_exts :: !(IfaceBackendExts phase)
1074                -- ^ Either `()` or `ModIfaceBackend` for
1075                -- a fully instantiated interface.
1076     }
1077
1078-- | Old-style accessor for whether or not the ModIface came from an hs-boot
1079-- file.
1080mi_boot :: ModIface -> Bool
1081mi_boot iface = mi_hsc_src iface == HsBootFile
1082
1083-- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be
1084-- found, 'defaultFixity' is returned instead.
1085mi_fix :: ModIface -> OccName -> Fixity
1086mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity
1087
1088-- | The semantic module for this interface; e.g., if it's a interface
1089-- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module'
1090-- will be @<A>@.
1091mi_semantic_module :: ModIface_ a -> Module
1092mi_semantic_module iface = case mi_sig_of iface of
1093                            Nothing -> mi_module iface
1094                            Just mod -> mod
1095
1096-- | The "precise" free holes, e.g., the signatures that this
1097-- 'ModIface' depends on.
1098mi_free_holes :: ModIface -> UniqDSet ModuleName
1099mi_free_holes iface =
1100  case splitModuleInsts (mi_module iface) of
1101    (_, Just indef)
1102        -- A mini-hack: we rely on the fact that 'renameFreeHoles'
1103        -- drops things that aren't holes.
1104        -> renameFreeHoles (mkUniqDSet cands) (indefUnitIdInsts (indefModuleUnitId indef))
1105    _   -> emptyUniqDSet
1106  where
1107    cands = map fst (dep_mods (mi_deps iface))
1108
1109-- | Given a set of free holes, and a unit identifier, rename
1110-- the free holes according to the instantiation of the unit
1111-- identifier.  For example, if we have A and B free, and
1112-- our unit identity is @p[A=<C>,B=impl:B]@, the renamed free
1113-- holes are just C.
1114renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName
1115renameFreeHoles fhs insts =
1116    unionManyUniqDSets (map lookup_impl (uniqDSetToList fhs))
1117  where
1118    hmap = listToUFM insts
1119    lookup_impl mod_name
1120        | Just mod <- lookupUFM hmap mod_name = moduleFreeHoles mod
1121        -- It wasn't actually a hole
1122        | otherwise                           = emptyUniqDSet
1123
1124instance Binary ModIface where
1125   put_ bh (ModIface {
1126                 mi_module    = mod,
1127                 mi_sig_of    = sig_of,
1128                 mi_hsc_src   = hsc_src,
1129                 mi_deps      = deps,
1130                 mi_usages    = usages,
1131                 mi_exports   = exports,
1132                 mi_used_th   = used_th,
1133                 mi_fixities  = fixities,
1134                 mi_warns     = warns,
1135                 mi_anns      = anns,
1136                 mi_decls     = decls,
1137                 mi_insts     = insts,
1138                 mi_fam_insts = fam_insts,
1139                 mi_rules     = rules,
1140                 mi_hpc       = hpc_info,
1141                 mi_trust     = trust,
1142                 mi_trust_pkg = trust_pkg,
1143                 mi_complete_sigs = complete_sigs,
1144                 mi_doc_hdr   = doc_hdr,
1145                 mi_decl_docs = decl_docs,
1146                 mi_arg_docs  = arg_docs,
1147                 mi_final_exts = ModIfaceBackend {
1148                   mi_iface_hash = iface_hash,
1149                   mi_mod_hash = mod_hash,
1150                   mi_flag_hash = flag_hash,
1151                   mi_opt_hash = opt_hash,
1152                   mi_hpc_hash = hpc_hash,
1153                   mi_plugin_hash = plugin_hash,
1154                   mi_orphan = orphan,
1155                   mi_finsts = hasFamInsts,
1156                   mi_exp_hash = exp_hash,
1157                   mi_orphan_hash = orphan_hash
1158                 }}) = do
1159        put_ bh mod
1160        put_ bh sig_of
1161        put_ bh hsc_src
1162        put_ bh iface_hash
1163        put_ bh mod_hash
1164        put_ bh flag_hash
1165        put_ bh opt_hash
1166        put_ bh hpc_hash
1167        put_ bh plugin_hash
1168        put_ bh orphan
1169        put_ bh hasFamInsts
1170        lazyPut bh deps
1171        lazyPut bh usages
1172        put_ bh exports
1173        put_ bh exp_hash
1174        put_ bh used_th
1175        put_ bh fixities
1176        lazyPut bh warns
1177        lazyPut bh anns
1178        put_ bh decls
1179        put_ bh insts
1180        put_ bh fam_insts
1181        lazyPut bh rules
1182        put_ bh orphan_hash
1183        put_ bh hpc_info
1184        put_ bh trust
1185        put_ bh trust_pkg
1186        put_ bh complete_sigs
1187        lazyPut bh doc_hdr
1188        lazyPut bh decl_docs
1189        lazyPut bh arg_docs
1190
1191   get bh = do
1192        mod         <- get bh
1193        sig_of      <- get bh
1194        hsc_src     <- get bh
1195        iface_hash  <- get bh
1196        mod_hash    <- get bh
1197        flag_hash   <- get bh
1198        opt_hash    <- get bh
1199        hpc_hash    <- get bh
1200        plugin_hash <- get bh
1201        orphan      <- get bh
1202        hasFamInsts <- get bh
1203        deps        <- lazyGet bh
1204        usages      <- {-# SCC "bin_usages" #-} lazyGet bh
1205        exports     <- {-# SCC "bin_exports" #-} get bh
1206        exp_hash    <- get bh
1207        used_th     <- get bh
1208        fixities    <- {-# SCC "bin_fixities" #-} get bh
1209        warns       <- {-# SCC "bin_warns" #-} lazyGet bh
1210        anns        <- {-# SCC "bin_anns" #-} lazyGet bh
1211        decls       <- {-# SCC "bin_tycldecls" #-} get bh
1212        insts       <- {-# SCC "bin_insts" #-} get bh
1213        fam_insts   <- {-# SCC "bin_fam_insts" #-} get bh
1214        rules       <- {-# SCC "bin_rules" #-} lazyGet bh
1215        orphan_hash <- get bh
1216        hpc_info    <- get bh
1217        trust       <- get bh
1218        trust_pkg   <- get bh
1219        complete_sigs <- get bh
1220        doc_hdr     <- lazyGet bh
1221        decl_docs   <- lazyGet bh
1222        arg_docs    <- lazyGet bh
1223        return (ModIface {
1224                 mi_module      = mod,
1225                 mi_sig_of      = sig_of,
1226                 mi_hsc_src     = hsc_src,
1227                 mi_deps        = deps,
1228                 mi_usages      = usages,
1229                 mi_exports     = exports,
1230                 mi_used_th     = used_th,
1231                 mi_anns        = anns,
1232                 mi_fixities    = fixities,
1233                 mi_warns       = warns,
1234                 mi_decls       = decls,
1235                 mi_globals     = Nothing,
1236                 mi_insts       = insts,
1237                 mi_fam_insts   = fam_insts,
1238                 mi_rules       = rules,
1239                 mi_hpc         = hpc_info,
1240                 mi_trust       = trust,
1241                 mi_trust_pkg   = trust_pkg,
1242                        -- And build the cached values
1243                 mi_complete_sigs = complete_sigs,
1244                 mi_doc_hdr     = doc_hdr,
1245                 mi_decl_docs   = decl_docs,
1246                 mi_arg_docs    = arg_docs,
1247                 mi_final_exts = ModIfaceBackend {
1248                   mi_iface_hash = iface_hash,
1249                   mi_mod_hash = mod_hash,
1250                   mi_flag_hash = flag_hash,
1251                   mi_opt_hash = opt_hash,
1252                   mi_hpc_hash = hpc_hash,
1253                   mi_plugin_hash = plugin_hash,
1254                   mi_orphan = orphan,
1255                   mi_finsts = hasFamInsts,
1256                   mi_exp_hash = exp_hash,
1257                   mi_orphan_hash = orphan_hash,
1258                   mi_warn_fn = mkIfaceWarnCache warns,
1259                   mi_fix_fn = mkIfaceFixCache fixities,
1260                   mi_hash_fn = mkIfaceHashCache decls
1261                 }})
1262
1263-- | The original names declared of a certain module that are exported
1264type IfaceExport = AvailInfo
1265
1266emptyPartialModIface :: Module -> PartialModIface
1267emptyPartialModIface mod
1268  = ModIface { mi_module      = mod,
1269               mi_sig_of      = Nothing,
1270               mi_hsc_src     = HsSrcFile,
1271               mi_deps        = noDependencies,
1272               mi_usages      = [],
1273               mi_exports     = [],
1274               mi_used_th     = False,
1275               mi_fixities    = [],
1276               mi_warns       = NoWarnings,
1277               mi_anns        = [],
1278               mi_insts       = [],
1279               mi_fam_insts   = [],
1280               mi_rules       = [],
1281               mi_decls       = [],
1282               mi_globals     = Nothing,
1283               mi_hpc         = False,
1284               mi_trust       = noIfaceTrustInfo,
1285               mi_trust_pkg   = False,
1286               mi_complete_sigs = [],
1287               mi_doc_hdr     = Nothing,
1288               mi_decl_docs   = emptyDeclDocMap,
1289               mi_arg_docs    = emptyArgDocMap,
1290               mi_final_exts        = () }
1291
1292emptyFullModIface :: Module -> ModIface
1293emptyFullModIface mod =
1294    (emptyPartialModIface mod)
1295      { mi_decls = []
1296      , mi_final_exts = ModIfaceBackend
1297        { mi_iface_hash = fingerprint0,
1298          mi_mod_hash = fingerprint0,
1299          mi_flag_hash = fingerprint0,
1300          mi_opt_hash = fingerprint0,
1301          mi_hpc_hash = fingerprint0,
1302          mi_plugin_hash = fingerprint0,
1303          mi_orphan = False,
1304          mi_finsts = False,
1305          mi_exp_hash = fingerprint0,
1306          mi_orphan_hash = fingerprint0,
1307          mi_warn_fn = emptyIfaceWarnCache,
1308          mi_fix_fn = emptyIfaceFixCache,
1309          mi_hash_fn = emptyIfaceHashCache } }
1310
1311-- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface'
1312mkIfaceHashCache :: [(Fingerprint,IfaceDecl)]
1313                 -> (OccName -> Maybe (OccName, Fingerprint))
1314mkIfaceHashCache pairs
1315  = \occ -> lookupOccEnv env occ
1316  where
1317    env = foldl' add_decl emptyOccEnv pairs
1318    add_decl env0 (v,d) = foldl' add env0 (ifaceDeclFingerprints v d)
1319      where
1320        add env0 (occ,hash) = extendOccEnv env0 occ (occ,hash)
1321
1322emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
1323emptyIfaceHashCache _occ = Nothing
1324
1325
1326-- | The 'ModDetails' is essentially a cache for information in the 'ModIface'
1327-- for home modules only. Information relating to packages will be loaded into
1328-- global environments in 'ExternalPackageState'.
1329data ModDetails
1330  = ModDetails {
1331        -- The next two fields are created by the typechecker
1332        md_exports   :: [AvailInfo],
1333        md_types     :: !TypeEnv,       -- ^ Local type environment for this particular module
1334                                        -- Includes Ids, TyCons, PatSyns
1335        md_insts     :: ![ClsInst],     -- ^ 'DFunId's for the instances in this module
1336        md_fam_insts :: ![FamInst],
1337        md_rules     :: ![CoreRule],    -- ^ Domain may include 'Id's from other modules
1338        md_anns      :: ![Annotation],  -- ^ Annotations present in this module: currently
1339                                        -- they only annotate things also declared in this module
1340        md_complete_sigs :: [CompleteMatch]
1341          -- ^ Complete match pragmas for this module
1342     }
1343
1344-- | Constructs an empty ModDetails
1345emptyModDetails :: ModDetails
1346emptyModDetails
1347  = ModDetails { md_types     = emptyTypeEnv,
1348                 md_exports   = [],
1349                 md_insts     = [],
1350                 md_rules     = [],
1351                 md_fam_insts = [],
1352                 md_anns      = [],
1353                 md_complete_sigs = [] }
1354
1355-- | Records the modules directly imported by a module for extracting e.g.
1356-- usage information, and also to give better error message
1357type ImportedMods = ModuleEnv [ImportedBy]
1358
1359-- | If a module was "imported" by the user, we associate it with
1360-- more detailed usage information 'ImportedModsVal'; a module
1361-- imported by the system only gets used for usage information.
1362data ImportedBy
1363    = ImportedByUser ImportedModsVal
1364    | ImportedBySystem
1365
1366importedByUser :: [ImportedBy] -> [ImportedModsVal]
1367importedByUser (ImportedByUser imv : bys) = imv : importedByUser bys
1368importedByUser (ImportedBySystem   : bys) =       importedByUser bys
1369importedByUser [] = []
1370
1371data ImportedModsVal
1372 = ImportedModsVal {
1373        imv_name :: ModuleName,          -- ^ The name the module is imported with
1374        imv_span :: SrcSpan,             -- ^ the source span of the whole import
1375        imv_is_safe :: IsSafeImport,     -- ^ whether this is a safe import
1376        imv_is_hiding :: Bool,           -- ^ whether this is an "hiding" import
1377        imv_all_exports :: !GlobalRdrEnv, -- ^ all the things the module could provide
1378          -- NB. BangPattern here: otherwise this leaks. (#15111)
1379        imv_qualified :: Bool            -- ^ whether this is a qualified import
1380        }
1381
1382-- | A ModGuts is carried through the compiler, accumulating stuff as it goes
1383-- There is only one ModGuts at any time, the one for the module
1384-- being compiled right now.  Once it is compiled, a 'ModIface' and
1385-- 'ModDetails' are extracted and the ModGuts is discarded.
1386data ModGuts
1387  = ModGuts {
1388        mg_module    :: !Module,         -- ^ Module being compiled
1389        mg_hsc_src   :: HscSource,       -- ^ Whether it's an hs-boot module
1390        mg_loc       :: SrcSpan,         -- ^ For error messages from inner passes
1391        mg_exports   :: ![AvailInfo],    -- ^ What it exports
1392        mg_deps      :: !Dependencies,   -- ^ What it depends on, directly or
1393                                         -- otherwise
1394        mg_usages    :: ![Usage],        -- ^ What was used?  Used for interfaces.
1395
1396        mg_used_th   :: !Bool,           -- ^ Did we run a TH splice?
1397        mg_rdr_env   :: !GlobalRdrEnv,   -- ^ Top-level lexical environment
1398
1399        -- These fields all describe the things **declared in this module**
1400        mg_fix_env   :: !FixityEnv,      -- ^ Fixities declared in this module.
1401                                         -- Used for creating interface files.
1402        mg_tcs       :: ![TyCon],        -- ^ TyCons declared in this module
1403                                         -- (includes TyCons for classes)
1404        mg_insts     :: ![ClsInst],      -- ^ Class instances declared in this module
1405        mg_fam_insts :: ![FamInst],
1406                                         -- ^ Family instances declared in this module
1407        mg_patsyns   :: ![PatSyn],       -- ^ Pattern synonyms declared in this module
1408        mg_rules     :: ![CoreRule],     -- ^ Before the core pipeline starts, contains
1409                                         -- See Note [Overall plumbing for rules] in Rules.hs
1410        mg_binds     :: !CoreProgram,    -- ^ Bindings for this module
1411        mg_foreign   :: !ForeignStubs,   -- ^ Foreign exports declared in this module
1412        mg_foreign_files :: ![(ForeignSrcLang, FilePath)],
1413        -- ^ Files to be compiled with the C compiler
1414        mg_warns     :: !Warnings,       -- ^ Warnings declared in the module
1415        mg_anns      :: [Annotation],    -- ^ Annotations declared in this module
1416        mg_complete_sigs :: [CompleteMatch], -- ^ Complete Matches
1417        mg_hpc_info  :: !HpcInfo,        -- ^ Coverage tick boxes in the module
1418        mg_modBreaks :: !(Maybe ModBreaks), -- ^ Breakpoints for the module
1419
1420                        -- The next two fields are unusual, because they give instance
1421                        -- environments for *all* modules in the home package, including
1422                        -- this module, rather than for *just* this module.
1423                        -- Reason: when looking up an instance we don't want to have to
1424                        --         look at each module in the home package in turn
1425        mg_inst_env     :: InstEnv,             -- ^ Class instance environment for
1426                                                -- /home-package/ modules (including this
1427                                                -- one); c.f. 'tcg_inst_env'
1428        mg_fam_inst_env :: FamInstEnv,          -- ^ Type-family instance environment for
1429                                                -- /home-package/ modules (including this
1430                                                -- one); c.f. 'tcg_fam_inst_env'
1431
1432        mg_safe_haskell :: SafeHaskellMode,     -- ^ Safe Haskell mode
1433        mg_trust_pkg    :: Bool,                -- ^ Do we need to trust our
1434                                                -- own package for Safe Haskell?
1435                                                -- See Note [RnNames . Trust Own Package]
1436
1437        mg_doc_hdr       :: !(Maybe HsDocString), -- ^ Module header.
1438        mg_decl_docs     :: !DeclDocMap,     -- ^ Docs on declarations.
1439        mg_arg_docs      :: !ArgDocMap       -- ^ Docs on arguments.
1440    }
1441
1442-- The ModGuts takes on several slightly different forms:
1443--
1444-- After simplification, the following fields change slightly:
1445--      mg_rules        Orphan rules only (local ones now attached to binds)
1446--      mg_binds        With rules attached
1447
1448---------------------------------------------------------
1449-- The Tidy pass forks the information about this module:
1450--      * one lot goes to interface file generation (ModIface)
1451--        and later compilations (ModDetails)
1452--      * the other lot goes to code generation (CgGuts)
1453
1454-- | A restricted form of 'ModGuts' for code generation purposes
1455data CgGuts
1456  = CgGuts {
1457        cg_module    :: !Module,
1458                -- ^ Module being compiled
1459
1460        cg_tycons    :: [TyCon],
1461                -- ^ Algebraic data types (including ones that started
1462                -- life as classes); generate constructors and info
1463                -- tables. Includes newtypes, just for the benefit of
1464                -- External Core
1465
1466        cg_binds     :: CoreProgram,
1467                -- ^ The tidied main bindings, including
1468                -- previously-implicit bindings for record and class
1469                -- selectors, and data constructor wrappers.  But *not*
1470                -- data constructor workers; reason: we regard them
1471                -- as part of the code-gen of tycons
1472
1473        cg_foreign   :: !ForeignStubs,   -- ^ Foreign export stubs
1474        cg_foreign_files :: ![(ForeignSrcLang, FilePath)],
1475        cg_dep_pkgs  :: ![InstalledUnitId], -- ^ Dependent packages, used to
1476                                            -- generate #includes for C code gen
1477        cg_hpc_info  :: !HpcInfo,           -- ^ Program coverage tick box information
1478        cg_modBreaks :: !(Maybe ModBreaks), -- ^ Module breakpoints
1479        cg_spt_entries :: [SptEntry]
1480                -- ^ Static pointer table entries for static forms defined in
1481                -- the module.
1482                -- See Note [Grand plan for static forms] in StaticPtrTable
1483    }
1484
1485-----------------------------------
1486-- | Foreign export stubs
1487data ForeignStubs
1488  = NoStubs
1489      -- ^ We don't have any stubs
1490  | ForeignStubs SDoc SDoc
1491      -- ^ There are some stubs. Parameters:
1492      --
1493      --  1) Header file prototypes for
1494      --     "foreign exported" functions
1495      --
1496      --  2) C stubs to use when calling
1497      --     "foreign exported" functions
1498
1499appendStubC :: ForeignStubs -> SDoc -> ForeignStubs
1500appendStubC NoStubs            c_code = ForeignStubs empty c_code
1501appendStubC (ForeignStubs h c) c_code = ForeignStubs h (c $$ c_code)
1502
1503{-
1504************************************************************************
1505*                                                                      *
1506                The interactive context
1507*                                                                      *
1508************************************************************************
1509
1510Note [The interactive package]
1511~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1512Type, class, and value declarations at the command prompt are treated
1513as if they were defined in modules
1514   interactive:Ghci1
1515   interactive:Ghci2
1516   ...etc...
1517with each bunch of declarations using a new module, all sharing a
1518common package 'interactive' (see Module.interactiveUnitId, and
1519PrelNames.mkInteractiveModule).
1520
1521This scheme deals well with shadowing.  For example:
1522
1523   ghci> data T = A
1524   ghci> data T = B
1525   ghci> :i A
1526   data Ghci1.T = A  -- Defined at <interactive>:2:10
1527
1528Here we must display info about constructor A, but its type T has been
1529shadowed by the second declaration.  But it has a respectable
1530qualified name (Ghci1.T), and its source location says where it was
1531defined.
1532
1533So the main invariant continues to hold, that in any session an
1534original name M.T only refers to one unique thing.  (In a previous
1535iteration both the T's above were called :Interactive.T, albeit with
1536different uniques, which gave rise to all sorts of trouble.)
1537
1538The details are a bit tricky though:
1539
1540 * The field ic_mod_index counts which Ghci module we've got up to.
1541   It is incremented when extending ic_tythings
1542
1543 * ic_tythings contains only things from the 'interactive' package.
1544
1545 * Module from the 'interactive' package (Ghci1, Ghci2 etc) never go
1546   in the Home Package Table (HPT).  When you say :load, that's when we
1547   extend the HPT.
1548
1549 * The 'thisPackage' field of DynFlags is *not* set to 'interactive'.
1550   It stays as 'main' (or whatever -this-unit-id says), and is the
1551   package to which :load'ed modules are added to.
1552
1553 * So how do we arrange that declarations at the command prompt get to
1554   be in the 'interactive' package?  Simply by setting the tcg_mod
1555   field of the TcGblEnv to "interactive:Ghci1".  This is done by the
1556   call to initTc in initTcInteractive, which in turn get the module
1557   from it 'icInteractiveModule' field of the interactive context.
1558
1559   The 'thisPackage' field stays as 'main' (or whatever -this-unit-id says.
1560
1561 * The main trickiness is that the type environment (tcg_type_env) and
1562   fixity envt (tcg_fix_env), now contain entities from all the
1563   interactive-package modules (Ghci1, Ghci2, ...) together, rather
1564   than just a single module as is usually the case.  So you can't use
1565   "nameIsLocalOrFrom" to decide whether to look in the TcGblEnv vs
1566   the HPT/PTE.  This is a change, but not a problem provided you
1567   know.
1568
1569* However, the tcg_binds, tcg_sigs, tcg_insts, tcg_fam_insts, etc fields
1570  of the TcGblEnv, which collect "things defined in this module", all
1571  refer to stuff define in a single GHCi command, *not* all the commands
1572  so far.
1573
1574  In contrast, tcg_inst_env, tcg_fam_inst_env, have instances from
1575  all GhciN modules, which makes sense -- they are all "home package"
1576  modules.
1577
1578
1579Note [Interactively-bound Ids in GHCi]
1580~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1581The Ids bound by previous Stmts in GHCi are currently
1582        a) GlobalIds, with
1583        b) An External Name, like Ghci4.foo
1584           See Note [The interactive package] above
1585        c) A tidied type
1586
1587 (a) They must be GlobalIds (not LocalIds) otherwise when we come to
1588     compile an expression using these ids later, the byte code
1589     generator will consider the occurrences to be free rather than
1590     global.
1591
1592 (b) Having an External Name is important because of Note
1593     [GlobalRdrEnv shadowing] in RdrName
1594
1595 (c) Their types are tidied. This is important, because :info may ask
1596     to look at them, and :info expects the things it looks up to have
1597     tidy types
1598
1599Where do interactively-bound Ids come from?
1600
1601  - GHCi REPL Stmts   e.g.
1602         ghci> let foo x = x+1
1603    These start with an Internal Name because a Stmt is a local
1604    construct, so the renamer naturally builds an Internal name for
1605    each of its binders.  Then in tcRnStmt they are externalised via
1606    TcRnDriver.externaliseAndTidyId, so they get Names like Ghic4.foo.
1607
1608  - Ids bound by the debugger etc have Names constructed by
1609    IfaceEnv.newInteractiveBinder; at the call sites it is followed by
1610    mkVanillaGlobal or mkVanillaGlobalWithInfo.  So again, they are
1611    all Global, External.
1612
1613  - TyCons, Classes, and Ids bound by other top-level declarations in
1614    GHCi (eg foreign import, record selectors) also get External
1615    Names, with Ghci9 (or 8, or 7, etc) as the module name.
1616
1617
1618Note [ic_tythings]
1619~~~~~~~~~~~~~~~~~~
1620The ic_tythings field contains
1621  * The TyThings declared by the user at the command prompt
1622    (eg Ids, TyCons, Classes)
1623
1624  * The user-visible Ids that arise from such things, which
1625    *don't* come from 'implicitTyThings', notably:
1626       - record selectors
1627       - class ops
1628    The implicitTyThings are readily obtained from the TyThings
1629    but record selectors etc are not
1630
1631It does *not* contain
1632  * DFunIds (they can be gotten from ic_instances)
1633  * CoAxioms (ditto)
1634
1635See also Note [Interactively-bound Ids in GHCi]
1636
1637Note [Override identical instances in GHCi]
1638~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1639If you declare a new instance in GHCi that is identical to a previous one,
1640we simply override the previous one; we don't regard it as overlapping.
1641e.g.    Prelude> data T = A | B
1642        Prelude> instance Eq T where ...
1643        Prelude> instance Eq T where ...   -- This one overrides
1644
1645It's exactly the same for type-family instances.  See #7102
1646-}
1647
1648-- | Interactive context, recording information about the state of the
1649-- context in which statements are executed in a GHCi session.
1650data InteractiveContext
1651  = InteractiveContext {
1652         ic_dflags     :: DynFlags,
1653             -- ^ The 'DynFlags' used to evaluate interative expressions
1654             -- and statements.
1655
1656         ic_mod_index :: Int,
1657             -- ^ Each GHCi stmt or declaration brings some new things into
1658             -- scope. We give them names like interactive:Ghci9.T,
1659             -- where the ic_index is the '9'.  The ic_mod_index is
1660             -- incremented whenever we add something to ic_tythings
1661             -- See Note [The interactive package]
1662
1663         ic_imports :: [InteractiveImport],
1664             -- ^ The GHCi top-level scope (ic_rn_gbl_env) is extended with
1665             -- these imports
1666             --
1667             -- This field is only stored here so that the client
1668             -- can retrieve it with GHC.getContext. GHC itself doesn't
1669             -- use it, but does reset it to empty sometimes (such
1670             -- as before a GHC.load). The context is set with GHC.setContext.
1671
1672         ic_tythings   :: [TyThing],
1673             -- ^ TyThings defined by the user, in reverse order of
1674             -- definition (ie most recent at the front)
1675             -- See Note [ic_tythings]
1676
1677         ic_rn_gbl_env :: GlobalRdrEnv,
1678             -- ^ The cached 'GlobalRdrEnv', built by
1679             -- 'InteractiveEval.setContext' and updated regularly
1680             -- It contains everything in scope at the command line,
1681             -- including everything in ic_tythings
1682
1683         ic_instances  :: ([ClsInst], [FamInst]),
1684             -- ^ All instances and family instances created during
1685             -- this session.  These are grabbed en masse after each
1686             -- update to be sure that proper overlapping is retained.
1687             -- That is, rather than re-check the overlapping each
1688             -- time we update the context, we just take the results
1689             -- from the instance code that already does that.
1690
1691         ic_fix_env :: FixityEnv,
1692            -- ^ Fixities declared in let statements
1693
1694         ic_default :: Maybe [Type],
1695             -- ^ The current default types, set by a 'default' declaration
1696
1697          ic_resume :: [Resume],
1698             -- ^ The stack of breakpoint contexts
1699
1700         ic_monad      :: Name,
1701             -- ^ The monad that GHCi is executing in
1702
1703         ic_int_print  :: Name,
1704             -- ^ The function that is used for printing results
1705             -- of expressions in ghci and -e mode.
1706
1707         ic_cwd :: Maybe FilePath
1708             -- virtual CWD of the program
1709    }
1710
1711data InteractiveImport
1712  = IIDecl (ImportDecl GhcPs)
1713      -- ^ Bring the exports of a particular module
1714      -- (filtered by an import decl) into scope
1715
1716  | IIModule ModuleName
1717      -- ^ Bring into scope the entire top-level envt of
1718      -- of this module, including the things imported
1719      -- into it.
1720
1721
1722-- | Constructs an empty InteractiveContext.
1723emptyInteractiveContext :: DynFlags -> InteractiveContext
1724emptyInteractiveContext dflags
1725  = InteractiveContext {
1726       ic_dflags     = dflags,
1727       ic_imports    = [],
1728       ic_rn_gbl_env = emptyGlobalRdrEnv,
1729       ic_mod_index  = 1,
1730       ic_tythings   = [],
1731       ic_instances  = ([],[]),
1732       ic_fix_env    = emptyNameEnv,
1733       ic_monad      = ioTyConName,  -- IO monad by default
1734       ic_int_print  = printName,    -- System.IO.print by default
1735       ic_default    = Nothing,
1736       ic_resume     = [],
1737       ic_cwd        = Nothing }
1738
1739icInteractiveModule :: InteractiveContext -> Module
1740icInteractiveModule (InteractiveContext { ic_mod_index = index })
1741  = mkInteractiveModule index
1742
1743-- | This function returns the list of visible TyThings (useful for
1744-- e.g. showBindings)
1745icInScopeTTs :: InteractiveContext -> [TyThing]
1746icInScopeTTs = ic_tythings
1747
1748-- | Get the PrintUnqualified function based on the flags and this InteractiveContext
1749icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
1750icPrintUnqual dflags InteractiveContext{ ic_rn_gbl_env = grenv } =
1751    mkPrintUnqualified dflags grenv
1752
1753-- | extendInteractiveContext is called with new TyThings recently defined to update the
1754-- InteractiveContext to include them.  Ids are easily removed when shadowed,
1755-- but Classes and TyCons are not.  Some work could be done to determine
1756-- whether they are entirely shadowed, but as you could still have references
1757-- to them (e.g. instances for classes or values of the type for TyCons), it's
1758-- not clear whether removing them is even the appropriate behavior.
1759extendInteractiveContext :: InteractiveContext
1760                         -> [TyThing]
1761                         -> [ClsInst] -> [FamInst]
1762                         -> Maybe [Type]
1763                         -> FixityEnv
1764                         -> InteractiveContext
1765extendInteractiveContext ictxt new_tythings new_cls_insts new_fam_insts defaults fix_env
1766  = ictxt { ic_mod_index  = ic_mod_index ictxt + 1
1767                            -- Always bump this; even instances should create
1768                            -- a new mod_index (#9426)
1769          , ic_tythings   = new_tythings ++ old_tythings
1770          , ic_rn_gbl_env = ic_rn_gbl_env ictxt `icExtendGblRdrEnv` new_tythings
1771          , ic_instances  = ( new_cls_insts ++ old_cls_insts
1772                            , new_fam_insts ++ fam_insts )
1773                            -- we don't shadow old family instances (#7102),
1774                            -- so don't need to remove them here
1775          , ic_default    = defaults
1776          , ic_fix_env    = fix_env  -- See Note [Fixity declarations in GHCi]
1777          }
1778  where
1779    new_ids = [id | AnId id <- new_tythings]
1780    old_tythings = filterOut (shadowed_by new_ids) (ic_tythings ictxt)
1781
1782    -- Discard old instances that have been fully overridden
1783    -- See Note [Override identical instances in GHCi]
1784    (cls_insts, fam_insts) = ic_instances ictxt
1785    old_cls_insts = filterOut (\i -> any (identicalClsInstHead i) new_cls_insts) cls_insts
1786
1787extendInteractiveContextWithIds :: InteractiveContext -> [Id] -> InteractiveContext
1788-- Just a specialised version
1789extendInteractiveContextWithIds ictxt new_ids
1790  | null new_ids = ictxt
1791  | otherwise    = ictxt { ic_mod_index  = ic_mod_index ictxt + 1
1792                         , ic_tythings   = new_tythings ++ old_tythings
1793                         , ic_rn_gbl_env = ic_rn_gbl_env ictxt `icExtendGblRdrEnv` new_tythings }
1794  where
1795    new_tythings = map AnId new_ids
1796    old_tythings = filterOut (shadowed_by new_ids) (ic_tythings ictxt)
1797
1798shadowed_by :: [Id] -> TyThing -> Bool
1799shadowed_by ids = shadowed
1800  where
1801    shadowed id = getOccName id `elemOccSet` new_occs
1802    new_occs = mkOccSet (map getOccName ids)
1803
1804setInteractivePackage :: HscEnv -> HscEnv
1805-- Set the 'thisPackage' DynFlag to 'interactive'
1806setInteractivePackage hsc_env
1807   = hsc_env { hsc_dflags = (hsc_dflags hsc_env)
1808                { thisInstalledUnitId = toInstalledUnitId interactiveUnitId } }
1809
1810setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
1811setInteractivePrintName ic n = ic{ic_int_print = n}
1812
1813    -- ToDo: should not add Ids to the gbl env here
1814
1815-- | Add TyThings to the GlobalRdrEnv, earlier ones in the list shadowing
1816-- later ones, and shadowing existing entries in the GlobalRdrEnv.
1817icExtendGblRdrEnv :: GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv
1818icExtendGblRdrEnv env tythings
1819  = foldr add env tythings  -- Foldr makes things in the front of
1820                            -- the list shadow things at the back
1821  where
1822    -- One at a time, to ensure each shadows the previous ones
1823    add thing env
1824       | is_sub_bndr thing
1825       = env
1826       | otherwise
1827       = foldl' extendGlobalRdrEnv env1 (concatMap localGREsFromAvail avail)
1828       where
1829          env1  = shadowNames env (concatMap availNames avail)
1830          avail = tyThingAvailInfo thing
1831
1832    -- Ugh! The new_tythings may include record selectors, since they
1833    -- are not implicit-ids, and must appear in the TypeEnv.  But they
1834    -- will also be brought into scope by the corresponding (ATyCon
1835    -- tc).  And we want the latter, because that has the correct
1836    -- parent (#10520)
1837    is_sub_bndr (AnId f) = case idDetails f of
1838                             RecSelId {}  -> True
1839                             ClassOpId {} -> True
1840                             _            -> False
1841    is_sub_bndr _ = False
1842
1843substInteractiveContext :: InteractiveContext -> TCvSubst -> InteractiveContext
1844substInteractiveContext ictxt@InteractiveContext{ ic_tythings = tts } subst
1845  | isEmptyTCvSubst subst = ictxt
1846  | otherwise             = ictxt { ic_tythings = map subst_ty tts }
1847  where
1848    subst_ty (AnId id)
1849      = AnId $ id `setIdType` substTyAddInScope subst (idType id)
1850      -- Variables in the interactive context *can* mention free type variables
1851      -- because of the runtime debugger. Otherwise you'd expect all
1852      -- variables bound in the interactive context to be closed.
1853    subst_ty tt
1854      = tt
1855
1856instance Outputable InteractiveImport where
1857  ppr (IIModule m) = char '*' <> ppr m
1858  ppr (IIDecl d)   = ppr d
1859
1860{-
1861************************************************************************
1862*                                                                      *
1863        Building a PrintUnqualified
1864*                                                                      *
1865************************************************************************
1866
1867Note [Printing original names]
1868~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1869Deciding how to print names is pretty tricky.  We are given a name
1870P:M.T, where P is the package name, M is the defining module, and T is
1871the occurrence name, and we have to decide in which form to display
1872the name given a GlobalRdrEnv describing the current scope.
1873
1874Ideally we want to display the name in the form in which it is in
1875scope.  However, the name might not be in scope at all, and that's
1876where it gets tricky.  Here are the cases:
1877
1878 1. T uniquely maps to  P:M.T      --->  "T"      NameUnqual
1879 2. There is an X for which X.T
1880       uniquely maps to  P:M.T     --->  "X.T"    NameQual X
1881 3. There is no binding for "M.T"  --->  "M.T"    NameNotInScope1
1882 4. Otherwise                      --->  "P:M.T"  NameNotInScope2
1883
1884(3) and (4) apply when the entity P:M.T is not in the GlobalRdrEnv at
1885all. In these cases we still want to refer to the name as "M.T", *but*
1886"M.T" might mean something else in the current scope (e.g. if there's
1887an "import X as M"), so to avoid confusion we avoid using "M.T" if
1888there's already a binding for it.  Instead we write P:M.T.
1889
1890There's one further subtlety: in case (3), what if there are two
1891things around, P1:M.T and P2:M.T?  Then we don't want to print both of
1892them as M.T!  However only one of the modules P1:M and P2:M can be
1893exposed (say P2), so we use M.T for that, and P1:M.T for the other one.
1894This is handled by the qual_mod component of PrintUnqualified, inside
1895the (ppr mod) of case (3), in Name.pprModulePrefix
1896
1897Note [Printing unit ids]
1898~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1899In the old days, original names were tied to PackageIds, which directly
1900corresponded to the entities that users wrote in Cabal files, and were perfectly
1901suitable for printing when we need to disambiguate packages.  However, with
1902UnitId, the situation can be different: if the key is instantiated with
1903some holes, we should try to give the user some more useful information.
1904-}
1905
1906-- | Creates some functions that work out the best ways to format
1907-- names for the user according to a set of heuristics.
1908mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
1909mkPrintUnqualified dflags env = QueryQualify qual_name
1910                                             (mkQualModule dflags)
1911                                             (mkQualPackage dflags)
1912  where
1913  qual_name mod occ
1914        | [gre] <- unqual_gres
1915        , right_name gre
1916        = NameUnqual   -- If there's a unique entity that's in scope
1917                       -- unqualified with 'occ' AND that entity is
1918                       -- the right one, then we can use the unqualified name
1919
1920        | [] <- unqual_gres
1921        , any is_name forceUnqualNames
1922        , not (isDerivedOccName occ)
1923        = NameUnqual   -- Don't qualify names that come from modules
1924                       -- that come with GHC, often appear in error messages,
1925                       -- but aren't typically in scope. Doing this does not
1926                       -- cause ambiguity, and it reduces the amount of
1927                       -- qualification in error messages thus improving
1928                       -- readability.
1929                       --
1930                       -- A motivating example is 'Constraint'. It's often not
1931                       -- in scope, but printing GHC.Prim.Constraint seems
1932                       -- overkill.
1933
1934        | [gre] <- qual_gres
1935        = NameQual (greQualModName gre)
1936
1937        | null qual_gres
1938        = if null (lookupGRE_RdrName (mkRdrQual (moduleName mod) occ) env)
1939          then NameNotInScope1
1940          else NameNotInScope2
1941
1942        | otherwise
1943        = NameNotInScope1   -- Can happen if 'f' is bound twice in the module
1944                            -- Eg  f = True; g = 0; f = False
1945      where
1946        is_name :: Name -> Bool
1947        is_name name = ASSERT2( isExternalName name, ppr name )
1948                       nameModule name == mod && nameOccName name == occ
1949
1950        forceUnqualNames :: [Name]
1951        forceUnqualNames =
1952          map tyConName [ constraintKindTyCon, heqTyCon, coercibleTyCon ]
1953          ++ [ eqTyConName ]
1954
1955        right_name gre = nameModule_maybe (gre_name gre) == Just mod
1956
1957        unqual_gres = lookupGRE_RdrName (mkRdrUnqual occ) env
1958        qual_gres   = filter right_name (lookupGlobalRdrEnv env occ)
1959
1960    -- we can mention a module P:M without the P: qualifier iff
1961    -- "import M" would resolve unambiguously to P:M.  (if P is the
1962    -- current package we can just assume it is unqualified).
1963
1964-- | Creates a function for formatting modules based on two heuristics:
1965-- (1) if the module is the current module, don't qualify, and (2) if there
1966-- is only one exposed package which exports this module, don't qualify.
1967mkQualModule :: DynFlags -> QueryQualifyModule
1968mkQualModule dflags mod
1969     | moduleUnitId mod == thisPackage dflags = False
1970
1971     | [(_, pkgconfig)] <- lookup,
1972       packageConfigId pkgconfig == moduleUnitId mod
1973        -- this says: we are given a module P:M, is there just one exposed package
1974        -- that exposes a module M, and is it package P?
1975     = False
1976
1977     | otherwise = True
1978     where lookup = lookupModuleInAllPackages dflags (moduleName mod)
1979
1980-- | Creates a function for formatting packages based on two heuristics:
1981-- (1) don't qualify if the package in question is "main", and (2) only qualify
1982-- with a unit id if the package ID would be ambiguous.
1983mkQualPackage :: DynFlags -> QueryQualifyPackage
1984mkQualPackage dflags pkg_key
1985     | pkg_key == mainUnitId || pkg_key == interactiveUnitId
1986        -- Skip the lookup if it's main, since it won't be in the package
1987        -- database!
1988     = False
1989     | Just pkgid <- mb_pkgid
1990     , searchPackageId dflags pkgid `lengthIs` 1
1991        -- this says: we are given a package pkg-0.1@MMM, are there only one
1992        -- exposed packages whose package ID is pkg-0.1?
1993     = False
1994     | otherwise
1995     = True
1996     where mb_pkgid = fmap sourcePackageId (lookupPackage dflags pkg_key)
1997
1998-- | A function which only qualifies package names if necessary; but
1999-- qualifies all other identifiers.
2000pkgQual :: DynFlags -> PrintUnqualified
2001pkgQual dflags = alwaysQualify {
2002        queryQualifyPackage = mkQualPackage dflags
2003    }
2004
2005{-
2006************************************************************************
2007*                                                                      *
2008                Implicit TyThings
2009*                                                                      *
2010************************************************************************
2011
2012Note [Implicit TyThings]
2013~~~~~~~~~~~~~~~~~~~~~~~~
2014  DEFINITION: An "implicit" TyThing is one that does not have its own
2015  IfaceDecl in an interface file.  Instead, its binding in the type
2016  environment is created as part of typechecking the IfaceDecl for
2017  some other thing.
2018
2019Examples:
2020  * All DataCons are implicit, because they are generated from the
2021    IfaceDecl for the data/newtype.  Ditto class methods.
2022
2023  * Record selectors are *not* implicit, because they get their own
2024    free-standing IfaceDecl.
2025
2026  * Associated data/type families are implicit because they are
2027    included in the IfaceDecl of the parent class.  (NB: the
2028    IfaceClass decl happens to use IfaceDecl recursively for the
2029    associated types, but that's irrelevant here.)
2030
2031  * Dictionary function Ids are not implicit.
2032
2033  * Axioms for newtypes are implicit (same as above), but axioms
2034    for data/type family instances are *not* implicit (like DFunIds).
2035-}
2036
2037-- | Determine the 'TyThing's brought into scope by another 'TyThing'
2038-- /other/ than itself. For example, Id's don't have any implicit TyThings
2039-- as they just bring themselves into scope, but classes bring their
2040-- dictionary datatype, type constructor and some selector functions into
2041-- scope, just for a start!
2042
2043-- N.B. the set of TyThings returned here *must* match the set of
2044-- names returned by LoadIface.ifaceDeclImplicitBndrs, in the sense that
2045-- TyThing.getOccName should define a bijection between the two lists.
2046-- This invariant is used in LoadIface.loadDecl (see note [Tricky iface loop])
2047-- The order of the list does not matter.
2048implicitTyThings :: TyThing -> [TyThing]
2049implicitTyThings (AnId _)       = []
2050implicitTyThings (ACoAxiom _cc) = []
2051implicitTyThings (ATyCon tc)    = implicitTyConThings tc
2052implicitTyThings (AConLike cl)  = implicitConLikeThings cl
2053
2054implicitConLikeThings :: ConLike -> [TyThing]
2055implicitConLikeThings (RealDataCon dc)
2056  = dataConImplicitTyThings dc
2057
2058implicitConLikeThings (PatSynCon {})
2059  = []  -- Pattern synonyms have no implicit Ids; the wrapper and matcher
2060        -- are not "implicit"; they are simply new top-level bindings,
2061        -- and they have their own declaration in an interface file
2062        -- Unless a record pat syn when there are implicit selectors
2063        -- They are still not included here as `implicitConLikeThings` is
2064        -- used by `tcTyClsDecls` whilst pattern synonyms are typed checked
2065        -- by `tcTopValBinds`.
2066
2067implicitClassThings :: Class -> [TyThing]
2068implicitClassThings cl
2069  = -- Does not include default methods, because those Ids may have
2070    --    their own pragmas, unfoldings etc, not derived from the Class object
2071
2072    -- associated types
2073    --    No recursive call for the classATs, because they
2074    --    are only the family decls; they have no implicit things
2075    map ATyCon (classATs cl) ++
2076
2077    -- superclass and operation selectors
2078    map AnId (classAllSelIds cl)
2079
2080implicitTyConThings :: TyCon -> [TyThing]
2081implicitTyConThings tc
2082  = class_stuff ++
2083      -- fields (names of selectors)
2084
2085      -- (possibly) implicit newtype axioms
2086      -- or type family axioms
2087    implicitCoTyCon tc ++
2088
2089      -- for each data constructor in order,
2090      --   the constructor, worker, and (possibly) wrapper
2091    [ thing | dc    <- tyConDataCons tc
2092            , thing <- AConLike (RealDataCon dc) : dataConImplicitTyThings dc ]
2093      -- NB. record selectors are *not* implicit, they have fully-fledged
2094      -- bindings that pass through the compilation pipeline as normal.
2095  where
2096    class_stuff = case tyConClass_maybe tc of
2097        Nothing -> []
2098        Just cl -> implicitClassThings cl
2099
2100-- For newtypes and closed type families (only) add the implicit coercion tycon
2101implicitCoTyCon :: TyCon -> [TyThing]
2102implicitCoTyCon tc
2103  | Just co <- newTyConCo_maybe tc = [ACoAxiom $ toBranchedAxiom co]
2104  | Just co <- isClosedSynFamilyTyConWithAxiom_maybe tc
2105                                   = [ACoAxiom co]
2106  | otherwise                      = []
2107
2108-- | Returns @True@ if there should be no interface-file declaration
2109-- for this thing on its own: either it is built-in, or it is part
2110-- of some other declaration, or it is generated implicitly by some
2111-- other declaration.
2112isImplicitTyThing :: TyThing -> Bool
2113isImplicitTyThing (AConLike cl) = case cl of
2114                                    RealDataCon {} -> True
2115                                    PatSynCon {}   -> False
2116isImplicitTyThing (AnId id)     = isImplicitId id
2117isImplicitTyThing (ATyCon tc)   = isImplicitTyCon tc
2118isImplicitTyThing (ACoAxiom ax) = isImplicitCoAxiom ax
2119
2120-- | tyThingParent_maybe x returns (Just p)
2121-- when pprTyThingInContext should print a declaration for p
2122-- (albeit with some "..." in it) when asked to show x
2123-- It returns the *immediate* parent.  So a datacon returns its tycon
2124-- but the tycon could be the associated type of a class, so it in turn
2125-- might have a parent.
2126tyThingParent_maybe :: TyThing -> Maybe TyThing
2127tyThingParent_maybe (AConLike cl) = case cl of
2128    RealDataCon dc  -> Just (ATyCon (dataConTyCon dc))
2129    PatSynCon{}     -> Nothing
2130tyThingParent_maybe (ATyCon tc)   = case tyConAssoc_maybe tc of
2131                                      Just tc -> Just (ATyCon tc)
2132                                      Nothing -> Nothing
2133tyThingParent_maybe (AnId id)     = case idDetails id of
2134                                      RecSelId { sel_tycon = RecSelData tc } ->
2135                                          Just (ATyCon tc)
2136                                      ClassOpId cls               ->
2137                                          Just (ATyCon (classTyCon cls))
2138                                      _other                      -> Nothing
2139tyThingParent_maybe _other = Nothing
2140
2141tyThingsTyCoVars :: [TyThing] -> TyCoVarSet
2142tyThingsTyCoVars tts =
2143    unionVarSets $ map ttToVarSet tts
2144    where
2145        ttToVarSet (AnId id)     = tyCoVarsOfType $ idType id
2146        ttToVarSet (AConLike cl) = case cl of
2147            RealDataCon dc  -> tyCoVarsOfType $ dataConRepType dc
2148            PatSynCon{}     -> emptyVarSet
2149        ttToVarSet (ATyCon tc)
2150          = case tyConClass_maybe tc of
2151              Just cls -> (mkVarSet . fst . classTvsFds) cls
2152              Nothing  -> tyCoVarsOfType $ tyConKind tc
2153        ttToVarSet (ACoAxiom _)  = emptyVarSet
2154
2155-- | The Names that a TyThing should bring into scope.  Used to build
2156-- the GlobalRdrEnv for the InteractiveContext.
2157tyThingAvailInfo :: TyThing -> [AvailInfo]
2158tyThingAvailInfo (ATyCon t)
2159   = case tyConClass_maybe t of
2160        Just c  -> [AvailTC n (n : map getName (classMethods c)
2161                                 ++ map getName (classATs c))
2162                             [] ]
2163             where n = getName c
2164        Nothing -> [AvailTC n (n : map getName dcs) flds]
2165             where n    = getName t
2166                   dcs  = tyConDataCons t
2167                   flds = tyConFieldLabels t
2168tyThingAvailInfo (AConLike (PatSynCon p))
2169  = map avail ((getName p) : map flSelector (patSynFieldLabels p))
2170tyThingAvailInfo t
2171   = [avail (getName t)]
2172
2173{-
2174************************************************************************
2175*                                                                      *
2176                TypeEnv
2177*                                                                      *
2178************************************************************************
2179-}
2180
2181-- | A map from 'Name's to 'TyThing's, constructed by typechecking
2182-- local declarations or interface files
2183type TypeEnv = NameEnv TyThing
2184
2185emptyTypeEnv    :: TypeEnv
2186typeEnvElts     :: TypeEnv -> [TyThing]
2187typeEnvTyCons   :: TypeEnv -> [TyCon]
2188typeEnvCoAxioms :: TypeEnv -> [CoAxiom Branched]
2189typeEnvIds      :: TypeEnv -> [Id]
2190typeEnvPatSyns  :: TypeEnv -> [PatSyn]
2191typeEnvDataCons :: TypeEnv -> [DataCon]
2192typeEnvClasses  :: TypeEnv -> [Class]
2193lookupTypeEnv   :: TypeEnv -> Name -> Maybe TyThing
2194
2195emptyTypeEnv        = emptyNameEnv
2196typeEnvElts     env = nameEnvElts env
2197typeEnvTyCons   env = [tc | ATyCon tc   <- typeEnvElts env]
2198typeEnvCoAxioms env = [ax | ACoAxiom ax <- typeEnvElts env]
2199typeEnvIds      env = [id | AnId id     <- typeEnvElts env]
2200typeEnvPatSyns  env = [ps | AConLike (PatSynCon ps) <- typeEnvElts env]
2201typeEnvDataCons env = [dc | AConLike (RealDataCon dc) <- typeEnvElts env]
2202typeEnvClasses  env = [cl | tc <- typeEnvTyCons env,
2203                            Just cl <- [tyConClass_maybe tc]]
2204
2205mkTypeEnv :: [TyThing] -> TypeEnv
2206mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
2207
2208mkTypeEnvWithImplicits :: [TyThing] -> TypeEnv
2209mkTypeEnvWithImplicits things =
2210  mkTypeEnv things
2211    `plusNameEnv`
2212  mkTypeEnv (concatMap implicitTyThings things)
2213
2214typeEnvFromEntities :: [Id] -> [TyCon] -> [FamInst] -> TypeEnv
2215typeEnvFromEntities ids tcs famInsts =
2216  mkTypeEnv (   map AnId ids
2217             ++ map ATyCon all_tcs
2218             ++ concatMap implicitTyConThings all_tcs
2219             ++ map (ACoAxiom . toBranchedAxiom . famInstAxiom) famInsts
2220            )
2221 where
2222  all_tcs = tcs ++ famInstsRepTyCons famInsts
2223
2224lookupTypeEnv = lookupNameEnv
2225
2226-- Extend the type environment
2227extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
2228extendTypeEnv env thing = extendNameEnv env (getName thing) thing
2229
2230extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
2231extendTypeEnvList env things = foldl' extendTypeEnv env things
2232
2233extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
2234extendTypeEnvWithIds env ids
2235  = extendNameEnvList env [(getName id, AnId id) | id <- ids]
2236
2237plusTypeEnv :: TypeEnv -> TypeEnv -> TypeEnv
2238plusTypeEnv env1 env2 = plusNameEnv env1 env2
2239
2240-- | Find the 'TyThing' for the given 'Name' by using all the resources
2241-- at our disposal: the compiled modules in the 'HomePackageTable' and the
2242-- compiled modules in other packages that live in 'PackageTypeEnv'. Note
2243-- that this does NOT look up the 'TyThing' in the module being compiled: you
2244-- have to do that yourself, if desired
2245lookupType :: DynFlags
2246           -> HomePackageTable
2247           -> PackageTypeEnv
2248           -> Name
2249           -> Maybe TyThing
2250
2251lookupType dflags hpt pte name
2252  | isOneShot (ghcMode dflags)  -- in one-shot, we don't use the HPT
2253  = lookupNameEnv pte name
2254  | otherwise
2255  = case lookupHptByModule hpt mod of
2256       Just hm -> lookupNameEnv (md_types (hm_details hm)) name
2257       Nothing -> lookupNameEnv pte name
2258  where
2259    mod = ASSERT2( isExternalName name, ppr name )
2260          if isHoleName name
2261            then mkModule (thisPackage dflags) (moduleName (nameModule name))
2262            else nameModule name
2263
2264-- | As 'lookupType', but with a marginally easier-to-use interface
2265-- if you have a 'HscEnv'
2266lookupTypeHscEnv :: HscEnv -> Name -> IO (Maybe TyThing)
2267lookupTypeHscEnv hsc_env name = do
2268    eps <- readIORef (hsc_EPS hsc_env)
2269    return $! lookupType dflags hpt (eps_PTE eps) name
2270  where
2271    dflags = hsc_dflags hsc_env
2272    hpt = hsc_HPT hsc_env
2273
2274-- | Get the 'TyCon' from a 'TyThing' if it is a type constructor thing. Panics otherwise
2275tyThingTyCon :: TyThing -> TyCon
2276tyThingTyCon (ATyCon tc) = tc
2277tyThingTyCon other       = pprPanic "tyThingTyCon" (ppr other)
2278
2279-- | Get the 'CoAxiom' from a 'TyThing' if it is a coercion axiom thing. Panics otherwise
2280tyThingCoAxiom :: TyThing -> CoAxiom Branched
2281tyThingCoAxiom (ACoAxiom ax) = ax
2282tyThingCoAxiom other         = pprPanic "tyThingCoAxiom" (ppr other)
2283
2284-- | Get the 'DataCon' from a 'TyThing' if it is a data constructor thing. Panics otherwise
2285tyThingDataCon :: TyThing -> DataCon
2286tyThingDataCon (AConLike (RealDataCon dc)) = dc
2287tyThingDataCon other                       = pprPanic "tyThingDataCon" (ppr other)
2288
2289-- | Get the 'ConLike' from a 'TyThing' if it is a data constructor thing.
2290-- Panics otherwise
2291tyThingConLike :: TyThing -> ConLike
2292tyThingConLike (AConLike dc) = dc
2293tyThingConLike other         = pprPanic "tyThingConLike" (ppr other)
2294
2295-- | Get the 'Id' from a 'TyThing' if it is a id *or* data constructor thing. Panics otherwise
2296tyThingId :: TyThing -> Id
2297tyThingId (AnId id)                   = id
2298tyThingId (AConLike (RealDataCon dc)) = dataConWrapId dc
2299tyThingId other                       = pprPanic "tyThingId" (ppr other)
2300
2301{-
2302************************************************************************
2303*                                                                      *
2304\subsection{MonadThings and friends}
2305*                                                                      *
2306************************************************************************
2307-}
2308
2309-- | Class that abstracts out the common ability of the monads in GHC
2310-- to lookup a 'TyThing' in the monadic environment by 'Name'. Provides
2311-- a number of related convenience functions for accessing particular
2312-- kinds of 'TyThing'
2313class Monad m => MonadThings m where
2314        lookupThing :: Name -> m TyThing
2315
2316        lookupId :: Name -> m Id
2317        lookupId = liftM tyThingId . lookupThing
2318
2319        lookupDataCon :: Name -> m DataCon
2320        lookupDataCon = liftM tyThingDataCon . lookupThing
2321
2322        lookupTyCon :: Name -> m TyCon
2323        lookupTyCon = liftM tyThingTyCon . lookupThing
2324
2325{-
2326************************************************************************
2327*                                                                      *
2328\subsection{Auxiliary types}
2329*                                                                      *
2330************************************************************************
2331
2332These types are defined here because they are mentioned in ModDetails,
2333but they are mostly elaborated elsewhere
2334-}
2335
2336------------------ Warnings -------------------------
2337-- | Warning information for a module
2338data Warnings
2339  = NoWarnings                          -- ^ Nothing deprecated
2340  | WarnAll WarningTxt                  -- ^ Whole module deprecated
2341  | WarnSome [(OccName,WarningTxt)]     -- ^ Some specific things deprecated
2342
2343     -- Only an OccName is needed because
2344     --    (1) a deprecation always applies to a binding
2345     --        defined in the module in which the deprecation appears.
2346     --    (2) deprecations are only reported outside the defining module.
2347     --        this is important because, otherwise, if we saw something like
2348     --
2349     --        {-# DEPRECATED f "" #-}
2350     --        f = ...
2351     --        h = f
2352     --        g = let f = undefined in f
2353     --
2354     --        we'd need more information than an OccName to know to say something
2355     --        about the use of f in h but not the use of the locally bound f in g
2356     --
2357     --        however, because we only report about deprecations from the outside,
2358     --        and a module can only export one value called f,
2359     --        an OccName suffices.
2360     --
2361     --        this is in contrast with fixity declarations, where we need to map
2362     --        a Name to its fixity declaration.
2363  deriving( Eq )
2364
2365instance Binary Warnings where
2366    put_ bh NoWarnings     = putByte bh 0
2367    put_ bh (WarnAll t) = do
2368            putByte bh 1
2369            put_ bh t
2370    put_ bh (WarnSome ts) = do
2371            putByte bh 2
2372            put_ bh ts
2373
2374    get bh = do
2375            h <- getByte bh
2376            case h of
2377              0 -> return NoWarnings
2378              1 -> do aa <- get bh
2379                      return (WarnAll aa)
2380              _ -> do aa <- get bh
2381                      return (WarnSome aa)
2382
2383-- | Constructs the cache for the 'mi_warn_fn' field of a 'ModIface'
2384mkIfaceWarnCache :: Warnings -> OccName -> Maybe WarningTxt
2385mkIfaceWarnCache NoWarnings  = \_ -> Nothing
2386mkIfaceWarnCache (WarnAll t) = \_ -> Just t
2387mkIfaceWarnCache (WarnSome pairs) = lookupOccEnv (mkOccEnv pairs)
2388
2389emptyIfaceWarnCache :: OccName -> Maybe WarningTxt
2390emptyIfaceWarnCache _ = Nothing
2391
2392plusWarns :: Warnings -> Warnings -> Warnings
2393plusWarns d NoWarnings = d
2394plusWarns NoWarnings d = d
2395plusWarns _ (WarnAll t) = WarnAll t
2396plusWarns (WarnAll t) _ = WarnAll t
2397plusWarns (WarnSome v1) (WarnSome v2) = WarnSome (v1 ++ v2)
2398
2399-- | Creates cached lookup for the 'mi_fix_fn' field of 'ModIface'
2400mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Maybe Fixity
2401mkIfaceFixCache pairs
2402  = \n -> lookupOccEnv env n
2403  where
2404   env = mkOccEnv pairs
2405
2406emptyIfaceFixCache :: OccName -> Maybe Fixity
2407emptyIfaceFixCache _ = Nothing
2408
2409-- | Fixity environment mapping names to their fixities
2410type FixityEnv = NameEnv FixItem
2411
2412-- | Fixity information for an 'Name'. We keep the OccName in the range
2413-- so that we can generate an interface from it
2414data FixItem = FixItem OccName Fixity
2415
2416instance Outputable FixItem where
2417  ppr (FixItem occ fix) = ppr fix <+> ppr occ
2418
2419emptyFixityEnv :: FixityEnv
2420emptyFixityEnv = emptyNameEnv
2421
2422lookupFixity :: FixityEnv -> Name -> Fixity
2423lookupFixity env n = case lookupNameEnv env n of
2424                        Just (FixItem _ fix) -> fix
2425                        Nothing         -> defaultFixity
2426
2427{-
2428************************************************************************
2429*                                                                      *
2430\subsection{WhatsImported}
2431*                                                                      *
2432************************************************************************
2433-}
2434
2435-- | Records whether a module has orphans. An \"orphan\" is one of:
2436--
2437-- * An instance declaration in a module other than the definition
2438--   module for one of the type constructors or classes in the instance head
2439--
2440-- * A transformation rule in a module other than the one defining
2441--   the function in the head of the rule
2442--
2443type WhetherHasOrphans   = Bool
2444
2445-- | Does this module define family instances?
2446type WhetherHasFamInst = Bool
2447
2448-- | Did this module originate from a *-boot file?
2449type IsBootInterface = Bool
2450
2451-- | Dependency information about ALL modules and packages below this one
2452-- in the import hierarchy.
2453--
2454-- Invariant: the dependencies of a module @M@ never includes @M@.
2455--
2456-- Invariant: none of the lists contain duplicates.
2457data Dependencies
2458  = Deps { dep_mods   :: [(ModuleName, IsBootInterface)]
2459                        -- ^ All home-package modules transitively below this one
2460                        -- I.e. modules that this one imports, or that are in the
2461                        --      dep_mods of those directly-imported modules
2462
2463         , dep_pkgs   :: [(InstalledUnitId, Bool)]
2464                        -- ^ All packages transitively below this module
2465                        -- I.e. packages to which this module's direct imports belong,
2466                        --      or that are in the dep_pkgs of those modules
2467                        -- The bool indicates if the package is required to be
2468                        -- trusted when the module is imported as a safe import
2469                        -- (Safe Haskell). See Note [RnNames . Tracking Trust Transitively]
2470
2471         , dep_orphs  :: [Module]
2472                        -- ^ Transitive closure of orphan modules (whether
2473                        -- home or external pkg).
2474                        --
2475                        -- (Possible optimization: don't include family
2476                        -- instance orphans as they are anyway included in
2477                        -- 'dep_finsts'.  But then be careful about code
2478                        -- which relies on dep_orphs having the complete list!)
2479                        -- This does NOT include us, unlike 'imp_orphs'.
2480
2481         , dep_finsts :: [Module]
2482                        -- ^ Transitive closure of depended upon modules which
2483                        -- contain family instances (whether home or external).
2484                        -- This is used by 'checkFamInstConsistency'.  This
2485                        -- does NOT include us, unlike 'imp_finsts'. See Note
2486                        -- [The type family instance consistency story].
2487
2488         , dep_plgins :: [ModuleName]
2489                        -- ^ All the plugins used while compiling this module.
2490         }
2491  deriving( Eq )
2492        -- Equality used only for old/new comparison in MkIface.addFingerprints
2493        -- See 'TcRnTypes.ImportAvails' for details on dependencies.
2494
2495instance Binary Dependencies where
2496    put_ bh deps = do put_ bh (dep_mods deps)
2497                      put_ bh (dep_pkgs deps)
2498                      put_ bh (dep_orphs deps)
2499                      put_ bh (dep_finsts deps)
2500                      put_ bh (dep_plgins deps)
2501
2502    get bh = do ms <- get bh
2503                ps <- get bh
2504                os <- get bh
2505                fis <- get bh
2506                pl <- get bh
2507                return (Deps { dep_mods = ms, dep_pkgs = ps, dep_orphs = os,
2508                               dep_finsts = fis, dep_plgins = pl })
2509
2510noDependencies :: Dependencies
2511noDependencies = Deps [] [] [] [] []
2512
2513-- | Records modules for which changes may force recompilation of this module
2514-- See wiki: https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/recompilation-avoidance
2515--
2516-- This differs from Dependencies.  A module X may be in the dep_mods of this
2517-- module (via an import chain) but if we don't use anything from X it won't
2518-- appear in our Usage
2519data Usage
2520  -- | Module from another package
2521  = UsagePackageModule {
2522        usg_mod      :: Module,
2523           -- ^ External package module depended on
2524        usg_mod_hash :: Fingerprint,
2525            -- ^ Cached module fingerprint
2526        usg_safe :: IsSafeImport
2527            -- ^ Was this module imported as a safe import
2528    }
2529  -- | Module from the current package
2530  | UsageHomeModule {
2531        usg_mod_name :: ModuleName,
2532            -- ^ Name of the module
2533        usg_mod_hash :: Fingerprint,
2534            -- ^ Cached module fingerprint
2535        usg_entities :: [(OccName,Fingerprint)],
2536            -- ^ Entities we depend on, sorted by occurrence name and fingerprinted.
2537            -- NB: usages are for parent names only, e.g. type constructors
2538            -- but not the associated data constructors.
2539        usg_exports  :: Maybe Fingerprint,
2540            -- ^ Fingerprint for the export list of this module,
2541            -- if we directly imported it (and hence we depend on its export list)
2542        usg_safe :: IsSafeImport
2543            -- ^ Was this module imported as a safe import
2544    }                                           -- ^ Module from the current package
2545  -- | A file upon which the module depends, e.g. a CPP #include, or using TH's
2546  -- 'addDependentFile'
2547  | UsageFile {
2548        usg_file_path  :: FilePath,
2549        -- ^ External file dependency. From a CPP #include or TH
2550        -- addDependentFile. Should be absolute.
2551        usg_file_hash  :: Fingerprint
2552        -- ^ 'Fingerprint' of the file contents.
2553
2554        -- Note: We don't consider things like modification timestamps
2555        -- here, because there's no reason to recompile if the actual
2556        -- contents don't change.  This previously lead to odd
2557        -- recompilation behaviors; see #8114
2558  }
2559  -- | A requirement which was merged into this one.
2560  | UsageMergedRequirement {
2561        usg_mod :: Module,
2562        usg_mod_hash :: Fingerprint
2563  }
2564    deriving( Eq )
2565        -- The export list field is (Just v) if we depend on the export list:
2566        --      i.e. we imported the module directly, whether or not we
2567        --           enumerated the things we imported, or just imported
2568        --           everything
2569        -- We need to recompile if M's exports change, because
2570        -- if the import was    import M,       we might now have a name clash
2571        --                                      in the importing module.
2572        -- if the import was    import M(x)     M might no longer export x
2573        -- The only way we don't depend on the export list is if we have
2574        --                      import M()
2575        -- And of course, for modules that aren't imported directly we don't
2576        -- depend on their export lists
2577
2578instance Binary Usage where
2579    put_ bh usg@UsagePackageModule{} = do
2580        putByte bh 0
2581        put_ bh (usg_mod usg)
2582        put_ bh (usg_mod_hash usg)
2583        put_ bh (usg_safe     usg)
2584
2585    put_ bh usg@UsageHomeModule{} = do
2586        putByte bh 1
2587        put_ bh (usg_mod_name usg)
2588        put_ bh (usg_mod_hash usg)
2589        put_ bh (usg_exports  usg)
2590        put_ bh (usg_entities usg)
2591        put_ bh (usg_safe     usg)
2592
2593    put_ bh usg@UsageFile{} = do
2594        putByte bh 2
2595        put_ bh (usg_file_path usg)
2596        put_ bh (usg_file_hash usg)
2597
2598    put_ bh usg@UsageMergedRequirement{} = do
2599        putByte bh 3
2600        put_ bh (usg_mod      usg)
2601        put_ bh (usg_mod_hash usg)
2602
2603    get bh = do
2604        h <- getByte bh
2605        case h of
2606          0 -> do
2607            nm    <- get bh
2608            mod   <- get bh
2609            safe  <- get bh
2610            return UsagePackageModule { usg_mod = nm, usg_mod_hash = mod, usg_safe = safe }
2611          1 -> do
2612            nm    <- get bh
2613            mod   <- get bh
2614            exps  <- get bh
2615            ents  <- get bh
2616            safe  <- get bh
2617            return UsageHomeModule { usg_mod_name = nm, usg_mod_hash = mod,
2618                     usg_exports = exps, usg_entities = ents, usg_safe = safe }
2619          2 -> do
2620            fp   <- get bh
2621            hash <- get bh
2622            return UsageFile { usg_file_path = fp, usg_file_hash = hash }
2623          3 -> do
2624            mod <- get bh
2625            hash <- get bh
2626            return UsageMergedRequirement { usg_mod = mod, usg_mod_hash = hash }
2627          i -> error ("Binary.get(Usage): " ++ show i)
2628
2629{-
2630************************************************************************
2631*                                                                      *
2632                The External Package State
2633*                                                                      *
2634************************************************************************
2635-}
2636
2637type PackageTypeEnv          = TypeEnv
2638type PackageRuleBase         = RuleBase
2639type PackageInstEnv          = InstEnv
2640type PackageFamInstEnv       = FamInstEnv
2641type PackageAnnEnv           = AnnEnv
2642type PackageCompleteMatchMap = CompleteMatchMap
2643
2644-- | Information about other packages that we have slurped in by reading
2645-- their interface files
2646data ExternalPackageState
2647  = EPS {
2648        eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface)),
2649                -- ^ In OneShot mode (only), home-package modules
2650                -- accumulate in the external package state, and are
2651                -- sucked in lazily.  For these home-pkg modules
2652                -- (only) we need to record which are boot modules.
2653                -- We set this field after loading all the
2654                -- explicitly-imported interfaces, but before doing
2655                -- anything else
2656                --
2657                -- The 'ModuleName' part is not necessary, but it's useful for
2658                -- debug prints, and it's convenient because this field comes
2659                -- direct from 'TcRnTypes.imp_dep_mods'
2660
2661        eps_PIT :: !PackageIfaceTable,
2662                -- ^ The 'ModIface's for modules in external packages
2663                -- whose interfaces we have opened.
2664                -- The declarations in these interface files are held in the
2665                -- 'eps_decls', 'eps_inst_env', 'eps_fam_inst_env' and 'eps_rules'
2666                -- fields of this record, not in the 'mi_decls' fields of the
2667                -- interface we have sucked in.
2668                --
2669                -- What /is/ in the PIT is:
2670                --
2671                -- * The Module
2672                --
2673                -- * Fingerprint info
2674                --
2675                -- * Its exports
2676                --
2677                -- * Fixities
2678                --
2679                -- * Deprecations and warnings
2680
2681        eps_free_holes :: InstalledModuleEnv (UniqDSet ModuleName),
2682                -- ^ Cache for 'mi_free_holes'.  Ordinarily, we can rely on
2683                -- the 'eps_PIT' for this information, EXCEPT that when
2684                -- we do dependency analysis, we need to look at the
2685                -- 'Dependencies' of our imports to determine what their
2686                -- precise free holes are ('moduleFreeHolesPrecise').  We
2687                -- don't want to repeatedly reread in the interface
2688                -- for every import, so cache it here.  When the PIT
2689                -- gets filled in we can drop these entries.
2690
2691        eps_PTE :: !PackageTypeEnv,
2692                -- ^ Result of typechecking all the external package
2693                -- interface files we have sucked in. The domain of
2694                -- the mapping is external-package modules
2695
2696        eps_inst_env     :: !PackageInstEnv,   -- ^ The total 'InstEnv' accumulated
2697                                               -- from all the external-package modules
2698        eps_fam_inst_env :: !PackageFamInstEnv,-- ^ The total 'FamInstEnv' accumulated
2699                                               -- from all the external-package modules
2700        eps_rule_base    :: !PackageRuleBase,  -- ^ The total 'RuleEnv' accumulated
2701                                               -- from all the external-package modules
2702        eps_ann_env      :: !PackageAnnEnv,    -- ^ The total 'AnnEnv' accumulated
2703                                               -- from all the external-package modules
2704        eps_complete_matches :: !PackageCompleteMatchMap,
2705                                  -- ^ The total 'CompleteMatchMap' accumulated
2706                                  -- from all the external-package modules
2707
2708        eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv), -- ^ The family instances accumulated from external
2709                                                         -- packages, keyed off the module that declared them
2710
2711        eps_stats :: !EpsStats                 -- ^ Stastics about what was loaded from external packages
2712  }
2713
2714-- | Accumulated statistics about what we are putting into the 'ExternalPackageState'.
2715-- \"In\" means stuff that is just /read/ from interface files,
2716-- \"Out\" means actually sucked in and type-checked
2717data EpsStats = EpsStats { n_ifaces_in
2718                         , n_decls_in, n_decls_out
2719                         , n_rules_in, n_rules_out
2720                         , n_insts_in, n_insts_out :: !Int }
2721
2722addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
2723-- ^ Add stats for one newly-read interface
2724addEpsInStats stats n_decls n_insts n_rules
2725  = stats { n_ifaces_in = n_ifaces_in stats + 1
2726          , n_decls_in  = n_decls_in stats + n_decls
2727          , n_insts_in  = n_insts_in stats + n_insts
2728          , n_rules_in  = n_rules_in stats + n_rules }
2729
2730{-
2731Names in a NameCache are always stored as a Global, and have the SrcLoc
2732of their binding locations.
2733
2734Actually that's not quite right.  When we first encounter the original
2735name, we might not be at its binding site (e.g. we are reading an
2736interface file); so we give it 'noSrcLoc' then.  Later, when we find
2737its binding site, we fix it up.
2738-}
2739
2740updNameCache :: IORef NameCache
2741             -> (NameCache -> (NameCache, c))  -- The updating function
2742             -> IO c
2743updNameCache ncRef upd_fn
2744  = atomicModifyIORef' ncRef upd_fn
2745
2746mkSOName :: Platform -> FilePath -> FilePath
2747mkSOName platform root
2748    = case platformOS platform of
2749      OSMinGW32 ->           root  <.> soExt platform
2750      _         -> ("lib" ++ root) <.> soExt platform
2751
2752mkHsSOName :: Platform -> FilePath -> FilePath
2753mkHsSOName platform root = ("lib" ++ root) <.> soExt platform
2754
2755soExt :: Platform -> FilePath
2756soExt platform
2757    = case platformOS platform of
2758      OSDarwin  -> "dylib"
2759      OSMinGW32 -> "dll"
2760      _         -> "so"
2761
2762{-
2763************************************************************************
2764*                                                                      *
2765                The module graph and ModSummary type
2766        A ModSummary is a node in the compilation manager's
2767        dependency graph, and it's also passed to hscMain
2768*                                                                      *
2769************************************************************************
2770-}
2771
2772-- | A ModuleGraph contains all the nodes from the home package (only).
2773-- There will be a node for each source module, plus a node for each hi-boot
2774-- module.
2775--
2776-- The graph is not necessarily stored in topologically-sorted order.  Use
2777-- 'GHC.topSortModuleGraph' and 'Digraph.flattenSCC' to achieve this.
2778data ModuleGraph = ModuleGraph
2779  { mg_mss :: [ModSummary]
2780  , mg_non_boot :: ModuleEnv ModSummary
2781    -- a map of all non-boot ModSummaries keyed by Modules
2782  , mg_boot :: ModuleSet
2783    -- a set of boot Modules
2784  , mg_needs_th_or_qq :: !Bool
2785    -- does any of the modules in mg_mss require TemplateHaskell or
2786    -- QuasiQuotes?
2787  }
2788
2789-- | Determines whether a set of modules requires Template Haskell or
2790-- Quasi Quotes
2791--
2792-- Note that if the session's 'DynFlags' enabled Template Haskell when
2793-- 'depanal' was called, then each module in the returned module graph will
2794-- have Template Haskell enabled whether it is actually needed or not.
2795needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
2796needsTemplateHaskellOrQQ mg = mg_needs_th_or_qq mg
2797
2798-- | Map a function 'f' over all the 'ModSummaries'.
2799-- To preserve invariants 'f' can't change the isBoot status.
2800mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
2801mapMG f mg@ModuleGraph{..} = mg
2802  { mg_mss = map f mg_mss
2803  , mg_non_boot = mapModuleEnv f mg_non_boot
2804  }
2805
2806mgBootModules :: ModuleGraph -> ModuleSet
2807mgBootModules ModuleGraph{..} = mg_boot
2808
2809mgModSummaries :: ModuleGraph -> [ModSummary]
2810mgModSummaries = mg_mss
2811
2812mgElemModule :: ModuleGraph -> Module -> Bool
2813mgElemModule ModuleGraph{..} m = elemModuleEnv m mg_non_boot
2814
2815-- | Look up a ModSummary in the ModuleGraph
2816mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
2817mgLookupModule ModuleGraph{..} m = lookupModuleEnv mg_non_boot m
2818
2819emptyMG :: ModuleGraph
2820emptyMG = ModuleGraph [] emptyModuleEnv emptyModuleSet False
2821
2822isTemplateHaskellOrQQNonBoot :: ModSummary -> Bool
2823isTemplateHaskellOrQQNonBoot ms =
2824  (xopt LangExt.TemplateHaskell (ms_hspp_opts ms)
2825    || xopt LangExt.QuasiQuotes (ms_hspp_opts ms)) &&
2826  not (isBootSummary ms)
2827
2828-- | Add a ModSummary to ModuleGraph. Assumes that the new ModSummary is
2829-- not an element of the ModuleGraph.
2830extendMG :: ModuleGraph -> ModSummary -> ModuleGraph
2831extendMG ModuleGraph{..} ms = ModuleGraph
2832  { mg_mss = ms:mg_mss
2833  , mg_non_boot = if isBootSummary ms
2834      then mg_non_boot
2835      else extendModuleEnv mg_non_boot (ms_mod ms) ms
2836  , mg_boot = if isBootSummary ms
2837      then extendModuleSet mg_boot (ms_mod ms)
2838      else mg_boot
2839  , mg_needs_th_or_qq = mg_needs_th_or_qq || isTemplateHaskellOrQQNonBoot ms
2840  }
2841
2842mkModuleGraph :: [ModSummary] -> ModuleGraph
2843mkModuleGraph = foldr (flip extendMG) emptyMG
2844
2845-- | A single node in a 'ModuleGraph'. The nodes of the module graph
2846-- are one of:
2847--
2848-- * A regular Haskell source module
2849-- * A hi-boot source module
2850--
2851data ModSummary
2852   = ModSummary {
2853        ms_mod          :: Module,
2854          -- ^ Identity of the module
2855        ms_hsc_src      :: HscSource,
2856          -- ^ The module source either plain Haskell or hs-boot
2857        ms_location     :: ModLocation,
2858          -- ^ Location of the various files belonging to the module
2859        ms_hs_date      :: UTCTime,
2860          -- ^ Timestamp of source file
2861        ms_obj_date     :: Maybe UTCTime,
2862          -- ^ Timestamp of object, if we have one
2863        ms_iface_date   :: Maybe UTCTime,
2864          -- ^ Timestamp of hi file, if we *only* are typechecking (it is
2865          -- 'Nothing' otherwise.
2866          -- See Note [Recompilation checking in -fno-code mode] and #9243
2867        ms_hie_date   :: Maybe UTCTime,
2868          -- ^ Timestamp of hie file, if we have one
2869        ms_srcimps      :: [(Maybe FastString, Located ModuleName)],
2870          -- ^ Source imports of the module
2871        ms_textual_imps :: [(Maybe FastString, Located ModuleName)],
2872          -- ^ Non-source imports of the module from the module *text*
2873        ms_parsed_mod   :: Maybe HsParsedModule,
2874          -- ^ The parsed, nonrenamed source, if we have it.  This is also
2875          -- used to support "inline module syntax" in Backpack files.
2876        ms_hspp_file    :: FilePath,
2877          -- ^ Filename of preprocessed source file
2878        ms_hspp_opts    :: DynFlags,
2879          -- ^ Cached flags from @OPTIONS@, @INCLUDE@ and @LANGUAGE@
2880          -- pragmas in the modules source code
2881        ms_hspp_buf     :: Maybe StringBuffer
2882          -- ^ The actual preprocessed source, if we have it
2883     }
2884
2885ms_installed_mod :: ModSummary -> InstalledModule
2886ms_installed_mod = fst . splitModuleInsts . ms_mod
2887
2888ms_mod_name :: ModSummary -> ModuleName
2889ms_mod_name = moduleName . ms_mod
2890
2891ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
2892ms_imps ms =
2893  ms_textual_imps ms ++
2894  map mk_additional_import (dynFlagDependencies (ms_hspp_opts ms))
2895  where
2896    mk_additional_import mod_nm = (Nothing, noLoc mod_nm)
2897
2898home_imps :: [(Maybe FastString, Located ModuleName)] -> [Located ModuleName]
2899home_imps imps = [ lmodname |  (mb_pkg, lmodname) <- imps,
2900                                  isLocal mb_pkg ]
2901  where isLocal Nothing = True
2902        isLocal (Just pkg) | pkg == fsLit "this" = True -- "this" is special
2903        isLocal _ = False
2904
2905ms_home_allimps :: ModSummary -> [ModuleName]
2906ms_home_allimps ms = map unLoc (ms_home_srcimps ms ++ ms_home_imps ms)
2907
2908-- | Like 'ms_home_imps', but for SOURCE imports.
2909ms_home_srcimps :: ModSummary -> [Located ModuleName]
2910ms_home_srcimps = home_imps . ms_srcimps
2911
2912-- | All of the (possibly) home module imports from a
2913-- 'ModSummary'; that is to say, each of these module names
2914-- could be a home import if an appropriately named file
2915-- existed.  (This is in contrast to package qualified
2916-- imports, which are guaranteed not to be home imports.)
2917ms_home_imps :: ModSummary -> [Located ModuleName]
2918ms_home_imps = home_imps . ms_imps
2919
2920-- The ModLocation contains both the original source filename and the
2921-- filename of the cleaned-up source file after all preprocessing has been
2922-- done.  The point is that the summariser will have to cpp/unlit/whatever
2923-- all files anyway, and there's no point in doing this twice -- just
2924-- park the result in a temp file, put the name of it in the location,
2925-- and let @compile@ read from that file on the way back up.
2926
2927-- The ModLocation is stable over successive up-sweeps in GHCi, wheres
2928-- the ms_hs_date and imports can, of course, change
2929
2930msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
2931msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
2932msHiFilePath  ms = ml_hi_file  (ms_location ms)
2933msObjFilePath ms = ml_obj_file (ms_location ms)
2934
2935msDynObjFilePath :: ModSummary -> DynFlags -> FilePath
2936msDynObjFilePath ms dflags = dynamicOutputFile dflags (msObjFilePath ms)
2937
2938-- | Did this 'ModSummary' originate from a hs-boot file?
2939isBootSummary :: ModSummary -> Bool
2940isBootSummary ms = ms_hsc_src ms == HsBootFile
2941
2942instance Outputable ModSummary where
2943   ppr ms
2944      = sep [text "ModSummary {",
2945             nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
2946                          text "ms_mod =" <+> ppr (ms_mod ms)
2947                                <> text (hscSourceString (ms_hsc_src ms)) <> comma,
2948                          text "ms_textual_imps =" <+> ppr (ms_textual_imps ms),
2949                          text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
2950             char '}'
2951            ]
2952
2953showModMsg :: DynFlags -> HscTarget -> Bool -> ModSummary -> String
2954showModMsg dflags target recomp mod_summary = showSDoc dflags $
2955   if gopt Opt_HideSourcePaths dflags
2956      then text mod_str
2957      else hsep $
2958         [ text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' ')
2959         , char '('
2960         , text (op $ msHsFilePath mod_summary) <> char ','
2961         ] ++
2962         if gopt Opt_BuildDynamicToo dflags
2963            then [ text obj_file <> char ','
2964                 , text dyn_file
2965                 , char ')'
2966                 ]
2967            else [ text obj_file, char ')' ]
2968  where
2969    op       = normalise
2970    mod      = moduleName (ms_mod mod_summary)
2971    mod_str  = showPpr dflags mod ++ hscSourceString (ms_hsc_src mod_summary)
2972    dyn_file = op $ msDynObjFilePath mod_summary dflags
2973    obj_file = case target of
2974                HscInterpreted | recomp -> "interpreted"
2975                HscNothing              -> "nothing"
2976                _                       -> (op $ msObjFilePath mod_summary)
2977
2978{-
2979************************************************************************
2980*                                                                      *
2981\subsection{Recompilation}
2982*                                                                      *
2983************************************************************************
2984-}
2985
2986-- | Indicates whether a given module's source has been modified since it
2987-- was last compiled.
2988data SourceModified
2989  = SourceModified
2990       -- ^ the source has been modified
2991  | SourceUnmodified
2992       -- ^ the source has not been modified.  Compilation may or may
2993       -- not be necessary, depending on whether any dependencies have
2994       -- changed since we last compiled.
2995  | SourceUnmodifiedAndStable
2996       -- ^ the source has not been modified, and furthermore all of
2997       -- its (transitive) dependencies are up to date; it definitely
2998       -- does not need to be recompiled.  This is important for two
2999       -- reasons: (a) we can omit the version check in checkOldIface,
3000       -- and (b) if the module used TH splices we don't need to force
3001       -- recompilation.
3002
3003{-
3004************************************************************************
3005*                                                                      *
3006\subsection{Hpc Support}
3007*                                                                      *
3008************************************************************************
3009-}
3010
3011-- | Information about a modules use of Haskell Program Coverage
3012data HpcInfo
3013  = HpcInfo
3014     { hpcInfoTickCount :: Int
3015     , hpcInfoHash      :: Int
3016     }
3017  | NoHpcInfo
3018     { hpcUsed          :: AnyHpcUsage  -- ^ Is hpc used anywhere on the module \*tree\*?
3019     }
3020
3021-- | This is used to signal if one of my imports used HPC instrumentation
3022-- even if there is no module-local HPC usage
3023type AnyHpcUsage = Bool
3024
3025emptyHpcInfo :: AnyHpcUsage -> HpcInfo
3026emptyHpcInfo = NoHpcInfo
3027
3028-- | Find out if HPC is used by this module or any of the modules
3029-- it depends upon
3030isHpcUsed :: HpcInfo -> AnyHpcUsage
3031isHpcUsed (HpcInfo {})                   = True
3032isHpcUsed (NoHpcInfo { hpcUsed = used }) = used
3033
3034{-
3035************************************************************************
3036*                                                                      *
3037\subsection{Safe Haskell Support}
3038*                                                                      *
3039************************************************************************
3040
3041This stuff here is related to supporting the Safe Haskell extension,
3042primarily about storing under what trust type a module has been compiled.
3043-}
3044
3045-- | Is an import a safe import?
3046type IsSafeImport = Bool
3047
3048-- | Safe Haskell information for 'ModIface'
3049-- Simply a wrapper around SafeHaskellMode to sepperate iface and flags
3050newtype IfaceTrustInfo = TrustInfo SafeHaskellMode
3051
3052getSafeMode :: IfaceTrustInfo -> SafeHaskellMode
3053getSafeMode (TrustInfo x) = x
3054
3055setSafeMode :: SafeHaskellMode -> IfaceTrustInfo
3056setSafeMode = TrustInfo
3057
3058noIfaceTrustInfo :: IfaceTrustInfo
3059noIfaceTrustInfo = setSafeMode Sf_None
3060
3061trustInfoToNum :: IfaceTrustInfo -> Word8
3062trustInfoToNum it
3063  = case getSafeMode it of
3064            Sf_None         -> 0
3065            Sf_Unsafe       -> 1
3066            Sf_Trustworthy  -> 2
3067            Sf_Safe         -> 3
3068            Sf_SafeInferred -> 4
3069            Sf_Ignore       -> 0
3070
3071numToTrustInfo :: Word8 -> IfaceTrustInfo
3072numToTrustInfo 0 = setSafeMode Sf_None
3073numToTrustInfo 1 = setSafeMode Sf_Unsafe
3074numToTrustInfo 2 = setSafeMode Sf_Trustworthy
3075numToTrustInfo 3 = setSafeMode Sf_Safe
3076numToTrustInfo 4 = setSafeMode Sf_SafeInferred
3077numToTrustInfo n = error $ "numToTrustInfo: bad input number! (" ++ show n ++ ")"
3078
3079instance Outputable IfaceTrustInfo where
3080    ppr (TrustInfo Sf_None)          = text "none"
3081    ppr (TrustInfo Sf_Ignore)        = text "none"
3082    ppr (TrustInfo Sf_Unsafe)        = text "unsafe"
3083    ppr (TrustInfo Sf_Trustworthy)   = text "trustworthy"
3084    ppr (TrustInfo Sf_Safe)          = text "safe"
3085    ppr (TrustInfo Sf_SafeInferred)  = text "safe-inferred"
3086
3087instance Binary IfaceTrustInfo where
3088    put_ bh iftrust = putByte bh $ trustInfoToNum iftrust
3089    get bh = getByte bh >>= (return . numToTrustInfo)
3090
3091{-
3092************************************************************************
3093*                                                                      *
3094\subsection{Parser result}
3095*                                                                      *
3096************************************************************************
3097-}
3098
3099data HsParsedModule = HsParsedModule {
3100    hpm_module    :: Located (HsModule GhcPs),
3101    hpm_src_files :: [FilePath],
3102       -- ^ extra source files (e.g. from #includes).  The lexer collects
3103       -- these from '# <file> <line>' pragmas, which the C preprocessor
3104       -- leaves behind.  These files and their timestamps are stored in
3105       -- the .hi file, so that we can force recompilation if any of
3106       -- them change (#3589)
3107    hpm_annotations :: ApiAnns
3108    -- See note [Api annotations] in ApiAnnotation.hs
3109  }
3110
3111{-
3112************************************************************************
3113*                                                                      *
3114\subsection{Linkable stuff}
3115*                                                                      *
3116************************************************************************
3117
3118This stuff is in here, rather than (say) in Linker.hs, because the Linker.hs
3119stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
3120-}
3121
3122isObjectLinkable :: Linkable -> Bool
3123isObjectLinkable l = not (null unlinked) && all isObject unlinked
3124  where unlinked = linkableUnlinked l
3125        -- A linkable with no Unlinked's is treated as a BCO.  We can
3126        -- generate a linkable with no Unlinked's as a result of
3127        -- compiling a module in HscNothing mode, and this choice
3128        -- happens to work well with checkStability in module GHC.
3129
3130linkableObjs :: Linkable -> [FilePath]
3131linkableObjs l = [ f | DotO f <- linkableUnlinked l ]
3132
3133-------------------------------------------
3134
3135-- | Is this an actual file on disk we can link in somehow?
3136isObject :: Unlinked -> Bool
3137isObject (DotO _)   = True
3138isObject (DotA _)   = True
3139isObject (DotDLL _) = True
3140isObject _          = False
3141
3142-- | Is this a bytecode linkable with no file on disk?
3143isInterpretable :: Unlinked -> Bool
3144isInterpretable = not . isObject
3145
3146-- | Retrieve the filename of the linkable if possible. Panic if it is a byte-code object
3147nameOfObject :: Unlinked -> FilePath
3148nameOfObject (DotO fn)   = fn
3149nameOfObject (DotA fn)   = fn
3150nameOfObject (DotDLL fn) = fn
3151nameOfObject other       = pprPanic "nameOfObject" (ppr other)
3152
3153-- | Retrieve the compiled byte-code if possible. Panic if it is a file-based linkable
3154byteCodeOfObject :: Unlinked -> CompiledByteCode
3155byteCodeOfObject (BCOs bc _) = bc
3156byteCodeOfObject other       = pprPanic "byteCodeOfObject" (ppr other)
3157
3158
3159-------------------------------------------
3160
3161-- | A list of conlikes which represents a complete pattern match.
3162-- These arise from @COMPLETE@ signatures.
3163
3164-- See Note [Implementation of COMPLETE signatures]
3165data CompleteMatch = CompleteMatch {
3166                            completeMatchConLikes :: [Name]
3167                            -- ^ The ConLikes that form a covering family
3168                            -- (e.g. Nothing, Just)
3169                          , completeMatchTyCon :: Name
3170                            -- ^ The TyCon that they cover (e.g. Maybe)
3171                          }
3172
3173instance Outputable CompleteMatch where
3174  ppr (CompleteMatch cl ty) = text "CompleteMatch:" <+> ppr cl
3175                                                    <+> dcolon <+> ppr ty
3176
3177-- | A map keyed by the 'completeMatchTyCon'.
3178
3179-- See Note [Implementation of COMPLETE signatures]
3180type CompleteMatchMap = UniqFM [CompleteMatch]
3181
3182mkCompleteMatchMap :: [CompleteMatch] -> CompleteMatchMap
3183mkCompleteMatchMap = extendCompleteMatchMap emptyUFM
3184
3185extendCompleteMatchMap :: CompleteMatchMap -> [CompleteMatch]
3186                       -> CompleteMatchMap
3187extendCompleteMatchMap = foldl' insertMatch
3188  where
3189    insertMatch :: CompleteMatchMap -> CompleteMatch -> CompleteMatchMap
3190    insertMatch ufm c@(CompleteMatch _ t) = addToUFM_C (++) ufm t [c]
3191
3192{-
3193Note [Implementation of COMPLETE signatures]
3194~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3195A COMPLETE signature represents a set of conlikes (i.e., constructors or
3196pattern synonyms) such that if they are all pattern-matched against in a
3197function, it gives rise to a total function. An example is:
3198
3199  newtype Boolean = Boolean Int
3200  pattern F, T :: Boolean
3201  pattern F = Boolean 0
3202  pattern T = Boolean 1
3203  {-# COMPLETE F, T #-}
3204
3205  -- This is a total function
3206  booleanToInt :: Boolean -> Int
3207  booleanToInt F = 0
3208  booleanToInt T = 1
3209
3210COMPLETE sets are represented internally in GHC with the CompleteMatch data
3211type. For example, {-# COMPLETE F, T #-} would be represented as:
3212
3213  CompleteMatch { complateMatchConLikes = [F, T]
3214                , completeMatchTyCon    = Boolean }
3215
3216Note that GHC was able to infer the completeMatchTyCon (Boolean), but for the
3217cases in which it's ambiguous, you can also explicitly specify it in the source
3218language by writing this:
3219
3220  {-# COMPLETE F, T :: Boolean #-}
3221
3222For efficiency purposes, GHC collects all of the CompleteMatches that it knows
3223about into a CompleteMatchMap, which is a map that is keyed by the
3224completeMatchTyCon. In other words, you could have a multiple COMPLETE sets
3225for the same TyCon:
3226
3227  {-# COMPLETE F, T1 :: Boolean #-}
3228  {-# COMPLETE F, T2 :: Boolean #-}
3229
3230And looking up the values in the CompleteMatchMap associated with Boolean
3231would give you [CompleteMatch [F, T1] Boolean, CompleteMatch [F, T2] Boolean].
3232dsGetCompleteMatches in DsMeta accomplishes this lookup.
3233
3234Also see Note [Typechecking Complete Matches] in TcBinds for a more detailed
3235explanation for how GHC ensures that all the conlikes in a COMPLETE set are
3236consistent.
3237-}
3238
3239-- | Foreign language of the phase if the phase deals with a foreign code
3240phaseForeignLanguage :: Phase -> Maybe ForeignSrcLang
3241phaseForeignLanguage phase = case phase of
3242  Phase.Cc           -> Just LangC
3243  Phase.Ccxx         -> Just LangCxx
3244  Phase.Cobjc        -> Just LangObjc
3245  Phase.Cobjcxx      -> Just LangObjcxx
3246  Phase.HCc          -> Just LangC
3247  Phase.As _         -> Just LangAsm
3248  Phase.MergeForeign -> Just RawObject
3249  _                  -> Nothing
3250
3251-------------------------------------------
3252
3253-- Take care, this instance only forces to the degree necessary to
3254-- avoid major space leaks.
3255instance (NFData (IfaceBackendExts (phase :: ModIfacePhase)), NFData (IfaceDeclExts (phase :: ModIfacePhase))) => NFData (ModIface_ phase) where
3256  rnf (ModIface f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 f12
3257                f13 f14 f15 f16 f17 f18 f19 f20 f21 f22 f23) =
3258    rnf f1 `seq` rnf f2 `seq` f3 `seq` f4 `seq` f5 `seq` f6 `seq` rnf f7 `seq` f8 `seq`
3259    f9 `seq` rnf f10 `seq` rnf f11 `seq` f12 `seq` rnf f13 `seq` rnf f14 `seq` rnf f15 `seq`
3260    rnf f16 `seq` f17 `seq` rnf f18 `seq` rnf f19 `seq` f20 `seq` f21 `seq` f22 `seq` rnf f23
3261