zcash-haskell/src/ZcashHaskell/Sapling.hs
Rene V. Vergara a6c358cd5d Commit for debuggin process
Erros with Parameters for rustWrapperSaplingSpendingkey function
   x in Sapling.hs module
2024-03-04 18:46:39 -05:00

102 lines
3 KiB
Haskell

-- Copyright 2022-2024 Vergara Technologies LLC
--
-- This file is part of Zcash-Haskell.
--
-- |
-- Module : ZcashHaskell.Sapling
-- Copyright : 2022-2024 Vergara Technologies
-- License : MIT
--
-- Maintainer : pitmutt@vergara.tech
-- Stability : experimental
-- Portability : unknown
--
-- Functions to interact with the Sapling shielded pool of the Zcash blockchain.
--
{-# LANGUAGE OverloadedStrings #-}
module ZcashHaskell.Sapling where
import C.Zcash
( rustWrapperIsShielded
, rustWrapperSaplingCheck
, rustWrapperSaplingNoteDecode
, rustWrapperSaplingVkDecode
, rustWrapperTxParse
, rustWrapperSaplingSpendingkey
)
import Data.Aeson
import qualified Data.ByteString as BS
import Data.ByteString.Lazy as BL
import Data.HexString (HexString(..), toBytes)
import Foreign.Rust.Marshall.Variable
( withPureBorshVarBuffer
, withPureBorshVarBuffer
)
import ZcashHaskell.Types
( DecodedNote(..)
, RawData(..)
, RawTxResponse(..)
, ShieldedOutput(..)
, decodeHexText
, SaplingSKeyParams(..)
)
import ZcashHaskell.Utils
import Data.Word
-- | Check if given bytesting is a valid encoded shielded address
isValidShieldedAddress :: BS.ByteString -> Bool
isValidShieldedAddress = rustWrapperIsShielded
getShieldedOutputs :: HexString -> [BS.ByteString]
getShieldedOutputs t = withPureBorshVarBuffer $ rustWrapperTxParse $ toBytes t
-- | 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
-- | 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
-- | Attempt to decode the given raw tx with the given Sapling viewing key
decodeSaplingOutput :: BS.ByteString -> BS.ByteString -> Maybe DecodedNote
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"
o <- obj .:? "orchard"
h <- obj .: "hex"
ht <- obj .: "height"
c <- obj .: "confirmations"
b <- obj .: "blocktime"
case o of
Nothing -> pure $ RawTxResponse i h (getShieldedOutputs h) [] ht c b
Just o' -> do
a <- o' .: "actions"
pure $ RawTxResponse i h (getShieldedOutputs h) a ht c b
-- | Attempts to obtain a sapling SpendinKey using a HDSeed, a Coin Type and an Account ID
genSaplingSpendingKey ::
BS.ByteString -> Word32 -> Word32 -> Maybe BS.ByteString
genSaplingSpendingKey seed coin_type account_id = do
if BS.length res > 0
then Just res
else Nothing
where
res = (withPureBorshVarBuffer . rustWrapperSaplingSpendingkey) seed coin_type account_id