summaryrefslogtreecommitdiff
path: root/ghc/Main.hs
Commit message (Collapse)AuthorAgeFilesLines
* Rework plugin initialisation pointsAaron Allen2023-05-051-3/+10
| | | | | | | | | | | | | | | | | | In general this patch pushes plugin initialisation points to earlier in the pipeline. As plugins can modify the `HscEnv`, it's imperative that the plugins are initialised as soon as possible and used thereafter. For example, there are some new tests which modify hsc_logger and other hooks which failed to fire before (and now do) One consequence of this change is that the error for specifying the usage of a HPT plugin from the command line has changed, because it's now attempted to be loaded at initialisation rather than causing a cyclic module import. Closes #21279 Co-authored-by: Matthew Pickering <matthewtpickering@gmail.com>
* Convert interface file loading errors into proper diagnosticsMatthew Pickering2023-04-181-3/+7
| | | | | | | | | | | | | | This patch converts all the errors to do with loading interface files into proper structured diagnostics. * DriverMessage: Sometimes in the driver we attempt to load an interface file so we embed the IfaceMessage into the DriverMessage. * TcRnMessage: Most the time we are loading interface files during typechecking, so we embed the IfaceMessage This patch also removes the TcRnInterfaceLookupError constructor which is superceded by the IfaceMessage, which is now structured compared to just storing an SDoc before.
* Allow configuration of error message printingMatthew Pickering2022-10-181-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This MR implements the idea of #21731 that the printing of a diagnostic method should be configurable at the printing time. The interface of the `Diagnostic` class is modified from: ``` class Diagnostic a where diagnosticMessage :: a -> DecoratedSDoc diagnosticReason :: a -> DiagnosticReason diagnosticHints :: a -> [GhcHint] ``` to ``` class Diagnostic a where type DiagnosticOpts a defaultDiagnosticOpts :: DiagnosticOpts a diagnosticMessage :: DiagnosticOpts a -> a -> DecoratedSDoc diagnosticReason :: a -> DiagnosticReason diagnosticHints :: a -> [GhcHint] ``` and so each `Diagnostic` can implement their own configuration record which can then be supplied by a client in order to dictate how to print out the error message. At the moment this only allows us to implement #21722 nicely but in future it is more natural to separate the configuration of how much information we put into an error message and how much we decide to print out of it. Updates Haddock submodule
* Interface Files with Core DefinitionsMatthew Pickering2022-10-111-0/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This commit adds three new flags * -fwrite-if-simplified-core: Writes the whole core program into an interface file * -fbyte-code-and-object-code: Generate both byte code and object code when compiling a file * -fprefer-byte-code: Prefer to use byte-code if it's available when running TH splices. The goal for including the core bindings in an interface file is to be able to restart the compiler pipeline at the point just after simplification and before code generation. Once compilation is restarted then code can be created for the byte code backend. This can significantly speed up start-times for projects in GHCi. HLS already implements its own version of these extended interface files for this reason. Preferring to use byte-code means that we can avoid some potentially expensive code generation steps (see #21700) * Producing object code is much slower than producing bytecode, and normally you need to compile with `-dynamic-too` to produce code in the static and dynamic way, the dynamic way just for Template Haskell execution when using a dynamically linked compiler. * Linking many large object files, which happens once per splice, can be quite expensive compared to linking bytecode. And you can get GHC to compile the necessary byte code so `-fprefer-byte-code` has access to it by using `-fbyte-code-and-object-code`. Fixes #21067
* Change `Backend` type and remove direct dependencieswip/backend-as-recordNorman Ramsey2022-05-211-8/+10
| | | | | | | | | | | | | | | | | | | With this change, `Backend` becomes an abstract type (there are no more exposed value constructors). Decisions that were formerly made by asking "is the current back end equal to (or different from) this named value constructor?" are now made by interrogating the back end about its properties, which are functions exported by `GHC.Driver.Backend`. There is a description of how to migrate code using `Backend` in the user guide. Clients using the GHC API can find a backdoor to access the Backend datatype in GHC.Driver.Backend.Internal. Bumps haddock submodule. Fixes #20927
* Basic response file supportBen Gamari2022-04-271-4/+3
| | | | | | | | Here we introduce support into our command-line parsing infrastructure and driver for handling gnu-style response file arguments, typically used to work around platform command-line length limitations. Fixes #16476.
* Track object file dependencies for TH accurately (#20604)Zubin Duggal2022-02-201-1/+1
| | | | | | | | | | | | | | | | | | | `hscCompileCoreExprHook` is changed to return a list of `Module`s required by a splice. These modules are accumulated in the TcGblEnv (tcg_th_needed_mods). Dependencies on the object files of these modules are recording in the interface. The data structures in `LoaderState` are replaced with more efficient versions to keep track of all the information required. The MultiLayerModulesTH_Make allocations increase slightly but runtime is faster. Fixes #20604 ------------------------- Metric Increase: MultiLayerModulesTH_Make -------------------------
* Fix a few Note inconsistenciesBen Gamari2022-02-011-1/+1
|
* Multiple Home UnitsMatthew Pickering2021-12-281-44/+252
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Multiple home units allows you to load different packages which may depend on each other into one GHC session. This will allow both GHCi and HLS to support multi component projects more naturally. Public Interface ~~~~~~~~~~~~~~~~ In order to specify multiple units, the -unit @⟨filename⟩ flag is given multiple times with a response file containing the arguments for each unit. The response file contains a newline separated list of arguments. ``` ghc -unit @unitLibCore -unit @unitLib ``` where the `unitLibCore` response file contains the normal arguments that cabal would pass to `--make` mode. ``` -this-unit-id lib-core-0.1.0.0 -i -isrc LibCore.Utils LibCore.Types ``` The response file for lib, can specify a dependency on lib-core, so then modules in lib can use modules from lib-core. ``` -this-unit-id lib-0.1.0.0 -package-id lib-core-0.1.0.0 -i -isrc Lib.Parse Lib.Render ``` Then when the compiler starts in --make mode it will compile both units lib and lib-core. There is also very basic support for multiple home units in GHCi, at the moment you can start a GHCi session with multiple units but only the :reload is supported. Most commands in GHCi assume a single home unit, and so it is additional work to work out how to modify the interface to support multiple loaded home units. Options used when working with Multiple Home Units There are a few extra flags which have been introduced specifically for working with multiple home units. The flags allow a home unit to pretend it’s more like an installed package, for example, specifying the package name, module visibility and reexported modules. -working-dir ⟨dir⟩ It is common to assume that a package is compiled in the directory where its cabal file resides. Thus, all paths used in the compiler are assumed to be relative to this directory. When there are multiple home units the compiler is often not operating in the standard directory and instead where the cabal.project file is located. In this case the -working-dir option can be passed which specifies the path from the current directory to the directory the unit assumes to be it’s root, normally the directory which contains the cabal file. When the flag is passed, any relative paths used by the compiler are offset by the working directory. Notably this includes -i and -I⟨dir⟩ flags. -this-package-name ⟨name⟩ This flag papers over the awkward interaction of the PackageImports and multiple home units. When using PackageImports you can specify the name of the package in an import to disambiguate between modules which appear in multiple packages with the same name. This flag allows a home unit to be given a package name so that you can also disambiguate between multiple home units which provide modules with the same name. -hidden-module ⟨module name⟩ This flag can be supplied multiple times in order to specify which modules in a home unit should not be visible outside of the unit it belongs to. The main use of this flag is to be able to recreate the difference between an exposed and hidden module for installed packages. -reexported-module ⟨module name⟩ This flag can be supplied multiple times in order to specify which modules are not defined in a unit but should be reexported. The effect is that other units will see this module as if it was defined in this unit. The use of this flag is to be able to replicate the reexported modules feature of packages with multiple home units. Offsetting Paths in Template Haskell splices ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When using Template Haskell to embed files into your program, traditionally the paths have been interpreted relative to the directory where the .cabal file resides. This causes problems for multiple home units as we are compiling many different libraries at once which have .cabal files in different directories. For this purpose we have introduced a way to query the value of the -working-dir flag to the Template Haskell API. By using this function we can implement a makeRelativeToProject function which offsets a path which is relative to the original project root by the value of -working-dir. ``` import Language.Haskell.TH.Syntax ( makeRelativeToProject ) foo = $(makeRelativeToProject "./relative/path" >>= embedFile) ``` > If you write a relative path in a Template Haskell splice you should use the makeRelativeToProject function so that your library works correctly with multiple home units. A similar function already exists in the file-embed library. The function in template-haskell implements this function in a more robust manner by honouring the -working-dir flag rather than searching the file system. Closure Property for Home Units ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ For tools or libraries using the API there is one very important closure property which must be adhered to: > Any dependency which is not a home unit must not (transitively) depend on a home unit. For example, if you have three packages p, q and r, then if p depends on q which depends on r then it is illegal to load both p and r as home units but not q, because q is a dependency of the home unit p which depends on another home unit r. If you are using GHC by the command line then this property is checked, but if you are using the API then you need to check this property yourself. If you get it wrong you will probably get some very confusing errors about overlapping instances. Limitations of Multiple Home Units ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ There are a few limitations of the initial implementation which will be smoothed out on user demand. * Package thinning/renaming syntax is not supported * More complicated reexports/renaming are not yet supported. * It’s more common to run into existing linker bugs when loading a large number of packages in a session (for example #20674, #20689) * Backpack is not yet supported when using multiple home units. * Dependency chasing can be quite slow with a large number of modules and packages. * Loading wired-in packages as home units is currently not supported (this only really affects GHC developers attempting to load template-haskell). * Barely any normal GHCi features are supported, it would be good to support enough for ghcid to work correctly. Despite these limitations, the implementation works already for nearly all packages. It has been testing on large dependency closures, including the whole of head.hackage which is a total of 4784 modules from 452 packages. Internal Changes ~~~~~~~~~~~~~~~~ * The biggest change is that the HomePackageTable is replaced with the HomeUnitGraph. The HomeUnitGraph is a map from UnitId to HomeUnitEnv, which contains information specific to each home unit. * The HomeUnitEnv contains: - A unit state, each home unit can have different package db flags - A set of dynflags, each home unit can have different flags - A HomePackageTable * LinkNode: A new node type is added to the ModuleGraph, this is used to place the linking step into the build plan so linking can proceed in parralel with other packages being built. * New invariant: Dependencies of a ModuleGraphNode can be completely determined by looking at the value of the node. In order to achieve this, downsweep now performs a more complete job of downsweeping and then the dependenices are recorded forever in the node rather than being computed again from the ModSummary. * Some transitive module calculations are rewritten to use the ModuleGraph which is more efficient. * There is always an active home unit, which simplifies modifying a lot of the existing API code which is unit agnostic (for example, in the driver). The road may be bumpy for a little while after this change but the basics are well-tested. One small metric increase, which we accept and also submodule update to haddock which removes ExtendedModSummary. Closes #10827 ------------------------- Metric Increase: MultiLayerModules ------------------------- Co-authored-by: Fendor <power.walross@gmail.com>
* More support for optional home-unitSylvain Henry2021-11-201-6/+7
| | | | | | | | | This is a preliminary refactoring for #14335 (supporting plugins in cross-compilers). In many places the home-unit must be optional because there won't be one available in the plugin environment (we won't be compiling anything in this environment). Hence we replace "HomeUnit" with "Maybe HomeUnit" in a few places and we avoid the use of "hsc_home_unit" (which is partial) in some few others.
* Refactor package importsSylvain Henry2021-10-221-1/+2
| | | | | | | | | Use an (Raw)PkgQual datatype instead of `Maybe FastString` to represent package imports. Factorize the code that renames RawPkgQual into PkgQual in function `rnPkgQual`. Renaming consists in checking if the FastString is the magic "this" keyword, the home-unit unit-id or something else. Bump haddock submodule
* Ensure .dyn_hi doesn't overwrite .hiZiyang Liu2021-09-171-0/+5
| | | | | | | | This commit fixes the following bug: when `outputHi` is set, and both `.dyn_hi` and `.hi` are needed, both would be written to `outputHi`, causing `.dyn_hi` to overwrite `.hi`. This causes subsequent `readIface` to fail - "mismatched interface file profile tag (wanted "", got "dyn")" - triggering unnecessary rebuild.
* Remove hschooks.c and -no-hs-main for ghc-binZubin Duggal2021-08-031-24/+0
|
* ghc: Introduce --run modeBen Gamari2021-08-021-3/+22
| | | | | | As described in #18011, this mode provides similar functionality to the `runhaskell` command, but doesn't require that the user know the path of yet another executable, simplifying interactions with upstream tools.
* Introduce FinderLocations for decoupling Finder from DynFlagsFendor2021-07-231-1/+3
|
* Avoid unsafePerformIO for getProgNameSylvain Henry2021-07-091-4/+6
| | | | | | | | getProgName was used to append the name of the program (e.g. "ghc") to printed error messages in the Show instance of GhcException. It doesn't belong here as GHCi and GHC API users may want to override this behavior by setting a different error handler. So we now call it in the defaultErrorHandler instead.
* driver: Convert runPipeline to use a free monadMatthew Pickering2021-07-071-13/+14
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch converts the runPipeline function to be implemented in terms of a free monad rather than the previous CompPipeline. The advantages of this are three-fold: 1. Different parts of the pipeline can return different results, the limits of runPipeline were being pushed already by !5555, this opens up futher fine-grainedism of the pipeline. 2. The same mechanism can be extended to build-plan at the module level so the whole build plan can be expressed in terms of one computation which can then be treated uniformly. 3. The pipeline monad can now be interpreted in different ways, for example, you may want to interpret the `TPhase` action into the monad for your own build system (such as shake). That bit will probably require a bit more work, but this is a step in the right directin. There are a few more modules containing useful functions for interacting with the pipelines. * GHC.Driver.Pipeline: Functions for building pipelines at a high-level * GHC.Driver.Pipeline.Execute: Functions for providing the default interpretation of TPhase, in terms of normal IO. * GHC.Driver.Pipeline.Phases: The home for TPhase, the typed phase data type which dictates what the phases are. * GHC.Driver.Pipeline.Monad: Definitions to do with the TPipelineClass and MonadUse class. Hooks consumers may notice the type of the `phaseHook` has got slightly more restrictive, you can now no longer control the continuation of the pipeline by returning the next phase to execute but only override individual phases. If this is a problem then please open an issue and we will work out a solution. ------------------------- Metric Decrease: T4029 -------------------------
* Dynflags: introduce DiagOptsSylvain Henry2021-07-011-1/+2
| | | | | | | | | | | | | | | | | | | | | | Use DiagOpts for diagnostic options instead of directly querying DynFlags (#17957). Surprising performance improvements on CI: T4801(normal) ghc/alloc 313236344.0 306515216.0 -2.1% GOOD T9961(normal) ghc/alloc 384502736.0 380584384.0 -1.0% GOOD ManyAlternatives(normal) ghc/alloc 797356128.0 786644928.0 -1.3% ManyConstructors(normal) ghc/alloc 4389732432.0 4317740880.0 -1.6% T783(normal) ghc/alloc 408142680.0 402812176.0 -1.3% Metric Decrease: T4801 T9961 T783 ManyAlternatives ManyConstructors Bump haddock submodule
* Make Logger independent of DynFlagsSylvain Henry2021-06-071-16/+22
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Introduce LogFlags as a independent subset of DynFlags used for logging. As a consequence in many places we don't have to pass both Logger and DynFlags anymore. The main reason for this refactoring is that I want to refactor the systools interfaces: for now many systools functions use DynFlags both to use the Logger and to fetch their parameters (e.g. ldInputs for the linker). I'm interested in refactoring the way they fetch their parameters (i.e. use dedicated XxxOpts data types instead of DynFlags) for #19877. But if I did this refactoring before refactoring the Logger, we would have duplicate parameters (e.g. ldInputs from DynFlags and linkerInputs from LinkerOpts). Hence this patch first. Some flags don't really belong to LogFlags because they are subsystem specific (e.g. most DumpFlags). For example -ddump-asm should better be passed in NCGConfig somehow. This patch doesn't fix this tight coupling: the dump flags are part of the UI but they are passed all the way down for example to infer the file name for the dumps. Because LogFlags are a subset of the DynFlags, we must update the former when the latter changes (not so often). As a consequence we now use accessors to read/write DynFlags in HscEnv instead of using `hsc_dflags` directly. In the process I've also made some subsystems less dependent on DynFlags: - CmmToAsm: by passing some missing flags via NCGConfig (see new fields in GHC.CmmToAsm.Config) - Core.Opt.*: - by passing -dinline-check value into UnfoldingOpts - by fixing some Core passes interfaces (e.g. CallArity, FloatIn) that took DynFlags argument for no good reason. - as a side-effect GHC.Core.Opt.Pipeline.doCorePass is much less convoluted.
* Add `MessageClass`, rework `Severity` and add `DiagnosticReason`.wip/adinapoli-message-class-new-designAlfredo Di Napoli2021-03-291-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Other than that: * Fix T16167,json,json2,T7478,T10637 tests to reflect the introduction of the `MessageClass` type * Remove `makeIntoWarning` * Remove `warningsToMessages` * Refactor GHC.Tc.Errors 1. Refactors GHC.Tc.Errors so that we use `DiagnosticReason` for "choices" (defer types errors, holes, etc); 2. We get rid of `reportWarning` and `reportError` in favour of a general `reportDiagnostic`. * Introduce `DiagnosticReason`, `Severity` is an enum: This big commit makes `Severity` a simple enumeration, and introduces the concept of `DiagnosticReason`, which classifies the /reason/ why we are emitting a particular diagnostic. It also adds a monomorphic `DiagnosticMessage` type which is used for generic messages. * The `Severity` is computed (for now) from the reason, statically. Later improvement will add a `diagReasonSeverity` function to compute the `Severity` taking `DynFlags` into account. * Rename `logWarnings` into `logDiagnostics` * Add note and expand description of the `mkHoleError` function
* Add UnitId to Target recordFendor2021-03-281-1/+1
| | | | | | | | | | In the future, we want `HscEnv` to support multiple home units at the same time. This means, that there will be 'Target's that do not belong to the current 'HomeUnit'. This is an API change without changing behaviour. Update haddock submodule to incorporate API changes.
* Refactor FinderCacheSylvain Henry2021-03-261-3/+7
|
* Refactor NameCacheSylvain Henry2021-03-261-1/+4
| | | | | | | | * Make NameCache the mutable one and replace NameCacheUpdater with it * Remove NameCache related code duplicated into haddock Bump haddock submodule
* Add a flag to dump the FastString tableSylvain Henry2021-03-031-1/+8
|
* Drop GHC_LOADED_IN_GHCIBen Gamari2021-02-141-13/+0
| | | | | | | This previously supported the ghc-in-ghci script which has been since dropped. Hadrian's ghci support does not need this macro (which disabled uses of UnboxedTuples) since it uses `-fno-code` rather than produce bytecode.
* Refactor LoggerSylvain Henry2021-02-131-11/+14
| | | | | | | | | | | | | | | | | | | | | Before this patch, the only way to override GHC's default logging behavior was to set `log_action`, `dump_action` and `trace_action` fields in DynFlags. This patch introduces a new Logger abstraction and stores it in HscEnv instead. This is part of #17957 (avoid storing state in DynFlags). DynFlags are duplicated and updated per-module (because of OPTIONS_GHC pragma), so we shouldn't store global state in them. This patch also fixes a race in parallel "--make" mode which updated the `generatedDumps` IORef concurrently. Bump haddock submodule The increase in MultilayerModules is tracked in #19293. Metric Increase: MultiLayerModules
* Remove errShortString, cleanup error-related functionsAlfredo Di Napoli2021-01-091-0/+1
| | | | | | | | | | | This commit removes the errShortString field from the ErrMsg type, allowing us to cleanup a lot of dynflag-dependent error functions, and move them in a more specialised 'GHC.Driver.Errors' closer to the driver, where they are actually used. Metric Increase: T4801 T9961
* Move Unit related fields from DynFlags to HscEnvSylvain Henry2020-12-141-21/+11
| | | | | | | | | | | | | The unit database cache, the home unit and the unit state were stored in DynFlags while they ought to be stored in the compiler session state (HscEnv). This patch fixes this. It introduces a new UnitEnv type that should be used in the future to handle separate unit environments (especially host vs target units). Related to #17957 Bump haddock submodule
* Move Plugins into HscEnv (#17957)Sylvain Henry2020-11-211-11/+5
| | | | | | | | | | Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule
* Refactor -dynamic-too handlingSylvain Henry2020-11-061-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows?
* Split GHC.Driver.TypesSylvain Henry2020-10-291-31/+34
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule
* Move File Target parser to library #18596Fendor2020-10-091-70/+2
|
* Expose RTS-only ways (#18651)Sylvain Henry2020-10-091-2/+2
| | | | | Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself.
* DynFlags: disentangle OutputableSylvain Henry2020-08-121-0/+1
| | | | | | | | | - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule
* Move GHC.Platform into the compilerSylvain Henry2020-07-251-4/+4
| | | | | | | Previously it was in ghc-boot so that ghc-pkg could use it. However it wasn't necessary because ghc-pkg only uses a subset of it: reading target arch and OS from the settings file. This is now done via GHC.Platform.ArchOS (was called PlatformMini before).
* Rename GHC.Driver.Ways into GHC.Platform.WaysSylvain Henry2020-07-251-1/+1
|
* Replace HscTarget with BackendSylvain Henry2020-07-221-19/+17
| | | | | | | | | They both have the same role and Backend name is more explicit. Metric Decrease: T3064 Update Haddock submodule
* DynFlags: don't store buildTagSylvain Henry2020-06-271-1/+1
| | | | | | | | | | | | `DynFlags.buildTag` was a field created from the set of Ways in `DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which was fragile. We want to avoid global state like this (#17957). Moreover in #14335 we also want to support loading units with different ways: target units would still use `DynFlags.ways` but plugins would use `GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build tag and with ways, we recompute the buildTag on-the-fly (should be pretty cheap) and we remove `DynFlags.buildTag` field.
* Rename Package into Unit (2)Sylvain Henry2020-06-131-11/+11
| | | | | | | * rename PackageState into UnitState * rename findWiredInPackages into findWiredInUnits * rename lookupModuleInAll[Packages,Units] * etc.
* Rename Package into UnitSylvain Henry2020-06-131-3/+3
| | | | | | | | | | | | | | | | | | | | | | | | | The terminology changed over time and now package databases contain "units" (there can be several units compiled from a single Cabal package: one per-component, one for each option set, one per instantiation, etc.). We should try to be consistent internally and use "units": that's what this renaming does. Maybe one day we'll fix the UI too (e.g. replace -package-id with -unit-id, we already have -this-unit-id and ghc-pkg has -unit-id...) but it's not done in this patch. * rename getPkgFrameworkOpts into getUnitFrameworkOpts * rename UnitInfoMap into ClosureUnitInfoMap * rename InstalledPackageIndex into UnitInfoMap * rename UnusablePackages into UnusableUnits * rename PackagePrecedenceIndex into UnitPrecedenceMap * rename PackageDatabase into UnitDatabase * rename pkgDatabase into unitDatabases * rename pkgState into unitState * rename initPackages into initUnits * rename renamePackage into renameUnitInfo * rename UnusablePackageReason into UnusableUnitReason * rename getPackage* into getUnit* * etc.
* Clean up boot vs non-boot disambiguating typesJohn Ericson2020-06-041-1/+1
| | | | | | | | | | | | | | | We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended" module names (without or with a unit id) disambiguating boot and normal modules. We think this is important enough across the compiler that it deserves a new nominal product type. We do this with synnoyms and a functor named with a `Gen` prefix, matching other newly created definitions. It was also requested that we keep custom `IsBoot` / `NotBoot` sum type. So we have it too. This means changing many the many bools to use that instead. Updates `haddock` submodule.
* Move Config module into GHC.SettingsSylvain Henry2020-05-241-1/+1
|
* Unit: split and rename modulesSylvain Henry2020-04-301-2/+2
| | | | | | | Introduce GHC.Unit.* hierarchy for everything concerning units, packages and modules. Update Haddock submodule
* Modules: Utils and Data (#13009)Sylvain Henry2020-04-261-12/+12
| | | | | | | Update Haddock submodule Metric Increase: haddock.compiler
* Modules (#13009)Sylvain Henry2020-04-181-4/+4
| | | | | | | | | | | | | | * SysTools * Parser * GHC.Builtin * GHC.Iface.Recomp * Settings Update Haddock submodule Metric Decrease: Naperian parsing001
* Modules: type-checker (#13009)Sylvain Henry2020-04-071-1/+1
| | | | Update Haddock submodule
* Store ComponentId detailsSylvain Henry2020-03-291-3/+3
| | | | | | | | | | | | | | | | As far as GHC is concerned, installed package components ("units") are identified by an opaque ComponentId string provided by Cabal. But we don't want to display it to users (as it contains a hash) so GHC queries the database to retrieve some infos about the original source package (name, version, component name). This patch caches these infos in the ComponentId itself so that we don't need to provide DynFlags (which contains installed package informations) to print a ComponentId. In the future we want GHC to support several independent package states (e.g. for plugins and for target code), hence we need to avoid implicitly querying a single global package state.
* Modules: Types (#13009)Sylvain Henry2020-03-291-6/+5
| | | | | | | Update Haddock submodule Metric Increase: haddock.compiler
* Use a Set to represent WaysSylvain Henry2020-03-111-2/+3
| | | | | | | | Should make `member` queries faster and avoid messing up with missing `nubSort`. Metric Increase: hie002
* Refactor GHC.Driver.Session (Ways and Flags)Sylvain Henry2020-03-111-4/+5
| | | | | | | | | | | | | * extract flags and ways into their own modules (with some renaming) * remove one SOURCE import of GHC.Driver.Session from GHC.Driver.Phases * when GHC uses dynamic linking (WayDyn), `interpWays` was only reporting WayDyn even if the host was profiled (WayProf). Now it returns both as expected (might fix #16803). * `mkBuildTag :: [Way] -> String` wasn't reporting a canonical tag for differently ordered lists. Now we sort and nub the list to fix this.