zgo-backend/test/Spec.hs

483 lines
17 KiB
Haskell
Raw Normal View History

2022-04-30 12:59:49 +00:00
{-# LANGUAGE OverloadedStrings #-}
2022-04-22 16:15:23 +00:00
module Spec where
2022-04-30 12:59:49 +00:00
import Control.Concurrent (forkIO, threadDelay)
import Control.Exception (bracket)
import Control.Monad.IO.Class
import qualified Data.Aeson as A
import qualified Data.ByteString as B
import Data.Char (isAscii)
import Data.Either
import Data.Maybe
2022-04-30 12:59:49 +00:00
import Data.SecureMem
import qualified Data.Text as T
2022-05-11 20:04:46 +00:00
import Data.Time.Clock
2022-04-30 12:59:49 +00:00
import Database.MongoDB
import Network.HTTP.Simple
import Network.HTTP.Types.Status
2022-05-11 20:04:46 +00:00
import Order
import Owner
2022-04-30 12:59:49 +00:00
import System.IO.Unsafe
2022-04-22 16:15:23 +00:00
import Test.Hspec
2022-04-30 12:59:49 +00:00
import Test.Hspec.Expectations.Json
import Test.Hspec.QuickCheck
2022-04-22 16:15:23 +00:00
import Test.QuickCheck
2022-04-30 12:59:49 +00:00
import Test.QuickCheck.Gen
2022-05-11 20:04:46 +00:00
import Test.QuickCheck.Monadic
import User
2022-04-22 16:15:23 +00:00
import ZGoBackend
2022-05-11 20:04:46 +00:00
import ZGoTx
2022-04-22 16:15:23 +00:00
2022-04-30 12:59:49 +00:00
passkey :: SecureMem
passkey = secureMemFromByteString "superSecret"
nodeAddress :: T.Text
nodeAddress =
"zs1xnpqd2tae9d95f8fhe4l0q7j44a5vf993m0pcnnvr56uqr4lgqlamesk5v4c5rhtvywc6lvlduy"
dbUser :: T.Text
dbUser = "zgo"
dbPassword :: T.Text
dbPassword = "zcashrules"
2022-04-22 16:15:23 +00:00
main :: IO ()
main =
hspec $ do
2022-04-30 12:59:49 +00:00
describe "Helper functions" $ do
describe "decodeHexText" $ do
it "converts to readable text" $ do
decodeHexText
"5a474f3a3a35643364343439342d353163302d343332642d383439352d3035303431393935376165610a5265706c792d546f3a0a7a733177366e6b616d65617a633567756a6d363933353073796c35773874677679617068756d73337077386579747a7935796d303878376476736b6d796b6b61746d777275636d67763365723865" `shouldBe`
"ZGO::5d3d4494-51c0-432d-8495-050419957aea\nReply-To:\nzs1w6nkameazc5gujm69350syl5w8tgvyaphums3pw8eytzy5ym08x7dvskmykkatmwrucmgv3er8e"
describe "hex strings" $ do
prop "encoding and decoding are inverse" $ \x ->
(decodeHexText . encodeHexText) (filter isAscii x) == filter isAscii x
describe "zToZGoTx" $ do
it "converts zcash tx to ZGo tx" $ do
let t =
ZcashTx
"someId"
0.5
50000000
1602000
18732456
False
20
"ZGO::5d3d4494-51c0-432d-8495-050419957aea\nReply-To:\nzs1w6nkameazc5gujm69350syl5w8tgvyaphums3pw8eytzy5ym08x7dvskmykkatmwrucmgv3er8e"
zToZGoTx t `shouldBe`
ZGoTx
""
"zs1w6nkameazc5gujm69350syl5w8tgvyaphums3pw8eytzy5ym08x7dvskmykkatmwrucmgv3er8e"
"5d3d4494-51c0-432d-8495-050419957aea"
20
18732456
0.5
"someId"
"ZGO::5d3d4494-51c0-432d-8495-050419957aea\nReply-To:\nzs1w6nkameazc5gujm69350syl5w8tgvyaphums3pw8eytzy5ym08x7dvskmykkatmwrucmgv3er8e"
describe "PIN generator" $ do
it "should give a 7 digit" $ do
length (T.unpack (unsafePerformIO generatePin)) `shouldBe` 7
describe "API endpoints" $ do
beforeAll_ startAPI $ do
describe "Price endpoint" $ do
it "returns a price for an existing currency" $ do
req <- testGet "/api/price" [("currency", Just "usd")]
res <- httpJSON req
getResponseStatus (res :: Response A.Value) `shouldBe` ok200
it "returns 204 when the currency is not supported" $ do
req <- testGet "/api/price" [("currency", Just "jpy")]
res <- httpLBS req
getResponseStatus res `shouldBe` noContent204
describe "Countries endpoint" $ do
it "returns a list of countries" $ do
req <- testGet "/api/countries" []
res <- httpJSON req
getResponseStatus (res :: Response A.Value) `shouldBe` ok200
describe "blockheight endpoint" $ do
it "returns a block number" $ do
req <- testGet "/api/blockheight" []
res <- httpJSON req
height (getResponseBody (res :: Response Block)) `shouldSatisfy` \x ->
x > 1600000
describe "unconfirmed Zcash txs" $ do
it "returns txs with less than 2 confirmations" $ do pending
describe "User endpoint" $ do
it "returns a user for a session" $ do
req <-
testGet
"/api/user"
2022-05-11 20:04:46 +00:00
[("session", Just "35bfb9c2-9ad2-4fe5-adda-99d63b8dcdcd")]
res <- httpJSON req
getResponseStatus (res :: Response A.Value) `shouldBe` ok200
it "returns 204 when no user" $ do
req <-
testGet
"/api/user"
[("session", Just "suchafak-euui-dican-eve-nbelieveitca")]
res <- httpLBS req
getResponseStatus res `shouldBe` noContent204
it "validate with correct pin" $ do
req <-
testPost
2022-05-11 20:04:46 +00:00
"/api/validateuser"
[ ("session", Just "35bfb9c2-9ad2-4fe5-adda-99d63b8dcdcd")
, ("pin", Just "1234567")
]
res <- httpLBS req
getResponseStatus res `shouldBe` accepted202
it "deletes user by id" $ do
req <- testDelete "/api/user/" "6272a90f2b05a74cf1000001"
res <- httpLBS req
getResponseStatus res `shouldBe` ok200
2022-04-30 12:59:49 +00:00
describe "Owner endpoint" $ do
2022-05-11 20:04:46 +00:00
prop "add owner" testOwnerAdd
it "return owner" $ do
req <-
testGet
"/api/owner"
[ ( "address"
, Just
"zs1w6nkameazc5gujm69350syl5w8tgvyaphums3pw8eytzy5ym08x7dvskmykkatmwrucmgv3er8e")
]
res <- httpJSON req
getResponseStatus (res :: Response A.Value) `shouldBe` ok200
2022-04-30 12:59:49 +00:00
describe "Order endpoint" $ do
2022-05-11 20:04:46 +00:00
prop "upsert order" testOrderAdd
it "get order by session" $ do
req <-
testGet
"/api/order"
[("session", Just "35bfb9c2-9ad2-4fe5-adda-99d63b8dcdcd")]
res <- httpJSON req
getResponseStatus (res :: Response A.Value) `shouldBe` ok200
it "get order by id" $ do
req <- testGet "/api/order/627ab3ea2b05a76be3000000" []
res <- httpJSON req
getResponseStatus (res :: Response A.Value) `shouldBe` ok200
2022-05-12 19:59:29 +00:00
it "get all orders for owner" $ do
req <- testGet "/api/allorders" [("address", Just "Zaddy")]
res <- httpJSON req
getResponseStatus (res :: Response A.Value) `shouldBe` ok200
2022-05-11 20:04:46 +00:00
it "delete order by id" $ do
req <- testDelete "/api/order/" "627ab3ea2b05a76be3000000"
res <- httpLBS req
getResponseStatus res `shouldBe` ok200
2022-05-12 19:59:29 +00:00
describe "Item endpoint" $ do
it "add item" $ do pending
it "get item" $ do pending
it "delete item" $ do pending
2022-04-30 12:59:49 +00:00
around handleDb $
describe "Database actions" $ do
describe "authentication" $ do
it "should succeed with good creds" $ \p -> do
r <- liftIO $ access p master "zgo" (auth "zgo" "zcashrules")
r `shouldBe` True
it "should fail with bad creds" $ \p -> do
r <- liftIO $ access p master "zgo" (auth "user" "pwd")
r `shouldBe` False
describe "Zcash prices" $ do
it "should update" $ \p -> do
doc <- access p master "test" $ findPrice "usd"
case doc of
Nothing -> True `shouldBe` False
Just d -> do
let q = parseZGoPrice d
case q of
Nothing -> True `shouldBe` False
Just r -> do
let t1 = ZGoBackend.timestamp r
_ <- checkZcashPrices p "test"
doc2 <- access p master "test" $ findPrice "usd"
case doc2 of
Nothing -> True `shouldBe` False
Just d2 -> do
let q2 = parseZGoPrice d2
case q2 of
Nothing -> True `shouldBe` False
Just r2 -> do
let t2 = ZGoBackend.timestamp r2
t2 `shouldSatisfy` (t1 <)
2022-05-11 20:04:46 +00:00
describe "user is" $ do
it "validated" $ \p -> do
t <-
access p master "test" $
findOne (select ["validated" =: False] "users")
case t of
Nothing -> True `shouldBe` False
Just r -> do
let s = parseUserBson r
case s of
Nothing -> True `shouldBe` False
Just z -> do
_ <- access p master "test" $ validateUser (usession z)
q <-
access p master "test" $
findOne
(select
["validated" =: True, "session" =: usession z]
"users")
isNothing q `shouldBe` False
it "deleted" $ \p -> do
t <- access p master "test" $ findOne (select [] "users")
case t of
Nothing -> True `shouldBe` False
Just r -> do
let s = parseUserBson r
case s of
Nothing -> True `shouldBe` False
Just z -> do
_ <- access p master "test" $ deleteUser (u_id z)
q <-
access p master "test" $
findOne
(select ["_id" =: (read (u_id z) :: ObjectId)] "users")
isNothing q `shouldBe` True
2022-04-30 12:59:49 +00:00
describe "Zcash transactions" $ do
it "logins are added to db" $ \p -> do
_ <- access p master "test" (delete (select [] "txs"))
_ <- scanZcash nodeAddress p "test"
threadDelay 1000000
t <- access p master "test" $ findOne (select [] "txs")
case t of
Nothing -> True `shouldBe` False
Just r -> do
let s = parseZGoTxBson r
case s of
Nothing -> True `shouldBe` False
Just z -> confirmations z `shouldSatisfy` (> 0)
it "payments are added to db" $ \p -> do
_ <- access p master "test" (delete (select [] "payments"))
_ <- scanZcash nodeAddress p "test"
threadDelay 1000000
t <- access p master "test" $ findOne (select [] "payments")
case t of
Nothing -> True `shouldBe` False
Just r -> do
let s = parseZGoTxBson r
case s of
Nothing -> True `shouldBe` False
Just z -> confirmations z `shouldSatisfy` (> 0)
2022-05-12 19:59:29 +00:00
xit "login txs are converted to users" $ \p -> do
2022-05-03 13:59:29 +00:00
let myTx =
ZGoTx
""
"zs1w6nkameazc5gujm69350syl5w8tgvyaphums3pw8eytzy5ym08x7dvskmykkatmwrucmgv3er8e"
"35bfb9c2-9ad2-4fe5-adda-99d63b8dcdca"
3
1613487
0.00000001
"abcdef"
"Super Memo"
_ <- access p master "test" (delete (select [] "users"))
_ <- access p master "test" (insert_ "txs" (encodeZGoTxBson myTx))
_ <- updateLogins nodeAddress p "test"
threadDelay 1000000
t <- access p master "test" $ findOne (select [] "users")
case t of
Nothing -> True `shouldBe` False
Just r -> do
let s = parseUserBson r
case s of
Nothing -> True `shouldBe` False
Just z -> length (T.unpack (usession z)) `shouldSatisfy` (> 0)
2022-04-30 12:59:49 +00:00
testGet :: B.ByteString -> [(B.ByteString, Maybe B.ByteString)] -> IO Request
testGet endpoint body = do
let user = "user"
let pwd = "superSecret"
let testRequest =
setRequestQueryString body $
setRequestPort 4000 $
setRequestBasicAuth user pwd $
setRequestMethod "GET" $ setRequestPath endpoint defaultRequest
return testRequest
testPost :: B.ByteString -> [(B.ByteString, Maybe B.ByteString)] -> IO Request
testPost endpoint body = do
let user = "user"
let pwd = "superSecret"
let testRequest =
setRequestQueryString body $
setRequestPort 4000 $
setRequestBasicAuth user pwd $
setRequestMethod "POST" $ setRequestPath endpoint defaultRequest
return testRequest
2022-05-11 20:04:46 +00:00
testPostJson :: B.ByteString -> A.Value -> IO Request
testPostJson endpoint body = do
let user = "user"
let pwd = "superSecret"
let testRequest =
setRequestBodyJSON body $
setRequestPort 4000 $
setRequestBasicAuth user pwd $
setRequestMethod "POST" $ setRequestPath endpoint defaultRequest
return testRequest
testDelete :: B.ByteString -> B.ByteString -> IO Request
testDelete endpoint par = do
let user = "user"
let pwd = "superSecret"
let testRequest =
setRequestPort 4000 $
setRequestBasicAuth user pwd $
setRequestMethod "DELETE" $
setRequestPath (B.append endpoint par) defaultRequest
return testRequest
2022-05-11 20:04:46 +00:00
testOwnerAdd :: Owner -> Property
testOwnerAdd o =
monadicIO $ do
req <- run $ testPostJson "/api/owner" (A.toJSON o) --`debug` show o
res <- httpLBS req
assert $ getResponseStatus res == created201
testOrderAdd :: ZGoOrder -> Property
testOrderAdd o =
monadicIO $ do
req <- run $ testPostJson "/api/order" (A.toJSON o)
res <- httpLBS req
assert $ getResponseStatus res == created201
2022-04-30 12:59:49 +00:00
-- | Open the MongoDB connection
openDbConnection :: IO Pipe
openDbConnection = do
pipe <- connect $ host "127.0.0.1"
access pipe master "zgo" (auth "zgo" "zcashrules")
return pipe
-- | Close the MongoDB pipe
closeDbConnection :: Pipe -> IO ()
closeDbConnection = close
-- | DB handling function
handleDb :: (Pipe -> Expectation) -> IO ()
handleDb = bracket openDbConnection closeDbConnection
startAPI :: IO ()
startAPI = do
putStrLn "Starting test server ..."
pipe <- connect $ host "127.0.0.1"
c <- access pipe master "zgo" (auth "zgo" "zcashrules")
_ <- forkIO (app pipe "test" passkey nodeAddress)
2022-05-11 20:04:46 +00:00
let myUser =
User
"6272a90f2b05a74cf1000001"
"zs1w6nkameazc5gujm69350syl5w8tgvyaphums3pw8eytzy5ym08x7dvskmykkatmwrucmgv3er8e"
"35bfb9c2-9ad2-4fe5-adda-99d63b8dcdcd"
1613487
"1234567"
False
_ <-
access
pipe
master
"test"
(insert_
"users"
[ "address" =: uaddress myUser
, "_id" =: (read (u_id myUser) :: ObjectId)
, "session" =: usession myUser
, "blocktime" =: ublocktime myUser
, "pin" =: upin myUser
, "validated" =: uvalidated myUser
])
let myOwner =
Owner
(Just (read "627ad3492b05a76be3000001"))
"zs1w6nkameazc5gujm69350syl5w8tgvyaphums3pw8eytzy5ym08x7dvskmykkatmwrucmgv3er8e"
"Test shop"
"usd"
False
0
False
0
"Bubba"
"Gibou"
"bubba@zgo.cash"
"1 Main St"
"Mpls"
"Minnesota"
"55401"
""
"bubbarocks.io"
"United States"
False
False
False
_ <- access pipe master "test" (delete (select [] "owners"))
let o = val myOwner
case o of
Doc d -> access pipe master "test" (insert_ "owners" d)
_ <- access pipe master "test" (delete (select [] "orders"))
myTs <- liftIO getCurrentTime
let myOrder =
ZGoOrder
(Just (read "627ab3ea2b05a76be3000000"))
"Zaddy"
"35bfb9c2-9ad2-4fe5-adda-99d63b8dcdcd"
myTs
False
"usd"
102.0
0
0
[]
let ordTest = val myOrder
case ordTest of
Doc oT -> access pipe master "test" (insert_ "orders" oT)
2022-04-30 12:59:49 +00:00
threadDelay 1000000
putStrLn "Test server is up!"
2022-05-11 20:04:46 +00:00
--QuickCheck instances
instance Arbitrary ZGoOrder where
arbitrary = do
i <- arbitrary
a <- arbitrary
s <- arbitrary
ts <- arbitrary
c <- arbitrary
cur <- arbitrary
p <- arbitrary
t <- arbitrary
tZ <- arbitrary
ZGoOrder i a s ts c cur p t tZ <$> arbitrary
instance Arbitrary LineItem where
arbitrary = do
i <- arbitrary
q <- arbitrary
n <- arbitrary
LineItem i q n <$> arbitrary
instance Arbitrary ObjectId where
arbitrary = do
x <- arbitrary
Oid x <$> arbitrary
instance Arbitrary Owner where
arbitrary = do
i <- arbitrary
a <- arbitrary
n <- arbitrary
c <- arbitrary
t <- arbitrary
tV <- arbitrary
v <- arbitrary
vV <- arbitrary
f <- arbitrary
l <- arbitrary
e <- arbitrary
s <- arbitrary
ct <- arbitrary
st <- arbitrary
p <- arbitrary
ph <- arbitrary
w <- arbitrary
co <- arbitrary
paid <- arbitrary
zats <- arbitrary
Owner i a n c t tV v vV f l e s ct st p ph w co paid zats <$> arbitrary