Skip to content
Snippets Groups Projects
  1. Feb 25, 2018
  2. Feb 24, 2018
    • Andrey Mokhov's avatar
      Update Hadrian submodule · bf3f0a68
      Andrey Mokhov authored
        * Make shell.nix less broken (hadrian/510)
        * Add --configure flag to the script
        * Undo iserv changes (hadrian/507)
        * Fix ghc-cabal: Parsec modules are now found in libraries/parsec/src (hadrian/506)
        * Move a bunch of types into dedicated modules (hadrian/502)
        * Add --quickjump to Haddock (hadrian/505)
        * Add iserv library (hadrian/504)
        * Merge pull request hadrian/503 from snowleopard/angerman-patch-1
        * Merge pull request hadrian/500 from snowleopard/runtime-deps
        * Fix Hadrian after Cabal changes (hadrian/498)
        * Drop custom logic for Scav_thr and Evac_thr (hadrian/497)
        * Fix Haddock (hadrian/496)
      bf3f0a68
  3. Feb 22, 2018
  4. Feb 21, 2018
  5. Feb 20, 2018
    • Ben Gamari's avatar
      Revert "Move `iserv` into `utils` and change package name · abfe1048
      Ben Gamari authored
      See Phab:D4377 for the rationale. We will try this again.
      
      This reverts commit 7c173b90.
      abfe1048
    • Ryan Scott's avatar
      Slight refactor of stock deriving internals · f4336593
      Ryan Scott authored
      Summary:
      Before, the `hasStockDeriving` function, which determines
      how derived bindings should be generated for stock classes, was
      awkwardly separated from the `checkSideConditions` function, which
      checks invariants of the same classes that `hasStockDeriving` does.
      As a result, there was a fair deal of hoopla needed to actually use
      `hasStockDeriving`.
      
      But this hoopla really isn't required—we should be using
      `hasStockDeriving` from within `checkSideConditions`, since they're
      looking up information about the same classes! By doing this, we can
      eliminate some kludgy code in the form of `mk_eqn_stock'`, which had
      an unreachable `pprPanic` that was stinking up the place.
      
      Reviewers: bgamari, dfeuer
      
      Reviewed By: bgamari
      
      Subscribers: dfeuer, rwbarton, thomie, carter
      
      GHC Trac Issues: #13154
      
      Differential Revision: https://phabricator.haskell.org/D4370
      f4336593
    • Ryan Scott's avatar
      Add ghc-prim.buildinfo to .gitignore · f511bb58
      Ryan Scott authored
      f511bb58
    • Ben Gamari's avatar
      circleci: Skip performance tests · 81a5e05d
      Ben Gamari authored
      Once we finally get the automation for #12758 we can re-enable these.
      81a5e05d
    • David Feuer's avatar
      Document missing dataToTag# . tagToEnum# rule · 517c1940
      David Feuer authored
      Explain why we don't have a rule to optimize `dataToTag# (tagToEnum# x)`
      to `x`.
      
      [skip ci]
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14282
      
      Differential Revision: https://phabricator.haskell.org/D4375
      517c1940
    • Tamar Christina's avatar
      Change how includes for input file directory works · eb2daa2b
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      GHC Used to only allow for one include mode, namely `-I`.  The problem
      with `-I` includes is that it supercedes all other includes, including
      the system include paths.
      
      This is not a problem for paths requested by the user, but it is a
      problem for the ones we implicitly derive and add.
      
      In particular we add the source directory of the input file to the
      include path. This is problematic because it causes any file with the
      name of a system include, to inadvertently loop as the wrong file gets
      included.
      
      Since this is an implicitly include, and as far as I can tell, only done
      so local includes are found (as the sources given to GCC reside in a
      temp folder) then switch from `-I` to `-iquote`.
      
      This requires a submodule update for haddock
      
      Test Plan: ./validate
      
      Reviewers: austin, bgamari, hvr
      
      Reviewed By: bgamari
      
      Subscribers: carter, rwbarton, thomie
      
      GHC Trac Issues: #14312
      
      Differential Revision: https://phabricator.haskell.org/D4080
      eb2daa2b
    • Ben Gamari's avatar
      testsuite: Bump allocations for T1969 and T5837 · 71294f30
      Ben Gamari authored
      Sadly it's not immediately obvious where this regression came from:
      
       * T5837 started failing on OS X with 0c2350c2
       * It's not clear when T1969 started failing due to the recent out of memory
         issues on Harbormaster
      71294f30
  6. Feb 19, 2018
  7. Feb 18, 2018
    • Ryan Scott's avatar
      Rename the types in a GADT constructor in toposorted order · 043466b9
      Ryan Scott authored
      Previously, we were extracting the free variables from a
      GADT constructor in an incorrect order, which caused the type
      variables for the constructor's type signature to end up in
      non-toposorted order. Thankfully, rearranging the order of types
      during renaming makes swift work of this bug.
      
      This fixes a regression introduced in commit
      fa29df02.
      For whatever reason, that commit also commented out a
      significant portion of the `T13123` test. This code appears
      to work, so I've opted to uncomment it.
      
      Test Plan: make test TEST=T14808
      
      Reviewers: simonpj, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14808
      
      Differential Revision: https://phabricator.haskell.org/D4413
      043466b9
    • Ömer Sinan Ağacan's avatar
      StgLint overhaul · 7f389a58
      Ömer Sinan Ağacan authored
      - Remove all type checks
      - Check two STG invariants (no unboxed let bindings, variables defined
        before used) and post-unarisation invariants.
      
      See the module header and #14787.
      
      This version validates with `-dstg-lint` added to `GhcStage2HcOpts` and
      `GhcLibHcOpts` and `EXTRA_HC_OPTS`.
      
      Unarise changes:
      
      - `unariseConArgBinder` and `unariseFunArgBinder` functions were almost
        the same; only difference was when unarising fun args we keep void
        args while in con args we drop them. A new function `unariseArgBinder`
        added with a `Bool` argument for whether we're unarising a con arg.
        `unariseConArgBinder` and `unariseFunArgBinder` are now defined as
      
            unariseConArgBinder = unarsieArgBinder True  -- data con
            unariseFunArgBinder = unariseArgBinder False -- not data con
      
      - A bug in `unariseConArgBinder` and `unariseFunArgBinder` (which are
        just calls to `unariseArgBinder` now) that invalidated the
        post-unarise invariants when the argument has single type rep (i.e.
        `length (typePrimRep x) == 1`) fixed. This isn't a correctness issue
        (it's fine not to unarise if a variable is already represented as
        single value), but it triggers StgLint.
      
      Test Plan:
      - Pass testsuite with `-dstg-lint` [done]
      - Boot stage2 (including libraries) with `-dstg-lint` [done]
      
      Reviewers: simonpj, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: duog, rwbarton, thomie, carter
      
      GHC Trac Issues: #14787
      
      Differential Revision: https://phabricator.haskell.org/D4404
      7f389a58
    • Tao He's avatar
      Improve error message for UNPACK/strictness annotations. · fc33f8b3
      Tao He authored
      
      Print different error message for improper UNPACK and strictness
      annotations.  Fix Trac #14761.
      
      Signed-off-by: Tao He's avatarHE, Tao <sighingnow@gmail.com>
      
      Test Plan: make test TEST="T7210 T14761a T14761b"
      
      Reviewers: goldfire, bgamari, RyanGlScott, simonpj
      
      Reviewed By: RyanGlScott, simonpj
      
      Subscribers: simonpj, goldfire, rwbarton, thomie, carter
      
      GHC Trac Issues: #14761
      
      Differential Revision: https://phabricator.haskell.org/D4397
      fc33f8b3
    • Douglas Wilson's avatar
      testsuite: Add newline to test output · d924c17d
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4389
      d924c17d
    • Michal Terepeta's avatar
      CBE: re-introduce bgamari's fixes · 4e513bf7
      Michal Terepeta authored and Ben Gamari's avatar Ben Gamari committed
      
      During some recent work on CBE we discovered that `zipWith` is used to
      check for equality, but that doesn't quite work if lists are of
      different lengths! This was fixed by bgamari, but unfortunately the fix
      had to be rolled back due to other changes in CBE in
      50adbd7c. Since I wanted to have another
      look at CBE anyway, we agreed that the first thing to do would be to
      re-introduce the fix.
      
      Sadly I don't have any actual test case that would exercise this.
      
      Signed-off-by: default avatarMichal Terepeta <michal.terepeta@gmail.com>
      
      Test Plan: ./validate
      
      Reviewers: bgamari, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14226
      
      Differential Revision: https://phabricator.haskell.org/D4387
      4e513bf7
    • Simon Marlow's avatar
      myThreadId# is trivial; make it an inline primop · c05529c2
      Simon Marlow authored and Ben Gamari's avatar Ben Gamari committed
      The pattern `threadCapability =<< myThreadId` is used a lot in code
      that uses `hs_try_putmvar`, I want to make it cheaper.
      
      Test Plan: validate
      
      Reviewers: bgamari, erikd
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4381
      c05529c2
    • Simon Marlow's avatar
      Tidy up and consolidate canned CmmReg and CmmGlobals · ccda4862
      Simon Marlow authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: validate
      
      Reviewers: bgamari, erikd
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4380
      ccda4862
    • adam's avatar
      Remove doubled words · bfb90bca
      adam authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4368
      bfb90bca
    • Ben Gamari's avatar
      Build Haddocks with --quickjump · 9ff4cce3
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      By request of @alexbiehl.
      CCing @snowleopard and @alpmestan as the same should be done in Hadrian.
      
      Bumps haddock submodule.
      
      Reviewers: alexbiehl
      
      Reviewed By: alexbiehl
      
      Subscribers: rwbarton, thomie, carter, snowleopard, alpmestan, alexbiehl
      
      Differential Revision: https://phabricator.haskell.org/D4365
      9ff4cce3
    • Matthías Páll Gissurarson's avatar
      Add valid refinement substitution suggestions for typed holes · 918c0b39
      Matthías Páll Gissurarson authored and Ben Gamari's avatar Ben Gamari committed
      This adds valid refinement substitution suggestions for typed holes and
      documentation thereof.
      
      Inspired by Agda's refinement facilities, this extends the typed holes
      feature to be able to search for valid refinement substitutions, which
      are substitutions that have one or more holes in them.
      
      When the flag `-frefinement-level-substitutions=n` where `n > 0` is
      passed, we also look for valid refinement substitutions, i.e.
      substitutions that are valid, but adds more holes. Consider the
      following:
      
        f :: [Integer] -> Integer
        f = _
      
      Here the valid substitutions suggested will be (with the new
      `-funclutter-valid-substitutions` flag for less verbosity set):
      
      ```
        Valid substitutions include
          f :: [Integer] -> Integer
          product :: forall (t :: * -> *).
                    Foldable t => forall a. Num a => t a -> a
          sum :: forall (t :: * -> *).
                Foldable t => forall a. Num a => t a -> a
          maximum :: forall (t :: * -> *).
                    Foldable t => forall a. Ord a => t a -> a
          minimum :: forall (t :: * -> *).
                    Foldable t => forall a. Ord a => t a -> a
          head :: forall a. [a] -> a
          (Some substitutions suppressed; use -fmax-valid-substitutions=N or
      -fno-max-valid-substitutions)
      ```
      
      When the `-frefinement-level-substitutions=1` flag is given, we
      additionally compute and report valid refinement substitutions:
      
      ```
        Valid refinement substitutions include
          foldl1 _ :: forall (t :: * -> *).
                      Foldable t => forall a. (a -> a -> a) -> t a -> a
          foldr1 _ :: forall (t :: * -> *).
                      Foldable t => forall a. (a -> a -> a) -> t a -> a
          head _ :: forall a. [a] -> a
          last _ :: forall a. [a] -> a
          error _ :: forall (a :: TYPE r).
                      GHC.Stack.Types.HasCallStack => [Char] -> a
          errorWithoutStackTrace _ :: forall (a :: TYPE r). [Char] -> a
          (Some refinement substitutions suppressed; use
      -fmax-refinement-substitutions=N or -fno-max-refinement-substitutions)
      ```
      
      Which are substitutions with holes in them. This allows e.g. beginners
      to discover the fold functions and similar.
      
      We find these refinement suggestions by considering substitutions that
      don't fit the type of the hole, but ones that would fit if given an
      additional argument. We do this by creating a new type variable with
      newOpenFlexiTyVarTy (e.g. `t_a1/m[tau:1]`), and then considering
      substitutions of the type `t_a1/m[tau:1] -> v` where `v` is the type of
      the hole. Since the simplifier is free to unify this new type variable
      with any type (and it is cloned before each check to avoid
      side-effects), we can now discover any identifiers that would fit if
      given another identifier of a suitable type. This is then generalized
      so that we can consider any number of additional arguments by setting
      the `-frefinement-level-substitutions` flag to any number, and then
      considering substitutions like e.g. `foldl _ _` with two additional
      arguments.
      
      This can e.g. help beginners discover the `fold` functions.
      This could also help more advanced users figure out which morphisms
      they can use when arrow chasing.
      Then you could write `m = _ . m2 . m3` where `m2` and `m3` are some
      morphisms, and not only get exact fits, but also help in finding
      morphisms that might get you a little bit closer to where you want to
      go in the diagram.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4357
      918c0b39
    • Ryan Scott's avatar
      Implement stopgap solution for #14728 · 1ede46d4
      Ryan Scott authored
      It turns out that one can produce ill-formed Core by
      combining `GeneralizedNewtypeDeriving`, `TypeInType`, and
      `TypeFamilies`, as demonstrated in #14728. The root of the problem
      is allowing the last parameter of a class to appear in a //kind// of
      an associated type family, as our current approach to deriving
      associated type family instances simply doesn't work well for that
      situation.
      
      Although it might be possible to properly implement this feature
      today (see https://ghc.haskell.org/trac/ghc/ticket/14728#comment:3
      for a sketch of how this might work), there does not currently exist
      a performant implementation of the algorithm needed to accomplish
      this. Until such an implementation surfaces, we will make this corner
      case of `GeneralizedNewtypeDeriving` an error.
      
      Test Plan: make test TEST="T14728a T14728b"
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14728
      
      Differential Revision: https://phabricator.haskell.org/D4402
      1ede46d4
    • Ben Gamari's avatar
      base: Fix changelog entry for openTempFile · 90804660
      Ben Gamari authored
      This change is present in 4.11.0.0.
      90804660
    • Ben Gamari's avatar
      a644dffe
  8. Feb 16, 2018
    • Ryan Scott's avatar
      Fix #14811 by wiring in $tcUnit# · d5ac5820
      Ryan Scott authored and David Feuer's avatar David Feuer committed
      Previously, we were skipping over `$tcUnit#` entirely when
      wiring in `Typeable` tycons, resulting in #14811. Easily fixed.
      
      Test Plan: make test TEST=T14811
      
      Reviewers: bgamari, dfeuer
      
      Reviewed By: dfeuer
      
      Subscribers: dfeuer, rwbarton, thomie, carter
      
      GHC Trac Issues: #14811
      
      Differential Revision: https://phabricator.haskell.org/D4414
      d5ac5820
Loading