[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Add more instances for Compose: Fractional, RealFrac, Floating, RealFloat

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Jan 15 10:55:33 UTC 2024



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
e43788d0 by Jason Shipman at 2024-01-14T12:47:38-05:00
Add more instances for Compose: Fractional, RealFrac, Floating, RealFloat

CLC proposal #226 https://github.com/haskell/core-libraries-committee/issues/226

- - - - -
ae6d8cd2 by Sebastian Graf at 2024-01-14T12:48:15-05:00
Pmc: COMPLETE pragmas associated with Family TyCons should apply to representation TyCons as well (#24326)

Fixes #24326.

- - - - -
a2de56da by sheaf at 2024-01-15T05:55:08-05:00
Use lookupOccRn_maybe in TH.lookupName

When looking up a value, we want to be able to find both variables
and record fields. So we should not use the lookupSameOccRn_maybe
function, as we can't know ahead of time which record field namespace
a record field with the given textual name will belong to.

Fixes #24293

- - - - -
cd50cb53 by Krzysztof Gogolewski at 2024-01-15T05:55:08-05:00
Make the build more strict on documentation errors

* Detect undefined labels. This can be tested by adding :ref:`nonexistent`
  to a documentation rst file; attempting to build docs will fail.
  Fixed the undefined label in `9.8.1-notes.rst`.
* Detect errors. While we have plenty of warnings, we can at least enforce
  that Sphinx does not report errors.
  Fixed the error in `required_type_arguments.rst`.

Unrelated change: I have documented that the `-dlint` enables
`-fcatch-nonexhaustive-cases`, as can be verified by checking
`enableDLint`.

- - - - -


20 changed files:

- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Types/CompleteMatch.hs
- docs/users_guide/9.8.1-notes.rst
- docs/users_guide/debugging.rst
- docs/users_guide/exts/required_type_arguments.rst
- hadrian/src/Rules/Documentation.hs
- libraries/base/changelog.md
- libraries/base/src/Data/Functor/Compose.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- + testsuite/tests/overloadedrecflds/should_compile/T24293.hs
- + testsuite/tests/overloadedrecflds/should_compile/T24293b.hs
- + testsuite/tests/overloadedrecflds/should_compile/T24293c.hs
- + testsuite/tests/overloadedrecflds/should_compile/T24293c.stderr
- testsuite/tests/overloadedrecflds/should_compile/all.T
- + testsuite/tests/pmcheck/complete_sigs/T24326.hs
- + testsuite/tests/pmcheck/complete_sigs/T24326.stderr
- testsuite/tests/pmcheck/complete_sigs/all.T


Changes:

=====================================
compiler/GHC/Tc/Gen/Splice.hs
=====================================
@@ -1944,8 +1944,8 @@ lookupName :: Bool      -- True  <=> type namespace
                         -- False <=> value namespace
            -> String -> TcM (Maybe TH.Name)
 lookupName is_type_name s
-  = do { mb_nm <- lookupSameOccRn_maybe rdr_name
-       ; return (fmap reifyName mb_nm) }
+  = do { mb_nm <- lookupOccRn_maybe rdr_name
+       ; return (fmap (reifyName . greName) mb_nm) }
   where
     th_name = TH.mkName s       -- Parses M.x into a base of 'x' and a module of 'M'
 
@@ -1960,6 +1960,12 @@ lookupName is_type_name s
         | otherwise
         = if isLexCon occ_fs then mkDataOccFS occ_fs
                              else mkVarOccFS  occ_fs
+                               -- NB: when we pick the variable namespace, we
+                               -- might well obtain an identifier in a record
+                               -- field namespace, as lookupOccRn_maybe looks in
+                               -- record field namespaces when looking up variables.
+                               -- This ensures we can look up record fields using
+                               -- this function (#24293).
 
     rdr_name = case TH.nameModule th_name of
                  Nothing  -> mkRdrUnqual occ


=====================================
compiler/GHC/Types/CompleteMatch.hs
=====================================
@@ -35,6 +35,11 @@ completeMatchAppliesAtType ty cm = all @Maybe ty_matches (cmResultTyCon cm)
     ty_matches sig_tc
       | Just (tc, _arg_tys) <- splitTyConApp_maybe ty
       , tc == sig_tc
+      || sig_tc `is_family_ty_con_of` tc
+         -- #24326: sig_tc might be the data Family TyCon of the representation
+         --         TyCon tc -- this CompleteMatch still applies
       = True
       | otherwise
       = False
+    fam_tc `is_family_ty_con_of` repr_tc =
+      (fst <$> tyConFamInst_maybe repr_tc) == Just fam_tc


=====================================
docs/users_guide/9.8.1-notes.rst
=====================================
@@ -256,7 +256,7 @@ Runtime system
 - The extensions fields of constructors of ``IE`` now take ``Maybe (WarningTxt p)``
   in ``GhcPs`` and ``GhcRn`` variants of the Syntax Tree.
   This represents the warning assigned to a certain export item,
-  which is used for :ref:`deprecated-exports`.
+  which is used for deprecated exports (see :ref:`warning-deprecated-pragma`).
 
 ``ghc-heap`` library
 ~~~~~~~~~~~~~~~~~~~~


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -1046,7 +1046,7 @@ Checking for consistency
     :shortdesc: Enable several common internal sanity checkers
     :type: dynamic
 
-    :implies: -dcore-lint, -dstg-lint, -dcmm-lint, -dasm-lint, -fllvm-fill-undef-with-garbage, -debug
+    :implies: -dcore-lint, -dstg-lint, -dcmm-lint, -dasm-lint, -fllvm-fill-undef-with-garbage, -fcatch-nonexhaustive-cases, -debug
     :since: 9.4.1
 
     Turn on various heavy-weight intra-pass sanity-checking measures within GHC


=====================================
docs/users_guide/exts/required_type_arguments.rst
=====================================
@@ -281,8 +281,8 @@ to bind type variables::
   const :: a -> b -> a               -- implicit quantification
   const :: forall a b. a -> b -> a   -- explicit quantification
 
-Normally, implicit quantification is unaffected by term variables in scope:
-::
+Normally, implicit quantification is unaffected by term variables in scope: ::
+
   f a = ...  -- the LHS binds `a`
     where const :: a -> b -> a
              -- implicit quantification over `a` takes place


=====================================
hadrian/src/Rules/Documentation.hs
=====================================
@@ -168,6 +168,12 @@ checkSphinxWarnings out = do
     when ("reference target not found" `isInfixOf` log)
       $ fail "Undefined reference targets found in Sphinx log."
 
+    when ("undefined label:" `isInfixOf` log)
+      $ fail "Undefined labels found in Sphinx log."
+
+    when ("ERROR:" `isInfixOf` log)
+      $ fail "Errors found in the Sphinx log."
+
 -- | Check that all GHC flags are documented in the users guide.
 checkUserGuideFlags :: FilePath -> Action ()
 checkUserGuideFlags documentedFlagList = do


=====================================
libraries/base/changelog.md
=====================================
@@ -33,6 +33,8 @@
 
     ([CLC proposal #104](https://github.com/haskell/core-libraries-committee/issues/104))
 
+  * Add more instances for `Compose`: `Fractional`, `RealFrac`, `Floating`, `RealFloat` ([CLC proposal #226](https://github.com/haskell/core-libraries-committee/issues/226))
+
 ## 4.19.0.0 *October 2023*
   * Add `{-# WARNING in "x-partial" #-}` to `Data.List.{head,tail}`.
     Use `{-# OPTIONS_GHC -Wno-x-partial #-}` to disable it.


=====================================
libraries/base/src/Data/Functor/Compose.hs
=====================================
@@ -171,3 +171,11 @@ deriving instance Num (f (g a)) => Num (Compose f g a)
 deriving instance Real (f (g a)) => Real (Compose f g a)
 -- | @since 4.19.0.0
 deriving instance Integral (f (g a)) => Integral (Compose f g a)
+-- | @since 4.20.0.0
+deriving instance Fractional (f (g a)) => Fractional (Compose f g a)
+-- | @since 4.20.0.0
+deriving instance RealFrac (f (g a)) => RealFrac (Compose f g a)
+-- | @since 4.20.0.0
+deriving instance Floating (f (g a)) => Floating (Compose f g a)
+-- | @since 4.20.0.0
+deriving instance RealFloat (f (g a)) => RealFloat (Compose f g a)


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -11569,12 +11569,14 @@ instance GHC.Exception.Type.Exception GHC.IOPort.IOPortException -- Defined in 
 instance [safe] GHC.Exception.Type.Exception System.Timeout.Timeout -- Defined in ‘System.Timeout’
 instance forall a k (b :: k). GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.Floating (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Float.Floating (f (g a)) => GHC.Float.Floating (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a b. GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Contravariant.Op a b) -- Defined in ‘Data.Functor.Contravariant’
 instance forall a. GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Float.Floating a => GHC.Float.Floating (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance GHC.Float.Floating GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Float.Floating GHC.Types.Float -- Defined in ‘GHC.Float’
 instance forall a k (b :: k). GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Float.RealFloat (f (g a)) => GHC.Float.RealFloat (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance GHC.Float.RealFloat GHC.Types.Double -- Defined in ‘GHC.Float’
@@ -11913,6 +11915,7 @@ instance GHC.Read.Read GHC.TypeNats.SomeNat -- Defined in ‘GHC.TypeNats’
 instance forall a k (b :: k). GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall a. GHC.Float.RealFloat a => GHC.Real.Fractional (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
 instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.Fractional (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Real.Fractional (f (g a)) => GHC.Real.Fractional (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a b. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Contravariant.Op a b) -- Defined in ‘Data.Functor.Contravariant’
 instance forall a. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Ord.Down a) -- Defined in ‘Data.Ord’
@@ -11960,6 +11963,7 @@ instance GHC.Real.Real GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Real.Real GHC.Types.Float -- Defined in ‘GHC.Float’
 instance forall a k (b :: k). GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.RealFrac (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Real.RealFrac (f (g a)) => GHC.Real.RealFrac (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance forall a. GHC.Real.Integral a => GHC.Real.RealFrac (GHC.Real.Ratio a) -- Defined in ‘GHC.Real’


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -14342,12 +14342,14 @@ instance GHC.Exception.Type.Exception GHC.JS.Prim.WouldBlockException -- Defined
 instance [safe] GHC.Exception.Type.Exception System.Timeout.Timeout -- Defined in ‘System.Timeout’
 instance forall a k (b :: k). GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.Floating (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Float.Floating (f (g a)) => GHC.Float.Floating (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a b. GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Contravariant.Op a b) -- Defined in ‘Data.Functor.Contravariant’
 instance forall a. GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Float.Floating a => GHC.Float.Floating (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance GHC.Float.Floating GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Float.Floating GHC.Types.Float -- Defined in ‘GHC.Float’
 instance forall a k (b :: k). GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Float.RealFloat (f (g a)) => GHC.Float.RealFloat (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance GHC.Float.RealFloat GHC.Types.Double -- Defined in ‘GHC.Float’
@@ -14686,6 +14688,7 @@ instance GHC.Read.Read GHC.TypeNats.SomeNat -- Defined in ‘GHC.TypeNats’
 instance forall a k (b :: k). GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall a. GHC.Float.RealFloat a => GHC.Real.Fractional (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
 instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.Fractional (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Real.Fractional (f (g a)) => GHC.Real.Fractional (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a b. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Contravariant.Op a b) -- Defined in ‘Data.Functor.Contravariant’
 instance forall a. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Ord.Down a) -- Defined in ‘Data.Ord’
@@ -14733,6 +14736,7 @@ instance GHC.Real.Real GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Real.Real GHC.Types.Float -- Defined in ‘GHC.Float’
 instance forall a k (b :: k). GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.RealFrac (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Real.RealFrac (f (g a)) => GHC.Real.RealFrac (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance forall a. GHC.Real.Integral a => GHC.Real.RealFrac (GHC.Real.Ratio a) -- Defined in ‘GHC.Real’


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -11838,12 +11838,14 @@ instance GHC.Exception.Type.Exception GHC.IOPort.IOPortException -- Defined in 
 instance [safe] GHC.Exception.Type.Exception System.Timeout.Timeout -- Defined in ‘System.Timeout’
 instance forall a k (b :: k). GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.Floating (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Float.Floating (f (g a)) => GHC.Float.Floating (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a b. GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Contravariant.Op a b) -- Defined in ‘Data.Functor.Contravariant’
 instance forall a. GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Float.Floating a => GHC.Float.Floating (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance GHC.Float.Floating GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Float.Floating GHC.Types.Float -- Defined in ‘GHC.Float’
 instance forall a k (b :: k). GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Float.RealFloat (f (g a)) => GHC.Float.RealFloat (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance GHC.Float.RealFloat GHC.Types.Double -- Defined in ‘GHC.Float’
@@ -12191,6 +12193,7 @@ instance GHC.Read.Read GHC.TypeNats.SomeNat -- Defined in ‘GHC.TypeNats’
 instance forall a k (b :: k). GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall a. GHC.Float.RealFloat a => GHC.Real.Fractional (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
 instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.Fractional (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Real.Fractional (f (g a)) => GHC.Real.Fractional (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a b. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Contravariant.Op a b) -- Defined in ‘Data.Functor.Contravariant’
 instance forall a. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Ord.Down a) -- Defined in ‘Data.Ord’
@@ -12238,6 +12241,7 @@ instance GHC.Real.Real GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Real.Real GHC.Types.Float -- Defined in ‘GHC.Float’
 instance forall a k (b :: k). GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.RealFrac (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Real.RealFrac (f (g a)) => GHC.Real.RealFrac (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance forall a. GHC.Real.Integral a => GHC.Real.RealFrac (GHC.Real.Ratio a) -- Defined in ‘GHC.Real’


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -11573,12 +11573,14 @@ instance GHC.Exception.Type.Exception GHC.IOPort.IOPortException -- Defined in 
 instance [safe] GHC.Exception.Type.Exception System.Timeout.Timeout -- Defined in ‘System.Timeout’
 instance forall a k (b :: k). GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.Floating (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Float.Floating (f (g a)) => GHC.Float.Floating (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a b. GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Contravariant.Op a b) -- Defined in ‘Data.Functor.Contravariant’
 instance forall a. GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Float.Floating a => GHC.Float.Floating (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance GHC.Float.Floating GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Float.Floating GHC.Types.Float -- Defined in ‘GHC.Float’
 instance forall a k (b :: k). GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Float.RealFloat (f (g a)) => GHC.Float.RealFloat (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance GHC.Float.RealFloat GHC.Types.Double -- Defined in ‘GHC.Float’
@@ -11917,6 +11919,7 @@ instance GHC.Read.Read GHC.TypeNats.SomeNat -- Defined in ‘GHC.TypeNats’
 instance forall a k (b :: k). GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall a. GHC.Float.RealFloat a => GHC.Real.Fractional (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
 instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.Fractional (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Real.Fractional (f (g a)) => GHC.Real.Fractional (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a b. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Contravariant.Op a b) -- Defined in ‘Data.Functor.Contravariant’
 instance forall a. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Real.Fractional a => GHC.Real.Fractional (Data.Ord.Down a) -- Defined in ‘Data.Ord’
@@ -11964,6 +11967,7 @@ instance GHC.Real.Real GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Real.Real GHC.Types.Float -- Defined in ‘GHC.Float’
 instance forall a k (b :: k). GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Const.Const a b) -- Defined in ‘Data.Functor.Const’
 instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.RealFrac (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
+instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Real.RealFrac (f (g a)) => GHC.Real.RealFrac (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance forall a. GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Ord.Down a) -- Defined in ‘Data.Ord’
 instance forall a. GHC.Real.Integral a => GHC.Real.RealFrac (GHC.Real.Ratio a) -- Defined in ‘GHC.Real’


=====================================
testsuite/tests/overloadedrecflds/should_compile/T24293.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T24293 where
+import Language.Haskell.TH
+
+data Cheval = Cheval { hibou :: Int }
+
+name = $(do
+  n <- lookupValueName "hibou"
+  pure $ LitE $ StringL $ show n)


=====================================
testsuite/tests/overloadedrecflds/should_compile/T24293b.hs
=====================================
@@ -0,0 +1,13 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE NoFieldSelectors #-}
+module T24293b where
+import Language.Haskell.TH
+
+data Cheval = Cheval { hibou :: Int }
+
+hibou :: Bool
+hibou = False
+
+name = $(do
+  n <- lookupValueName "hibou"
+  pure $ LitE $ StringL $ show n)


=====================================
testsuite/tests/overloadedrecflds/should_compile/T24293c.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE DuplicateRecordFields #-}
+module T24293c where
+import Language.Haskell.TH
+
+data Cheval = Cheval { hibou :: Int }
+data Agneau = Agneau { hibou :: Bool }
+
+name = $(do
+  n <- lookupValueName "hibou"
+  pure $ LitE $ StringL $ show n)


=====================================
testsuite/tests/overloadedrecflds/should_compile/T24293c.stderr
=====================================
@@ -0,0 +1,11 @@
+
+T24293c.hs:9:9: error: [GHC-87543]
+    • Ambiguous occurrence ‘hibou’.
+      It could refer to
+         either the field ‘hibou’ of record ‘Cheval’,
+                defined at T24293c.hs:6:24,
+             or the field ‘hibou’ of record ‘Agneau’,
+                defined at T24293c.hs:7:24.
+    • In the untyped splice:
+        $(do n <- lookupValueName "hibou"
+             pure $ LitE $ StringL $ show n)


=====================================
testsuite/tests/overloadedrecflds/should_compile/all.T
=====================================
@@ -57,3 +57,6 @@ test('T22106_D', [extra_files(['T22106_aux.hs'])], multimod_compile, ['T22106_D'
 test('T22424', req_th, compile, ['-this-unit-id="me"'])
 test('T23279', [extra_files(['T23279_aux.hs'])], multimod_compile, ['T23279', '-v0'])
 test('T23557', [extra_files(['T23557_aux.hs'])], multimod_compile, ['T23557', '-v0'])
+test('T24293', req_th, compile, [''])
+test('T24293b', req_th, compile, [''])
+test('T24293c', req_th, compile_fail, [''])


=====================================
testsuite/tests/pmcheck/complete_sigs/T24326.hs
=====================================
@@ -0,0 +1,33 @@
+{-# OPTIONS_GHC -Wincomplete-patterns #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE PatternSynonyms #-}
+{-# LANGUAGE ViewPatterns #-}
+
+module T24326 where
+
+data family Foo
+data instance Foo = A | B
+{-# COMPLETE A :: Foo #-}
+
+class C a where
+  matches :: a -> Bool
+
+pattern P :: C a => a
+pattern P <- (matches -> True)
+
+data D = D Bool
+instance C D where { matches (D b) = b }
+
+data family B a
+data instance B Bool = BBool Bool
+instance C (B Bool) where { matches (BBool b) = b }
+{-# COMPLETE P :: B #-}
+
+f :: Foo -> Int
+f A = 0 -- should not warn
+
+f1 :: D -> ()
+f1 P = () -- should warn, because COMPLETE doesn't apply at D
+
+f2 :: B Bool -> ()
+f2 P = () -- should not warn


=====================================
testsuite/tests/pmcheck/complete_sigs/T24326.stderr
=====================================
@@ -0,0 +1,4 @@
+
+T24326.hs:30:1: warning: [GHC-62161] [-Wincomplete-patterns (in -Wextra)]
+    Pattern match(es) are non-exhaustive
+    In an equation for ‘f1’: Patterns of type ‘D’ not matched: _


=====================================
testsuite/tests/pmcheck/complete_sigs/all.T
=====================================
@@ -1,7 +1,9 @@
+setTestOpts(extra_hc_opts('-Wincomplete-patterns'))
+
 test('completesig01', normal, compile, [''])
 test('completesig02', normal, compile, [''])
-test('Completesig03', normal, multimod_compile, ['Completesig03', '-Wall'])
-test('completesig04', normal, compile, ['-Wincomplete-patterns'])
+test('Completesig03', normal, multimod_compile, ['Completesig03', ''])
+test('completesig04', normal, compile, [''])
 test('completesig05', normal, compile, [''])
 test('completesig06', normal, compile, [''])
 test('completesig07', normal, compile, [''])
@@ -29,3 +31,4 @@ test('T18277', normal, compile, [''])
 test('T18960', normal, compile, [''])
 test('T18960b', normal, compile, [''])
 test('T19475', normal, compile, [''])
+test('T24326', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3520552a26e2d9e5101ff3644f7ad721ad3eaaef...cd50cb53187dd6018f0e218b1e5bd6701b8ae5f5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3520552a26e2d9e5101ff3644f7ad721ad3eaaef...cd50cb53187dd6018f0e218b1e5bd6701b8ae5f5
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240115/2ce6dc7d/attachment-0001.html>


More information about the ghc-commits mailing list