summaryrefslogtreecommitdiff
path: root/compiler/parser
Commit message (Collapse)AuthorAgeFilesLines
...
* Change 'Tab character' warnings so there is one per file (#9723)Dave Laing2015-04-021-2/+37
| | | | | | | | Reviewed By: nomeata, thomie Differential Revision: https://phabricator.haskell.org/D760 Signed-off-by: Dave Laing <dave.laing.80@gmail.com>
* Syntax check package-qualified imports (#9225)Thomas Miedema2015-03-311-2/+10
| | | | | | | | | Version numbers are not allowed in the package name of a package-qualified import. Reviewed By: austin, ezyang Differential Revision: https://phabricator.haskell.org/D755
* Correct documentation in `Parser`.Matthew Pickering2015-03-211-2/+2
| | | | | | | | | Removed a trailing `in` from the final line which caused a compilation error. [skip ci] Reviewed by: thomie Differential Revision: https://phabricator.haskell.org/D744
* Re-export `<$>` from Prelude (#10113)Herbert Valerio Riedel2015-03-071-0/+2
| | | | | | | | | | | | | | | | | | | | | Whether to re-export the `<$>` non-method operator from `Prelude` wasn't explicitly covered in the original AMP proposal[1], but it turns out that not doing so forces most code that makes use of applicatives to import `Data.Functor` or `Control.Applicative` just to get that operator into scope. To this end, it was proposed to add `<$>` to Prelude as well[2]. The down-side is that this increases the amount of redundant-import warnings triggered, as well as the relatively minor issue of stealing the `<$>` operator from the default namespace for good (although at this point `<$>` is supposed to be ubiquitous anyway due to `Applicative` being implicitly required into the next Haskell Report) [1]: https://wiki.haskell.org/Functor-Applicative-Monad_Proposal [2]: http://thread.gmane.org/gmane.comp.lang.haskell.libraries/24161 Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D680
* Update shift/reduce commentary in Parser.yEdward Z. Yang2015-03-061-111/+272
| | | | | | | | | | | | Summary: Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: none Reviewers: austin, simonpj, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D697
* Refactor the handling of quasi-quotesSimon Peyton Jones2015-02-102-12/+9
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | As Trac #10047 points out, a quasi-quotation [n|...blah...|] is supposed to behave exactly like $(n "...blah..."). But it doesn't! This was outright wrong: quasiquotes were being run even inside brackets. Now that TH supports both typed and untyped splices, a quasi-quote is properly regarded as a particular syntax for an untyped splice. But apart from that they should be treated the same. So this patch refactors the handling of quasiquotes to do just that. The changes touch quite a lot of files, but mostly in a routine way. The biggest changes by far are in RnSplice, and more minor changes in TcSplice. These are the places where there was real work to be done. Everything else is routine knock-on changes. * No more QuasiQuote forms in declarations, expressions, types, etc. So we get rid of these data constructors * HsBinds.QuasiQuoteD * HsExpr.HsSpliceE * HsPat.QuasiQuotePat * HsType.HsQuasiQuoteTy * We get rid of the HsQuasiQuote type altogether * Instead, we augment the HsExpr.HsSplice type to have three consructors, for the three types of splice: * HsTypedSplice * HsUntypedSplice * HsQuasiQuote There are some related changes in the data types in HsExpr near HsSplice. Specifically: PendingRnSplice, PendingTcSplice, UntypedSpliceFlavour. * In Hooks, we combine rnQuasiQuoteHook and rnRnSpliceHook into one. A smaller, clearer interface. * We have to update the Haddock submodule, to accommodate the hsSyn changes
* GRHS with empty wherebinds gets wrong SrcSpanAlan Zimmerman2015-02-051-1/+1
| | | | | | | | | | | | | | | | | Summary: When parsing a rhs, the GRHS is constructed via unguardedRHS which is given a SrcSpan which only takes account of the '=' and wherebinds, so does not include the exp when wherebinds are empty. Test Plan: ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D643
* compiler/parser/cutils: drop unused 'ghc_memcmp_off' helperSergei Trofimovich2015-01-202-7/+0
| | | | | | | | | | | | | | | Function came out of use in 2006: > commit 9d7da331989abcd1844e9d03b8d1e4163796fa85 > Author: simonmar <unknown> > Date: Fri Jan 6 16:30:19 2006 +0000 > > [project @ 2006-01-06 16:30:17 by simonmar] > Add support for UTF-8 source files Found by uselex.rb: ghc_memcmp_off: [R]: exported from: ./compiler/stage1/build/parser/cutils.o ./compiler/stage2/build/parser/cutils.o Signed-off-by: Sergei Trofimovich <siarheit@google.com>
* API Annotations documentation update, parsing issue, add example testAlan Zimmerman2015-01-193-13/+22
| | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Add a reference note to each AnnKeywordId haddock comment so GHC developers will have an idea why they are there. Add a new test to ghc-api/annotations to serve as a template for other GHC developers when they need to update the parser. It provides output which checks that each SrcSpan that an annotation is attached to actually appears in the `ParsedSource`, and lists the individual annotations. The idea is that a developer writes a version of this which parses a sample file using whatever syntax is changed in Parser.y, and can then check that all the annotations come through. Depends on D538 Test Plan: ./validate Reviewers: simonpj, hvr, austin Reviewed By: austin Subscribers: thomie, jstolarek Differential Revision: https://phabricator.haskell.org/D620
* API Annotations tweaks.Alan Zimmerman2015-01-164-506/+725
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: HsTyLit now has SourceText Update documentation of HsSyn to reflect which annotations are attached to which element. Ensure that the parser always keeps HsSCC and HsTickPragma values, to be ignored in the desugar phase if not needed Bringing in SourceText for pragmas Add Location in NPlusKPat Add Location in FunDep Make RecCon payload Located Explicitly add AnnVal to RdrName where it is compound Add Location in IPBind Add Location to name in IEThingAbs Add Maybe (Located id,Bool) to Match to track fun_id,infix This includes converting Match into a record and adding a note about why the fun_id needs to be replicated in the Match. Add Location in KindedTyVar Sort out semi-colons for parsing - import statements - stmts - decls - decls_cls - decls_inst This updates the haddock submodule. Test Plan: ./validate Reviewers: hvr, austin, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D538
* Fix panics of PartialTypeSignatures combined with extensionsThomas Winant2015-01-131-2/+13
| | | | | | | | | | | | | | | | | | | Summary: Disallow wildcards in stand-alone deriving instances (StandaloneDeriving), default signatures (DefaultSignatures) and instances signatures (InstanceSigs). Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: carter, thomie, monoidal Differential Revision: https://phabricator.haskell.org/D595 GHC Trac Issues: #9922
* Improve HsBangSimon Peyton Jones2015-01-081-5/+5
| | | | | | | | | | | | Provoked by questions from Johan - Improve comments, fix misleading stuff - Add commented synonyms for HsSrcBang, HsImplBang, and use them throughout - Rename HsUserBang to HsSrcBang - Rename dataConStrictMarks to dataConSrcBangs dataConRepBangs to dataConImplBangs This renaming affects Haddock in a trivial way, hence submodule update
* Rename NamedWildcards flag to NamedWildCardsThomas Winant2014-12-231-1/+1
| | | | | | | | | | | | | | | | Summary: Mind the capital C. As there is already a flag RecordWildCards with a capital C, we should at least try to be consistent in the spelling of WildCards. Test Plan: validate Reviewers: goldfire, simonpj, austin Reviewed By: simonpj, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D584
* Parser: use 'error' token in error reporting rulesSergei Trofimovich2014-12-161-13/+20
| | | | | | | | | | | | | | | | Summary: It exempts us from 11 reduce/reduce conflicts and 12 shift/reduce conflicts. Signed-off-by: Sergei Trofimovich <siarheit@google.com> Reviewers: simonpj, mikeizbicki, austin, simonmar Reviewed By: simonmar Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D571
* Generalized Coverage pass to allow adding multiple types of TickishsPeter Wortmann2014-12-162-4/+7
| | | | | | | | This allows having, say, HPC ticks, automatic cost centres and source notes active at the same time. We especially take care to un-tangle the infrastructure involved in generating them. (From Phabricator D169)
* Improve documentation of syntax for promoted listsSimon Peyton Jones2014-12-151-2/+6
| | | | | | | THe documentation in 7.9.4 of promoted list and tuple types was misleading, which led to Trac #9882. This patch makes explicit that only type-level with two or more elements can have the quote omitted.
* Fix panic on [t| _ |] (Trac #9879)Thomas Winant2014-12-151-1/+4
| | | | | | | | | | | | | | | | | | | | Summary: Type brackets containing a wildcard, e.g. `[t| _ |]`, caused a panic. Fix it by disallowing wildcards in type brackets. Together with D572, this fixes #9879. Test Plan: new test WildcardInTypeBrackets should pass Reviewers: austin Reviewed By: austin Subscribers: carter, thomie, monoidal Differential Revision: https://phabricator.haskell.org/D573 GHC Trac Issues: #9879
* Parser: remove unused rule (copy/paste error)Sergei Trofimovich2014-12-131-7/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Found out when tracking down conflicts reported by happy. It was accidentally introduced in large Api Annotations patch: 803fc5db31f084b73713342cdceaed5a9c664267 Before: unused rules: 1 shift/reduce conflicts: 60 reduce/reduce conflicts: 16 After: shift/reduce conflicts: 60 reduce/reduce conflicts: 12 Unused rule is seen in happy's --info= output as: rule 180 is unused ... decl_cls -> 'default' infixexp '::' sigtypedoc (180) decl_cls -> 'default' infixexp '::' sigtypedoc (181) While at it removed 'q' typo in parser conflict log :) Signed-off-by: Sergei Trofimovich <siarheit@google.com> Reviewers: simonmar, austin, alanz Reviewed By: alanz Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D569
* Implement -XStaticValuesFacundo Domínguez2014-12-092-0/+9
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: As proposed in [1], this extension introduces a new syntactic form `static e`, where `e :: a` can be any closed expression. The static form produces a value of type `StaticPtr a`, which works as a reference that programs can "dereference" to get the value of `e` back. References are like `Ptr`s, except that they are stable across invocations of a program. The relevant wiki pages are [2, 3], which describe the motivation/ideas and implementation plan respectively. [1] Jeff Epstein, Andrew P. Black, and Simon Peyton-Jones. Towards Haskell in the cloud. SIGPLAN Not., 46(12):118–129, September 2011. ISSN 0362-1340. [2] https://ghc.haskell.org/trac/ghc/wiki/StaticPointers [3] https://ghc.haskell.org/trac/ghc/wiki/StaticPointers/ImplementationPlan Authored-by: Facundo Domínguez <facundo.dominguez@tweag.io> Authored-by: Mathieu Boespflug <m@tweag.io> Authored-by: Alexander Vershilov <alexander.vershilov@tweag.io> Test Plan: `./validate` Reviewers: hvr, simonmar, simonpj, austin Reviewed By: simonpj, austin Subscribers: qnikst, bgamari, mboes, carter, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D550 GHC Trac Issues: #7015
* Fix parser for UNPACK pragmasSimon Peyton Jones2014-12-011-5/+5
| | | | | | | | {-# NOUNPACK #-} {-# NOUNPACK #-} ! were being parsed the same way. The former was wrong. Thanks to Alan Zimmerman for pointing this out
* More Tweaks for API AnotationsAlan Zimmerman2014-11-303-30/+66
| | | | | | | | | | | | | | Summary: Attaching semis to preceding AST element, not following Test Plan: sh ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: cactus, thomie, carter Differential Revision: https://phabricator.haskell.org/D529
* Implement Partial Type SignaturesThomas Winant2014-11-282-32/+324
| | | | | | | | | | | | | | | | | | | | Summary: Add support for Partial Type Signatures, i.e. holes in types, see: https://ghc.haskell.org/trac/ghc/wiki/PartialTypeSignatures This requires an update to the Haddock submodule. Test Plan: validate Reviewers: austin, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie, Iceland_jack, dominique.devriese, simonmar, carter, goldfire Differential Revision: https://phabricator.haskell.org/D168 GHC Trac Issues: #9478
* Minor tweaks to API AnnotationAlan Zimmerman2014-11-242-8/+10
| | | | | | | | | | | | | | | | | | | Summary: Add missing Outputable instance for AnnotationComment Update documentation Adjust parser to capture annotations correctly Test Plan: ./validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D520
* Capture original source for literalsAlan Zimmerman2014-11-213-55/+81
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Make HsLit and OverLitVal have original source strings, for source to source conversions using the GHC API This is part of the ongoing AST Annotations work, as captured in https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations and https://ghc.haskell.org/trac/ghc/ticket/9628#comment:28 The motivations for the literals is as follows ```lang=haskell x,y :: Int x = 0003 y = 0x04 s :: String s = "\x20" c :: Char c = '\x20' d :: Double d = 0.00 blah = x where charH = '\x41'# intH = 0004# wordH = 005## floatH = 3.20# doubleH = 04.16## x = 1 ``` Test Plan: ./sh validate Reviewers: simonpj, austin Reviewed By: simonpj, austin Subscribers: thomie, goldfire, carter, simonmar Differential Revision: https://phabricator.haskell.org/D412 GHC Trac Issues: #9628
* Add API AnnotationsAlan Zimmerman2014-11-214-630/+1464
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: The final design and discussion is captured at https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations This is a proof of concept implementation of a completely separate annotation structure, populated in the parser,and tied to the AST by means of a virtual "node-key" comprising the surrounding SrcSpan and a value derived from the specific constructor used for the node. The key parts of the design are the following. == The Annotations == In `hsSyn/ApiAnnotation.hs` ```lang=haskell type ApiAnns = (Map.Map ApiAnnKey SrcSpan, Map.Map SrcSpan [Located Token]) type ApiAnnKey = (SrcSpan,AnnKeywordId) -- --------------------------------------------------------------------- -- | Retrieve an annotation based on the @SrcSpan@ of the annotated AST -- element, and the known type of the annotation. getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> Maybe SrcSpan getAnnotation (anns,_) span ann = Map.lookup (span,ann) anns -- |Retrieve the comments allocated to the current @SrcSpan@ getAnnotationComments :: ApiAnns -> SrcSpan -> [Located Token] getAnnotationComments (_,anns) span = case Map.lookup span anns of Just cs -> cs Nothing -> [] -- | Note: in general the names of these are taken from the -- corresponding token, unless otherwise noted data AnnKeywordId = AnnAs | AnnBang | AnnClass | AnnClose -- ^ } or ] or ) or #) etc | AnnComma | AnnDarrow | AnnData | AnnDcolon .... ``` == Capturing in the lexer/parser == The annotations are captured in the lexer / parser by extending PState to include a field In `parser/Lexer.x` ```lang=haskell data PState = PState { .... annotations :: [(ApiAnnKey,SrcSpan)] -- Annotations giving the locations of 'noise' tokens in the -- source, so that users of the GHC API can do source to -- source conversions. } ``` The lexer exposes a helper function to add an annotation ```lang=haskell addAnnotation :: SrcSpan -> Ann -> SrcSpan -> P () addAnnotation l a v = P $ \s -> POk s { annotations = ((AK l a), v) : annotations s } () ``` The parser also has some helper functions of the form ```lang=haskell type MaybeAnn = Maybe (SrcSpan -> P ()) gl = getLoc gj x = Just (gl x) ams :: Located a -> [MaybeAnn] -> P (Located a) ams a@(L l _) bs = (mapM_ (\a -> a l) $ catMaybes bs) >> return a ``` This allows annotations to be captured in the parser by means of ``` ctypedoc :: { LHsType RdrName } : 'forall' tv_bndrs '.' ctypedoc {% hintExplicitForall (getLoc $1) >> ams (LL $ mkExplicitHsForAllTy $2 (noLoc []) $4) [mj AnnForall $1,mj AnnDot $3] } | context '=>' ctypedoc {% ams (LL $ mkQualifiedHsForAllTy $1 $3) [mj AnnDarrow $2] } | ipvar '::' type {% ams (LL (HsIParamTy (unLoc $1) $3)) [mj AnnDcolon $2] } | typedoc { $1 } ``` == Parse result == ```lang-haskell data HsParsedModule = HsParsedModule { hpm_module :: Located (HsModule RdrName), hpm_src_files :: [FilePath], -- ^ extra source files (e.g. from #includes). The lexer collects -- these from '# <file> <line>' pragmas, which the C preprocessor -- leaves behind. These files and their timestamps are stored in -- the .hi file, so that we can force recompilation if any of -- them change (#3589) hpm_annotations :: ApiAnns } -- | The result of successful parsing. data ParsedModule = ParsedModule { pm_mod_summary :: ModSummary , pm_parsed_source :: ParsedSource , pm_extra_src_files :: [FilePath] , pm_annotations :: ApiAnns } ``` This diff depends on D426 Test Plan: sh ./validate Reviewers: austin, simonpj, Mikolaj Reviewed By: simonpj, Mikolaj Subscribers: Mikolaj, goldfire, thomie, carter Differential Revision: https://phabricator.haskell.org/D438 GHC Trac Issues: #9628
* AST changes to prepare for API annotations, for #9628Alan Zimmerman2014-11-213-139/+168
| | | | | | | | | | | | | | | | | | | | | | | | | Summary: AST changes to prepare for API annotations Add locations to parts of the AST so that API annotations can then be added. The outline of the whole process is captured here https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations This change updates the haddock submodule. Test Plan: sh ./validate Reviewers: austin, simonpj, Mikolaj Reviewed By: simonpj, Mikolaj Subscribers: thomie, goldfire, carter Differential Revision: https://phabricator.haskell.org/D426 GHC Trac Issues: #9628
* Fix #7484, checking for good binder names in Convert.Richard Eisenberg2014-11-211-0/+6
| | | | | This commit also refactors a bunch of lexeme-oriented code into a new module Lexeme, and includes a submodule update for haddock.
* Fix #9209, by reporting an error instead of panicking on bad splices.Richard Eisenberg2014-11-202-31/+41
|
* Add support for pattern synonym type signatures.Dr. ERDI Gergo2014-11-202-38/+40
| | | | | | | | | | | | Syntax is of the form pattern P :: (Prov b) => (Req a) => a -> b -> Int -> T a which declares a pattern synonym called `P`, with argument types `a`, `b`, and `Int`, and result type `T a`, with provided context `(Prov b)` and required context `(Req a)`. The Haddock submodule is also updated to use this new syntax in generated docs.
* Update shift/reduce conflict number in parserDr. ERDI Gergo2014-11-201-0/+12
|
* ghc generates more user-friendly error messagesMike Izbicki2014-11-192-0/+41
| | | | | | | | | | Test Plan: Compiled ghc fine. Opened ghci and fed it invalid code. It gave the improved error messages in response. Reviewers: austin Subscribers: thomie, simonpj, spacekitteh, rwbarton, simonmar, carter Differential Revision: https://phabricator.haskell.org/D201
* small parser/lexer cleanupYuri de Wit2014-11-074-571/+571
| | | | | | | | | | | | | | | | | | Summary: The last three '#define ...' macros were removed from Parser.y.pp and this file was renamed to Parser.y. This basically got rid of a CPP step in the build. Also converted two modules in compiler/parser/ from .lhs to .hs. Test Plan: Does it build? Yes, I performed a full build here and things are looking good. Reviewers: austin Reviewed By: austin Subscribers: adamse, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D411
* Don't re-export `Alternative(..)` from Control.Monad (re #9586)Herbert Valerio Riedel2014-09-261-4/+0
| | | | | | | | | | | | | | | | | This was done in d94de87252d0fe2ae97341d186b03a2fbe136b04 to avoid orphans but since a94dc4c3067c6a0925e2e39f35ef0930771535f1 moved `Alternative` into GHC.Base, this isn't needed anymore. This is important, as otherwise this would require a non-neglectable amount of `Control.Monad hiding ((<|>), empty)` imports in user code. The Haddock submodule is updated as well Test Plan: partial local ./validate --fast, let Harbormaster doublecheck it Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D248
* Complain about illegal type literals in renamer, not parserSimon Peyton Jones2014-09-263-18/+3
| | | | | | A premature complaint was causing Trac #9634. Acutally this change also simplifies the lexer and eliminates duplication. (The renamer was already making the check, as it happens.)
* Add -fwarn-context-quantification (#4426)Krzysztof Gogolewski2014-09-182-6/+4
| | | | | | | | | | | | | | | | | | | | | | Summary: This warning (enabled by default) reports places where a context implicitly binds a type variable, for example type T a = {-forall m.-} Monad m => a -> m a Also update Haddock submodule. Test Plan: validate Reviewers: hvr, goldfire, simonpj, austin Reviewed By: austin Subscribers: simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D211 GHC Trac Issues: #4426
* Make Applicative a superclass of MonadAustin Seipp2014-09-092-0/+13
| | | | | | | | | | | | | | | | | | | | | Summary: This includes pretty much all the changes needed to make `Applicative` a superclass of `Monad` finally. There's mostly reshuffling in the interests of avoid orphans and boot files, but luckily we can resolve all of them, pretty much. The only catch was that Alternative/MonadPlus also had to go into Prelude to avoid this. As a result, we must update the hsc2hs and haddock submodules. Signed-off-by: Austin Seipp <austin@well-typed.com> Test Plan: Build things, they might not explode horribly. Reviewers: hvr, simonmar Subscribers: simonmar Differential Revision: https://phabricator.haskell.org/D13
* PostTcType replaced with TypeAnnotAlan Zimmerman2014-09-062-25/+44
| | | | | | | | | | | | | | | | | | | | | Summary: This is a first step toward allowing generic traversals of the AST without 'landmines', by removing the `panic`s located throughout `placeHolderType`, `placeHolderKind` & co. See more on the discussion at https://www.mail-archive.com/ghc-devs@haskell.org/msg05564.html (This also makes a corresponding update to the `haddock` submodule.) Test Plan: `sh validate` and new tests pass. Reviewers: austin, simonpj, goldfire Reviewed By: austin, simonpj, goldfire Subscribers: edsko, Fuuzetsu, thomasw, holzensp, goldfire, simonmar, relrod, ezyang, carter Projects: #ghc Differential Revision: https://phabricator.haskell.org/D157
* Make Lexer.x more like the 2010 reportThomas Miedema2014-09-011-42/+73
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: I tried reading the lexer and the 2010 report side-by-side. Althought I didn't quite finish, here are some small discrepancies that I found. This revision may be low priority for reviewers, but having these commits just in my local repository does no good either. Changes: * $nl was defined, but not used anywhere * formfeed is a newline character * add \: to $ascsymbol For simplification reason, the colon (':') was added to the character set $ascsymbol in the 2010 report. Here we make the same change. * introduce the macros `qvarid`, `qconid`, `qvarsym` and `qconsym` * foreign is a Haskell keyword * add/update comments Test Plan: Harbormaster (is awesome) Reviewers: simonmar, hvr, austin Reviewed By: austin Subscribers: hvr, simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D180
* Two buglets in record wild-cards (Trac #9436 and #9437)Simon Peyton Jones2014-08-251-4/+4
| | | | | | | of named fields, whereas the code in RnPat.rnHsRecFields is much better set up to do so. Both easily fixed.
* Add parser support for explicitly bidirectional pattern synonymsDr. ERDI Gergo2014-07-292-5/+47
|
* New parser for pattern synonym declarations:Dr. ERDI Gergo2014-07-292-7/+28
| | | | | | Like splitCon for constructor definitions, the left-hand side of a pattern declaration is parsed as a single pattern which is then split into a ConName and argument variable names
* Implement OVERLAPPING and OVERLAPPABLE pragmas (see #9242)Iavor S. Diatchki2014-07-272-10/+14
| | | | | | | | | | | | | | | | | | | | | | This also removes the short-lived NO_OVERLAP pragama, and renames OVERLAP to OVERLAPS. An instance may be annotated with one of 4 pragams, to control its interaction with other overlapping instances: * OVERLAPPABLE: this instance is ignored if a more specific candidate exists * OVERLAPPING: this instance is preferred over more general candidates * OVERLAPS: both OVERLAPPING and OVERLAPPABLE (i.e., the previous GHC behavior). When compiling with -XOverlappingInstances, all instance are OVERLAPS. * INCOHERENT: same as before (see manual for details). When compiling with -XIncoherentInstances, all instances are INCOHERENT.
* 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
* Adding more parser exports and some documentation.Andrew Gibiansky2014-07-201-3/+28
| | | | | | | | | | | | | | Summary: Add a few exports to be generated by the Happy parser module. Add documentation showing how to use the Happy parser. Test Plan: Validate Reviewers: carter, austin Reviewed By: austin Subscribers: phaskell, simonmar, relrod, carter Differential Revision: https://phabricator.haskell.org/D71
* parser: detabify/dewhitespace cutils.cAustin Seipp2014-07-201-5/+3
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* parser: detabify/dewhitespace CtypeAustin Seipp2014-07-201-27/+20
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* Entirely re-jig the handling of default type-family instances (fixes Trac #9063)Simon Peyton Jones2014-07-151-21/+53
| | | | | | | | | | | | | | | | | | | | | | | | | | | In looking at Trac #9063 I decided to re-design the default instances for associated type synonyms. Previously it was all jolly complicated, to support generality that no one wanted, and was arguably undesirable. Specifically * The default instance for an associated type can have only type variables on the LHS. (Not type patterns.) * There can be at most one default instances declaration for each associated type. To achieve this I had to do a surprisingly large amount of refactoring of HsSyn, specifically to parameterise HsDecls.TyFamEqn over the type of the LHS patterns. That change in HsDecls has a (trivial) knock-on effect in Haddock, so this commit does a submodule update too. The net result is good though. The code is simpler; the language specification is simpler. Happy days. Trac #9263 and #9264 are thereby fixed as well.
* Overlapable pragmas for individual instances (#9242)Iavor S. Diatchki2014-06-292-5/+22
| | | | | | | | | | | | | | | | | | | | | | | | | | | Programmers may provide a pragma immediately after the `instance` keyword to control the overlap/incoherence behavior for individual instances. For example: instance {-# OVERLAP #-} C a where ... I chose this notation, rather than the other two outlined in the ticket for these reasons: 1. Having the pragma after the type looks odd, I think. 2. Having the pragma after there `where` does not work for stand-alone derived instances I have implemented 3 pragams: 1. NO_OVERLAP 2. OVERLAP 3. INCOHERENT These correspond directly to the internal modes currently supported by GHC. If a pragma is specified, it will be used no matter what flags are turned on. For example, putting `NO_OVERLAP` on an instance will mark it as non-overlapping, even if `OVERLAPPIN_INSTANCES` is turned on for the module.
* Add -XBinaryLiterals language extension (re #9224)Herbert Valerio Riedel2014-06-272-3/+23
| | | | | | | | | | | | | | | | | | | | | | | Haskell2010 supports - base-10 (prefix-less), - base-8 (via `0[oO]`-prefix), and - base-16 (via `0[xX]`-prefix) integer literals. This commit adds syntax support for base-2 integer literals via the new `0[bB]` prefix. The use of a `0b` prefix for indicating binary literals is known from popular programming languages such as C++14, Perl, Python, Ruby, and Java. This syntax extension is disabled by default and can be enabled via the new `{-# LANGUAGE BinaryLiterals #-}` pragma and/or the new `-XBinaryLiterals` This new extensions requires to upgrade the `ExtsBitmap` type from `Word` to `Word64` as this adds a 33th flag which is not guaranteed to fit into a `Word`. Signed-off-by: Herbert Valerio Riedel <hvr@gnu.org> Differential Revision: https://phabricator.haskell.org/D22
* Refactor extension-bitmap in LexerHerbert Valerio Riedel2014-06-271-196/+173
| | | | | | | | | | | | | | This introduces an Enum type `ExtBits` for the currently used 32 flags and introduces a type-synonym `ExtsBitmap` for representing a set over `ExtBits`. While at it, the current `Int` was replaced by `Word` to have the compiler catch any missed use-sites. This will make it easy to swap the `Word`-representation of `ExtsBitmap` by something different, such as e.g. a `Word64` Test Plan: successful validate Differential Revision: https://phabricator.haskell.org/D23