summaryrefslogtreecommitdiff
path: root/compiler/deSugar/DsArrows.lhs
Commit message (Collapse)AuthorAgeFilesLines
* compiler: de-lhs deSugar/Austin Seipp2014-12-031-1197/+0
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* De-tabify and remove trailing whitespaceSimon Peyton Jones2014-09-261-223/+217
|
* When desugaring Use the smart mkCoreConApps and friendsSimon Peyton Jones2014-08-071-2/+2
| | | | | | | | This is actually the bug that triggered Trac #9390. We had an unboxed tuple (# writeArray# ..., () #), and that writeArray# argument isn't ok-for-speculation, so disobeys the invariant. The desugaring of unboxed tuples was to blame; the fix is easy.
* Add LANGUAGE pragmas to compiler/ source filesHerbert Valerio Riedel2014-05-151-1/+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.
* Instead of tracking Origin in LHsBindsLR, track it in MatchGroupDr. ERDI Gergo2014-04-131-2/+2
|
* Roleify TcCoercionJoachim Breitner2013-11-271-1/+1
| | | | | | | | | | | | Previously, TcCoercion were only used to represent boxed Nominal coercions. In order to also talk about boxed Representational coercions in the type checker, we add Roles to TcCoercion. Again, we closely mirror Coercion. The roles are verified by a few assertions, and at the latest after conversion to Coercion. I have put my trust in the comprehensiveness of the testsuite here, but any role error after desugaring popping up now might be caused by this refactoring.
* Add support for pattern splices.Geoffrey Mainland2013-10-041-0/+1
|
* Globally replace "hackage.haskell.org" with "ghc.haskell.org"Simon Marlow2013-10-011-1/+1
|
* Rearrange the typechecking of arrows, especially arrow "forms"Simon Peyton Jones2013-03-041-211/+275
| | | | | | | | | | | | | | | | | | | | | | | | | | | | The typechecking of arrow forms (in GHC 7.6) is known to be bogus, as described in Trac #5609, because it marches down tuple types that may not yet be fully worked out, depending on when constraint solving happens. Moreover, coercions are generated and simply discarded. The fact that it works at all is a miracle. This refactoring is based on a conversation with Ross, where we rearranged the typing of the argument stack, so that the arrows have the form a (env, (arg1, (arg2, ...(argn, ())))) res rather than a (arg1, (arg2, ...(argn, env))) res as it was before. This is vastly simpler to typecheck; just look at the beautiful, simple type checking of arrow forms now! We need a new HsCmdCast to capture the coercions generated from the argument stack. This leaves us in a better position to tackle the open arrow tickets * Trac #5777 still fails. (I was hoping this patch would cure it.) * Trac #5609 is too complicated for me to grok. Ross? * Trac #344 * Trac #5333
* Add OverloadedLists, allowing list syntax to be overloadedSimon Peyton Jones2013-02-141-1/+1
| | | | | | | | | | | | | | | | | | | | | | | This work was all done by Achim Krause <achim.t.krause@gmail.com> George Giorgidze <giorgidze@gmail.com> Weijers Jeroen <jeroen.weijers@uni-tuebingen.de> It allows list syntax, such as [a,b], [a..b] and so on, to be overloaded so that it works for a variety of types. The design is described here: http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists Eg. you can use it for maps, so that [(1,"foo"), (4,"bar")] :: Map Int String The main changes * The ExplicitList constructor of HsExpr gets witness field * Ditto ArithSeq constructor * Ditto the ListPat constructor of HsPat Everything else flows from this.
* Refactor HsExpr.MatchGroupSimon Peyton Jones2013-01-041-8/+7
| | | | | | | | | | | * Make MatchGroup into a record, and use the record fields * Split the type field into two: mg_arg_tys and mg_res_ty This makes life much easier for the desugarer when the case alterantives are empty A little bit of this change unavoidably ended up in the preceding commit about empty case alternatives
* rename do_map_arrow as do_premap (no semantic change)Ross Paterson2012-12-231-38/+38
|
* This big patch re-factors the way in which arrow-syntax is handledSimon Peyton Jones2012-10-031-57/+63
| | | | | | | | | | | | | | | | | | | | | | All the work was done by Dan Winograd-Cort. The main thing is that arrow comamnds now have their own data type HsCmd (defined in HsExpr). Previously it was punned with the HsExpr type, which was jolly confusing, and made it hard to do anything arrow-specific. To make this work, we now parameterise * MatchGroup * Match * GRHSs, GRHS * StmtLR and friends over the "body", that is the kind of thing they enclose. This "body" parameter can be instantiated to either LHsExpr or LHsCmd respectively. Everything else is really a knock-on effect; there should be no change (yet!) in behaviour. But it should be a sounder basis for fixing bugs.
* Tidy up a remaining glitch in unificationSimon Peyton Jones2012-05-011-2/+2
| | | | | | | | | | | | | | | | | | There was one place, in type checking parallel list comprehensions where we were unifying types, but had no convenient way to use the resulting coercion; instead we just checked that it was Refl. This was Wrong Wrong; it might fail unpredicably in a GADT-like situation, and it led to extra error-generation code used only in this one place. This patch tidies it all up, by moving the 'return' method from the *comprehension* to the ParStmtBlock. The latter is a new data type, now used for each sub-chunk of a parallel list comprehension. Because of the data type change, quite a few modules are touched, but only in a fairly trivial way. The real changes are in TcMatches (and corresponding desugaring); plus deleting code from TcUnify. This patch also fixes the pretty-printing bug in Trac #6060
* fix #5022: polymorphic definitions inside arrow recRoss Paterson2011-12-191-95/+143
| | | | | | | | | | | | | | | | | | | | | | | | | | | This is quite tricky, with examples like this: import Control.Arrow pRepeat :: a -> [a] pRepeat = proc x -> do rec s <- returnA -< f_rec x:s -- f_rec is monomorphic here let f_later y = y -- f_later is polymorphic here _ <- returnA -< (f_later True, f_later 'a') let f_rec y = y -- f_rec is polymorphic here returnA -< f_later s -- f_later is monomorphic here Fixed the typechecking of arrow RecStmt to track changes to the monad version. It was simplest to add a field recS_later_rets corresponding to recS_rec_rets. It's only used for the arrow version, and always empty for the monad version. But I think it would be cleaner to put the rec_ids and later_ids in a single list with supplementary info saying how they're used. Also fixed several glitches in the desugaring of arrow RecStmt. The fact that the monomorphic variables shadow their polymorphic counterparts is a major pain. Also a bit of general cleanup of DsArrows while I was there.
* Allow full constraint solving under a for-all (Trac #5595)Simon Peyton Jones2011-12-051-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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.
* 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.
* Overhaul of infrastructure for profiling, coverage (HPC) and breakpointsSimon Marlow2011-11-021-3/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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)
* 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)
* Merge branch 'master' of http://darcs.haskell.org/ghc into ghc-genericsJose Pedro Magalhaes2011-05-041-7/+8
|\ | | | | | | | | Fixed conflicts: compiler/prelude/PrelNames.lhs
| * Simon's hacking on monad-comp; incompleteSimon Peyton Jones2011-04-291-6/+7
| |
| * Preliminary monad-comprehension patch (Trac #4370)Simon Peyton Jones2011-04-281-2/+2
| | | | | | | | | | | | | | | | This is the work of Nils Schweinsberg <mail@n-sch.de> It adds the language extension -XMonadComprehensions, which generalises list comprehension syntax [ e | x <- xs] to work over arbitrary monads.
* | Remove HsNumTy and TypePati.Jose Pedro Magalhaes2011-05-041-1/+0
|/ | | | They belonged to the old generic deriving mechanism, so they can go. Adapted a lot of code as a consequence.
* Tidy up rebindable syntax for MDosimonpj@microsoft.com2010-12-221-2/+2
| | | | | | | | | | | | | | | | | | | | For a long time an 'mdo' expression has had a SyntaxTable attached to it. However, we're busy deprecating SyntaxTables in favour of rebindable syntax attached to individual Stmts, and MDoExpr was totally inconsistent with DoExpr in this regard. This patch tidies it all up. Now there's no SyntaxTable on MDoExpr, and 'modo' is generally handled much more like 'do'. There is resulting small change in behaviour: now MonadFix is required only if you actually *use* recursion in mdo. This seems consistent with the implicit dependency analysis that is done for mdo. Still to do: * Deal with #4148 (this patch is on the way) * Get rid of the last remaining SyntaxTable on HsCmdTop
* Remove the now-unused constructor VarPatOutsimonpj@microsoft.com2010-11-051-2/+0
|
* Add rebindable syntax for if-then-elsesimonpj@microsoft.com2010-10-221-9/+15
| | | | | | | | | | | There are two main changes * New LANGUAGE option RebindableSyntax, which implies NoImplicitPrelude * if-the-else becomes rebindable, with function name "ifThenElse" (but case expressions are unaffected) Thanks to Sam Anklesaria for doing most of the work here
* Move error-ids to MkCore (from PrelRules)simonpj@microsoft.com2010-09-141-1/+0
| | | | and adjust imports accordingly
* Super-monster patch implementing the new typechecker -- at lastsimonpj@microsoft.com2010-09-131-6/+15
| | | | | | | | | This major patch implements the new OutsideIn constraint solving algorithm in the typecheker, following our JFP paper "Modular type inference with local assumptions". Done with major help from Dimitrios Vytiniotis and Brent Yorgey.
* minor fix to commentRoss Paterson2010-08-221-1/+1
|
* fix #3822: desugaring case command in arrow notationRoss Paterson2010-06-151-17/+11
| | | | | | Get the set of free variables from the generated case expression: includes variables in the guards and decls that were missed before, and is also a bit simpler.
* Fix Trac #3964: view patterns in DsArrowssimonpj@microsoft.com2010-04-091-1/+2
| | | | | Just a missing case; I've eliminated the catch-all so that we get a warning next time we extend HsPat
* Refactor part of the renamer to fix Trac #3901simonpj@microsoft.com2010-03-041-22/+18
| | | | | | | | | | | | | | | | | | | | | | | | | | This one was bigger than I anticipated! The problem was that were were gathering the binders from a pattern before renaming -- but with record wild-cards we don't know what variables are bound by C {..} until after the renamer has filled in the "..". So this patch does the following * Change all the collect-X-Binders functions in HsUtils so that they expect to only be called *after* renaming. That means they don't need to return [Located id] but just [id]. Which turned out to be a very worthwhile simplification all by itself. * Refactor the renamer, and in ptic RnExpr.rnStmt, so that it doesn't need to use collectLStmtsBinders on pre-renamed Stmts. * This in turn required me to understand how GroupStmt and TransformStmts were renamed. Quite fiddly. I rewrote most of it; result is much shorter. * In doing so I flattened HsExpr.GroupByClause into its parent GroupStmt, with trivial knock-on effects in other files. Blargh.
* Minor refactoringsimonpj@microsoft.com2009-10-301-1/+1
| | | | MkCore.mkCoreTupTy moves to TysWiredIn, where it is called mkBoxedTupleTy
* Add 'rec' to stmts in a 'do', and deprecate 'mdo'simonpj@microsoft.com2009-10-281-1/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The change is this (see Trac #2798). Instead of writing mdo { a <- getChar ; b <- f c ; c <- g b ; putChar c ; return b } you would write do { a <- getChar ; rec { b <- f c ; c <- g b } ; putChar c ; return b } That is, * 'mdo' is eliminated * 'rec' is added, which groups a bunch of statements into a single recursive statement This 'rec' thing is already present for the arrow notation, so it makes the two more uniform. Moreover, 'rec' lets you say more precisely where the recursion is (if you want to), whereas 'mdo' just says "there's recursion here somewhere". Lastly, all this works with rebindable syntax (which mdo does not). Currently 'mdo' is enabled by -XRecursiveDo. So we now deprecate this flag, with another flag -XDoRec to enable the 'rec' keyword. Implementation notes: * Some changes in Lexer.x * All uses of RecStmt now use record syntax I'm still not really happy with the "rec_ids" and "later_ids" in the RecStmt constructor, but I don't dare change it without consulting Ross about the consequences for arrow syntax.
* Add tuple sections as a new featuresimonpj@microsoft.com2009-07-231-10/+5
| | | | | | | | | | | | | | | | This patch adds tuple sections, so that (x,,z) means \y -> (x,y,z) Thanks for Max Bolinbroke for doing the hard work. In the end, instead of using two constructors in HsSyn, I used just one (still called ExplicitTuple) whose arguments can be Present (LHsExpr id) or Missing PostTcType While I was at it, I did a bit of refactoring too.
* Handle introduction of MkCore in DsArrowsMax Bolingbroke2008-07-311-0/+1
|
* Split the Id related functions out from Var into Id, document Var and some of IdMax Bolingbroke2008-07-311-0/+1
|
* Make DsArrows warning-freeIan Lynagh2008-05-041-25/+33
|
* Monadify deSugar/DsArrows: use do, return, applicative, standard monad functionsTwan van Laarhoven2008-01-171-402/+344
|
* Implement generalised list comprehensionssimonpj@microsoft.com2007-12-201-41/+41
| | | | | | | | | | | | | | | | | | | | This patch implements generalised list comprehensions, as described in the paper "Comprehensive comprehensions" (Peyton Jones & Wadler, Haskell Workshop 2007). If you don't use the new comprehensions, nothing should change. The syntax is not exactly as in the paper; see the user manual entry for details. You need an accompanying patch to the base library for this stuff to work. The patch is the work of Max Bolingbroke [batterseapower@hotmail.com], with some advice from Simon PJ. The related GHC Wiki page is http://hackage.haskell.org/trac/ghc/wiki/SQLLikeComprehensions
* View patterns, record wildcards, and record punsDan Licata2007-10-101-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch implements three new features: * view patterns (syntax: expression -> pat in a pattern) * working versions of record wildcards and record puns See the manual for detailed descriptions. Other minor observable changes: * There is a check prohibiting local fixity declarations when the variable being fixed is not defined in the same let * The warn-unused-binds option now reports warnings for do and mdo stmts Implementation notes: * The pattern renamer is now in its own module, RnPat, and the implementation is now in a CPS style so that the correct context is delivered to pattern expressions. * These features required a fairly major upheaval to the renamer. Whereas the old version used to collect up all the bindings from a let (or top-level, or recursive do statement, ...) and put them into scope before renaming anything, the new version does the collection as it renames. This allows us to do the right thing with record wildcard patterns (which need to be expanded to see what names should be collected), and it allows us to implement the desired semantics for view patterns in lets. This change had a bunch of domino effects brought on by fiddling with the top-level renaming. * Prior to this patch, there was a tricky bug in mkRecordSelId in HEAD, which did not maintain the invariant necessary for loadDecl. See note [Tricky iface loop] for details.
* Fix CodingStyle#Warnings URLsIan Lynagh2007-09-041-1/+1
|
* Use OPTIONS rather than OPTIONS_GHC for pragmasIan Lynagh2007-09-031-2/+2
| | | | | | | Older GHCs can't parse OPTIONS_GHC. This also changes the URL referenced for the -w options from WorkingConventions#Warnings to CodingStyle#Warnings for the compiler modules.
* FIX for #1080Ross Paterson2007-09-031-2/+64
| | | | | | | Arrow desugaring now uses a private version of collectPatBinders and friends, in order to include dictionary bindings from ConPatOut. It doesn't fix arrowrun004 (#1333), though.
* Add {-# OPTIONS_GHC -w #-} and some blurb to all compiler modulesIan Lynagh2007-09-011-0/+7
|
* Remove mapAccumL, mapAccumR, mapAccumBIan Lynagh2007-07-021-0/+2
| | | | | mapAccumL and mapAccumR are in Data.List now. mapAccumB is unused.
* Breakpoints: get the names of the free variables rightSimon Marlow2007-04-241-2/+2
| | | | | | | | | | | | Previously we relied on the names of the Ids attached to a tick being the same as the names of the original variables in the source code. Sometimes this worked, sometimes it didn't because the simplifier would inline away the Id. So now we do this properly and retain the original OccNames from the source code for each breakpoint, and use these to construct the new Ids when we stop. Doing this involved moving the tracking of in-scope variables from the desugarer to the coverage pass.
* Adding arrows to the acceptable code for hpcandy@galois.com2006-10-251-0/+6
|
* Module header tidyup, phase 1Simon Marlow2006-10-111-30/+23
| | | | | | | | | | | | This patch is a start on removing import lists and generally tidying up the top of each module. In addition to removing import lists: - Change DATA.IOREF -> Data.IORef etc. - Change List -> Data.List etc. - Remove $Id$ - Update copyrights - Re-order imports to put non-GHC imports last - Remove some unused and duplicate imports
* Global renamings in HsSynsimonpj@microsoft.com2006-09-291-2/+2
|