[Git][ghc/ghc][wip/ttg/types/basic] 4 commits: make XCInlinePragma strict since its dataConCantHappen
Hassan Al-Awwadi (@hassan.awwadi)
gitlab at gitlab.haskell.org
Mon Oct 28 17:59:27 UTC 2024
Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC
Commits:
9a620c77 by Hassan Al-Awwadi at 2024-10-28T17:38:43+01:00
make XCInlinePragma strict since its dataConCantHappen
- - - - -
846d96d9 by Hassan Al-Awwadi at 2024-10-28T17:51:31+01:00
no GHC.prelude in InlinePragma
- - - - -
6e92f6ee by Hassan Al-Awwadi at 2024-10-28T17:56:00+01:00
cleanup stray NonCanonical
- - - - -
e6c990bc by Hassan Al-Awwadi at 2024-10-28T18:11:13+01:00
remove explicit imports
- - - - -
2 changed files:
- compiler/Language/Haskell/Syntax/InlinePragma.hs
- utils/check-exact/ExactPrint.hs
Changes:
=====================================
compiler/Language/Haskell/Syntax/InlinePragma.hs
=====================================
@@ -1,22 +1,10 @@
module Language.Haskell.Syntax.InlinePragma where
-import GHC.Prelude
-
+import Data.Eq
+import Data.Int (Int)
+import Data.Bool (Bool(..))
+import Text.Show (Show)
import Language.Haskell.Syntax.Extension
- ( XActiveAfter,
- XActiveBefore,
- XAlwaysActive,
- XFinalActive,
- XInlinable,
- XInline,
- XInlinePragma,
- XNeverActive,
- XNoInline,
- XNoUserInlinePrag,
- XOpaque,
- XXActivation,
- XXCInlinePragma,
- XXInlineSpec )
data InlinePragma p -- Note [InlinePragma] in GHC.Hs.InlinePragma
= InlinePragma
@@ -26,7 +14,7 @@ data InlinePragma p -- Note [InlinePragma] in GHC.Hs.InlinePragma
-- See Note [inl_inline and inl_act] in GHC.Hs.InlinePragma
, inl_rule :: RuleMatchInfo -- Should the function be treated like a constructor?
}
- | XCInlinePragma (XXCInlinePragma p)
+ | XCInlinePragma !(XXCInlinePragma p)
-- | Inline Specification
=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2380,7 +2380,7 @@ instance ExactPrint (LocatedP (OverlapMode (GhcPass p))) where
c' <- markAnnCloseP'' c
return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Incoherent src))
- exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (NonCanonical src)) = do
+ exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (XOverlapMode (NonCanonical src))) = do
o' <- markAnnOpen'' o src "{-# INCOHERENT"
c' <- markAnnCloseP'' c
return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Incoherent src))
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/606eabf190f98fc0ece53349829ca8c00eee4013...e6c990bcdb31be117fa85d28dc2708f82d10874f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/606eabf190f98fc0ece53349829ca8c00eee4013...e6c990bcdb31be117fa85d28dc2708f82d10874f
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/20241028/d1394774/attachment-0001.html>
More information about the ghc-commits
mailing list