[Git][ghc/ghc][wip/ttg/types/basic] cleanup
Hassan Al-Awwadi (@hassan.awwadi)
gitlab at gitlab.haskell.org
Mon Oct 21 13:30:49 UTC 2024
Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC
Commits:
f2131576 by Hassan Al-Awwadi at 2024-10-21T15:30:31+02:00
cleanup
- - - - -
3 changed files:
- compiler/GHC/Hs/InlinePragma.hs
- compiler/GHC/Hs/OverlapPragma.hs
- compiler/GHC/Iface/Syntax.hs
Changes:
=====================================
compiler/GHC/Hs/InlinePragma.hs
=====================================
@@ -38,6 +38,7 @@ import Language.Haskell.Syntax.Basic(Arity)
import Language.Haskell.Syntax.InlinePragma
import Language.Haskell.Syntax.Extension
import GHC.Data.FastString (fsLit)
+import GHC.Utils.Binary (Binary, put_, get, putByte, getByte)
{-
************************************************************************
@@ -583,3 +584,11 @@ pprInline' emptyInline (InlinePragma
pp_info | isFunLike info = empty
| otherwise = ppr info
pprInline' _ (XCInlinePragma impossible) = dataConCantHappen impossible
+
+instance Binary RuleMatchInfo where
+ put_ bh FunLike = putByte bh 0
+ put_ bh ConLike = putByte bh 1
+ get bh = do
+ h <- getByte bh
+ if h == 1 then return ConLike
+ else return FunLike
\ No newline at end of file
=====================================
compiler/GHC/Hs/OverlapPragma.hs
=====================================
@@ -13,13 +13,15 @@ module GHC.Hs.OverlapPragma(
, convertOverlapMode
) where
+import GHC.Prelude
+
import Language.Haskell.Syntax.OverlapPragma
-import Language.Haskell.Syntax.Extension
+import Language.Haskell.Syntax.Extension
-import GHC.Prelude
-import GHC.Types.SourceText
import GHC.Hs.Extension (GhcPass, GhcTc)
+import GHC.Types.SourceText
+
import GHC.Utils.Binary
import GHC.Utils.Outputable
@@ -47,7 +49,7 @@ newtype NonCanonical = NonCanonical SourceText
-----------------------
--- converting
+-- converting
convertOverlapMode :: OverlapMode (GhcPass p) -> OverlapMode (GhcPass p')
convertOverlapMode = \case
NoOverlap s -> NoOverlap s
@@ -110,8 +112,9 @@ instance Binary OverlapFlag where
b <- get bh
return OverlapFlag { overlapMode = h, isSafeOverlap = b }
+
------------------------
--- helper functions
+-- helper functions
hasIncoherentFlag :: OverlapMode (GhcPass p) -> Bool
hasIncoherentFlag = \case
Incoherent _ -> True
@@ -127,7 +130,7 @@ hasOverlappableFlag = \case
_ -> False
hasOverlappingFlag :: OverlapMode (GhcPass p) -> Bool
-hasOverlappingFlag = \case
+hasOverlappingFlag = \case
Overlapping _ -> True
Overlaps _ -> True
Incoherent _ -> True
=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -1689,14 +1689,6 @@ instance Binary IfaceActivation where
ab <- get bh
return (IfActiveAfter src ab)
-instance Binary RuleMatchInfo where
- put_ bh FunLike = putByte bh 0
- put_ bh ConLike = putByte bh 1
- get bh = do
- h <- getByte bh
- if h == 1 then return ConLike
- else return FunLike
-
instance Binary IfaceInlineSpec where
put_ bh IfNoUserInlinePrag = putByte bh 0
put_ bh (IfInline s) = do putByte bh 1
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f21315769fd4c6ec228702abaa6701f080287566
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f21315769fd4c6ec228702abaa6701f080287566
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/20241021/afed0cb7/attachment-0001.html>
More information about the ghc-commits
mailing list