Compare commits

..

34 commits

Author SHA1 Message Date
ac86d1ee59
Correct block recording 2023-10-13 15:35:48 -05:00
5788a26880
Enable new native transaction scanning 2023-10-13 15:20:01 -05:00
ec72015524
Correct ZEC calculation 2023-10-13 15:06:08 -05:00
19b352c381
Continue debugging 2023-10-13 14:59:14 -05:00
4558dfb8da
Add more debugging 2023-10-13 14:53:33 -05:00
a3eb5d29ee
Add debugging 2023-10-13 14:45:19 -05:00
c2be91dfcc
Add ZGo order parsing and payment tracking 2023-10-13 14:20:10 -05:00
d7ced42d86
Implement saving of scanned txs 2023-10-12 14:53:53 -05:00
ccd9e8280e
Tests for adding UVK 2023-10-11 14:25:01 -05:00
b14a5cfb83
Improve messaging for PIN send 2023-10-11 07:51:16 -05:00
f5dbde0ed6
Improve PIN send 2023-10-10 11:12:58 -05:00
a2654a6f01
Correct the Sapling vk call 2023-10-09 16:28:17 -05:00
cd5af6b907
Add UFVK support for ZGo shops 2023-10-04 14:10:13 -05:00
68285fbc39
Update to next zcash_haskell version 2023-10-04 14:09:49 -05:00
3f3cb9ef7c
Remove call to zcashd to validate VK 2023-10-04 11:19:11 -05:00
493d17abfd
Improve decoding of Txs 2023-10-03 11:07:01 -05:00
bf740857b3
Modify tx scanner to generate ZcashTx 2023-10-03 10:47:54 -05:00
cd259f244a
Update version of zcash-haskell 2023-10-02 15:27:59 -05:00
d235c56cfb
Correct tx filtering 2023-09-29 14:33:17 -05:00
74ba9d23f0
Update to next version of zcash-haskell 2023-09-29 14:15:17 -05:00
0224db1993
Implement Sapling decoding 2023-09-29 13:49:34 -05:00
3ed60ae2dd
Update version of zcash-haskell 2023-09-29 13:30:14 -05:00
af22c0d71f
Further troubleshooting 2023-09-28 15:55:39 -05:00
d90f7cdfea
Troubleshoot the Sapling decode 2023-09-28 15:49:05 -05:00
78c8b9ef5c
Update Sapling decoding 2023-09-28 15:35:17 -05:00
f0d1e933c6
Add debugging for shielded decode 2023-09-28 15:26:56 -05:00
5f32fd1142
Correct the Sapling decoding 2023-09-28 15:17:41 -05:00
ae5606f4be
Update dep on zcash-haskell 2023-09-28 14:52:10 -05:00
82f6535765
Update zcash-haskell dependency 2023-09-28 14:26:49 -05:00
0f4a5f547f
Update deps to latest version of zcash-haskell 2023-09-28 13:59:07 -05:00
b36f1240b0
Correct call to getrawtransaction 2023-09-28 13:37:23 -05:00
181f4bb749
Update base block for first run 2023-09-28 13:29:16 -05:00
fb600aa5fc
Correct data type for getblock 2023-09-28 13:26:24 -05:00
85bf0fef59
Fix call to getblock 2023-09-28 13:11:48 -05:00
7 changed files with 418 additions and 93 deletions

View file

@ -23,7 +23,8 @@ main = do
putStrLn "Connected to MongoDB!" putStrLn "Connected to MongoDB!"
checkZcashPrices pipe (c_dbName loadedConfig) checkZcashPrices pipe (c_dbName loadedConfig)
scanZcash' loadedConfig pipe scanZcash' loadedConfig pipe
scanPayments loadedConfig pipe {-scanPayments loadedConfig pipe-}
scanTxNative loadedConfig pipe
checkPayments pipe (c_dbName loadedConfig) checkPayments pipe (c_dbName loadedConfig)
expireOwners pipe (c_dbName loadedConfig) expireOwners pipe (c_dbName loadedConfig)
updateLogins pipe loadedConfig updateLogins pipe loadedConfig

View file

@ -420,8 +420,7 @@ findExpiringOwners now =
findWithKeys :: Action IO [Document] findWithKeys :: Action IO [Document]
findWithKeys = findWithKeys =
rest =<< rest =<< find (select ["paid" =: True, "payconf" =: True] "owners")
find (select ["paid" =: True, "invoices" =: True, "payconf" =: True] "owners")
removePro :: T.Text -> Action IO () removePro :: T.Text -> Action IO ()
removePro o = removePro o =

View file

