1
1
mirror of https://github.com/github/semantic.git synced 2024-12-25 16:02:43 +03:00

Merge branch 'ordered-map-but-this-time-working' into split-rendering-of-keyed-nodes

This commit is contained in:
Rob Rix 2015-12-14 17:59:28 -05:00
commit 6180986275
4 changed files with 27 additions and 1 deletions

View File

@ -77,6 +77,7 @@ test-suite semantic-diff-test
type: exitcode-stdio-1.0
hs-source-dirs: test
main-is: Spec.hs
other-modules: OrderedMapSpec
build-depends: base
, containers
, free

View File

@ -39,7 +39,7 @@ empty :: OrderedMap key value
empty = OrderedMap []
union :: Eq key => OrderedMap key value -> OrderedMap key value -> OrderedMap key value
union (OrderedMap a) (OrderedMap b) = OrderedMap $ a ++ filter ((`elem` extant) . fst) b
union (OrderedMap a) (OrderedMap b) = OrderedMap $ a ++ filter (not . (`elem` extant) . fst) b
where extant = fst <$> a
unions :: Eq key => [OrderedMap key value] -> OrderedMap key value

21
test/OrderedMapSpec.hs Normal file
View File

@ -0,0 +1,21 @@
module OrderedMapSpec where
import OrderedMap as Map
import Test.Hspec
spec :: Spec
spec = do
describe "difference" $ do
it "should return those elements of a not in b" $
Map.difference a b `shouldBe` (Map.fromList [ ("a", 1) ])
describe "union" $ do
it "should return those elements in either a or b" $
Map.union a b `shouldBe` (Map.fromList $ ("a", 1) : Map.toList b)
describe "intersectionWith" $ do
it "should return those elements in both a and b, combined with a function" $
Map.intersectionWith (+) a b `shouldBe` (Map.fromList [ ("b", 4), ("c", 6) ])
where a = Map.fromList [ ("a", 1), ("b", 2), ("c", 3) ]
b = Map.fromList [ ("b", 2), ("c", 3), ("d", 4) ]

View File

@ -1,5 +1,7 @@
module Main where
import qualified OrderedMapSpec
import Categorizable
import Diff
import Interpreter
@ -235,6 +237,8 @@ main = hspec $ do
it "should produce ranges offset by its start index" $
rangesAndWordsFrom 100 "a b" `shouldBe` [ (Range 100 101, "a"), (Range 102 103, "b") ]
describe "OrderedMap" OrderedMapSpec.spec
where
rightRowText text = rightRow [ Text text ]
rightRow xs = Row EmptyLine (Line xs)