Skip to content
Snippets Groups Projects
  1. Mar 29, 2023
    • sheaf's avatar
      Handle records in the renamer · 3f374399
      sheaf authored
      This patch moves the field-based logic for disambiguating record updates
      to the renamer. The type-directed logic, scheduled for removal, remains
      in the typechecker.
      
      To do this properly (and fix the myriad of bugs surrounding the treatment
      of duplicate record fields), we took the following main steps:
      
        1. Create GREInfo, a renamer-level equivalent to TyThing which stores
           information pertinent to the renamer.
           This allows us to uniformly treat imported and local Names in the
           renamer, as described in Note [GREInfo].
      
        2. Remove GreName. Instead of a GlobalRdrElt storing GreNames, which
           distinguished between normal names and field names, we now store
           simple Names in GlobalRdrElt, along with the new GREInfo information
           which allows us to recover the FieldLabel for record fields.
      
        3. Add namespacing for record fields, within the OccNames themselves.
           This allows us to remove the mangling of duplicate field selectors.
      
           This change ensures we don't print mangled names to the user in
           error messages, and allows us to handle duplicate record fields
           in Template Haskell.
      
        4. Move record disambiguation to the renamer, and operate on the
           level of data constructors instead, to handle #21443.
      
           The error message text for ambiguous record updates has also been
           changed to reflect that type-directed disambiguation is on the way
           out.
      
      (3) means that OccEnv is now a bit more complex: we first key on the
      textual name, which gives an inner map keyed on NameSpace:
      
        OccEnv a ~ FastStringEnv (UniqFM NameSpace a)
      
      Note that this change, along with (2), both increase the memory residency
      of GlobalRdrEnv = OccEnv [GlobalRdrElt], which causes a few tests to
      regress somewhat in compile-time allocation.
      
      Even though (3) simplified a lot of code (in particular the treatment of
      field selectors within Template Haskell and in error messages), it came
      with one important wrinkle: in the situation of
      
        -- M.hs-boot
        module M where { data A; foo :: A -> Int }
        -- M.hs
        module M where { data A = MkA { foo :: Int } }
      
      we have that M.hs-boot exports a variable foo, which is supposed to match
      with the record field foo that M exports. To solve this issue, we add a
      new impedance-matching binding to M
      
        foo{var} = foo{fld}
      
      This mimics the logic that existed already for impedance-binding DFunIds,
      but getting it right was a bit tricky.
      See Note [Record field impedance matching] in GHC.Tc.Module.
      
      We also needed to be careful to avoid introducing space leaks in GHCi.
      So we dehydrate the GlobalRdrEnv before storing it anywhere, e.g. in
      ModIface. This means stubbing out all the GREInfo fields, with the
      function forceGlobalRdrEnv.
      When we read it back in, we rehydrate with rehydrateGlobalRdrEnv.
      This robustly avoids any space leaks caused by retaining old type
      environments.
      
      Fixes #13352 #14848 #17381 #17551 #19664 #21443 #21444 #21720 #21898 #21946 #21959 #22125 #22160 #23010 #23062 #23063
      
      Updates haddock submodule
      
      -------------------------
      Metric Increase:
          MultiComponentModules
          MultiLayerModules
          MultiLayerModulesDefsGhci
          MultiLayerModulesNoCode
          T13701
          T14697
          hard_hole_fits
      -------------------------
      3f374399
  2. Mar 28, 2023
  3. Mar 27, 2023
    • Simon Peyton Jones's avatar
      Make exprIsConApp_maybe a bit cleverer · c1f755c4
      Simon Peyton Jones authored
      Addresses #23159.
      
      See Note Note [Exploit occ-info in exprIsConApp_maybe]
      in GHC.Core.SimpleOpt.
      
      Compile times go down very slightly, but always go down,
      never up.  Good!
      
      Metrics: compile_time/bytes allocated
      ------------------------------------------------
       CoOpt_Singletons(normal)   -1.8%
                 T15703(normal)   -1.2% GOOD
      
                      geo. mean   -0.1%
                      minimum     -1.8%
                      maximum     +0.0%
      
      Metric Decrease:
          CoOpt_Singletons
          T15703
      c1f755c4
  4. Mar 26, 2023
  5. Mar 25, 2023
  6. Mar 24, 2023
    • Ben Gamari's avatar
      codeGen/tsan: Disable instrumentation of unaligned stores · 509d1f11
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      There is some disagreement regarding the prototype of
      `__tsan_unaligned_write` (specifically whether it takes just the written
      address, or the address and the value as an argument). Moreover, I have
      observed crashes which appear to be due to it. Disable instrumentation
      of unaligned stores as a temporary mitigation.
      
      Fixes #23096.
      509d1f11
    • Joachim Breitner's avatar
      User's guide: Improve docs for -Wall · 46120bb6
      Joachim Breitner authored and Marge Bot's avatar Marge Bot committed
      previously it would list the warnings _not_ enabled by -Wall. That’s
      unnecessary round-about and was out of date. So let's just name
      the relevant warnings (based on `compiler/GHC/Driver/Flags.hs`).
      46120bb6
    • Ben Gamari's avatar
      nativeGen/AArch64: Fix bitmask immediate predicate · b8d783d2
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Previously the predicate for determining whether a logical instruction
      operand could be encoded as a bitmask immediate was far too
      conservative. This meant that, e.g., pointer untagged required five
      instructions whereas it should only require one.
      
      Fixes #23030.
      b8d783d2
    • Adam Gundry's avatar
      Move mention of warning groups change to 9.8.1 release notes · 0426515b
      Adam Gundry authored and Marge Bot's avatar Marge Bot committed
      0426515b
    • Adam Gundry's avatar
      Allow WARNING pragmas to be controlled with custom categories · f932c589
      Adam Gundry authored and Marge Bot's avatar Marge Bot committed
      Closes #17209. This implements GHC Proposal 541, allowing a WARNING
      pragma to be annotated with a category like so:
      
          {-# WARNING in "x-partial" head "This function is undefined on empty lists." #-}
      
      The user can then enable, disable and set the severity of such warnings
      using command-line flags `-Wx-partial`, `-Werror=x-partial` and so on.  There
      is a new warning group `-Wextended-warnings` containing all these warnings.
      Warnings without a category are treated as if the category was `deprecations`,
      and are (still) controlled by the flags `-Wdeprecations`
      and `-Wwarnings-deprecations`.
      
      Updates Haddock submodule.
      f932c589
  7. Mar 23, 2023
  8. Mar 22, 2023
    • Sylvain Henry's avatar
      Testsuite: use js_skip for T2615 (#22374) · 30d45e97
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      30d45e97
    • Torsten Schmits's avatar
      Add structured error messages for GHC.Tc.Utils.TcMType · cedf9a3b
      Torsten Schmits authored and Marge Bot's avatar Marge Bot committed
      Tracking ticket: #20119
      
      MR: !10138
      
      This converts uses of `mkTcRnUnknownMessage` to newly added constructors
      of `TcRnMessage`.
      cedf9a3b
    • Simon Peyton Jones's avatar
      Refactor the constraint solver pipeline · e0b8eaf3
      Simon Peyton Jones authored
      The big change is to put the entire type-equality solver into
      GHC.Tc.Solver.Equality, rather than scattering it over Canonical
      and Interact.  Other changes
      
      * EqCt becomes its own data type, a bit like QCInst.  This is
        great because EqualCtList is then just [EqCt]
      
      * New module GHC.Tc.Solver.Dict has come of the class-contraint
        solver.  In due course it will be all.  One step at a time.
      
      This MR is intended to have zero change in behaviour: it is a
      pure refactor.  It opens the way to subsequent tidying up, we
      believe.
      e0b8eaf3
    • Sylvain Henry's avatar
      Testsuite: use req_interp predicate for T20214 · ad765b6f
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      ad765b6f
    • Sylvain Henry's avatar
      Testsuite: use req_interp predicate for T16318 (#22370) · a1528b68
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      a1528b68
    • Rodrigo Mesquita's avatar
      fix: Incorrect @since annotations in GHC.TypeError · 048c881e
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      Fixes #23128
      048c881e
    • Sylvain Henry's avatar
      Testsuite: use appropriate predicate for ManyUbxSums test (#22576) · 0ab0cc11
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      0ab0cc11
    • Simon Peyton Jones's avatar
      Be more careful about quantification · 926ad6de
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      This MR is driven by #23051. It does several things:
      
      * It is guided by the generalisation plan described in #20686.
        But it is still far from a complete implementation of that plan.
      
      * Add Note [Inferred type with escaping kind] to GHC.Tc.Gen.Bind.
        This explains that we don't (yet, pending #20686) directly
        prevent generalising over escaping kinds.
      
      * In `GHC.Tc.Utils.TcMType.defaultTyVar` we default RuntimeRep
        and Multiplicity variables, beause we don't want to quantify over
        them.  We want to do the same for a Concrete tyvar, but there is
        nothing sensible to default it to (unless it has kind RuntimeRep,
        in which case it'll be caught by an earlier case). So we promote
        instead.
      
      * Pure refactoring in GHC.Tc.Solver:
        * Rename decideMonoTyVars to decidePromotedTyVars, since that's
          what it does.
      
        * Move the actual promotion of the tyvars-to-promote from
          `defaultTyVarsAndSimplify` to `decidePromotedTyVars`.  This is a
          no-op; just tidies up the code.  E.g then we don't need to
          return the promoted tyvars from `decidePromotedTyVars`.
      
        * A little refactoring in `defaultTyVarsAndSimplify`, but no
          change in behaviour.
      
      * When making a TauTv unification variable into a ConcreteTv
        (in GHC.Tc.Utils.Concrete.makeTypeConcrete), preserve the occ-name
        of the type variable.  This just improves error messages.
      
      * Kill off dead code: GHC.Tc.Utils.TcMType.newConcreteHole
      926ad6de
  9. Mar 21, 2023
Loading