Skip to content
Snippets Groups Projects
  1. Feb 15, 2017
  2. Feb 14, 2017
    • Tamar Christina's avatar
      Fix ExtraSymbols jump table on Windows. · 2f1017b9
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      This corrects the `jump islands` calculations for Windows.  The code was
      incorrectly creating a new entry for every `usage` of a symbol instead
      of every used symbol. e.g. if a symbol is used 5 times it used to create
      5 jump islands. This is incorrect and not in line with what the `ELF`
      and `Mach-O` linkers do. Also since we allocate `n` spaces where `n` is
      number of symbols, we would quickly run out of space and abort.
      
      Test Plan: ./validate
      
      Reviewers: simonmar, hvr, erikd, bgamari, austin
      
      Reviewed By: bgamari
      
      Subscribers: thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D3026
      2f1017b9
    • Tamar Christina's avatar
      Expand list of always loaded Windows shared libs · 04f67c99
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      When the `GCC` driver envokes the pipeline a `SPEC` is used to determine
      how to configure the compiler and which libraries to pass along.
      
      For Windows/mingw, this specfile is
      https://github.com/gcc-mirror/gcc/blob/master/gcc/config/i386/mingw32.h
      
      This expands the list of base DLLs with the ones that GCC always links,
      and adds extra sibling dlls of `stdc++` in case it is linked in.
      
      Following D3028 this patch only needs to load the always load only the
      top level individual shared libs.
      
      Test Plan: ./validate
      
      Reviewers: RyanGlScott, austin, bgamari, erikd, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: RyanGlScott, thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D3029
      04f67c99
    • Siddharth's avatar
      Typecast covers entire expression to fix format warning. · 60c49861
      Siddharth authored and Ben Gamari's avatar Ben Gamari committed
      - Fixes (#12636).
      - changes all the typecasts to _unsinged long long_ to
        have the format specifiers work.
      
      Reviewers: austin, bgamari, erikd, simonmar, Phyx
      
      Reviewed By: erikd, Phyx
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D3129
      60c49861
  3. Feb 12, 2017
    • olsner's avatar
      Apply SplitSections to all C compilations · a50082c1
      olsner authored and Ben Gamari's avatar Ben Gamari committed
      Previously this was added only to the RTS's C files (those are the bulk
      of it though), but there are C bits in ghc-prim, integer-gmp and base
      too.
      
      Followup for #8405, allows the large table of character properties in
      base to be stripped when not used.
      
      Test Plan: validate
      
      Reviewers: austin, bgamari, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: thomie, snowleopard
      
      Differential Revision: https://phabricator.haskell.org/D3121
      a50082c1
    • Ben Gamari's avatar
      rts/Profiling: Factor out report generation · 56c9bb39
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Here we move the actual report generation logic to
      `rts/ProfilerReport.c`. This break is actually quite clean,
      
          void writeCCSReport( FILE *prof_file, CostCentreStack const *ccs,
                               ProfilerTotals totals );
      
      This is more profiler refactoring in preparation for machine-readable
      output.
      
      Test Plan: Validate
      
      Reviewers: austin, erikd, simonmar
      
      Reviewed By: simonmar
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D3097
      56c9bb39
    • Ben Gamari's avatar
      rts/Profiling: Kill a few globals and add consts · 1a14d384
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Previously it was quite difficult to follow the dataflow through this
      file due to global mutation and rather non-descriptive types.
      
      This is a cleanup in preparation for factoring out the report-generating
      logic, which is itself in preparation for somedayteaching the profiler
      to produce more machine-readable reports (JSON perhaps?).
      
      Test Plan: Validate
      
      Reviewers: austin, erikd, simonmar
      
      Reviewed By: simonmar
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D3096
      1a14d384
  4. Feb 10, 2017
  5. Feb 08, 2017
    • Ben Gamari's avatar
      Fix stop_thread unwinding information · 34e35233
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This corrects the unwind information for `stg_stop_thread`, which
      allows us to unwind back to the C stack after reaching the end of the 
      STG stack.
      
      Test Plan: Validate
      
      Reviewers: simonmar, austin, erikd
      
      Reviewed By: simonmar
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2746
      34e35233
    • Ben Gamari's avatar
      Cmm: Add support for undefined unwinding statements · 3328ddb8
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      And use to mark `stg_stack_underflow_frame`, which we are unable to
      determine a caller from.
      
      To simplify parsing at the moment we steal the `return` keyword to
      indicate an undefined unwind value. Perhaps this should be revisited.
      
      Reviewers: scpmw, simonmar, austin, erikd
      
      Subscribers: dfeuer, thomie
      
      Differential Revision: https://phabricator.haskell.org/D2738
      3328ddb8
    • Ben Gamari's avatar
      Generalize CmmUnwind and pass unwind information through NCG · 3eb737ee
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      As discussed in D1532, Trac Trac #11337, and Trac Trac #11338, the stack
      unwinding information produced by GHC is currently quite approximate.
      Essentially we assume that register values do not change at all within a
      basic block. While this is somewhat true in normal Haskell code, blocks
      containing foreign calls often break this assumption. This results in
      unreliable call stacks, especially in the code containing foreign calls.
      This is worse than it sounds as unreliable unwinding information can at
      times result in segmentation faults.
      
      This patch set attempts to improve this situation by tracking unwinding
      information with finer granularity. By dispensing with the assumption of
      one unwinding table per block, we allow the compiler to accurately
      represent the areas surrounding foreign calls.
      
      Towards this end we generalize the representation of unwind information
      in the backend in three ways,
      
       * Multiple CmmUnwind nodes can occur per block
      
       * CmmUnwind nodes can now carry unwind information for multiple
         registers (while not strictly necessary; this makes emitting
         unwinding information a bit more convenient in the compiler)
      
       * The NCG backend is given an opportunity to modify the unwinding
         records since it may need to make adjustments due to, for instance,
         native calling convention requirements for foreign calls (see
         #11353).
      
      This sets the stage for resolving #11337 and #11338.
      
      Test Plan: Validate
      
      Reviewers: scpmw, simonmar, austin, erikd
      
      Subscribers: qnikst, thomie
      
      Differential Revision: https://phabricator.haskell.org/D2741
      3eb737ee
  6. Feb 04, 2017
    • Takenobu Tani's avatar
      Fix comment (old file names) in rts/ · 31bb85ff
      Takenobu Tani authored and Matthew Pickering's avatar Matthew Pickering committed
      [skip ci]
      
      There ware some old file names (.lhs, ...) at comments.
      
      * rts/win32/ThrIOManager.c
        - Conc.lhs -> Conc.hs
      
      * rts/PrimOps.cmm
        - ByteCodeLink.lhs -> ByteCodeLink.hs
        - StgMiscClosures.hc -> StgMiscClosures.cmm
      
      * rts/AutoApply.h
        - AutoApply.hc -> AutoApply.cmm
      
      * rts/HeapStackCheck.cmm
        - PrimOps.hc -> PrimOps.cmm
      
      * rts/LdvProfile.h
        - Updates.hc -> Updates.cmm
      
      * rts/Schedule.c
        - StgStartup.hc -> StgStartup.cmm
      
      * rts/Weak.c
        - StgMiscClosures.hc -> StgMiscClosures.cmm
      
      Reviewers: bgamari, austin, erikd, simonmar
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D3075
      31bb85ff
  7. Feb 03, 2017
    • Sylvain Henry's avatar
      Ditch static flags · bbd3c399
      Sylvain Henry authored
      This patch converts the 4 lasting static flags (read from the command
      line and unsafely stored in immutable global variables) into dynamic
      flags. Most use cases have been converted into reading them from a DynFlags.
      
      In cases for which we don't have easy access to a DynFlags, we read from
      'unsafeGlobalDynFlags' that is set at the beginning of each 'runGhc'.
      It's not perfect (not thread-safe) but it is still better as we can
      set/unset these 4 flags before each run when using GHC API.
      
      Updates haddock submodule.
      
      Rebased and finished by: bgamari
      
      Test Plan: validate
      
      Reviewers: goldfire, erikd, hvr, austin, simonmar, bgamari
      
      Reviewed By: simonmar
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2839
      
      GHC Trac Issues: #8440
      bbd3c399
  8. Feb 02, 2017
    • Ben Gamari's avatar
      Add support for StaticPointers in GHCi · eedb3df0
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Here we add support to GHCi for StaticPointers. This process begins by
      adding remote GHCi messages for adding entries to the static pointer
      table. We then collect binders needing SPT entries after linking and
      send the interpreter a message adding entries with the appropriate
      fingerprints.
      
      Test Plan: `make test TEST=StaticPtr`
      
      Reviewers: facundominguez, mboes, simonpj, simonmar, goldfire, austin,
      hvr, erikd
      
      Reviewed By: simonpj, simonmar
      
      Subscribers: RyanGlScott, simonpj, thomie
      
      Differential Revision: https://phabricator.haskell.org/D2504
      
      GHC Trac Issues: #12356
      eedb3df0
  9. Jan 31, 2017
    • Alex Biehl's avatar
      Abstract over the way eventlogs are flushed · 4dfc6d1c
      Alex Biehl authored
      Currently eventlog data is always written to a file `progname.eventlog`.
      This patch introduces the `flushEventLog` field in `RtsConfig` which
      allows to customize the writing of eventlog data.
      
      One possible scenario is the ongoing live-profile-monitor effort by
      @NCrashed which slurps all eventlog data through `fluchEventLog`.
      
      `flushEventLog` takes a buffer with eventlog data and its size and
      returns `false` (0) in case eventlog data could not be procesed.
      
      Reviewers: simonmar, austin, erikd, bgamari
      
      Reviewed By: simonmar, bgamari
      
      Subscribers: qnikst, thomie, NCrashed
      
      Differential Revision: https://phabricator.haskell.org/D2934
      4dfc6d1c
  10. Jan 30, 2017
    • Tamar Christina's avatar
      Slighly clean up symbol loading error. · f41c27d3
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      The symbol not found error that is triggered
      during lazy-loading was a bit chaotic before.
      
      This reformats it a bit to:
      
      ```
      ghc-stage2.exe:  | E:\...\libLLVMSupport.a: unknown symbol `_ZN4llvm5APIntC1Ejyb'
      ghc-stage2.exe:  | E:\...\libLLVMCore.a: unknown symbol `_ZN4llvm5APInt14AssignSlowCaseERKS0_'
      ghc-stage2.exe:  | E:\...\libLLVMCore.a: unknown symbol `_ZN4llvm13ConstantRangeC1ENS_5APIntES1_'
      ghc-stage2.exe:  | E:\...\libLLVMCore.a: unknown symbol `_ZN4llvm14FoldingSetImplC2Ej'
      ghc-stage2.exe:  | E:\...\libLLVMCore.a: unknown symbol `_ZN4llvm15LLVMContextImplD1Ev'
      ghc-stage2.exe:  | E:\...\libLLVMLTO.a: unknown symbol `_ZN4llvm11LLVMContextD1Ev'
      ghc-stage2.exe:  | E:\...\libLLVMCore.a: unknown symbol `_ZNK4llvm5Value10getContextEv'
      ghc-stage2.exe: ^^ Could not load 'LLVMIsMultithreaded', dependency unresolved.
      See top entry above.
      ```
      
      I have also thought about also showing the demangled names, as it may
      be useful for the end user.
      
      `libgcc` seems to provide a method for this so we wouldn't need any
      extra dependency.
      
      Any thoughts on this or would it not be useful?
      
      Reviewers: austin, erikd, simonmar, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: RyanGlScott, thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D3027
      
      GHC Trac Issues: #13093, #13113
      f41c27d3
  11. Jan 26, 2017
  12. Jan 18, 2017
    • Tamar Christina's avatar
      Clean up RTS Linker Windows. · 0b7cd65e
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      Clean up the linker code for PE.
      
      1. Stop copying structures from the windows header
         and use those that are in the headers. There's no
         point in copying them and we got a few types wrong.
      
      2. Replace custom typedef with C99 types. If we're not
         going to use the Windows type aliases, at least use
         standard ones.
      
      Test Plan: ./validate
      
      Reviewers: simonmar, austin, erikd, bgamari
      
      Reviewed By: simonmar, bgamari
      
      Subscribers: dfeuer, thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D2944
      0b7cd65e
    • Gabor Greif's avatar
      Spelling fixes in comments [ci skip] · 70472bf2
      Gabor Greif authored
      70472bf2
  13. Jan 16, 2017
  14. Jan 15, 2017
    • Ryan Scott's avatar
      Improve access violation reporting on Windows · c13151e5
      Ryan Scott authored
      Summary:
      This patch is courtesy of @awson.
      
      Currently, whenever GHC catches a segfault on Windows, it simply reports the
      somewhat uninformative message
      `Segmentation fault/access violation in generated code`. This patch adds to
      the message the type of violation (read/write/dep) and location information,
      which should help debugging segfaults in the future.
      
      Fixes #13108.
      
      Test Plan: Build on Windows
      
      Reviewers: austin, erikd, bgamari, simonmar, Phyx
      
      Reviewed By: bgamari, Phyx
      
      Subscribers: awson, thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D2969
      
      GHC Trac Issues: #13108
      c13151e5
    • Tamar Christina's avatar
      Fix abort and import lib search on Windows · 331f88d0
      Tamar Christina authored
      Summary:
      Apparently `sysErrorBelch` doesn't terminate the program anymore making
      previously unreachable code now execute. If a dll is not found the error
      message we return needs to be a heap value.
      
      Secondly also allow the pattern `lib<name>` to be allowed for finding an
      import library with the name `lib<name>.dll.a`.
      
      Test Plan: ./validate, new tests T13082_good and T13082_fail
      
      Reviewers: austin, RyanGlScott, hvr, erikd, simonmar, bgamari
      
      Reviewed By: RyanGlScott, bgamari
      
      Subscribers: thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D2941
      
      GHC Trac Issues: #13082
      331f88d0
  15. Jan 13, 2017
  16. Jan 10, 2017
  17. Jan 06, 2017
    • Simon Marlow's avatar
      More fixes for #5654 · 3a18baff
      Simon Marlow authored
      * In stg_ap_0_fast, if we're evaluating a thunk, the thunk might
        evaluate to a function in which case we may have to adjust its CCS.
      
      * The interpreter has its own implementation of stg_ap_0_fast, so we
        have to do the same shenanigans with creating empty PAPs and copying
        PAPs there.
      
      * GHCi creates Cost Centres as children of CCS_MAIN, which enterFunCCS()
        wrongly assumed to imply that they were CAFs.  Now we use the is_caf
        flag for this, which we have to correctly initialise when we create a
        Cost Centre in GHCi.
      3a18baff
  18. Dec 27, 2016
    • Peter Trommler's avatar
      Testsuite: Skip failing tests on PowerPC 64-bit · 4dec7d19
      Peter Trommler authored and Ben Gamari's avatar Ben Gamari committed
      The Power ISA says the result of a division by zero is undefined.  So
      ignore stdout on PowerPC 64-bit systems.
      
      Disable ext-interp tests on 64-bit PowerPC.  We don't have support for
      PowerPC 64-bit ELF in the RTS linker, which is needed for the external
      interpreter.
      
      Test Plan: ./validate
      
      Reviewers: austin, simonmar, hvr, erikd, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2782
      4dec7d19
  19. Dec 23, 2016
  20. Dec 17, 2016
    • Simon Marlow's avatar
      Fix bug in previous fix for #5654 · 2a02040b
      Simon Marlow authored and Ben Gamari's avatar Ben Gamari committed
      I forgot to account for BCOs, which have a different layout from
      functions.  This caused crashes when using profiling with GHCi (via
      -fexternal-interpreter -prof), which unfortunately is not tested at all
      by validate, even when profiling is enabled.  I'm going to add some
      testing that would have caught this in a separate patch.
      
      Test Plan:
      ```
      cd nofib/spectral/puzzle && make NoFibWithGHCi=YES
      EXTRA_RUNTEST_OPTS='-fexternal-interpreter -prof'
      ```
      New testsuite tests coming in a separate diff.
      
      Reviewers: niteria, austin, erikd, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2868
      
      GHC Trac Issues: #5654
      2a02040b
    • Ben Gamari's avatar
      rts/win32/IOManager: Fix integer types · 2d1beb1e
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This code has been broken on 64-bit systems for some time: the length
      and timeout arguments of `addIORequest` and `addDelayRequest`,
      respectively, were declared as `int`. However, they were passed Haskell
      integers from their respective primops. Integer overflow and madness
      ensued. This resulted in #7325 and who knows what else.
      
      Also, there were a few left-over `BOOL`s in here which were not passed
      to Windows system calls; these were changed to C99 `bool`s.
      
      However, there is still a bit of signedness inconsistency within the
      `delay#` call-chain,
      
       * `GHC.Conc.IO.threadDelay` and the `delay#` primop accept `Int`
         arguments
      
       * The `delay#` implementation in `PrimOps.cmm` expects the timeout as
         a `W_`
      
       * `AsyncIO.c:addDelayRequest` expects an `HsInt` (was `int` prior to
         this patch)
      
       * `IOManager.c:AddDelayRequest` expects an `HsInt`` (was `int`)
      
       * The Windows `Sleep` function expects a `DWORD` (which is unsigned)
      
      Test Plan: Validate on Windows
      
      Reviewers: erikd, austin, simonmar, Phyx
      
      Reviewed By: Phyx
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2861
      
      GHC Trac Issues: #7325
      2d1beb1e
    • Sergei Trofimovich's avatar
      rts/Compact.cmm: fix UNREG build failure · c4808602
      Sergei Trofimovich authored
      
      The change does the following:
      - Add explicit declaration of exception closures
        from base. C backend needs those symbols to be
        visible.
      - Reorder cmm functions in use order. Again C
        backend needs symbol declaration/definition
        before use. even for module-local cmm functions.
      
      Fixes the following build failure:
      
        rts_dist_HC rts/dist/build/Compact.o
          In file included from /tmp/ghc3348_0/ghc_4.hc:3:0: error:
          /tmp/ghc3348_0/ghc_4.hc: In function 'stg_compactAddWithSharingzh':
      
          /tmp/ghc3348_0/ghc_4.hc:27:11: error:
           error: 'stg_compactAddWorkerzh' undeclared (first use in this function)
           JMP_((W_)&stg_compactAddWorkerzh);
                     ^
          ...
          /tmp/ghc3348_0/ghc_4.hc:230:13: error:
           error: 'base_GHCziIOziException_cannotCompactMutable_closure'
           undeclared (first use in this function)
           R1.w = (W_)&base_GHCziIOziException_cannotCompactMutable_closure;
                       ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
      
      Signed-off-by: default avatarSergei Trofimovich <siarheit@google.com>
      c4808602
  21. Dec 15, 2016
    • Simon Marlow's avatar
      Fix cost-centre-stacks bug (#5654) · 394231b3
      Simon Marlow authored and Ben Gamari's avatar Ben Gamari committed
      This fixes some cases of wrong stacks being generated by the profiler.
      For background and details on the fix see
      `Note [Evaluating functions with profiling]` in `rts/Apply.cmm`.
      
      This does have an impact on allocations for some programs when
      profiling.  nofib results:
      
      ```
         k-nucleotide          +0.0%     +8.8%    +11.0%    +11.0%      0.0%
               puzzle          +0.0%    +12.5%     0.244     0.246      0.0%
            typecheck           0.0%     +8.7%    +16.1%    +16.2%      0.0%
      ------------------------------------------------------------------------
      --------
                  Min          -0.0%     -0.0%    -34.4%    -35.5%    -25.0%
                  Max          +0.0%    +12.5%    +48.9%    +49.4%    +10.6%
       Geometric Mean          +0.0%     +0.6%     +2.0%     +1.8%     -0.3%
      
      ```
      
      But runtimes don't seem to be affected much, and the examples I looked
      at were completely legitimate.  For example, in puzzle we have this:
      
      ```
      position :: ItemType -> StateType ->  BankType
      position Bono = bonoPos
      position Edge = edgePos
      position Larry = larryPos
      position Adam = adamPos
      ```
      
      where the identifiers on the rhs are all record selectors.  Previously
      the profiler gave a stack that looked like
      
      ```
        position
        bonoPos
        ...
      ```
      
      i.e. `bonoPos` was at the same level of the call stack as `position`,
      but now it looks like
      
      ```
        position
         bonoPos
         ...
      ```
      
      I used the normaliser from the testsuite to diff the profiling output
      from other nofib programs and they all looked better.
      
      Test Plan:
      * the broken test passes
      * validate
      * compiled and ran all of nofib, measured perf, diff'd several .prof
      files
      
      Reviewers: niteria, erikd, austin, scpmw, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D2804
      
      GHC Trac Issues: #5654, #10007
      394231b3
    • Tamar Christina's avatar
      Reset FPU precision back to MSVCRT defaults · 6f7d8279
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      Mingw-w64 does a stupid thing. They set the FPU precision to extended
      mode by default.  The reasoning is that it's for compatibility with GNU
      Linux ported libraries. However the problem is this is incompatible with
      the standard Windows double precision mode.  In fact, if we create a new
      OS thread then Windows will reset the FPU to double precision mode.  So
      we end up with a weird state where the main thread by default has a
      different precision than any child threads.
      
      Test Plan: ./validate new test T7289
      
      Reviewers: simonmar, austin, bgamari, erikd
      
      Reviewed By: simonmar
      
      Subscribers: thomie, #ghc_windows_task_force
      
      Differential Revision: https://phabricator.haskell.org/D2819
      
      GHC Trac Issues: #7289
      6f7d8279
  22. Dec 13, 2016
  23. Dec 11, 2016
    • Moritz Angermann's avatar
      Make globals use sharedCAF · c3c70244
      Moritz Angermann authored and Tamar Christina's avatar Tamar Christina committed
      Summary:
      The use of globals is quite painful when multiple rts are loaded, e.g.
      when plugins are loaded, which bring in a second rts. The sharedCAF
      appraoch was employed for the FastStringTable; I've taken the libery
      to extend this to the other globals I could find.
      
      This is a reboot of D2575, that should hopefully not exhibit the same
      windows build issues.
      
      Reviewers: Phyx, simonmar, goldfire, bgamari, austin, hvr, erikd
      
      Reviewed By: Phyx, simonmar, bgamari
      
      Subscribers: mpickering, thomie
      
      Differential Revision: https://phabricator.haskell.org/D2773
      c3c70244
  24. Dec 10, 2016
  25. Dec 09, 2016
  26. Dec 08, 2016
  27. Dec 07, 2016
Loading