Skip to content
This repository has been archived by the owner on Jun 15, 2023. It is now read-only.

Commit

Permalink
Merge pull request #47 from garyb/bump
Browse files Browse the repository at this point in the history
Update dependencies
  • Loading branch information
garyb authored Mar 18, 2019
2 parents 9095d45 + 1cd819e commit f5e3c78
Show file tree
Hide file tree
Showing 7 changed files with 91 additions and 48 deletions.
12 changes: 6 additions & 6 deletions bower.json
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,13 @@
"dependencies": {
"purescript-prelude": "^4.0.1",
"purescript-matryoshka": "^0.4.0",
"purescript-pathy": "^6.0.0",
"purescript-profunctor-lenses": "^4.0.0",
"purescript-ejson": "^11.0.0"
"purescript-pathy": "^7.0.0",
"purescript-profunctor-lenses": "^6.1.0",
"purescript-ejson": "^12.0.0"
},
"devDependencies": {
"purescript-quickcheck": "^5.0.0",
"purescript-test-unit": "^14.0.0",
"purescript-argonaut": "^4.0.1"
"purescript-quickcheck": "^6.1.0",
"purescript-argonaut": "^6.0.0",
"purescript-assert": "^4.1.0"
}
}
14 changes: 6 additions & 8 deletions test/src/Argonaut.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
-- | Having an array of `Json`s construct a list of Sql² projections
module Test.Argonaut where

import Prelude
import Test.Prelude

import Data.Argonaut (JCursor(..), jsonParser)
import Data.Argonaut as JS
Expand All @@ -19,8 +19,6 @@ import Matryoshka (ana, elgotPara, Coalgebra, ElgotAlgebra)
import Partial.Unsafe (unsafePartial)
import SqlSquared as S
import SqlSquared.Utils ((×), (∘), (⋙))
import Test.Unit (suite, test, TestSuite)
import Test.Unit.Assert as Assert

data UnfoldableJC = JC JCursor | S String | I Int

Expand Down Expand Up @@ -65,7 +63,7 @@ jarray =
, """{"foo": true}"""
, """[12, null]"""
]
testSuite TestSuite
testSuite Test
testSuite =
suite "tests for argonaut example" do
test "interpretation works"
Expand All @@ -79,7 +77,7 @@ testSuite =
: (JField "foo" $ JField "bar" $ JField "baz" $ JCursorTop)
: L.Nil
in
Assert.equal expected $ map (S.print ∘ jcursorToSql) js
assertEqual { expected, actual: map (S.print ∘ jcursorToSql) js }
test "extraction of fields works"
let
actualFields =
Expand All @@ -95,7 +93,7 @@ testSuite =
: "*.bar.baz"
: L.Nil
in
Assert.equal expectedFields actualFields
assertEqual { expected: expectedFields, actual: actualFields }
test "allParents extracted"
let
field =
Expand All @@ -115,7 +113,7 @@ testSuite =
: "*.foo.bar[0].baz[1]"
: L.Nil
in
Assert.equal expected $ Set.fromFoldable $ map S.print $ allParents field
assertEqual { expected, actual: Set.fromFoldable $ map S.print $ allParents field }
test "allFields works"
let
actualFields = Set.fromFoldable $ map S.print $ allFields jarray
Expand All @@ -131,4 +129,4 @@ testSuite =
: "*.bar"
: L.Nil
in
Assert.equal expectedFields actualFields
assertEqual { expected: expectedFields, actual: actualFields }
10 changes: 4 additions & 6 deletions test/src/Constructors.purs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Test.Constructors where

import Prelude
import Test.Prelude

import Data.Either as E
import Data.Lens ((.~), (<>~), (?~))
Expand All @@ -11,8 +11,6 @@ import Data.Symbol (SProxy(..))
import Pathy as Pt
import SqlSquared as S
import SqlSquared.Utils ((×), (∘))
import Test.Unit (suite, test, TestSuite)
import Test.Unit.Assert as Assert

selectQuery S.Sql
selectQuery =
Expand Down Expand Up @@ -66,10 +64,10 @@ expectedSqlString ∷ String
expectedSqlString =
"SELECT DISTINCT foo AS field, bar.baz.* FROM `/mongo/testDb/patients` WHERE quux = 12.0 GROUP BY zzz HAVING ooo > 2 ORDER BY zzz ASC"

testSuite TestSuite
testSuite Test
testSuite = do
suite "tests for sql constructors" do
test "constructing select query with multiple arguments"
$ Assert.equal expectedSqlString $ S.print selectQuery
$ assertEqual { actual: S.print selectQuery, expected: expectedSqlString }
test "building select query with lenses"
$ Assert.equal expectedSqlString $ S.print buildSelectQuery
$ assertEqual { actual: S.print buildSelectQuery, expected: expectedSqlString }
3 changes: 1 addition & 2 deletions test/src/Main.purs
Original file line number Diff line number Diff line change
@@ -1,9 +1,8 @@
module Test.Main where

import Prelude
import Test.Prelude

import Effect (Effect)
import Test.Unit.Main (runTest)
import Test.Constructors as Constructors
import Test.Argonaut as Argonaut
import Test.Gen as Gen
Expand Down
38 changes: 18 additions & 20 deletions test/src/Parse.purs
Original file line number Diff line number Diff line change
@@ -1,63 +1,61 @@
module Test.Parse where

import Prelude
import Test.Prelude

import Data.Either as E
import SqlSquared (parseQuery, printQuery, SqlQuery)
import SqlSquared.Parser (prettyParse)
import Test.Queries as Q
import Test.Unit (suite, test, TestSuite)
import Test.Unit.Assert as Assert

