- 21 Nov, 2014 40 commits
-
-
Alan Zimmerman authored
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
-
Herbert Valerio Riedel authored
This adds the module `Data.Void` (formerly provided by Edward Kmett's `void` package) to `base`. The original Haskell98 compatible implementation has been modified to use modern GHC features (among others this makes use of `EmptyCase` as motivated by #2431), and `vacuousM` was dropped since it's redundant now with the AMP in place. Instances for classes not part of `base` had to be dropped as well. TODO: Documentation could be improved Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D506
-
Luite Stegeman authored
Summary: This patch exports functions for finding the active package databases and their locations from the Packages module. This allows GHC API clients to use other tools, like Cabal, to gather package information that's not directly available from the binary package db. Reviewers: duncan, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D514
-
leroux authored
Summary: ghci unset could not reverse language extensions. Reviewers: hvr, thomie, austin Reviewed By: hvr, thomie, austin Subscribers: goldfire, hvr, thomie, carter Differential Revision: https://phabricator.haskell.org/D516 GHC Trac Issues: #9293
-
Alan Zimmerman authored
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
-
Alan Zimmerman authored
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
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
Unfortunately, splice patterns in brackets still do not work because we don't run splices in brackets. Without running a pattern splice, we can't know what variables it binds, so we're stuck. This is still a substantial improvement, and it may be the best we can do. Still must document new behavior.
-
eir@cis.upenn.edu authored
Test case: th/T1476b.
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
This commit also refactors a bunch of lexeme-oriented code into a new module Lexeme, and includes a submodule update for haddock.
-
eir@cis.upenn.edu authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Dot-dot record-wildcard notation is simply illegal for constructors without any named fields, but that was neither documented nor checked. This patch does so - Make the check in RnPat - Add test T9815 - Fix CmmLayoutStack which was using the illegal form (!) - Document in user manual
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Test T2239 actually succeeds without impredicativity, because of the new co/contra subsumption check
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
I can't say I really understand this DLL-split thing, but the build fails if I don't remove TcMType here. I've put this in a commit on its own, but it's a knock-on effect of the immediately preceding wave of typechecker changes
-
Simon Peyton Jones authored
We weren't promoting enough type variables, with unpredictable consequences. The new code is, if anything, simpler.
-
Simon Peyton Jones authored
This has to be done by the full constraint solver anyway, and it's rare, so there's really no point in doing it twice. This change just deletes some (tricky) code.
-
Simon Peyton Jones authored
This was being doing independently in two places. Now it's done in one place, TcType.canUnifyWithPolyType
-
Simon Peyton Jones authored
This is a pretty big patch, but which substantially iproves the subsumption check. Trac #9569 was the presenting example, showing how type inference could depend rather delicately on eta expansion. But there are other less exotic examples; see Note [Co/contra-variance of subsumption checking] in TcUnify. The driving change is to TcUnify.tcSubType. But also * HsWrapper gets a new constructor WpFun, which behaves very like CoFun: if wrap1 :: exp_arg <= act_arg wrap2 :: act_res <= exp_res then WpFun wrap1 wrap2 : (act_arg -> arg_res) <= (exp_arg -> exp_res) * I generalised TcExp.tcApp to call tcSubType on the result, rather than tcUnifyType. I think this just makes it consistent with everything else, notably tcWrapResult. As usual I ended up doing some follow-on refactoring * AmbigOrigin is gone (in favour of TypeEqOrigin) * Combined BindPatSigCtxt and PatSigCxt into one * Improved a bit of error message generation
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
When a pattern synonym is for an unlifted pattern, its "builder" would naturally be a top-level unlifted binding, which isn't allowed. So we give it an extra Void# argument. Our Plan A involved then making *two* Ids for these builders, with some consequential fuss in the desugarer. This was more pain than I liked, so I've re-jigged it. * There is just one builder for a pattern synonym. * It may have an extra Void# arg, but this decision is signalled by the Bool in the psBuilder field. I did the same for the psMatcher field. Both Bools are serialised into interface files, so there is absolutely no doubt whether that extra Void# argument is required. * I renamed "wrapper" to "builder". We have too may "wrappers" * In order to deal with typecchecking occurrences of P in expressions, I refactored the tcInferId code in TcExpr. All of this allowed me to revert 5fe872 "Apply compulsory unfoldings during desugaring, except for `seq` which is special." which turned out to be a rather messy hack in DsBinds
-
Simon Peyton Jones authored
-
Joachim Breitner authored
Phrases like “Currently, you can...” are going to sound strange in a few years; I rephrased the note to sound less like a proposal and more like an explanation.
-
lukexi authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
jpm@cs.ox.ac.uk authored
Summary: (this has been submitted on behalf on @dreixel) Reviewers: simonpj, hvr, austin Reviewed By: simonpj, austin Subscribers: goldfire, thomie, carter, dreixel Differential Revision: https://phabricator.haskell.org/D476 GHC Trac Issues: #5462
-
Eric Seidel authored
Summary: add `-fwarn-missing-exported-sigs` to only warn about missing signatures if the name is exported Test Plan: validate, see testsuite/tests/warnings/should_compile/T2526.hs Reviewers: ezyang, austin, thomie Reviewed By: austin, thomie Subscribers: ezyang, thomie, carter Differential Revision: https://phabricator.haskell.org/D482 GHC Trac Issues: #2526 Conflicts: docs/users_guide/7.10.1-notes.xml
-
David Feuer authored
Summary: Fixes #9368 Reviewers: nomeata, hvr, ekmett, austin Reviewed By: ekmett, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D498 GHC Trac Issues: #9368
-
Herbert Valerio Riedel authored
Summary: The `Data.OldList` module was originally created in 3daf0023 to provide a way to access the original list-specialised functions from `Data.List`. It was also made an exposed module in order to facilitate adapting the `haskell2010`/`haskell98` packages. However, since the `haskell2010`/`haskell98` packages were dropped, we no longer need to expose `Data.OldList`. Depends on D511 Reviewers: ekmett, austin Reviewed By: ekmett, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D513
-