Skip to content
Snippets Groups Projects
  1. Jun 18, 2017
  2. Jun 17, 2017
    • Tamar Christina's avatar
      Remove the Windows GCC driver. · d6cecde5
      Tamar Christina authored
      Summary:
      This patch drops the GCC driver and instead moves
      the only remaining path that we need to keep for
      backwards compatibility to the settings file.
      
      It also generalizes the code that expands `$TopDir`
      so it can expand it within any location in the string
      and also changes it so `$TopDir` is expanded only
      after the words call because `$TopDir` can contains
      spaces which would be horribly broken.
      
      Test Plan: ./validate
      
      Reviewers: austin, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, erikd
      
      GHC Trac Issues: #13709
      
      Differential Revision: https://phabricator.haskell.org/D3592
      d6cecde5
  3. Jun 16, 2017
    • Tamar Christina's avatar
      Provide way to build using existing C compiler on Windows. · fda094d0
      Tamar Christina authored
      Summary:
      There are various distros that build GHC using their own C compilers
      such as MSYS2. Currently they have to patch the build scripts everytime.
      
      This patch provides the configure argument `--enable-distro-toolchain`
      which allows one to build using any C compiler on the path.
      
      This is also useful for testing new versions of GCC.
      
      Test Plan:
      ./configure --enable-distro-toolchain && make - && make THREADS=9 test
      ./validate
      
      Reviewers: austin, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, erikd, #ghc_windows_task_force
      
      GHC Trac Issues: #13792
      
      Differential Revision: https://phabricator.haskell.org/D3637
      fda094d0
    • Simon Peyton Jones's avatar
      Fix the treatment of 'closed' definitions · dc8e6861
      Simon Peyton Jones authored
      The IdBindingInfo field of ATcId serves two purposes
      
      - to control generalisation when we have -XMonoLocalBinds
      - to check for floatability when dealing with (static e)
      
      These are related, but not the same, and they'd becomme confused.
      Trac #13804 showed this up via an example like this:
      
        f periph = let sr :: forall a. [a] -> [a]
                       sr = if periph then reverse else id
      
                       sr2 = sr
                       -- The question: is sr2 generalised?
                       -- It should be, because sr has a type sig
                       -- even though it has periph free
                   in
                   (sr2 [True], sr2 "c")
      
      Here sr2 should be generalised, despite the free var 'periph'
      in 'sr' because 'sr' has a closed type signature.
      
      I documented all this very carefully this time, in TcRnTypes:
        Note [Meaning of IdBindingInfo]
        Note [Bindings with closed types: ClosedTypeId]
      dc8e6861
    • Ben Gamari's avatar
      base: Validate input in setNumCapabilities · 98494031
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: validate
      
      Reviewers: austin, hvr, erikd, simonmar
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13832
      
      Differential Revision: https://phabricator.haskell.org/D3652
      98494031
  4. Jun 14, 2017
  5. Jun 13, 2017
  6. Jun 12, 2017
  7. Jun 08, 2017
    • SantiM's avatar
      Correct optimization flags documentation · b2b41601
      SantiM authored
      In a previous change (commit 4fd6207e),
      the users guide was moved from XML to the RST format. This process
      introduced a typo: "No -O*-type option specified:" was changed to "-O*"
      (which is not correct). This change fixes it.
      
      See result in: https://prnt.sc/fh332n
      
      Fixes ticket #13756.
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13756
      
      Differential Revision: https://phabricator.haskell.org/D3631
      b2b41601
    • Douglas Wilson's avatar
      Don't pass -dcore-lint to haddock in Haddock.mk · b10d3f36
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      This fixes the regressions in the haddock performance tests introduced
      in c9eb4385.
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13789
      
      Differential Revision: https://phabricator.haskell.org/D3629
      b10d3f36
    • Douglas Wilson's avatar
      Add tcRnGetNameToInstancesIndex · 56ef5444
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      This function in tcRnDriver, retrieves an index by name of all Class and
      Family instances in the current environment.
      
      This is to be used by haddock which currently looks up instances for
      each name, which looks at every instance for every lookup.
      
      Using this function instead of tcRnGetInfo, the haddock.base performance
      test improves by 10%
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: alexbiehl, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3624
      56ef5444
    • Douglas Wilson's avatar
      Refactor temp files cleanup · 3ee3822c
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      Remove filesToNotIntermediateClean from DynFlags, create a data type
      FilesToClean, and change filesToClean in DynFlags to be a FilesToClean.
      
      Modify SysTools.newTempName and the Temporary constructor of
      PipelineMonad.PipelineOutput to take a TempFileLifetime, which specifies
      whether a temp file should live until the end of GhcMonad.withSession,
      or until the next time cleanIntermediateTempFiles is called.
      
      These changes allow the cleaning of intermediate files in GhcMake to be
      much more efficient.
      
      HscTypes.hptObjs is removed as it is no longer used.
      
      A new performance test T13701 is added, which passes both with and
      without -keep-tmp-files.  The test fails by 25% without the patch, and
      passes when -keep-tmp-files is added.
      
      Note that there are still at two hotspots caused by
      algorithms quadratic in the number of modules, however neither of them
      allocate. They are:
      
      * DriverPipeline.compileOne'.needsLinker
      * GhcMake.getModLoop
      
      DriverPipeline.compileOne'.needsLinker is changed slightly to improve
      the situation.
      
      I don't like adding these Types to DynFlags, but they need to be seen by
      Dynflags, SysTools and PipelineMonad. The alternative seems to be to
      create a new module.
      
      Reviewers: austin, hvr, bgamari, dfeuer, niteria, simonmar, erikd
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13701
      
      Differential Revision: https://phabricator.haskell.org/D3620
      3ee3822c
    • Moritz Angermann's avatar
      Check target libtool · cd8f4b99
      Moritz Angermann authored and Ben Gamari's avatar Ben Gamari committed
      This will qualify the libtool with the target, e.g.
      arch-vendor-os-libtool, instead of simply using libtool.
      
      Reviewers: austin, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: Ericson2314, ryantrinkle, rwbarton, thomie, erikd
      
      Differential Revision: https://phabricator.haskell.org/D3617
      cd8f4b99
    • Moritz Angermann's avatar
      [linker] fix armv7 & add aarch64 · 1c83fd81
      Moritz Angermann authored and Ben Gamari's avatar Ben Gamari committed
      This adds Global Offset Table logic, as well as PLT like logic for armv7
      and aarch64; which replaces the preexisting symbolExtras logic, by
      placing the PLT tables next to the separtely loaded sections. This is
      needed to ensure that the symbol stubs are in range.
      
      Reviewers: bgamari, austin, erikd, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: Ericson2314, ryantrinkle, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3448
      1c83fd81
    • Ben Gamari's avatar
      testsuite: Add performance test, Naperian · 7bb2aa00
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This is a module contributed by Austin Seipp which is fairly minimal
      (albeit requiring vector) but is still representative of contemporary
      Haskell.
      
      Reviewers: austin
      
      Subscribers: dfeuer, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3596
      7bb2aa00
    • Ben Gamari's avatar
      Bump nofib submodule · ffd948e2
      Ben Gamari authored
      ffd948e2
    • Ben Gamari's avatar
      Revert "Make LLVM output robust to -dead_strip on mach-o platforms" · 1c76dd85
      Ben Gamari authored
      This reverts commit 667abf17.
      1c76dd85
    • Ben Gamari's avatar
      Linker: Fix whitespace · 3e8ab7c6
      Ben Gamari authored
      [skip ci]
      3e8ab7c6
    • Simon Marlow's avatar
      Fix a lost-wakeup bug in BLACKHOLE handling (#13751) · 59847290
      Simon Marlow authored
      Summary:
      The problem occurred when
      * Threads A & B evaluate the same thunk
      * Thread A context-switches, so the thunk gets blackholed
      * Thread C enters the blackhole, creates a BLOCKING_QUEUE attached to
        the blackhole and thread A's `tso->bq` queue
      * Thread B updates the blackhole with a value, overwriting the BLOCKING_QUEUE
      * We GC, replacing A's update frame with stg_enter_checkbh
      * Throw an exception in A, which ignores the stg_enter_checkbh frame
      
      Now we have C blocked on A's tso->bq queue, but we forgot to check the
      queue because the stg_enter_checkbh frame has been thrown away by the
      exception.
      
      The solution and alternative designs are discussed in Note [upd-black-hole].
      
      This also exposed a bug in the interpreter, whereby we were sometimes
      context-switching without calling `threadPaused()`.  I've fixed this
      and added some Notes.
      
      Test Plan:
      * `cd testsuite/tests/concurrent && make slow`
      * validate
      
      Reviewers: niteria, bgamari, austin, erikd
      
      Reviewed By: erikd
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13751
      
      Differential Revision: https://phabricator.haskell.org/D3630
      59847290
    • Tamar Christina's avatar
      Fix slash escaping in cwrapper.c · bca56bd0
      Tamar Christina authored
      Summary: Escape `\` in paths on Windows in `cwapper.c` when we re-output the paths.
      
      Test Plan: ./validate
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13666
      
      Differential Revision: https://phabricator.haskell.org/D3628
      bca56bd0
  8. Jun 07, 2017
    • Simon Peyton Jones's avatar
      Test Trac #13750 · ef07010c
      Simon Peyton Jones authored
      ef07010c
    • Simon Peyton Jones's avatar
      Stop the specialiser generating loopy code · 2b74bd9d
      Simon Peyton Jones authored
      This patch fixes a bad bug in the specialiser, which showed up as
      Trac #13429.  When specialising an imported DFun, the specialiser could
      generate a recusive loop where none existed in the original program.
      
      It's all rather tricky, and I've documented it at some length in
         Note [Avoiding loops]
      
      We'd encoutered exactly this before (Trac #3591) but I had failed
      to realise that the very same thing could happen for /imported/
      DFuns.
      
      I did quite a bit of refactoring.
      
      The compiler seems to get a tiny bit faster on
         deriving/perf/T10858
      but almost all the gain had occurred before now; this
      patch just pushed it over the line.
      2b74bd9d
    • Simon Peyton Jones's avatar
      Spelling typos · 92a4f908
      Simon Peyton Jones authored
      92a4f908
  9. Jun 06, 2017
    • Gabor Greif's avatar
      Typo in output of remote slave startup [merge cand] · e77b9a20
      Gabor Greif authored
      The output is not being checked in the test suite.
      However other tools may check it for obtaining the status
      of the remote slave.
      
      So I'd suggest to merge this to 8.2 branch, in order to not
      fragment the tooling's checks.
      e77b9a20
  10. Jun 05, 2017
    • Alan Zimmerman's avatar
      Udate hsSyn AST to use Trees that Grow · 8e6ec0fa
      Alan Zimmerman authored
      Summary:
      See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow
      
      This commit prepares the ground for a full extensible AST, by replacing the type
      parameter for the hsSyn data types with a set of indices into type families,
      
          data GhcPs -- ^ Index for GHC parser output
          data GhcRn -- ^ Index for GHC renamer output
          data GhcTc -- ^ Index for GHC typechecker output
      
      These are now used instead of `RdrName`, `Name` and `Id`/`TcId`/`Var`
      
      Where the original name type is required in a polymorphic context, this is
      accessible via the IdP type family, defined as
      
          type family IdP p
          type instance IdP GhcPs = RdrName
          type instance IdP GhcRn = Name
          type instance IdP GhcTc = Id
      
      These types are declared in the new 'hsSyn/HsExtension.hs' module.
      
      To gain a better understanding of the extension mechanism, it has been applied
      to `HsLit` only, also replacing the `SourceText` fields in them with extension
      types.
      
      To preserve extension generality, a type class is introduced to capture the
      `SourceText` interface, which must be honoured by all of the extension points
      which originally had a `SourceText`.  The class is defined as
      
          class HasSourceText a where
            -- Provide setters to mimic existing constructors
            noSourceText  :: a
            sourceText    :: String -> a
      
            setSourceText :: SourceText -> a
            getSourceText :: a -> SourceText
      
      And the constraint is captured in `SourceTextX`, which is a constraint type
      listing all the extension points that make use of the class.
      
      Updating Haddock submodule to match.
      
      Test Plan: ./validate
      
      Reviewers: simonpj, shayan-najd, goldfire, austin, bgamari
      
      Subscribers: rwbarton, thomie, mpickering
      
      Differential Revision: https://phabricator.haskell.org/D3609
      8e6ec0fa
    • Douglas Wilson's avatar
      Desugar modules compiled with -fno-code · c9eb4385
      Douglas Wilson authored
      Previously modules with hscTarget == HscNothing were not desugared.
      This patch changes behavior so that all modules HsSrcFile Modules except GHC.Prim
      are desugared. Modules with hscTarget == HscNothing are not simplified.
      
      Warnings and errors produced by the desugarer will now be produced when
      compiling with -fno-code.
      
      HscMain.finishTypecheckingOnly is removed, HscMain.hscIncrementalCompile is
      simplified a bit, and HscMain.finish takes in the removed logic. I think this
      is easier to follow.
      
      Updates haddock submodule.
      
      Tests T8101, T8101b, T10600 are no longer expect_broken.
      
      Reviewers: ezyang, austin, bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #10600
      
      Differential Revision: https://phabricator.haskell.org/D3542
      c9eb4385
    • Simon Peyton Jones's avatar
      Make the MR warning more accurage · a65dfea5
      Simon Peyton Jones authored
      Trac #13785 showed that we were emitting monomorphism warnings
      when we shouldn't.  The fix turned out to be simple.
      
      In fact test T10935 then turned out to be another example of
      the over-noisy warning so I changed the test slightly.
      a65dfea5
    • Simon Peyton Jones's avatar
      Test Trac #13784 · 6597f084
      Simon Peyton Jones authored
      6597f084
  11. Jun 02, 2017
    • Ben Gamari's avatar
      ghc.mk: Ensure that ghc-pkg path is quoted · ff363bd7
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Otherwise this will fail if the prefix path contains spaces. Thanks to
      marinelli for pointing this out.
      
      Test Plan: Validate
      
      Reviewers: austin
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3604
      ff363bd7
    • Ryan Scott's avatar
      Use lengthIs and friends in more places · a786b136
      Ryan Scott authored
      While investigating #12545, I discovered several places in the code
      that performed length-checks like so:
      
      ```
      length ts == 4
      ```
      
      This is not ideal, since the length of `ts` could be much longer than 4,
      and we'd be doing way more work than necessary! There are already a slew
      of helper functions in `Util` such as `lengthIs` that are designed to do
      this efficiently, so I found every place where they ought to be used and
      did just that. I also defined a couple more utility functions for list
      length that were common patterns (e.g., `ltLength`).
      
      Test Plan: ./validate
      
      Reviewers: austin, hvr, goldfire, bgamari, simonmar
      
      Reviewed By: bgamari, simonmar
      
      Subscribers: goldfire, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3622
      a786b136
Loading