- 09 May, 2015 1 commit
-
-
Edward Z. Yang authored
Summary: This commit adds stage 1 support for Template Haskell quoting, e.g. [| ... expr ... |], which is useful for authors of quasiquoter libraries that do not actually need splices. The TemplateHaskell extension now does not unconditionally fail; it only fails if the renamer encounters a splice that it can't run. In order to make sure the referenced data structures are consistent, template-haskell is now a boot library. In the following patches, there are: - A few extra safety checks which should be enabled in stage1 - Separation of the th/ testsuite into quotes/ which can be run on stage1 Note for reviewer: big diff changes are simply code being moved out of an ifdef; there was no other substantive change to that code. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, austin, goldfire Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D876 GHC Trac Issues: #10382
-
- 08 May, 2015 4 commits
-
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Alan Zimmerman authored
Summary: The parser production for squals has : squals ',' transformqual {% addAnnotation (gl $ last $ unLoc $1) AnnComma (gl $2) >> ams (sLL $1 $> ()) (fst $ unLoc $3) >> return (sLL $1 $> [sLL $1 $> ((snd $ unLoc $3) (reverse (unLoc $1)))]) } This attaches the comma to the wrong part of the squals, as it is generated in reverse order. Test Plan: ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: bgamari, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D846 GHC Trac Issues: #10312
-
Alan Zimmerman authored
Summary: For the following code {-# LANGUAGE TupleSections #-} foo = do liftIO $ atomicModifyIORef ciTokens ((,()) . f) the annotation is missing for the comma. Test Plan: ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D834 GHC Trac Issues: #10280
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
- 07 May, 2015 4 commits
-
-
Alan Zimmerman authored
Summary: The RdrHsSyn.isFunLhs function has the following isFunLhs e = go e [] where go (L loc (HsVar f)) es | not (isRdrDataCon f) = return (Just (L loc f, False, es)) go (L _ (HsApp f e)) es = go f (e:es) go (L _ (HsPar e)) es@(_:_) = go e es The treatment of HsPar means that any parentheses around an infix function will be discarded. e.g. (f =*= g) sa i = f (toF sa i) =^= g (toG sa i) will lose the ( before f and the closing one after g Test Plan: ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D832 GHC Trac Issues: #10269
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
...to make clearer what the cross-stage lifting code applies to (c.f. Trac #10384)
-
Simon Peyton Jones authored
-
- 06 May, 2015 11 commits
-
-
Austin Seipp authored
This reverts commit fb54b2c1. As Alan pointed out, this will make cherry picking a lot harder until 7.10.2, so lets back it out until after the release.
-
Austin Seipp authored
This reverts commit 81030ede. Alan is abandoning this approach in favor of D836.
-
Alan Zimmerman authored
When parsing {-# LANGUAGE ScopedTypeVariables #-} extremumNewton :: forall tag. forall tag1. tag -> tag1 -> Int extremumNewton = undefined The parser attaches an AnnForall to the second forall, which appears as a nested HsForAllTy. Somewhere this nesting is flattened, and the tyvarbndrs are collapsed into a single HsForAllTy. In this process the second AnnForAll loses its anchor in the AST. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D833 GHC Trac Issues: #10278
-
Alan Zimmerman authored
The HsOpTy can be constructed for a promoted type operator, in which case it has the following form | btype SIMPLEQUOTE qconop type { sLL $1 $> $ mkHsOpTy $1 $3 $4 } | btype SIMPLEQUOTE varop type { sLL $1 $> $ mkHsOpTy $1 $3 $4 } The SIMPLEQUOTE does not get an annotation, so cannot be reproduced via the API Annotations. Also, in splice_exp :: { LHsExpr RdrName } : TH_ID_SPLICE { sL1 $1 $ mkHsSpliceE (sL1 $1 $ HsVar (mkUnqual varName (getTH_ID_SPLICE $1))) } | '$(' exp ')' {% ams (sLL $1 $> $ mkHsSpliceE $2) [mo $1,mc $3] } | TH_ID_TY_SPLICE { sL1 $1 $ mkHsSpliceTE (sL1 $1 $ HsVar (mkUnqual varName (getTH_ID_TY_SPLICE $1))) } | '$$(' exp ')' {% ams (sLL $1 $> $ mkHsSpliceTE $2) [mo $1,mc $3] } the TH_ID_SPLICE and TH_ID_TY_SPLICE positions are lost. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D825 GHC Trac Issues: #10268
-
Matthew Pickering authored
See #10299 Previously `'[]` was parsed to a `HsTyVar` rather than a `HsExplicitListTy`. This patch fixes the shift-reduce conflict which caused this problem. Reviewed By: alanz, austin Differential Revision: https://phabricator.haskell.org/D840
-
Alan Zimmerman authored
At the moment ghc-exactprint, which uses the GHC API Annotations to provide a framework for roundtripping Haskell source code with optional AST edits, has to implement a horrible workaround to manage the points where layout needs to be captured. These are MatchGroup HsDo HsCmdDo HsLet LetStmt HsCmdLet GRHSs To provide a more natural representation, the contents subject to layout rules need to be wrapped in a SrcSpan. This commit does this. Trac ticket #10250 Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D815 GHC Trac Issues: #10250
-
bernalex authored
Signed-off-by:
Alexander Berntsen <alexander@plaimi.net> Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D872
-
Javran Cheng authored
Depends on D767 Setting this flag prevents RTS from giving RTS suggestions like "Use `+RTS -Ksize -RTS' to increase it." According to the comment @rwbarton made in #9579, sometimes "+RTS" suggestions don't make sense (e.g. when the program is precompiled and installed through package managers), we can encourage people to distribute binaries with either "-no-rtsopts-suggestions" or "-rtsopts". Reviewed By: erikd, austin Differential Revision: https://phabricator.haskell.org/D809 GHC Trac Issues: #9579
-
Zejun Wu authored
Retain ic_monad and ic_int_print in InteractiveContext after load when they are defined in external packages. This is supposed to be the desired behavior that the interactive-print and setGHCiMonad will survive after :cd, :add, :load, :reload and :set in GHCi. Test Plan: Install a interactive-print function and GHCi monad from extenal pacakge. Try :cd, :load and other commands, make sure that the interactive-print function and GHCi monad always keep the same. Reviewed By: simonmar Differential Revision: https://phabricator.haskell.org/D867
-
Vikraman Choudhury authored
I noticed this typo while using template haskell. Signed-off-by:
Vikraman Choudhury <git@vikraman.org> Test Plan: ``` λ> :set -XTemplateHaskell λ> :m +Language.Haskell.TH λ> data Foo = Foo λ> $(conE ''Foo) <interactive>:9:9: Type constructor ‘Foo’ used where a value identifier was expected In the expression: Foo In an equation for ‘f’: f = Foo ``` Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D871
-
Christiaan Baaij authored
Before, the type of an expression, and the type of a variable binding that expression used to be different in GHCi. The reason being that types of bound variables were already normalised. Now, both are normalised. This implements the suggestions as given in Trac #10321 Also adds an expected output for test T10321 Reviewed By: goldfire, simonpj Differential Revision: https://phabricator.haskell.org/D870 GHC Trac Issues: #10321
-
- 05 May, 2015 2 commits
-
-
Edward Z. Yang authored
Clarify that repeated checkCrossStageLifting in RnSplice/TcExpr check untyped/typed brackets, respectively. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Erik de Castro Lopo authored
This was supposed to be part of commit 63a10bbc but I pushed from the wrong machine. This fixes cross compiling to arm. Signed-off-by:
Erik de Castro Lopo <erikd@mega-nerd.com>
-
- 04 May, 2015 5 commits
-
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D850
-
Edward Z. Yang authored
Previously, if we got a package key in our splice, we'd give a very unhelpful error message saying we couldn't find a package 'base-4.7.0.1', despite there being a package with that source package ID. Really, we couldn't find a package with that *key*, so clarify, and also tell the user what the real package key is. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Erik de Castro Lopo authored
Test was failing (could not execute: pgmlc) for arm (which uses the llvm backend) due to the `-pgmlc pgmlc` in OPTIONS_GHC. It was also failing on amd64 in the same way when `-fllvm` was added to the command line. Its safe to remove because the compiler should already know which llvm tool to use. Test Plan: validate Reviewers: dterei, austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D874
-
Erik de Castro Lopo authored
Test `T703` was found to be failing on arm/linux. The solution was to add a linker flag to explicitly set the stack to non-executable. Signed-off-by:
Erik de Castro Lopo <erikd@mega-nerd.com> Test Plan: validate on x86_64 and arm linux Reviewers: ezyang, rwbarton, austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D875 GHC Trac Issues: #10369
-
Adam Gundry authored
Fixes #9840 and #10306, and includes an alternative resolution to #8028. This permits empty closed type families, and documents them in the user guide. It updates the Haddock submodule to support the API change. Test Plan: Added `indexed-types/should_compile/T9840` and updated `indexed-types/should_fail/ClosedFam4` and `th/T8028`. Reviewers: austin, simonpj, goldfire Reviewed By: goldfire Subscribers: bgamari, jstolarek, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D841 GHC Trac Issues: #9840, #10306
-
- 01 May, 2015 6 commits
-
-
Simon Peyton Jones authored
This motivation is to declare class IP much earlier (in ghc-prim), so that implicit parameters (which depend on IP) is available to library code, notably the 'error' function. * Move class IP from base:GHC.IP to ghc-prim:GHC.Classes * Delete module GHC.IP from base * Move types Symbol and Nat from base:GHC.TypeLits to ghc-prim:GHC.Types There was a name clash in GHC.RTS.Flags, where I renamed the local type Nat to RtsNat.
-
Simon Peyton Jones authored
We were trying to load the type for Integer to do defaulting in ghc-prim, but it's simply not available at that time.
-
Simon Peyton Jones authored
See Note [Deriveds do rewrite Deriveds]. The important point is that we want to maintain the Note [Can-rewrite relation] property, lest we risk loops.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
This makes TupleTyCon into an ordinary AlgTyCon, distinguished by its AlgTyConRhs, rather than a separate constructor of TyCon. It is preparatory work for making constraint tuples into classes, for which the ConstraintTuple tuples will have a TyConParent of a ClassTyCon. Tuples didn't have this possiblity before. The patch affects other modules because I eliminated the unsatisfactory partial functions tupleTyConBoxity and tupleTyConSort. And tupleTyConArity which is just tyConArity.
-
Simon Peyton Jones authored
-
- 30 Apr, 2015 3 commits
-
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Gabor Greif authored
-
Simon Peyton Jones authored
Previously (Trac #10351) we could get Non type-variable argument in the constraint: C [t] (Use FlexibleContexts to permit this) When checking that `f' has the inferred type f :: forall t. C [t] => t -> () which is a bit stupid: we have *inferred* a type that we immediately *reject*. This patch arranges that that the generalisation mechanism (TcSimplify.decideQuantification) doesn't pick a predicate that will be rejected by the subsequent validity check. This forced some minor refactoring, as usual.
-
- 29 Apr, 2015 4 commits
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Fixed by the patch for #10009
-
Simon Peyton Jones authored
This regrettably-big patch substantially improves the way in which "improvement" happens in the constraint solver. It was triggered by trying to crack Trac #10009, but it turned out to solve #10340 as well. The big picture, with several of the trickiest examples, is described in Note [The improvement story] in TcInteract. The major change is this: * After solving we explicitly try "improvement", by - making the unsolved Wanteds into Deriveds - allowing Deriveds to rewrite Deriveds This more aggressive rewriting "unlocks" some extra guess-free unifications. * The main loop is in TcInteract.solveSimpleWanteds, but I also ended up refactoring TcSimplify.simpl_loop, and its surrounding code. Notably, any insolubles from the Givens are pulled out and treated separately, rather than staying in the inert set during the solveSimpleWanteds loop. There are a lot of follow-on changes * Do not emit generate Derived improvements from Wanteds. This saves work in the common case where they aren't needed. * For improvement we should really do type-class reduction on Derived constraints in doTopReactDict. That entailed changing the GenInst constructor a bit; a local and minor change * Some annoying faffing about with dropping derived constraints; see dropDerivedWC, dropDerivedSimples, dropDerivedInsols, and their Notes. * Some substantial refactoring in TcErrors.reportWanteds. This work wasn't strictly forced, but I got sucked into it. All the changes are in TcErrors. * Use TcS.unifyTyVar consistently, rather than setWantedTyBind, so that unifications are properly tracked. * Refactoring around solveWantedsTcM, solveWantedsAndDrop. They previously guaranteed a zonked result, but it's more straightforward for clients to zonk.
-
Simon Peyton Jones authored
Because when flattening a Derived constraint, the evidence doesn't exist (it's an error thunk)
-