summaryrefslogtreecommitdiff
path: root/compiler
Commit message (Collapse)AuthorAgeFilesLines
* Unique-ify the names of top-level auxiliary bindings in derived instances ↵Simon Peyton Jones2014-12-021-8/+41
| | | | | | | | (Trac #7947) The problem and its solution are explained in Note [Auxiliary binders] in TcGenDeriv
* Fix another bug in deriving( Data ) for data families; Trac #4896Simon Peyton Jones2014-12-021-9/+25
| | | | | | | | | | | | | | | | | | | | | | | If we have data family D a data instance D (a,b,c) = ... deriving( Data ) then we want to generate instance ... => Data (D (a,b,c)) where ... dataCast1 x = gcast1 x The "1" here comes from the kind of D. But the kind of the *representation* TyCon is data Drep a b c = .... ie Drep :: * -> * -> * -> * So we must look for the *family* TyCon in this (rather horrible) dataCast1 / dataCast2 binding.
* Minor refactoring of Edward's recent orphans patch (Trac #2182)Simon Peyton Jones2014-12-028-252/+289
| | | | | | | This patch is all small stuff - Move VisibleOrphanModules from Module to InstEnv (with the other orphan stuff) - Move Notes about orphans from IfaceSyn to InstEnv (ditto) - Make use of the record field names in InstEnvs
* Rename Untouchables to TcLevelSimon Peyton Jones2014-12-0215-179/+181
| | | | | | | | This is a long-overdue renaming Untouchables --> TcLevel It is renaming only; no change in functionality. We really wanted to get this done before the 7.10 fork.
* Remove references to SynTyCon. Fixes #9812Jan Stolarek2014-12-024-10/+12
|
* Comments and formatting in TyConJan Stolarek2014-12-021-81/+118
|
* 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
* Remove references to Parser.y.ppThomas Miedema2014-12-013-6/+3
| | | | | | | | | | | | | | Summary: Commit 37d64a51348a803a1cf974d9e97ec9231215064a removed the preprocessing step for Parser.y. Reviewers: rodlogic, austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D543
* Wibble to the "instance signatures" patchSimon Peyton Jones2014-12-011-1/+1
| | | | Sorry about this. I somehow failed to include this one line in my patch.
* Fix the handling of instance signatures (Trac #9582, #9833)Simon Peyton Jones2014-12-013-67/+88
| | | | | | | | | This finally solves the issue of instance-method signatures that are more polymorphic than the instanted class method. See Note [Instance method signatures] in TcInstDcls. A very nice fix for the two Trac tickets above.
* unlit compiler/types/ modulesHerbert Valerio Riedel2014-12-0114-637/+504
| | | | Differential Revision: https://phabricator.haskell.org/D544
* unlit compiler/stranal/ modulesHerbert Valerio Riedel2014-12-013-129/+121
| | | | | | Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D541
* Revert "Remove RAWCPP_FLAGS"Herbert Valerio Riedel2014-12-011-2/+2
| | | | | | | | | | | | This reverts commit 460eebec65811c6a7bbe11645df322dda868e80d. Thomas requested to revert the commit with the words: > Please revert this commit, it is horribly wrong. I'll have a proper look > later, but not supplying `-traditional` to the C preprocessor is the cause > of #9828. the reverted commit was related to #9094
* Unlit AsmCodeGen.lhsHerbert Valerio Riedel2014-11-301-4/+0
| | | | Fwiw, this wasn't really a proper .lhs to begin with...
* Unlit compiler/cmm/ module(s)Herbert Valerio Riedel2014-11-301-32/+23
| | | | | | | | | | Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D540
* compiler: fix trac issue #8815Sivaram Balakrishnan2014-11-301-1/+2
| | | | | | | | | | | | | | Summary: This patch changes the error message as suggested in trac issue #8815 comments. Reviewers: jstolarek, austin Reviewed By: jstolarek, austin Subscribers: jstolarek, thomie, carter Differential Revision: https://phabricator.haskell.org/D533 GHC Trac Issues: #8815
* compiler: unlit profiling/ modulesAustin Seipp2014-11-302-10/+4
| | | | | | | | | | | | Summary: Signed-off-by: Austin Seipp <austin@well-typed.com> Test Plan: `./validate` Reviewers: hvr Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D537
* Fix obscure problem with using the system linker (#8935)Peter Trommler2014-11-302-24/+53
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: In a statically linked GHCi symbol `environ` resolves to NULL when called from a Haskell script. When resolving symbols in a Haskell script we need to search the executable program and its dependent (DT_NEEDED) shared libraries first and then search the loaded libraries. We want to be able to override functions in loaded libraries later. Libraries must be opened with local scope (RTLD_LOCAL) and not global. The latter adds all symbols to the executable program's symbols where they are then searched in loading order. We want reverse loading order. When libraries are loaded with local scope the dynamic linker cannot use symbols in that library when resolving the dependencies in another shared library. This changes the way files compiled to object code must be linked into temporary shared libraries. We link with the last temporary shared library created so far if it exists. Since each temporary shared library is linked to the previous temporary shared library the dynamic linker finds the latest definition of a symbol by following the dependency chain. See also Note [RTLD_LOCAL] for a summary of the problem and solution. Cherry-picked commit 2f8b4c Changed linker argument ordering On some ELF systems GNU ld (and others?) default to --as-needed and the order of libraries in the link matters. The last temporary shared library, must appear before all other libraries. Switching the position of extra_ld_inputs and lib_path_objs does that. Fixes #8935 and #9186 Reviewers: austin, hvr, rwbarton, simonmar Reviewed By: simonmar Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D349 GHC Trac Issues: #8935, #9186, #9480
* More Tweaks for API AnotationsAlan Zimmerman2014-11-305-36/+82
| | | | | | | | | | | | | | 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
* Shorten long lines in DynFlags, add details to ghci usage guide.Lennart Kolmodin2014-11-301-393/+501
| | | | | | | | | | | | | | | | Summary: Shorten long lines in DynFlags. Describe --show-options in ghci usage guide. Reviewers: jstolarek, austin Reviewed By: jstolarek, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D532 GHC Trac Issues: #9259
* Filter instance visibility based on set of visible orphans, fixes #2182.ghc-instvisEdward Z. Yang2014-11-2916-86/+216
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Amazingly, the fix for this very old bug is quite simple: when type-checking, maintain a set of "visible orphan modules" based on the orphans list of modules which we explicitly imported. When we import an instance and it is an orphan, we check if it is in the visible modules set, and if not, ignore it. A little bit of refactoring for when orphan-hood is calculated happens so that we always know if an instance is an orphan or not. For GHCi, we preinitialize the visible modules set based on the list of interactive imports which are active. Future work: Cache the visible orphan modules set for GHCi, rather than recomputing it every type-checking round. (But it's tricky what to do when you /remove/ a module: you need a data structure a little more complicated than just a set of modules.) Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: new tests and validate Reviewers: simonpj, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D488 GHC Trac Issues: #2182
* Special case interactive package key for mkQualPackage.Edward Z. Yang2014-11-291-1/+1
| | | | Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* Fix testsuite failures after the PartialTypeSignatures mergeThomas Winant2014-11-291-6/+10
| | | | | | | | | | | | | | | Summary: Properly detect insoluble wanteds This used to be correct, but was recently incorrectly refactored. Reviewers: austin, hvr Reviewed By: austin, hvr Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D531
* Implement Partial Type SignaturesThomas Winant2014-11-2839-237/+956
| | | | | | | | | | | | | | | | | | | | 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
* Rename some of the functions in NameSet, to make the uniform with VarSet etcSimon Peyton Jones2014-11-2830-109/+109
| | | | | | | | | | | | | For ages NameSet has used different names, eg. addOneToNameSet rather than extendNameSet nameSetToList rather than nameSetElems etc. Other set-like modules use uniform naming conventions. This patch makes NameSet follow suit. No change in behaviour; this is just renaming. I'm doing this just before the fork so that merging is easier.
* Kind variables in RHS of an associated type instances should be bound on LHSSimon Peyton Jones2014-11-283-49/+43
| | | | | | | | | | | | | | | | | | | | | | | This patche fixes Trac #9574. The previous Note [Renaming associated types] in RnTypes appears to me to be wrong; it confused class and instance declarations. I have: * Treated kind and type variables uniformly. Both must be bound on the LHS of an associated type instance. Eg instance C ('KProxy :: KProxy o) where type F 'KProxy = NatTr (Proxy :: o -> *) is illegal because 'o' is not bound on the LHS of the instance. * Moved the Note to RnSource and fixed it up This improves the error message from T7938. However it made the code in T6118 incorrect. We had: instance SingE (a :: Maybe k) where type Demote a = Maybe (Demote (Any :: k)) and that is now rejected, rightly I think.
* Tidy up tracing somewhatSimon Peyton Jones2014-11-283-37/+49
| | | | | This is a knock-on from the -dump-to-file changes. (I found that -ddump-cs-trace stuff wasn't coming out!)
* Don't discard a bang on a newtype pattern (Trac #9844)Simon Peyton Jones2014-11-283-13/+57
| | | | We were wrongly simply dropping the bang, in tidy_bang_pat.
* compiler: add new modules pulling in FunFlagsSergei Trofimovich2014-11-272-5/+4
| | | | | | | | And also sync type signature under '#ifndef GHCI' Tested by setting GhcWithInterpreter = NO Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
* Embed Git commit id into `ghc --info` outputHerbert Valerio Riedel2014-11-272-0/+3
| | | | | | | | | | | | | | | | | | | | | | | Since we switched to a Git submodule based GHC Git repo, `ghc.git`'s commit id uniquely identifies the state of the GHC source-tree. So having that information embedded into the `ghc` executable provides valuable information to track accurately (especially when created by buildbots) from which source-tree-state a given `ghc` snapshot (distribution) was generated. So this commit adds a new field `"Project Git commit id"` to the `ghc --info` meta-data containing the `./configure`-time Git commit id as reported by `git rev-parse HEAD`. This field can also be queried with `ghc --print-project-git-commit-id`. For source distributions, the file `GIT_COMMIT_ID` is created (with some sanity checking to detect stale commit ids, as that would render this information rather useless) Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D528
* Get the right fixity-env in standalone deriving (Trac #9830)Simon Peyton Jones2014-11-272-10/+28
|
* Don't require ConstraintKinds at usage sites (Trac #9838)Simon Peyton Jones2014-11-272-71/+101
|
* Resume reporting incomplete pattern matches for record updatesSimon Peyton Jones2014-11-272-3/+6
| | | | | | They were being inadvertently suppressed, even if you said -fwarn-incomplete-record-updates See Trac #5728
* Don't require PatternSynonyms language extension to just use pattern synonymsDr. ERDI Gergo2014-11-271-6/+0
| | | | (see #9838)
* Change loadSrcInterface to return a list of ModIfaceEdward Z. Yang2014-11-263-37/+94
| | | | | | | | | | | | | | | | | | | | Summary: This change is in preparation to support signature imports, which may pull in multiple interface files. At the moment, the list always contains only one element, but in a later patch it may contain more. I also adjusted some error reporting code so that it didn't take the full iface, but just whether or not the iface in question was a boot module. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D436
* Inline mkModuleToPkgConfAll into mkModuleToPkgConfGeneric.Edward Z. Yang2014-11-261-37/+17
| | | | Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* Replace `STRICT[12345]` macros by `BangPatterns`Yuri de Wit2014-11-253-31/+6
| | | | | | | | | | This removes the macros `STRICT1()`, `STRICT2()`, `STRICT3()`, `STRICT4()`, and `STRICT5()` CPP macros from `HsVersions.hs` and replaces the few use sites by uses of `BangPatterns`. Reviewed By: hvr Differential Revision: https://phabricator.haskell.org/D525
* Add `--fwarn-trustworthy-safe` to `-Wall` again.David Terei2014-11-241-1/+2
| | | | | This redoes part of 475dd93efa which was reversed in 452d6aa95b after breaking validate on windows.
* Minor tweaks to API AnnotationAlan Zimmerman2014-11-243-14/+17
| | | | | | | | | | | | | | | | | | | 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
* Add -fdefer-typed-holes flag which defers hole errors to runtime.Merijn Verstraaten2014-11-215-30/+79
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: As proposed by Richard on Trac. This patch adds a new flag -fdefer-typed-holes and changes the semantics of the -fno-warn-typed-holes flag. To summarise, by default GHC has typed holes enabled and produces a compile error when it encounters a typed hole. When -fdefer-type-errors OR -fdefer-typed-holes is enabled, hole errors are converted to warnings and result in runtime errors when evaluated. The warning flag -fwarn-typed-holes is on by default. Without -fdefer-type-errors or -fdefer-typed-holes this flag is a no-op, since typed holes are an error under these conditions. If either of the defer flags are enabled (converting typed hole errors into warnings) the -fno-warn-typed-holes flag disables the warnings. This means compilation silently succeeds and evaluating a hole will produce a runtime error. The rationale behind allowing typed holes warnings to be silenced is that tools like Syntastic for vim highlight warnings and hole warnings may be undesirable. Signed-off-by: Merijn Verstraaten <merijn@inconsistent.nl> Test Plan: validate Reviewers: austin, simonpj, thomie Reviewed By: simonpj, thomie Subscribers: Fuuzetsu, thomie, carter Differential Revision: https://phabricator.haskell.org/D442 GHC Trac Issues: #9497 Conflicts: compiler/main/DynFlags.hs
* ghc: allow --show-options and --interactive togetherLennart Kolmodin2014-11-214-593/+663
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Previously 'ghc --show-options' showed all options that GHC can possibly accept. With this patch, it'll only show the options that have effect in non-interactive modes. This change also adds support for using 'ghc --interactive --show-options' which previously was disallowed. This command will show all options that have effect in the interactive mode. The CmdLineParser is updated to know about the GHC modes, and then each flag is annotated with which mode it has effect. This fixes #9259. Test Plan: Try out --show-options with --interactive on the command line. With and without --interactive should give different results. Run the test suite, mode001 has been updated to verify this new flag combination. Reviewers: austin, jstolarek Reviewed By: austin, jstolarek Subscribers: jstolarek, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D337 GHC Trac Issues: #9259
* llvmGen: Compatibility with LLVM 3.5 (re #9142)Ben Gamari2014-11-215-31/+127
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Due to changes in LLVM 3.5 aliases now may only refer to definitions. Previously to handle symbols defined outside of the current commpilation unit GHC would emit both an `external` declaration, as well as an alias pointing to it, e.g., @stg_BCO_info = external global i8 @stg_BCO_info$alias = alias private i8* @stg_BCO_info Where references to `stg_BCO_info` will use the alias `stg_BCO_info$alias`. This is not permitted under the new alias behavior, resulting in errors resembling, Alias must point to a definition i8* @"stg_BCO_info$alias" To fix this, we invert the naming relationship between aliases and definitions. That is, now the symbol definition takes the name `@stg_BCO_info$def` and references use the actual name, `@stg_BCO_info`. This means the external symbols can be handled by simply emitting an `external` declaration, @stg_BCO_info = external global i8 Whereas in the case of a forward declaration we emit, @stg_BCO_info = alias private i8* @stg_BCO_info$def Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D155
* Update Foreign.* for Safe Haskell now that they're safe by defaultDavid Terei2014-11-214-0/+16
|
* Capture original source for literalsAlan Zimmerman2014-11-2123-248/+330
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Export more Packages functionsLuite Stegeman2014-11-211-4/+11
| | | | | | | | | | | | | | | | | 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
* Add API AnnotationsAlan Zimmerman2014-11-2119-663/+1832
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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-2143-612/+857
| | | | | | | | | | | | | | | | | | | | | | | | | 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 #9824 by not warning about unused matches in pattern quotes.Richard Eisenberg2014-11-211-0/+3
|
* Fix #1476 by making splice patterns work.Richard Eisenberg2014-11-213-12/+39
| | | | | | | | | 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.
* Fix #7484, checking for good binder names in Convert.Richard Eisenberg2014-11-218-79/+269
| | | | | This commit also refactors a bunch of lexeme-oriented code into a new module Lexeme, and includes a submodule update for haddock.