summaryrefslogtreecommitdiff
Commit message (Collapse)AuthorAgeFilesLines
* Fix failing API Annotations tests from master cherry pickwip/7.10-api-annotsAlan Zimmerman2015-05-082-4/+11
|
* ApiAnnotations: misplaced AnnComma for squals productionAlan Zimmerman2015-05-088-1/+689
| | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: The parser production for squals has : squals ',' transformqual {% addAnnotation (gl $ last $ unLoc $1) AnnComma (gl $2) >> ams (sLL $1 $> ()) (fst $ unLoc $3) >> return (sLL $1 $> [sLL $1 $> ((snd $ unLoc $3) (reverse (unLoc $1)))]) } This attaches the comma to the wrong part of the squals, as it is generated in reverse order. Test Plan: ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: bgamari, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D846 GHC Trac Issues: #10312 (cherry picked from commit 713612674634754edd17264e688f0479d943d8d2)
* ApiAnnotations : AnnComma missing in TupleSectionAlan Zimmerman2015-05-088-2/+162
| | | | | | | | | | | | | | | | | | | | | | | | | | Summary: For the following code {-# LANGUAGE TupleSections #-} foo = do liftIO $ atomicModifyIORef ciTokens ((,()) . f) the annotation is missing for the comma. Test Plan: ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D834 GHC Trac Issues: #10280 (cherry picked from commit 225df19a87d8de8245db84d558618f4824631acc)
* ApiAnnotations : RdrHsSyn.isFunLhs discards parenthesesAlan Zimmerman2015-05-088-23/+184
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: The RdrHsSyn.isFunLhs function has the following isFunLhs e = go e [] where go (L loc (HsVar f)) es | not (isRdrDataCon f) = return (Just (L loc f, False, es)) go (L _ (HsApp f e)) es = go f (e:es) go (L _ (HsPar e)) es@(_:_) = go e es The treatment of HsPar means that any parentheses around an infix function will be discarded. e.g. (f =*= g) sa i = f (toF sa i) =^= g (toG sa i) will lose the ( before f and the closing one after g Test Plan: ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D832 GHC Trac Issues: #10269 (cherry picked from commit 5bde9f7c1834ab4da1fad1838afec1a578c26530)
* ApiAnnotations : quoted type variables missing leading quoteAlan Zimmerman2015-05-089-16/+219
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The HsOpTy can be constructed for a promoted type operator, in which case it has the following form | btype SIMPLEQUOTE qconop type { sLL $1 $> $ mkHsOpTy $1 $3 $4 } | btype SIMPLEQUOTE varop type { sLL $1 $> $ mkHsOpTy $1 $3 $4 } The SIMPLEQUOTE does not get an annotation, so cannot be reproduced via the API Annotations. Also, in splice_exp :: { LHsExpr RdrName } : TH_ID_SPLICE { sL1 $1 $ mkHsSpliceE (sL1 $1 $ HsVar (mkUnqual varName (getTH_ID_SPLICE $1))) } | '$(' exp ')' {% ams (sLL $1 $> $ mkHsSpliceE $2) [mo $1,mc $3] } | TH_ID_TY_SPLICE { sL1 $1 $ mkHsSpliceTE (sL1 $1 $ HsVar (mkUnqual varName (getTH_ID_TY_SPLICE $1))) } | '$$(' exp ')' {% ams (sLL $1 $> $ mkHsSpliceTE $2) [mo $1,mc $3] } the TH_ID_SPLICE and TH_ID_TY_SPLICE positions are lost. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D825 GHC Trac Issues: #10268 (cherry picked from commit 15aafc7fb61d2cbf95f2a564762399e82fe44e9c)
* Correct parsing of lifted empty list constructorMatthew Pickering2015-05-082-8/+22
| | | | | | | | | | | | | | | | | See #10299 Previously `'[]` was parsed to a `HsTyVar` rather than a `HsExplicitListTy`. This patch fixes the shift-reduce conflict which caused this problem. Reviewed By: alanz, austin Differential Revision: https://phabricator.haskell.org/D840 (cherry picked from commit caeae1a33e28745b51d952b034e253d3e51e0605) Conflicts: compiler/parser/Parser.y
* ApiAnnotations : lexer discards comment close in nested commentAlan Zimmerman2015-05-084-15/+17
| | | | | | | | | | | | | | | | | | | | | | | | | | When parsing a nested comment, such as {- {- nested comment -} {-# nested pragma #-} -} The lexer returns the comment annotation as {- {- nested comment {-# nested pragma # -} Restore the missing comment end markers in the annotation. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D829 GHC Trac Issues: #10277 (cherry picked from commit 5fded20c51ae61770f909351c851aaca3d3e331c)
* API Annotations : ExprWithTySig processing discards annotated spansAlan Zimmerman2015-05-088-2/+162
| | | | | | | | | | | | | | | | | | | | | | | | | | | | In RdrHsSyn.checkAPat the processing for ExprWithTySig is defined as ExprWithTySig e t _ -> do e <- checkLPat msg e -- Pattern signatures are parsed as sigtypes, -- but they aren't explicit forall points. Hence -- we have to remove the implicit forall here. let t' = case t of L _ (HsForAllTy Implicit _ _ (L _ []) ty) -> ty other -> other return (SigPatIn e (mkHsWithBndrs t')) The t' variable ends up losing its original SrcSpan in the first case branch. This results in annotations becoming detached from the AST. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D823 GHC Trac Issues: #10255 (cherry picked from commit 8dc294487fdaf102349c373c7db4796693573310) Conflicts: testsuite/tests/ghc-api/annotations/Makefile
* parser : the API annotation on opt_sig is being discardedAlan Zimmerman2015-05-084-9/+23
| | | | | | | | | | | | | | | | | | | | | The opt_sig production is defined as opt_sig :: { ([AddAnn],Maybe (LHsType RdrName)) } : {- empty -} { ([],Nothing) } | '::' sigtype { ([mj AnnDcolon $1],Just $2) } It is used in the alt and decl_no_th productions, but neither of them add the returned annotations. This commit captures the annotations in the calling productions. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D822 GHC Trac Issues: #10254 (cherry picked from commit 919b51174163907d2bc3bb41aadf56aa8bb42e9b)
* parser: API Annotations : guardquals1 does not annotate commas properlyAlan Zimmerman2015-05-084-132/+174
| | | | | | | | | | | | | | | | | | | The `guardquals1` production includes : guardquals1 ',' qual {% addAnnotation (gl $ last $ unLoc $1) AnnComma (gl $2) >> return (sLL $1 $> ($3 : unLoc $1)) } The AnnComma should be attached to `(gl $ head $ unLoc $1)`, rather than `last`. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D818 GHC Trac Issues: #10256 (cherry picked from commit 9eab6feed44ad8beb6703d2e27ce47a8f79d0f49)
* parser: opt_kind_sig has incorrect SrcSpanAlan Zimmerman2015-05-086-27/+56
| | | | | | | | | | | | | | | | | | | | | | The production for opt_kind_sig is opt_kind_sig :: { Located (Maybe (LHsKind RdrName)) } : { noLoc Nothing } | '::' kind {% ajl (sLL $1 $> (Just $2)) AnnDcolon (gl $1) } The outer Location is used only to get the full span for the enclosing declration, and is then stripped. The inner LHsKind then has a SrcSpan that does not include the '::' Extend the SrcSpan on $2 to include $1 Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D813 GHC Trac Issues: #10209 (cherry picked from commit 8aefc9b746512e91891879ad546e850e8a427d23)
* Wibble to DmdAnalSimon Peyton Jones2015-05-071-4/+4
| | | | | | | | | | This fixes a typo in d5773a4939b1feea51ec0db6624c9462751e948a Teach DmdAnal that coercions are value arguments! (Trac #10288) Sorry about that; I'm not sure how it slipped through. (cherry picked from commit 5c7e4db5ce84395eb0d727eb3b0f505a00191164)
* base: Fix confusing docs typoAlexander Berntsen2015-05-061-4/+3
| | | | | | | | | | Signed-off-by: Alexander Berntsen <alexander@plaimi.net> Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D872 (cherry picked from commit fa0474da6954a3e57785fe703acc83e2fecef88f)
* Fix typo: identifer -> identifierVikraman Choudhury2015-05-062-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | I noticed this typo while using template haskell. Signed-off-by: Vikraman Choudhury <git@vikraman.org> Test Plan: ``` λ> :set -XTemplateHaskell λ> :m +Language.Haskell.TH λ> data Foo = Foo λ> $(conE ''Foo) <interactive>:9:9: Type constructor ‘Foo’ used where a value identifier was expected In the expression: Foo In an equation for ‘f’: f = Foo ``` Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D871 (cherry picked from commit 458a97b86ad154812d08e0fe3548b88ac8412b4f) Conflicts: testsuite/tests/rename/should_compile/rn040.hs
* Teach DmdAnal that coercions are value arguments!Simon Peyton Jones2015-05-061-7/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The demand analyser was treating coercion args like type args, which meant that the arguments in a strictness signature got out of step with the arguments of a call. Result chaos and disaster. Trac #10288 showed it up. It's hard to get this bug to show up in practice because - functions abstracted over coercions are usually abstracted over *boxed* coercions - we don't currently unbox a boxed-coercion arg because it's GADT (I see how to fix this too) But after floating, optimisation, and so on, Trac #10288 did get a function abstracted over an unboxed coercion, and then the -flate-dmd-anal pass went wrong. I don't think I can come up with a test case, but I don't think it matters too much. Still to come - Fix a second bug, namely that coercion variables are wrongly marked as absent because DmdAnal doesn't check the the free variables of casts. I think this never bites in practice (see the follow-up commit) - Make GADT products work with strictness analysis (cherry picked from commit d5773a4939b1feea51ec0db6624c9462751e948a)
* arm: Force non-executable stack (#10369)Erik de Castro Lopo2015-05-061-1/+2
| | | | | | | | | | | | | | | | | | | | Test `T703` was found to be failing on arm/linux. The solution was to add a linker flag to explicitly set the stack to non-executable. Signed-off-by: Erik de Castro Lopo <erikd@mega-nerd.com> Test Plan: validate on x86_64 and arm linux Reviewers: ezyang, rwbarton, austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D875 GHC Trac Issues: #10369 (cherry picked from commit 63a10bbc42492c58feb377d79e05a185e6efcd5a)
* Use the gold linker for aarch64/linux (#9673)Erik de Castro Lopo2015-05-061-7/+11
| | | | | | | | | | | | | | | | | | Like 32 bit Arm, Aarch64 requires use of the gold linker. Signed-off-by: Erik de Castro Lopo <erikd@mega-nerd.com> Test Plan: 'make install' on aarch64, validate elsewhere Reviewers: rwbarton, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D858 GHC Trac Issues: #9673 (cherry picked from commit 0bbc2ac6dae9ce2838f23a75a6a989826c06f3f5)
* Fix fundep coverage-condition check for poly-kindsSimon Peyton Jones2015-05-063-4/+16
| | | | | | | | | | | See Note [Closing over kinds in coverage] in FunDeps. I'd already fixed this bug once, for Trac #8391, but I put the call to closeOverKinds in the wrong place, so Trac #10109 failed. (It checks the /liberal/ coverage condition, which The fix was easy: move the call to the right place! (cherry picked from commit 49d9b009a2affb6015b8f6e2f15e4660a53c0d9a)
* Make sure GHC.List.last is memory-efficientJoachim Breitner2015-05-061-2/+9
| | | | | | | | by eta-expanding its definition so that GHC optmizes the foldl here. Also make sure that other uses of last go via foldl as well, to allow list fusion (tested in T9339). Fixes #10260. (cherry picked from commit 524ddbdad5816f77b7b719cac0671eebd3473616)
* base: Export GHC.Event(.Internal).LifetimeBen Gamari2015-04-253-0/+9
| | | | | | | | | This was an unfortunate oversight in the original event manager rework patch. Fixes #10308 Differential Revision: https://phabricator.haskell.org/D845 (cherry picked from commit 9a0c17950fdfd0c89c672da9d8b25a419f66c1f8)
* Bump base version to 4.8.1.0Herbert Valerio Riedel2015-04-2568-76/+76
| | | | Several test outputs needed base-4.8.0.0 replaced by base-4.8.1.0
* Accept changed DmdType in spec-inline test outputHerbert Valerio Riedel2015-04-251-1/+1
| | | | In GHC HEAD the corresponding update occured in e6e0415befc97
* Commit missing T10148 files and ignore the built executable.Edward Z. Yang2015-04-252-0/+7
| | | | Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* testsuite: Accept qualified GHC.Prim.ConstraintHerbert Valerio Riedel2015-04-2515-21/+24
| | | | | | I suspect this was caused by f6c690ba6491e0e943bd07763c0063a55ff0c760 which would be compensated by 547c597112954353cef7157cb0a389bc4f6303eb (which OTOH was not cherry-picked into 7.10)
* T10195: Drop -fno-warn-redundant-constraints for GHC 7.10Herbert Valerio Riedel2015-04-251-1/+0
|
* configure: Test for #9920 when compiling for armErik de Castro Lopo2015-04-251-0/+34
| | | | | | | | | | | | | The ghc-7.10 branch requires use of llvm-3.5, but the llvm-3.5.0 release had a bug that was fixed in llvm-3.5.1. When we are targeting arm, test for this bug in the llvm program `llc` during confgure and if present, abort configuration with an informative error message. Signed-off-by: Erik de Castro Lopo <erikd@mega-nerd.com> Differential Revision: https://phabricator.haskell.org/D857
* configure: LLVM and LD detection improvements (#10329)Erik de Castro Lopo2015-04-253-32/+62
| | | | | | | | | | | The ghc-7.10 branch *only* works with llvm-3.5. This commit is basically the ghc-7.10 branch version of 485dba86d2 in the master branch. Signed-off-by: Erik de Castro Lopo <erikd@mega-nerd.com> Differential Revision: https://phabricator.haskell.org/D856
* Update Cabal submodule to 1.22.3.0 releaseHerbert Valerio Riedel2015-04-231-0/+0
| | | | | | | | | | | | Highlights since 1.22.2.0: - cabal check will fail on -fprof-auto passed as a ghc-option - filterConfigureFlags: filter more flags. - fix ghcjs-pkg version number handling Addresses #10304 (cherry picked from commit 4bc925a67285a71ddd14642e218d85de83bc214a)
* GHC.Prim.Constraint is not built-in syntaxSimon Peyton Jones2015-04-144-15/+25
| | | | | | This fixes Trac #10233 (cherry picked from commit 74d2c33a1f4ebe3de090bc73d08910bbdd31f8f1)
* More aggressive Given/Wanted overlap checkSimon Peyton Jones2015-04-144-67/+110
| | | | | | | | | | | | | | | This fixes Trac #10195 For some reason we considered untouchability before, but Trac #10195 shows that this is positively worng. See Note [Instance and Given overlap] in TcInteract. Looking at the Git log, it seems that this bug was introduced at the same time that we introduced the Given/Wanted overlap check in the first place. (cherry picked from commit 8b7ceece52d2a0bb8a4ea5609da286fb76d88211)
* Do version specific detection of LLVM tools (#10170).Erik de Castro Lopo2015-04-142-30/+52
| | | | | | | | | | | | | | | | | | | | | | | | | | | | The LLVM developers seem to make breaking changes in the LLVM IR language between major releases. As a consumer of the LLVM tools GHC now needs to be locked more tightly to a single version of the LLVM tools. GHC HEAD currently only supports LLVM version 3.6. This commit changes the configure script to look for `llc-3.6` and `opt-3.6` before looking for `llc` and `opt`. If the former are not found, but the later are, check that they actually are version 3.6. At the same time, when detecting known problems with the LLVM tools (ie #9439) test for it using the versions of the LLVM tools retrieved from the bootstrap compiler's settings file. Test Plan: Manual testing. Reviewers: thomie, rwbarton, nomeata, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D745 GHC Trac Issues: #10170 (cherry picked from commit 42448e3757f25735a0a5b5e2b7ee456b5e8b0039)
* Fix detection of llvm-x.xThomas Miedema2015-04-143-8/+18
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Four bug fixes and a little refactoring. * `find -perm \mode` should be `find -perm /mode` (#9697) * `find -regex '$3' should be `find -regex "$3"` (#7661) From `man sh` on my system (Ubuntu 14.04): "Enclosing characters in single quotes preserves the literal meaning of all the characters ..." * LlcCmd and OptCmd should be passed to ghc, using `-pgmlo` and `-pgmlc`, for detection of #9439. * -pgmlo and -pgmlc were undocumented because of an xml tag misplacement. Test Plan: The aclocal.m4 macro has seen about 10 iterations since its inception. Without a testsuite, I can't guarantee this version is bug free either. It's all pretty frustrating. Reviewers: bgamari, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D683 GHC Trac Issues: #9697, #7661, #9439 (cherry picked from commit 1dfab7a8ace5f09f00f8fb695932b4324e88b822)
* Move libffi configuration after basic toolchain setupReid Barton2015-04-141-56/+56
| | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: The relevant aspect is that the libffi configuration's AC_CHECK_LIB and AC_CHECK_HEADERS are moved after FIND_GCC. There are two reasons to do this: 1. We should detect the presence of libffi using the C compiler that we are eventually going to use to build GHC. 2. Running AC_CHECK_HEADERS before FIND_GCC pollutes the CPP variable with "gcc -E" (wrong when cross-compiling), and CPP is not reset by FIND_GCC. Thus this patch fixes x86_64 -> i386 cross-compilation of integer-gmp2. Test Plan: Local x86_64 -> i386 cross-compiling validate; Harbormaster Reviewers: austin Reviewed By: austin Subscribers: erikd, carter, thomie Differential Revision: https://phabricator.haskell.org/D597 (cherry picked from commit a5bc2579afac3268c31626777406c295c7e67755)
* use projectVersion from DynFlags rather than cProjectVersion for versionedAppDirLuite Stegeman2015-04-141-1/+1
| | | | | | | | | | Reviewed By: edsko, austin Differential Revision: https://phabricator.haskell.org/D824 GHC Trac Issues: #10232 (cherry picked from commit 6109b312cdd9dfe4bdad4030e0185dd67e6ec18d)
* Import rand using capiReid Barton2015-04-141-2/+2
| | | | | | | | | | | | | | | | | | Summary: Android has no rand symbol (it's a static inline function there). Test Plan: ghc-android builds Reviewers: trofi, austin, hvr Reviewed By: hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D826 GHC Trac Issues: #10274 (cherry picked from commit f536d89603bb49dea192b47f54416dc88da980af)
* Zap usage info in CSE (Trac #10218)Simon Peyton Jones2015-04-1410-32/+84
| | | | | | | | | | | | | | | | | | | Trac #10218 reports a subtle bug that turned out to be: - CSE invalidated the usage information computed by earlier demand analysis, by increasing sharing - that made a single-entry thunk into a multi-entry thunk - and with -feager-blackholing, that led to <<loop>> The patch fixes it by making the CSE pass zap usage information for let-bound identifiers. It can be restored by -flate-dmd-anal. (But making -flate-dmd-anal the default needs some careful work; see Trac #7782.) (cherry picked from commit d261d4cbcc867405f71d7c9580628f52978e2267)
* Test Trac #10148Simon Peyton Jones2015-04-143-0/+29
| | | | (cherry picked from commit eacda9244913709ed025767418468b4cfc878cf9)
* Fix a long-standing bug in the demand analyserSimon Peyton Jones2015-04-142-87/+165
| | | | | | | | | | | | | | | | | | | | This patch fixes Trac #10148, an outright and egregious bug in the demand analyser. It is explained in Note [Demand on case-alternative binders] in Demand.hs. I did some other minor refactoring. To my astonishment I got some big compiler perf changes * perf/compiler/T5837: bytes allocated -76% * perf/compiler/T5030: bytes allocated -10% * perf/compiler/T3294: max bytes used -25% Happy days (cherry picked from commit 9f0f99fd41ff82cc223d3b682703e508efb564d2)
* Look inside synonyms for foralls when unifyingSimon Peyton Jones2015-04-075-4/+26
| | | | | | This fixes Trac #10194 (cherry picked from commit 553c5182156c5e4c15e3bd1c17c6d83a95a6c408)
* Do not quantify over the function itself in a RULESimon Peyton Jones2015-04-073-17/+68
| | | | | | | | | We were erroneously quantifying over the function when it had a dictionary type. A bit pathological, but possible. This fixes Trac #10251 (cherry picked from commit cfb60421a43f23e75ead85d99cec207a156f9312)
* Add a bizarre corner-case to cgExpr (Trac #9964)Simon Peyton Jones2015-04-073-23/+67
| | | | | | | | | | | | | David Feuer managed to tickle a corner case in the code generator. See Note [Scrutinising VoidRep] in StgCmmExpr. I rejigged the comments in that area of the code generator Note [Dodgy unsafeCoerce 1] Note [Dodgy unsafeCoerce 2] but I can't say I fully understand them, alas. (cherry picked from commit 9c78d09e344e97d2d5c37b9bb46e311a3cf031e2)
* The production for squals is incorrect; see D806 for specifics.Alan Zimmerman2015-04-0711-32/+80
| | | | | | | | | | | | This diff depends on D803. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D806 GHC Trac Issues: #10214 (cherry picked from commit cf196400609d920e7f8189b9376833f4f5886360)
* The production for `pquals` is incorrect; the specifics are in D803.Alan Zimmerman2015-04-078-3/+256
| | | | | | | | | | Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D803 GHC Trac Issues: #10207 (cherry picked from commit f1a4e42ea2e5302147dcb69b9baa6f4aa3af6e37)
* rts/Linker.c: distinct between DATA and CODE labels when importingSergei Trofimovich2015-04-071-18/+42
| | | | | | | | | | | | | | | | | | | | | | The patch is a last major piece to make unregisterised GHC build under GCC's link-time optimizer. Before the patch we imported everything external as functions. Now we distinct between global variables and functions. The difference is crucial on ia64 and a complement to fixes: > d82f592522eb8e063276a8a8c87ab93e18353c6b > CMM: add a mechanism to import C .data labels > e18525fae273f4c1ad8d6cbe1dea4fc074cac721 > pprC: declare extern cmm primitives as functions, not data Signed-off-by: Sergei Trofimovich <siarheit@google.com> Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D797 (cherry picked from commit ab76b0990e9f7d20bde403be38935f9d16491806)
* Suggest how to fix .ghci when it is group writeable (#8248)Vikas Menon2015-04-071-1/+3
| | | | | | | | | | | | | | | | | | | | | ``` chmod 664 $PATH_TO_GHCI_CONF/.ghci ``` Run ghci. You will now get a warning + a suggestion: ``` *** WARNING: $PATH_TO_GHCI_CONF/.ghci is writable by someone else, IGNORING! Suggested fix: execute 'chmod 644 $PATH_TO_GHCI_CONF/.ghci' ``` Execute fix and the warning should disappear. Reviewed By: mboes, thomie Differential Revision: https://phabricator.haskell.org/D805 (cherry picked from commit b972de0365f94e1be9d78537152eee969dc5f4cb)
* fix '&stg_interp_constr_entry' FFI type to be FunPtrSergei Trofimovich2015-04-071-13/+16
| | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: It used to be Ptr, which is slightly incorrect. ia64 has different representations for those types. Found when tried to build unregisterised ghc with -flto, GCC's link-time optimisation which happens to check data / code declaration inconsistencies. It our case 'stg_interp_constr_entry' is an RTS function: StgFunPtr f (StgFunPtr) while '"&f" :: Ptr()' produces StgWordArray f[]; Signed-off-by: Sergei Trofimovich <siarheit@google.com> Reviewers: simonmar, hvr, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D796 (cherry picked from commit 22eecaff9db1feb7eef9ee8ed11fcef4df01b08e)
* User's guide: .a files can be 2-2.5x larger with -split-objsThomas Miedema2015-04-071-4/+4
| | | | | | | | | | And remove warning. This feature is available through cabal even. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D801 (cherry picked from commit fef4948f172b66eaf8db520b381dd4a8237b5644)
* Remove an incorrect statement about -fwarn-tabsDave Laing2015-04-031-2/+0
| | | | | | | | | | Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D772 GHC Trac Issues: #10213 (cherry picked from commit 2255c76c7049314d3d8545efb6317688ba0da72c)
* docs: some 7.10.2 release notesAustin Seipp2015-04-031-1/+15
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* docs: add 7.10.2 relnotes skeletonAustin Seipp2015-04-033-0/+23
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>