Don't run ...Many tests against mongo 2.4
This commit is contained in:
parent
e2e9f12af8
commit
173e90eb90
2 changed files with 157 additions and 132 deletions
|
@ -43,7 +43,7 @@ module Database.MongoDB.Query (
|
||||||
MRResult, mapReduce, runMR, runMR',
|
MRResult, mapReduce, runMR, runMR',
|
||||||
-- * Command
|
-- * Command
|
||||||
Command, runCommand, runCommand1,
|
Command, runCommand, runCommand1,
|
||||||
eval, retrieveServerData
|
eval, retrieveServerData, ServerData(..)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude hiding (lookup)
|
import Prelude hiding (lookup)
|
||||||
|
@ -77,7 +77,7 @@ import Control.Monad.Trans.Control (MonadBaseControl(..))
|
||||||
import Data.Binary.Put (runPut)
|
import Data.Binary.Put (runPut)
|
||||||
import Data.Bson (Document, Field(..), Label, Val, Value(String, Doc, Bool),
|
import Data.Bson (Document, Field(..), Label, Val, Value(String, Doc, Bool),
|
||||||
Javascript, at, valueAt, lookup, look, genObjectId, (=:),
|
Javascript, at, valueAt, lookup, look, genObjectId, (=:),
|
||||||
(=?), (!?), Val(..), ObjectId)
|
(=?), (!?), Val(..), ObjectId, Value(..))
|
||||||
import Data.Bson.Binary (putDocument)
|
import Data.Bson.Binary (putDocument)
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
@ -907,27 +907,25 @@ deleteBlock ordered col (prevCount, docs) = do
|
||||||
let n = fromMaybe 0 $ doc !? "n"
|
let n = fromMaybe 0 $ doc !? "n"
|
||||||
case (look "writeErrors" doc, look "writeConcernError" doc) of
|
case (look "writeErrors" doc, look "writeConcernError" doc) of
|
||||||
(Nothing, Nothing) -> return $ WriteResult False 0 Nothing n [] [] []
|
(Nothing, Nothing) -> return $ WriteResult False 0 Nothing n [] [] []
|
||||||
(Just err, Nothing) -> do
|
(Just (Array err), Nothing) -> do
|
||||||
return $ WriteResult True 0 Nothing n [] [
|
return $ WriteResult True 0 Nothing n [] (map (anyToWriteError prevCount) err) []
|
||||||
WriteFailure 0 -- TODO add normal index
|
|
||||||
(maybe 0 id $ lookup "ok" doc)
|
|
||||||
(show err)] []
|
|
||||||
(Nothing, Just (Doc err)) -> do
|
(Nothing, Just (Doc err)) -> do
|
||||||
return $ WriteResult True 0 Nothing n [] [] [
|
return $ WriteResult True 0 Nothing n [] [] [
|
||||||
WriteConcernError
|
WriteConcernError
|
||||||
(fromMaybe (-1) $ err !? "code")
|
(fromMaybe (-1) $ err !? "code")
|
||||||
(fromMaybe "" $ err !? "errmsg")
|
(fromMaybe "" $ err !? "errmsg")
|
||||||
]
|
]
|
||||||
(Just err, Just (Doc writeConcernErr)) -> do
|
(Just (Array err), Just (Doc writeConcernErr)) -> do
|
||||||
return $ WriteResult True 0 Nothing n [] [
|
return $ WriteResult True 0 Nothing n [] (map (anyToWriteError prevCount) err) [
|
||||||
WriteFailure 0 -- TODO add normal index
|
|
||||||
(maybe 0 id $ lookup "ok" doc)
|
|
||||||
(show err)] [
|
|
||||||
WriteConcernError
|
WriteConcernError
|
||||||
(fromMaybe (-1) $ writeConcernErr !? "code")
|
(fromMaybe (-1) $ writeConcernErr !? "code")
|
||||||
(fromMaybe "" $ writeConcernErr !? "errmsg")
|
(fromMaybe "" $ writeConcernErr !? "errmsg")
|
||||||
]
|
]
|
||||||
|
|
||||||
|
anyToWriteError :: Int -> Value -> Failure
|
||||||
|
anyToWriteError ind (Doc d) = docToWriteError d
|
||||||
|
anyToWriteError ind _ = WriteFailure ind (-1) "Unknown bson value"
|
||||||
|
|
||||||
-- * Read
|
-- * Read
|
||||||
|
|
||||||
data ReadMode =
|
data ReadMode =
|
||||||
|
|
|
@ -5,7 +5,7 @@ module QuerySpec (spec) where
|
||||||
import Data.String (IsString(..))
|
import Data.String (IsString(..))
|
||||||
import TestImport
|
import TestImport
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Control.Monad (forM_)
|
import Control.Monad (forM_, when)
|
||||||
import System.Environment (getEnv)
|
import System.Environment (getEnv)
|
||||||
import System.IO.Error (catchIOError)
|
import System.IO.Error (catchIOError)
|
||||||
import qualified Data.List as L
|
import qualified Data.List as L
|
||||||
|
@ -23,6 +23,11 @@ db action = do
|
||||||
close pipe
|
close pipe
|
||||||
return result
|
return result
|
||||||
|
|
||||||
|
getWireVersion :: IO Int
|
||||||
|
getWireVersion = db $ do
|
||||||
|
sd <- retrieveServerData
|
||||||
|
return $ maxWireVersion sd
|
||||||
|
|
||||||
withCleanDatabase :: ActionWith () -> IO ()
|
withCleanDatabase :: ActionWith () -> IO ()
|
||||||
withCleanDatabase action = dropDB >> action () >> dropDB >> return ()
|
withCleanDatabase action = dropDB >> action () >> dropDB >> return ()
|
||||||
where
|
where
|
||||||
|
@ -192,109 +197,125 @@ spec = around withCleanDatabase $ do
|
||||||
|
|
||||||
describe "updateMany" $ do
|
describe "updateMany" $ do
|
||||||
it "updates value" $ do
|
it "updates value" $ do
|
||||||
_id <- db $ insert "team" ["name" =: "Yankees", "league" =: "American"]
|
wireVersion <- getWireVersion
|
||||||
result <- db $ rest =<< find (select [] "team")
|
when (wireVersion > 1) $ do
|
||||||
result `shouldBe` [["_id" =: _id, "name" =: "Yankees", "league" =: "American"]]
|
_id <- db $ insert "team" ["name" =: "Yankees", "league" =: "American"]
|
||||||
_ <- db $ updateMany "team" [([ "_id" =: _id]
|
result <- db $ rest =<< find (select [] "team")
|
||||||
, ["$set" =: ["league" =: "European"]]
|
result `shouldBe` [["_id" =: _id, "name" =: "Yankees", "league" =: "American"]]
|
||||||
, [])]
|
_ <- db $ updateMany "team" [([ "_id" =: _id]
|
||||||
updatedResult <- db $ rest =<< find (select [] "team")
|
, ["$set" =: ["league" =: "European"]]
|
||||||
updatedResult `shouldBe` [["_id" =: _id, "name" =: "Yankees", "league" =: "European"]]
|
, [])]
|
||||||
|
updatedResult <- db $ rest =<< find (select [] "team")
|
||||||
|
updatedResult `shouldBe` [["_id" =: _id, "name" =: "Yankees", "league" =: "European"]]
|
||||||
it "upserts value" $ do
|
it "upserts value" $ do
|
||||||
c <- db $ count (select [] "team")
|
wireVersion <- getWireVersion
|
||||||
c `shouldBe` 0
|
when (wireVersion > 1) $ do
|
||||||
_ <- db $ updateMany "team" [( []
|
c <- db $ count (select [] "team")
|
||||||
, ["name" =: "Giants", "league" =: "MLB"]
|
c `shouldBe` 0
|
||||||
, [Upsert]
|
_ <- db $ updateMany "team" [( []
|
||||||
)]
|
, ["name" =: "Giants", "league" =: "MLB"]
|
||||||
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
, [Upsert]
|
||||||
map L.sort updatedResult `shouldBe` [["league" =: "MLB", "name" =: "Giants"]]
|
)]
|
||||||
|
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
||||||
|
map L.sort updatedResult `shouldBe` [["league" =: "MLB", "name" =: "Giants"]]
|
||||||
it "updates all documents with Multi enabled" $ do
|
it "updates all documents with Multi enabled" $ do
|
||||||
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "American"]
|
wireVersion <- getWireVersion
|
||||||
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "MiLB"]
|
when (wireVersion > 1) $ do
|
||||||
_ <- db $ updateMany "team" [( ["name" =: "Yankees"]
|
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "American"]
|
||||||
, ["$set" =: ["league" =: "MLB"]]
|
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "MiLB"]
|
||||||
, [MultiUpdate]
|
_ <- db $ updateMany "team" [( ["name" =: "Yankees"]
|
||||||
)]
|
, ["$set" =: ["league" =: "MLB"]]
|
||||||
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
, [MultiUpdate]
|
||||||
(L.sort $ map L.sort updatedResult) `shouldBe` [ ["league" =: "MLB", "name" =: "Yankees"]
|
)]
|
||||||
, ["league" =: "MLB", "name" =: "Yankees"]
|
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
||||||
]
|
(L.sort $ map L.sort updatedResult) `shouldBe` [ ["league" =: "MLB", "name" =: "Yankees"]
|
||||||
|
, ["league" =: "MLB", "name" =: "Yankees"]
|
||||||
|
]
|
||||||
it "updates one document when there is no Multi option" $ do
|
it "updates one document when there is no Multi option" $ do
|
||||||
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "American"]
|
wireVersion <- getWireVersion
|
||||||
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "MiLB"]
|
when (wireVersion > 1) $ do
|
||||||
_ <- db $ updateMany "team" [( ["name" =: "Yankees"]
|
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "American"]
|
||||||
, ["$set" =: ["league" =: "MLB"]]
|
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "MiLB"]
|
||||||
, []
|
_ <- db $ updateMany "team" [( ["name" =: "Yankees"]
|
||||||
)]
|
, ["$set" =: ["league" =: "MLB"]]
|
||||||
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
, []
|
||||||
(L.sort $ map L.sort updatedResult) `shouldBe` [ ["league" =: "MLB", "name" =: "Yankees"]
|
)]
|
||||||
, ["league" =: "MiLB", "name" =: "Yankees"]
|
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
||||||
]
|
(L.sort $ map L.sort updatedResult) `shouldBe` [ ["league" =: "MLB", "name" =: "Yankees"]
|
||||||
|
, ["league" =: "MiLB", "name" =: "Yankees"]
|
||||||
|
]
|
||||||
it "can process different updates" $ do
|
it "can process different updates" $ do
|
||||||
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "American"]
|
wireVersion <- getWireVersion
|
||||||
_ <- db $ insert "team" ["name" =: "Giants" , "league" =: "MiLB"]
|
when (wireVersion > 1) $ do
|
||||||
_ <- db $ updateMany "team" [ ( ["name" =: "Yankees"]
|
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "American"]
|
||||||
, ["$set" =: ["league" =: "MiLB"]]
|
_ <- db $ insert "team" ["name" =: "Giants" , "league" =: "MiLB"]
|
||||||
, []
|
_ <- db $ updateMany "team" [ ( ["name" =: "Yankees"]
|
||||||
)
|
, ["$set" =: ["league" =: "MiLB"]]
|
||||||
, ( ["name" =: "Giants"]
|
|
||||||
, ["$set" =: ["league" =: "MLB"]]
|
|
||||||
, []
|
|
||||||
)
|
|
||||||
]
|
|
||||||
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
|
||||||
(L.sort $ map L.sort updatedResult) `shouldBe` [ ["league" =: "MLB" , "name" =: "Giants"]
|
|
||||||
, ["league" =: "MiLB", "name" =: "Yankees"]
|
|
||||||
]
|
|
||||||
it "can process different updates" $ do
|
|
||||||
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "American", "score" =: (Nothing :: Maybe Int)]
|
|
||||||
_ <- db $ insert "team" ["name" =: "Giants" , "league" =: "MiLB", "score" =: (1 :: Int)]
|
|
||||||
updateResult <- (db $ updateMany "team" [ ( ["name" =: "Yankees"]
|
|
||||||
, ["$inc" =: ["score" =: (1 :: Int)]]
|
|
||||||
, []
|
|
||||||
)
|
|
||||||
, ( ["name" =: "Giants"]
|
|
||||||
, ["$inc" =: ["score" =: (2 :: Int)]]
|
|
||||||
, []
|
|
||||||
)
|
|
||||||
])
|
|
||||||
failed updateResult `shouldBe` True
|
|
||||||
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
|
||||||
(L.sort $ map L.sort updatedResult) `shouldBe` [ ["league" =: "American", "name" =: "Yankees", "score" =: (Nothing :: Maybe Int)]
|
|
||||||
, ["league" =: "MiLB" , "name" =: "Giants" , "score" =: (1 :: Int)]
|
|
||||||
]
|
|
||||||
it "can handle big updates" $ do
|
|
||||||
let docs = (flip map) [0..20000] $ \i ->
|
|
||||||
["name" =: (T.pack $ "name " ++ (show i))]
|
|
||||||
ids <- db $ insertAll "bigCollection" docs
|
|
||||||
let updateDocs = (flip map) ids (\i -> ( [ "_id" =: i]
|
|
||||||
, ["$set" =: ["name" =: ("name " ++ (show i))]]
|
|
||||||
, []
|
, []
|
||||||
))
|
)
|
||||||
_ <- db $ updateMany "team" updateDocs
|
, ( ["name" =: "Giants"]
|
||||||
updatedResult <- db $ rest =<< find (select [] "team")
|
, ["$set" =: ["league" =: "MLB"]]
|
||||||
forM_ updatedResult $ \r -> let (i :: ObjectId) = "_id" `at` r
|
, []
|
||||||
in (("name" `at` r) :: String) `shouldBe` ("name" ++ (show i))
|
)
|
||||||
|
]
|
||||||
|
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
||||||
|
(L.sort $ map L.sort updatedResult) `shouldBe` [ ["league" =: "MLB" , "name" =: "Giants"]
|
||||||
|
, ["league" =: "MiLB", "name" =: "Yankees"]
|
||||||
|
]
|
||||||
|
it "can process different updates" $ do
|
||||||
|
wireVersion <- getWireVersion
|
||||||
|
when (wireVersion > 1) $ do
|
||||||
|
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "American", "score" =: (Nothing :: Maybe Int)]
|
||||||
|
_ <- db $ insert "team" ["name" =: "Giants" , "league" =: "MiLB", "score" =: (1 :: Int)]
|
||||||
|
updateResult <- (db $ updateMany "team" [ ( ["name" =: "Yankees"]
|
||||||
|
, ["$inc" =: ["score" =: (1 :: Int)]]
|
||||||
|
, []
|
||||||
|
)
|
||||||
|
, ( ["name" =: "Giants"]
|
||||||
|
, ["$inc" =: ["score" =: (2 :: Int)]]
|
||||||
|
, []
|
||||||
|
)
|
||||||
|
])
|
||||||
|
failed updateResult `shouldBe` True
|
||||||
|
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
||||||
|
(L.sort $ map L.sort updatedResult) `shouldBe` [ ["league" =: "American", "name" =: "Yankees", "score" =: (Nothing :: Maybe Int)]
|
||||||
|
, ["league" =: "MiLB" , "name" =: "Giants" , "score" =: (1 :: Int)]
|
||||||
|
]
|
||||||
|
it "can handle big updates" $ do
|
||||||
|
wireVersion <- getWireVersion
|
||||||
|
when (wireVersion > 1) $ do
|
||||||
|
let docs = (flip map) [0..20000] $ \i ->
|
||||||
|
["name" =: (T.pack $ "name " ++ (show i))]
|
||||||
|
ids <- db $ insertAll "bigCollection" docs
|
||||||
|
let updateDocs = (flip map) ids (\i -> ( [ "_id" =: i]
|
||||||
|
, ["$set" =: ["name" =: ("name " ++ (show i))]]
|
||||||
|
, []
|
||||||
|
))
|
||||||
|
_ <- db $ updateMany "team" updateDocs
|
||||||
|
updatedResult <- db $ rest =<< find (select [] "team")
|
||||||
|
forM_ updatedResult $ \r -> let (i :: ObjectId) = "_id" `at` r
|
||||||
|
in (("name" `at` r) :: String) `shouldBe` ("name" ++ (show i))
|
||||||
|
|
||||||
describe "updateAll" $ do
|
describe "updateAll" $ do
|
||||||
it "can process different updates" $ do
|
it "can process different updates" $ do
|
||||||
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "American", "score" =: (Nothing :: Maybe Int)]
|
wireVersion <- getWireVersion
|
||||||
_ <- db $ insert "team" ["name" =: "Giants" , "league" =: "MiLB", "score" =: (1 :: Int)]
|
when (wireVersion > 1) $ do
|
||||||
updateResult <- (db $ updateAll "team" [ ( ["name" =: "Yankees"]
|
_ <- db $ insert "team" ["name" =: "Yankees", "league" =: "American", "score" =: (Nothing :: Maybe Int)]
|
||||||
, ["$inc" =: ["score" =: (1 :: Int)]]
|
_ <- db $ insert "team" ["name" =: "Giants" , "league" =: "MiLB", "score" =: (1 :: Int)]
|
||||||
, []
|
updateResult <- (db $ updateAll "team" [ ( ["name" =: "Yankees"]
|
||||||
)
|
, ["$inc" =: ["score" =: (1 :: Int)]]
|
||||||
, ( ["name" =: "Giants"]
|
, []
|
||||||
, ["$inc" =: ["score" =: (2 :: Int)]]
|
)
|
||||||
, []
|
, ( ["name" =: "Giants"]
|
||||||
)
|
, ["$inc" =: ["score" =: (2 :: Int)]]
|
||||||
])
|
, []
|
||||||
failed updateResult `shouldBe` True
|
)
|
||||||
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
])
|
||||||
(L.sort $ map L.sort updatedResult) `shouldBe` [ ["league" =: "American", "name" =: "Yankees", "score" =: (Nothing :: Maybe Int)]
|
failed updateResult `shouldBe` True
|
||||||
, ["league" =: "MiLB" , "name" =: "Giants" , "score" =: (3 :: Int)]
|
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
||||||
]
|
(L.sort $ map L.sort updatedResult) `shouldBe` [ ["league" =: "American", "name" =: "Yankees", "score" =: (Nothing :: Maybe Int)]
|
||||||
|
, ["league" =: "MiLB" , "name" =: "Giants" , "score" =: (3 :: Int)]
|
||||||
|
]
|
||||||
|
|
||||||
describe "delete" $ do
|
describe "delete" $ do
|
||||||
it "actually deletes something" $ do
|
it "actually deletes something" $ do
|
||||||
|
@ -336,34 +357,40 @@ spec = around withCleanDatabase $ do
|
||||||
|
|
||||||
describe "deleteMany" $ do
|
describe "deleteMany" $ do
|
||||||
it "actually deletes something" $ do
|
it "actually deletes something" $ do
|
||||||
_ <- db $ insert "team" ["name" =: ("Giants" :: String)]
|
wireVersion <- getWireVersion
|
||||||
_ <- db $ insert "team" ["name" =: ("Yankees" :: String)]
|
when (wireVersion > 1) $ do
|
||||||
_ <- db $ deleteMany "team" [ (["name" =: ("Giants" :: String)], [])
|
_ <- db $ insert "team" ["name" =: ("Giants" :: String)]
|
||||||
, (["name" =: ("Yankees" :: String)], [])
|
_ <- db $ insert "team" ["name" =: ("Yankees" :: String)]
|
||||||
]
|
_ <- db $ deleteMany "team" [ (["name" =: ("Giants" :: String)], [])
|
||||||
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
, (["name" =: ("Yankees" :: String)], [])
|
||||||
length updatedResult `shouldBe` 0
|
]
|
||||||
|
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
||||||
|
length updatedResult `shouldBe` 0
|
||||||
|
|
||||||
describe "deleteAll" $ do
|
describe "deleteAll" $ do
|
||||||
it "actually deletes something" $ do
|
it "actually deletes something" $ do
|
||||||
_ <- db $ insert "team" [ "name" =: ("Giants" :: String)
|
wireVersion <- getWireVersion
|
||||||
, "score" =: (Nothing :: Maybe Int)
|
when (wireVersion > 1) $ do
|
||||||
]
|
_ <- db $ insert "team" [ "name" =: ("Giants" :: String)
|
||||||
_ <- db $ insert "team" [ "name" =: ("Yankees" :: String)
|
, "score" =: (Nothing :: Maybe Int)
|
||||||
, "score" =: (1 :: Int)
|
]
|
||||||
]
|
_ <- db $ insert "team" [ "name" =: ("Yankees" :: String)
|
||||||
_ <- db $ deleteAll "team" [ (["name" =: ("Giants" :: String)], [])
|
, "score" =: (1 :: Int)
|
||||||
, (["name" =: ("Yankees" :: String)], [])
|
]
|
||||||
]
|
_ <- db $ deleteAll "team" [ (["name" =: ("Giants" :: String)], [])
|
||||||
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
, (["name" =: ("Yankees" :: String)], [])
|
||||||
length updatedResult `shouldBe` 0
|
]
|
||||||
|
updatedResult <- db $ rest =<< find ((select [] "team") {project = ["_id" =: (0 :: Int)]})
|
||||||
|
length updatedResult `shouldBe` 0
|
||||||
it "can handle big deletes" $ do
|
it "can handle big deletes" $ do
|
||||||
let docs = (flip map) [0..20000] $ \i ->
|
wireVersion <- getWireVersion
|
||||||
["name" =: (T.pack $ "name " ++ (show i))]
|
when (wireVersion > 1) $ do
|
||||||
_ <- db $ insertAll "bigCollection" docs
|
let docs = (flip map) [0..20000] $ \i ->
|
||||||
_ <- db $ deleteAll "bigCollection" $ map (\d -> (d, [])) docs
|
["name" =: (T.pack $ "name " ++ (show i))]
|
||||||
updatedResult <- db $ rest =<< find ((select [] "bigCollection") {project = ["_id" =: (0 :: Int)]})
|
_ <- db $ insertAll "bigCollection" docs
|
||||||
length updatedResult `shouldBe` 0
|
_ <- db $ deleteAll "bigCollection" $ map (\d -> (d, [])) docs
|
||||||
|
updatedResult <- db $ rest =<< find ((select [] "bigCollection") {project = ["_id" =: (0 :: Int)]})
|
||||||
|
length updatedResult `shouldBe` 0
|
||||||
|
|
||||||
describe "allCollections" $ do
|
describe "allCollections" $ do
|
||||||
it "returns all collections in a database" $ do
|
it "returns all collections in a database" $ do
|
||||||
|
|
Loading…
Reference in a new issue