summaryrefslogtreecommitdiff
Commit message (Collapse)AuthorAgeFilesLines
* Use TypeLits in the meta-data encoding of GHC.Genericswip/GenericsMetaData2Jose Pedro Magalhaes2014-11-2310-717/+508
| | | | | The following wiki page contains more information about this: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Amoreconservativefirstapproachtothisproblem
* Call `popCountBigNat` directly (#9818)Herbert Valerio Riedel2014-11-221-1/+1
| | | | | This calls the `popCountBigNat` primitive directly instead of going through `Integer`'s `popCount`.
* Implement {gcd,lcm}/Natural optimisation (#9818)Herbert Valerio Riedel2014-11-221-0/+27
| | | | | | This provides the equivalent of the existing `{gcd,lcm}/Integer` optimisations for the `Natural` type, when using the `integer-gmp2` backend.
* Fix `fromInteger` constructing invalid `Natural`Herbert Valerio Riedel2014-11-221-1/+1
| | | | | | This fixes a case where `isValidNatural . fromInteger` would be `False`. Re #9818
* Add `isValidNatural` predicate (#9818)Herbert Valerio Riedel2014-11-221-0/+21
| | | | | | | | | This predicate function encodes the internal `Natural` invariants, and is useful for testsuites or code that directly constructs `Natural` values. C.f. `integer-gmp2`'s `isValidBigNat#` and `isValidInteger#` predicates for testing internal invariants.
* Add gcd/Word RULE-based optimisationHerbert Valerio Riedel2014-11-221-0/+9
| | | | | | This makes use of the `gcdWord` primitive provided by be7fb7e58c70cd9b0a933fb26cd5f2607d6dc4b2 which should make the `Word`-variant of `gcd` as performant as the `Int`-variant.
* Remove reference to `MIN_VERSION_integer_gmp2`Herbert Valerio Riedel2014-11-221-1/+1
| | | | | This is slipped in by accident as part of c774b28f76ee4c220f7c1c9fd81585e0e3af0e8a (re #9281)
* integer-gmp2: export `Word`-counterpart of gcdIntHerbert Valerio Riedel2014-11-222-1/+9
| | | | | | It's trivial for `integer-gmp2` (#9281) to provide it, and it'll be useful for a future 'Natural'-related commit, as well as providing a `Word` optimised `gcd`-RULE.
* Revert "Test Trac #9318"Herbert Valerio Riedel2014-11-223-20/+0
| | | | | | | This reverts commit 5760eb598e0dfa451407195f15072204c15233ed because the very same test was already added via 5eebd990ea7a5bc1937657b101ae83475e20fc7a and is causing `./validate` to fail due to "framework failure".
* Re-center bytes-allocated for `haddock.compiler`Herbert Valerio Riedel2014-11-221-1/+2
| | | | | | | | This should silence the perf/haddock haddock.compiler [stat not good enough] (normal) test-failure...
* Implement `Natural` number type (re #9818)Herbert Valerio Riedel2014-11-227-0/+579
| | | | | | | | | | | | | | | | | This implements a `Natural` type for representing unsigned arbitrary precision integers. When available, `integer-gmp>=1.0.0`'s `BigNat` type is used as building-block to construct `Natural` as an algebraic data-type. Otherwise, `Natural` falls back being a `newtype`-wrapper around `Integer` (as is done in Edward Kmett's `nats` package). The `GHC.Natural` module exposes an internal GHC-specific API, while `Numeric.Natural` provides the official & portable API. Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D473
* Deprecate Data.Version.versionTags (#2496)Thomas Miedema2014-11-228-23/+23
| | | | | | | | | | | | The library submission was accepted: http://www.haskell.org/pipermail/libraries/2014-September/023777.html The T5892ab testcases were changed to use `Data.Tree` instead of `Data.Version` Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D395
* Add -fdefer-typed-holes flag which defers hole errors to runtime.Merijn Verstraaten2014-11-2127-62/+226
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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-2111-693/+732
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Add function for size-checked conversion of Integral typesSean Leather2014-11-212-1/+107
| | | | | | | | | | | | | | | | The new function `Data.Bits.toIntegralSized` provides a similar functionality to `fromIntegral` but adds validation that the argument fits in the result type's size. The implementation of `toIntegralSized` has been derived from `intCastMaybe` (which is part of Herbert Valerio Riedel's `int-cast` package, see http://hackage.haskell.org/package/int-cast) Addresses #9816 Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D512
* Add displayException method to Exception (#9822)Michael Snoyman2014-11-212-0/+11
| | | | | | | | Defaults to using `show` to prevent any breakage of existing code. Also provide a custom implementation for `SomeException` which uses the underlying exception's `displayException`. Differential Revision: https://phabricator.haskell.org/D517
* 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
* Be consistent with placement of Safe Haskell mode at top of fileDavid Terei2014-11-2140-48/+52
|
* Improve Safe Haskell bounds for changes to base over timeDavid Terei2014-11-2120-59/+58
|
* Update Foreign.* for Safe Haskell now that they're safe by defaultDavid Terei2014-11-2115-19/+47
|
* Update Control.Monad.ST.* for Safe Haskell as now they're safe by defaultDavid Terei2014-11-217-8/+10
|
* Add T7220a.stderrJoachim Breitner2014-11-211-0/+14
| | | | | which presumably was just forgotten when creating the testcase in commit 7b1a856.
* Add 'fillBytes' to Foreign.Marshal.Utils.Alex Petrov2014-11-212-2/+19
| | | | | | | | fillBytes uses 'memset' to fill a memory area with a given byte value. Reviewed By: austin, hvr Differential Revision: https://phabricator.haskell.org/D465
* Capture original source for literalsAlan Zimmerman2014-11-2131-248/+687
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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 Data.Void to base (re #9814)Herbert Valerio Riedel2014-11-213-0/+78
| | | | | | | | | | | | | | | | | 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
* 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
* Fixes ghci :unset -X<ext> so that it doesn't fail to reverse option. (fixes ↵Muhaimin Ahsan2014-11-218-5/+110
| | | | | | | | | | | | | | | | trac #9293) 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
* Add API AnnotationsAlan Zimmerman2014-11-2132-664/+2331
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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-2147-620/+864
| | | | | | | | | | | | | | | | | | | | | | | | | 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
* Update manual for pattern splices (#1476)Richard Eisenberg2014-11-211-13/+42
|
* Fix #9824 by not warning about unused matches in pattern quotes.Richard Eisenberg2014-11-212-1/+4
|
* Test #9824 in th/T9824Richard Eisenberg2014-11-212-0/+7
|
* Release notes for #1476, #7484.Richard Eisenberg2014-11-211-0/+11
|
* Fix #1476 by making splice patterns work.Richard Eisenberg2014-11-214-13/+40
| | | | | | | | | 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.
* Test that nested pattern splices don't scope (#1476).Richard Eisenberg2014-11-213-0/+16
| | | | Test case: th/T1476b.
* Test #1476 in th/T1476Richard Eisenberg2014-11-212-0/+11
|
* Fix #7484, checking for good binder names in Convert.Richard Eisenberg2014-11-2110-80/+270
| | | | | This commit also refactors a bunch of lexeme-oriented code into a new module Lexeme, and includes a submodule update for haddock.
* Test #7484 in th/T7484Richard Eisenberg2014-11-213-0/+12
|
* Comments onlySimon Peyton Jones2014-11-212-30/+7
|
* Test Trac #8149Simon Peyton Jones2014-11-213-0/+14
|
* Fix Trac #9815Simon Peyton Jones2014-11-216-8/+37
| | | | | | | | | | | 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
* Wibbles (usually improvements) to error messagesSimon Peyton Jones2014-11-2145-327/+401
|
* Test T2239 actually succeeds without impredicativity, because of the new ↵Simon Peyton Jones2014-11-213-33/+21
| | | | co/contra subsumption check
* Fix up tests for Trac #7220; the old test really was ambiguousSimon Peyton Jones2014-11-213-4/+33
|
* Test Trac #9569Simon Peyton Jones2014-11-214-0/+38
|
* Delete duplicated testsSimon Peyton Jones2014-11-215-41/+0
|
* Trac #9222 is actually an ambiguous type, now detectedSimon Peyton Jones2014-11-213-1/+31
|
* Test Trac #9318Simon Peyton Jones2014-11-213-0/+20
|
* Remove TcMType from compiler_stage2_dll0_MODULESSimon Peyton Jones2014-11-211-1/+0
| | | | | | | | 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
* Fix a latent promotion bug in TcSimplify.simplifyInferSimon Peyton Jones2014-11-211-13/+20
| | | | | We weren't promoting enough type variables, with unpredictable consequences. The new code is, if anything, simpler.