Skip to content
Snippets Groups Projects
  1. May 25, 2023
  2. May 24, 2023
    • Magnus Viernickel's avatar
      [feat] add .direnv to the .gitignore file · f21ce0e4
      Magnus Viernickel authored and Marge Bot's avatar Marge Bot committed
      f21ce0e4
    • Rodrigo Mesquita's avatar
      configure: Fix support check for response files. · a320ca76
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      In failing to escape the '-o' in '-o\nconftest\nconftest.o\n' argument
      to printf, the writing of the arguments response file always failed.
      
      The fix is to pass the arguments after `--` so that they are treated
      positional arguments rather than flags to printf.
      
      Closes #23435
      a320ca76
    • Ben Gamari's avatar
      users guide: A few small mark-up fixes · eac4420a
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      eac4420a
    • Matthew Pickering's avatar
      rts: ticky: Rename TICK_ALLOC_HEAP_NOCTR to TICK_ALLOC_RTS · b2dabe3a
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      This macro increments the ALLOC_HEAP_tot and ALLOC_HEAP_ctr so it makes
      more sense to name it after that rather than the suffix NOCTR, whose
      meaning has been lost to the mists of time.
      b2dabe3a
    • Matthew Pickering's avatar
      rts: Define ticky macro stubs · 44af57de
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      These macros have long been undefined which has meant we were missing
      reporting these allocations in ticky profiles.
      
      The most critical missing definition was TICK_ALLOC_HEAP_NOCTR which was
      missing all the RTS calls to allocate, this leads to a the overall
      ALLOC_RTS_tot number to be severaly underreported.
      
      Of particular interest though is the ALLOC_STACK_ctr and ALLOC_STACK_tot
      counters which are useful to tracking stack allocations.
      
      Fixes #23421
      44af57de
    • Matthew Pickering's avatar
      Remove outdated "Don't check hs-boot type family instances too early" note · ae683454
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      This note was introduced in 25b70a29 which delayed performing some
      consistency checks for type families. However, the change was reverted
      later in 69987720 but the note was not
      removed.
      
      I found it confusing when reading to code to try and work out what
      special behaviour there was for hs-boot files (when in-fact there isn't
      any).
      ae683454
    • Krzysztof Gogolewski's avatar
      linear lint: Add missing processing of DEFAULT · 8539764b
      Krzysztof Gogolewski authored and Marge Bot's avatar Marge Bot committed
      In this correct program
      
      f :: a %1 -> a
      f x = case x of x { _DEFAULT -> x }
      
      after checking the alternative we weren't popping the case binder 'x'
      from the usage environment, which meant that the lambda-bound 'x'
      was counted twice: in the scrutinee and (incorrectly) in the alternative.
      In fact, we weren't checking the usage of 'x' at all.
      Now the code for handling _DEFAULT is similar to the one handling
      data constructors.
      
      Fixes #23025.
      8539764b
    • Hai Nguyen Quang's avatar
      Migrate errors in GHC.Tc.Validity · 838aaf4b
      Hai Nguyen Quang authored and Marge Bot's avatar Marge Bot committed
      This patch migrates the error messages in GHC.Tc.Validity to use
      the new diagnostic infrastructure.
      
      It adds the constructors:
      
        - TcRnSimplifiableConstraint
        - TcRnArityMismatch
        - TcRnIllegalInstanceDecl, with sub-datatypes for HasField errors
          and fundep coverage condition errors.
      838aaf4b
  3. May 23, 2023
    • Simon Peyton Jones's avatar
      Avoid an assertion failure in abstractFloats · 6abf3648
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      The function GHC.Core.Opt.Simplify.Utils.abstractFloats
      was carelessly calling lookupIdSubst_maybe on a CoVar;
      but a precondition of the latter is being given an Id.
      
      In fact it's harmless to call it on a CoVar, but still, the
      precondition on lookupIdSubst_maybe makes sense, so I added
      a test for CoVars.
      
      This avoids a crash in a DEBUG compiler, but otherwise has
      no effect. Fixes #23426.
      6abf3648
    • Simon Peyton Jones's avatar
      Add the SolverStage monad · e1590ddc
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      This refactoring makes a substantial improvement in the
      structure of the type-checker's constraint solver: #23070.
      
      Specifically:
      
      * Introduced the SolverStage monad.   See GHC.Tc.Solver.Monad
        Note [The SolverStage monad]
      
      * Make each solver pipeline (equalities, dictionaries, irreds etc)
        deal with updating the inert set, as a separate SolverStage.  There
        is sometimes special stuff to do, and it means that each full
        pipeline can have type SolverStage Void, indicating that they never
        return anything.
      
      * Made GHC.Tc.Solver.Equality.zonkEqTypes into a SolverStage.  Much nicer.
      
      * Combined the remnants of GHC.Tc.Solver.Canonical and
        GHC.Tc.Solver.Interact into a new module GHC.Tc.Solver.Solve.
        (Interact and Canonical are removed.)
      
      * Gave the same treatment to dictionary and irred constraints
        as I have already done for equality constraints:
          * New types (akin to EqCt): IrredCt and DictCt
          * Ct is now just a simple sum type
                data Ct
                  = CDictCan      DictCt
                  | CIrredCan     IrredCt
                  | CEqCan        EqCt
                  | CQuantCan     QCInst
                  | CNonCanonical CtEvidence
          * inert_dicts can now have the better type DictMap DictCt, instead of
            DictMap Ct; and similarly inert_irreds.
      
      * Significantly simplified the treatment of implicit parameters.
        Previously we had a number of special cases
          * interactGivenIP, an entire function
          * special case in maybeKickOut
          * special case in findDict, when looking up dictionaries
        But actually it's simpler than that. When adding a new Given, implicit
        parameter constraint to the InertSet, we just need to kick out any
        existing inert constraints that mention that implicit parameter.
      
        The main work is done in GHC.Tc.Solver.InertSet.delIPDict, along with
        its auxiliary GHC.Core.Predicate.mentionsIP.
      
        See Note [Shadowing of implicit parameters] in GHC.Tc.Solver.Dict.
      
      * Add a new fast-path in GHC.Tc.Errors.Hole.tcCheckHoleFit.
        See Note [Fast path for tcCheckHoleFit].  This is a big win in some cases:
        test hard_hole_fits gets nearly 40% faster (at compile time).
      
      * Add a new fast-path for solving /boxed/ equality constraints
        (t1 ~ t2).  See Note [Solving equality classes] in GHC.Tc.Solver.Dict.
        This makes a big difference too: test T17836 compiles 40% faster.
      
      * Implement the PermissivePlan of #23413, which concerns what happens with
        insoluble Givens.   Our previous treatment was wildly inconsistent as that
        ticket pointed out.
      
        A part of this, I simplified GHC.Tc.Validity.checkAmbiguity: now we simply
        don't run the ambiguity check at all if -XAllowAmbiguousTypes is on.
      
      Smaller points:
      
      * In `GHC.Tc.Errors.misMatchOrCND` instead of having a special case for
        insoluble /occurs/ checks, broaden in to all insouluble constraints.
        Just generally better. See Note [Insoluble mis-match] in that module.
      
      As noted above, compile time perf gets better.  Here are the changes
      over 0.5% on Fedora.  (The figures are slightly larger on Windows for
      some reason.)
      
      Metrics: compile_time/bytes allocated
      -------------------------------------
                      LargeRecord(normal)   -0.9%
      MultiLayerModulesTH_OneShot(normal)   +0.5%
                           T11822(normal)   -0.6%
                           T12227(normal)   -1.8% GOOD
                           T12545(normal)   -0.5%
                           T13035(normal)   -0.6%
                           T15703(normal)   -1.4% GOOD
                           T16875(normal)   -0.5%
                           T17836(normal)  -40.7% GOOD
                          T17836b(normal)  -12.3% GOOD
                          T17977b(normal)   -0.5%
                            T5837(normal)   -1.1%
                            T8095(normal)   -2.7% GOOD
                            T9020(optasm)   -1.1%
                   hard_hole_fits(normal)  -37.0% GOOD
      
                                geo. mean   -1.3%
                                minimum    -40.7%
                                maximum     +0.5%
      
      Metric Decrease:
          T12227
          T15703
          T17836
          T17836b
          T8095
          hard_hole_fits
          LargeRecord
          T9198
          T13035
      e1590ddc
    • Rodrigo Mesquita's avatar
      Merge outdated Note [Data con representation] into Note [Data constructor representation] · b8fe6a0c
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      Introduce new Note [Constructor applications in STG] to better support
      the merge, and reference it from the relevant bits in the STG syntax.
      b8fe6a0c
    • Rodrigo Mesquita's avatar
      Enforce invariant on typePrimRepArgs in the types · e54d9259
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      As part of the documentation effort in !10165 I came across this
      invariant on 'typePrimRepArgs' which is easily expressed at the
      type-level through a NonEmpty list.
      
      It allowed us to remove one panic.
      e54d9259
    • Rodrigo Mesquita's avatar
      Rename mkLFImported to importedIdLFInfo · e93ab972
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      The `mkLFImported` sounded too much like a constructor of sorts, when
      really it got the `LFInfo` of an imported Id from its `lf_info` field
      when this existed, and otherwise returned a conservative estimate of
      that imported Id's LFInfo. This in contrast to functions such as
      `mkLFReEntrant` which really are about constructing an `LFInfo`.
      e93ab972
    • Rodrigo Mesquita's avatar
      Update Note [Core letrec invariant] · 12294b22
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      Authored by @simonpj
      12294b22
    • Rodrigo Mesquita's avatar
      Make LFInfos for DataCons on construction · 0598f7f0
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      As a result of the discussion in !10165, we decided to amend the
      previous commit which fixed the logic of `mkLFImported` with regard to
      datacon workers and wrappers.
      
      Instead of having the logic for the LFInfo of datacons be in
      `mkLFImported`, we now construct an LFInfo for all data constructors on
      GHC.Types.Id.Make and store it in the `lfInfo` field.
      
      See the new Note [LFInfo of DataCon workers and wrappers] and
      ammendments to Note [The LFInfo of Imported Ids]
      0598f7f0
    • Rodrigo Mesquita's avatar
      codeGen: Fix LFInfo of imported datacon wrappers · 2fc18e9e
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      As noted in #23231 and in the previous commit, we were failing to give a
      an LFInfo of LFCon to a nullary datacon wrapper from another module,
      failing to properly tag pointers which ultimately led to the
      segmentation fault in #23146.
      
      On top of the previous commit which now considers wrappers where we
      previously only considered workers, we change the order of the guards so
      that we check for the arity of the binding before we check whether it is
      a constructor. This allows us to
      (1) Correctly assign `LFReEntrant` to imported wrappers whose worker was
      nullary, which we previously would fail to do
      (2) Remove the `isNullaryRepDataCon` predicate:
          (a) which was previously wrong, since it considered wrappers whose
          workers had zero-width arguments to be non-nullary and would fail to
          give `LFCon` to them
          (b) is now unnecessary, since arity == 0 guarantees
              - that the worker takes no arguments at all
              - and the wrapper takes no arguments and its RHS must be an
                application of the worker to zero-width-args only.
              - we lint these two items with an assertion that the datacon
                `hasNoNonZeroWidthArgs`
      
      We also update `isTagged` to use the new logic in determining the
      LFInfos of imported Ids.
      
      The creation of LFInfos for imported Ids and this detail are explained
      in Note [The LFInfo of Imported Ids].
      
      Note that before the patch to those issues we would already consider these
      nullary wrappers to have `LFCon` lambda form info; but failed to re-construct
      that information in `mkLFImported`
      
      Closes #23231, #23146
      
      (I've additionally batched some fixes to documentation I found while
      investigating this issue)
      2fc18e9e
    • Ben Gamari's avatar
      codeGen: Give proper LFInfo to datacon wrappers · 33a8c348
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      As noted in `Note [Conveying CAF-info and LFInfo between modules]`,
      when importing a binding from another module we must ensure that it gets
      the appropriate `LambdaFormInfo` if it is in WHNF to ensure that
      references to it are tagged correctly.
      
      However, the implementation responsible for doing this,
      `GHC.StgToCmm.Closure.mkLFImported`, only dealt with datacon workers and
      not wrappers. This lead to the crash of this program in #23146:
      
          module B where
      
          type NP :: [UnliftedType] -> UnliftedType
          data NP xs where
            UNil :: NP '[]
      
          module A where
          import B
      
          fieldsSam :: NP xs -> NP xs -> Bool
          fieldsSam UNil UNil = True
      
          x = fieldsSam UNil UNil
      
      Due to its GADT nature, `UNil` produces a trivial wrapper
      
          $WUNil :: NP '[]
          $WUNil = UNil @'[] @~(<co:1>)
      
      which is referenced in the RHS of `A.x`. Due to the above-mentioned bug
      in `mkLFImported`, the references to `$WUNil` passed to `fieldsSam` were
      not tagged. This is problematic as `fieldsSam` expected its arguments to
      be tagged as they are unlifted.
      
      The fix is straightforward: extend the logic in `mkLFImported` to cover
      (nullary) datacon wrappers as well as workers. This is safe because we
      know that the wrapper of a nullary datacon will be in WHNF, even if it
      includes equalities evidence (since such equalities are not runtime
      relevant).
      
      Thanks to @MangoIV for the great ticket and @alt-romes for his
      minimization and help debugging.
      
      Fixes #23146.
      33a8c348
    • Ben Gamari's avatar
      codeGen: Fix some Haddocks · 76727617
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      76727617
    • Ben Gamari's avatar
      testsuite: Add tests for #23146 · 33cf4659
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Both lifted and unlifted variants.
      33cf4659
    • Krzysztof Gogolewski's avatar
      Add an error origin for impedance matching (#23427) · 9db0eadd
      Krzysztof Gogolewski authored and Marge Bot's avatar Marge Bot committed
      9db0eadd
    • Greg Steuck's avatar
      Bring back getExecutablePath to getBaseDir on OpenBSD · 9d531f9a
      Greg Steuck authored and Marge Bot's avatar Marge Bot committed
      Fix #18173
      9d531f9a
    • Greg Steuck's avatar
      Disable T17414 on OpenBSD · 882e43b7
      Greg Steuck authored and Marge Bot's avatar Marge Bot committed
      Like on other systems it's not guaranteed that there's sufficient
      space in /tmp to write 2G out.
      882e43b7
    • Greg Steuck's avatar
      Revert "Change hostSupportsRPaths to report False on OpenBSD" · 2b53f206
      Greg Steuck authored and Marge Bot's avatar Marge Bot committed
      This reverts commit 1e0d8fdb.
      2b53f206
  4. May 22, 2023
  5. May 20, 2023
  6. May 19, 2023
    • Simon Peyton Jones's avatar
      Type inference for data family newtype instances · 525ed554
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      This patch addresses #23408, a tricky case with data family
      newtype instances.  Consider
      
        type family TF a where TF Char = Bool
        data family DF a
        newtype instance DF Bool = MkDF Int
      
      and [W] Int ~R# DF (TF a), with a Given (a ~# Char).   We must fully
      rewrite the Wanted so the tpye family can fire; that wasn't happening.
      525ed554
    • Oleg Grenrus's avatar
      Make Warn = Located DriverMessage · 4bca0486
      Oleg Grenrus authored
      This change makes command line argument parsing use diagnostic
      framework for producing warnings.
      4bca0486
  7. May 18, 2023
Loading