Skip to content
This repository was archived by the owner on Oct 4, 2020. It is now read-only.

Update tests for 0.7 and fix bug in JS code #34

Merged
merged 3 commits into from
Jun 11, 2015
Merged
Show file tree
Hide file tree
Changes from all commits
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
10 changes: 9 additions & 1 deletion gulpfile.js
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
var gulp = require("gulp");
var plumber = require("gulp-plumber");
var purescript = require("gulp-purescript");
var run = require("gulp-run");
var rimraf = require("rimraf");

var sources = [
Expand Down Expand Up @@ -52,4 +53,11 @@ gulp.task("dotpsci", function () {
.pipe(purescript.dotPsci());
});

gulp.task("default", ["make", "docs", "dotpsci"]);
gulp.task("test", ["make"], function() {
return gulp.src(sources.concat(["tests/**/*.purs", "bower_components/purescript-lists/test-src/Data/List.purs"]))
.pipe(plumber())
.pipe(purescript.psc({ main: "Tests", ffi: foreigns }))
.pipe(run("node"));
});

gulp.task("default", ["make", "docs", "dotpsci", "test"]);
1 change: 1 addition & 0 deletions package.json
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
"gulp": "^3.8.11",
"gulp-plumber": "^1.0.0",
"gulp-purescript": "^0.5.0-rc.1",
"gulp-run": "^1.6.8",
"rimraf": "^2.3.3"
}
}
2 changes: 1 addition & 1 deletion src/Data/StrMap.js
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

// module Data.StrMap

