Skip to content
Snippets Groups Projects
  1. Feb 20, 2018
  2. Feb 19, 2018
  3. 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
  4. 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
  5. Feb 15, 2018
    • Moritz Angermann's avatar
      Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` · 7c173b90
      Moritz Angermann authored
      This is done for consistency. We usually call the package file the same name the
      folder has.  The move into `utils` is done so that we can move the library into
      `libraries/iserv` and the proxy into `utils/iserv-proxy` and then break the
      `iserv.cabal` apart.  This will make building the cross compiler with TH
      simpler, because we can build the library and proxy as separate packages.
      
      Reviewers: bgamari, simonmar, goldfire, erikd
      
      Reviewed By: simonmar
      
      Subscribers: tdammers, rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4377
      7c173b90
    • David Feuer's avatar
      Get eqTypeRep to inline · 8529fbba
      David Feuer authored
      GHC didn't inline `eqTypeRep`, presumably because it ended up
      being too big. This was unfortunate because it produces a
      `Maybe`, which will almost always be scrutinized immediately.
      
      Split `eqTypeRep` into a worker and a tiny wrapper, and mark the
      wrapper `INLINABLE`. This change actually seems to reduce Core size,
      at least in a small test.
      
      Reviewers: hvr, bgamari, mpickering
      
      Reviewed By: mpickering
      
      Subscribers: mpickering, rwbarton, thomie, carter
      
      GHC Trac Issues: #14790
      
      Differential Revision: https://phabricator.haskell.org/D4405
      8529fbba
    • Alp Mestanogullari's avatar
      rts.cabal.in: advertise profiling flavours of libraries, behind a flag · 0c2350c2
      Alp Mestanogullari authored and Moritz Angermann's avatar Moritz Angermann committed
      The make build system appears to be doing a bit of magic in order to supply
      the profiled flavours of libHSrts and libCffi, as they're not advertised in
      the 'extra-library-flavours' field of rts.cabal.in. This patch explicitly
      advertises _p and _thr_p flavours of the RTS library and libCffi, but only
      when the RTS is configured with the (newly introduced) 'profiling' flag.
      
      This is necessary for Hadrian, as a branch (soon to be merged) does away with
      ghc-cabal and relies just on Cabal to get package information. Without this
      patch, Cabal can never inform us that _p and _thr_p flavours should be
      built (and registered in the package db) as well, which obviously prevents us
      from building a profiled GHC.
      
      Reviewers: bgamari, erikd, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4409
      0c2350c2
    • Moritz Angermann's avatar
      Update .cabal files for Cabal 2.1 · e03ca71f
      Moritz Angermann authored
      cabal introduces SPDX identifier, and as such we need to change the
      BSD3 license name. Also the >= qualifier is no longer prefered.
      
      Test Plan: ./validate
      
      Reviewers: bgamari, erikd, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: alpmestan, rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4406
      e03ca71f
    • Moritz Angermann's avatar
      Adds `smp` flag to rts.cabal. · d5ff33d3
      Moritz Angermann authored
      Reviewers: bgamari, erikd, simonmar
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4393
      d5ff33d3
    • Moritz Angermann's avatar
      adds -latomic to. ghc-prim · ec9aacf3
      Moritz Angermann authored
      Reviewers: bgamari, hvr
      
      Reviewed By: bgamari
      
      Subscribers: erikd, hvr, rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4378
      ec9aacf3
  6. Feb 14, 2018
    • Sergey Vinokurov's avatar
      Various documentation improvements · df449e17
      Sergey Vinokurov authored and Ben Gamari's avatar Ben Gamari committed
       * Fix missing code example in changelog for 8.4.1
      
       * List 'setEnv' as opposite of 'getEnv'
      
         It seems best to direct users to use 'System.Environment.setEnv'
         rather than 'System.Posix.Env.putEnv'. This is due to 'setEnv' being
         located in the same module as 'getEnv' and my virtue of working on
         Windows platform, whereas 'putEnv' does not have that quality because
         it's part of the 'unix' package.
      
       * Reflect in docs the fact that 'readMVar' is not a composition of
         'takeMVVar' and 'putMVar' any more
      df449e17
  7. Feb 13, 2018
    • Tao He's avatar
      Raise parse error for `data T where`. · 8936ab69
      Tao He authored
      
      Empty GADTs data declarations can't be identified in type checker. This
      patch adds additional checks in parser and raise a parse error when
      encounter empty GADTs declarations but extension `GADTs` is not enabled.
      
      Only empty declarations are checked in parser to avoid affecting
      existing
      error messages related to missing GADTs extension.
      
      This patch should fix issue 8258.
      
      Signed-off-by: Tao He's avatarHE, Tao <sighingnow@gmail.com>
      
      Test Plan: make test TEST="T8258 T8258NoGADTs"
      
      Reviewers: bgamari, mpickering, alanz, RyanGlScott
      
      Reviewed By: bgamari, RyanGlScott
      
      Subscribers: adamse, RyanGlScott, rwbarton, thomie, mpickering, carter
      
      GHC Trac Issues: #8258
      
      Differential Revision: https://phabricator.haskell.org/D4350
      8936ab69
    • Ben Gamari's avatar
      Fix tests broken by c9a88db3 · 0c9777b7
      Ben Gamari authored
      0c9777b7
    • Ömer Sinan Ağacan's avatar
      Collect CCs in CorePrep, including CCs in unfoldings · 59574058
      Ömer Sinan Ağacan authored
      This patch includes two changes:
      
      1. Move cost centre collection from `SCCfinal` to `CorePrep`, to be able
         to collect cost centres in unfoldings. `CorePrep` drops unfoldings, so
         that's the latest stage in the compilation pipeline for this.
      
         After this change `SCCfinal` no longer collects all cost centres, but
         it still generates & collects CAF cost centres + updates cost centre
         stacks of `StgRhsClosure` and `StgRhsCon`s.
      
         This fixes #5889.
      
      2. Initialize cost centre stack fields of `StgRhs` in `coreToStg`. With
         this we no longer need to update cost centre stack fields in
         `SCCfinal`, so that module is removed.
      
         Cost centre initialization explained in Note [Cost-centre
         initialization plan].
      
         Because with -fcaf-all we need to attach a new cost-centre to each
         CAF, `coreTopBindToStg` now returns `CollectedCCs`.
      
      Test Plan: validate
      
      Reviewers: simonpj, bgamari, simonmar
      
      Reviewed By: simonpj, bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #5889
      
      Differential Revision: https://phabricator.haskell.org/D4325
      59574058
    • David Feuer's avatar
      Make ($!) representation-polymorphic · c9a88db3
      David Feuer authored
      Now that `($)` is representation-polymorphic, `($!)` should
      surely follow suit.
      
      Reviewers: hvr, bgamari, simonpj
      
      Reviewed By: bgamari, simonpj
      
      Subscribers: simonpj, rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4382
      c9a88db3
  8. Feb 12, 2018
  9. Feb 10, 2018
  10. Feb 08, 2018
    • Simon Peyton Jones's avatar
      Fix isDroppableCt (Trac #14763) · 6edafe3b
      Simon Peyton Jones authored
      When finishing up an implication constraint, it's a bit tricky to
      decide which Derived constraints to retain (for error reporting) and
      which to discard.  I got this wrong in commit
         f20cf982
         (Remove wc_insol from WantedConstraints)
      
      The particular problem in Trac #14763 was that we were reporting as an
      error a fundep-generated constraint
        (ex ~ T)
      where 'ex' is an existentially-bound variable in a pattern match.
      But this isn't really an error at all.
      
      This patch fixes the problem. Indeed, since I had to understand
      this rather tricky code, I took the opportunity to clean it up
      and document better.  See
        isDroppableCt :: Ct -> Bool
      and Note [Dropping derived constraints]
      
      I also removed wl_deriv altogether from the WorkList data type.  It
      was there in the hope of gaining efficiency by not even processing
      lots of derived constraints, but it has turned out that most derived
      constraints (notably equalities) must be processed anyway; see
      Note [Prioritise equalities] in TcSMonad.
      
      The two are coupled because to decide which constraints to put in
      wl_deriv I was using another variant of isDroppableCt.  Now it's much
      simpler -- and perhaps even more efficient too.
      6edafe3b
    • Douglas Wilson's avatar
      rts: fix barf format attribute · 059596df
      Douglas Wilson authored and Tamar Christina's avatar Tamar Christina committed
      Summary: See definition of PRINTF above the change
      
      Reviewers: bgamari, erikd, simonmar, Phyx
      
      Reviewed By: Phyx
      
      Subscribers: Phyx, rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4392
      059596df
Loading