zcash-haskell/src/ZcashHaskell/Sapling.hs

208 lines
6.1 KiB
Haskell
Raw Normal View History

2024-01-18 18:55:23 +00:00
-- Copyright 2022-2024 Vergara Technologies LLC
--
-- This file is part of Zcash-Haskell.
--
2023-12-20 20:03:42 +00:00
-- |
-- Module : ZcashHaskell.Sapling
-- Copyright : 2022-2024 Vergara Technologies
2024-01-18 18:55:23 +00:00
-- License : MIT
2023-12-20 20:03:42 +00:00
--
2024-01-18 18:55:23 +00:00
-- Maintainer : pitmutt@vergara.tech
2023-12-20 20:03:42 +00:00
-- Stability : experimental
-- Portability : unknown
--
-- Functions to interact with the Sapling shielded pool of the Zcash blockchain.
--
2024-01-18 18:55:23 +00:00
{-# LANGUAGE OverloadedStrings #-}
2023-06-14 15:53:29 +00:00
module ZcashHaskell.Sapling where
2023-06-14 15:53:29 +00:00
import C.Zcash
( rustWrapperIsShielded
, rustWrapperReadSaplingCommitmentTree
, rustWrapperReadSaplingPosition
, rustWrapperReadSaplingWitness
2023-06-14 15:53:29 +00:00
, rustWrapperSaplingCheck
2024-03-15 15:11:27 +00:00
, rustWrapperSaplingChgPaymentAddress
, rustWrapperSaplingDecodeEsk
2023-08-22 20:05:40 +00:00
, rustWrapperSaplingNoteDecode
2024-03-10 12:47:26 +00:00
, rustWrapperSaplingPaymentAddress
2024-03-05 13:36:45 +00:00
, rustWrapperSaplingSpendingkey
2023-06-14 15:53:29 +00:00
, rustWrapperSaplingVkDecode
2023-09-27 15:37:53 +00:00
, rustWrapperTxParse
2023-06-14 15:53:29 +00:00
)
import Data.Aeson
import qualified Data.ByteString as BS
import Data.HexString (HexString(..), fromText, hexString, toBytes, toText)
2024-03-05 13:36:45 +00:00
import Data.Word
import Foreign.Rust.Marshall.Variable
2024-03-03 21:19:06 +00:00
( withPureBorshVarBuffer
, withPureBorshVarBuffer
)
import ZcashHaskell.Types
2024-03-10 12:47:26 +00:00
( AccountId
, CoinType
, DecodedNote(..)
, RawData(..)
, RawTxResponse(..)
, SaplingCommitmentTree(..)
2024-03-14 16:30:54 +00:00
, SaplingReceiver(..)
2024-03-10 12:47:26 +00:00
, SaplingSpendingKey(..)
, SaplingWitness(..)
, Scope(..)
2024-03-10 12:47:26 +00:00
, Seed(..)
, ShieldedOutput(..)
2024-03-14 16:30:54 +00:00
, ToBytes(..)
, ZcashNet(..)
, decodeHexText
, getValue
)
2024-03-10 12:47:26 +00:00
import ZcashHaskell.Utils (decodeBech32)
-- | Check if given bytesting is a valid encoded shielded address
isValidShieldedAddress :: BS.ByteString -> Bool
isValidShieldedAddress = rustWrapperIsShielded
2023-06-14 14:55:52 +00:00
2024-02-06 19:10:06 +00:00
getShieldedOutputs :: HexString -> [BS.ByteString]
getShieldedOutputs t = withPureBorshVarBuffer $ rustWrapperTxParse $ toBytes t
serializeShieldedOutput :: ShieldedOutput -> BS.ByteString
serializeShieldedOutput so =
hexBytes . fromText $
toText (s_cv so) <>
toText (s_cmu so) <>
toText (s_ephKey so) <>
toText (s_encCipherText so) <>
toText (s_outCipherText so) <> toText (s_proof so)
2023-06-14 14:55:52 +00:00
-- | Check if given bytestring is a valid Sapling viewing key
isValidSaplingViewingKey :: BS.ByteString -> Bool
isValidSaplingViewingKey k =
case hrp decodedKey of
"zxviews" -> rustWrapperSaplingVkDecode $ bytes decodedKey
_ -> False
where
decodedKey = decodeBech32 k
2023-06-14 15:53:29 +00:00
-- | Check if the given bytestring for the Sapling viewing key matches the second bytestring for the address
matchSaplingAddress :: BS.ByteString -> BS.ByteString -> Bool
matchSaplingAddress = rustWrapperSaplingCheck
2023-08-22 20:05:40 +00:00
2023-08-23 20:19:31 +00:00
-- | Attempt to decode the given raw tx with the given Sapling viewing key
decodeSaplingOutput :: BS.ByteString -> BS.ByteString -> Maybe DecodedNote
2023-08-22 20:05:40 +00:00
decodeSaplingOutput key out =
case a_value decodedAction of
0 -> Nothing
_ -> Just decodedAction
where
decodedAction =
withPureBorshVarBuffer $ rustWrapperSaplingNoteDecode key out
instance FromJSON RawTxResponse where
parseJSON =
withObject "RawTxResponse" $ \obj -> do
i <- obj .: "txid"
2023-09-28 18:56:31 +00:00
o <- obj .:? "orchard"
h <- obj .: "hex"
2023-10-02 20:25:44 +00:00
ht <- obj .: "height"
c <- obj .: "confirmations"
b <- obj .: "blocktime"
sSpend <- obj .: "vShieldedSpend"
2023-09-28 18:56:31 +00:00
case o of
Nothing ->
pure $ RawTxResponse i h sSpend (getShieldedOutputs h) [] ht c b
2023-09-28 18:56:31 +00:00
Just o' -> do
a <- o' .: "actions"
pure $ RawTxResponse i h sSpend (getShieldedOutputs h) a ht c b
2024-03-10 12:47:26 +00:00
-- | Attempt to decode the given raw tx with the given Sapling spending key
decodeSaplingOutputEsk ::
SaplingSpendingKey
-> ShieldedOutput
-> ZcashNet
-> Scope
-> Integer
-> Maybe DecodedNote
decodeSaplingOutputEsk key out znet scope pos =
case a_value decodedAction of
0 -> Nothing
_ -> Just decodedAction
where
decodedAction =
withPureBorshVarBuffer $
rustWrapperSaplingDecodeEsk
(getBytes key)
(serializeShieldedOutput out)
(scope == External)
2024-04-16 00:58:26 +00:00
(znet == MainNet)
(fromIntegral pos)
2024-03-10 12:47:26 +00:00
-- | Attempts to obtain a sapling SpendingKey using a HDSeed
genSaplingSpendingKey :: Seed -> CoinType -> Int -> Maybe SaplingSpendingKey
genSaplingSpendingKey seed c i = do
2024-03-11 20:23:29 +00:00
if BS.length res == 169
2024-03-14 16:30:54 +00:00
then Just $ SaplingSpendingKey res
2024-03-10 12:47:26 +00:00
else Nothing
where
2024-03-11 20:23:29 +00:00
res =
withPureBorshVarBuffer
(rustWrapperSaplingSpendingkey
2024-03-14 16:30:54 +00:00
(getBytes seed)
(fromIntegral $ getValue c)
(fromIntegral i))
2024-03-10 12:47:26 +00:00
-- | Attempts to generate a sapling Payment Address using an ExtendedSpendingKey and a Diversifier Index
genSaplingPaymentAddress :: Int -> SaplingSpendingKey -> Maybe SaplingReceiver
genSaplingPaymentAddress i extspk =
2024-03-10 12:47:26 +00:00
if BS.length res == 43
2024-03-14 16:30:54 +00:00
then Just $ SaplingReceiver res
2024-03-10 12:47:26 +00:00
else Nothing
where
res =
withPureBorshVarBuffer
2024-03-14 16:30:54 +00:00
(rustWrapperSaplingPaymentAddress
(getBytes extspk)
(fromIntegral (i * 111)))
-- | Generate an internal Sapling address
2024-03-14 17:35:13 +00:00
genSaplingInternalAddress :: SaplingSpendingKey -> Maybe SaplingReceiver
2024-03-15 15:11:27 +00:00
genSaplingInternalAddress sk =
if BS.length res == 43
2024-03-15 15:11:27 +00:00
then Just $ SaplingReceiver res
2024-03-12 19:57:43 +00:00
else Nothing
where
2024-03-15 15:11:27 +00:00
res =
withPureBorshVarBuffer (rustWrapperSaplingChgPaymentAddress $ getBytes sk)
-- | Update a Sapling commitment tree
updateSaplingCommitmentTree ::
SaplingCommitmentTree -- ^ the base tree
-> HexString -- ^ the new note commitment
-> Maybe SaplingCommitmentTree
updateSaplingCommitmentTree tree cmu =
if BS.length (hexBytes updatedTree) > 1
then Just $ SaplingCommitmentTree updatedTree
else Nothing
where
updatedTree =
withPureBorshVarBuffer $
rustWrapperReadSaplingCommitmentTree
(hexBytes $ sapTree tree)
(hexBytes cmu)
-- | Get the Sapling incremental witness from a commitment tree
getSaplingWitness :: SaplingCommitmentTree -> Maybe SaplingWitness
getSaplingWitness tree =
if BS.length (hexBytes wit) > 1
then Just $ SaplingWitness wit
else Nothing
where
wit =
withPureBorshVarBuffer $
rustWrapperReadSaplingWitness (hexBytes $ sapTree tree)
-- | Get the Sapling note position from a witness
getSaplingNotePosition :: SaplingWitness -> Integer
getSaplingNotePosition =
fromIntegral . rustWrapperReadSaplingPosition . hexBytes . sapWit