-- | This module exports hash constructions used by Bitcoin addresses. module Bitcoin.Address.Hash ( -- * PubHash160 PubHash160 , unPubHash160 , parsePubHash160 , pubHash160 , pubUncompressedHash160 -- * ScriptHash160 , ScriptHash160 , unScriptHash160 , parseScriptHash160 , scriptHash160 -- * ScriptSHA256 , ScriptSHA256 , unScriptSHA256 , parseScriptSHA256 , scriptSHA256 ) where import Bitcoin.Keys (Pub, pubCompressed, pubUncompressed) import Bitcoin.Hash (hash160) import Bitcoin.Hash.Prim (sha256) import Control.Monad import qualified Data.Bitcoin.Script as S import qualified Data.ByteString as B import qualified Data.ByteString.Builder as BB import qualified Data.ByteString.Lazy.Char8 as BL8 import Bitcoin.Address.Internal (scriptBytes) -------------------------------------------------------------------------------- -- | The 'hash160' of a 'Pub'lic key. newtype PubHash160 = PubHash160 B.ByteString deriving newtype (Eq, Ord) -- | Base-16 encoded. instance Show PubHash160 where showsPrec n (PubHash160 b) = showParen (n > 10) $ showString "PubHash160 " . mappend (BL8.unpack (BB.toLazyByteString (BB.byteStringHex b))) -- | Get the 20 bytes in 'PubHash160'. unPubHash160 :: PubHash160 -> B.ByteString {-# INLINE unPubHash160 #-} unPubHash160 (PubHash160 x) = x -- | Create a 'PubHash160' from its 20 raw bytes. parsePubHash160 :: B.ByteString -> Maybe PubHash160 {-# INLINE parsePubHash160 #-} parsePubHash160 b = do guard (B.length b == 20) pure (PubHash160 b) -- | The 'hash160' of the compressed SEC representation of a 'Pub'lic key. -- -- Usually, __this is what you want__. pubHash160 :: Pub -> PubHash160 {-# INLINE pubHash160 #-} pubHash160 = PubHash160 . hash160 . pubCompressed -- | The 'hash160' of the uncompressed SEC representation of a 'Pub'lic key. -- -- It's very unlikely that you want this. Except if it's ten years ago or you -- are dealing with very old addresses. -- -- __WARNING__ do not use this with SegWit addresses 'Bitcoin.Address.P2WPKH', -- or in 'Bitcoin.Address.P2WSH' 'S.Script's. pubUncompressedHash160 :: Pub -> PubHash160 {-# INLINE pubUncompressedHash160 #-} pubUncompressedHash160 = PubHash160 . hash160 . pubUncompressed -------------------------------------------------------------------------------- -- | The 'hash160' of a 'S.Script' as required by 'Bitcoin.Address.P2SH'. newtype ScriptHash160 = ScriptHash160 B.ByteString deriving newtype (Eq, Ord) -- | Base-16 encoded. instance Show ScriptHash160 where showsPrec n (ScriptHash160 b) = showParen (n > 10) $ showString "ScriptHash160 " . mappend (BL8.unpack (BB.toLazyByteString (BB.byteStringHex b))) -- | Get the 20 bytes in 'ScriptHash160'. unScriptHash160 :: ScriptHash160 -> B.ByteString {-# INLINE unScriptHash160 #-} unScriptHash160 (ScriptHash160 x) = x -- | Create a 'ScriptHash160' from its 20 raw bytes. parseScriptHash160 :: B.ByteString -> Maybe ScriptHash160 {-# INLINE parseScriptHash160 #-} parseScriptHash160 b = do guard (B.length b == 20) pure (ScriptHash160 b) -- | Hash a 'S.Script' as required by 'Bitcoin.Address.P2SH'. scriptHash160 :: S.Script -> ScriptHash160 {-# INLINE scriptHash160 #-} scriptHash160 = ScriptHash160 . hash160 . scriptBytes -------------------------------------------------------------------------------- -- | The 'sha256' of a 'S.Script' as required by 'Bitcoin.Address.P2WSH'. newtype ScriptSHA256 = ScriptSHA256 B.ByteString deriving newtype (Eq, Ord) -- | Base-16 encoded. instance Show ScriptSHA256 where showsPrec n (ScriptSHA256 b) = showParen (n > 10) $ showString "ScriptSHA256 " . mappend (BL8.unpack (BB.toLazyByteString (BB.byteStringHex b))) -- | Get the 32 bytes in 'ScriptSHA256'. unScriptSHA256 :: ScriptSHA256 -> B.ByteString {-# INLINE unScriptSHA256 #-} unScriptSHA256 (ScriptSHA256 x) = x -- | Create a 'ScriptSHA256' from its 32 raw bytes. parseScriptSHA256 :: B.ByteString -> Maybe ScriptSHA256 {-# INLINE parseScriptSHA256 #-} parseScriptSHA256 b = do guard (B.length b == 32) pure (ScriptSHA256 b) -- | Hash a 'S.Script' as required by 'Bitcoin.Address.P2WSH'. scriptSHA256 :: S.Script -> ScriptSHA256 {-# INLINE scriptSHA256 #-} scriptSHA256 = ScriptSHA256 . sha256 . scriptBytes