[commit: ghc] wip/pattern-synonyms's head updated: Store IfExtNames for PatSyn matchers and wrappers in interface file (e0f47fe)

git at git.haskell.org git at git.haskell.org
Sat Apr 12 10:52:04 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

Branch 'wip/pattern-synonyms' now includes:

     466d069 Bump version: 7.7 -> 7.9
     24669fe Update Win32 submodule to pull in version bump
     9f58cec Fix glitch in core-spec pdf
     48326cf Fix iOS build (fallout from 28b031c506)
     99484c9 Add a perf-cross build setting.
     044f233 Bump win32 version number in release notes
     1dd38a5 Remove Coercible documentation from compiler/prelude/primops.txt.pp
     fda9beb Fix some edge cases in 8f8bd88c (#7134)
     5671ad6 Update to latest Cabal 1.18 branch tip
     71a412c No need to remove testsuite/.git
     50e4d40 Individual sdist-foo targets
     a2269bf Remove some references to deprecated -fglasgow-exts in user's guide
     ea584ab Loopification jump between stack and heap checks
     c6ce808 Remove unnecessary LANGUAGE pragma
     99c3ed8 Simplify Control Flow Optimisations Cmm pass
     78afa20 Nuke dead code
     d5fb670 Fix a popular typo in comments
     f028975 Remove redundant NoMonoLocalBinds pragma
     b5c45d8 Remove unused import
     5f64b2c Add test-case for #8726
     526cbc7 Document deprecations in Hoopl
     dba9bf6 Eliminate duplicate code in Cmm pipeline
     2b33f6e Final fix to #7134 (and #8717 as well.)
     2f6d36f Tweak holes documentation
     40ce203 Fix #8698 by properly handling long section names and reenabling .ctors handling
     5bda0d0 Mention that MR is off by default in GHCi in documentation
     ad44e47 Switch to relative URLs in .gitmodules
     b755c7b Correctly clone submodules from github
     41cfc96 Tweak documentation of monomorphism restriction
     298a25b Fix __thread detection (#8722)
     b4eb630 Remove ios_HOST check for GCTDecl.h
     03200e8 Fix some Python brainos in testlib (except e is not valid form).
     c3ff5f2 Add test case for #8743
     312686c In deepSplitCprType_maybe, be more forgiving
     218dead Fix #8706, documenting that type operators are not promoted.
     4f6a0f4 T8256 needs vector
     674c969 Fix #8631.
     e0a5541 Issue an error for pattern synonyms defined in a local scope (#8757)
     719108f Add test suite for #8757
     7561e37 double-negate test for Stage1Only to fix `make clean`
     65170fc Let `make distclean` remove `/{ch01,ch02,index}.html`
     02c7135 Move test case for #8631 to the correct directory.
     8cc398f Fix #8758 by assuming RankNTypes when checking GND code.
     9e0c1ae Test #6147, which was fixed with the roles commit.
     d1dff94 Test #7481, which had already been fixed.
     6122efc Fix #8759 by not panicking with TH and patsyns.
     e0dadc8 Apply changes relative to TH.Pred becoming a TH.Type's synonym (issue #7021)
     182ff9e Fix tests due to issue #7021
     8e303d7 Refactor previous commit on fixing #7021.
     cdceadf Implement CallArity analysis
     9bc8265 Add a unit test for CallArity
     393ea73 Update test cases due to call arity
     a4450ec Note [Eta expansion in match]
     b4715d6 Replace forall'ed Coercible by ~R# in RULES
     f4fb94f In CoreSubst, optimize Coercible values aggressively
     d557d8c In simpleOptExpr, unfold compulsary unfoldings
     8f16233 Add Case TyConAppCo to match_co
     377672a Test case for RULE map coerce = coerce
     a27b298 Use exprIsLambda_maybe in match
     cde88e2 Test case: Looking through unfoldings when matching lambdas
     5d04603 Remove eta-expansion in Rules.match
     e16826b Cleaned up Maybes.lhs
     9f607ee Link to #minimal-pragma from release notes
     e2cacb6 Manual hlinting: or (map f) = any f
     3477216 Fix Manual hlinting patch
     3d80787 Fix some typos in comments
     3d9644c Remove space after ASSERT.
     473f12a Fix #5682. Now, '(:) parses.
     1382975 Fix #8773.
     68f0a6a Fix --enable-unregistered by passing NOSMP to .hc compiler (#8748)
     4bb50ed Fix --enable-unregistered by declaring missing RTS functions (#8748)
     ebace69 rts/Capability.c: fix crash in -threaded mode on UNREG build
     858a807 includes/Stg.h: add declarations for hs_popcnt and frinds
     2d0fa9a rts/package.conf.in: fix UNREG on --with-system-libffi when include-dir is passed explicitely
     2d5372c mk/config.mk.in: lower -O2 optimization down to -O1 on UNREG
     a365eab Fix installation of hpc (#8735)
     c83eabf Fix check for TLS support in Storage.c
     5023c91 Fix #8754 in a round-about way.
     a8a01e7 Fix #8745 - GND is now -XSafe compatible.
     dc08091 Fix #8770
     b626c3d Add comments explaining #8754
     2931d19 More liberally eta-expand a case-expression
     47f473b Use NoGen plan for unboxed-tuple bindings
     5dd1cbb Allow ($) to return an unlifted type (Trac #8739)
     cd3a3a2 Add some more traceTcS calls
     89d2c04 Keep kind-inconsistent Given type equalities (fixes Trac #8705)
     642bba3 Revert "Add comments explaining #8754"
     e789a4f Revert "Fix #8754 in a round-about way."
     4c93a40 Make CallArity make more use of many-calls
     fa353f2 Call Arity refactoring: Use a product domain
     983fbbe Call Arity refactoring: Factor out callArityBound
     7c603ab Call Arity refactoring: instance Outputable Count
     2ab00bf Call Arity: Now also done on Top-Level binds
     7e787e7 Move unit call arity unittests into subdirectory
     d51d7ef Call arity: Handle type application correctly
     f347bfe Support mutual recursion
     d3c579c Call arity testcase for #3924
     ba4616b Call Arity: Update compiler perf number changes
     af7428e Call Arity refactoring: fakeBoringCalls
     47d725f Update to primitive-0.5.2.1
     43c314c add omitted FP_PROG_AR_SUPPORTS_ATFILE into the distribution configure.ac (fixes #8794)
     5c6ced5 fix build failure on Solaris 10 due to RANLIB being set to ':' by configure (#8795)
     27fe128 add more information about the nature of support of prefetch primops on none x86/AMD64 -fasm platforms (and -fvia) to the 7.8 release notes
     e638acb fix sed expression in build dependencies rules to work well with non-GNU sed (fixes #8764)
     e75ebc4 Switch on -dynamic-too with QuasiQuotes as well.
     2b34947 Clear up docs regarding LLVM backend (#8792)
     f99a032 Fix #8801: exclude extra packages from the sdist.
     d3af980 Really fix #5682 (parsing of promoted datacons)
     925b0a4 RetainerProfile.c: include missing header (#8810)
     3361e6c Update to primitive-0.5.2.1 (again)
     55cc01a Add test case for #8806.
     5a57675 Add a test for d3af980 (#5682)
     c72e889 Fix #8754 again.
     5075c19 Add VERSION file to gitignore.
     beac525 Fix installation of ghc-split (#8760)
     ed1aced Fix #8696 - don't generate static intra-package references.
     4f69b1e Fix Haddock formatting
     ede5b51 Make Outputable instance for HsDocString useful
     018676c Use U+2018 instead of U+201B quote mark in compiler messages
     98b6756 Fix #8807.
     32f41c7 Make distribution tarball compression format configurable
     b1ee32e Follow-up to 32f41c79
     b1ddec1 Fix a bug in codegen for non-updatable selector thunks (#8817)
     68c0d86 fix comment on allocate() (#8254)
     af6746f Add hs_thread_done() (#8124)
     67029f2 PPC: Fix loads of PIC data with > 16 bit offsets (#7830).
     a864c34 Bump T6048 tests.
     7161152 Documentation updates for 7.8.1 release
     025a66e Fix binary-dist target with xz/gzip
     f962725 Note that we need Cabal-1.18 in the release notes
     251b18a binary-dist: when using xz, use extreme compression.
     3fba875 add missing files (#8124)
     176205c fix copy/pasto
     afb42a5 Update time to 1.4.2 release
     01f9ac3 Update `Cabal` to 1.18.1.3 release
     cb8a63c Major Call Arity rework
     2d82846 Typos in comments
     eeb1400 Add some debug tracing
     4b355cd Make the demand on a binder compatible with type (fixes Trac #8569)
     96daafc Attach the right location to pattern synonym error message (fixes Trac #8841)
     bf9bf60 Test for Trac #8841 now works
     7fa6c67 Trac #8569 fixed
     1ac9114 Test #8851.
     0014fb3 Run testcase for 8124 only with threaded ways
     3efcb0a Make sync-all handle all github protocols correctly
     cdac487 Make -XDeriveFunctor more generous about non-last arguments (Trac #8678)
     cf1a0f9 Fix the treatment of lexically scoped kind variables (Trac #8856)
     062391b Test Trac #8856
     d246c62 Also allow http://github.com (#8824)
     9d14262 Improve documentation of standalone deriving (c.f. Trac #8851)
     f521a26 Unify, rather than match, in GND processing (fixes Trac #8865)
     ddf79eb Add "bench" build flavour to build system
     9c9bb00 Fix copy-paste error in build system comment
     a10ed3e Comments only
     ef44a42 Make SetLevels do substitution properly (fixes Trac #8714)
     41f8031 Fix last-minute typo in SetLevels commit ef44a4
     22f010e codeGen: allocate small arrays of statically known size inline
     a70e7b4 Represent offsets into heap objects with byte, not word, offsets
     b684f27 Refactor inline array allocation
     c1d74ab Fix incorrect loop condition in inline array allocation
     22e4bba Add test for inline array allocation
     d8b3826 Validate computed sums in inline array allocation test
     d793a14 Add perf test for inline array allocation
     7f919de Call Arity: Resurrect fakeBoringCalls
     b0416e7 Comments on virtHp, realHp (Trac #8864)
     b340681 A bit more tracing to do with SPECIALISE pragmas
     60bbc0a Export runTcInteractive from TcRnDriver, and from GHC (Trac #8878)
     7ef90e3 Comments only
     8fd7d58 Add BuiltinRules for constant-folding not# and notI# (logical complement)
     ea6dcef Test Trac #8832
     4d1b7b4 Add OutputableBndr instance for OccName
     23c0f1e pprIfaceContextArr: print a context including the "=>" arrow
     24eea38 pprIfaceDecl for IfacePatSyn: use pprPatSynSig
     065c35a Pretty-print the following TyThings via their IfaceDecl counterpart:  * AnId  * ACoAxiom  * AConLike
     ed2a8f0 Improve copy/clone array primop docs
     e55acf0 Update to containers-0.5.5.0
     46d05ba Fix two issues in stg_newArrayzh
     a0bcbb5 fix SHELL makefile variable to be set by the configure script (fixes #8783)
     623883f disable shared libs on sparc (linux/solaris) (fixes #8857)
     b7e5d72 Fix incorrect blocksize calculation on Win64
     d574fcb config.mk.in: ARM now supports dynamic linking with the LLVM backend
     b84b5da DriverPipeline: Ensure -globalopt is passed to LLVM opt
     b99ace3 Fix incorrect maxStkSize calculation (#8858)
     cbdd832 Fix T2110 now that base has map/coerce rule.
     210ccab codeGen: allocate small byte arrays of statically known size inline
     5972229 Remove "Safe mode" check for Coercible instances
     8ee6162 Recharacterize test according to discussion in #8851.
     8c5ea91 Fix #8884.
     337bac3 Fix typo in user's manual, changing "-j N" to "-jN".
     797da5c Call Arity : Note about fakeBoringCalls
     41ab584 Remove unused gHC_COERCIBLE
     c61d40e testsuite: look for tests-ghc directories for libraries
     df265b9 Update to containers-0.5.5.1
     4133ff8 Reference  Note [Kind-changing of (~) and Coercible]
     d53ccab Another reference to Note [Kind-changing of (~) and Coercible]
     1e36a38 Document Coercible in the user guide
     f3eeb93 Honor Op_PrintExplicitForalls setting in pprIfaceForAllPart
     5908a74 Use prefix notation in pprIfaceDecl for IfaceIds
     5200369 Reinstate pretty-printing of AnIds via pprId (#8776)
     de32a95 Add test case for #8776
     306d255 Call Arity: Never eta-expand thunks in recursive groups
     aab6b9b Call Arity test case: Check what happens with unboxed lets
     7602bd4 Remove code reporting issues with Safe Haskell and coerce.
     0142237 Test case: :info Coercible in GHCi
     db497cd Fix comment for ghci script files
     d59170b Coercible is now exported from GHC.Types (#8894)
     5d59265 Remove support for "primclass"
     7a7af1f Unflatten the constraints of an inferred types (Trac #8889)
     a79613a Revert ad15c2, which causes Windows seg-faults (Trac #8834)
     7511d5b Fix validation issue due to Coercible move (#8894)
     2b3feaa Comments only
     f4d15cb More debug info
     0e2155d Test Trac #8889
     a5ab610 Test case: ghci059: Forgot stdout file
     3099e40 Add some documentation about type-level literals.
     696bfc4 Update submodule to Win32-2.3.0.2
     87bbc69 Make sure we occurrence-analyse unfoldings (fixes Trac #8892)
     5e4bdb5 Implement ordering comparisons for type-level naturals and symbols.
     a3f78e2 isLexVarSym: check all characters of the name, not just the first one.
     21028ee Update expected test outputs to match new format of pretty-printing interface contents
     a6939ec Don't use gcptr for interior pointers
     df409de Flush after TH in #8884 test case
     ba0c012 Typos
     f9b6a2b testsuite: add test for #8831
     7a1c851 linker: Fix indirect calls for x86_64 windows (#2283)
     99ef279 Update ghc --help references to --make and a.out (fixes #8600)
     1eece45 codeGen: inline allocation optimization for clone array primops
     4bc3c82 Mark test for #8831 as known-broken
     1a63f17 Follow hs_popcntX changes in ghc-prim
     16d04d9 Enable popcnt test now when segfault is fixed
     be2e0e8 Make cabal01 pass with Cabal 1.18 (#8738).
     9b38f6a Comments only -- clarifying Notes around compatibility.
     b0bcbc0 Remove redundant compatibility check.
     4779602 Add test case for #8917
     c99941c Fix #8917.
     d523f9b sync-all: Skip END actions on exceptions
     ac24bf4 add --with-ar and --with-ranlib configure parameters
     ace7477 Add a simplistic Vagrantfile with bootstrapping
     045b280 change deriveConstants to use nm in a POSIX way (fixes #8781)
     34b0721 Convert haddock into a proper submodule (re #8545)
     8f26728 ghc-cabal: force use of UTF8 when writing out `haddock-prologue.txt`
     ffed708 Apply the kind subst to the (kinds of the) quanitifed tyvars in deriveTyData
     28e8d87 Simplify handling of the interactive package; fixes Trac #8831
     7973bfb Test Trac #8893
     1a7709e Trac #8831 is fixed
     90142be Fix typo
     4b4fc7d Catch a bunch of typos in comments
     61654e5 The substitution is never needed, so don't prepare it
     8f73037 Revert "Fix #8745 - GND is now -XSafe compatible."
     15b1eb7 Revert "change deriveConstants to use nm in a POSIX way (fixes #8781)"
     74894e0 Add missing kind-check for tcEqType on forall-types
     3f59647 Don't export isTcReflCo_maybe (unused)
     5a51b69 Comments only
     c89c57e For equalities with incompatible kinds, new IrredCan goes in the inert set, not work list
     9f9b10f Debug tracing only
     6ae678e Flattener preserves synonyms, rewriteEvidence can drop buggy "optimisation"
     a8b7b28 Implicit parameters should not be allowed in class and instance declarations
     5c7ced0 Comments only
     73cab20 relnotes: GND is not -XSafe compatible.
     0b6fa3e Eliminate redundant seq's (Trac #8900)
     41ba7cc Improve the desugaring of RULE left-hand-sides (fixes Trac #8848)
     b800e52 Comments only
     88d9452 Test Trac #8848
     2d1ecd2 Suppress uniques for simpl016 to normalise debug output
     ce335ce Typos in comments
     11b31c3 Add flags to control memcpy and memset inlining
     f868254 Fixup help text
     6189c76 --with-gcc overrides CC_STAGE0 when not cross-compiling (#8498)
     a6f2c85 Don't perform permission checks for scripts named with -ghci-script (#6017)
     975e9cb Include EXTRA_LD_OPTS (amongst other things) when linking programs
     e7f26cd Pass custom CC and LD opts to Cabal when configuring a package
     d011cde Include SRC_CC_OPTS and SRC_LD_OPTS when compiling ghc-cabal
     2aa7810 Use LDFLAGS when compiling ghc-pwd
     261a97b increase bounds for T3064
     c4eeacd Use the correct callClobberedRegs on Windows/x64 (#8834)
     7ef3f0d rts: remove unused functions, fix validate on OS X
     e54828b Make copy array ops out-of-line by default
     4c8edfd Remove debugging output
     90329b6 Add SmallArray# and SmallMutableArray# types
     838bfb2 Add missing symbols to linker
     dd02850 PrimOps.cmm: whitespace only
     4de517f Add more missing linker symbols
     c310823 CopySmallArrayStressTest needs random
     1a11e9b Add inline versions of copy ops for small arrays
     345eea2 Update Haddock submodule
     52c6dc9 Temporarily fight off build bogons on OS X
     5d7f590 Support thin archive format
     63b0e1b Update Haddock submodule
     791f4fa Make sure that polykinded Typeable is defaultable (Trac #8931)
     3671d00 Fix desguaring of bang patterns (Trac #8952)
     8bf8ce1 Test Trac #8931
     b20bc18 Parse the variables in a type signature in the order given (Trac #8945)
     2033a58 Update Haddock submodule
     e94ed11 With AutoDeriveTypeable, derive for promoted constructors, too.
     750271e Simplify and tidy up the handling of tuple names
     c6c8678 Revert "Revert ad15c2, which causes Windows seg-faults (Trac #8834)"
     f0af58d windows: Fix #8870
     59b9b06 Fix copy/paste error (#8937)
     ee13437 Test return value of clock_gettime() for errors.
     e81d110 Disable thin archive support on Windows
     d468cd3 Fix #8958.
     f772344 Add test case for #8950.
     8f831ec Require PatternSynonyms language flag when encountering a use of pattern synonym (#8961)
     d8d798b Small issue with signatures in a TH splice (fixes Trac #8932)
     bd79b98 Update long-out-of-date performance numbers on 32-bit
     ee481ff Ignore repeated loads of the same archive (#8942)
     ec3e949 Include LD_OPTS when building the RTS shared libs
     54e6555 Derive Typable for promoted data constructors (Trac #8950)
     b059dcc users_guide: note -XPatternSynonyms is required for use sites
     b30771d Clarify bits about role inference in users' guide.
     cbe59d8 Improve tracing slightly
     4dc9f98 Zonk the existential type variables in tcPatSynDecl
     17c9554 Improve documentation of GeneralisedNewtypeDeriving
     d2c4f97 Add comments & notes explaining the typing of pattern synonym definitions
     396648e Don't preprocess .s files
     848f595 Allow a longer demand signature than arity
     2c516c4 Refactor in worker/wrapper generation
     cc3ccf9 Test Trac #8963
     50bfd42 Improve error reporting for untouchable type variables
     f8e12e2 Fix #5435, adding new test config check_stdout.
     b4dd566 Suppress uniques to stop output wobbling (test for Trac #8958)
     b8132a9 Fix egregious blunder in the type flattener
     c269b7e Split off pattern synonym definition checking from pattern inversion
     c7498bb Fix #8641, creating directories when we have stubs.
     6782330 Update Haddock submodule reference.
     b7f51d6 Remove unused variable binding to fix validate
     dd3a6d2 Add source file for new test that checks that as-patterns are rejected in pattern synonym definitions
     7233638 Expected output of as-pattern test
     e0f47fe Store IfExtNames for PatSyn matchers and wrappers in interface file


More information about the ghc-commits mailing list