Skip to content
Snippets Groups Projects
Commit 7f0decd5 authored by Matthew Pickering's avatar Matthew Pickering Committed by Marge Bot
Browse files

Don't include BufPos in interface files

Ticket #22162 pointed out that the build directory was leaking into the
ABI hash of a module because the BufPos depended on the location of the
build tree.

BufPos is only used in GHC.Parser.PostProcess.Haddock, and the
information doesn't need to be propagated outside the context of a
module.

Fixes #22162
parent 66af1399
No related tags found
No related merge requests found
Pipeline #57678 canceled
......@@ -781,5 +781,5 @@ toHieName name
| isKnownKeyName name = KnownKeyName (nameUnique name)
| isExternalName name = ExternalName (nameModule name)
(nameOccName name)
(nameSrcSpan name)
| otherwise = LocalName (nameOccName name) (nameSrcSpan name)
(removeBufSpan $ nameSrcSpan name)
| otherwise = LocalName (nameOccName name) (removeBufSpan $ nameSrcSpan name)
......@@ -68,6 +68,7 @@ module GHC.Types.SrcLoc (
getBufPos,
BufSpan(..),
getBufSpan,
removeBufSpan,
-- * Located
Located,
......@@ -392,6 +393,10 @@ data UnhelpfulSpanReason
| UnhelpfulOther !FastString
deriving (Eq, Show)
removeBufSpan :: SrcSpan -> SrcSpan
removeBufSpan (RealSrcSpan s _) = RealSrcSpan s Strict.Nothing
removeBufSpan s = s
{- Note [Why Maybe BufPos]
~~~~~~~~~~~~~~~~~~~~~~~~~~
In SrcLoc we store (Maybe BufPos); in SrcSpan we store (Maybe BufSpan).
......
......@@ -1312,19 +1312,6 @@ instance Binary RealSrcSpan where
return (mkRealSrcSpan (mkRealSrcLoc f sl sc)
(mkRealSrcLoc f el ec))
instance Binary BufPos where
put_ bh (BufPos i) = put_ bh i
get bh = BufPos <$> get bh
instance Binary BufSpan where
put_ bh (BufSpan start end) = do
put_ bh start
put_ bh end
get bh = do
start <- get bh
end <- get bh
return (BufSpan start end)
instance Binary UnhelpfulSpanReason where
put_ bh r = case r of
UnhelpfulNoLocationInfo -> putByte bh 0
......@@ -1343,10 +1330,11 @@ instance Binary UnhelpfulSpanReason where
_ -> UnhelpfulOther <$> get bh
instance Binary SrcSpan where
put_ bh (RealSrcSpan ss sb) = do
put_ bh (RealSrcSpan ss _sb) = do
putByte bh 0
-- BufSpan doesn't ever get serialised because the positions depend
-- on build location.
put_ bh ss
put_ bh sb
put_ bh (UnhelpfulSpan s) = do
putByte bh 1
......@@ -1356,8 +1344,7 @@ instance Binary SrcSpan where
h <- getByte bh
case h of
0 -> do ss <- get bh
sb <- get bh
return (RealSrcSpan ss sb)
return (RealSrcSpan ss Strict.Nothing)
_ -> do s <- get bh
return (UnhelpfulSpan s)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment