Skip to content
This repository was archived by the owner on Jun 10, 2021. It is now read-only.
Merged
Show file tree
Hide file tree
Changes from 1 commit
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
21 changes: 13 additions & 8 deletions bower.json
Original file line number Diff line number Diff line change
Expand Up @@ -13,13 +13,14 @@
"tests"
],
"dependencies": {
"purescript-aff": "^1.0.0",
"purescript-argonaut": "^1.0.0",
"purescript-datetime": "^1.0.0",
"purescript-foldable-traversable": "^1.0.0",
"purescript-foreign": "^1.0.0",
"purescript-string-parsers": "^1.0.1",
"purescript-uri": "^1.0.0"
"purescript-aff": "^2.0.2",
"purescript-argonaut": "^2.0.0",
"purescript-datetime": "^2.0.0",
"purescript-foldable-traversable": "^2.0.0",
"purescript-foreign": "^3.0.1",
"purescript-string-parsers": "^2.0.0",
"purescript-uri": "^2.0.0",
"purescript-transformers": "^2.1.0"
},
"homepage": "https://github.com/dicefm/purescript-node-mongodb",
"authors": [
Expand All @@ -34,5 +35,9 @@
"mongodb",
"mongo"
],
"license": "MIT"
"license": "MIT",
"devDependencies": {
"purescript-debug": "^2.0.0",
"purescript-assert": "^2.0.0"
}
}
7 changes: 4 additions & 3 deletions examples/Examples/Data/Event.purs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
module Data.Event where

import Prelude
import Data.Argonaut ((~>), (:=), (.?), jsonEmptyObject, printJson)
import Data.Argonaut.Core (Json(), JString(), toString)
import Data.Argonaut.Encode (EncodeJson, encodeJson)
Expand Down Expand Up @@ -29,7 +30,7 @@ instance encodeJsonEvent :: EncodeJson Event where
~> jsonEmptyObject

instance showEvent :: Show Event where
show (Event e) = "Event " ++
"{ name: " ++ show e.name ++
show (Event e) = "Event " <>
"{ name: " <> show e.name <>
"}"

7 changes: 7 additions & 0 deletions examples/Examples/Database/Mongo/Find.js
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
exports.traceAny = function (a) {
return function () {
console.log(a);
return {};
};
};

16 changes: 3 additions & 13 deletions examples/Examples/Database/Mongo/Find.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,24 +10,14 @@ import Control.Monad.Eff.Exception

import Data.Argonaut (printJson)
import Data.Argonaut.Core (Json(..))
import Data.Argonaut.Decode (DecodeJson, decodeJson)
-- import Data.Argonaut.Decode (DecodeJson, decodeJson)
Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Delete this line pls.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Since these examples are broken and I've basically converted all the examples into test cases, do you think we still need them?

We could just add a link to Readme.MD, saying "please check out the tests for more examples?"

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah, I think that's a good idea!

import Data.Either
import Data.Event
import Data.Maybe
import Data.String.Regex
import Data.URI

import Debug.Trace

foreign import traceAny
"""
function traceAny(a){
return function () {
console.log(a);
return {};
};
}
""" :: forall e a. a -> Eff (trace :: Trace | e) Unit
foreign import traceAny :: forall e a. a -> Eff (trace :: Trace | e) Unit

uri :: String
uri = "mongodb://127.0.0.1/events"
Expand All @@ -39,6 +29,6 @@ main = launchAff $ do
cur <- find [ "name" := "Wow!" ] [ "name" := 1 ] col
res <- collect cur

liftEff $ traceAny (res :: [Event])
liftEff $ traceAny (res :: Array Event)

close database
4 changes: 2 additions & 2 deletions src/Database/Mongo/Bson/BsonValue.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,8 @@ module Database.Mongo.Bson.BsonValue
) where

import Data.Argonaut.Core (Json())
import Data.String.Regex
import Data.Tuple
import Data.String.Regex (Regex)
import Data.Tuple (Tuple(..))

type Field = Tuple String BsonValue

Expand Down
8 changes: 4 additions & 4 deletions src/Database/Mongo/Mongo.purs
Original file line number Diff line number Diff line change
Expand Up @@ -17,23 +17,23 @@ module Database.Mongo.Mongo
, updateMany, updateMany'
) where

