zcash-haskell/src/ZcashHaskell/Utils.hs
Rene Vergara 4e86a2f5a4
Zebra Raw Tx deserialization (#44)
Implements features to deserialize the hex representation of of a Zebra Transaction

Reviewed-on: #44
Co-authored-by: Rene Vergara <rene@vergara.network>
Co-committed-by: Rene Vergara <rene@vergara.network>
2024-03-26 14:56:10 +00:00

110 lines
3.4 KiB
Haskell

-- Copyright 2022-2024 Vergara Technologies LLC
--
-- This file is part of Zcash-Haskell.
--
-- |
-- Module : ZcashHaskell.Utils
-- Copyright : 2022-2024 Vergara Technologies LLC
-- License : MIT
--
-- Maintainer : pitmutt@vergara.tech
-- Stability : experimental
-- Portability : unknown
--
-- A set of functions to assist in the handling of elements of the Zcash protocol, allowing for decoding of memos, addresses and viewing keys.
--
{-# LANGUAGE OverloadedStrings #-}
module ZcashHaskell.Utils where
import C.Zcash
( rustWrapperBech32Decode
, rustWrapperBech32Encode
, rustWrapperF4Jumble
, rustWrapperF4UnJumble
, rustWrapperTxRead
)
import Control.Exception (SomeException(..), try)
import Control.Monad.IO.Class
import Data.Aeson
import qualified Data.ByteString as BS
import Data.HexString (HexString(..))
import qualified Data.Text as T
import qualified Data.Text.Encoding as E
import Foreign.Rust.Marshall.Variable
import Network.HTTP.Client (HttpException(..))
import Network.HTTP.Simple
import ZcashHaskell.Types
-- * Utility functions
-- | Decode the given bytestring using Bech32
decodeBech32 :: BS.ByteString -> RawData
decodeBech32 = withPureBorshVarBuffer . rustWrapperBech32Decode
-- | Encode the given Human Readable Part and bytestring as a Bech32m string
encodeBech32m :: BS.ByteString -> BS.ByteString -> T.Text
encodeBech32m h d = withPureBorshVarBuffer $ rustWrapperBech32Encode h d
-- | Apply the F4Jumble transformation to the given bytestring
f4Jumble :: BS.ByteString -> BS.ByteString
f4Jumble = withPureBorshVarBuffer . rustWrapperF4Jumble
-- | Apply the inverse F4Jumble transformation to the given bytestring
f4UnJumble :: BS.ByteString -> BS.ByteString
f4UnJumble = withPureBorshVarBuffer . rustWrapperF4UnJumble
-- * Node interaction
-- | Make a Zcash RPC call
makeZcashCall ::
(MonadIO m, FromJSON a)
=> BS.ByteString
-> BS.ByteString
-> T.Text
-> [Data.Aeson.Value]
-> m (Response a)
makeZcashCall username password m p = do
let payload = RpcCall "1.0" "test" m p
let myRequest =
setRequestBodyJSON payload $
setRequestPort 8232 $
setRequestBasicAuth username password $
setRequestMethod "POST" defaultRequest
httpJSON myRequest
-- | Make a Zebra RPC call
makeZebraCall ::
FromJSON a
=> T.Text -- ^ Hostname for `zebrad`
-> Int -- ^ Port for `zebrad`
-> T.Text -- ^ RPC method to call
-> [Data.Aeson.Value] -- ^ List of parameters
-> IO (Either String a)
makeZebraCall host port m params = do
let payload = RpcCall "2.0" "zh" m params
let myRequest =
setRequestBodyJSON payload $
setRequestPort port $
setRequestHost (E.encodeUtf8 host) $
setRequestMethod "POST" defaultRequest
r <-
try $ httpJSON myRequest :: FromJSON a1 =>
IO (Either SomeException (Response (RpcResponse a1)))
case r of
Left ex -> return $ Left $ show ex
Right res -> do
let zebraResp = getResponseBody res
case err zebraResp of
Just zErr -> return $ Left $ T.unpack $ emessage zErr
Nothing ->
case result zebraResp of
Nothing -> return $ Left "Empty response from Zebra"
Just zR -> return $ Right zR
readZebraTransaction :: HexString -> Maybe RawZebraTx
readZebraTransaction hex =
if BS.length (hexBytes $ zt_id rawTx) < 1
then Nothing
else Just rawTx
where
rawTx = (withPureBorshVarBuffer . rustWrapperTxRead) $ hexBytes hex