[Git][ghc/ghc][master] Fix pretty-printing of type family dependencies

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Nov 1 00:04:38 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
49f69f50 by Krzysztof Gogolewski at 2023-10-31T20:04:13-04:00
Fix pretty-printing of type family dependencies

"where" should be after the injectivity annotation.

- - - - -


5 changed files:

- compiler/GHC/Iface/Syntax.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


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))
          ]


=====================================
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/-/commit/49f69f50afbfd352f0e9645b4dbe87200e63b37e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/49f69f50afbfd352f0e9645b4dbe87200e63b37e
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/a75cdf1a/attachment-0001.html>


More information about the ghc-commits mailing list