import Prelude
import Prelude (class Show, Unit, show, ($), (<<<))
import Control.Monad.Aff (Aff(), makeAff', Canceler(), nonCanceler)
import Control.Monad.Eff (Eff())
import Control.Monad.Eff.Exception (Error(), error)

import Data.Argonaut.Core (Json())
import Data.Argonaut.Encode (class EncodeJson, encodeJson)
import Data.Argonaut.Decode (class DecodeJson, decodeJson)
import Data.Either
import Data.Either (Either(..))
import Data.Function.Uncurried (Fn3(), runFn3, Fn4(), runFn4, Fn5(), runFn5, Fn6(), runFn6, Fn7(), runFn7, Fn8(), runFn8)

import Database.Mongo.Options (InsertOptions(), insertOptions, UpdateOptions(), updateOptions)
import Database.Mongo.Results (WriteResult())
import Database.Mongo.Bson.BsonValue (Document(), printBson)
import Data.URI
import Data.URI (printURIRef, runParseURIRef)

import Text.Parsing.StringParser
import Text.Parsing.StringParser (ParseError)

-- | The effect type for DB request made with Mongo
foreign import data DB :: !
Expand Down
5 changes: 2 additions & 3 deletions src/Database/Mongo/Options.purs
Original file line number Diff line number Diff line change
Expand Up @@ -6,13 +6,12 @@ module Database.Mongo.Options
, defaultUpdateOptions, updateOptions
) where

import Prelude
import Prelude (pure, bind, ($))
import Data.Argonaut ((~>), (:=), (.?), jsonEmptyObject)
import Data.Argonaut.Core (Json())
import Data.Argonaut.Encode (class EncodeJson, encodeJson)
import Data.Argonaut.Decode (class DecodeJson, decodeJson)
import Data.Either
import Data.Maybe
import Data.Maybe (Maybe(..))

-- | The type of WriteConcern
type WriteConcern = Number
Expand Down
25 changes: 17 additions & 8 deletions src/Database/Mongo/Results.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,12 +2,12 @@ module Database.Mongo.Results
( WriteResult()
) where

import Prelude
import Data.Argonaut ((.?), jsonEmptyObject)
import Prelude (pure, bind, ($))
import Data.Argonaut ((.?), (:=), (~>), jsonEmptyObject)
import Data.Argonaut.Encode (class EncodeJson)
import Data.Argonaut.Decode (class DecodeJson, decodeJson)
import Data.Either
import Data.Maybe
import Data.Either (Either(..))
import Data.Maybe (Maybe(..), fromMaybe)

newtype WriteResult = WriteResult
{ success :: Boolean
Expand All @@ -33,14 +33,23 @@ instance decodeJsonWriteResult :: DecodeJson WriteResult where
}

instance encodeJsonWriteResult :: EncodeJson WriteResult where
encodeJson (WriteResult w) = jsonEmptyObject
encodeJson (WriteResult w)
= "ok" := boolToJsNumber w.success
~> "n" := w.total
~> "nInserted" := fromMaybe 0.0 w.inserted
~> "nModified" := fromMaybe 0.0 w.modified
Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

👍 Awesome, I noticed this was broken as well.

Copy link
Contributor Author

@zhangchiqing zhangchiqing Jan 10, 2017

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Thanks :)

BTW, I have a question: I used 0.0 here instead of 0 because WriteResult takes Maybe Number, and 0 is a Int not a Number. But I don't understand why I can't create a Number by (0 :: Number), it doesn't typecheck. That's why I used 0.0. The same trick I used here

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think that's purescript works.

~> jsonEmptyObject

boolToJsNumber :: Boolean -> Int
boolToJsNumber false = 0
boolToJsNumber true = 1

-- node mongodb module sends back `1` to mean `true`, this is why we need types
-- as Javascript is abused!
jsNumberToBool :: Either String Int -> Boolean
jsNumberToBool :: Int -> Boolean
jsNumberToBool e = case e of
Left _ -> false
Right x -> if x == 1 then true else false
1 -> true
_ -> false

extract :: Either String Number -> Maybe Number
extract e = case e of
Expand Down
32 changes: 32 additions & 0 deletions test/Data/Event.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
module Test.Data.Event where

import Prelude
import Data.Argonaut (jsonEmptyObject, (~>), (:=), (.?))
import Data.Argonaut.Encode.Class (class EncodeJson)
import Data.Argonaut.Decode (decodeJson)
import Data.Argonaut.Decode.Class (class DecodeJson)
import Data.Maybe (Maybe)

newtype Event = Event
{ name :: Maybe String
}

instance decodeJsonEvent :: DecodeJson Event where
decodeJson json = do
obj <- decodeJson json
name <- obj .? "name"
pure $ Event
{ name : name
}

instance encodeJsonEvent :: EncodeJson Event where
encodeJson (Event e)
= "name" := e.name
~> jsonEmptyObject

instance showEvent :: Show Event where
show (Event e) = "Event " <>
"{ name: " <> show e.name <>
"}"


25 changes: 25 additions & 0 deletions test/Database/Mongo/Find.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
module Test.Database.Mongo.Find where

import Prelude (Unit, bind, (>), ($))
import Data.Array (length)
import Data.Maybe (Maybe(..))
import Database.Mongo.Bson.BsonValue ((:=))
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (log)
import Test.Data.Event (Event(..))
import Test.Assert (assert)
import Database.Mongo.Mongo (Database, collect, find, collection)
import Test.Type (Test)

evt :: Event
evt = Event
{ name : Just "Wow"
}

