Skip to content
Snippets Groups Projects
  1. Jul 18, 2023
    • sheaf's avatar
      Re-instate -Wincomplete-record-updates · df706de3
      sheaf authored and Marge Bot's avatar Marge Bot committed
      Commit e74fc066 refactored the handling of record updates to use
      the HsExpanded mechanism. This meant that the pattern matching inherent
      to a record update was considered to be "generated code", and thus we
      stopped emitting "incomplete record update" warnings entirely.
      
      This commit changes the "data Origin = Source | Generated" datatype,
      adding a field to the Generated constructor to indicate whether we
      still want to perform pattern-match checking. We also have to do a bit
      of plumbing with HsCase, to record that the HsCase arose from an
      HsExpansion of a RecUpd, so that the error message continues to mention
      record updates as opposed to a generic "incomplete pattern matches in case"
      error.
      
      Finally, this patch also changes the way we handle inaccessible code
      warnings. Commit e74fc066 was also a regression in this regard, as we
      were emitting "inaccessible code" warnings for case statements spuriously
      generated when desugaring a record update (remember: the desugaring mechanism
      happens before typechecking; it thus can't take into account e.g. GADT information
      in order to decide which constructors to include in the RHS of the desugaring
      of the record update).
      We fix this by changing the mechanism through which we disable inaccessible
      code warnings: we now check whether we are in generated code in
      GHC.Tc.Utils.TcMType.newImplication in order to determine whether to
      emit inaccessible code warnings.
      
      Fixes #23520
      Updates haddock submodule, to avoid incomplete record update warnings
      df706de3
    • sheaf's avatar
      exactprint: silence incomplete record update warnings · 860f6269
      sheaf authored and Marge Bot's avatar Marge Bot committed
      860f6269
    • sheaf's avatar
      base: add COMPLETE pragma to BufferCodec PatSyn · 22565506
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This implements CLC proposal #178, rectifying an oversight in the
      implementation of CLC proposal #134 which could lead to spurious
      pattern match warnings.
      
      https://github.com/haskell/core-libraries-committee/issues/178
      https://github.com/haskell/core-libraries-committee/issues/134
      22565506
  2. Jul 17, 2023
    • Alan Zimmerman's avatar
      EPA: Store leading AnnSemi for decllist in al_rest · 654fdb98
      Alan Zimmerman authored and Marge Bot's avatar Marge Bot committed
      This simplifies the markAnnListA implementation in ExactPrint
      654fdb98
    • sheaf's avatar
      Suggest similar names in imports · 1af2e773
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit adds similar name suggestions when importing. For example
      
        module A where { spelling = 'o' }
        module B where { import B ( speling ) }
      
      will give rise to the error message:
      
        Module ‘A’ does not export ‘speling’.
        Suggested fix: Perhaps use ‘spelling’
      
      This also provides hints when users try to import record fields defined
      with NoFieldSelectors.
      1af2e773
    • sheaf's avatar
      rnImports: var shouldn't import NoFldSelectors · c7bbad9a
      sheaf authored and Marge Bot's avatar Marge Bot committed
      In an import declaration such as
      
        import M ( var )
      
      the import of the variable "var" should **not** bring into scope record
      fields named "var" which are defined with NoFieldSelectors.
      Doing so can cause spurious "unused import" warnings, as reported in
      ticket #23557.
      
      Fixes #23557
      c7bbad9a
  3. Jul 16, 2023
    • sheaf's avatar
      Don't use substTyUnchecked in newMetaTyVar · eb1a6ab1
      sheaf authored and Marge Bot's avatar Marge Bot committed
      There were some comments that explained that we needed to use an
      unchecked substitution function because of issue #12931, but that
      has since been fixed, so we should be able to use substTy instead now.
      eb1a6ab1
    • Andrei Borzenkov's avatar
      Type patterns (#22478, #18986) · 2afbddb0
      Andrei Borzenkov authored
      Improved name resolution and type checking of type patterns in constructors:
      
      1. HsTyPat: a new dedicated data type that represents type patterns in
         HsConPatDetails instead of reusing HsPatSigType
      
      2. rnHsTyPat: a new function that renames a type
         pattern and collects its binders into three groups:
          - explicitly bound type variables, excluding locally bound
            variables
          - implicitly bound type variables from kind signatures
            (only if ScopedTypeVariables are enabled)
          - named wildcards (only from kind signatures)
      2a. rnHsPatSigTypeBindingVars: removed in favour of rnHsTyPat
      2b. rnImplcitTvBndrs: removed because no longer needed
      
      3. collect_pat: updated to collect type variable binders from type patterns
         (this means that types and terms use the same infrastructure to detect
         conflicting bindings, unused variables and name shadowing)
      3a. CollVarTyVarBinders: a new CollectFlag constructor that enables
          collection of type variables
      
      4. tcHsTyPat: a new function that typechecks type patterns, capable of
         handling polymorphic kinds.
         See Note [Type patterns: binders and unifiers]
      
      Examples of code that is now accepted:
      
         f = \(P @a) -> \(P @a) -> ...  -- triggers -Wname-shadowing
      
         g :: forall a. Proxy a -> ...
         g (P @a) = ...                 -- also triggers -Wname-shadowing
      
         h (P @($(TH.varT (TH.mkName "t")))) = ...
                                        -- t is bound at splice time
      
         j (P @(a :: (x,x))) = ...      -- (x,x) is no longer rejected
      
         data T where
           MkT :: forall (f :: forall k. k -> Type).
             f Int -> f Maybe -> T
         k :: T -> ()
         k (MkT @f (x :: f Int) (y :: f Maybe)) = ()
                                        -- f :: forall k. k -> Type
      
      Examples of code that is rejected with better error messages:
      
        f (Left @a @a _) = ...
        -- new message:
        --     • Conflicting definitions for ‘a’
        --       Bound at: Test.hs:1:11
        --                 Test.hs:1:14
      
      Examples of code that is now rejected:
      
        {-# OPTIONS_GHC -Werror=unused-matches #-}
        f (P @a) = ()
        -- Defined but not used: type variable ‘a’
      2afbddb0
    • Vladislav Zavialov's avatar
      List and Tuple<n>: update documentation · 7f13acbf
      Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
      Add the missing changelog.md entries and @since-annotations.
      7f13acbf
  4. Jul 15, 2023
  5. Jul 14, 2023
  6. Jul 13, 2023
    • Rodrigo Mesquita's avatar
      configure: Drop DllWrap command · 5e951395
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      We used to configure into settings a DllWrap command for windows
      builds and distributions, however, we no longer do, and dllwrap is
      effectively unused.
      
      This simplification is motivated in part by the larger
      toolchain-selection project (#19877, !9263)
      5e951395
    • sheaf's avatar
      Refactor lookupGRE_... functions · 7f0a86ed
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit consolidates all the logic for looking up something in
      the Global Reader Environment into the single function lookupGRE.
      This allows us to declaratively specify all the different modes of
      looking up in the GlobalRdrEnv, and avoids manually passing around
      filtering functions as was the case in e.g. the function
      GHC.Rename.Env.lookupSubBndrOcc_helper.
      
      -------------------------
      Metric Decrease:
          T8095
      -------------------------
      -------------------------
      Metric Increase:
          T8095
      -------------------------
      7f0a86ed
    • sheaf's avatar
      Introduce greInfo, greParent · 6fd8f566
      sheaf authored and Marge Bot's avatar Marge Bot committed
      These are simple helper functions that wrap the internal
      field names gre_info, gre_par.
      6fd8f566
    • sheaf's avatar
      Fix deprecation of record fields · 6143838a
      sheaf authored and Marge Bot's avatar Marge Bot committed
      Commit 3f374399 inadvertently broke the deprecation/warning mechanism
      for record fields due to its introduction of record field namespaces.
      
      This patch ensures that, when a top-level deprecation is applied to
      an identifier, it applies to all the record fields as well.
      This is achieved by refactoring GHC.Rename.Env.lookupLocalTcNames, and
      GHC.Rename.Env.lookupBindGroupOcc, to not look up a fixed number of
      NameSpaces but to look up all NameSpaces and filter out the irrelevant
      ones.
      6143838a
    • Bartłomiej Cieślar's avatar
      changes · 2af23f0e
      Bartłomiej Cieślar authored and Marge Bot's avatar Marge Bot committed
      2af23f0e
    • Bartłomiej Cieślar's avatar
      updates to comments · b2846cb5
      Bartłomiej Cieślar authored and Marge Bot's avatar Marge Bot committed
      b2846cb5
    • Bartłomiej Cieślar's avatar
      Comments · 84c1a4a2
      Bartłomiej Cieślar authored and Marge Bot's avatar Marge Bot committed
      84c1a4a2
    • Krzysztof Gogolewski's avatar
      Fix #23567, a specializer bug · bf9b9de0
      Krzysztof Gogolewski authored and Marge Bot's avatar Marge Bot committed
      Found by Simon in ghc/ghc#23567 (comment 507834)
      
      The testcase isn't ideal because it doesn't detect the bug in master,
      unless doNotUnbox is removed as in
      ghc/ghc#23567 (comment 507692).
      But I have confirmed that with that modification, it fails before
      and passes afterwards.
      bf9b9de0
    • Matthew Pickering's avatar
      Use deb10 for i386 bindists · c39f279b
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      deb9 is now EOL so it's time to upgrade the i386 bindist to use deb10
      
      Fixes #23585
      c39f279b
  7. Jul 12, 2023
  8. Jul 11, 2023
  9. Jul 10, 2023
  10. Jul 08, 2023
Loading