parseSucc String TestSuite
parseSucc String Test
parseSucc s =
test "parse/success"
case prettyParse parseQuery s of
E.Left err → Assert.assert ("\n" <> err) false
E.Left err → assert ("\n" <> err) false
E.Right (sql SqlQuery) →
case prettyParse parseQuery (printQuery sql) of
E.Left err →
Assert.assert
assert
("Failed to print and reparse.\n\n" <>
" Original: " <> s <> "\n\n" <>
" Printed: " <> printQuery sql <> "\n\n" <> err) false
E.Right (sql' SqlQuery)
| sql' /= sql →
Assert.assert
assert
("Failed to parse to an equivalent AST.\n\n" <>
" Original: " <> s <> "\n\n" <>
" Parsed: " <> printQuery sql <> "\n\n" <>
" Printed: " <> printQuery sql') false
| otherwise →
Assert.assert "OK!" true
assert "OK!" true

parseFail String TestSuite
parseFail String Test
parseFail s =
test "parse/fail"
case parseQuery s of
E.Left err → pure unit
E.Right (sql SqlQuery) → Assert.assert s false
E.Right (sql SqlQuery) → assert s false

parseFailWith String String TestSuite
parseFailWith String String Test
parseFailWith s err =
test "parse/failWith"
case parseQuery s of
E.Left err' →
if show err' == err
then pure unit
else Assert.assert
else assert
("expected query:" <> s <>
"\n\n to fail input error: " <> err <>
"\n\n but instead fot error: " <> show err')
false
E.Right (sql SqlQuery) →
Assert.assert
assert
("expected to fail with:" <> err <>
"\n\tbut input query:" <> s <>
"\n\twas parsed as:" <> printQuery sql)
false

testSuite TestSuite
testSuite Test
testSuite = suite "parsers" do
testSuite1
testSuite2
Expand All @@ -66,7 +64,7 @@ testSuite = suite "parsers" do
testSuite5
testSuite6

testSuite1 TestSuite
testSuite1 Test
testSuite1 = do
parseFailWith """
import `/path/To/Your/File/myModule`; SELECT id("HELLO")
Expand Down Expand Up @@ -253,7 +251,7 @@ testSuite1 = do
select foo from :From
"""

testSuite2 TestSuite
testSuite2 Test
testSuite2 = do
parseSucc """
SELECT state AS `ResultAlias`, COUNT(*) as cnt FROM zips GROUP BY state ORDER BY state
Expand Down Expand Up @@ -399,7 +397,7 @@ testSuite2 = do
select distinct discipline from olympics where event like "%pursuit"
"""

testSuite3 TestSuite
testSuite3 Test
testSuite3 = do
parseSucc """
select count(*) as cnt from zips where state in ("AZ", "CO")
Expand Down Expand Up @@ -593,7 +591,7 @@ testSuite3 = do
select city, state, sum(pop) as total from zips group by city, state order by sum(pop) desc limit 10
"""

testSuite4 TestSuite
testSuite4 Test
testSuite4 = do
parseSucc """
select city, pop from zips where pop > 90000 order by city, pop desc
Expand Down Expand Up @@ -751,7 +749,7 @@ testSuite4 = do
select city, loc[0] as lat from largeZips
"""

testSuite5 TestSuite
testSuite5 Test
testSuite5 = do
parseSucc """
select committer.login, count(*) from slamengine_commits
Expand Down Expand Up @@ -933,7 +931,7 @@ testSuite5 = do
select foo from bar union all select baz from quux
"""

testSuite6 TestSuite
testSuite6 Test
testSuite6 = do
parseSucc Q.q1
parseSucc Q.q2
Expand Down
10 changes: 4 additions & 6 deletions test/src/Precedence.purs
Original file line number Diff line number Diff line change
@@ -1,17 +1,15 @@
module Test.Precedence where

import Prelude
import Test.Prelude

import Data.Either as E
import Matryoshka (project)
import SqlSquared as S
import Test.Unit (suite, test, Test, TestSuite)
import Test.Unit.Assert as Assert

testParsedSql (S.Sql Test) String Test
testParsedSql f s =
case S.prettyParse S.parse s of
E.Left err → Assert.assert ("\n" <> err) false
E.Left err → assert ("\n" <> err) false
E.Right sql → f sql

limitedJoinQuery String
Expand All @@ -23,8 +21,8 @@ expectLimit sql =
(S.Binop { lhs: _, rhs: _, op: S.Limit }) → true
_ → false

testSuite TestSuite
testSuite Test
testSuite = do
suite "tests for parser precedence" do
test "limit should have higher precedence than join condition"
$ testParsedSql (Assert.assert "limit parsed incorrectly" <<< expectLimit) limitedJoinQuery
$ testParsedSql (assert "limit parsed incorrectly" <<< expectLimit) limitedJoinQuery
52 changes: 52 additions & 0 deletions test/src/Prelude.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,52 @@
module Test.Prelude
( module Test.Prelude
, module Prelude
) where

import Prelude

import Control.Monad.Reader (ReaderT, ask, local, runReaderT)
import Data.List as List
import Data.Maybe (Maybe(..))
import Data.Monoid (power)
import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Class.Console (log)
import Effect.Exception (throw)
import Test.Assert as Assert
import Test.QuickCheck (unSeed)
import Test.QuickCheck as QC

type Test = ReaderT Int Effect Unit

runTest :: Test -> Effect Unit
runTest = flip runReaderT 0

suite :: String -> Test -> Test
suite = test

test :: String -> Test -> Test
test name run = do
indent <- ask
log (mkIndent indent <> name)
local (_ + 2) run

mkIndent :: Int -> String
mkIndent = power " "

assert :: String -> Boolean -> Test
assert msg = liftEffect <<< Assert.assert' msg

assertEqual :: forall a. Eq a => Show a => { actual :: a, expected :: a } -> Test
assertEqual = liftEffect <<< Assert.assertEqual

quickCheck :: forall prop. QC.Testable prop => prop -> Test
quickCheck prop = liftEffect do
seed <- QC.randomSeed
let summary = QC.checkResults (QC.quickCheckPure' seed 100 prop)
case List.head summary.failures of
Nothing -> pure unit
Just err -> throw $ "Property failed (seed " <> show (unSeed err.seed) <> ") failed: \n" <> err.message

failure :: String -> Test
failure = liftEffect <<< throw

0 comments on commit f5e3c78

Please sign in to comment.