Compare commits
No commits in common. "ac86d1ee599fda157971c79a210fe4d9e3268a27" and "a134947df6af5b0729be20540addffdc91fd36c6" have entirely different histories.
ac86d1ee59
...
a134947df6
7 changed files with 93 additions and 418 deletions
|
@ -23,8 +23,7 @@ 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
|
||||||
|
|
|
@ -420,7 +420,8 @@ findExpiringOwners now =
|
||||||
|
|
||||||
findWithKeys :: Action IO [Document]
|
findWithKeys :: Action IO [Document]
|
||||||
findWithKeys =
|
findWithKeys =
|
||||||
rest =<< find (select ["paid" =: True, "payconf" =: True] "owners")
|
rest =<<
|
||||||
|
find (select ["paid" =: True, "invoices" =: True, "payconf" =: True] "owners")
|
||||||
|
|
||||||
removePro :: T.Text -> Action IO ()
|
removePro :: T.Text -> Action IO ()
|
||||||
removePro o =
|
removePro o =
|
||||||
|
|
|
@ -52,7 +52,6 @@ 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
|
||||||
|
@ -70,7 +69,6 @@ import ZcashHaskell.Orchard
|
||||||
import ZcashHaskell.Sapling
|
import ZcashHaskell.Sapling
|
||||||
import ZcashHaskell.Types
|
import ZcashHaskell.Types
|
||||||
( BlockResponse(..)
|
( BlockResponse(..)
|
||||||
, DecodedNote(..)
|
|
||||||
, RawData(..)
|
, RawData(..)
|
||||||
, RawTxResponse(..)
|
, RawTxResponse(..)
|
||||||
, RpcCall(..)
|
, RpcCall(..)
|
||||||
|
@ -373,7 +371,12 @@ listCountries :: Action IO [Document]
|
||||||
listCountries = rest =<< find (select [] "countries")
|
listCountries = rest =<< find (select [] "countries")
|
||||||
|
|
||||||
sendPin ::
|
sendPin ::
|
||||||
BS.ByteString -> BS.ByteString -> T.Text -> T.Text -> T.Text -> IO String
|
BS.ByteString
|
||||||
|
-> 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
|
||||||
|
@ -385,73 +388,17 @@ 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
|
r <- liftIO $ try $ makeZcashCall nodeUser nodePwd "z_sendmany" pd -- IO (Either HttpException (Response Object))
|
||||||
case r of
|
case r of
|
||||||
Right res -> do
|
Right res -> do
|
||||||
let sCode = getResponseStatus (res :: Response (RpcResponse T.Text))
|
let sCode = getResponseStatus (res :: Response Object)
|
||||||
let rBody = getResponseBody res
|
|
||||||
if sCode == ok200
|
if sCode == ok200
|
||||||
then do
|
then return "Pin sent!"
|
||||||
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
|
||||||
|
@ -466,7 +413,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
|
||||||
_ <- liftIO $ sendPin nodeUser nodePwd node (address tx) (T.pack newPin)
|
_ <- 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 $
|
||||||
|
@ -1228,56 +1175,37 @@ 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 $ C.pack q
|
if isValidSaplingViewingKey qBytes
|
||||||
then do
|
then if matchSaplingAddress
|
||||||
if matchSaplingAddress
|
qBytes
|
||||||
qBytes
|
(bytes . decodeBech32 . C.pack . T.unpack $ uaddress u')
|
||||||
(bytes . decodeBech32 . C.pack . T.unpack $ uaddress u')
|
then do
|
||||||
then do
|
owner <- liftAndCatchIO $ run (findOwner $ uaddress u')
|
||||||
owner <- liftAndCatchIO $ run (findOwner $ uaddress u')
|
case cast' . Doc =<< owner of
|
||||||
case cast' . Doc =<< owner of
|
Nothing -> status badRequest400
|
||||||
Nothing -> status badRequest400
|
Just o' -> do
|
||||||
Just o' -> do
|
unless (oviewkey o' /= "") $ do
|
||||||
unless (oviewkey o' /= "") $ do
|
vkInfo <-
|
||||||
liftAndCatchIO $ run (upsertViewingKey o' q)
|
liftAndCatchIO $
|
||||||
status created201
|
makeZcashCall
|
||||||
else status forbidden403
|
nodeUser
|
||||||
else case decodeUfvk (C.pack q) of
|
nodePwd
|
||||||
Nothing -> status badRequest400
|
"z_importviewingkey"
|
||||||
Just fvk -> do
|
[ Data.Aeson.String (T.strip . T.pack $ q)
|
||||||
if isValidUnifiedAddress $
|
, "no"
|
||||||
C.pack . T.unpack $ uaddress u'
|
] -- TODO: Remove this call to the node
|
||||||
then do
|
let content =
|
||||||
if matchOrchardAddress
|
getResponseBody vkInfo :: RpcResponse Object
|
||||||
(C.pack q)
|
if isNothing (err content)
|
||||||
(C.pack . T.unpack $ uaddress u')
|
then do
|
||||||
then do
|
_ <-
|
||||||
owner <-
|
liftAndCatchIO $ run (upsertViewingKey o' q)
|
||||||
liftAndCatchIO $ run (findOwner $ uaddress u')
|
status created201
|
||||||
case cast' . Doc =<< owner of
|
else do
|
||||||
Nothing -> status badRequest400
|
text $ L.pack . show $ err content
|
||||||
Just o' -> do
|
status badRequest400
|
||||||
unless (oviewkey o' /= "") $ do
|
else status forbidden403
|
||||||
liftAndCatchIO $
|
else status badRequest400 -- TODO: add Unified VK support
|
||||||
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"
|
||||||
|
@ -1875,14 +1803,9 @@ generateToken = do
|
||||||
runCryptoRNGT rngState $ randomString 24 "abcdef0123456789"
|
runCryptoRNGT rngState $ randomString 24 "abcdef0123456789"
|
||||||
|
|
||||||
getBlockInfo ::
|
getBlockInfo ::
|
||||||
BS.ByteString -> BS.ByteString -> T.Text -> IO (Maybe BlockResponse)
|
BS.ByteString -> BS.ByteString -> SC.Scientific -> IO (Maybe BlockResponse)
|
||||||
getBlockInfo nodeUser nodePwd bh = do
|
getBlockInfo nodeUser nodePwd bh = do
|
||||||
blockInfo <-
|
blockInfo <- makeZcashCall nodeUser nodePwd "getblock" [Number bh]
|
||||||
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
|
||||||
|
@ -1890,61 +1813,38 @@ getBlockInfo nodeUser nodePwd bh = do
|
||||||
print $ err content
|
print $ err content
|
||||||
return Nothing
|
return Nothing
|
||||||
|
|
||||||
scanTxNative :: Config -> Pipe -> IO ()
|
scanTxNative :: Pipe -> T.Text -> BS.ByteString -> BS.ByteString -> IO ()
|
||||||
scanTxNative config pipe = do
|
scanTxNative pipe db nodeUser nodePwd = 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 nodeUser = c_nodeUser config
|
let ownerList = cast' . Doc <$> keyOwnerList
|
||||||
let nodePwd = c_nodePwd config
|
let keyList = map (maybe "" oviewkey) ownerList
|
||||||
let ownerList = mapMaybe (cast' . Doc) keyOwnerList
|
|
||||||
lastBlockData <- access pipe master db findBlock
|
lastBlockData <- access pipe master db findBlock
|
||||||
latestBlock <- getBlockInfo nodeUser nodePwd "-1"
|
latestBlock <- getBlockInfo nodeUser nodePwd (SC.scientific (-1) 0)
|
||||||
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 . T.pack . show)
|
(getBlockInfo nodeUser nodePwd . fromInteger)
|
||||||
[(bl_height lB - 50) .. (bl_height lB)]
|
[2220000 .. (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
|
||||||
print "checking txs against keys..."
|
mapM_ (checkTx filteredTxList) keyList
|
||||||
mapM_ (checkTx filteredTxList) ownerList
|
|
||||||
access pipe master (c_dbName config) $
|
|
||||||
upsertBlock (last $ catMaybes filteredBlockList)
|
|
||||||
Just lastBlock -> do
|
Just lastBlock -> do
|
||||||
blockList' <-
|
let blockList' = [(bl_height lastBlock + 1) .. (bl_height lB)]
|
||||||
mapM
|
print blockList'
|
||||||
(getBlockInfo nodeUser nodePwd . T.pack . show)
|
print keyList
|
||||||
[(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
|
||||||
|
@ -1956,145 +1856,39 @@ scanTxNative config pipe = do
|
||||||
nodeUser
|
nodeUser
|
||||||
nodePwd
|
nodePwd
|
||||||
"getrawtransaction"
|
"getrawtransaction"
|
||||||
[Data.Aeson.String txid, Number $ SC.scientific 1 0]
|
[Data.Aeson.String txid]
|
||||||
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] -> Owner -> IO ()
|
checkTx :: [RawTxResponse] -> T.Text -> IO ()
|
||||||
checkTx txList' k = do
|
checkTx txList k = do
|
||||||
let sOutList = concatMap rt_shieldedOutputs txList'
|
if isValidSaplingViewingKey (E.encodeUtf8 k)
|
||||||
if isValidSaplingViewingKey (E.encodeUtf8 $ oviewkey k)
|
|
||||||
then do
|
then do
|
||||||
print "decoding Sapling tx"
|
let decodedTxList =
|
||||||
let decodedSapList' = concatMap (decodeSaplingTx $ oviewkey k) txList'
|
map
|
||||||
let zList = catMaybes decodedSapList'
|
(decodeSaplingOutput (E.encodeUtf8 k))
|
||||||
mapM_ (recordPayment pipe (c_dbName config) (oaddress k)) zList
|
(concatMap
|
||||||
|
rt_shieldedOutputs
|
||||||
|
(filter (\x -> rt_shieldedOutputs x /= []) txList))
|
||||||
|
print decodedTxList
|
||||||
else do
|
else do
|
||||||
let vk = decodeUfvk $ E.encodeUtf8 $ oviewkey k
|
let vk = decodeUfvk $ E.encodeUtf8 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'
|
map
|
||||||
let zList' = catMaybes decodedSapList
|
(decodeSaplingOutput (s_key v))
|
||||||
mapM_ (recordPayment pipe (c_dbName config) (oaddress k)) zList'
|
(concatMap rt_shieldedOutputs txList)
|
||||||
let decodedOrchList = concatMap (decodeUnifiedOrchardTx v) txList'
|
print decodedSapList
|
||||||
let oList = catMaybes decodedOrchList
|
let decodedOrchList =
|
||||||
mapM_ (recordPayment pipe (c_dbName config) (oaddress k)) oList
|
map
|
||||||
decodeSaplingTx :: T.Text -> RawTxResponse -> [Maybe ZcashTx]
|
(decryptOrchardAction v)
|
||||||
decodeSaplingTx k t =
|
(concatMap rt_orchardActions txList)
|
||||||
map
|
print decodedOrchList
|
||||||
(buildZcashTx t .
|
|
||||||
decodeSaplingOutput (bytes (decodeBech32 $ E.encodeUtf8 k)))
|
|
||||||
(rt_shieldedOutputs t)
|
|
||||||
decodeUnifiedSaplingTx :: BS.ByteString -> RawTxResponse -> [Maybe ZcashTx]
|
|
||||||
decodeUnifiedSaplingTx k t =
|
|
||||||
map (buildZcashTx t . decodeSaplingOutput k) (rt_shieldedOutputs t)
|
|
||||||
decodeUnifiedOrchardTx ::
|
|
||||||
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
|
||||||
|
|
||||||
|
|
19
src/ZGoTx.hs
19
src/ZGoTx.hs
|
@ -105,7 +105,6 @@ 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
|
||||||
|
@ -113,7 +112,6 @@ 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
|
||||||
|
@ -148,12 +146,6 @@ 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 <-
|
||||||
|
@ -165,7 +157,7 @@ pMsg = do
|
||||||
pMemo :: Parser MemoToken
|
pMemo :: Parser MemoToken
|
||||||
pMemo = do
|
pMemo = do
|
||||||
optional $ some spaceChar
|
optional $ some spaceChar
|
||||||
t <- pSession <|> pSaplingAddress <|> pUnifiedAddress <|> pOrderId <|> pMsg
|
t <- pSession <|> pSaplingAddress <|> pMsg
|
||||||
optional $ some spaceChar
|
optional $ some spaceChar
|
||||||
return t
|
return t
|
||||||
|
|
||||||
|
@ -190,15 +182,8 @@ 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) (isOrder tks)
|
pure $ ZGoMemo (isSession tks) (isAddress tks) (isPayment 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) &&
|
||||||
|
|
|
@ -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: 1d558fc646a7758d60a721124812070de222c2e1
|
commit: d78c269d96fe7d8a626cf701b8051c40f251e232
|
||||||
- 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
|
||||||
|
|
|
@ -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: 1d558fc646a7758d60a721124812070de222c2e1
|
commit: d78c269d96fe7d8a626cf701b8051c40f251e232
|
||||||
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: eab3c6817bb3cb5738725824d16eb023cb2967ef3bbaa8f8252524602f606dbb
|
sha256: 69201a27ac966be478ef0b8e3fa8e8bf5cbcc67a58cd254326545eb4f3e93569
|
||||||
size: 1229
|
size: 1229
|
||||||
version: 0.2.0
|
version: 0.2.0
|
||||||
original:
|
original:
|
||||||
commit: 1d558fc646a7758d60a721124812070de222c2e1
|
commit: d78c269d96fe7d8a626cf701b8051c40f251e232
|
||||||
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
|
||||||
|
|
120
test/Spec.hs
120
test/Spec.hs
|
@ -101,9 +101,8 @@ main = do
|
||||||
case m of
|
case m of
|
||||||
Left e -> putStrLn $ errorBundlePretty e
|
Left e -> putStrLn $ errorBundlePretty e
|
||||||
Right m' ->
|
Right m' ->
|
||||||
m_address m' `shouldBe`
|
m_session m' `shouldBe`
|
||||||
Just
|
U.fromString "5d3d4494-51c0-432d-8495-050419957aea"
|
||||||
"u17n7hpwaujyq7ux8f9jpyymtnk5urw7pyrf60smp5mawy7jgz325hfvz3jn3zsfya8yxryf9q7ldk8nu8df0emra5wne28zq9d9nm2pu4x6qwjha565av9aze0xgujgslz74ufkj0c0cylqwjyrh9msjfh7jzal6d3qzrnhkkqy3pqm8j63y07jxj7txqeac982778rmt64f32aum94x"
|
|
||||||
it "parse YWallet memo - Orchard" $ do
|
it "parse YWallet memo - Orchard" $ do
|
||||||
let m =
|
let m =
|
||||||
runParser
|
runParser
|
||||||
|
@ -113,9 +112,8 @@ main = do
|
||||||
case m of
|
case m of
|
||||||
Left e -> putStrLn $ errorBundlePretty e
|
Left e -> putStrLn $ errorBundlePretty e
|
||||||
Right m' ->
|
Right m' ->
|
||||||
m_address m' `shouldBe`
|
m_session m' `shouldBe`
|
||||||
Just
|
U.fromString "ad8477d3-4fdd-4c97-90b2-76630b5f77e1"
|
||||||
"u17n7hpwaujyq7ux8f9jpyymtnk5urw7pyrf60smp5mawy7jgz325hfvz3jn3zsfya8yxryf9q7ldk8nu8df0emra5wne28zq9d9nm2pu4x6qwjha565av9aze0xgujgslz74ufkj0c0cylqwjyrh9msjfh7jzal6d3qzrnhkkqy3pqm8j63y07jxj7txqeac982778rmt64f32aum94x"
|
|
||||||
it "parse Zingo memo - Orchard" $ do
|
it "parse Zingo memo - Orchard" $ do
|
||||||
let m =
|
let m =
|
||||||
runParser
|
runParser
|
||||||
|
@ -125,9 +123,8 @@ main = do
|
||||||
case m of
|
case m of
|
||||||
Left e -> putStrLn $ errorBundlePretty e
|
Left e -> putStrLn $ errorBundlePretty e
|
||||||
Right m' ->
|
Right m' ->
|
||||||
m_address m' `shouldBe`
|
m_session m' `shouldBe`
|
||||||
Just
|
U.fromString "5d3d4494-51c0-432d-8495-050419957aea"
|
||||||
"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
|
||||||
|
@ -691,8 +688,6 @@ 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" $
|
||||||
|
@ -733,7 +728,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 Sapling key" $ do
|
it "succeeds with correct key" $ do
|
||||||
req <-
|
req <-
|
||||||
testPostJson "/api/ownervk" $
|
testPostJson "/api/ownervk" $
|
||||||
A.object ["payload" A..= (vk1 :: String)]
|
A.object ["payload" A..= (vk1 :: String)]
|
||||||
|
@ -743,26 +738,6 @@ 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
|
||||||
|
@ -1201,25 +1176,8 @@ 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 $
|
map unwrapDoc $ filter filterDocs $ val <$> [myUser, myUser1, myUser2]
|
||||||
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
|
||||||
|
@ -1275,60 +1233,6 @@ 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
|
||||||
|
@ -1338,14 +1242,6 @@ 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 =
|
||||||
|
|
Loading…
Reference in a new issue