{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- ----------------------------------------------------------------------------
--
--  (c) The University of Glasgow 2006
--
-- Fingerprints for recompilation checking and ABI versioning, and
-- implementing fast comparison of Typeable.
--
-- ----------------------------------------------------------------------------

module GHC.Fingerprint.Type (Fingerprint(..)) where

import GHC.Base
import GHC.List (length, replicate)
import GHC.Num
import GHC.Show
import GHC.Word
import Numeric (showHex)

-- Using 128-bit MD5 fingerprints for now.

data Fingerprint = Fingerprint {-# UNPACK #-} !Word64 {-# UNPACK #-} !Word64
  deriving ( Eq  -- ^ @since 4.4.0.0
           , Ord -- ^ @since 4.4.0.0
           )

-- | @since 4.7.0.0
instance Show Fingerprint where
  show :: Fingerprint -> String
show (Fingerprint Word64
w1 Word64
w2) = Word64 -> String
hex16 Word64
w1 String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word64 -> String
hex16 Word64
w2
    where
      -- | Formats a 64 bit number as 16 digits hex.
      hex16 :: Word64 -> String
      hex16 :: Word64 -> String
hex16 Word64
i = let hex :: String
hex = Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
i String
""
                 in Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
16 Int -> Int -> Int
forall a. Num a => a -> a -> a
- String -> Int
forall a. [a] -> Int
length String
hex) Char
'0' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
hex