| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Unit.External
Synopsis
- newtype ExternalUnitCache = ExternalUnitCache {}
 - initExternalUnitCache :: IO ExternalUnitCache
 - eucEPS :: ExternalUnitCache -> IO ExternalPackageState
 - data ExternalPackageState = EPS {
- eps_is_boot :: !(InstalledModuleEnv ModuleNameWithIsBoot)
 - eps_PIT :: !PackageIfaceTable
 - eps_free_holes :: InstalledModuleEnv (UniqDSet ModuleName)
 - eps_PTE :: !PackageTypeEnv
 - eps_inst_env :: !PackageInstEnv
 - eps_fam_inst_env :: !PackageFamInstEnv
 - eps_rule_base :: !PackageRuleBase
 - eps_ann_env :: !PackageAnnEnv
 - eps_complete_matches :: !PackageCompleteMatches
 - eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv)
 - eps_stats :: !EpsStats
 
 - initExternalPackageState :: ExternalPackageState
 - data EpsStats = EpsStats {
- n_ifaces_in :: !Int
 - n_decls_in :: !Int
 - n_decls_out :: !Int
 - n_rules_in :: !Int
 - n_rules_out :: !Int
 - n_insts_in :: !Int
 - n_insts_out :: !Int
 
 - addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
 - type PackageTypeEnv = TypeEnv
 - type PackageIfaceTable = ModuleEnv ModIface
 - type PackageInstEnv = InstEnv
 - type PackageFamInstEnv = FamInstEnv
 - type PackageRuleBase = RuleBase
 - type PackageCompleteMatches = CompleteMatches
 - emptyPackageIfaceTable :: PackageIfaceTable
 
Documentation
newtype ExternalUnitCache Source #
Information about the currently loaded external packages. This is mutable because packages will be demand-loaded during a compilation run as required.
Constructors
| ExternalUnitCache | |
Fields  | |
data ExternalPackageState Source #
Information about other packages that we have slurped in by reading their interface files
Constructors
| EPS | |
Fields 
  | |
Accumulated statistics about what we are putting into the ExternalPackageState.
 "In" means stuff that is just read from interface files,
 "Out" means actually sucked in and type-checked
Constructors
| EpsStats | |
Fields 
  | |
addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats Source #
Add stats for one newly-read interface
type PackageTypeEnv = TypeEnv Source #
type PackageIfaceTable = ModuleEnv ModIface Source #
Helps us find information about modules in the imported packages
type PackageInstEnv = InstEnv Source #
type PackageFamInstEnv = FamInstEnv Source #
type PackageRuleBase = RuleBase Source #
emptyPackageIfaceTable :: PackageIfaceTable Source #
Constructs an empty PackageIfaceTable