Addition of functinality for manipulating Unified Addresses and Viewing Keys #1
5 changed files with 70 additions and 2 deletions
|
@ -32,6 +32,7 @@ library:
|
|||
- foreign-rust
|
||||
- generics-sop
|
||||
- aeson
|
||||
- http-conduit
|
||||
pkg-config-dependencies:
|
||||
- rustzcash_wrapper-uninstalled
|
||||
|
||||
|
|
|
@ -35,8 +35,8 @@ decodeUfvk str =
|
|||
|
||||
-- | Attempts to decode the given @OrchardAction@ using the given @UnifiedFullViewingKey@.
|
||||
decryptOrchardAction ::
|
||||
OrchardAction -> UnifiedFullViewingKey -> Maybe DecodedNote
|
||||
decryptOrchardAction encAction key =
|
||||
UnifiedFullViewingKey -> OrchardAction -> Maybe DecodedNote
|
||||
decryptOrchardAction key encAction =
|
||||
case a_value decodedAction of
|
||||
0 -> Nothing
|
||||
_ -> Just decodedAction
|
||||
|
|
|
@ -1,4 +1,5 @@
|
|||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DerivingVia #-}
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
|
@ -39,6 +40,48 @@ data RawData = RawData
|
|||
deriving (BorshSize, ToBorsh, FromBorsh) via AsStruct RawData
|
||||
|
||||
-- * `zcashd` RPC
|
||||
-- | A type to model Zcash RPC calls
|
||||
data RpcCall = RpcCall
|
||||
{ jsonrpc :: T.Text
|
||||
, callId :: T.Text
|
||||
, method :: T.Text
|
||||
, parameters :: [Data.Aeson.Value]
|
||||
} deriving stock (Prelude.Show, GHC.Generic)
|
||||
|
||||
instance ToJSON RpcCall where
|
||||
toJSON (RpcCall j c m p) =
|
||||
object ["jsonrpc" .= j, "id" .= c, "method" .= m, "params" .= p]
|
||||
|
||||
-- | A type to model the response of the Zcash RPC
|
||||
data RpcResponse r = MakeRpcResponse
|
||||
{ err :: Maybe RpcError
|
||||
, respId :: T.Text
|
||||
, result :: Maybe r
|
||||
} deriving stock (Prelude.Show, GHC.Generic)
|
||||
deriving anyclass (ToJSON)
|
||||
|
||||
instance (FromJSON r) => FromJSON (RpcResponse r) where
|
||||
parseJSON =
|
||||
withObject "RpcResponse" $ \obj -> do
|
||||
e <- obj .: "error"
|
||||
i <- obj .: "id"
|
||||
r <- obj .: "result"
|
||||
pure $ MakeRpcResponse e i r
|
||||
|
||||
-- | A type to model the errors from the Zcash RPC
|
||||
data RpcError = RpcError
|
||||
{ ecode :: Double
|
||||
, emessage :: T.Text
|
||||
} deriving stock (Prelude.Show, GHC.Generic)
|
||||
deriving anyclass (ToJSON)
|
||||
|
||||
instance FromJSON RpcError where
|
||||
parseJSON =
|
||||
withObject "RpcError" $ \obj -> do
|
||||
c <- obj .: "code"
|
||||
m <- obj .: "message"
|
||||
pure $ RpcError c m
|
||||
|
||||
-- | Type to represent response from the `zcashd` RPC `getblock` method
|
||||
data BlockResponse = BlockResponse
|
||||
{ bl_confirmations :: Integer -- ^ Block confirmations
|
||||
|
|
|
@ -9,6 +9,8 @@
|
|||
--
|
||||
-- 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
|
||||
|
@ -16,8 +18,12 @@ import C.Zcash
|
|||
, rustWrapperF4Jumble
|
||||
, rustWrapperF4UnJumble
|
||||
)
|
||||
import Control.Monad.IO.Class
|
||||
import Data.Aeson
|
||||
import qualified Data.ByteString as BS
|
||||
import qualified Data.Text as T
|
||||
import Foreign.Rust.Marshall.Variable
|
||||
import Network.HTTP.Simple
|
||||
import ZcashHaskell.Types
|
||||
|
||||
-- | Decode the given bytestring using Bech32
|
||||
|
@ -31,3 +37,20 @@ f4Jumble = withPureBorshVarBuffer . rustWrapperF4Jumble
|
|||
-- | Apply the inverse F4Jumble transformation to the given bytestring
|
||||
f4UnJumble :: BS.ByteString -> BS.ByteString
|
||||
f4UnJumble = withPureBorshVarBuffer . rustWrapperF4UnJumble
|
||||
|
||||
-- | 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
|
||||
|
|
|
@ -44,6 +44,7 @@ library
|
|||
, bytestring
|
||||
, foreign-rust
|
||||
, generics-sop
|
||||
, http-conduit
|
||||
, text
|
||||
default-language: Haskell2010
|
||||
|
||||
|
|
Loading…
Reference in a new issue