summaryrefslogtreecommitdiff
path: root/compiler/main/InteractiveEval.hs
Commit message (Collapse)AuthorAgeFilesLines
* Update Foreign.* for Safe Haskell now that they're safe by defaultDavid Terei2014-11-211-0/+4
|
* Define mapUnionVarSet, and use itSimon Peyton Jones2014-08-291-2/+2
| | | | Call sites are much easier to understand than before
* Rename PackageId to PackageKey, distinguishing it from Cabal's PackageId.Edward Z. Yang2014-07-211-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Previously, both Cabal and GHC defined the type PackageId, and we expected them to be roughly equivalent (but represented differently). This refactoring separates these two notions. A package ID is a user-visible identifier; it's the thing you write in a Cabal file, e.g. containers-0.9. The components of this ID are semantically meaningful, and decompose into a package name and a package vrsion. A package key is an opaque identifier used by GHC to generate linking symbols. Presently, it just consists of a package name and a package version, but pursuant to #9265 we are planning to extend it to record other information. Within a single executable, it uniquely identifies a package. It is *not* an InstalledPackageId, as the choice of a package key affects the ABI of a package (whereas an InstalledPackageId is computed after compilation.) Cabal computes a package key for the package and passes it to GHC using -package-name (now *extremely* misnamed). As an added bonus, we don't have to worry about shadowing anymore. As a follow on, we should introduce -current-package-key having the same role as -package-name, and deprecate the old flag. This commit is just renaming. The haddock submodule needed to be updated. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, simonmar, hvr, austin Subscribers: simonmar, relrod, carter Differential Revision: https://phabricator.haskell.org/D79 Conflicts: compiler/main/HscTypes.lhs compiler/main/Packages.lhs utils/haddock
* Add LANGUAGE pragmas to compiler/ source filesHerbert Valerio Riedel2014-05-151-0/+2
| | | | | | | | | | | | | | | | | | In some cases, the layout of the LANGUAGE/OPTIONS_GHC lines has been reorganized, while following the convention, to - place `{-# LANGUAGE #-}` pragmas at the top of the source file, before any `{-# OPTIONS_GHC #-}`-lines. - Moreover, if the list of language extensions fit into a single `{-# LANGUAGE ... -#}`-line (shorter than 80 characters), keep it on one line. Otherwise split into `{-# LANGUAGE ... -#}`-lines for each individual language extension. In both cases, try to keep the enumeration alphabetically ordered. (The latter layout is preferable as it's more diff-friendly) While at it, this also replaces obsolete `{-# OPTIONS ... #-}` pragma occurences by `{-# OPTIONS_GHC ... #-}` pragmas.
* Fix a typo in commentGabor Greif2014-01-101-1/+1
|
* Comments onlySimon Peyton Jones2014-01-091-4/+8
|
* Refactor the way shadowing in handled in GHCiSimon Peyton Jones2014-01-031-1/+1
| | | | | | | | | | | | | | | | | | | | | | If you say ghci> import Foo( T ) ghci> data T = MkT ghci> data T = XXX then the second 'data T' should shadow the first. But the qualified Foo.T should still be available. We really weren't handling this correctly at all, resulting in Trac #8639 and #8628 among others This patch: * Add RdrName.extendGlobalRdrEnv, which does shadowing properly * Change HscTypes.icExtendGblRdrEnv (was badly-named icPlusGblRdrEnv) to use the new function * Change RnNames.extendGobalRdrEnvRn to use the new function * Move gresFrom Avails into RdrName * Better pprGlobalRdrEnv function in RdrName
* Refactor handleRunStatus some more, add comments and tidy up formattingSimon Marlow2013-11-281-55/+65
| | | | | | | I liked the idea of combining traceRunStatus and handleRunStatus, but I think we lost a bit of clarity where traceRunStatus wants to fall back to handleRunStatus when the breakpoint is enabled. So I refactored it a bit more.
* Refactor traceRunStatus/handleRunStatusSimon Peyton Jones2013-11-221-75/+58
| | | | | No change in behaviour, but I combined these two functions, and I think the result is a good deal clearer
* Restructure compilation pipeline to allow hooksAustin Seipp2013-09-221-0/+1
| | | | | | | | | | | | | | | | This commit exposes GHC's internal compiler pipeline through a `Hooks` module in the GHC API. It currently allows you to hook: * Foreign import/exports declarations * The frontend up to type checking * The one shot compilation mode * Core compilation, and the module iface * Linking and the phases in DriverPhases.hs * Quasiquotation Authored-by: Luite Stegeman <stegeman@gmail.com> Authored-by: Edsko de Vries <edsko@well-typed.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Revise implementation of overlapping type family instances.Richard Eisenberg2013-06-211-2/+2
| | | | | | | | | | | | | | | | | | | This commit changes the syntax and story around overlapping type family instances. Before, we had "unbranched" instances and "branched" instances. Now, we have closed type families and open ones. The behavior of open families is completely unchanged. In particular, coincident overlap of open type family instances still works, despite emails to the contrary. A closed type family is declared like this: > type family F a where > F Int = Bool > F a = Char The equations are tried in order, from top to bottom, subject to certain constraints, as described in the user manual. It is not allowed to declare an instance of a closed family.
* Split off a InteractiveEvalTypes module to remove an import loopIan Lynagh2013-04-061-38/+2
|
* Implement type family instance support for ":info" (#4175)Patrick Palka2013-03-151-5/+11
| | | | v2: added a couple of comments
* Use throwGhcExceptionIO rather than throwGhcException in InteractiveEval.hsIan Lynagh2013-01-301-7/+10
|
* Fix to 02c4ab049: use a weak pointer to the sandbox threadSimon Marlow2013-01-301-1/+12
| | | | | Otherwise, the sandbox thread cannot be considered deadlocked by the RTS, and conc033(ghci) hangs (amongst others).
* When printing types in the interactive UI, take account of free variablesSimon Peyton Jones2013-01-221-0/+1
| | | | | | | Often the types we print are full-generalised, but in fact *kinds* are not, so we need to use tidyOpenType. Fixes Trac #7587
* Redirect asynchronous exceptions to the sandbox thread in runStmt (#1381)Simon Marlow2012-12-201-11/+32
| | | | | | | See comment for details. We no longer use pushInterruptTargetThread/popInterruptTargetThread, so these could go away in due course.
* Add ":info!" to GHCi. This shows all instances without filtering first.Iavor S. Diatchki2012-11-291-4/+6
| | | | | | | | | The default behavior of :info is to show only those instances of for a type, where all relevant type constructor names are in scope. This keeps down the number of instances shown to the user. In some cases, it is nice to be able to see all instances for a type. This patch implements this with the :info! command.
* Replace all uses of ghcError with throwGhcException and purge ghcError.Erik de Castro Lopo2012-11-301-5/+5
|
* Add -fghci-hist-size=N to set the number of previous steps stored by :traceSimon Marlow2012-11-011-4/+6
|
* Refactor the way dump flags are handledIan Lynagh2012-10-181-1/+1
| | | | | | | | | | | | | We were being inconsistent about how we tested whether dump flags were enabled; in particular, sometimes we also checked the verbosity, and sometimes we didn't. This lead to oddities such as "ghc -v4" printing an "Asm code" section which didn't contain any code, and "-v4" enabled some parts of "-ddump-deriv" but not others. Now all the tests use dopt, which also takes the verbosity into account as appropriate.
* Some alpha renamingIan Lynagh2012-10-161-5/+5
| | | | | Mostly d -> g (matching DynFlag -> GeneralFlag). Also renamed if* to when*, matching the Haskell if/when names
* Move wORD_SIZE into platformConstantsIan Lynagh2012-09-161-1/+2
|
* GHC 7.4 is now required for building HEADIan Lynagh2012-07-201-4/+0
|
* Pass DynFlags down to showSDocIan Lynagh2012-06-121-3/+5
|
* Better error messages for setContext (#5527).Paolo Capriotti2012-06-071-12/+23
| | | | | | Make InteractiveEval.setContext throw a clearer exception when it is asked to add an IIModule which is not a home module or is not interpreted.
* Merge remote-tracking branch 'origin/unboxed-tuple-arguments2'Paolo Capriotti2012-06-051-3/+4
|\
| * Support code generation for unboxed-tuple function argumentsunboxed-tuple-arguments2Max Bolingbroke2012-05-151-3/+4
| | | | | | | | | | | | | | | | | | | | | | This is done by a 'unarisation' pre-pass at the STG level which translates away all (live) binders binding something of unboxed tuple type. This has the following knock-on effects: * The subkind hierarchy is vastly simplified (no UbxTupleKind or ArgKind) * Various relaxed type checks in typechecker, 'foreign import prim' etc * All case binders may be live at the Core level
* | Remove more uses of stdout and stderrIan Lynagh2012-05-291-3/+3
|/
* Add a fixity environment to InteractiveContext (#2947)Paolo Capriotti2012-05-151-3/+14
|
* Allow threads in GHCi to receive BlockedIndefintely* exceptions (#2786)Simon Marlow2012-04-121-2/+2
| | | | | | This is a partial fix for #2786. It seems we still don't get NonTermination exceptions for interpreted computations, but we do now get the BlockedIndefinitely family.
* Fix a race condition in the GHCi debugger exposed by testcase break011.Paolo Capriotti2012-04-111-0/+5
|
* GHCi: add :seti, for options that apply only at the prompt (#3217)Simon Marlow2012-03-011-11/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | GHCi now maintains two DynFlags: one that applies to whole modules loaded with :load, and one that applies to things typed at the prompt (expressions, statements, declarations, commands). The :set command modifies both DynFlags. This is for backwards compatibility: users won't notice any difference. The :seti command applies only to the interactive DynFlags. Additionally, I made a few changes to ":set" (with no arguments): * Now it only prints out options that differ from the defaults, rather than the whole list. * There is a new variant, ":set -a" to print out all options (the old behaviour). * It also prints out language options. e.g. Prelude> :set options currently set: none. base language is: Haskell2010 with the following modifiers: -XNoDatatypeContexts -XNondecreasingIndentation GHCi-specific dynamic flag settings: other dynamic, non-language, flag settings: -fimplicit-import-qualified warning settings: ":seti" (with no arguments) does the same as ":set", but for the interactive options. It also has the "-a" option. The interactive DynFlags are kept in the InteractiveContext, and copied into the HscEnv at the appropriate points (all in HscMain). There are some new GHC API operations: -- | Set the 'DynFlags' used to evaluate interactive expressions. setInteractiveDynFlags :: GhcMonad m => DynFlags -> m () -- | Get the 'DynFlags' used to evaluate interactive expressions. getInteractiveDynFlags :: GhcMonad m => m DynFlags -- | Sets the program 'DynFlags'. setProgramDynFlags :: GhcMonad m => DynFlags -> m [PackageId] -- | Returns the program 'DynFlags'. getProgramDynFlags :: GhcMonad m => m DynFlags Note I have not completed the whole of the plan outlined in #3217 yet: when in the context of a loaded module we don't take the interactive DynFlags from that module. That needs some more refactoring and thinking about, because we'll need to save and restore the original interactive DynFlags. This solves the immediate problem that people are having with the new flag checking in 7.4.1, because now it is possible to set language options in ~/.ghci that do not affect loaded modules and thereby cause recompilation.
* Refactoring: make IIModule contain ModuleName, not Module, for consistencySimon Marlow2012-02-141-3/+3
|
* Fix mistake in previous commits.David Terei2012-01-261-1/+1
|
* Have hscStmtWithLocation return (IO [HValue]).David Terei2012-01-251-9/+6
|
* Formatting wibbles.David Terei2012-01-251-1/+3
|
* Major refactoring of CoAxiomsSimon Peyton Jones2012-01-031-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch should have no user-visible effect. It implements a significant internal refactoring of the way that FC axioms are handled. The ultimate goal is to put us in a position to implement "pattern-matching axioms". But the changes here are only does refactoring; there is no change in functionality. Specifically: * We now treat data/type family instance declarations very, very similarly to types class instance declarations: - Renamed InstEnv.Instance as InstEnv.ClsInst, for symmetry with FamInstEnv.FamInst. This change does affect the GHC API, but for the better I think. - Previously, each family type/data instance declaration gave rise to a *TyCon*; typechecking a type/data instance decl produced that TyCon. Now, each type/data instance gives rise to a *FamInst*, by direct analogy with each class instance declaration giving rise to a ClsInst. - Just as each ClsInst contains its evidence, a DFunId, so each FamInst contains its evidence, a CoAxiom. See Note [FamInsts and CoAxioms] in FamInstEnv. The CoAxiom is a System-FC thing, and can relate any two types, whereas the FamInst relates directly to the Haskell source language construct, and always has a function (F tys) on the LHS. - Just as a DFunId has its own declaration in an interface file, so now do CoAxioms (see IfaceSyn.IfaceAxiom). These changes give rise to almost all the refactoring. * We used to have a hack whereby a type family instance produced a dummy type synonym, thus type instance F Int = Bool -> Bool translated to axiom FInt :: F Int ~ R:FInt type R:FInt = Bool -> Bool This was always a hack, and now it's gone. Instead the type instance declaration produces a FamInst, whose axiom has kind axiom FInt :: F Int ~ Bool -> Bool just as you'd expect. * Newtypes are done just as before; they generate a CoAxiom. These CoAxioms are "implicit" (do not generate an IfaceAxiom declaration), unlike the ones coming from family instance declarations. See Note [Implicit axioms] in TyCon On the whole the code gets significantly nicer. There were consequential tidy-ups in the vectoriser, but I think I got them right.
* Tabs -> SpacesDavid Terei2011-12-191-92/+85
|
* Use -fwarn-tabs when validatingIan Lynagh2011-11-041-0/+7
| | | | | We only use it for "compiler" sources, i.e. not for libraries. Many modules have a -fno-warn-tabs kludge for now.
* A little more refactoring, triggered by the fix to Trac #5545Simon Peyton Jones2011-10-211-4/+4
|
* fix value of this_mod passed to tcRnImports (#5545)Simon Marlow2011-10-181-6/+1
|
* Fix dynCompileExprIan Lynagh2011-10-051-0/+13
| | | | | It broke during the ic_exports tidyup (e.g. commit 5cd39aa33f970ff42e22b1c9c73502e4229dc488).
* Implement GHCi command :kind! which normalises its typeSimon Peyton Jones2011-09-231-3/+3
| | | | | | | | | | | | | | | | type family F a type instance F Int = Bool type instance F Bool = Char In GHCi *TF> :kind (F Int, F Bool) (F Int, F Bool) :: * *TF> :kind! F Int (F Int, F Bool) :: * = (Bool, Char) We could call it ":normalise" but it seemed quite nice to have an eager version of :kind
* move AvailInfo and related things into its own moduleSimon Marlow2011-09-211-0/+1
|
* Add support for all top-level declarations to GHCiSimon Marlow2011-09-211-28/+48
| | | | | | | | | | | | | | | | This is work mostly done by Daniel Winograd-Cort during his internship at MSR Cambridge, with some further refactoring by me. This commit adds support to GHCi for most top-level declarations that can be used in Haskell source files. Class, data, newtype, type, instance are all supported, as are Type Family-related declarations. The current set of declarations are shown by :show bindings. As with variable bindings, entities bound by newer declarations shadow earlier ones. Tests are in testsuite/tests/ghci/scripts/ghci039--ghci054. Documentation to follow.
* Implement -XConstraintKindMax Bolingbroke2011-09-061-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Basically as documented in http://hackage.haskell.org/trac/ghc/wiki/KindFact, this patch adds a new kind Constraint such that: Show :: * -> Constraint (?x::Int) :: Constraint (Int ~ a) :: Constraint And you can write *any* type with kind Constraint to the left of (=>): even if that type is a type synonym, type variable, indexed type or so on. The following (somewhat related) changes are also made: 1. We now box equality evidence. This is required because we want to give (Int ~ a) the *lifted* kind Constraint 2. For similar reasons, implicit parameters can now only be of a lifted kind. (?x::Int#) => ty is now ruled out 3. Implicit parameter constraints are now allowed in superclasses and instance contexts (this just falls out as OK with the new constraint solver) Internally the following major changes were made: 1. There is now no PredTy in the Type data type. Instead GHC checks the kind of a type to figure out if it is a predicate 2. There is now no AClass TyThing: we represent classes as TyThings just as a ATyCon (classes had TyCons anyway) 3. What used to be (~) is now pretty-printed as (~#). The box constructor EqBox :: (a ~# b) -> (a ~ b) 4. The type LCoercion is used internally in the constraint solver and type checker to represent coercions with free variables of type (a ~ b) rather than (a ~# b)
* Refactor the imports of InteractiveContextSimon Peyton Jones2011-08-021-25/+28
| | | | | | | | | | | | | | | | | | | | | | | | | | | | Instead of two fields ic_toplev_scope :: [Module] ic_imports :: [ImportDecl RdrName] we now just have one ic_imports :: [InteractiveImport] with the auxiliary data type data InteractiveImport = IIDecl (ImportDecl RdrName) -- Bring the exports of a particular module -- (filtered by an import decl) into scope | IIModule Module -- Bring into scope the entire top-level envt of -- of this module, including the things imported -- into it. This makes lots of code less confusing. No change in behaviour. It's preparatory to fixing Trac #5147. While I was at I also * Cleaned up the handling of the "implicit" Prelude import by adding a ideclImplicit field to ImportDecl. This significantly reduces plumbing in the handling of the implicit Prelude import * Used record notation consistently for ImportDecl
* Separate the warning flags into their own datatypeIan Lynagh2011-07-141-1/+1
| | | | | | | The -w flag wasn't turning off a few warnings (Opt_WarnMissingImportList, Opt_WarnMissingLocalSigs, Opt_WarnIdentities). Rather than just adding them, I've separated the Opt_Warn* contructors off into their own type, so -w now just sets the list of warning flags to [].
* SafeHaskell: Fix validation errors when unsafe base usedDavid Terei2011-06-171-1/+5
|