summaryrefslogtreecommitdiff
path: root/compiler/parser
Commit message (Collapse)AuthorAgeFilesLines
* Allow full constraint solving under a for-all (Trac #5595)Simon Peyton Jones2011-12-052-0/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The main idea is that when we unify forall a. t1 ~ forall a. t2 we get constraints from unifying t1~t2 that mention a. We are producing a coercion witnessing the equivalence of the for-alls, and inside *that* coercion we need bindings for the solved constraints arising from t1~t2. We didn't have way to do this before. The big change is that here's a new type TcEvidence.TcCoercion, which is much like Coercion.Coercion except that there's a slot for TcEvBinds in it. This has a wave of follow-on changes. Not deep but broad. * New module TcEvidence, which now contains the HsWrapper TcEvBinds, EvTerm etc types that used to be in HsBinds * The typechecker works exclusively in terms of TcCoercion. * The desugarer converts TcCoercion to Coercion * The main payload is in TcUnify.unifySigmaTy. This is the function that had a gross hack before, but is now beautiful. * LCoercion is gone! Hooray. Many many fiddly changes in conssequence. But it's nice.
* Merge branch 'master' of http://darcs.haskell.org/ghcDavid Waern2011-11-292-0/+9
|\
| * Implement a capi calling convention; fixes #2979Ian Lynagh2011-11-282-0/+8
| | | | | | | | | | | | | | | | | | In GHC, this provides an easy way to call a C function via a C wrapper. This is important when the function is really defined by CPP. Requires the new CApiFFI extension. Not documented yet, as it's still an experimental feature at this stage.
| * Allow the quotes to be omitted in {-# SCC "<varid>" #-}Simon Marlow2011-11-281-0/+1
| |
* | Merge branch 'master' of http://darcs.haskell.org/ghcDavid Waern2011-11-263-10/+25
|\ \ | |/
| * Fix newtype wrapper for 'PData[s] (Wrap a)' and fix VECTORISE type and ↵Manuel M T Chakravarty2011-11-251-3/+4
| | | | | | | | | | | | | | | | instance pragmas * Correct usage of new type wrappers from MkId * 'VECTORISE [SCALAR] type T = S' didn't work correctly across module boundaries * Clean up 'VECTORISE SCALAR instance'
| * Support "phase control" for SPECIALISE pragmasSimon Peyton Jones2011-11-242-6/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | This featurelet allows Trac #5237 to be fixed. The idea is to allow SPECIALISE pragmas to specify the phases in which the RULE is active, just as you can do with RULES themselves. {-# SPECIALISE [1] foo :: Int -> Int #-} This feature is so obvious that not having it is really a bug. There are, needless to say, a few wrinkles. See Note [Activation pragmas for SPECIALISE] in DsBinds
| * Decode escape sequences properly in line pragmas (see comment for details).Simon Marlow2011-11-231-1/+13
| |
* | Keep unicode characters in Haddock comments and comments in the token stream.David Waern2011-11-251-12/+12
|/
* Track #included files for recompilation checking (#4900, #3589)Simon Marlow2011-11-181-0/+6
| | | | | | | | | | This was pretty straightforward: collect the filenames in the lexer, and add them in to the tcg_dependent_files list that the typechecker collects. Note that we still don't get #included files in the ghc -M output. Since we don't normally lex the whole file in ghc -M, this same mechanism can't be used directly.
* Removing the default grouping clause from the SQL-like comprehension notation ;George Giorgidze2011-11-171-14/+8
|
* Changes to the kind checkerJose Pedro Magalhaes2011-11-161-2/+2
| | | | | | | | | | | | | We now always check against an expected kind. When we really don't know what kind to expect, we match against a new meta kind variable. Also, we are more explicit about tuple sorts: HsUnboxedTuple -> Produced by the parser HsBoxedTuple -> Certainly a boxed tuple HsConstraintTuple -> Certainly a constraint tuple HsBoxedOrConstraintTuple -> Could be a boxed or a constraint tuple. Produced by the parser only, disappears after type checking
* Restore file modeJose Pedro Magalhaes2011-11-111-0/+0
|
* New kind-polymorphic coreJose Pedro Magalhaes2011-11-114-72/+104
| | | | | | | | | This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds
* added NOUNPACK pragma (see #2338)Stefan Wehr2011-11-092-0/+4
|
* Use -fwarn-tabs when validatingIan Lynagh2011-11-042-0/+14
| | | | | We only use it for "compiler" sources, i.e. not for libraries. Many modules have a -fno-warn-tabs kludge for now.
* Overhaul of infrastructure for profiling, coverage (HPC) and breakpointsSimon Marlow2011-11-022-2/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | User visible changes ==================== Profilng -------- Flags renamed (the old ones are still accepted for now): OLD NEW --------- ------------ -auto-all -fprof-auto -auto -fprof-exported -caf-all -fprof-cafs New flags: -fprof-auto Annotates all bindings (not just top-level ones) with SCCs -fprof-top Annotates just top-level bindings with SCCs -fprof-exported Annotates just exported bindings with SCCs -fprof-no-count-entries Do not maintain entry counts when profiling (can make profiled code go faster; useful with heap profiling where entry counts are not used) Cost-centre stacks have a new semantics, which should in most cases result in more useful and intuitive profiles. If you find this not to be the case, please let me know. This is the area where I have been experimenting most, and the current solution is probably not the final version, however it does address all the outstanding bugs and seems to be better than GHC 7.2. Stack traces ------------ +RTS -xc now gives more information. If the exception originates from a CAF (as is common, because GHC tends to lift exceptions out to the top-level), then the RTS walks up the stack and reports the stack in the enclosing update frame(s). Result: +RTS -xc is much more useful now - but you still have to compile for profiling to get it. I've played around a little with adding 'head []' to GHC itself, and +RTS -xc does pinpoint the problem quite accurately. I plan to add more facilities for stack tracing (e.g. in GHCi) in the future. Coverage (HPC) -------------- * derived instances are now coloured yellow if they weren't used * likewise record field names * entry counts are more accurate (hpc --fun-entry-count) * tab width is now correct (markup was previously off in source with tabs) Internal changes ================ In Core, the Note constructor has been replaced by Tick (Tickish b) (Expr b) which is used to represent all the kinds of source annotation we support: profiling SCCs, HPC ticks, and GHCi breakpoints. Depending on the properties of the Tickish, different transformations apply to Tick. See CoreUtils.mkTick for details. Tickets ======= This commit closes the following tickets, test cases to follow: - Close #2552: not a bug, but the behaviour is now more intuitive (test is T2552) - Close #680 (test is T680) - Close #1531 (test is result001) - Close #949 (test is T949) - Close #2466: test case has bitrotted (doesn't compile against current version of vector-space package)
* VECTORISE pragmas for type classes and instancesManuel M T Chakravarty2011-10-311-0/+5
| | | | * Frontend support (not yet used in the vectoriser)
* Tabs -> spacesManuel M T Chakravarty2011-10-311-924/+924
|
* Setup new Safe Haskell interfaceDavid Terei2011-10-251-1/+1
|
* Unconditionally derive some instancesIan Lynagh2011-10-251-3/+1
| | | | They used to be only derived when DEBUG was on
* Layout onlySimon Peyton Jones2011-10-241-4/+5
|
* fix panic in string-gap lexing (#5425)Simon Marlow2011-10-101-2/+3
|
* Fully implement for VECTORISE type pragmas (non-SCALAR).Manuel M T Chakravarty2011-10-101-4/+9
|
* Handle newtypes and type functions correctly in FFI types; fixes #3008Ian Lynagh2011-10-011-3/+3
| | | | | | You can now use type functions in FFI types. Newtypes are now only looked through if the constructor is in scope.
* Tidy up the shape-checking for instance typesSimon Peyton Jones2011-09-292-25/+3
| | | | | | (in instance and standalone deriving decls) Fixes Trac #5513.
* Give a better error message for unterminated quasiquotations (fixes #5204).Geoffrey Mainland2011-09-291-5/+10
|
* Define a TraditionalRecordSyntax extension; fixes #3356Ian Lynagh2011-09-273-3/+20
| | | | | | This allows the extension (which is on by default) to be turned off, which gets us a small step closer to replacing Haskell98 records with something better.
* Whitespace only in parser/RdrHsSyn.lhsIan Lynagh2011-09-271-284/+284
|
* Change the way IfExtName is serialized so (most) wired-in names get special ↵Max Bolingbroke2011-09-271-12/+9
| | | | | | | | representation This lets IfaceType be dumber, with fewer special cases, because deserialization for more wired-in names will work. Once we have polymorphic kinds we will be able to replace IfaceTyCon with a simple IfExtName.
* Merge branch 'no-pred-ty'Max Bolingbroke2011-09-094-67/+49
|\ | | | | | | | | | | | | | | | | | | Conflicts: compiler/iface/BuildTyCl.lhs compiler/iface/MkIface.lhs compiler/iface/TcIface.lhs compiler/typecheck/TcTyClsDecls.lhs compiler/types/Class.lhs compiler/utils/Util.lhs
| * ConstraintKind -> ConstraintKindsSimon Peyton Jones2011-09-071-2/+2
| |
| * Implement -XConstraintKindMax Bolingbroke2011-09-064-67/+49
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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)
* | Implement associated type defaultsMax Bolingbroke2011-09-091-5/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Basically, now you can write: class Cls a where type Typ a type Typ a = Just a And now if an instance does not specify an explicit associated type instance, one will be generated afresh based on that default. So for example this instance: instance Cls Int where Will be equivalent to this one: instance Cls Int where type Typ Int = Just Int
* | Revert "Get rid of associated-type default declarations"Max Bolingbroke2011-09-092-2/+9
|/ | | | This reverts commit 5e102e64d6e581e3ea1f290547fc4be6fce20a00.
* Get rid of associated-type default declarationsSimon Peyton Jones2011-09-012-9/+2
| | | | | | | | | | | | We had the idea that you might be able to define a default instance for an associated type family, thus: class C a where type T a :: * type T a = a -> a It's an idea that makes sense, but it was only 10% implemented. This patch just removes that misleading 10%.
* Allow associated types to have fresh parametersSimon Peyton Jones2011-09-011-12/+14
| | | | | | | | | | | | | | | | | This patch allows class C a where type T a b :: * instance C Int type T Int b = b -> b That is, T has a type index 'b' that is not one of the class variables. On the way I did a good deal of refactoring (as usual), especially in TcInstDcls.tcLocalInstDecl1, which checks for consistent instantiation of the class instance and the type instance. Less code, more expressiveness. See Note [Checking consistent instantiation]
* Add VECTORISE [SCALAR] type pragmaManuel M T Chakravarty2011-08-191-5/+9
| | | | | | | | | - Pragma to determine how a given type is vectorised - At this stage only the VECTORISE SCALAR variant is used by the vectoriser. - '{-# VECTORISE SCALAR type t #-}' implies that 't' cannot contain parallel arrays and may be used in vectorised code. However, its constructors can only be used in scalar code. We use this, e.g., for 'Int'. - May be used on imported types See also http://hackage.haskell.org/trac/ghc/wiki/DataParallel/VectPragma
* Update to work with Alex 3.0: basically disabling Alex's new UnicodeSimon Marlow2011-08-051-3/+12
| | | | | | support because we have our own, and defining alexGetByte instead of alexGetChar (actually we also define alexGetChar, for backwards compatibility).
* Remove all escape handling from quasiquotes; fixes Trac #5348Simon Peyton Jones2011-08-031-10/+6
| | | | There is a long discussion in the ticket.
* Refactor the imports of InteractiveContextSimon Peyton Jones2011-08-021-1/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* White space onlySimon Peyton Jones2011-07-271-1/+1
|
* Separate the warning flags into their own datatypeIan Lynagh2011-07-141-4/+4
| | | | | | | 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 [].
* More Lexer.x tidy-upsIan Lynagh2011-07-141-8/+4
|
* Remove some unused, commented-out code from Lexer.xIan Lynagh2011-07-141-38/+7
|
* Whitespace in Lexer.xIan Lynagh2011-07-141-484/+485
|
* Remove 'threadsafe' FFI importsIan Lynagh2011-07-133-10/+3
| | | | They've been deprecated since GHC 6.12.
* Fix bug in parsing of module headers (see #5243)Simon Marlow2011-07-121-3/+7
|
* Make an extension for interruptible FFI callsIan Lynagh2011-07-111-26/+29
|
* SafeHaskell: Add safe import flag (not functional)David Terei2011-06-172-3/+10
|