exports._copy = (m) {
exports._copy = function(m) {
var r = {};
for (var k in m) {
r[k] = m[k];
Expand Down
134 changes: 67 additions & 67 deletions tests/Data/Map.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,16 @@ module Tests.Data.Map where
import Prelude

import Control.Alt ((<|>))
import Data.Array (groupBy, map, length, nubBy, sortBy)
import Data.List (List(..), groupBy, length, nubBy, sortBy, singleton, toList)
import Data.Foldable (foldl, for_)
import Data.Function (on)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Int (fromNumber)
import Data.Tuple (Tuple(..), fst)
import Debug.Trace
import Control.Monad.Eff.Console (log)
import Test.Data.List
import Test.QuickCheck ((<?>), quickCheck, quickCheck')
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Test.QuickCheck.Gen (Gen(..))
import qualified Data.Map as M

instance arbMap :: (Eq k, Ord k, Arbitrary k, Arbitrary v) => Arbitrary (M.Map k v) where
Expand All @@ -32,33 +33,32 @@ instance showSmallKey :: Show SmallKey where
show J = "J"

instance eqSmallKey :: Eq SmallKey where
(==) A A = true
(==) B B = true
(==) C C = true
(==) D D = true
(==) E E = true
(==) F F = true
(==) G G = true
(==) H H = true
(==) I I = true
(==) J J = true
(==) _ _ = false
(/=) x y = not (x == y)

smallKeyToNumber :: SmallKey -> Number
smallKeyToNumber A = 0
smallKeyToNumber B = 1
smallKeyToNumber C = 2
smallKeyToNumber D = 3
smallKeyToNumber E = 4
smallKeyToNumber F = 5
smallKeyToNumber G = 6
smallKeyToNumber H = 7
smallKeyToNumber I = 8
smallKeyToNumber J = 9
eq A A = true
eq B B = true
eq C C = true
eq D D = true
eq E E = true
eq F F = true
eq G G = true
eq H H = true
eq I I = true
eq J J = true
eq _ _ = false

smallKeyToInt :: SmallKey -> Int
smallKeyToInt A = 0
smallKeyToInt B = 1
smallKeyToInt C = 2
smallKeyToInt D = 3
smallKeyToInt E = 4
smallKeyToInt F = 5
smallKeyToInt G = 6
smallKeyToInt H = 7
smallKeyToInt I = 8
smallKeyToInt J = 9

instance ordSmallKey :: Ord SmallKey where
compare = compare `on` smallKeyToNumber
compare = compare `on` smallKeyToInt

instance arbSmallKey :: Arbitrary SmallKey where
arbitrary = do
Expand Down Expand Up @@ -93,7 +93,7 @@ instance arbInstruction :: (Arbitrary k, Arbitrary v) => Arbitrary (Instruction
k <- arbitrary
return (Delete k)

runInstructions :: forall k v. (Ord k) => [Instruction k v] -> M.Map k v -> M.Map k v
runInstructions :: forall k v. (Ord k) => List (Instruction k v) -> M.Map k v -> M.Map k v
runInstructions instrs t0 = foldl step t0 instrs
where
step tree (Insert k v) = M.insert k v tree
Expand All @@ -102,98 +102,98 @@ runInstructions instrs t0 = foldl step t0 instrs
smallKey :: SmallKey -> SmallKey
smallKey k = k

number :: Number -> Number
number :: Int -> Int
number n = n

mapTests = do

-- Data.Map

trace "Test inserting into empty tree"
log "Test inserting into empty tree"
quickCheck $ \k v -> M.lookup (smallKey k) (M.insert k v M.empty) == Just (number v)
<?> ("k: " ++ show k ++ ", v: " ++ show v)

trace "Test delete after inserting"
log "Test delete after inserting"
quickCheck $ \k v -> M.isEmpty (M.delete (smallKey k) (M.insert k (number v) M.empty))
<?> ("k: " ++ show k ++ ", v: " ++ show v)

trace "Insert two, lookup first"
log "Insert two, lookup first"
quickCheck $ \k1 v1 k2 v2 -> k1 == k2 || M.lookup k1 (M.insert (smallKey k2) (number v2) (M.insert (smallKey k1) (number v1) M.empty)) == Just v1
<?> ("k1: " ++ show k1 ++ ", v1: " ++ show v1 ++ ", k2: " ++ show k2 ++ ", v2: " ++ show v2)

trace "Insert two, lookup second"
log "Insert two, lookup second"
quickCheck $ \k1 v1 k2 v2 -> M.lookup k2 (M.insert (smallKey k2) (number v2) (M.insert (smallKey k1) (number v1) M.empty)) == Just v2
<?> ("k1: " ++ show k1 ++ ", v1: " ++ show v1 ++ ", k2: " ++ show k2 ++ ", v2: " ++ show v2)

trace "Insert two, delete one"
log "Insert two, delete one"
quickCheck $ \k1 v1 k2 v2 -> k1 == k2 || M.lookup k2 (M.delete k1 (M.insert (smallKey k2) (number v2) (M.insert (smallKey k1) (number v1) M.empty))) == Just v2
<?> ("k1: " ++ show k1 ++ ", v1: " ++ show v1 ++ ", k2: " ++ show k2 ++ ", v2: " ++ show v2)

trace "Check balance property"
quickCheck' (fromNumber 5000) $ \instrs ->
log "Check balance property"
quickCheck' 5000 $ \instrs ->
let
tree :: M.Map SmallKey Number
tree :: M.Map SmallKey Int
tree = runInstructions instrs M.empty
in M.checkValid tree <?> ("Map not balanced:\n " ++ show tree ++ "\nGenerated by:\n " ++ show instrs)

trace "Lookup from empty"
quickCheck $ \k -> M.lookup k (M.empty :: M.Map SmallKey Number) == Nothing
log "Lookup from empty"
quickCheck $ \k -> M.lookup k (M.empty :: M.Map SmallKey Int) == Nothing

trace "Lookup from singleton"
quickCheck $ \k v -> M.lookup (k :: SmallKey) (M.singleton k (v :: Number)) == Just v
log "Lookup from singleton"
quickCheck $ \k v -> M.lookup (k :: SmallKey) (M.singleton k (v :: Int)) == Just v

trace "Random lookup"
quickCheck' (fromNumber 5000) $ \instrs k v ->
log "Random lookup"
quickCheck' 5000 $ \instrs k v ->
let
tree :: M.Map SmallKey Number
tree :: M.Map SmallKey Int
tree = M.insert k v (runInstructions instrs M.empty)
in M.lookup k tree == Just v <?> ("instrs:\n " ++ show instrs ++ "\nk:\n " ++ show k ++ "\nv:\n " ++ show v)

trace "Singleton to list"
quickCheck $ \k v -> M.toList (M.singleton k v :: M.Map SmallKey Number) == [Tuple k v]
log "Singleton to list"
quickCheck $ \k v -> M.toList (M.singleton k v :: M.Map SmallKey Int) == singleton (Tuple k v)

trace "toList . fromList = id"
log "toList . fromList = id"
quickCheck $ \arr -> let f x = M.toList (M.fromList x)
in f (f arr) == f (arr :: [Tuple SmallKey Number]) <?> show arr
in f (f arr) == f (arr :: List (Tuple SmallKey Int)) <?> show arr

trace "fromList . toList = id"
log "fromList . toList = id"
quickCheck $ \m -> let f m = M.fromList (M.toList m) in
M.toList (f m) == M.toList (m :: M.Map SmallKey Number) <?> show m
M.toList (f m) == M.toList (m :: M.Map SmallKey Int) <?> show m

trace "fromListWith const = fromList"
log "fromListWith const = fromList"
quickCheck $ \arr -> M.fromListWith const arr ==
M.fromList (arr :: [Tuple SmallKey Number]) <?> show arr
M.fromList (arr :: List (Tuple SmallKey Int)) <?> show arr

trace "fromListWith (<>) = fromList . collapse with (<>) . group on fst"
log "fromListWith (<>) = fromList . collapse with (<>) . group on fst"
quickCheck $ \arr ->
let combine (Tuple s a) (Tuple t b) = (Tuple s $ b <> a)
foldl1 g (x : xs) = foldl g x xs
foldl1 g (Cons x xs) = foldl g x xs
f = M.fromList <<< (<$>) (foldl1 combine) <<<
groupBy ((==) `on` fst) <<< sortBy (compare `on` fst) in
M.fromListWith (<>) arr == f (arr :: [Tuple String String]) <?> show arr
M.fromListWith (<>) arr == f (arr :: List (Tuple String String)) <?> show arr

trace "Lookup from union"
log "Lookup from union"
quickCheck $ \m1 m2 k -> M.lookup (smallKey k) (M.union m1 m2) == (case M.lookup k m1 of
Nothing -> M.lookup k m2
Just v -> Just (number v)) <?> ("m1: " ++ show m1 ++ ", m2: " ++ show m2 ++ ", k: " ++ show k ++ ", v1: " ++ show (M.lookup k m1) ++ ", v2: " ++ show (M.lookup k m2) ++ ", union: " ++ show (M.union m1 m2))

trace "Union is idempotent"
quickCheck $ \m1 m2 -> (m1 `M.union` m2) == ((m1 `M.union` m2) `M.union` (m2 :: M.Map SmallKey Number))
log "Union is idempotent"
quickCheck $ \m1 m2 -> (m1 `M.union` m2) == ((m1 `M.union` m2) `M.union` (m2 :: M.Map SmallKey Int))

trace "Union prefers left"
quickCheck $ \m1 m2 k -> M.lookup k (M.union m1 (m2 :: M.Map SmallKey Number)) == (M.lookup k m1 <|> M.lookup k m2)
log "Union prefers left"
quickCheck $ \m1 m2 k -> M.lookup k (M.union m1 (m2 :: M.Map SmallKey Int)) == (M.lookup k m1 <|> M.lookup k m2)

trace "unionWith"
log "unionWith"
for_ [Tuple (+) 0, Tuple (*) 1] $ \(Tuple op ident) ->
quickCheck $ \m1 m2 k ->
let u = M.unionWith op m1 m2 :: M.Map SmallKey Number
let u = M.unionWith op m1 m2 :: M.Map SmallKey Int
in case M.lookup k u of
Nothing -> not (M.member k m1 || M.member k m2)
Just v -> v == op (fromMaybe ident (M.lookup k m1)) (fromMaybe ident (M.lookup k m2))

trace "unionWith argument order"
log "unionWith argument order"
quickCheck $ \m1 m2 k ->
let u = M.unionWith (-) m1 m2 :: M.Map SmallKey Number
let u = M.unionWith (-) m1 m2 :: M.Map SmallKey Int
in1 = M.member k m1
v1 = M.lookup k m1
in2 = M.member k m2
Expand All @@ -204,7 +204,7 @@ mapTests = do
Just v -> Just v == v2
Nothing -> not (in1 || in2)

trace "size"
log "size"
quickCheck $ \xs ->
let xs' = nubBy ((==) `on` fst) xs
in M.size (M.fromList xs') == length (xs' :: [Tuple SmallKey Number])
in M.size (M.fromList xs') == length (xs' :: List (Tuple SmallKey Int))
Loading