Last active
August 14, 2021 14:33
-
-
Save roconnor-blockstream/2d0c3e340b7f17178984a71786280537 to your computer and use it in GitHub Desktop.
Example of sendings funds to an experimenal Simplicity address, `ert1l68kf04lea9jldsr5uszea6g6uf9jxx92jn3mswp7q3z04m4xnfzq4kqz7r` on elements regtest and redeeming thoses funds.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{ | |
"txid": "0e8e133dd88282a4f64919e046027d3b40a572c32d0ce6b646a403bed0d51750", | |
"hash": "0e8e133dd88282a4f64919e046027d3b40a572c32d0ce6b646a403bed0d51750", | |
"wtxid": "0e8e133dd88282a4f64919e046027d3b40a572c32d0ce6b646a403bed0d51750", | |
"withash": "ab3393f4fb64685a4de07ac89c6903d6a0ba107c87fff33c9a981a7590bae48e", | |
"version": 2, | |
"size": 240, | |
"vsize": 240, | |
"weight": 960, | |
"locktime": 0, | |
"vin": [ | |
{ | |
"txid": "90673637f96363266d3836bd07f4a319ba9d363749076fda02e51eb2630b46d9", | |
"vout": 0, | |
"scriptSig": { | |
"asm": "", | |
"hex": "" | |
}, | |
"is_pegin": false, | |
"sequence": 4294967293 | |
} | |
], | |
"vout": [ | |
{ | |
"value": 1.00001000, | |
"asset": "b248df0c57c299290f3a46ff74e4a8ca9f365632bfd6fa43f915e6756bc756ee", | |
"commitmentnonce": "", | |
"commitmentnonce_fully_valid": false, | |
"n": 0, | |
"scriptPubKey": { | |
"asm": "-1 65e3fec95a686e3328badbb8cc7243febbd7f399c629ef22678fa0ae30b79401", | |
"hex": "4f2065e3fec95a686e3328badbb8cc7243febbd7f399c629ef22678fa0ae30b79401", | |
"reqSigs": 1, | |
"type": "witness_unknown", | |
"addresses": [ | |
"ert1lvh3laj26dphrx296mwuvcujrl6aa0uuecc577gn837s2uv9hjsqsyrhw3l" | |
] | |
} | |
}, | |
{ | |
"value": 999998.99994200, | |
"asset": "b248df0c57c299290f3a46ff74e4a8ca9f365632bfd6fa43f915e6756bc756ee", | |
"commitmentnonce": "", | |
"commitmentnonce_fully_valid": false, | |
"n": 1, | |
"scriptPubKey": { | |
"asm": "0 9d49d38da6ace03ebdc8ee76ddaa462c2f30abf5", | |
"hex": "00149d49d38da6ace03ebdc8ee76ddaa462c2f30abf5", | |
"reqSigs": 1, | |
"type": "witness_v0_keyhash", | |
"addresses": [ | |
"ert1qn4ya8rdx4nsra0wgaemdm2jx9shnp2l4kcp6gc" | |
] | |
} | |
}, | |
{ | |
"value": 0.00004800, | |
"asset": "b248df0c57c299290f3a46ff74e4a8ca9f365632bfd6fa43f915e6756bc756ee", | |
"commitmentnonce": "", | |
"commitmentnonce_fully_valid": false, | |
"n": 2, | |
"scriptPubKey": { | |
"asm": "", | |
"hex": "", | |
"type": "fee" | |
} | |
} | |
], | |
"hex": "020000000001d9460b63b21ee502da6f074937369dba19a3f407bd36386d266363f9373667900000000000fdffffff0301ee56c76b75e615f943fad6bf3256369fcaa8e474ff463a0f2999c2570cdf48b2010000000005f5e4e800224f2065e3fec95a686e3328badbb8cc7243febbd7f399c629ef22678fa0ae30b7940101ee56c76b75e615f943fad6bf3256369fcaa8e474ff463a0f2999c2570cdf48b20100005af30a844858001600149d49d38da6ace03ebdc8ee76ddaa462c2f30abf501ee56c76b75e615f943fad6bf3256369fcaa8e474ff463a0f2999c2570cdf48b20100000000000012c0000000000000", | |
"blockhash": "481c9b4e66209354f0e5a1ef3c589ab28f220ba9b69a474b8060357b6b8dbd7b", | |
"confirmations": 2, | |
"time": 1600265345, | |
"blocktime": 1600265345 | |
} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Simplicity.Elements.Example.CheckSigHashAll where | |
-- Built upon https://github.com/ElementsProject/simplicity/tree/ccd93b3dd7dab92f22fbc7ebe1e2f1359d854f59 | |
import qualified Codec.Binary.Bech32.Internal as Bech32 | |
import Data.Array (inRange, listArray) | |
import Data.Bifunctor (first) | |
import Data.Bits ((.&.), shiftL, testBit, xor) | |
import qualified Data.ByteString as BS | |
import qualified Data.ByteString.Char8 as BSC | |
import qualified Data.ByteString.Lazy as BSL | |
import Data.Char (toLower, toUpper) | |
import Data.Foldable (toList) | |
import Data.List (foldl') | |
import Data.Maybe (isNothing) | |
import Data.Serialize ( decode, encode, runPut | |
, put, putByteString | |
, putWord8, putWord16le, putWord32le, putWord64le | |
) | |
import Data.String (fromString) | |
import qualified Data.Text as Text | |
import Numeric (readHex, showHex) | |
import Simplicity.Digest | |
import Simplicity.LibSecp256k1.Schnorr | |
import Simplicity.MerkleRoot | |
import Simplicity.Programs.CheckSigHash | |
import Simplicity.Elements.Dag (unwrap) | |
import Simplicity.Elements.DataTypes | |
import Simplicity.Elements.Primitive | |
import Simplicity.Elements.Jets | |
import Simplicity.Elements.Programs.CheckSigHashAll.Lib | |
import Simplicity.Serialization | |
import qualified Simplicity.Ty.Word as Ty | |
import Simplicity.Word | |
order = 0xFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFEBAAEDCE6AF48A03BBFD25E8CD0364141 | |
priv = order `div` 2 | |
pubkey = XOnlyPubKey 0x00000000000000000000003b78ce563f89a0ed9414f5aa28ad0d96d6795f9c63 | |
k = order `div` 2 | |
r :: Word256 | |
r = 0x00000000000000000000003b78ce563f89a0ed9414f5aa28ad0d96d6795f9c63 | |
schnorrTag = encode . bsHash $ BSC.pack "BIPSchnorr" | |
sigTag = encode . bsHash $ BSC.pack "Simplicity-Draft\USSignature" | |
dummysig = Sig 0 0 | |
simplictySegwitVersion = (-1) `mod` 32 | |
Right hrp = Bech32.humanReadablePartFromText . fromString $ "ert" | |
hashAll_jets = jetSubst hashAll | |
program_jets sig = jetSubst $ checkSigHash' (unwrap hashAll_jets) pubkey sig | |
program_cmr = commitmentRoot . unwrap $ program_jets dummysig | |
Right address = Bech32.encode hrp (Bech32.dataPartFromWords [toEnum simplictySegwitVersion] | |
<> (Bech32.dataPartFromBytes . encode $ program_cmr)) | |
default_amount = "100001000" | |
default_fee = "1000" | |
default_asset = "b248df0c57c299290f3a46ff74e4a8ca9f365632bfd6fa43f915e6756bc756ee" | |
applyDefault def "" = def | |
applyDefault _ str = str | |
main :: IO () | |
main = do | |
putStrLn $ "Computing universal address for " ++ show pubkey ++ ": " ++ show address | |
putStrLn "" | |
putStrLn "Redeem" | |
putStrLn "======" | |
putStr "Enter blech32 payment address: " | |
blech_input <- getLine | |
putStr "Enter source txid: " | |
txid_input <- getLine | |
putStr "Enter source index: " | |
vout_input <- getLine | |
putStr $ "Enter input amount (" ++ default_amount ++ "): " | |
amount_input <- applyDefault default_amount <$> getLine | |
putStr $ "Enter explicit asset (" ++ default_asset ++ "): " | |
asset_input <- applyDefault default_asset <$> getLine | |
putStr $ "Enter fee (" ++ default_fee ++ "): " | |
fee_input <- applyDefault default_fee <$> getLine | |
sigtx <- either fail return $ parseInputs blech_input txid_input vout_input amount_input asset_input fee_input | |
let Just env = primEnv sigtx 0 todo | |
let Just hash = fastEval (unwrap hashAll_jets) env () | |
let whash = fromIntegral (Ty.fromWord256 hash) :: Word256 | |
let msg = bsHash $ sigTag <> sigTag <> encode (commitmentRoot (unwrap hashAll_jets)) <> encode whash | |
let e = integerHash256 . bsHash $ schnorrTag <> schnorrTag <> encode r <> encode pubkey <> encode msg | |
let sig = Sig r (fromInteger ((k + priv * e) `mod` order)) | |
let program_sig = program_jets sig | |
putStrLn $ "Computing signature: " ++ show (bsToHex (encode sig)) | |
putStr "Checking signature: " | |
case fastEval (unwrap program_sig) env () of | |
Just () -> putStrLn "ok" | |
Nothing -> fail "bad signature" | |
putStrLn "Simplicity Program:" | |
let witness = runPut . putBitStream . putTermLengthCode $ unwrap program_sig | |
putStrLn . bsToHex $ witness | |
putStrLn "Transaction:" | |
putStrLn . bsToHex . runPut $ putOurTx sigtx witness | |
parseInputs blech txid_str vout_str amount_str asset_str fee_str = do | |
(hrp, blechData) <- first show $ blech32Decode (fromString blech) | |
guardE (Bech32.humanReadablePartToText hrp == fromString "el") "Not an el address" | |
let blechWord5 = Bech32.dataPartToWords blechData | |
guardE (not (null blechWord5)) "Empty address" | |
let sv = fromIntegral . fromEnum $ head blechWord5 | |
(blinding_pubkey, address) <- maybe (Left "Bad Binary Encoding") (Right . BS.splitAt 33) | |
$ Bech32.dataPartToBytes (Bech32.dataPartFromWords (tail blechWord5)) | |
guardE (inRange (2, 40) (BS.length address)) "Bad address size" | |
txid_hex <- BS.reverse <$> hexToBS txid_str | |
asset_hex <- BS.reverse <$> hexToBS asset_str | |
asset <- Asset . Explicit <$> decode asset_hex | |
txid <- decode txid_hex | |
vout <- case reads vout_str of {[(n,[])] -> Right n; _ -> Left "invalid vout" } | |
amount <- case reads amount_str of {[(n,[])] -> Right n; _ -> Left "invalid amount" } | |
fee <- case reads fee_str of {[(n,[])] -> Right n; _ -> Left "invalid fee" } | |
guardE (fee < amount) "Fee too large" | |
let input = SigTxInput { sigTxiIsPegin = False | |
, sigTxiPreviousOutpoint = Outpoint { opHash = txid, opIndex = vout } | |
, sigTxiTxo = UTXO { utxoAsset = asset, utxoAmount = Amount (Explicit amount), utxoScript = todo } | |
, sigTxiSequence = 0xfffffffd | |
, sigTxiIssuance = Nothing } | |
let outputScript = BS.singleton (if 0 == sv then 0 else sv + 0x50) <> BS.singleton (fromIntegral (BS.length address)) <> address | |
let output = TxOutput { txoAsset = asset, txoAmount = Amount (Explicit (amount - fee)), txoNonce = Nothing, txoScript = BSL.fromStrict outputScript } | |
let outputFee = TxOutput { txoAsset = asset, txoAmount = Amount (Explicit fee), txoNonce = Nothing, txoScript = mempty } | |
let inputs = listArray (0, 0) [input] | |
let outputs = listArray (0, 1) [output, outputFee] | |
return SigTx { sigTxVersion = 2, sigTxIn = inputs, sigTxOut = outputs, sigTxLock = 0} | |
hexToBS [] = Right mempty | |
hexToBS [x] = Left "odd length" | |
hexToBS (x:y:t) = go (readHex [x,y]) | |
where | |
go [(n,[])] = mappend (BS.singleton n) <$> hexToBS t | |
go _ = Left "bad characters" | |
bsToHex s = BS.unpack s >>= render | |
where | |
render n = replicate (2-l) '0' ++ str | |
where | |
str = showHex n "" | |
l = length str | |
-- simplified to be specific to our transaction. | |
putOurTx tx witness = | |
putWord32le (sigTxVersion tx) | |
>> putWord8 0x01 -- flag for witness | |
>> putWord8 0x01 -- number of inputs | |
>> put (sigTxiPreviousOutpoint input) | |
>> putWord8 0x00 -- sigScript | |
>> putWord32le (sigTxiSequence input) | |
>> putWord8 0x02 -- number of outputs | |
>> putOutput output | |
>> putOutput fee | |
>> putWord32le (sigTxLock tx) | |
>> putWord8 0x00 -- range proof | |
>> putWord8 0x00 -- range proof | |
>> putWord8 0x01 -- witness stack size | |
>> putVarBS witness | |
>> putWord8 0x00 -- pegin proof | |
>> putWord8 0x00 -- surjection proof | |
>> putWord8 0x00 -- range proof | |
>> putWord8 0x00 -- surjection proof | |
>> putWord8 0x00 -- range proof | |
where | |
[input] = toList (sigTxIn tx) | |
[output, fee] = toList (sigTxOut tx) | |
putOutput txo = | |
put (txoAsset txo) | |
>> put (txoAmount txo) | |
>> putNonce (txoNonce txo) | |
>> putVarBS (BSL.toStrict (txoScript txo)) | |
varLength n | n < 0xfc = putWord8 (fromIntegral n) | |
| n <= 0xffff = putWord8 0xfd >> putWord16le (fromIntegral n) | |
| n <= 0xffffffff = putWord8 0xfe >> putWord32le (fromIntegral n) | |
| n <= 0xffffffffffffffff = putWord8 0xff >> putWord64le (fromIntegral n) | |
putVarBS bs = varLength (BS.length bs) >> putByteString bs | |
todo :: a | |
todo = undefined | |
-- Below is derived from <https://hackage.haskell.org/package/bech32-1.1.0> and is under Apache-2.0 licence | |
-- <https://hackage.haskell.org/package/bech32-1.1.0/src/LICENSE> | |
blech32Decode blech32 = do | |
guardE (Text.map toUpper blech32 == blech32 || Text.map toLower blech32 == blech32) | |
Bech32.StringToDecodeHasMixedCase | |
(hrpUnparsed, dcpUnparsed) <- | |
maybeToEither Bech32.StringToDecodeMissingSeparatorChar $ | |
splitAtLastOccurrence Bech32.separatorChar $ Text.map toLower blech32 | |
hrp <- first humanReadablePartError $ Bech32.humanReadablePartFromText hrpUnparsed | |
dcp <- first | |
(Bech32.StringToDecodeContainsInvalidChars . fmap | |
(\(Bech32.CharPosition p) -> | |
Bech32.CharPosition $ p + Text.length hrpUnparsed + separatorLength)) | |
(parseDataWithChecksumPart dcpUnparsed) | |
guardE (length dcp >= checksumLength) Bech32.StringToDecodeTooShort | |
guardE (verifyChecksum hrp dcp) $ | |
Bech32.StringToDecodeContainsInvalidChars [] {-$ findErrorPositions hrp dcp -} | |
let dp = Bech32.dataPartFromWords $ take (length dcp - checksumLength) dcp | |
return (hrp, dp) | |
where | |
checksumLength = 12 | |
separatorLength = 1 | |
verifyChecksum hrp dat = polymod (Bech32.humanReadablePartToWords hrp ++ dat) == 1 | |
polymod :: [Bech32.Word5] -> Word64 | |
polymod values = foldl' go 1 values .&. 0xfffffffffffffff | |
where | |
go chk value = | |
foldl' xor chk' [g | (g, i) <- zip generator [55 ..], testBit chk i] | |
where | |
chk' = (chk `shiftL` 5) `xor` (fromIntegral . fromEnum) value | |
generator = | |
[ 0x7d52fba40bd886 | |
, 0x5e8dbf1a03950c | |
, 0x1c3a3c74072a18 | |
, 0x385d72fa0e5139 | |
, 0x7093e5a608865b ] | |
-- | Parse a data-with-checksum part, checking that each character is part | |
-- of the supported character set. If one or more characters are not in the | |
-- supported character set, return the list of illegal character positions. | |
parseDataWithChecksumPart :: Text.Text -> Either [Bech32.CharPosition] [Bech32.Word5] | |
parseDataWithChecksumPart dcpUnparsed = | |
case mapM Bech32.dataCharToWord $ Text.unpack dcpUnparsed of | |
Nothing -> Left invalidCharPositions | |
Just dcp -> Right dcp | |
where | |
invalidCharPositions = | |
Bech32.CharPosition . fst <$> filter (isNothing . snd) | |
([0 .. ] `zip` (Bech32.dataCharToWord <$> Text.unpack dcpUnparsed)) | |
-- | Convert an error encountered while parsing a human-readable part into a | |
-- general decoding error. | |
humanReadablePartError Bech32.HumanReadablePartTooLong = Bech32.StringToDecodeContainsInvalidChars [Bech32.CharPosition Bech32.humanReadablePartMaxLength] | |
humanReadablePartError Bech32.HumanReadablePartTooShort = Bech32.StringToDecodeContainsInvalidChars [Bech32.CharPosition $ Bech32.humanReadablePartMinLength - 1] | |
humanReadablePartError (Bech32.HumanReadablePartContainsInvalidChars ps) = Bech32.StringToDecodeContainsInvalidChars ps | |
guardE :: Bool -> e -> Either e () | |
guardE b e = if b then Right () else Left e | |
maybeToEither a (Just b) = Right b | |
maybeToEither a Nothing = Left a | |
-- | Splits the given 'Text' into a prefix and a suffix using the last | |
-- occurrence of the specified separator character as a splitting point. | |
-- Evaluates to 'Nothing' if the specified 'Text' does not contain the | |
-- separator character. | |
splitAtLastOccurrence :: Char -> Text.Text -> Maybe (Text.Text, Text.Text) | |
splitAtLastOccurrence c s | |
| isNothing (Text.find (== c) s) = Nothing | |
| otherwise = pure (prefix, suffix) | |
where | |
(prefixPlusOne, suffix) = Text.breakOnEnd (Text.pack [c]) s | |
prefix = Text.dropEnd 1 prefixPlusOne |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Computing universal address for XOnlyPubKey 86918276961810349294276103416548851884759982251107: "ert1lvh3laj26dphrx296mwuvcujrl6aa0uuecc577gn837s2uv9hjsqsyrhw3l" | |
Redeem | |
====== | |
Enter blech32 payment address: el1qqdt7gm0hjwm0ypslyt038vdf7j3cfudtkszsrxm6pxfhtu25qmgjh3s03ftjw822nx4v9a06vl9u42mgrjhaqjzgyxwdp6yle | |
Enter source txid: 0e8e133dd88282a4f64919e046027d3b40a572c32d0ce6b646a403bed0d51750 | |
Enter source index: 0 | |
Enter input amount (100001000): | |
Enter explicit asset (b248df0c57c299290f3a46ff74e4a8ca9f365632bfd6fa43f915e6756bc756ee): | |
Enter fee (1000): | |
Computing signature: "00000000000000000000003b78ce563f89a0ed9414f5aa28ad0d96d6795f9c63edc8553daec50ea2486737a9139020775bba8def13938d41f4402c2917f3ff77" | |
Checking signature: ok | |
Simplicity Program: | |
e8e34902040810204174081680aea128a85a82d416fd0268167c00502d7c085b350a05805a340b4ee140b8170217020a85985c002e121706e022e001708e1027108a85c37830b8105c238985a02a164171570c1311703e0c2816dda2e2fe2613880542c42d41703e002e34e02281708e201704e21140b00b8b3860b89b88c502e1fc582e28e37140b00b405c002e260b8db9082e1e171af108b8d790028160171c7128b89b8d8502e2de430b8838d8502c02d0172139002e3ee25140b90fc8e1723790e281601724b9242e4471d0a05c73c8e171a7220502c02d017000b8ff91a2e51f214502e4a72705c95e488a05805c80e488b90fca3140b929c9a1729391e281601680b923ca01723f924281728f94a2e43f29c502c02e5072c44e002e4af2445c8de5a0a05805985bc2e1e45213986490204170130102c08141c2cf316616a0991c1c862481020b80b00b00b01b810a03ac830d0c30c30e1663e930fa45061861c2d23e930fc04507d42830f9987e0e283f00140b3187d461f5187e20141f848a05985a870b8585c1b821c2e0038e164071a01c9253139da418830c30c385992408105c04c04c05804de70b4e42c82d213821c1c80e023f0830fc245061f130fc34502c461f4187d061f890502c42d0494482814828148281482817080b858e17072481020408102040b50ba85a829ac502d616388b109b85805b82dc16e0b705b851c2e291c2e3e182e2ae2b171485c50139302e28e28102cb2171685c67c662e3209c602c02d01680b8bc4e3b140b70c0f040395c172c498081140304f0644182a16441c2a30c4187186da71c61f9be38e30dce11870b01f98d30e16016d0b810dc2ce385805c2c838e385881c6217429f4378ba15ba16c502e856e85617436f4298a05805d0f1d0a22e85de880140ba1cfa1e45d0bdd0c0281601680ba193a1bc5d111d0be281743a74390ba1502a1743ff43b8ba1402e866e88013828a85905b42e886e8741743af4360a05d0ddd0dc2e84b0a85d0e3d0d82e885e889140ba1e3a1bc4e857150b30ba227a2485d08a17442f4488ba23ba1fc502c02e895e8961741d85d127d0f62e899e89c140b00b30b705c316ee0a05838102e3f1f90a61fa0b506182c006a1663f41a1fa0d4da05007000e206607010fa11c2e84901c185d179d1962746589d1962746589d1962e8cce8cc140ba34ba2b44e8d21746905d1a41746905985985bc07130ba260e28f047a400000000000000000000000076f19cac7f1341db2829eb54515a1b2dacf2bf38c7db90aa7b5d8a1d4490ce6f52272040eeb7751bde27271a83e88058522fe7feee0 | |
Transaction: | |
0200000001015017d5d0be03a446b6e60c2dc372a5403b7d0246e01949f6a48282d83d138e0e0000000000fdffffff0201ee56c76b75e615f943fad6bf3256369fcaa8e474ff463a0f2999c2570cdf48b2010000000005f5e10000160014c60f8a57271d4a99aac2f5fa67cbcaab681cafd001ee56c76b75e615f943fad6bf3256369fcaa8e474ff463a0f2999c2570cdf48b20100000000000003e8000000000000000001fdb803e8e34902040810204174081680aea128a85a82d416fd0268167c00502d7c085b350a05805a340b4ee140b8170217020a85985c002e121706e022e001708e1027108a85c37830b8105c238985a02a164171570c1311703e0c2816dda2e2fe2613880542c42d41703e002e34e02281708e201704e21140b00b8b3860b89b88c502e1fc582e28e37140b00b405c002e260b8db9082e1e171af108b8d790028160171c7128b89b8d8502e2de430b8838d8502c02d0172139002e3ee25140b90fc8e1723790e281601724b9242e4471d0a05c73c8e171a7220502c02d017000b8ff91a2e51f214502e4a72705c95e488a05805c80e488b90fca3140b929c9a1729391e281601680b923ca01723f924281728f94a2e43f29c502c02e5072c44e002e4af2445c8de5a0a05805985bc2e1e45213986490204170130102c08141c2cf316616a0991c1c862481020b80b00b00b01b810a03ac830d0c30c30e1663e930fa45061861c2d23e930fc04507d42830f9987e0e283f00140b3187d461f5187e20141f848a05985a870b8585c1b821c2e0038e164071a01c9253139da418830c30c385992408105c04c04c05804de70b4e42c82d213821c1c80e023f0830fc245061f130fc34502c461f4187d061f890502c42d0494482814828148281482817080b858e17072481020408102040b50ba85a829ac502d616388b109b85805b82dc16e0b705b851c2e291c2e3e182e2ae2b171485c50139302e28e28102cb2171685c67c662e3209c602c02d01680b8bc4e3b140b70c0f040395c172c498081140304f0644182a16441c2a30c4187186da71c61f9be38e30dce11870b01f98d30e16016d0b810dc2ce385805c2c838e385881c6217429f4378ba15ba16c502e856e85617436f4298a05805d0f1d0a22e85de880140ba1cfa1e45d0bdd0c0281601680ba193a1bc5d111d0be281743a74390ba1502a1743ff43b8ba1402e866e88013828a85905b42e886e8741743af4360a05d0ddd0dc2e84b0a85d0e3d0d82e885e889140ba1e3a1bc4e857150b30ba227a2485d08a17442f4488ba23ba1fc502c02e895e8961741d85d127d0f62e899e89c140b00b30b705c316ee0a05838102e3f1f90a61fa0b506182c006a1663f41a1fa0d4da05007000e206607010fa11c2e84901c185d179d1962746589d1962746589d1962e8cce8cc140ba34ba2b44e8d21746905d1a41746905985985bc07130ba260e28f047a400000000000000000000000076f19cac7f1341db2829eb54515a1b2dacf2bf38c7db90aa7b5d8a1d4490ce6f52272040eeb7751bde27271a83e88058522fe7feee00000000000 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{ | |
"txid": "e540eb71a139da3dcf2926bcd90c2b2b417e5f59e855620c0853eb76415d3d5b", | |
"hash": "73f14ee301e733292193b33fb7f470ccd97cb33f96c131f84120a524f7b909dd", | |
"wtxid": "73f14ee301e733292193b33fb7f470ccd97cb33f96c131f84120a524f7b909dd", | |
"withash": "641caa1ca4938fc70ae7ab715a02fed63dd567a9150fdbf06fe1423565272648", | |
"version": 2, | |
"size": 1125, | |
"vsize": 403, | |
"weight": 1611, | |
"locktime": 0, | |
"vin": [ | |
{ | |
"txid": "0e8e133dd88282a4f64919e046027d3b40a572c32d0ce6b646a403bed0d51750", | |
"vout": 0, | |
"scriptSig": { | |
"asm": "", | |
"hex": "" | |
}, | |
"is_pegin": false, | |
"sequence": 4294967293, | |
"txinwitness": [ | |
"e8e34902040810204174081680aea128a85a82d416fd0268167c00502d7c085b350a05805a340b4ee140b8170217020a85985c002e121706e022e001708e1027108a85c37830b8105c238985a02a164171570c1311703e0c2816dda2e2fe2613880542c42d41703e002e34e02281708e201704e21140b00b8b3860b89b88c502e1fc582e28e37140b00b405c002e260b8db9082e1e171af108b8d790028160171c7128b89b8d8502e2de430b8838d8502c02d0172139002e3ee25140b90fc8e1723790e281601724b9242e4471d0a05c73c8e171a7220502c02d017000b8ff91a2e51f214502e4a72705c95e488a05805c80e488b90fca3140b929c9a1729391e281601680b923ca01723f924281728f94a2e43f29c502c02e5072c44e002e4af2445c8de5a0a05805985bc2e1e45213986490204170130102c08141c2cf316616a0991c1c862481020b80b00b00b01b810a03ac830d0c30c30e1663e930fa45061861c2d23e930fc04507d42830f9987e0e283f00140b3187d461f5187e20141f848a05985a870b8585c1b821c2e0038e164071a01c9253139da418830c30c385992408105c04c04c05804de70b4e42c82d213821c1c80e023f0830fc245061f130fc34502c461f4187d061f890502c42d0494482814828148281482817080b858e17072481020408102040b50ba85a829ac502d616388b109b85805b82dc16e0b705b851c2e291c2e3e182e2ae2b171485c50139302e28e28102cb2171685c67c662e3209c602c02d01680b8bc4e3b140b70c0f040395c172c498081140304f0644182a16441c2a30c4187186da71c61f9be38e30dce11870b01f98d30e16016d0b810dc2ce385805c2c838e385881c6217429f4378ba15ba16c502e856e85617436f4298a05805d0f1d0a22e85de880140ba1cfa1e45d0bdd0c0281601680ba193a1bc5d111d0be281743a74390ba1502a1743ff43b8ba1402e866e88013828a85905b42e886e8741743af4360a05d0ddd0dc2e84b0a85d0e3d0d82e885e889140ba1e3a1bc4e857150b30ba227a2485d08a17442f4488ba23ba1fc502c02e895e8961741d85d127d0f62e899e89c140b00b30b705c316ee0a05838102e3f1f90a61fa0b506182c006a1663f41a1fa0d4da05007000e206607010fa11c2e84901c185d179d1962746589d1962746589d1962e8cce8cc140ba34ba2b44e8d21746905d1a41746905985985bc07130ba260e28f047a400000000000000000000000076f19cac7f1341db2829eb54515a1b2dacf2bf38c7db90aa7b5d8a1d4490ce6f52272040eeb7751bde27271a83e88058522fe7feee0" | |
] | |
} | |
], | |
"vout": [ | |
{ | |
"value": 1.00000000, | |
"asset": "b248df0c57c299290f3a46ff74e4a8ca9f365632bfd6fa43f915e6756bc756ee", | |
"commitmentnonce": "", | |
"commitmentnonce_fully_valid": false, | |
"n": 0, | |
"scriptPubKey": { | |
"asm": "0 c60f8a57271d4a99aac2f5fa67cbcaab681cafd0", | |
"hex": "0014c60f8a57271d4a99aac2f5fa67cbcaab681cafd0", | |
"reqSigs": 1, | |
"type": "witness_v0_keyhash", | |
"addresses": [ | |
"ert1qcc8c54e8r49fn2kz7hax0j724d5pet7sady3v2" | |
] | |
} | |
}, | |
{ | |
"value": 0.00001000, | |
"asset": "b248df0c57c299290f3a46ff74e4a8ca9f365632bfd6fa43f915e6756bc756ee", | |
"commitmentnonce": "", | |
"commitmentnonce_fully_valid": false, | |
"n": 1, | |
"scriptPubKey": { | |
"asm": "", | |
"hex": "", | |
"type": "fee" | |
} | |
} | |
], | |
"hex": "0200000001015017d5d0be03a446b6e60c2dc372a5403b7d0246e01949f6a48282d83d138e0e0000000000fdffffff0201ee56c76b75e615f943fad6bf3256369fcaa8e474ff463a0f2999c2570cdf48b2010000000005f5e10000160014c60f8a57271d4a99aac2f5fa67cbcaab681cafd001ee56c76b75e615f943fad6bf3256369fcaa8e474ff463a0f2999c2570cdf48b20100000000000003e8000000000000000001fdb803e8e34902040810204174081680aea128a85a82d416fd0268167c00502d7c085b350a05805a340b4ee140b8170217020a85985c002e121706e022e001708e1027108a85c37830b8105c238985a02a164171570c1311703e0c2816dda2e2fe2613880542c42d41703e002e34e02281708e201704e21140b00b8b3860b89b88c502e1fc582e28e37140b00b405c002e260b8db9082e1e171af108b8d790028160171c7128b89b8d8502e2de430b8838d8502c02d0172139002e3ee25140b90fc8e1723790e281601724b9242e4471d0a05c73c8e171a7220502c02d017000b8ff91a2e51f214502e4a72705c95e488a05805c80e488b90fca3140b929c9a1729391e281601680b923ca01723f924281728f94a2e43f29c502c02e5072c44e002e4af2445c8de5a0a05805985bc2e1e45213986490204170130102c08141c2cf316616a0991c1c862481020b80b00b00b01b810a03ac830d0c30c30e1663e930fa45061861c2d23e930fc04507d42830f9987e0e283f00140b3187d461f5187e20141f848a05985a870b8585c1b821c2e0038e164071a01c9253139da418830c30c385992408105c04c04c05804de70b4e42c82d213821c1c80e023f0830fc245061f130fc34502c461f4187d061f890502c42d0494482814828148281482817080b858e17072481020408102040b50ba85a829ac502d616388b109b85805b82dc16e0b705b851c2e291c2e3e182e2ae2b171485c50139302e28e28102cb2171685c67c662e3209c602c02d01680b8bc4e3b140b70c0f040395c172c498081140304f0644182a16441c2a30c4187186da71c61f9be38e30dce11870b01f98d30e16016d0b810dc2ce385805c2c838e385881c6217429f4378ba15ba16c502e856e85617436f4298a05805d0f1d0a22e85de880140ba1cfa1e45d0bdd0c0281601680ba193a1bc5d111d0be281743a74390ba1502a1743ff43b8ba1402e866e88013828a85905b42e886e8741743af4360a05d0ddd0dc2e84b0a85d0e3d0d82e885e889140ba1e3a1bc4e857150b30ba227a2485d08a17442f4488ba23ba1fc502c02e895e8961741d85d127d0f62e899e89c140b00b30b705c316ee0a05838102e3f1f90a61fa0b506182c006a1663f41a1fa0d4da05007000e206607010fa11c2e84901c185d179d1962746589d1962746589d1962e8cce8cc140ba34ba2b44e8d21746905d1a41746905985985bc07130ba260e28f047a400000000000000000000000076f19cac7f1341db2829eb54515a1b2dacf2bf38c7db90aa7b5d8a1d4490ce6f52272040eeb7751bde27271a83e88058522fe7feee00000000000", | |
"blockhash": "b63a5c75082635ab3a444bfcac9b67417f342c56d38e920b53c91a6fd44f396b", | |
"confirmations": 1, | |
"time": 1600265578, | |
"blocktime": 1600265578 | |
} |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment