module GHC.Types.SptEntry
( SptEntry(..)
)
where
import GHC.Types.Name ( Name )
import GHC.Fingerprint.Type ( Fingerprint )
import GHC.Prelude
import GHC.Utils.Binary
import GHC.Utils.Outputable
data SptEntry = SptEntry !Name !Fingerprint
instance Outputable SptEntry where
ppr :: SptEntry -> SDoc
ppr (SptEntry Name
n Fingerprint
fpr) = Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
n SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
colon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Fingerprint -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fingerprint
fpr
instance Binary SptEntry where
get :: ReadBinHandle -> IO SptEntry
get ReadBinHandle
bh = do
nm <- ReadBinHandle -> IO Name
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
fp <- get bh
pure $ SptEntry nm fp
put_ :: WriteBinHandle -> SptEntry -> IO ()
put_ WriteBinHandle
bh (SptEntry Name
nm Fingerprint
fp) = do
WriteBinHandle -> Name -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Name
nm IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Fingerprint
fp