Skip to content
Snippets Groups Projects
  1. Nov 17, 2016
    • Edward Z. Yang's avatar
      Remove fancy shadowing logic; always override in package database order. · b5b9cf3a
      Edward Z. Yang authored
      
      This is a stopgap fix for GHC 8.0 bug #12485: in particular,
      it relaxes need for -package-db flags to be given in
      dependency order.  The trade-off is that we are a lot more
      unsafe when there are packages with duplicate 'id's in
      the database stack: the new code will not do an ABI compatibility
      check: if two packages have the same 'id', they are assumed to
      be ABI compatible.  If this is not true, GHC may build
      segfaulting executables.
      
      Missing test updates, but I'm putting it up so people can
      take a look.
      
      In GHC 8.2, we'll record ABIs for all dependencies, allowing
      GHC to make better decisions about shadowing.
      
      Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>
      
      Test Plan: validate
      
      Reviewers: austin, niteria, bgamari, simonmar
      
      Reviewed By: simonmar
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2613
      
      GHC Trac Issues: #12485
      ghc-8.0.2-rc1
      b5b9cf3a
    • Facundo Domínguez's avatar
      Have reify work for local variables with functional dependencies. · e7c12cda
      Facundo Domínguez authored and Ben Gamari's avatar Ben Gamari committed
      It turned out that finalizers were run too early and information
      resulting from simplifying constraints was not available.
      
      This patch runs finalizers after a first call to simplifyTop, and
      then calls simplifyTop a second time to deal with constraints
      that could result from running the finalizers.
      
      Fixes T12777
      
      Test Plan: ./validate
      
      Reviewers: goldfire, simonpj, bgamari, austin
      
      Reviewed By: simonpj
      
      Subscribers: mpickering, mboes, thomie
      
      Differential Revision: https://phabricator.haskell.org/D2659
      
      GHC Trac Issues: #12777
      
      (cherry picked from commit 231a3ae1)
      e7c12cda
  2. Nov 16, 2016
  3. Nov 15, 2016
  4. Nov 14, 2016
  5. Nov 11, 2016
    • Ben Gamari's avatar
      ghc-pkg: Munge dynamic library directories · e7017ca8
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Otherwise we end up looking in the wrong place for dynamic libraries on
      Windows. This addresses a regression introduced by D2611. See #12479.
      
      Test Plan: validate across platforms
      
      Reviewers: austin
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2640
      
      GHC Trac Issues: #12479
      
      (cherry picked from commit 75e69edb498511cf2b28dec4e14e6d11232f3e32)
      e7017ca8
    • David Feuer's avatar
      Read parentheses better · cca8ceec
      David Feuer authored
      Instead of pulling a token and looking for `'('` or `')'`,
      just look for the character itself. This prevents us from
      lexing every single item twice, once to see if it's a
      left parenthesis and once to actually parse it.
      
      Partially fixes #12665
      
      Test Plan: Validate
      
      Reviewers: austin, bgamari, hvr
      
      Reviewed By: bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2623
      
      GHC Trac Issues: #12665
      cca8ceec
    • Ben Gamari's avatar
      testsuite: Fix framework failure in T12771 · 6060964c
      Ben Gamari authored
      Extraneous extra_files
      6060964c
    • Ben Gamari's avatar
      testsuite: Accept T12227 allocations · d5518f72
      Ben Gamari authored
      Sadly I was not able to track down the source of this but there is
      really no more time. Looks like we'll just need to accept it.
      d5518f72
    • Ben Gamari's avatar
      Pass -no-pie to GCC · fefe02c0
      Ben Gamari authored
      Certain distributions (e.g. Debian and Ubuntu) have enabled PIE be
      default in their GCC packaging. This breaks our abuse of GCC as a linker
      which requires that we pass -Wl,-r, which is incompatible with
      PIE (since the former implies that we are generating a relocatable
      object file and the latter an executable).
      
      This is a second attempt at D2691. This attempt constrasts with D2691 in that
      it preserves the "does gcc support -no-pie" flag in settings, allowing this to
      be reconfigured by `configure` during installation of a binary distribution.
      Thanks for @rwbarton for drawing attention to this issue.
      
      Test Plan: Validate
      
      Reviewers: austin, hvr, erikd
      
      Reviewed By: erikd
      
      Subscribers: thomie, rwbarton, erikd
      
      Differential Revision: https://phabricator.haskell.org/D2693
      
      GHC Trac Issues: #12759
      fefe02c0
    • Ben Gamari's avatar
      Revert "Pass --no-pie to GCC" · 3da461d9
      Ben Gamari authored
      This reverts commit 60c299a2. We really
      want to be able to change this in the binary distribution `configure`
      script. Trying again in D2693.
      3da461d9
  6. Nov 10, 2016
    • Ben Gamari's avatar
      Pass --no-pie to GCC · 60c299a2
      Ben Gamari authored
      Certain distributions (e.g. Debian and Ubuntu) have enabled PIE be
      default in their GCC packaging. This breaks our abuse of GCC as a linker
      which requires that we pass -Wl,-r, which is incompatible with
      PIE (since the former implies that we are generating a relocatable
      object file and the latter an executable).
      60c299a2
  7. Nov 07, 2016
    • Ryan Scott's avatar
      Add test for #12788 · b72b7c8a
      Ryan Scott authored
      Commit bce99086 (#12584) fixed #12788. Let's
      add a test to make sure it stays fixed.
      
      (cherry picked from commit ec22bacd)
      b72b7c8a
    • Ben Gamari's avatar
      configure: Pass HC_OPTS_STAGEx to build system · 891ffe90
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: Try `./configure HC_OPTS_STAGE0=-foobar` and watch it fail
      
      Reviewers: austin, hvr
      
      Subscribers: thomie, erikd
      
      Differential Revision: https://phabricator.haskell.org/D2674
      
      (cherry picked from commit c8e79c03)
      891ffe90
    • Ben Gamari's avatar
      build system: Include CONF_LD_LINKER_OPTS in ALL_LD_OPTS · 7bd5dd09
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This ensures that artifacts built with build-prog see these options.
      Also spruce up comments.
      
      Test Plan: Carefully read it.
      
      Reviewers: austin, hvr, erikd
      
      Reviewed By: erikd
      
      Subscribers: thomie, erikd
      
      Differential Revision: https://phabricator.haskell.org/D2673
      
      (cherry picked from commit e2a9b529a8b06e2dace8c2b4c58710cf5e57ef03)
      7bd5dd09
    • Ben Gamari's avatar
      ghc-cabal: Use correct name of linker flags env variable · 3a0532a8
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Currently passing the `CONF_LD_LINKER_OPTS_STAGE0` environment
      variable to `configure` is broken due to this naming inconsistency.
      
      Test Plan: Try passing `CONF_LD_LINKER_OPTS_STAGE0` to `configure`.
      Look at resulting stage0 ghc invocation.
      
      Reviewers: austin
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2672
      
      (cherry picked from commit 97505ad7b23f5e43e1e1a69c159c2c7054f600e7)
      3a0532a8
    • Tamar Christina's avatar
      Align GHCi's library search order more closely with LDs · 95b6affc
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      Summary:
      Given a static library and an import library in the same folder. e.g.
      
      ```
      libfoo.a
      libfoo.dll.a
      ```
      
      running `ghci -lfoo` we should prefer the import library `libfoo.dll.a`
      over `libfoo.a` because we prefer having to just load the DLL.
      And not having to do any linking.
      
      This also more closely emulated the behaviour of LD, which has a search order of
      
      ```
      libxxx.dll.a
      xxx.dll.a
      libxxx.a
      cygxxx.dll (*)
      libxxx.dll
      xxx.dll
      ```
      
      Test Plan: ./validate
      
      Reviewers: RyanGlScott, austin, hvr, bgamari, erikd, simonmar
      
      Reviewed By: RyanGlScott
      
      Subscribers: thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D2651
      
      GHC Trac Issues: #12771
      
      (cherry picked from commit 795be0ea)
      95b6affc
    • Ryan Scott's avatar
      Describe symptoms of (and the cure for) #12768 in 8.0.2 release notes · 411bd2df
      Ryan Scott authored
      GHC 8.0.2 introduced a bugfix involving GeneralizedNewtypeDeriving in
      96d45145. This made typechecking of
      GND-produced code a bit stricter, and an unfortunate side effect of this was
      that there were a couple of corner-case programs that stopped compiling
      when transitioning from GHC 8.0.1 to 8.0.2.
      
      Since the number of affected programs seems quite small, and since the fix
      is so straightforward, we opt to simply note this discrepancy in the 8.0.2
      release notes.
      
      Resolves #12768.
      
      (cherry picked from commit ead83db8)
      411bd2df
    • Simon Peyton Jones's avatar
      Fundeps work even for unary type classes · 8719d871
      Simon Peyton Jones authored
      The functional-dependency improvement functions,
         improveFromAnother
         improveFromInstEnv
      had a side-condition that said the type class has to have at
      least two arguments.  But not so, as Trac #12763 shows:
      
         class C a | -> a where ...
      
      is perfectly legal, albeit a bit of a corner case.
      
      (cherry picked from commit 801c2637)
      8719d871
    • Ryan Scott's avatar
      Update 8.0.2 release notes for #12784 · 2591a4b9
      Ryan Scott authored
      Summary:
      The fix for #12220 exposed some ill-typed programs which passed the typechecker
      in GHC 8.0.1 but now fail to typecheck in GHC 8.0.2. It's a bit difficult to
      characterize what exactly triggers this bug, but we at least have a minimal
      example and a simple fix to illustrate the problem and solution, so let's
      add that the the 8.0.2 release notes to advertise this change.
      
      Resolves #12784.
      
      Reviewers: rwbarton, austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2682
      
      GHC Trac Issues: #12784
      
      (cherry picked from commit 2e8463b2)
      2591a4b9
    • Simon Peyton Jones's avatar
      Fix Trac #12797: approximateWC · 28c62bb5
      Simon Peyton Jones authored
      This patch makes approximateWC a bit more gung-ho when called
      from the defaulting code.  See Note [ApproximateWC], item (1).
      
      (cherry picked from commit 13508bad)
      28c62bb5
    • Ryan Scott's avatar
      Add test for #12732 · 4227f3ea
      Ryan Scott authored
      (cherry picked from commit 60343a41)
      4227f3ea
    • Simon Peyton Jones's avatar
      Fix the in-scope set for extendTvSubstWithClone · cc3a9504
      Simon Peyton Jones authored
      We'd forgotten the variables free in the kind.
      
      Ditto extendCvSubstWithClone
      
      (cherry picked from commit 15fc5281)
      cc3a9504
    • Matthew Pickering's avatar
      Refine ASSERT in buildPatSyn for the nullary case. · c33aad1e
      Matthew Pickering authored and Ben Gamari's avatar Ben Gamari committed
      For a nullary pattern synonym we add an extra void argument to the
      matcher in order to preserve laziness. The check in buildPatSyn
      wasn't aware of this special case which was causing the assertion to
      fail.
      
      Reviewers: austin, simonpj, bgamari
      
      Reviewed By: simonpj, bgamari
      
      Subscribers: simonpj, thomie
      
      Differential Revision: https://phabricator.haskell.org/D2624
      
      GHC Trac Issues: #12746
      
      (cherry picked from commit 23143f60)
      c33aad1e
    • Simon Marlow's avatar
      Omit unnecessary linker flags · 5c91d076
      Simon Marlow authored and Ben Gamari's avatar Ben Gamari committed
      This omits -L and -l flags from the linker command line that shouldn't
      be necessary because GHC will already add them via the -package-id
      flags we pass.
      
      This also reverts part of 90538d86
      that rearranges the linker command line and causes some knock-on
      problems (see D2618).
      
      Test Plan: validate (need to validate on Windows too)
      
      Reviewers: Phyx, bgamari, niteria, austin, erikd
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2639
      
      GHC Trac Issues: #12738
      
      (cherry picked from commit a977c965)
      5c91d076
  8. Nov 04, 2016
    • Simon Marlow's avatar
      Fix failure in setnumcapabilities001 (#12728) · 2722cd55
      Simon Marlow authored and Ben Gamari's avatar Ben Gamari committed
      The value of enabled_capabilities can change across a call to
      requestSync(), and we were erroneously using an old value, causing
      things to go wrong later.  It manifested as an assertion failure, I'm
      not sure whether there are worse consequences or not, but we should
      get this fix into 8.0.2 anyway.
      
      The failure didn't happen for me because it only shows up on machines
      with fewer than 4 processors, due to the new logic to enable -qn
      automatically.  I've bumped the test parameter 8 to make it more
      likely to exercise that code.
      
      Test Plan: Ran setnumcapabilities001 many times
      
      Reviewers: niteria, austin, erikd, rwbarton, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2617
      
      GHC Trac Issues: #12728
      
      (cherry picked from commit acc98510)
      2722cd55
  9. Nov 01, 2016
  10. Oct 22, 2016
    • Duncan Coutts's avatar
      Add and use a new dynamic-library-dirs field in the ghc-pkg info · 9448e627
      Duncan Coutts authored and Ben Gamari's avatar Ben Gamari committed
      Build systems / package managers want to be able to control the file
      layout of installed libraries. In general they may want/need to be able
      to put the static libraries and dynamic libraries in different places.
      The ghc-pkg library regisrtation needs to be able to handle this.
      
      This is already possible in principle by listing both a static lib dir
      and a dynamic lib dir in the library-dirs field (indeed some previous
      versions of Cabal did this for shared libs on ELF platforms).
      
      The downside of listing both dirs is twofold. There is a lack of
      precision, if we're not careful with naming then we could end up
      picking up the wrong library. The more immediate problem however is
      that if we list both directories then both directories get included
      into the ELF and Mach-O shared object runtime search paths. On ELF this
      merely slows down loading of shared libs (affecting prog startup time).
      On the latest OSX versions this provokes a much more serious problem:
      that there is a rather low limit on the total size of the section
      containing the runtime search path (and lib names and related) and thus
      listing any unnecessary directories wastes the limited space.
      
      So the solution in this patch is fairly straightforward: split the
      static and dynamic library search paths in the ghc-pkg db and its use
      within ghc. This is a traditional solution: pkg-config has the same
      static / dynamic split (though it describes in in terms of private and
      public, but it translates into different behaviour for static and
      dynamic linking).
      
      Indeed it would make perfect sense to also have a static/dynamic split
      for the list of the libraries to use i.e. to have dynamic variants of
      the hs-libraries and extra-libraries fields. These are not immediately
      required so this patch does not add it, but it is a reasonable
      direction to follow.
      
      To handle compatibility, if the new dynamic-library-dirs field is not
      specified then its value is taken from the library-dirs field.
      
      Contains Cabal submodule update.
      
      Test Plan:
      Run ./validate
      
      Get christiaanb and carter to test it on OSX Sierra, in combination
      with Cabal/cabal-install changes to the default file layout for
      libraries.
      
      Reviewers: carter, bgamari, hvr, austin, christiaanb
      
      Subscribers: thomie, Phyx, ezyang
      
      Differential Revision: https://phabricator.haskell.org/D2625
      
      GHC Trac Issues: #12479
      9448e627
    • Simon Peyton Jones's avatar
      Test for newtype with unboxed argument · 4c8aab8f
      Simon Peyton Jones authored
      Newtypes cannot (currently) have an unboxed argument type.
      But Trac #12729 showed that this was only being checked for
      newtypes in H98 syntax; in GADT snytax they were let through.
      
      This patch moves the test to checkValidDataCon, where it properly
      belongs.
      
      (cherry picked from commit 1f09c16c)
      4c8aab8f
  11. Oct 18, 2016
    • Ryan Scott's avatar
      Add test for #12411 · d84a824c
      Ryan Scott authored
      The fix for #12584 also fixed the problem in #12411. Let's add a test to ensure
      that it stays fixed.
      
      (cherry picked from commit 184d7cb8)
      d84a824c
    • Ryan Scott's avatar
      Fix Show derivation in the presence of RebindableSyntax/OverloadedStrings · d7a1f682
      Ryan Scott authored
      Summary:
      To fix this issue, we simply disable `RebindableSyntax` whenever we rename
      the code generated from a deriving clause.
      
      Fixes #12688.
      
      Test Plan: make test TEST=T12688
      
      Reviewers: simonpj, austin, bgamari
      
      Reviewed By: simonpj, bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2591
      
      GHC Trac Issues: #12688
      
      (cherry picked from commit b501709e)
      d7a1f682
    • Simon Peyton Jones's avatar
      Fix shadowing in mkWwBodies · 8ab454d9
      Simon Peyton Jones authored
      This bug, exposed by Trac #12562 was very obscure, and has been
      lurking for a long time.  What happened was that, in the
      worker/wrapper split
      
        a tyvar binder for a worker function
        accidentally shadowed an in-scope term variable
        that was mentioned in the body of the function
      
      It's jolly hard to provoke, so I have not even attempted to make
      a test case.  There's a Note [Freshen WW arguments] to explain.
      
      Interestingly, fixing the bug (which meant fresher type variables)
      revealed a second lurking bug: I'd failed to apply the substitution to
      the coercion in the second last case of mkWWArgs, which introduces a
      Cast.
      
      (cherry picked from commit 692c8df0)
      8ab454d9
Loading