module GHC.Unit.Module.ModGuts ( ModGuts (..) , mg_mnwib , CgGuts (..) ) where import GHC.Prelude import GHC.ByteCode.Types import GHC.ForeignSrcLang import GHC.Hs import GHC.Unit import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings import GHC.Core.InstEnv ( InstEnv, ClsInst ) import GHC.Core.FamInstEnv import GHC.Core ( CoreProgram, CoreRule ) import GHC.Core.TyCon import GHC.Core.PatSyn import GHC.Linker.Types ( SptEntry(..) ) import GHC.Types.Annotations ( Annotation ) import GHC.Types.Avail import GHC.Types.CompleteMatch import GHC.Types.Fixity.Env import GHC.Types.ForeignStubs import GHC.Types.HpcInfo import GHC.Types.Name.Reader import GHC.Types.Name.Set (NameSet) import GHC.Types.SafeHaskell import GHC.Types.SourceFile ( HscSource(..), hscSourceToIsBoot ) import GHC.Types.SrcLoc import GHC.Types.CostCentre import Data.Set (Set) -- | A ModGuts is carried through the compiler, accumulating stuff as it goes -- There is only one ModGuts at any time, the one for the module -- being compiled right now. Once it is compiled, a 'ModIface' and -- 'ModDetails' are extracted and the ModGuts is discarded. data ModGuts = ModGuts { ModGuts -> Module mg_module :: !Module, -- ^ Module being compiled ModGuts -> HscSource mg_hsc_src :: HscSource, -- ^ Whether it's an hs-boot module ModGuts -> SrcSpan mg_loc :: SrcSpan, -- ^ For error messages from inner passes ModGuts -> [AvailInfo] mg_exports :: ![AvailInfo], -- ^ What it exports ModGuts -> Dependencies mg_deps :: !Dependencies, -- ^ What it depends on, directly or -- otherwise ModGuts -> [Usage] mg_usages :: ![Usage], -- ^ What was used? Used for interfaces. ModGuts -> Bool mg_used_th :: !Bool, -- ^ Did we run a TH splice? ModGuts -> GlobalRdrEnv mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment -- These fields all describe the things **declared in this module** ModGuts -> FixityEnv mg_fix_env :: !FixityEnv, -- ^ Fixities declared in this module. -- Used for creating interface files. ModGuts -> [TyCon] mg_tcs :: ![TyCon], -- ^ TyCons declared in this module -- (includes TyCons for classes) ModGuts -> [ClsInst] mg_insts :: ![ClsInst], -- ^ Class instances declared in this module ModGuts -> [FamInst] mg_fam_insts :: ![FamInst], -- ^ Family instances declared in this module ModGuts -> [PatSyn] mg_patsyns :: ![PatSyn], -- ^ Pattern synonyms declared in this module ModGuts -> [CoreRule] mg_rules :: ![CoreRule], -- ^ Before the core pipeline starts, contains -- See Note [Overall plumbing for rules] in "GHC.Core.Rules" ModGuts -> CoreProgram mg_binds :: !CoreProgram, -- ^ Bindings for this module ModGuts -> ForeignStubs mg_foreign :: !ForeignStubs, -- ^ Foreign exports declared in this module ModGuts -> [(ForeignSrcLang, FilePath)] mg_foreign_files :: ![(ForeignSrcLang, FilePath)], -- ^ Files to be compiled with the C compiler ModGuts -> Warnings GhcRn mg_warns :: !(Warnings GhcRn), -- ^ Warnings declared in the module ModGuts -> [Annotation] mg_anns :: [Annotation], -- ^ Annotations declared in this module ModGuts -> [CompleteMatch] mg_complete_matches :: [CompleteMatch], -- ^ Complete Matches ModGuts -> HpcInfo mg_hpc_info :: !HpcInfo, -- ^ Coverage tick boxes in the module ModGuts -> Maybe ModBreaks mg_modBreaks :: !(Maybe ModBreaks), -- ^ Breakpoints for the module -- The next two fields are unusual, because they give instance -- environments for *all* modules in the home package, including -- this module, rather than for *just* this module. -- Reason: when looking up an instance we don't want to have to -- look at each module in the home package in turn ModGuts -> InstEnv mg_inst_env :: InstEnv, -- ^ Class instance environment for -- /home-package/ modules (including this -- one); c.f. 'tcg_inst_env' ModGuts -> FamInstEnv mg_fam_inst_env :: FamInstEnv, -- ^ Type-family instance environment for -- /home-package/ modules (including this -- one); c.f. 'tcg_fam_inst_env' ModGuts -> NameSet mg_boot_exports :: !NameSet, -- Things that are also export via hs-boot file ModGuts -> SafeHaskellMode mg_safe_haskell :: SafeHaskellMode, -- ^ Safe Haskell mode ModGuts -> Bool mg_trust_pkg :: Bool, -- ^ Do we need to trust our -- own package for Safe Haskell? -- See Note [Trust Own Package] -- in "GHC.Rename.Names" ModGuts -> Maybe Docs mg_docs :: !(Maybe Docs) -- ^ Documentation. } mg_mnwib :: ModGuts -> ModuleNameWithIsBoot mg_mnwib :: ModGuts -> ModuleNameWithIsBoot mg_mnwib ModGuts mg = ModuleName -> IsBootInterface -> ModuleNameWithIsBoot forall mod. mod -> IsBootInterface -> GenWithIsBoot mod GWIB (Module -> ModuleName forall unit. GenModule unit -> ModuleName moduleName (ModGuts -> Module mg_module ModGuts mg)) (HscSource -> IsBootInterface hscSourceToIsBoot (ModGuts -> HscSource mg_hsc_src ModGuts mg)) -- The ModGuts takes on several slightly different forms: -- -- After simplification, the following fields change slightly: -- mg_rules Orphan rules only (local ones now attached to binds) -- mg_binds With rules attached --------------------------------------------------------- -- The Tidy pass forks the information about this module: -- * one lot goes to interface file generation (ModIface) -- and later compilations (ModDetails) -- * the other lot goes to code generation (CgGuts) -- | A restricted form of 'ModGuts' for code generation purposes data CgGuts = CgGuts { CgGuts -> Module cg_module :: !Module, -- ^ Module being compiled CgGuts -> [TyCon] cg_tycons :: [TyCon], -- ^ Algebraic data types (including ones that started -- life as classes); generate constructors and info -- tables. Includes newtypes, just for the benefit of -- External Core CgGuts -> CoreProgram cg_binds :: CoreProgram, -- ^ The tidied main bindings, including -- previously-implicit bindings for record and class -- selectors, and data constructor wrappers. But *not* -- data constructor workers; reason: we regard them -- as part of the code-gen of tycons CgGuts -> [CostCentre] cg_ccs :: [CostCentre], -- List of cost centres used in bindings and rules CgGuts -> ForeignStubs cg_foreign :: !ForeignStubs, -- ^ Foreign export stubs CgGuts -> [(ForeignSrcLang, FilePath)] cg_foreign_files :: ![(ForeignSrcLang, FilePath)], CgGuts -> Set UnitId cg_dep_pkgs :: !(Set UnitId), -- ^ Dependent packages, used to -- generate #includes for C code gen CgGuts -> HpcInfo cg_hpc_info :: !HpcInfo, -- ^ Program coverage tick box information CgGuts -> Maybe ModBreaks cg_modBreaks :: !(Maybe ModBreaks), -- ^ Module breakpoints CgGuts -> [SptEntry] cg_spt_entries :: [SptEntry] -- ^ Static pointer table entries for static forms defined in -- the module. -- See Note [Grand plan for static forms] in "GHC.Iface.Tidy.StaticPtrTable" }