main :: Database -> Test Unit
main database = do
liftEff $ log "should find"
col <- collection "events" database
cur <- find [ "name" := "Wow" ] [ "name" := 1.0 ] col
res <- collect cur
liftEff $ assert $ length (res :: Array Event) > 0
32 changes: 32 additions & 0 deletions test/Database/Mongo/Insert.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
module Test.Database.Mongo.Insert where

import Prelude (Unit, bind, ($), (==), (<<<))
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple)
import Data.StrMap (fromFoldable)
import Data.Argonaut (fromObject, (:=))
import Data.Argonaut.Encode (encodeJson)
import Data.Argonaut.Core (Json)
import Database.Mongo.Mongo (Database, insertOne, collection)
import Database.Mongo.Options (defaultInsertOptions)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (log)

import Test.Data.Event (Event(..))
import Test.Assert
import Test.Type (Test)

evt :: Event
evt = Event
{ name : Just "Wow"
}

obj :: Array (Tuple String Json) -> Json
obj = fromObject <<< fromFoldable

main :: Database -> Test Unit
main database = do
liftEff $ log "should insert"
col <- collection "events" database
res <- insertOne evt defaultInsertOptions col
liftEff $ assert $ (obj [ "ok" := 1, "n" := 1, "nInserted" := 0, "nModified" := 0]) == (encodeJson res)
32 changes: 32 additions & 0 deletions test/Database/Mongo/Update.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
module Test.Database.Mongo.Update where

import Prelude (Unit, bind, (==), ($), (<<<))
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple)
import Data.StrMap (fromFoldable)
import Data.Argonaut as A
import Data.Argonaut.Core (Json)
import Data.Argonaut.Encode (encodeJson)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (log)
import Test.Data.Event (Event(..))
import Test.Assert (assert)
import Database.Mongo.Mongo (Database, updateOne, collection)
import Database.Mongo.Bson.BsonValue as B
import Database.Mongo.Options
import Test.Type (Test)

evt :: Event
evt = Event
{ name : Just "Wow"
}

obj :: Array (Tuple String Json) -> Json
obj = A.fromObject <<< fromFoldable

main :: Database -> Test Unit
main database = do
liftEff $ log "should update"
col <- collection "events" database
res <- updateOne ["name" B.:= "Wow"] ["name" B.:= "lol"] defaultUpdateOptions col
liftEff $ assert $ (obj [ "ok" A.:= 1, "n" A.:= 1, "nModified" A.:= 1, "nInserted" A.:= 0]) == (encodeJson res)
Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Didn't know you could do that with infixed symbols.

Copy link
Contributor Author

@zhangchiqing zhangchiqing Jan 10, 2017

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I don't like this actually.

res here is a WriteResult, to verify it, It's better to construct another WriteResult then compare. But I can't take this approach, because the constructor of WriteResult is not exported.

That's why I used this workaround here which will encode the WriteResult into Json, then create another Json to compare. I don't like it because it's testing two functions together: insertOne + encodeJson.

What do you think? Is there better pattern for asserting the result?

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Probably is, but let's leave it for now.

43 changes: 41 additions & 2 deletions test/Main.purs
Original file line number Diff line number Diff line change
@@ -1,5 +1,44 @@
module Test.Main where

import Control.Monad.Eff.Console
import Prelude
import Data.Either (Either(..))
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (log) as Eff
import Control.Monad.Eff.Exception (EXCEPTION, Error)
import Control.Monad.Aff (Aff, launchAff, attempt)
import Control.Monad.Aff.Console (CONSOLE, log, logShow)
import Database.Mongo.Mongo (DB, Database, close, connect)
import Test.Database.Mongo.Insert as Insert
import Test.Database.Mongo.Find as Find
import Test.Database.Mongo.Update as Update
import Test.Assert (ASSERT)
import Test.Type (Test)

main = log "Write some tests."
connectDB :: forall e. String -> Aff ( db :: DB | e) (Either Error Database)
connectDB dbUri = attempt $ connect dbUri

testInsert :: Database -> Test Unit
testInsert = Insert.main

testFind :: Database -> Test Unit
testFind = Find.main

testUpdate :: Database -> Test Unit
testUpdate = Update.main

uri :: String
uri = "mongodb://127.0.0.1:27017/purescript-node-mongodb-test"

main :: Eff (console :: CONSOLE, db :: DB, err :: EXCEPTION, assert :: ASSERT) Unit
main = do
Eff.log "Testing purescript-node-mongodb"
void $ launchAff do
log "connecting db"
eitherDatabase <- connectDB uri
case eitherDatabase of
Left error -> logShow error
Right database -> do
testInsert database
testFind database
testUpdate database
close database
8 changes: 8 additions & 0 deletions test/Type.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
module Test.Type where

import Control.Monad.Aff (Aff)
import Control.Monad.Aff.Console (CONSOLE)
import Database.Mongo.Mongo (DB)
import Test.Assert (ASSERT)

type Test a = forall e. Aff (console :: CONSOLE, db :: DB, assert :: ASSERT | e) a