Skip to content
Snippets Groups Projects
  1. Oct 17, 2015
    • Ben Gamari's avatar
      Libdw: Add libdw-based stack unwinding · a6a3dabc
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This adds basic support to the RTS for DWARF-assisted unwinding of the
      Haskell and C stack via libdw. This only adds the infrastructure;
      consumers of this functionality will be introduced in future diffs.
      
      Currently we are carrying the initial register collection code in
      Libdw.c but this will eventually make its way upstream to libdw.
      
      Test Plan: See future patches
      
      Reviewers: Tarrasch, scpmw, austin, simonmar
      
      Reviewed By: austin, simonmar
      
      Subscribers: simonmar, thomie, erikd
      
      Differential Revision: https://phabricator.haskell.org/D1196
      
      GHC Trac Issues: #10656
      a6a3dabc
    • Ryan Scott's avatar
      Move Control.Monad.IO.Class to base from transformers · fff02548
      Ryan Scott authored
      See Trac #10773
      
      Remove Control.Monad.IO.Class from `transformers`. Updates
      `transformers` submodule.
      
      See Trac #10773
      
      Test Plan: ./validate
      
      Reviewers: ekmett, hvr, bgamari, austin
      
      Reviewed By: hvr, bgamari, austin
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1147
      
      GHC Trac Issues: #10773
      fff02548
    • Tamar Christina's avatar
      Silence the linker on Windows so tests pass · 603a369d
      Tamar Christina authored and Thomas Miedema's avatar Thomas Miedema committed
      Silence the unconditional debugBelch statements recently added to HEAD
      which on Windows cause debug information to always be printed.
      
      Differential Revision: https://phabricator.haskell.org/D1338
      603a369d
    • Thomas Miedema's avatar
      Build system: fix `make -j1` (#10973) · 3340fe01
      Thomas Miedema authored
      There are multiple hacks all over the build system to account for the
      fact that the ghc package uses different build subdirectories
      (stage1/stage2) than the other packages (dist/dist-install).
      
      One such hack filtered on 'ghc%', with the intention of filtering the
      ghc package only. After renaming bin-package-db to ghc-boot
      (d2f9972a, Phab:D1313, #10796), ghc-boot
      also got caught in the hack, which broke the build when running without
      parallelism.
      
      This patch replaces the before mentioned hack by a different one, such
      that filtering on 'ghc%' is no longer necessary. See Note [inconsistent
      distdirs].
      
      Reviewed by: austin
      
      Differential Revision: https://phabricator.haskell.org/D1333
      3340fe01
  2. Oct 16, 2015
  3. Oct 15, 2015
  4. Oct 14, 2015
    • Erik de Castro Lopo's avatar
      Fix GHCi on Arm (#10375). · 933adc0f
      Erik de Castro Lopo authored
      Arm has two instruction sets, Arm and Thumb, and an execution mode for each.
      Executing Arm code in Thumb mode or vice-versa will likely result in an
      Illegal instruction exception.
      
      Furthermore, Haskell code compiled via LLVM was generating Arm instructions
      while C code compiled via GCC was generating Thumb code by default. When
      these two object code types were being linked by the system linker, all was
      fine, because the system linker knows how to jump and call from one
      instruction set to the other.
      
      The first problem was with GHCi's object code loader which did not know
      about Thumb vs Arm. When loading an object file `StgCRun` would jump
      into the loaded object which could change the mode causing a crash after
      it returned. This was fixed by forcing all C code to generate Arm
      instructions by passing `-marm` to GCC.
      
      The second problem was the `mkJumpToAddr` function which was generating
      Thumb instructions. Changing that to generate Arm instructions instead
      results in a working GHCi on Arm.
      
      Test Plan: validate on x86_64 and arm
      
      Reviewers: bgamari, austin, hvr
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1323
      
      GHC Trac Issues: #10375
      933adc0f
    • Austin Seipp's avatar
      travis: use LLVM 3.7 · 77561617
      Austin Seipp authored
      
      Signed-off-by: default avatarAustin Seipp <austin@well-typed.com>
      77561617
  5. Oct 13, 2015
    • Erik de Castro Lopo's avatar
      Switch to LLVM version 3.7 · 29310b62
      Erik de Castro Lopo authored
      Before this commit, GHC only supported LLVM 3.6. Now it only supports
      LLVM 3.7 which was released in August 2015. LLVM version 3.6 and earlier
      do not work on AArch64/Arm64, but 3.7 does.
      
      Also:
      * Add CC_Ghc constructor to LlvmCallConvention.
      * Replace `maxSupportLlvmVersion`/`minSupportLlvmVersion` with
        a single `supportedLlvmVersion` variable.
      * Get `supportedLlvmVersion` from version specified in configure.ac.
      * Drop llvmVersion field from DynFlags (no longer needed because only
        one version is supported).
      
      Test Plan: Validate on x86_64 and arm
      
      Reviewers: bgamari, austin
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1320
      
      GHC Trac Issues: #10953
      29310b62
    • Matthew Farkas-Dyck's avatar
    • joeyadams's avatar
      base: Add forkOSWithUnmask · dec5cd40
      joeyadams authored
      Fixes #8010, according to the specified libraries proposal. [1]
      
      Also, some minor wordsmithing.
      
        [1] http://thread.gmane.org/gmane.comp.lang.haskell.libraries/22709
      
      
      
      Signed-off-by: default avatarAustin Seipp <austin@well-typed.com>
      dec5cd40
    • Ryan Scott's avatar
      docs: overhaul Derive{Functor,Foldable,Traversable} notes · e5bfd704
      Ryan Scott authored
      The previous users' guide documentation was too implementation-oriented. This
      attempts to make it more accessible to those who aren't familiar with how
      `-XDeriveFunctor` and friends work (and more importantly, what will not work
      when using them).
      
      Fixes #10831.
      
      Reviewed By: austin
      
      Differential Revision: https://phabricator.haskell.org/D1293
      
      GHC Trac Issues: #10831
      e5bfd704
    • Ömer Sinan Ağacan's avatar
      Fix incorrect import warnings when methods with identical names are imported · 1818b48e
      Ömer Sinan Ağacan authored
      Currently, GHC's warning generation code is assuming that a name (`RdrName`)
      can be imported at most once. This is a correct assumption, because 1) it's OK
      to import same names as long as we don't use any of them 2) when we use one of
      them, GHC generates an error because it doesn't disambiguate it automatically.
      
      But apparently the story is different with typeclass methods. If I import two
      methods with same names, it's OK to use them in typeclass instance
      declarations, because the context specifies which one to use. For example, this
      is OK (where modules A and B define typeclasses A and B, both with a function
      has),
      
          import A
          import B
      
          data Blah = Blah
      
          instance A Blah where
            has = Blah
      
          instance B Blah where
            has = Blah
      
      But GHC's warning generator is not taking this into account, and so if I change
      import list of this program to:
      
          import A (A (has))
          import B (B (has))
      
      GHC is printing these warnings:
      
          Main.hs:5:1: Warning:
              The import of ‘A.has’ from module ‘A’ is redundant
      
          Main.hs:6:1: Warning:
              The import of ‘B.has’ from module ‘B’ is redundant
      
      Why? Because warning generation code is _silently_ ignoring multiple symbols
      with same names.
      
      With this patch, GHC takes this into account. If there's only one name, then
      this patch reduces to the previous version, that is, it works exactly the same
      as current GHC (thanks goes to @quchen for realizing this).
      
      Reviewed By: austin
      
      Differential Revision: https://phabricator.haskell.org/D1257
      
      GHC Trac Issues: #10890
      1818b48e
    • Ryan Scott's avatar
      Make dataToQa aware of Data instances which use functions to implement toConstr · d2f9972a
      Ryan Scott authored
      Trac #10796 exposes a way to make `template-haskell`'s `dataToQa` function
      freak out if using a `Data` instance that produces a `Constr` (by means of
      `toConstr`) using a function name instead of a data constructor name. While
      such `Data` instances are somewhat questionable, they are nevertheless present
      in popular libraries (e.g., `containers`), so we can at least make `dataToQa`
      aware of their existence.
      
      In order to properly distinguish strings which represent variables (as opposed
      to data constructors), it was necessary to move functionality from `Lexeme` (in
      `ghc`) to `GHC.Lexeme` in a new `ghc-boot` library (which was previously named
      `bin-package-db`).
      
      Reviewed By: goldfire, thomie
      
      Differential Revision: https://phabricator.haskell.org/D1313
      
      GHC Trac Issues: #10796
      d2f9972a
    • bernalex's avatar
      Slightly wibble TcSimplify documentation · 94ef79a7
      bernalex authored
      
      Add some commas, fix some typos, etc.
      
      Signed-off-by: default avatarAlexander Berntsen <alexander@plaimi.net>
      
      Reviewed By: austin
      
      Differential Revision: https://phabricator.haskell.org/D1321
      94ef79a7
    • Austin Seipp's avatar
      testsuite: attempt fixing T10935 output · 330ba6ad
      Austin Seipp authored
      
      This fallout was caused by f8fbf385 (see #10935), and looks easy
      enough, but admittedly I just tried patching the output, so we're doing it
      live.
      
      Signed-off-by: default avatarAustin Seipp <austin@well-typed.com>
      330ba6ad
    • Andrew Farmer's avatar
      Don't inline/apply other rules when simplifying a rule RHS. · dcc34287
      Andrew Farmer authored
      HERMIT users depend on RULES to specify equational properties. 7.10.2
      performed both inlining and simplification in both sides of the rules, meaning
      they can't really be used for this. This breaks most HERMIT use cases.  A
      separate commit already disabled this for the LHS of rules. This does so for
      the RHS.
      
      See Trac #10829 for nofib results.
      
      Reviewed By: austin, bgamari, simonpj
      
      Differential Revision: https://phabricator.haskell.org/D1246
      
      GHC Trac Issues: #10829
      dcc34287
  6. Oct 12, 2015
    • Simon Peyton Jones's avatar
      Reinstate monomorphism-restriction warnings · f8fbf385
      Simon Peyton Jones authored
      This patch is driven by Trac #10935, and reinstates the
      -fwarn-monomorphism-restriction warning.  It was first lost in 2010:
      d2ce0f52 "Super-monster patch implementing the new typechecker -- at
      last"
      
      I think the existing documentation is accurate; it is not even
      turned on by -Wall.
      
      I added one test.
      f8fbf385
    • Simon Peyton Jones's avatar
      Test Trac #10931 · 6b7bad92
      Simon Peyton Jones authored
      6b7bad92
    • Herbert Valerio Riedel's avatar
      base: MRP-refactoring of AMP instances · e737a512
      Herbert Valerio Riedel authored
      This refactors `(>>)`/`(*>)`/`return`/`pure` methods into normal form.
      
      The redundant explicit `return` method definitions are dropped
      altogether.
      
      The explicit `(>>) = (*>)` definitions can't be removed yet, as
      the default implementation of `(>>)` is still in terms of `(*>)`
      (even though that should have been changed according to the AMP but
      wasn't -- see note in GHC.Base for details why this had to be postponed)
      
      A nofib comparision shows this refactoring to result in minor runtime
      improvements (unless those are within normal measurement fluctuations):
      
              Program           Size    Allocs   Runtime   Elapsed  TotalMem
        -------------------------------------------------------------------------
                  Min          -0.0%     -0.0%     -1.6%     -3.9%     -1.1%
                  Max          -0.0%     +0.0%     +0.5%     +0.5%      0.0%
        Geometric Mean         -0.0%     -0.0%     -0.4%     -0.5%     -0.0%
      
      Full `nofib` report at https://phabricator.haskell.org/P68
      
      Reviewers: quchen, alanz, austin, #core_libraries_committee, bgamari
      
      Reviewed By: bgamari
      
      Differential Revision: https://phabricator.haskell.org/D1316
      e737a512
    • Erik de Castro Lopo's avatar
      PPC: Fix right shift by 32 bits #10870 · 4bd58c17
      Erik de Castro Lopo authored
      Summary: Test included.
      
      Test Plan: Run test T10870.hs on X86/X86_64/Arm/Arm64 etc
      
      Reviewers: bgamari, nomeata, austin
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1322
      
      GHC Trac Issues: #10870
      4bd58c17
    • Erik de Castro Lopo's avatar
      f0023409
  7. Oct 10, 2015
Loading