Skip to content
Snippets Groups Projects
  1. Aug 09, 2023
    • Sebastian Graf's avatar
      Disable tests RepPolyWrappedVar2 and RepPolyUnsafeCoerce1 in JS backend · d8d993f1
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      ... because those coerce between incompatible/unknown PrimReps.
      d8d993f1
    • Sebastian Graf's avatar
      Core.Ppr: Omit case binder for empty case alternatives · 8c73505e
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      A minor improvement to pretty-printing
      8c73505e
    • Sebastian Graf's avatar
      Simplify: Simplification of arguments in a single function · d004a36d
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      The Simplifier had a function `simplArg` that wasn't called in `rebuildCall`,
      which seems to be the main way to simplify args. Hence I consolidated the code
      path to call `simplArg`, too, renaming to `simplLazyArg`.
      d004a36d
    • Sebastian Graf's avatar
      exprIsTrivial: Factor out shared implementation · ce8aa54c
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      The duplication between `exprIsTrivial` and `getIdFromTrivialExpr_maybe` has
      been bugging me for a long time.
      
      This patch introduces an inlinable worker function `trivial_expr_fold` acting
      as the single, shared decision procedure of triviality. It "returns" a
      Church-encoded `Maybe (Maybe Id)`, so when it is inlined, it fuses to similar
      code as before.
      (Better code, even, in the case of `getIdFromTrivialExpr` which presently
      allocates a `Just` constructor that cancels away after this patch.)
      ce8aa54c
    • Sebastian Graf's avatar
      More explicit strictness in GHC.Real · 2274abc8
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      2274abc8
    • Sebastian Graf's avatar
      Cleanup a TODO introduced in 1f94e0f7 · 1a98d673
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      The change must have slipped through review of !4412
      1a98d673
    • Alan Zimmerman's avatar
      EPA: Remove Location from WarningTxt source · 6eab07b2
      Alan Zimmerman authored and Marge Bot's avatar Marge Bot committed
      This is not needed.
      6eab07b2
    • Fraser Tweedale's avatar
      numberToRangedRational: fix edge cases for exp ≈ (maxBound :: Int) · 4bc7b1e5
      Fraser Tweedale authored and Marge Bot's avatar Marge Bot committed
      Currently a negative exponent less than `minBound :: Int` results in
      Infinity, which is very surprising and obviously wrong.
      
      ```
      λ> read "1e-9223372036854775808" :: Double
      0.0
      λ> read "1e-9223372036854775809" :: Double
      Infinity
      ```
      
      There is a further edge case where the exponent can overflow when
      increased by the number of tens places in the integer part, or
      underflow when decreased by the number of leading zeros in the
      fractional part if the integer part is zero:
      
      ```
      λ> read "10e9223372036854775807" :: Double
      0.0
      λ> read "0.01e-9223372036854775808" :: Double
      Infinity
      ```
      
      To resolve both of these issues, perform all arithmetic and
      comparisons involving the exponent in type `Integer`.  This approach
      also eliminates the need to explicitly check the exponent against
      `maxBound :: Int` and `minBound :: Int`, because the allowed range
      of the exponent (i.e. the result of `floatRange` for the target
      floating point type) is certainly within those bounds.
      
      This change implements CLC proposal 192:
      https://github.com/haskell/core-libraries-committee/issues/192
      4bc7b1e5
    • sheaf's avatar
      Compute all emitted diagnostic codes · 0ef1d8ae
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit introduces in GHC.Types.Error.Codes the function
      
        constructorCodes :: forall diag. (...) => Map DiagnosticCode String
      
      which computes a collection of all the diagnostic codes that correspond
      to a particular type. In particular, we can compute the collection of
      all diagnostic codes emitted by GHC using the invocation
      
        constructorCodes @GhcMessage
      
      We then make use of this functionality in the new "codes" test which
      checks consistency and coverage of GHC diagnostic codes.
      It performs three checks:
      
        - check 1: all non-outdated GhcDiagnosticCode equations
          are statically used.
        - check 2: all outdated GhcDiagnosticCode equations
          are statically unused.
        - check 3: all statically used diagnostic codes are covered by
          the testsuite (modulo accepted exceptions).
      0ef1d8ae
  2. Aug 08, 2023
    • Ryan Scott's avatar
      tcExpr: Push expected types for untyped TH splices inwards · 3b373838
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      In !10911, I deleted a `tcExpr` case for `HsUntypedSplice` in favor of a much
      simpler case that simply delegates to `tcApp`. Although this passed the test
      suite at the time, this was actually an error, as the previous `tcExpr` case
      was critically pushing the expected type inwards. This actually matters for
      programs like the one in #23796, which GHC would not accept with type inference
      alone—we need full-blown type _checking_ to accept these.
      
      I have added back the previous `tcExpr` case for `HsUntypedSplice` and now
      explain why we have two different `HsUntypedSplice` cases (one in `tcExpr` and
      another in `splitHsApps`) in `Note [Looking through Template Haskell splices in
      splitHsApps]` in `GHC.Tc.Gen.Head`.
      
      Fixes #23796.
      3b373838
    • Ben Gamari's avatar
      configure: Derive library version from ghc-prim.cabal.in · 01961be3
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Since ghc-prim.cabal is now generated by Hadrian, we cannot depend upon
      it.
      
      Closes #23726.
      01961be3
  3. Aug 07, 2023
  4. Aug 05, 2023
    • Luite Stegeman's avatar
      JS: Improve compatibility with recent emsdk · aa07402e
      Luite Stegeman authored
      The JavaScript code in libraries/base/jsbits/base.js had some
      hardcoded offsets for fields in structs, because we expected
      the layout of the data structures to remain unchanged. Emsdk
      3.1.42 changed the layout of the stat struct, breaking this
      assumption, and causing code in .hsc files accessing the
      stat struct to fail.
      
      This patch improves compatibility with recent emsdk by
      removing the assumption that data layouts stay unchanged:
      
          1. offsets of fields in structs used by JavaScript code are
             now computed by the configure script, so both the .js and
             .hsc files will automatically use the new layout if anything
             changes.
          2. the distrib/configure script checks that the emsdk version
             on a user's system is the same version that a bindist was
             booted with, to avoid data layout inconsistencies
      
      See #23641
      aa07402e
    • Ben Gamari's avatar
      Bump nofib submodule · 19dea673
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Ensuring that nofib can be build using the same range of bootstrap
      compilers as GHC itself.
      19dea673
    • sheaf's avatar
      Remove zonk in tcVTA · 8d686854
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This removes the zonk in GHC.Tc.Gen.App.tc_inst_forall_arg and its
      accompanying Note [Visible type application zonk]. Indeed, this zonk
      is no longer necessary, as we no longer maintain the invariant that
      types are well-kinded without zonking; only that typeKind does not
      crash; see Note [The Purely Kinded Type Invariant (PKTI)].
      
      This commit removes this zonking step (as well as a secondary zonk),
      and replaces the aforementioned Note with the explanatory
      Note [Type application substitution], which justifies why the
      substitution performed in tc_inst_forall_arg remains valid without
      this zonking step.
      
      Fixes #23661
      8d686854
    • Ben Gamari's avatar
      Initial commit of Note [Thunks, blackholes, and indirections] · 91353622
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      This Note attempts to summarize the treatment of thunks, thunk update,
      and indirections.
      
      This fell out of work on #23185.
      91353622
    • Matthew Craven's avatar
      Bump bytestring submodule to 0.11.5.1 · 43578d60
      Matthew Craven authored and Marge Bot's avatar Marge Bot committed
      43578d60
  5. Aug 04, 2023
    • sheaf's avatar
      Update inert_solved_dicts for ImplicitParams · 41bf2c09
      sheaf authored and Marge Bot's avatar Marge Bot committed
      When adding an implicit parameter dictionary to the inert set, we must
      make sure that it replaces any previous implicit parameter dictionaries
      that overlap, in order to get the appropriate shadowing behaviour, as in
      
        let ?x = 1 in let ?x = 2 in ?x
      
      We were already doing this for inert_cans, but we weren't doing the same
      thing for inert_solved_dicts, which lead to the bug reported in #23761.
      
      The fix is thus to make sure that, when handling an implicit parameter
      dictionary in updInertDicts, we update **both** inert_cans and
      inert_solved_dicts to ensure a new implicit parameter dictionary
      correctly shadows old ones.
      
      Fixes #23761
      41bf2c09
    • Matthew Craven's avatar
      Adjust and clarify handling of primop effects · 8ba20b21
      Matthew Craven authored and Marge Bot's avatar Marge Bot committed
      Fixes #17900; fixes #20195.
      
      The existing "can_fail" and "has_side_effects" primop attributes
      that previously governed this were used in inconsistent and
      confusingly-documented ways, especially with regard to raising
      exceptions.  This patch replaces them with a single "effect"
      attribute, which has four possible values: NoEffect, CanFail,
      ThrowsException, and ReadWriteEffect.  These are described in
      Note [Classifying primop effects].
      
      A substantial amount of related documentation has been re-drafted
      for clarity and accuracy.
      
      In the process of making this attribute format change for literally
      every primop, several existing mis-classifications were detected and
      corrected.  One of these mis-classifications was tagToEnum#, which
      is now considered CanFail; this particular fix is known to cause a
      regression in performance for derived Enum instances.  (See #23782.)
      Fixing this is left as future work.
      
      New primop attributes "cheap" and "work_free" were also added,
      and used in the corresponding parts of GHC.Core.Utils.
      
      In view of their actual meaning and uses, `primOpOkForSideEffects`
      and `exprOkForSideEffects` have been renamed to `primOpOkToDiscard`
      and `exprOkToDiscard`, respectively.
      
      Metric Increase:
          T21839c
      8ba20b21
    • Ben Gamari's avatar
      ghc-platform: Add upper bound on base · 3ac423b9
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Hackage upload requires this.
      3ac423b9
    • Alan Zimmerman's avatar
      EPA make getLocA a synonym for getHasLoc · de25487d
      Alan Zimmerman authored and Marge Bot's avatar Marge Bot committed
      This is basically a no-op change, but allows us to make future changes
      that can rely on the HasLoc instances
      
      And I presume this means we can use more precise functions based on
      class resolution, so the Windows CI build reports
      
      Metric Decrease:
          T12234
          T13035
      de25487d
    • Rodrigo Mesquita's avatar
      Improve ghc-toolchain validation configure warning · 03f2debd
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      Fixes the layout of the ghc-toolchain validation warning produced by
      configure.
      03f2debd
    • Aaron Allen's avatar
      [#23663] Show Flag Suggestions in GHCi · a1899d8f
      Aaron Allen authored and Marge Bot's avatar Marge Bot committed
      Makes suggestions when using `:set` in GHCi with a misspelled flag. This
      mirrors how invalid flags are handled when passed to GHC directly. Logic
      for producing flag suggestions was moved to GHC.Driver.Sesssion so it
      can be shared.
      
      resolves #23663
      a1899d8f
    • Vladislav Zavialov's avatar
      Fix (~) and (@) infix operators in TH splices (#23748) · 46fd8ced
      Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
      8168b42a "Whitespace-sensitive bang patterns" allows GHC to accept
      the following infix operators:
      
      	a ~ b = ()
      	a @ b = ()
      
      But not if TH is used to generate those declarations:
      
      	$([d| a ~ b = ()
      	      a @ b = ()
      	    |])
      
      	-- Test.hs:5:2: error: [GHC-55017]
      	--    Illegal variable name: ‘~’
      	--    When splicing a TH declaration: (~_0) a_1 b_2 = GHC.Tuple.Prim.()
      
      This is easily fixed by modifying `reservedOps` in GHC.Utils.Lexeme
      46fd8ced
    • Jan Hrček's avatar
      Fix haddock markup in code example for coerce · 1b15dbc4
      Jan Hrček authored and Marge Bot's avatar Marge Bot committed
      1b15dbc4
    • Ben Gamari's avatar
      nativeGen/AArch64: Fix sign extension in MulMayOflo · 824092f2
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Previously the 32-bit implementations of MulMayOflo would use the
      a non-sensical sign-extension mode. Rewrite these to reflect what gcc 11
      produces. Also similarly rework the 16- and 8-bit cases.
      
      This now passes the MulMayOflo tests in ghc/test-primops> in all four
      widths, including the precision tests.
      
      Fixes #23721.
      824092f2
    • Ben Gamari's avatar
      testsuite: Mark MulMayOflo_full as broken rather than skipping · fd7ce39c
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      To ensure that we don't accidentally fix it.
      
      See #23742.
      fd7ce39c
    • Ben Gamari's avatar
      linker/PEi386: Don't sign-extend symbol section number · 0eb54c05
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Previously we incorrectly interpreted PE section numbers as signed
      values. However, this isn't the case; rather, it's an unsigned 16-bit number
      with a few special bit-patterns (0xffff and 0xfffe). This resulted in #22941
      as the linker would conclude that the sections were invalid.
      
      Fixing this required quite a bit of refactoring.
      
      Closes #22941.
      0eb54c05
    • Ben Gamari's avatar
      testsuite/interface-stability: normalise versions · 4b647936
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      This eliminates spurious changes from version bumps.
      4b647936
    • Ben Gamari's avatar
      testsuite: Update base-exports · 8b176514
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      8b176514
    • Ben Gamari's avatar
      gitlab-ci: Only mark linker_unload_native as broken in static jobs · e75a58d1
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      This test passes on dynamically-linked Alpine.
      
      (cherry picked from commit f356a7e8)
      e75a58d1
    • Ben Gamari's avatar
      testsuite: Declare bkpcabal08 as fragile · d52be957
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Due to spurious output changes described in #23648.
      
      (cherry picked from commit c046a238)
      d52be957
    • Ben Gamari's avatar
      testsuite: Normalise versions more aggressively · 3ab5efd9
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      In backpack hashes can contain `+` characters.
      
      (cherry picked from commit 024861af)
      3ab5efd9
    • Ben Gamari's avatar
      base: Bump version to 4.19 · 1211112a
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Updates all boot library submodules.
      
      (cherry picked from commit 433d99a3)
      1211112a
    • Ben Gamari's avatar
      template-haskell: Bump version to 2.21.0.0 · 83766dbf
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Bumps exceptions submodule.
      
      (cherry picked from commit bf57fc9a)
      83766dbf
    • Ben Gamari's avatar
      configure: Bump minimal boot GHC version to 9.4 · cebb5819
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      (cherry picked from commit d3ffdaf9)
      cebb5819
    • Ben Gamari's avatar
      Bump deepseq submodule to 1.5. · e77a0b41
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      And bump bounds
      
      (cherry picked from commit 1228d3a4)
      e77a0b41
    • Ryan Scott's avatar
      Look through TH splices in splitHsApps · fdef003a
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      This modifies `splitHsApps` (a key function used in typechecking function
      applications) to look through untyped TH splices and quasiquotes. Not doing so
      was the cause of #21077. This builds on !7821 by making `splitHsApps` match on
      `HsUntypedSpliceTop`, which contains the `ThModFinalizers` that must be run as
      part of invoking the TH splice. See the new `Note [Looking through Template
      Haskell splices in splitHsApps]` in `GHC.Tc.Gen.Head`.
      
      Along the way, I needed to make the type of `splitHsApps.set` slightly more
      general to accommodate the fact that the location attached to a quasiquote is
      a `SrcAnn NoEpAnns` rather than a `SrcSpanAnnA`.
      
      Fixes #21077.
      fdef003a
Loading