@ -52,6 +52,7 @@ import Numeric
import Order import Order
import Owner import Owner
import Payment import Payment
import System.IO
import System.IO.Unsafe import System.IO.Unsafe
import System.Random import System.Random
import Test.QuickCheck import Test.QuickCheck
@ -69,6 +70,7 @@ import ZcashHaskell.Orchard
import ZcashHaskell.Sapling import ZcashHaskell.Sapling
import ZcashHaskell.Types import ZcashHaskell.Types
( BlockResponse(..) ( BlockResponse(..)
, DecodedNote(..)
, RawData(..) , RawData(..)
, RawTxResponse(..) , RawTxResponse(..)
, RpcCall(..) , RpcCall(..)
@ -371,12 +373,7 @@ listCountries :: Action IO [Document]
listCountries = rest =<< find (select [] "countries") listCountries = rest =<< find (select [] "countries")
sendPin :: sendPin ::
BS.ByteString BS.ByteString -> BS.ByteString -> T.Text -> T.Text -> T.Text -> IO String
-> BS.ByteString
-> T.Text
-> T.Text
-> T.Text
-> Action IO String
sendPin nodeUser nodePwd nodeAddress addr pin = do sendPin nodeUser nodePwd nodeAddress addr pin = do
let pd = let pd =
[ Data.Aeson.String nodeAddress [ Data.Aeson.String nodeAddress
@ -388,17 +385,73 @@ sendPin nodeUser nodePwd nodeAddress addr pin = do
, "memo" .= encodeHexText ("ZGo PIN: " <> pin) , "memo" .= encodeHexText ("ZGo PIN: " <> pin)
] ]
]) ])
, Data.Aeson.Number $ SC.scientific 1 1
, Data.Aeson.Null
, Data.Aeson.String "AllowRevealedAmounts"
] ]
r <- liftIO $ try $ makeZcashCall nodeUser nodePwd "z_sendmany" pd -- IO (Either HttpException (Response Object)) r <- liftIO $ try $ makeZcashCall nodeUser nodePwd "z_sendmany" pd
case r of case r of
Right res -> do Right res -> do
let sCode = getResponseStatus (res :: Response Object) let sCode = getResponseStatus (res :: Response (RpcResponse T.Text))
let rBody = getResponseBody res
if sCode == ok200 if sCode == ok200
then return "Pin sent!" then do
case result rBody of
Nothing -> return "Couldn't parse node response"
Just x -> do
putStr " Sending."
checkOpResult nodeUser nodePwd x
return "Pin sent!"
else return "Pin sending failed :(" else return "Pin sending failed :("
Left ex -> Left ex ->
return $ "Failed to send tx to node :(" ++ show (ex :: HttpException) return $ "Failed to send tx to node :(" ++ show (ex :: HttpException)
-- | Type for Operation Result
data OpResult = OpResult
{ opsuccess :: T.Text
, opmessage :: Maybe T.Text
, optxid :: Maybe T.Text
} deriving (Show, Eq)
instance FromJSON OpResult where
parseJSON =
withObject "OpResult" $ \obj -> do
s <- obj .: "status"
r <- obj .:? "result"
e <- obj .:? "error"
t <-
case r of
Nothing -> return Nothing
Just r' -> r' .: "txid"
m <-
case e of
Nothing -> return Nothing
Just m' -> m' .: "message"
pure $ OpResult s m t
checkOpResult :: BS.ByteString -> BS.ByteString -> T.Text -> IO ()
checkOpResult user pwd opid = do
response <-
makeZcashCall
user
pwd
"z_getoperationstatus"
[Data.Aeson.Array (V.fromList [Data.Aeson.String opid])]
let rpcResp = getResponseBody response :: (RpcResponse [OpResult])
case result rpcResp of
Nothing -> putStrLn "Couldn't read response from node"
Just opCode -> mapM_ showResult opCode
where
showResult t =
case opsuccess t of
"success" ->
putStrLn $ " Success! Tx ID: " ++ maybe "" T.unpack (optxid t)
"executing" -> do
putStr "."
hFlush stdout
threadDelay 1000000 >> checkOpResult user pwd opid
_ -> putStrLn $ " Failed :( " ++ maybe "" T.unpack (opmessage t)
-- | Function to create user from ZGoTx -- | Function to create user from ZGoTx
addUser :: addUser ::
BS.ByteString BS.ByteString
@ -413,7 +466,7 @@ addUser nodeUser nodePwd p db node (Just tx) = do
isNew <- liftIO $ isUserNew p db tx isNew <- liftIO $ isUserNew p db tx
when isNew $ do when isNew $ do
newPin <- liftIO generatePin newPin <- liftIO generatePin
_ <- sendPin nodeUser nodePwd node (address tx) (T.pack newPin) _ <- liftIO $ sendPin nodeUser nodePwd node (address tx) (T.pack newPin)
let pinHash = let pinHash =
BLK.hash BLK.hash
[ BA.pack . BS.unpack . C.pack . T.unpack $ [ BA.pack . BS.unpack . C.pack . T.unpack $
@ -1175,8 +1228,9 @@ routes pipe config = do
case cast' . Doc =<< u of case cast' . Doc =<< u of
Nothing -> status unauthorized401 Nothing -> status unauthorized401
Just u' -> do Just u' -> do
if isValidSaplingViewingKey qBytes if isValidSaplingViewingKey $ C.pack q
then if matchSaplingAddress then do
if matchSaplingAddress
qBytes qBytes
(bytes . decodeBech32 . C.pack . T.unpack $ uaddress u') (bytes . decodeBech32 . C.pack . T.unpack $ uaddress u')
then do then do
@ -1185,27 +1239,45 @@ routes pipe config = do
Nothing -> status badRequest400 Nothing -> status badRequest400
Just o' -> do Just o' -> do
unless (oviewkey o' /= "") $ do unless (oviewkey o' /= "") $ do
vkInfo <-
liftAndCatchIO $
makeZcashCall
nodeUser
nodePwd
"z_importviewingkey"
[ Data.Aeson.String (T.strip . T.pack $ q)
, "no"
] -- TODO: Remove this call to the node
let content =
getResponseBody vkInfo :: RpcResponse Object
if isNothing (err content)
then do
_ <-
liftAndCatchIO $ run (upsertViewingKey o' q) liftAndCatchIO $ run (upsertViewingKey o' q)
status created201 status created201
else do
text $ L.pack . show $ err content
status badRequest400
else status forbidden403 else status forbidden403
else status badRequest400 -- TODO: add Unified VK support else case decodeUfvk (C.pack q) of
Nothing -> status badRequest400
Just fvk -> do
if isValidUnifiedAddress $
C.pack . T.unpack $ uaddress u'
then do
if matchOrchardAddress
(C.pack q)
(C.pack . T.unpack $ uaddress u')
then do
owner <-
liftAndCatchIO $ run (findOwner $ uaddress u')
case cast' . Doc =<< owner of
Nothing -> status badRequest400
Just o' -> do
unless (oviewkey o' /= "") $ do
liftAndCatchIO $
run (upsertViewingKey o' q)
status created201
else status forbidden403
else do
if matchSaplingAddress
(s_key fvk)
(bytes . decodeBech32 . C.pack . T.unpack $
uaddress u')
then do
owner <-
liftAndCatchIO $ run (findOwner $ uaddress u')
case cast' . Doc =<< owner of
Nothing -> status badRequest400
Just o' -> do
unless (oviewkey o' /= "") $ do
liftAndCatchIO $
run (upsertViewingKey o' q)
status created201
else status forbidden403
--Get items associated with the given address --Get items associated with the given address
get "/api/items" $ do get "/api/items" $ do
session <- param "session" session <- param "session"
@ -1803,9 +1875,14 @@ generateToken = do
runCryptoRNGT rngState $ randomString 24 "abcdef0123456789" runCryptoRNGT rngState $ randomString 24 "abcdef0123456789"
getBlockInfo :: getBlockInfo ::
BS.ByteString -> BS.ByteString -> SC.Scientific -> IO (Maybe BlockResponse) BS.ByteString -> BS.ByteString -> T.Text -> IO (Maybe BlockResponse)
getBlockInfo nodeUser nodePwd bh = do getBlockInfo nodeUser nodePwd bh = do
blockInfo <- makeZcashCall nodeUser nodePwd "getblock" [Number bh] blockInfo <-
makeZcashCall
nodeUser
nodePwd
"getblock"
[Data.Aeson.String bh, Number $ SC.scientific 1 0]
let content = getResponseBody blockInfo :: RpcResponse BlockResponse let content = getResponseBody blockInfo :: RpcResponse BlockResponse
if isNothing (err content) if isNothing (err content)
then return $ result content then return $ result content
@ -1813,38 +1890,61 @@ getBlockInfo nodeUser nodePwd bh = do
print $ err content print $ err content
return Nothing return Nothing
scanTxNative :: Pipe -> T.Text -> BS.ByteString -> BS.ByteString -> IO () scanTxNative :: Config -> Pipe -> IO ()
scanTxNative pipe db nodeUser nodePwd = do scanTxNative config pipe = do
let db = c_dbName config
keyOwnerList <- access pipe master db findWithKeys keyOwnerList <- access pipe master db findWithKeys
unless (null keyOwnerList) $ do unless (null keyOwnerList) $ do
let ownerList = cast' . Doc <$> keyOwnerList let nodeUser = c_nodeUser config
let keyList = map (maybe "" oviewkey) ownerList let nodePwd = c_nodePwd config
let ownerList = mapMaybe (cast' . Doc) keyOwnerList
lastBlockData <- access pipe master db findBlock lastBlockData <- access pipe master db findBlock
latestBlock <- getBlockInfo nodeUser nodePwd (SC.scientific (-1) 0) latestBlock <- getBlockInfo nodeUser nodePwd "-1"
case latestBlock of case latestBlock of
Nothing -> fail "No block data from node" Nothing -> fail "No block data from node"
Just lB -> do Just lB -> do
case cast' . Doc =<< lastBlockData of case cast' . Doc =<< lastBlockData of
Nothing -> do Nothing -> do
print "Getting blocks"
blockList <- blockList <-
mapM mapM
(getBlockInfo nodeUser nodePwd . fromInteger) (getBlockInfo nodeUser nodePwd . T.pack . show)
[2220000 .. (bl_height lB)] [(bl_height lB - 50) .. (bl_height lB)]
print "filtering blocks..."
let filteredBlockList = filter filterBlock blockList let filteredBlockList = filter filterBlock blockList
print "extracting txs from blocks..."
let txIdList = concatMap extractTxs filteredBlockList let txIdList = concatMap extractTxs filteredBlockList
print "getting tx data from node..."
txList <- mapM (getTxData nodeUser nodePwd) txIdList txList <- mapM (getTxData nodeUser nodePwd) txIdList
print "filtering txs..."
let filteredTxList = map fromJust $ filter filterTx txList let filteredTxList = map fromJust $ filter filterTx txList
mapM_ (checkTx filteredTxList) keyList print "checking txs against keys..."
mapM_ (checkTx filteredTxList) ownerList
access pipe master (c_dbName config) $
upsertBlock (last $ catMaybes filteredBlockList)
Just lastBlock -> do Just lastBlock -> do
let blockList' = [(bl_height lastBlock + 1) .. (bl_height lB)] blockList' <-
print blockList' mapM
print keyList (getBlockInfo nodeUser nodePwd . T.pack . show)
[(bl_height lastBlock + 1) .. (bl_height lB)]
print "filtering blocks..."
let filteredBlockList = filter filterBlock blockList'
print "extracting txs from blocks..."
let txIdList = concatMap extractTxs filteredBlockList
print "getting tx data from node..."
txList <- mapM (getTxData nodeUser nodePwd) txIdList
print "filtering txs..."
let filteredTxList = map fromJust $ filter filterTx txList
print "checking txs against keys..."
mapM_ (checkTx filteredTxList) ownerList
access pipe master (c_dbName config) $
upsertBlock (last $ catMaybes filteredBlockList)
where where
filterBlock :: Maybe BlockResponse -> Bool filterBlock :: Maybe BlockResponse -> Bool
filterBlock b = maybe 0 bl_confirmations b >= 5 filterBlock b = maybe 0 bl_confirmations b >= 5
filterTx :: Maybe RawTxResponse -> Bool filterTx :: Maybe RawTxResponse -> Bool
filterTx t = filterTx t =
not (null (maybe [] rt_shieldedOutputs t)) && not (null (maybe [] rt_shieldedOutputs t)) ||
not (null (maybe [] rt_orchardActions t)) not (null (maybe [] rt_orchardActions t))
extractTxs :: Maybe BlockResponse -> [T.Text] extractTxs :: Maybe BlockResponse -> [T.Text]
extractTxs = maybe [] bl_txs extractTxs = maybe [] bl_txs
@ -1856,39 +1956,145 @@ scanTxNative pipe db nodeUser nodePwd = do
nodeUser nodeUser
nodePwd nodePwd
"getrawtransaction" "getrawtransaction"
[Data.Aeson.String txid] [Data.Aeson.String txid, Number $ SC.scientific 1 0]
let content = getResponseBody txInfo :: RpcResponse RawTxResponse let content = getResponseBody txInfo :: RpcResponse RawTxResponse
if isNothing (err content) if isNothing (err content)
then return $ result content then return $ result content
else do else do
print $ err content print $ err content
return Nothing return Nothing
checkTx :: [RawTxResponse] -> T.Text -> IO () checkTx :: [RawTxResponse] -> Owner -> IO ()
checkTx txList k = do checkTx txList' k = do
if isValidSaplingViewingKey (E.encodeUtf8 k) let sOutList = concatMap rt_shieldedOutputs txList'
if isValidSaplingViewingKey (E.encodeUtf8 $ oviewkey k)
then do then do
let decodedTxList = print "decoding Sapling tx"
map let decodedSapList' = concatMap (decodeSaplingTx $ oviewkey k) txList'
(decodeSaplingOutput (E.encodeUtf8 k)) let zList = catMaybes decodedSapList'
(concatMap mapM_ (recordPayment pipe (c_dbName config) (oaddress k)) zList
rt_shieldedOutputs
(filter (\x -> rt_shieldedOutputs x /= []) txList))
print decodedTxList
else do else do
let vk = decodeUfvk $ E.encodeUtf8 k let vk = decodeUfvk $ E.encodeUtf8 $ oviewkey k
case vk of case vk of
Nothing -> print "Not a valid key" Nothing -> print "Not a valid key"
Just v -> do Just v -> do
let decodedSapList = let decodedSapList =
concatMap (decodeUnifiedSaplingTx (s_key v)) txList'
let zList' = catMaybes decodedSapList
mapM_ (recordPayment pipe (c_dbName config) (oaddress k)) zList'
let decodedOrchList = concatMap (decodeUnifiedOrchardTx v) txList'
let oList = catMaybes decodedOrchList
mapM_ (recordPayment pipe (c_dbName config) (oaddress k)) oList
decodeSaplingTx :: T.Text -> RawTxResponse -> [Maybe ZcashTx]
decodeSaplingTx k t =
map map
(decodeSaplingOutput (s_key v)) (buildZcashTx t .
(concatMap rt_shieldedOutputs txList) decodeSaplingOutput (bytes (decodeBech32 $ E.encodeUtf8 k)))
print decodedSapList (rt_shieldedOutputs t)
let decodedOrchList = decodeUnifiedSaplingTx :: BS.ByteString -> RawTxResponse -> [Maybe ZcashTx]
map decodeUnifiedSaplingTx k t =
(decryptOrchardAction v) map (buildZcashTx t . decodeSaplingOutput k) (rt_shieldedOutputs t)
(concatMap rt_orchardActions txList) decodeUnifiedOrchardTx ::
print decodedOrchList UnifiedFullViewingKey -> RawTxResponse -> [Maybe ZcashTx]
decodeUnifiedOrchardTx k t =
map (buildZcashTx t . decryptOrchardAction k) (rt_orchardActions t)
buildZcashTx :: RawTxResponse -> Maybe DecodedNote -> Maybe ZcashTx
buildZcashTx t n =
case n of
Nothing -> Nothing
Just n ->
Just $
ZcashTx
(rt_id t)
(fromIntegral (a_value n) / 100000000)
(toInteger $ a_value n)
(rt_blockheight t)
(rt_blocktime t)
False
(rt_confirmations t)
(E.decodeUtf8Lenient $ a_memo n)
recordPayment :: Pipe -> T.Text -> T.Text -> ZcashTx -> IO ()
recordPayment p dbName z x = do
let zM = runParser pZGoMemo (T.unpack . ztxid $ x) (zmemo x)
case zM of
Right m -> do
case m_orderId m of
Nothing -> print "Not an order Tx"
Just orderId -> do
print orderId
o <- access p master dbName $ findOrderById (T.unpack orderId)
let xOrder = o >>= (cast' . Doc)
case xOrder of
Nothing -> error "Failed to retrieve order from database"
Just xO -> do
when
(not (qpaid xO) &&
qtotalZec xO == zamount x && z == qaddress xO) $ do
let sReg = mkRegex "(.*)-([a-fA-f0-9]{24})"
let sResult = matchAllText sReg (T.unpack $ qsession xO)
if not (null sResult)
then case fst $ head sResult ! 1 of
"Xero" -> do
xeroConfig <- access p master dbName findXero
let xC = xeroConfig >>= (cast' . Doc)
case xC of
Nothing -> error "Failed to read Xero config"
Just xConf -> do
requestXeroToken
p
dbName
xConf
""
(qaddress xO)
payXeroInvoice
p
dbName
(qexternalInvoice xO)
(qaddress xO)
(qtotal xO)
(qtotalZec xO)
liftIO $
access p master dbName $
markOrderPaid (T.unpack orderId, zamount x)
"WC" -> do
let wOwner = fst $ head sResult ! 2
wooT <-
access p master dbName $
findWooToken $ Just (read wOwner)
let wT = wooT >>= (cast' . Doc)
case wT of
Nothing ->
error "Failed to read WooCommerce token"
Just wt -> do
let iReg = mkRegex "(.*)-(.*)-.*"
let iResult =
matchAllText
iReg
(T.unpack $ qexternalInvoice xO)
if not (null iResult)
then do
let wUrl =
E.decodeUtf8With lenientDecode .
B64.decodeLenient . C.pack $
fst $ head iResult ! 1
let iNum = fst $ head iResult ! 2
payWooOrder
(T.unpack wUrl)
(C.pack iNum)
(C.pack $ maybe "" show (q_id xO))
(C.pack . T.unpack $ w_token wt)
(C.pack . show $ qprice xO)
(C.pack . show $ qtotalZec xO)
liftIO $
access p master dbName $
markOrderPaid
(T.unpack orderId, zamount x)
else error
"Couldn't parse externalInvoice for WooCommerce"
_ -> putStrLn "Not an integration order"
else liftIO $
access p master dbName $
markOrderPaid (T.unpack orderId, zamount x)
Left e -> print "Unable to parse order memo"
debug = flip trace debug = flip trace

View file

@ -105,6 +105,7 @@ data ZGoMemo = ZGoMemo
{ m_session :: Maybe U.UUID { m_session :: Maybe U.UUID
, m_address :: Maybe T.Text , m_address :: Maybe T.Text
, m_payment :: Bool , m_payment :: Bool
, m_orderId :: Maybe T.Text
} deriving (Eq, Show) } deriving (Eq, Show)
data MemoToken data MemoToken
@ -112,6 +113,7 @@ data MemoToken
| PayMsg !U.UUID | PayMsg !U.UUID
| Address !T.Text | Address !T.Text
| Msg !T.Text | Msg !T.Text
| OrderId !T.Text
deriving (Show, Eq) deriving (Show, Eq)
type Parser = Parsec Void T.Text type Parser = Parsec Void T.Text
@ -146,6 +148,12 @@ pUnifiedAddress = do
then pure $ Address $ T.pack ("u1" <> a) then pure $ Address $ T.pack ("u1" <> a)
else fail "Failed to parse Unified Address" else fail "Failed to parse Unified Address"
pOrderId :: Parser MemoToken
pOrderId = do
string "ZGo Order::"
a <- some hexDigitChar
pure $ OrderId . T.pack $ a
pMsg :: Parser MemoToken pMsg :: Parser MemoToken
pMsg = do pMsg = do
msg <- msg <-
@ -157,7 +165,7 @@ pMsg = do
pMemo :: Parser MemoToken pMemo :: Parser MemoToken
pMemo = do pMemo = do
optional $ some spaceChar optional $ some spaceChar
t <- pSession <|> pSaplingAddress <|> pMsg t <- pSession <|> pSaplingAddress <|> pUnifiedAddress <|> pOrderId <|> pMsg
optional $ some spaceChar optional $ some spaceChar
return t return t
@ -182,8 +190,15 @@ isMemoToken kind t =
pZGoMemo :: Parser ZGoMemo pZGoMemo :: Parser ZGoMemo
pZGoMemo = do pZGoMemo = do
tks <- some pMemo tks <- some pMemo
pure $ ZGoMemo (isSession tks) (isAddress tks) (isPayment tks) pure $ ZGoMemo (isSession tks) (isAddress tks) (isPayment tks) (isOrder tks)
where where
isOrder [] = Nothing
isOrder tks =
if not (null tks)
then case head tks of
OrderId x -> Just x
_ -> isOrder $ tail tks
else Nothing
isPayment [] = False isPayment [] = False
isPayment tks = isPayment tks =
not (null tks) && not (null tks) &&

View file

@ -45,7 +45,7 @@ extra-deps:
- git: https://github.com/reach-sh/haskell-hexstring.git - git: https://github.com/reach-sh/haskell-hexstring.git
commit: 085c16fb21b9f856a435a3faab980e7e0b319341 commit: 085c16fb21b9f856a435a3faab980e7e0b319341
- git: https://git.vergara.tech/Vergara_Tech/zcash-haskell.git - git: https://git.vergara.tech/Vergara_Tech/zcash-haskell.git
commit: d78c269d96fe7d8a626cf701b8051c40f251e232 commit: 1d558fc646a7758d60a721124812070de222c2e1
- git: https://git.vergara.tech/Vergara_Tech/haskell-foreign-rust.git - git: https://git.vergara.tech/Vergara_Tech/haskell-foreign-rust.git
commit: 787c2e813eb3a5d16c375d4b37dfefbd2adcdf05 commit: 787c2e813eb3a5d16c375d4b37dfefbd2adcdf05
- git: https://github.com/well-typed/borsh.git - git: https://github.com/well-typed/borsh.git

View file

@ -16,15 +16,15 @@ packages:
commit: 085c16fb21b9f856a435a3faab980e7e0b319341 commit: 085c16fb21b9f856a435a3faab980e7e0b319341
git: https://github.com/reach-sh/haskell-hexstring.git git: https://github.com/reach-sh/haskell-hexstring.git
- completed: - completed:
commit: d78c269d96fe7d8a626cf701b8051c40f251e232 commit: 1d558fc646a7758d60a721124812070de222c2e1
git: https://git.vergara.tech/Vergara_Tech/zcash-haskell.git git: https://git.vergara.tech/Vergara_Tech/zcash-haskell.git
name: zcash-haskell name: zcash-haskell
pantry-tree: pantry-tree:
sha256: 69201a27ac966be478ef0b8e3fa8e8bf5cbcc67a58cd254326545eb4f3e93569 sha256: eab3c6817bb3cb5738725824d16eb023cb2967ef3bbaa8f8252524602f606dbb
size: 1229 size: 1229
version: 0.2.0 version: 0.2.0
original: original:
commit: d78c269d96fe7d8a626cf701b8051c40f251e232 commit: 1d558fc646a7758d60a721124812070de222c2e1
git: https://git.vergara.tech/Vergara_Tech/zcash-haskell.git git: https://git.vergara.tech/Vergara_Tech/zcash-haskell.git
- completed: - completed:
commit: 787c2e813eb3a5d16c375d4b37dfefbd2adcdf05 commit: 787c2e813eb3a5d16c375d4b37dfefbd2adcdf05

View file

@ -101,8 +101,9 @@ main = do
case m of case m of
Left e -> putStrLn $ errorBundlePretty e Left e -> putStrLn $ errorBundlePretty e
Right m' -> Right m' ->
m_session m' `shouldBe` m_address m' `shouldBe`
U.fromString "5d3d4494-51c0-432d-8495-050419957aea" Just
"u17n7hpwaujyq7ux8f9jpyymtnk5urw7pyrf60smp5mawy7jgz325hfvz3jn3zsfya8yxryf9q7ldk8nu8df0emra5wne28zq9d9nm2pu4x6qwjha565av9aze0xgujgslz74ufkj0c0cylqwjyrh9msjfh7jzal6d3qzrnhkkqy3pqm8j63y07jxj7txqeac982778rmt64f32aum94x"
it "parse YWallet memo - Orchard" $ do it "parse YWallet memo - Orchard" $ do
let m = let m =
runParser runParser
@ -112,8 +113,9 @@ main = do
case m of case m of
Left e -> putStrLn $ errorBundlePretty e Left e -> putStrLn $ errorBundlePretty e
Right m' -> Right m' ->
m_session m' `shouldBe` m_address m' `shouldBe`
U.fromString "ad8477d3-4fdd-4c97-90b2-76630b5f77e1" Just
"u17n7hpwaujyq7ux8f9jpyymtnk5urw7pyrf60smp5mawy7jgz325hfvz3jn3zsfya8yxryf9q7ldk8nu8df0emra5wne28zq9d9nm2pu4x6qwjha565av9aze0xgujgslz74ufkj0c0cylqwjyrh9msjfh7jzal6d3qzrnhkkqy3pqm8j63y07jxj7txqeac982778rmt64f32aum94x"
it "parse Zingo memo - Orchard" $ do it "parse Zingo memo - Orchard" $ do
let m = let m =
runParser runParser
@ -123,8 +125,9 @@ main = do
case m of case m of
Left e -> putStrLn $ errorBundlePretty e Left e -> putStrLn $ errorBundlePretty e
Right m' -> Right m' ->
m_session m' `shouldBe` m_address m' `shouldBe`
U.fromString "5d3d4494-51c0-432d-8495-050419957aea" Just
"u17n7hpwaujyq7ux8f9jpyymtnk5urw7pyrf60smp5mawy7jgz325hfvz3jn3zsfya8yxryf9q7ldk8nu8df0emra5wne28zq9d9nm2pu4x6qwjha565av9aze0xgujgslz74ufkj0c0cylqwjyrh9msjfh7jzal6d3qzrnhkkqy3pqm8j63y07jxj7txqeac982778rmt64f32aum94x"
describe "PIN generator" $ do describe "PIN generator" $ do
it "should give a 7 digit" $ do it "should give a 7 digit" $ do
pin <- generatePin pin <- generatePin
@ -688,6 +691,8 @@ main = do
"zxviews1qdjagrrpqqqqpq8es75mlu6rref0qyrstchf8dxzeygtsejwfqu8ckhwl2qj5m8am7lmupxk3vkvdjm8pawjpmesjfapvsqw96pa46c2z0kk7letrxf7mkltwz54fwpxc7kc79mm5kce3rwn5ssl009zwsra2spppwgrx25s9k5hq65f69l4jz2tjmqgy0pl49qmtaj3nudk6wglwe2hpa327hydlchtyq9av6wjd6hu68e04ahwk9a9n2kt0kj3nj99nue65awtu5cwwcpjs" "zxviews1qdjagrrpqqqqpq8es75mlu6rref0qyrstchf8dxzeygtsejwfqu8ckhwl2qj5m8am7lmupxk3vkvdjm8pawjpmesjfapvsqw96pa46c2z0kk7letrxf7mkltwz54fwpxc7kc79mm5kce3rwn5ssl009zwsra2spppwgrx25s9k5hq65f69l4jz2tjmqgy0pl49qmtaj3nudk6wglwe2hpa327hydlchtyq9av6wjd6hu68e04ahwk9a9n2kt0kj3nj99nue65awtu5cwwcpjs"
let vk2 = let vk2 =
"zxviews1qdjagrrpqqqqpq8es75mlufakef0qyrstchf8dxzeygtsejwfqu8ckhwl2qj5m8am7lmupxk3vkvdjm8pawjpmesjfapvsqw96pa46c2z0kk7letrxf7mkltwz54fwpxc7kc79mm5kce3rwn5ssl009zwsra2spppwgrx25s9k5hq65f69l4jz2tjmqgy0pl49qmtaj3nudk6wglwe2hpa327hydlchtyq9av6wjd6hu68e04ahwk9a9n2kt0kj3nj99nue65awtu5cwwcpjs" "zxviews1qdjagrrpqqqqpq8es75mlufakef0qyrstchf8dxzeygtsejwfqu8ckhwl2qj5m8am7lmupxk3vkvdjm8pawjpmesjfapvsqw96pa46c2z0kk7letrxf7mkltwz54fwpxc7kc79mm5kce3rwn5ssl009zwsra2spppwgrx25s9k5hq65f69l4jz2tjmqgy0pl49qmtaj3nudk6wglwe2hpa327hydlchtyq9av6wjd6hu68e04ahwk9a9n2kt0kj3nj99nue65awtu5cwwcpjs"
let vk3 =
"uview1u833rp8yykd7h4druwht6xp6k8krle45fx8hqsw6vzw63n24atxpcatws82z092kryazuu6d7rayyut8m36wm4wpjy2z8r9hj48fx5pf49gw4sjrq8503qpz3vqj5hg0vg9vsqeasg5qjuyh94uyfm7v76udqcm2m0wfc25hcyqswcn56xxduq3xkgxkr0l73cjy88fdvf90eq5fda9g6x7yv7d0uckpevxg6540wc76xrc4axxvlt03ptaa2a0rektglmdy68656f3uzcdgqqyu0t7wk5cvwghyyvgqc0rp3vgu5ye4nd236ml57rjh083a2755qemf6dk6pw0qrnfm7246s8eg2hhzkzpf9h73chhng7xhmyem2sjh8rs2m9nhfcslsgenm"
it "returns 401 with bad session" $ do it "returns 401 with bad session" $ do
req <- req <-
testPostJson "/api/ownervk" $ testPostJson "/api/ownervk" $
@ -728,7 +733,7 @@ main = do
[("session", Just "35bfb9c2-9ad2-4fe5-adda-99d63b8dcdcd")] [("session", Just "35bfb9c2-9ad2-4fe5-adda-99d63b8dcdcd")]
req req
getResponseStatus res `shouldBe` badRequest400 getResponseStatus res `shouldBe` badRequest400
it "succeeds with correct key" $ do it "succeeds with correct Sapling key" $ do
req <- req <-
testPostJson "/api/ownervk" $ testPostJson "/api/ownervk" $
A.object ["payload" A..= (vk1 :: String)] A.object ["payload" A..= (vk1 :: String)]
@ -738,6 +743,26 @@ main = do
[("session", Just "35bfb9c2-9ad2-4fe5-adda-99d63b8dcdcd")] [("session", Just "35bfb9c2-9ad2-4fe5-adda-99d63b8dcdcd")]
req req
getResponseStatus res `shouldBe` created201 getResponseStatus res `shouldBe` created201
it "succeeds with correct Unified key and UA" $ do
req <-
testPostJson "/api/ownervk" $
A.object ["payload" A..= (vk3 :: String)]
res <-
httpLBS $
setRequestQueryString
[("session", Just "35bfb9c2-9ad2-4fe5-daad-99d63b8dcdaa")]
req
getResponseStatus res `shouldBe` created201
xit "succeeds with correct Unified key and Sapling address" $ do
req <-
testPostJson "/api/ownervk" $
A.object ["payload" A..= (vk3 :: String)]
res <-
httpLBS $
setRequestQueryString
[("session", Just "35bfb9c2-a92d-4fe5-daad-99d63b8dcdaa")]
req
getResponseStatus res `shouldBe` created201
around handleDb $ around handleDb $
describe "Database actions" $ do describe "Database actions" $ do
describe "authentication" $ do describe "authentication" $ do
@ -1176,8 +1201,25 @@ startAPI config = do
1613487 1613487
"8ea140fbb30615d6cae383c4f62f3ad9afb10b804f63138d5b53990bd56e0162" "8ea140fbb30615d6cae383c4f62f3ad9afb10b804f63138d5b53990bd56e0162"
True True
let myUser3 =
User
(Just (read "6272a90f2b05a74cf1500003" :: ObjectId))
"u15hjz9v46azzmdept050heh8795qxzwy2pykg097lg69jpk4qzah90cj2q4amq0c07gta60x8qgw00qewcy3hg9kv9h6zjkh3jc66vr40u6uu2dxmqkqhypud95vm0gq7y5ga7c8psdqgthsrwvgd676a2pavpcd4euwwapgackxa3qhvga0wnl0k6vncskxlq94vqwjd7zepy3qd5jh"
"35bfb9c2-9ad2-4fe5-daad-99d63b8dcdaa"
1613487
"8ea140fbb30615d6cae383c4f62f3ad9afb10b804f63138d5b53990bd56e0162"
True
let myUser4 =
User
(Just (read "6272a90f2b05a74cf7500003" :: ObjectId))
"zs1fau9x305eztcdm5f08q9uc4hmvvjpjrgjcwcj0mjwhd83pdj0j92rxwqp6zkjmz3e49ej4xrcc8"
"35bfb9c2-a92d-4fe5-daad-99d63b8dcdaa"
1613487
"8ea140fbb30615d6cae383c4f62f3ad9afb10b804f63138d5b53990bd56e0162"
True
let userList = let userList =
map unwrapDoc $ filter filterDocs $ val <$> [myUser, myUser1, myUser2] map unwrapDoc $
filter filterDocs $ val <$> [myUser, myUser1, myUser2, myUser3, myUser4]
_ <- access pipe master "test" (insertAll_ "users" userList) _ <- access pipe master "test" (insertAll_ "users" userList)
let myOwner = let myOwner =
Owner Owner
@ -1233,6 +1275,60 @@ startAPI config = do
False False
"" ""
"" ""
let myOwner2 =
Owner
(Just (read "627ad3492b05a76be3700008"))
"u15hjz9v46azzmdept050heh8795qxzwy2pykg097lg69jpk4qzah90cj2q4amq0c07gta60x8qgw00qewcy3hg9kv9h6zjkh3jc66vr40u6uu2dxmqkqhypud95vm0gq7y5ga7c8psdqgthsrwvgd676a2pavpcd4euwwapgackxa3qhvga0wnl0k6vncskxlq94vqwjd7zepy3qd5jh"
"Test shop 3"
"usd"
False
0
False
0
"Roxy"
"Foo"
"roxy@zgo.cash"
"1 Main St"
"Mpls"
"Minnesota"
"55401"
""
"missyfoo.io"
"United States"
True
False
False
(UTCTime (fromGregorian 2024 8 6) (secondsToDiffTime 0))
False
""
""
let myOwner3 =
Owner
(Just (read "627ad3492b05a76be3750008"))
"zs1fau9x305eztcdm5f08q9uc4hmvvjpjrgjcwcj0mjwhd83pdj0j92rxwqp6zkjmz3e49ej4xrcc8"
"Test shop 4"
"usd"
False
0
False
0
"Roxy"
"Foo"
"roxy@zgo.cash"
"1 Main St"
"Mpls"
"Minnesota"
"55401"
""
"missyfoo.io"
"United States"
True
False
False
(UTCTime (fromGregorian 2024 8 6) (secondsToDiffTime 0))
False
""
""
_ <- access pipe master "test" (Database.MongoDB.delete (select [] "owners")) _ <- access pipe master "test" (Database.MongoDB.delete (select [] "owners"))
let o = val myOwner let o = val myOwner
case o of case o of
@ -1242,6 +1338,14 @@ startAPI config = do
case o1 of case o1 of
Doc d1 -> access pipe master "test" (insert_ "owners" d1) Doc d1 -> access pipe master "test" (insert_ "owners" d1)
_ -> fail "Couldn't save Owner1 in DB" _ -> fail "Couldn't save Owner1 in DB"
let o2 = val myOwner2
case o2 of
Doc d2 -> access pipe master "test" (insert_ "owners" d2)
_ -> fail "Couldn't save Owner2 in DB"
let o3 = val myOwner3
case o3 of
Doc d3 -> access pipe master "test" (insert_ "owners" d3)
_ -> fail "Couldn't save Owner2 in DB"
_ <- access pipe master "test" (Database.MongoDB.delete (select [] "orders")) _ <- access pipe master "test" (Database.MongoDB.delete (select [] "orders"))
myTs <- liftIO getCurrentTime myTs <- liftIO getCurrentTime
let myOrder = let myOrder =