[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: docs: fix ScopedTypeVariables example (#24101)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Oct 31 17:33:16 UTC 2023



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


Commits:
909f1ad0 by Krzysztof Gogolewski at 2023-10-31T13:33:09-04:00
docs: fix ScopedTypeVariables example (#24101)

The previous example didn't compile.

Furthermore, it wasn't demonstrating the point properly.
I have changed it to an example which shows that 'a' in the signature
must be the same 'a' as in the instance head.

- - - - -
f5abb277 by Krzysztof Gogolewski at 2023-10-31T13:33:10-04:00
Fix pretty-printing of type family dependencies

"where" should be after the injectivity annotation.

- - - - -


6 changed files:

- compiler/GHC/Iface/Syntax.hs
- docs/users_guide/exts/scoped_type_variables.rst
- 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


Changes:

=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -1067,8 +1067,9 @@ pprIfaceDecl ss (IfaceFamily { ifName = tycon
   = vcat [ pprStandaloneKindSig name_doc (mkIfaceTyConKind binders res_kind)
          , hang (text "type family"
                    <+> pprIfaceDeclHead suppress_bndr_sig [] ss tycon binders
+                   <+> pp_inj res_var inj
                    <+> ppShowRhs ss (pp_where rhs))
-              2 (pp_inj res_var inj <+> ppShowRhs ss (pp_rhs rhs))
+              2 (ppShowRhs ss (pp_rhs rhs))
            $$
            nest 2 (ppShowRhs ss (pp_branches rhs))
          ]


=====================================
docs/users_guide/exts/scoped_type_variables.rst
=====================================
@@ -293,11 +293,11 @@ signatures/ of the methods. For example, the following will be accepted without
 explicitly enabling :extension:`ScopedTypeVariables`: ::
 
       class D a where
-        m :: [a] -> a
+        m :: a -> a
 
-      instance D [a] where
+      instance Num a => D [a] where
         m :: [a] -> [a]
-        m = reverse
+        m x = map (*2) x
 
 Note that writing ``m :: [a] -> [a]`` requires the use of the
 :extension:`InstanceSigs` extension.


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -1657,7 +1657,7 @@ module Data.Type.Bool where
     forall k (tru :: k) (fls :: k). If GHC.Types.True tru fls = tru
     forall k (tru :: k) (fls :: k). If GHC.Types.False tru fls = fls
   type Not :: GHC.Types.Bool -> GHC.Types.Bool
-  type family Not a where = res | res -> a
+  type family Not a = res | res -> a where
       Not GHC.Types.False = GHC.Types.True
       Not GHC.Types.True = GHC.Types.False
   type (||) :: GHC.Types.Bool -> GHC.Types.Bool -> GHC.Types.Bool


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -1657,7 +1657,7 @@ module Data.Type.Bool where
     forall k (tru :: k) (fls :: k). If GHC.Types.True tru fls = tru
     forall k (tru :: k) (fls :: k). If GHC.Types.False tru fls = fls
   type Not :: GHC.Types.Bool -> GHC.Types.Bool
-  type family Not a where = res | res -> a
+  type family Not a = res | res -> a where
       Not GHC.Types.False = GHC.Types.True
       Not GHC.Types.True = GHC.Types.False
   type (||) :: GHC.Types.Bool -> GHC.Types.Bool -> GHC.Types.Bool


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -1657,7 +1657,7 @@ module Data.Type.Bool where
     forall k (tru :: k) (fls :: k). If GHC.Types.True tru fls = tru
     forall k (tru :: k) (fls :: k). If GHC.Types.False tru fls = fls
   type Not :: GHC.Types.Bool -> GHC.Types.Bool
-  type family Not a where = res | res -> a
+  type family Not a = res | res -> a where
       Not GHC.Types.False = GHC.Types.True
       Not GHC.Types.True = GHC.Types.False
   type (||) :: GHC.Types.Bool -> GHC.Types.Bool -> GHC.Types.Bool


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -1657,7 +1657,7 @@ module Data.Type.Bool where
     forall k (tru :: k) (fls :: k). If GHC.Types.True tru fls = tru
     forall k (tru :: k) (fls :: k). If GHC.Types.False tru fls = fls
   type Not :: GHC.Types.Bool -> GHC.Types.Bool
-  type family Not a where = res | res -> a
+  type family Not a = res | res -> a where
       Not GHC.Types.False = GHC.Types.True
       Not GHC.Types.True = GHC.Types.False
   type (||) :: GHC.Types.Bool -> GHC.Types.Bool -> GHC.Types.Bool



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7b06e3b1571743d4b8b2d3fbb66143004310d2fe...f5abb27792158f322a6addb367690b9d7f254fd6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7b06e3b1571743d4b8b2d3fbb66143004310d2fe...f5abb27792158f322a6addb367690b9d7f254fd6
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/20231031/b93d0424/attachment-0001.html>


More information about the ghc-commits mailing list