{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module TextShow.GHC.Fingerprint () where
import Data.Semigroup.Compat (mtimesDefault)
import Data.Text.Lazy.Builder (Builder, singleton)
import Data.Word (Word64)
import GHC.Fingerprint.Type (Fingerprint(..))
import Prelude ()
import Prelude.Compat
import TextShow.Classes (TextShow(..))
import TextShow.Data.Integral (showbHex)
import TextShow.Utils (lengthB)
instance TextShow Fingerprint where
showb :: Fingerprint -> Builder
showb (Fingerprint Word64
w1 Word64
w2) = Word64 -> Builder
hex16 Word64
w1 forall a. Semigroup a => a -> a -> a
<> Word64 -> Builder
hex16 Word64
w2
where
hex16 :: Word64 -> Builder
hex16 :: Word64 -> Builder
hex16 Word64
i = let hex :: Builder
hex = forall a. (Integral a, TextShow a) => a -> Builder
showbHex Word64
i
in forall b a. (Integral b, Monoid a) => b -> a -> a
mtimesDefault (forall a. Ord a => a -> a -> a
max Int64
0 forall a b. (a -> b) -> a -> b
$ Int64
16 forall a. Num a => a -> a -> a
- Builder -> Int64
lengthB Builder
hex) (Char -> Builder
singleton Char
'0') forall a. Semigroup a => a -> a -> a
<> Builder
hex