summaryrefslogtreecommitdiff
path: root/testsuite/tests
Commit message (Collapse)AuthorAgeFilesLines
* Use TypeLits in the meta-data encoding of GHC.Genericswip/GenericsMetaData2Jose Pedro Magalhaes2014-11-234-237/+189
| | | | | The following wiki page contains more information about this: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Amoreconservativefirstapproachtothisproblem
* 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...
* Deprecate Data.Version.versionTags (#2496)Thomas Miedema2014-11-225-21/+19
| | | | | | | | | | | | 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-2119-3/+64
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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-213-1/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Improve Safe Haskell bounds for changes to base over timeDavid Terei2014-11-215-42/+34
|
* Add T7220a.stderrJoachim Breitner2014-11-211-0/+14
| | | | | which presumably was just forgotten when creating the testcase in commit 7b1a856.
* Capture original source for literalsAlan Zimmerman2014-11-218-0/+357
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Fixes ghci :unset -X<ext> so that it doesn't fail to reverse option. (fixes ↵Muhaimin Ahsan2014-11-217-5/+109
| | | | | | | | | | | | | | | | 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-2112-0/+498
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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-211-4/+2
| | | | | | | | | | | | | | | | | | | | | | | | | 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-1/+1
|
* Test #9824 in th/T9824Richard Eisenberg2014-11-212-0/+7
|
* Fix #1476 by making splice patterns work.Richard Eisenberg2014-11-211-1/+1
| | | | | | | | | 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-211-1/+1
| | | | | 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
|
* Test Trac #8149Simon Peyton Jones2014-11-213-0/+14
|
* Fix Trac #9815Simon Peyton Jones2014-11-213-0/+11
| | | | | | | | | | | 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
|
* Implement #5462 (deriving clause for arbitrary classes)Jose Pedro Magalhaes2014-11-2011-6/+232
| | | | | | | | | | | | | | 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
* Add flag `-fwarn-missing-exported-sigs`Eric Seidel2014-11-203-0/+12
| | | | | | | | | | | | | | | | | | | 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
* Hide `Data.OldList` moduleHerbert Valerio Riedel2014-11-209-12/+12
| | | | | | | | | | | | | | | | | | | | | Summary: The `Data.OldList` module was originally created in 3daf0023d2dcf7caf85d61f2dc177f8e9421b2fd 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
* Test #9109 in typecheck/should_fail/T9109Richard Eisenberg2014-11-203-0/+24
|
* Test #9201 in typecheck/should_fail/T9201Richard Eisenberg2014-11-203-0/+13
|
* Test #9318 in typecheck/should_fail/T9318Richard Eisenberg2014-11-203-0/+20
|
* Test #9151 in typecheck/should_compile/T9151.Richard Eisenberg2014-11-202-0/+12
| | | | | This test case should pass right now -- the bug is fixed, presumably by #9200.
* Fix #9220 by adding role annotations.Richard Eisenberg2014-11-204-1/+101
| | | | | This includes a submodule update for `array`. There is also an added test in libraries/array/tests/T9220.
* Fix #9209, by reporting an error instead of panicking on bad splices.Richard Eisenberg2014-11-201-1/+1
|
* Test #9209 in th/T9209Richard Eisenberg2014-11-203-0/+10
|
* Add support for pattern synonym type signatures.Dr. ERDI Gergo2014-11-208-1/+55
| | | | | | | | | | | | 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.
* Make calling conventions in template haskell Syntax.hs consistent with those ↵Luite Stegeman2014-11-193-0/+57
| | | | | | | | | | | | | | | | | | in ghc ForeignCall.hs this impliments #9703 from ghc trac Test Plan: still needs tests Reviewers: cmsaperstein, ekmett, goldfire, austin Reviewed By: goldfire, austin Subscribers: goldfire, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D353 GHC Trac Issues: #9703
* ghc generates more user-friendly error messagesMike Izbicki2014-11-1910-9/+29
| | | | | | | | | | 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
* compiler/main: fixes #9776Carlos Tomé2014-11-193-0/+6
| | | | | | | | | | | | | | Test Plan: test T9776 under tests/driver Reviewers: jstolarek, austin Reviewed By: jstolarek, austin Subscribers: jstolarek, thomie, carter Differential Revision: https://phabricator.haskell.org/D503 GHC Trac Issues: #9776
* make TcRnMonad.lhs respect -ddump-to-fileGreg Weber2014-11-191-1/+0
| | | | | | | | | | | | | | | | | | | | | Summary: allows things such as: -ddump-to-file -ddump-splices Test Plan: compile with flags -ddump-to-file -ddump-splices verify that it does output an extra file Try out other flags. I noticed that with -ddump-tc there is some output going to file and some to stdout. Reviewers: hvr, austin Reviewed By: austin Subscribers: simonpj, thomie, carter Differential Revision: https://phabricator.haskell.org/D460 GHC Trac Issues: #9126
* Allow -dead_strip linking on platforms with .subsections_via_symbolsMoritz Angermann2014-11-198-0/+53
| | | | | | | | | | | | | | | | | Summary: This allows to link objects produced with the llvm code generator to be linked with -dead_strip. This applies to at least the iOS cross compiler and OS X compiler. Signed-off-by: Moritz Angermann <moritz@lichtzwerge.de> Test Plan: Create a ffi library and link it with -dead_strip. If the resulting binary does not crash, the patch works as advertised. Reviewers: rwbarton, simonmar, hvr, dterei, mzero, ezyang, austin Reviewed By: dterei, ezyang, austin Subscribers: thomie, mzero, simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D206
* Restore exact old semantics of `decodeFloat`Herbert Valerio Riedel2014-11-193-0/+40
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | `integer-gmp2` uses the new 64bit-based IEEE deconstructing primop introduced in b62bd5ecf3be421778e4835010b6b334e95c5a56. However, the returned values differ for exceptional IEEE values: Previous (expected) semantics: > decodeFloat (-1/0) (-4503599627370496,972) > decodeFloat (1/0) (4503599627370496,972) > decodeFloat (0/0) (-6755399441055744,972) Currently (broken) semantics: > decodeFloat (-1/0 :: Double) (-9223372036854775808,-53) > decodeFloat (1/0 :: Double) (-9223372036854775808,-53) > decodeFloat (0/0 :: Double) (-9223372036854775808,-53) This patch reverts to the old expected semantics. I plan to revisit the implementation during GHC 7.11 development. This should address #9810 Reviewed By: austin, ekmett, luite Differential Revision: https://phabricator.haskell.org/D486
* Reimplement im/export primitives for integer-gmp2Herbert Valerio Riedel2014-11-191-19/+17
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The import/export operations were available in `integer-gmp-0.5.1` already, but need to be reimplemented from scratch for the `integer-gmp-1.0.0` rewrite. This also adds a few more operations than were previously available for use w/ the `BigNat` type (which will be useful for implementing serialisation for the upcoming `Natural` type) Specifically, the following operations are (re)added (albeit with slightly different type-signatures): - `sizeInBaseBigNat` - `sizeInBaseInteger` - `sizeInBaseWord#` - `exportBigNatToAddr` - `exportIntegerToAddr` - `exportWordToAddr` - `exportBigNatToMutableByteArray` - `exportIntegerToMutableByteArray` - `exportWordToMutableByteArray` - `importBigNatFromAddr` - `importIntegerFromAddr` - `importBigNatFromByteArray` - `importIntegerFromByteArray` NOTE: The `integerGmpInternals` test-case is updated but not yet re-enabled as it contains tests for other primitives which aren't yet reimplemented. This addresses #9281 Reviewed By: austin, duncan Differential Revision: https://phabricator.haskell.org/D480
* Support for "with" renaming syntax, and output a feature flag.Edward Z. Yang2014-11-181-1/+4
| | | | | | | | | | | | | | | | | | | Summary: - Feature flag indicates to Cabal that we support thinning and renaming as it needs. - Support -package "base with (Foo as Bar)" which brings the ordinary modules into scope, as well as adding the renamings to scope. 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/D485
* When outputting list of available instances, sort it.Edward Z. Yang2014-11-1812-36/+38
| | | | | | | | | | | | | | | | | Summary: The intent of this commit is to make test suite cases more stable, so that it doesn't matter what order we load interface files in, the test output doesn't change. 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/D484
* Fix ffi023Simon Marlow2014-11-182-1/+8
|
* Adding dedicated Show instances for SrcSpan/SrcLocAlan Zimmerman2014-11-175-0/+59
| | | | | | | | | | | | | | | | | | | Summary: The derived Show instances for SrcSpan and SrcLoc are very verbose. This patch replaces them with hand-made ones which use positional syntax for the record constructors, rather than exhaustively listing each one. Test Plan: sh ./validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D445