[Git][ghc/ghc][wip/az/epa-noann-not-monoid] EPA: Replace Monoid with NoAnn
Alan Zimmerman (@alanz)
gitlab at gitlab.haskell.org
Thu Nov 16 22:00:57 UTC 2023
Alan Zimmerman pushed to branch wip/az/epa-noann-not-monoid at Glasgow Haskell Compiler / GHC
Commits:
0f63b876 by Alan Zimmerman at 2023-11-16T22:00:03+00:00
EPA: Replace Monoid with NoAnn
Remove the final Monoid instances in the exact print infrastructure.
For Windows CI
Metric Decrease:
T5205
- - - - -
2 changed files:
- compiler/GHC/Parser/Annotation.hs
- utils/check-exact/Orphans.hs
Changes:
=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -1393,7 +1393,7 @@ instance (Semigroup a) => Semigroup (EpAnn a) where
-- annotations must follow it. So we combine them which yields the
-- largest span
-instance Semigroup Anchor where
+instance Semigroup EpaLocation where
EpaSpan s1 m1 <> EpaSpan s2 m2 = EpaSpan (combineRealSrcSpans s1 s2) (liftA2 combineBufSpans m1 m2)
EpaSpan s1 m1 <> _ = EpaSpan s1 m1
_ <> EpaSpan s2 m2 = EpaSpan s2 m2
=====================================
utils/check-exact/Orphans.hs
=====================================
@@ -5,65 +5,61 @@ module Orphans where
import GHC hiding (EpaComment)
--- ---------------------------------------------------------------------
--- Orphan NoAnn instances. See https://gitlab.haskell.org/ghc/ghc/-/issues/20372
+-- -- ---------------------------------------------------------------------
instance NoAnn [a] where
noAnn = []
-instance NoAnn AnnPragma where
- noAnn = AnnPragma noAnn noAnn noAnn
-
-instance NoAnn EpAnnImportDecl where
- noAnn = EpAnnImportDecl noAnn Nothing Nothing Nothing Nothing Nothing
+instance (NoAnn a, NoAnn b) => NoAnn (a, b) where
+ noAnn = (noAnn, noAnn)
-instance NoAnn AnnParen where
- noAnn = AnnParen AnnParens noAnn noAnn
+instance NoAnn EpaLocation where
+ noAnn = EpaDelta (SameLine 0) []
-instance NoAnn HsRuleAnn where
- noAnn = HsRuleAnn Nothing Nothing noAnn
+instance NoAnn EpAnnSumPat where
+ noAnn = EpAnnSumPat [] [] []
-instance NoAnn AnnSig where
- noAnn = AnnSig noAnn noAnn
+instance NoAnn AnnPragma where
+ noAnn = AnnPragma noAnn noAnn []
-instance NoAnn GrhsAnn where
- noAnn = GrhsAnn Nothing noAnn
+instance NoAnn AddEpAnn where
+ noAnn = AddEpAnn noAnn noAnn
-instance NoAnn EpAnnUnboundVar where
- noAnn = EpAnnUnboundVar noAnn noAnn
+instance NoAnn AnnKeywordId where
+ noAnn = Annlarrowtail {- gotta pick one -}
-instance (NoAnn a, NoAnn b) => NoAnn (a, b) where
- noAnn = (noAnn, noAnn)
+instance NoAnn AnnParen where
+ noAnn = AnnParen AnnParens noAnn noAnn
-instance NoAnn AnnExplicitSum where
- noAnn = AnnExplicitSum noAnn noAnn noAnn noAnn
+instance NoAnn AnnsIf where
+ noAnn = AnnsIf noAnn noAnn noAnn Nothing Nothing
instance NoAnn EpAnnHsCase where
noAnn = EpAnnHsCase noAnn noAnn noAnn
-instance NoAnn AnnsIf where
- noAnn = AnnsIf noAnn noAnn noAnn noAnn noAnn
-
-instance NoAnn (Maybe a) where
- noAnn = Nothing
+instance NoAnn AnnFieldLabel where
+ noAnn = AnnFieldLabel Nothing
instance NoAnn AnnProjection where
noAnn = AnnProjection noAnn noAnn
-instance NoAnn AnnFieldLabel where
- noAnn = AnnFieldLabel Nothing
+instance NoAnn AnnExplicitSum where
+ noAnn = AnnExplicitSum noAnn noAnn noAnn noAnn
-instance NoAnn EpaLocation where
- noAnn = EpaDelta (SameLine 0) []
+instance NoAnn EpAnnUnboundVar where
+ noAnn = EpAnnUnboundVar noAnn noAnn
-instance NoAnn AddEpAnn where
- noAnn = AddEpAnn noAnn noAnn
+instance NoAnn GrhsAnn where
+ noAnn = GrhsAnn Nothing noAnn
-instance NoAnn AnnKeywordId where
- noAnn = Annlarrowtail {- gotta pick one -}
+instance NoAnn HsRuleAnn where
+ noAnn = HsRuleAnn Nothing Nothing noAnn
-instance NoAnn EpAnnSumPat where
- noAnn = EpAnnSumPat noAnn noAnn noAnn
+instance NoAnn AnnSig where
+ noAnn = AnnSig noAnn noAnn
+
+instance NoAnn EpAnnImportDecl where
+ noAnn = EpAnnImportDecl noAnn Nothing Nothing Nothing Nothing Nothing
instance NoAnn AnnsModule where
- noAnn = AnnsModule [] mempty Nothing
+ noAnn = AnnsModule [] [] Nothing
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0f63b876652bc0a05d925c22873159014554fcfe
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0f63b876652bc0a05d925c22873159014554fcfe
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/20231116/e563ddb4/attachment-0001.html>
More information about the ghc-commits
mailing list