2cf80b1
Description: Don't include BufPos in interface files
2cf80b1
Author: Matthew Pickering
2cf80b1
Origin: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8972
2cf80b1
Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/22162
2cf80b1
Index: b/compiler/GHC/Iface/Ext/Types.hs
2cf80b1
===================================================================
2cf80b1
--- a/compiler/GHC/Iface/Ext/Types.hs
2cf80b1
+++ b/compiler/GHC/Iface/Ext/Types.hs
2cf80b1
@@ -746,5 +746,5 @@ toHieName name
2cf80b1
   | isKnownKeyName name = KnownKeyName (nameUnique name)
2cf80b1
   | isExternalName name = ExternalName (nameModule name)
2cf80b1
                                        (nameOccName name)
2cf80b1
-                                       (nameSrcSpan name)
2cf80b1
-  | otherwise = LocalName (nameOccName name) (nameSrcSpan name)
2cf80b1
+                                       (removeBufSpan $ nameSrcSpan name)
2cf80b1
+  | otherwise = LocalName (nameOccName name) (removeBufSpan $ nameSrcSpan name)
2cf80b1
Index: b/compiler/GHC/Types/SrcLoc.hs
2cf80b1
===================================================================
2cf80b1
--- a/compiler/GHC/Types/SrcLoc.hs
2cf80b1
+++ b/compiler/GHC/Types/SrcLoc.hs
2cf80b1
@@ -72,6 +72,7 @@ module GHC.Types.SrcLoc (
2cf80b1
         getBufPos,
2cf80b1
         BufSpan(..),
2cf80b1
         getBufSpan,
2cf80b1
+        removeBufSpan,
2cf80b1
 
2cf80b1
         -- * Located
2cf80b1
         Located,
2cf80b1
@@ -397,6 +398,10 @@ data UnhelpfulSpanReason
2cf80b1
   | UnhelpfulOther !FastString
2cf80b1
   deriving (Eq, Show)
2cf80b1
 
2cf80b1
+removeBufSpan :: SrcSpan -> SrcSpan
2cf80b1
+removeBufSpan (RealSrcSpan s _) = RealSrcSpan s Nothing
2cf80b1
+removeBufSpan s = s
2cf80b1
+
2cf80b1
 {- Note [Why Maybe BufPos]
2cf80b1
 ~~~~~~~~~~~~~~~~~~~~~~~~~~
2cf80b1
 In SrcLoc we store (Maybe BufPos); in SrcSpan we store (Maybe BufSpan).
2cf80b1
Index: b/compiler/GHC/Utils/Binary.hs
2cf80b1
===================================================================
2cf80b1
--- a/compiler/GHC/Utils/Binary.hs
2cf80b1
+++ b/compiler/GHC/Utils/Binary.hs
2cf80b1
@@ -1444,19 +1444,6 @@ instance Binary RealSrcSpan where
2cf80b1
             return (mkRealSrcSpan (mkRealSrcLoc f sl sc)
2cf80b1
                                   (mkRealSrcLoc f el ec))
2cf80b1
 
2cf80b1
-instance Binary BufPos where
2cf80b1
-  put_ bh (BufPos i) = put_ bh i
2cf80b1
-  get bh = BufPos <$> get bh
2cf80b1
-
2cf80b1
-instance Binary BufSpan where
2cf80b1
-  put_ bh (BufSpan start end) = do
2cf80b1
-    put_ bh start
2cf80b1
-    put_ bh end
2cf80b1
-  get bh = do
2cf80b1
-    start <- get bh
2cf80b1
-    end <- get bh
2cf80b1
-    return (BufSpan start end)
2cf80b1
-
2cf80b1
 instance Binary UnhelpfulSpanReason where
2cf80b1
   put_ bh r = case r of
2cf80b1
     UnhelpfulNoLocationInfo -> putByte bh 0
2cf80b1
@@ -1475,10 +1462,11 @@ instance Binary UnhelpfulSpanReason wher
2cf80b1
       _ -> UnhelpfulOther <$> get bh
2cf80b1
 
2cf80b1
 instance Binary SrcSpan where
2cf80b1
-  put_ bh (RealSrcSpan ss sb) = do
2cf80b1
+  put_ bh (RealSrcSpan ss _sb) = do
2cf80b1
           putByte bh 0
2cf80b1
+          -- BufSpan doesn't ever get serialised because the positions depend
2cf80b1
+          -- on build location.
2cf80b1
           put_ bh ss
2cf80b1
-          put_ bh sb
2cf80b1
 
2cf80b1
   put_ bh (UnhelpfulSpan s) = do
2cf80b1
           putByte bh 1
2cf80b1
@@ -1488,8 +1476,7 @@ instance Binary SrcSpan where
2cf80b1
           h <- getByte bh
2cf80b1
           case h of
2cf80b1
             0 -> do ss <- get bh
2cf80b1
-                    sb <- get bh
2cf80b1
-                    return (RealSrcSpan ss sb)
2cf80b1
+                    return (RealSrcSpan ss Nothing)
2cf80b1
             _ -> do s <- get bh
2cf80b1
                     return (UnhelpfulSpan s)
2cf80b1