Skip to content
Snippets Groups Projects
  1. Apr 30, 2019
    • Travis Whitaker's avatar
      Correct closure observation, construction, and mutation on weak memory machines. · 49af1c8e
      Travis Whitaker authored
      Here the following changes are introduced:
          - A read barrier machine op is added to Cmm.
          - The order in which a closure's fields are read and written is changed.
          - Memory barriers are added to RTS code to ensure correctness on
            out-or-order machines with weak memory ordering.
      
      Cmm has a new CallishMachOp called MO_ReadBarrier. On weak memory machines, this
      is lowered to an instruction that ensures memory reads that occur after said
      instruction in program order are not performed before reads coming before said
      instruction in program order. On machines with strong memory ordering properties
      (e.g. X86, SPARC in TSO mode) no such instruction is necessary, so
      MO_ReadBarrier is simply erased. However, such an instruction is necessary on
      weakly ordered machines, e.g. ARM and PowerPC.
      
      Weam memory ordering has consequences for how closures are observed and mutated.
      For example, consider a closure that needs to be updated to an indirection. In
      order for the indirection to be safe for concurrent observers to enter, said
      observers must read the indirection's info table before they read the
      indirectee. Furthermore, the entering observer makes assumptions about the
      closure based on its info table contents, e.g. an INFO_TYPE of IND imples the
      closure has an indirectee pointer that is safe to follow.
      
      When a closure is updated with an indirection, both its info table and its
      indirectee must be written. With weak memory ordering, these two writes can be
      arbitrarily reordered, and perhaps even interleaved with other threads' reads
      and writes (in the absence of memory barrier instructions). Consider this
      example of a bad reordering:
      
      - An updater writes to a closure's info table (INFO_TYPE is now IND).
      - A concurrent observer branches upon reading the closure's INFO_TYPE as IND.
      - A concurrent observer reads the closure's indirectee and enters it. (!!!)
      - An updater writes the closure's indirectee.
      
      Here the update to the indirectee comes too late and the concurrent observer has
      jumped off into the abyss. Speculative execution can also cause us issues,
      consider:
      
      - An observer is about to case on a value in closure's info table.
      - The observer speculatively reads one or more of closure's fields.
      - An updater writes to closure's info table.
      - The observer takes a branch based on the new info table value, but with the
        old closure fields!
      - The updater writes to the closure's other fields, but its too late.
      
      Because of these effects, reads and writes to a closure's info table must be
      ordered carefully with respect to reads and writes to the closure's other
      fields, and memory barriers must be placed to ensure that reads and writes occur
      in program order. Specifically, updates to a closure must follow the following
      pattern:
      
      - Update the closure's (non-info table) fields.
      - Write barrier.
      - Update the closure's info table.
      
      Observing a closure's fields must follow the following pattern:
      
      - Read the closure's info pointer.
      - Read barrier.
      - Read the closure's (non-info table) fields.
      
      This patch updates RTS code to obey this pattern. This should fix long-standing
      SMP bugs on ARM (specifically newer aarch64 microarchitectures supporting
      out-of-order execution) and PowerPC. This fixesd issue #15449.
      49af1c8e
  2. Apr 09, 2019
  3. Apr 08, 2019
    • Ryan Scott's avatar
      Bump hpc submodule · cf9e1837
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      Currently, the `hpc` submodule is pinned against the `wip/final-mfp`
      branch, not against `master`. This pins it back against `master`.
      cf9e1837
    • John Ericson's avatar
      settings.in: Reformat · f5604d37
      John Ericson authored and Marge Bot's avatar Marge Bot committed
      We're might be about to switch to generating it in Hadrian/Make. This
      reformat makes it easier to programmingmatically generate and end up
      with the exact same thing, which is good for diffing to ensure no
      regressions.
      
      I had this as part of !712, but given the difficulty of satisfying CI, I
      figured I should break things up even further.
      f5604d37
    • Ömer Sinan Ağacan's avatar
      testsuite: Show exit code of GHCi tests on failure · 7287bb9e
      Ömer Sinan Ağacan authored and Marge Bot's avatar Marge Bot committed
      7287bb9e
    • Ömer Sinan Ağacan's avatar
      Skip test ArithInt16 and ArithWord16 in GHCi way · 1085090e
      Ömer Sinan Ağacan authored and Marge Bot's avatar Marge Bot committed
      These tests use unboxed tuples, which GHCi doesn't support
      1085090e
    • Sebastian Graf's avatar
      Make `singleConstructor` cope with pattern synonyms · d236d9d0
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      Previously, `singleConstructor` didn't handle singleton `COMPLETE` sets
      of a single pattern synonym, resulting in incomplete pattern warnings
      in #15753.
      
      This is fixed by making `singleConstructor` (now named
      `singleMatchConstructor`) query `allCompleteMatches`, necessarily making
      it effectful. As a result, most of this patch is concerned with
      threading the side-effect through to `singleMatchConstructor`.
      
      Unfortunately, this is not enough to completely fix the original
      reproduction from #15753 and #15884, which are related to function
      applications in pattern guards being translated too conservatively.
      d236d9d0
    • Matthew Pickering's avatar
      Use ./hadrian/ghci.sh in .ghcid · 4dda2270
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      4dda2270
    • Yuriy Syrovetskiy's avatar
      Fix whitespace style · a42d206a
      Yuriy Syrovetskiy authored and Marge Bot's avatar Marge Bot committed
      a42d206a
    • Ben Gamari's avatar
      testsuite: Unmark T16190 as broken · 97d3d546
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Was broken via #16389 yet strangely it has started passing despite the
      fact that the suggested root cause has not changed.
      97d3d546
    • Yuriy Syrovetskiy's avatar
      Add `-optcxx` option (#16477) · 97502be8
      Yuriy Syrovetskiy authored and Marge Bot's avatar Marge Bot committed
      97502be8
    • Phuong Trinh's avatar
      Fix #16500: look for interface files in -hidir flag in OneShot mode · 2b3f4718
      Phuong Trinh authored and Marge Bot's avatar Marge Bot committed
      We are currently ignoring options set in the hiDir field of hsc_dflags
      when looking for interface files while compiling in OneShot mode. This
      is inconsistent with the behaviour of other directory redirecting fields
      (such as objectDir or hieDir). It is also inconsistent with the
      behaviour of compilation in CompManager mode (a.k.a `ghc --make`) which
      looks for interface files in the directory set in hidir flag. This
      changes Finder.hs so that we use the value of hiDir while looking for
      interface in OneShot mode.
      2b3f4718
    • Michal Terepeta's avatar
      Generate straightline code for inline array allocation · 63b7d5fb
      Michal Terepeta authored and Marge Bot's avatar Marge Bot committed
      
      GHC has an optimization for allocating arrays when the size is
      statically known -- it'll generate the code allocating and initializing
      the array inline (instead of a call to a procedure from
      `rts/PrimOps.cmm`).
      
      However, the generated code uses a loop to do the initialization. Since
      we already check that the requested size is small (we check against
      `maxInlineAllocSize`), we can generate faster straightline code instead.
      This brings about 15% improvement for `newSmallArray#` in my testing and
      slightly simplifies the code in GHC.
      
      Signed-off-by: default avatarMichal Terepeta <michal.terepeta@gmail.com>
      63b7d5fb
  4. Apr 07, 2019
    • Eric Crockett's avatar
      Fix #16282. · 3a38ea44
      Eric Crockett authored and Ben Gamari's avatar Ben Gamari committed
      Previously, -W(all-)missed-specs was created with 'NoReason',
      so no information about the flag was printed along with the warning.
      Now, -Wall-missed-specs is listed as the Reason if it was set,
      otherwise -Wmissed-specs is listed as the reason.
      3a38ea44
  5. Apr 04, 2019
    • Ryan Scott's avatar
      Tweak error messages for narrowly-kinded assoc default decls · 33b0a291
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      This program, from #13971, currently has a rather confusing error
      message:
      
      ```hs
      class C a where
        type T a :: k
        type T a = Int
      ```
      ```
          • Kind mis-match on LHS of default declaration for ‘T’
          • In the default type instance declaration for ‘T’
            In the class declaration for ‘C’
      ```
      
      It's not at all obvious why GHC is complaining about the LHS until
      you realize that the default, when printed with
      `-fprint-explicit-kinds`, is actually `type T @{k} @* a = Int`.
      That is to say, the kind of `a` is being instantiated to `Type`,
      whereas it ought to be a kind variable. The primary thrust of this
      patch is to weak the error message to make this connection
      more obvious:
      
      ```
          • Illegal argument ‘*’ in:
              ‘type T @{k} @* a = Int’
              The arguments to ‘T’ must all be type variables
          • In the default type instance declaration for ‘T’
            In the class declaration for ‘C’
      ```
      
      Along the way, I performed some code cleanup suggested by @rae in
      ghc/ghc#13971 (comment 191287). Before,
      we were creating a substitution from the default declaration's type
      variables to the type family tycon's type variables by way of
      `tcMatchTys`. But this is overkill, since we already know (from the
      aforementioned validity checking) that all the arguments in a default
      declaration must be type variables anyway. Therefore, creating the
      substitution is as simple as using `zipTvSubst`. I took the
      opportunity to perform this refactoring while I was in town.
      
      Fixes #13971.
      33b0a291
    • Andreas Klebinger's avatar
      Restore Xmm registers properly in StgCRun.c · cbb88865
      Andreas Klebinger authored and Marge Bot's avatar Marge Bot committed
      This fixes #16514: Xmm6-15 was restored based off rax instead of rsp.
      The code was introduced in the fix for #14619.
      cbb88865
    • Ben Gamari's avatar
      testsuite: Add testcase for #16111 · 6c0dd085
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      6c0dd085
    • Ryan Scott's avatar
      Use funPrec, not topPrec, to parenthesize GADT argument types · 51fd3571
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      A simple oversight. Fixes #16527.
      51fd3571
    • Ryan Scott's avatar
      Fix #16518 with some more kind-splitting smarts · 25c02ea1
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      This patch corrects two simple oversights that led to #16518:
      
      1. `HsUtils.typeToLHsType` was taking visibility into account in the
         `TyConApp` case, but not the `AppTy` case. I've factored out the
         visibility-related logic into its own `go_app` function and now
         invoke `go_app` from both the `TyConApp` and `AppTy` cases.
      2. `Type.fun_kind_arg_flags` did not properly split kinds with
         nested `forall`s, such as
         `(forall k. k -> Type) -> (forall k. k -> Type)`. This was simply
         because `fun_kind_arg_flags`'s `FunTy` case always bailed out and
         assumed all subsequent arguments were `Required`, which clearly
         isn't the case for nested `forall`s. I tweaked the `FunTy` case
         to recur on the result kind.
      25c02ea1
    • Yuriy Syrovetskiy's avatar
      Replace git.haskell.org with gitlab.haskell.org (#16196) · 75abaaea
      Yuriy Syrovetskiy authored and Marge Bot's avatar Marge Bot committed
      75abaaea
  6. Apr 03, 2019
    • Ben Gamari's avatar
      gitlab: Fix label names in issue templates · 895394c2
      Ben Gamari authored
      895394c2
    • Ben Gamari's avatar
      gitlab-ci: Build hyperlinked sources for releases · 6f13e7b1
      Ben Gamari authored
      Fixes #16445.
      6f13e7b1
    • Sebastian Graf's avatar
      Fix Uncovered set of literal patterns · 4626cf21
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      Issues #16289 and #15713 are proof that the pattern match checker did
      an unsound job of estimating the value set abstraction corresponding to
      the uncovered set.
      
      The reason is that the fix from #11303 introducing `NLit` was
      incomplete: The `LitCon` case desugared to `Var` rather than `LitVar`,
      which would have done the necessary case splitting analogous to the
      `ConVar` case.
      
      This patch rectifies that by introducing the fresh unification variable
      in `LitCon` in value abstraction position rather than pattern postition,
      recording a constraint equating it to the constructor expression rather
      than the literal. Fixes #16289 and #15713.
      4626cf21
    • Ben Gamari's avatar
      configure: Always use AC_LINK_ELSEIF when testing against assembler · 7b090b53
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      This fixes #16440, where the build system incorrectly concluded that the
      `.subsections_via_symbols` assembler directive was supported on a Linux
      system. This was caused by the fact that gcc was invoked with `-flto`;
      when so-configured gcc does not call the assembler but rather simply
      serialises its AST for compilation during the final link.
      
      This is described in Note [autoconf assembler checks and -flto].
      7b090b53
    • Chris Martin's avatar
      Inline the definition of 'ap' in the Monad laws · bf6dbe3d
      Chris Martin authored and Marge Bot's avatar Marge Bot committed
      The law as it is currently written is meaningless, because nowhere have
      we defined the implementation of 'ap'. The reader of the Control.Monad
      documentation is provided with only a type signature,
      
      > ap :: Monad m => m (a -> b) -> m a -> m b
      
      an informal description,
      
      > In many situations, the liftM operations can be replaced by uses of
      > ap, which promotes function application.
      
      and a relationship between 'ap' and the 'liftM' functions
      
      > return f `ap` x1 `ap` ... `ap` xn
      > is equivalent to
      > liftMn f x1 x2 ... xn
      
      Without knowing how 'ap' is defined, a law involving 'ap' cannot
      provide any guidance for how to write a lawful Monad instance, nor can
      we conclude anything from the law.
      
      I suspect that a reader equipped with the understanding that 'ap' was
      defined prior to the invention of the Applicative class could deduce
      that 'ap' must be defined in terms of (>>=), but nowhere as far as I can
      tell have we written this down explicitly for readers without the
      benefit of historical context.
      
      If the law is meant to express a relationship among (<*>), (>>=), and
      'return', it seems that it is better off making this statement directly,
      sidestepping 'ap' altogether.
      bf6dbe3d
    • Chris Martin's avatar
      Correct two misspellings of "separately" · 722fdddf
      Chris Martin authored and Marge Bot's avatar Marge Bot committed
      722fdddf
    • Ben Gamari's avatar
      integer-simple: Add documentation for Integer type · dd3a3d08
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      dd3a3d08
    • Ben Gamari's avatar
      integer-gmp: Write friendlier documentation for Integer · 3364def0
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      3364def0
    • Frank Steffahn's avatar
      users-guide: Typo in Users Guide, Glasgow Exts · 733f1b52
      Frank Steffahn authored and Marge Bot's avatar Marge Bot committed
      733f1b52
    • Andrew Martin's avatar
      base: Add documentation that liftA2 used to not be a typeclass method · ea192a09
      Andrew Martin authored and Marge Bot's avatar Marge Bot committed
      ea192a09
    • Nathan Collins's avatar
      users-guide: Fix typo · 2ec749b5
      Nathan Collins authored and Marge Bot's avatar Marge Bot committed
      2ec749b5
    • Andreas Klebinger's avatar
      Fix faulty substitutions in StgCse (#11532). · 5a75ccd0
      Andreas Klebinger authored and Marge Bot's avatar Marge Bot committed
      `substBndr` should rename bindings which shadow existing ids.
      However while it was renaming the bindings it was not adding proper substitutions
      for renamed bindings.
      Instead of adding a substitution of the form `old -> new` for renamed
      bindings it mistakenly added `old -> old` if no replacement had taken
      place while adding none if `old` had been renamed.
      
      As a byproduct this should improve performance, as we no longer add
      useless substitutions for unshadowed bindings.
      5a75ccd0
  7. Apr 02, 2019
Loading