commit 4aea313efabd6fbdd82e06446cf3dfd9bcdfff9c
parent 396bf8385106080140cd3a0a262688a10fb65ea3
Author: Jared Tobin <jared@jtobin.io>
Date: Mon, 16 Dec 2024 17:17:35 -0330
lib: witness script hash
Diffstat:
3 files changed, 56 insertions(+), 10 deletions(-)
diff --git a/lib/Bitcoin/Prim/Script.hs b/lib/Bitcoin/Prim/Script.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE BinaryLiterals #-}
{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
@@ -23,6 +24,10 @@ import Data.Word (Word8, Word16, Word32)
_MAX_REDEEM_SCRIPT_SIZE :: Int
_MAX_REDEEM_SCRIPT_SIZE = 520
+-- max witness script size
+_MAX_WITNESS_SCRIPT_SIZE :: Int
+_MAX_WITNESS_SCRIPT_SIZE = 10_000
+
-- realization for small builders
toStrict :: BSB.Builder -> BS.ByteString
toStrict = BS.toStrict . BSB.toLazyByteString
@@ -47,6 +52,18 @@ instance Show ScriptHash where
!w4_lo = BS.index "0123456789abcdef" (fi h .&. 0b00001111)
in C.chr (fi w4_hi) : C.chr (fi w4_lo) : go t
+newtype WitnessScriptHash = WitnessScriptHash BS.ByteString
+ deriving Eq
+
+instance Show WitnessScriptHash where
+ show (WitnessScriptHash bs) = "WitnessScriptHash 0x" <> go bs where
+ go b = case BS.uncons b of
+ Nothing -> mempty
+ Just (h, t) ->
+ let !w4_hi = BS.index "0123456789abcdef" (fi h `B.shiftR` 4)
+ !w4_lo = BS.index "0123456789abcdef" (fi h .&. 0b00001111)
+ in C.chr (fi w4_hi) : C.chr (fi w4_lo) : go t
+
-- | Render a 'Script' as a base16-encoded ByteString.
to_base16 :: Script -> BS.ByteString
to_base16 (Script bs) = toStrict (go 0) where
@@ -167,7 +184,6 @@ from_script (Script bs) = go 0 where
_ -> go (succ j)
-
ba_to_bs :: PB.ByteArray -> BS.ByteString
ba_to_bs bs = PB.foldrByteArray BS.cons mempty bs
@@ -176,6 +192,11 @@ to_scripthash (Script bs)
| PB.sizeofByteArray bs > _MAX_REDEEM_SCRIPT_SIZE = Nothing
| otherwise = Just (ScriptHash (RIPEMD160.hash (SHA256.hash (ba_to_bs bs))))
+to_witness_scripthash :: Script -> Maybe WitnessScriptHash
+to_witness_scripthash (Script bs)
+ | PB.sizeofByteArray bs > _MAX_WITNESS_SCRIPT_SIZE = Nothing
+ | otherwise = Just (WitnessScriptHash (SHA256.hash (ba_to_bs bs)))
+
pushbytes :: Opcode -> Maybe Int
pushbytes = \case
OP_PUSHBYTES_0 -> Just 00
@@ -516,8 +537,3 @@ data Opcode =
| OP_INVALIDOPCODE
deriving (Eq, Show, Enum)
--- XX hacky test stuff
-
-test_s :: BS.ByteString
-test_s = "76a91489abcdefabbaabbaabbaabbaabbaabbaabbaabba88ac"
-
diff --git a/ppad-btcprim.cabal b/ppad-btcprim.cabal
@@ -28,9 +28,9 @@ library
base >= 4.9 && < 5
, bytestring >= 0.9 && < 0.13
, primitive >= 0.8 && < 0.10
- , ppad-sha256
- , ppad-ripemd160
- , ppad-bech32
+ , ppad-sha256 >= 0.2 && < 0.3
+ , ppad-ripemd160 >= 0.1 && < 0.2
+ , ppad-bech32 >= 0.1 && < 0.2
test-suite btcprim-tests
type: exitcode-stdio-1.0
@@ -43,8 +43,11 @@ test-suite btcprim-tests
build-depends:
, base
+ , base16-bytestring
, bytestring
, ppad-btcprim
+ , ppad-sha256
+ , ppad-ripemd160
, tasty
, tasty-hunit
diff --git a/test/Main.hs b/test/Main.hs
@@ -1,8 +1,35 @@
+{-# LANGUAGE OverloadedStrings #-}
+
module Main where
-import qualified Bitcoin.Prim.Script as Script
+import qualified Data.ByteString as BS
+import Bitcoin.Prim.Script
import Test.Tasty
import Test.Tasty.HUnit
main :: IO ()
main = pure ()
+
+-- p2pkh
+
+-- https://en.bitcoin.it/wiki/Script#
+-- Standard_Transaction_to_Bitcoin_address_(pay-to-pubkey-hash)
+script_base16 :: BS.ByteString
+script_base16 = "76a91489abcdefabbaabbaabbaabbaabbaabbaabbaabba88ac"
+
+-- https://en.bitcoin.it/wiki/Script#
+-- Standard_Transaction_to_Bitcoin_address_(pay-to-pubkey-hash)
+script_terms :: [Term]
+script_terms = [
+ OPCODE OP_DUP,OPCODE OP_HASH160,OPCODE OP_PUSHBYTES_20,BYTE 0x89,BYTE 0xab
+ , BYTE 0xcd,BYTE 0xef,BYTE 0xab,BYTE 0xba,BYTE 0xab,BYTE 0xba,BYTE 0xab
+ , BYTE 0xba,BYTE 0xab,BYTE 0xba,BYTE 0xab,BYTE 0xba,BYTE 0xab,BYTE 0xba
+ , BYTE 0xab,BYTE 0xba,BYTE 0xab,BYTE 0xba,OPCODE OP_EQUALVERIFY
+ , OPCODE OP_CHECKSIG
+ ]
+
+-- p2sh
+
+redeemscript_base16 :: BS.ByteString
+redeemscript_base16 = "5221038282263212c609d9ea2a6e3e172de238d8c39cabe56f3f9e451d2c4c7739ba8721031b84c5567b126440995d3ed5aaba0565d71e1834604819ff9c17f5e9d5dd078f2102b4632d08485ff1df2db55b9dafd23347d1c47a457072a1e87be26896549a873753ae"
+