Skip to content
Snippets Groups Projects
  1. Oct 08, 2016
  2. Oct 07, 2016
  3. Oct 06, 2016
    • Edward Z. Yang's avatar
    • Joachim Breitner's avatar
      Remove dead code “mkHsConApp” · 57a207ca
      Joachim Breitner authored
      Differential Revision: https://phabricator.haskell.org/D2574
      57a207ca
    • Joachim Breitner's avatar
      RegAlloc: Make some pattern matched complete · a2bedb5c
      Joachim Breitner authored
      these actually are complete, but due to the use of pattern guards, the
      compiler does not see that. Refactor the code that it does.
      
      Differential Revision: https://phabricator.haskell.org/D2574
      a2bedb5c
    • Ryan Scott's avatar
      Refactor TcDeriv and TcGenDeriv · 4a03012a
      Ryan Scott authored
      Summary:
      Keeping a promise I made to Simon to clean up these modules.
      
      This change splits up the massive `TcDeriv` and `TcGenDeriv` modules into
      somewhat more manageable pieces. The new modules are:
      
      * `TcGenFunctor`: This contains the deriving machinery for `Functor`,
        `Foldable`, and `Traversable` (which all use the same underlying algorithm).
      * `TcDerivInfer`: This is the new home for `inferConstraints`,
        `simplifyInstanceContexts`, and related functions, whose role is to come up
        with the derived instance context and subsequently simplify it.
      * `TcDerivUtils`: This is a grab-bag module that contains several
        error-checking utilities originally in `TcDeriv`, as well as some functions
        that `TcDeriv` and `TcDerivInfer` both need.
      
      The end result is that `TcDeriv` is now less than 1,600 SLOC (originally 2,686
      SLOC), and `TcGenDeriv` is now about 2,000 SLOC (originally 2,964).
      
      In addition, this also implements a couple of tiny refactorings:
      
      * I transformed `type Condition = (DynFlags, TyCon) -> Validity` into
        `type Condition = DynFlags -> TyCon -> Validity`
      * I killed the `DerivSpecGeneric` constructor for `DerivSpecMechanism`, and
        merged its functionality into `DerivSpecStock`. In addition,
        `hasStockDeriving` now contains key-value pairs for `Generic` and `Generic1`,
        so they're no longer treated as an awkward special case in `TcDeriv`.
      
      Test Plan: ./validate
      
      Reviewers: simonpj, austin, bgamari
      
      Reviewed By: simonpj
      
      Subscribers: thomie, mpickering
      
      Differential Revision: https://phabricator.haskell.org/D2568
      4a03012a
    • Ryan Scott's avatar
      Remove unused T12124.srderr · 58ecdf83
      Ryan Scott authored
      This was (accidentally?) introduced in 465c6c5d
      58ecdf83
  4. Oct 05, 2016
  5. Oct 04, 2016
  6. Oct 02, 2016
  7. Oct 01, 2016
    • Tamar Christina's avatar
      Add NUMA support for Windows · c93813d9
      Tamar Christina authored
      Summary:
      NOTE: I have been able to do simple testing on emulated NUMA nodes.
                 Real hardware would be needed for a proper test.
      
      D2199 Added NUMA support for Linux, I have just filled in the missing pieces following
      the description of the Linux APIs.
      
      Test Plan:
      Use `bcdedit.exe /set groupsize 2` to modify the kernel again (Similar to D2533).
      
      This generates some NUMA nodes:
      
      ```
      Logical Processor to NUMA Node Map:
      NUMA Node 0:
      **
      --
      NUMA Node 1:
      --
      **
      
      Approximate Cross-NUMA Node Access Cost (relative to fastest):
           00  01
      00: 1.1 1.1
      01: 1.0 1.0
      ```
      
      run ` ../test-numa.exe +RTS --numa -RTS`
      
      and check PerfMon for NUMA allocations.
      
      Reviewers: simonmar, erikd, bgamari, austin
      
      Reviewed By: simonmar
      
      Subscribers: thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D2534
      
      GHC Trac Issues: #12602
      c93813d9
    • Tamar Christina's avatar
      Use check stacking on Windows. · 1e795a00
      Tamar Christina authored
      Summary:
      #8870 added as a temporary work around a much higher initial reserve
      and committed stack space of 2mb. This is causing problems with other windows applications.
      
      The hack was supposed to be temporary untill we could emit `__chkstk` instructions.
      But GCC can emit stack checks automatically for us if `-fstack-check` is passed.
      
      This will then emit calls to `___chkstk_ms` before stack allocations.
      
      ```
        633de0:       48 83 e0 f0             and    $0xfffffffffffffff0,%rax
        633de4:       e8 07 0c 0d 00          callq  7049f0 <___chkstk_ms>
        633de9:       48 29 c4                sub    %rax,%rsp
      ```
      
      The hack is now no longer needed.
      
      Test Plan: ./validate
      
      Reviewers: austin, erikd, awson, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D2535
      
      GHC Trac Issues: #12186
      1e795a00
    • Ben Gamari's avatar
      Mark T11978a as broken due to #12019 · d1b4fec1
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: `validate --slow`
      
      Reviewers: austin
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2536
      
      GHC Trac Issues: #12019
      d1b4fec1
    • Matthew Pickering's avatar
      Move -dno-debug-output to the end of the test flags · f869b23e
      Matthew Pickering authored and Ben Gamari's avatar Ben Gamari committed
      It is often convenient to copy the test invocation and remove this flag
      in order to see compiler traces. Moving it to the end makes it easier to
      remove.
      
      Remove trailing whitespace
      
      Reviewers: austin, thomie, bgamari
      
      Reviewed By: bgamari
      
      Differential Revision: https://phabricator.haskell.org/D2543
      f869b23e
    • tmcgilchrist's avatar
      Recognise US spelling for specialisation flags. · 151edd89
      tmcgilchrist authored and Ben Gamari's avatar Ben Gamari committed
      The user guide says that we allow the user to use `specialise` or
      `specialize` interchangeably but this wasn't the case for the relevant
      flags. This patch adds aliases for the flags which control
      specialisation.
      
      Reviewers: erikd, austin, mpickering, bgamari
      
      Reviewed By: mpickering, bgamari
      
      Subscribers: mpickering, thomie
      
      Differential Revision: https://phabricator.haskell.org/D2542
      
      GHC Trac Issues: #12575
      151edd89
    • Tamar Christina's avatar
      Support more than 64 logical processors on Windows · 3c179054
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      Windows support for more than 64 logical processors are implemented
      using processor groups.
      
      Essentially what it's doing is keeping the existing maximum of 64
      processors and keeping the affinity mask a 64 bit value, but adds an
      hierarchy above that.
      
      This support was added to Windows 7 and so we need to at runtime detect
      if the APIs are still there due to our minimum supported version being
      Windows Vista.
      
      The Maximum number of groups supported at this time is 4, so 256 logical
      cores.  The group indices are 0 based. One thread can have affinity with
      multiple groups.
      
      See
      https://msdn.microsoft.com/en-us/library/windows/desktop/ms684251.aspx
      and particularly helpful is the whitepaper: 'Supporting Systems that
      have more than 64 processors' at
      https://msdn.microsoft.com/en-us/library/windows/hardware/dn653313.aspx
      
      Processor groups are not guaranteed to be uniformly distributed nor
      guaranteed to be filled before a next group is needed. The OS will
      assign processors to groups based on physical proximity and will never
      partially assign cores from one physical cpu to more than one group. If
      one has two 48 core CPUs then you'd end up with two groups of 48 logical
      cpus. Now add a 3rd CPU with 10 cores and the group it is assigned to
      depends where the socket is on the board.
      
      Test Plan:
      ./validate or make test -c . in the rts test folder.
      
      This tests for regressions, to test this particular functionality
      itself:
      
         <program> +RTS -N -qa -RTS
      
      Test is detailed in description.
      
      Reviewers: bgamari, simonmar, austin, erikd
      
      Reviewed By: simonmar
      
      Subscribers: thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D2533
      
      GHC Trac Issues: #11054
      3c179054
    • mniip's avatar
      GHCi: Don't remove shadowed bindings from typechecker scope. · 59d7ee53
      mniip authored
      The shadowed out bindings are accessible via qualified names like
      Ghci1.foo.  Since they are accessable in the renamer the typechecker
      should be able to see them too.  As a consequence they show up in :show
      bindings.
      
      This fixes T11547
      
      Test Plan:
      Fixed current tests to accomodate to new stuff in :show bindings
      Added a test that verifies that the typechecker doesn't crash
      
      Reviewers: austin, bgamari, simonpj
      
      Reviewed By: simonpj
      
      Subscribers: simonpj, thomie
      
      Differential Revision: https://phabricator.haskell.org/D2447
      
      GHC Trac Issues: #11547
      59d7ee53
Loading