mirror of
https://github.com/github/semantic.git
synced 2024-11-25 02:58:36 +03:00
🔥 qualifications of zip & zipWith.
This commit is contained in:
parent
fa8f9c15b0
commit
379208b3a3
@ -55,8 +55,8 @@ run :: (Eq a, Eq annotation) => Comparable a annotation -> Algorithm a annotatio
|
|||||||
run _ (Pure diff) = Just diff
|
run _ (Pure diff) = Just diff
|
||||||
|
|
||||||
run comparable (Free (Recursive (annotation1 :< a) (annotation2 :< b) f)) = run comparable . f $ recur a b where
|
run comparable (Free (Recursive (annotation1 :< a) (annotation2 :< b) f)) = run comparable . f $ recur a b where
|
||||||
recur (Indexed a') (Indexed b') | length a' == length b' = annotate . Indexed $ Prelude.zipWith (interpret comparable) a' b'
|
recur (Indexed a') (Indexed b') | length a' == length b' = annotate . Indexed $ zipWith (interpret comparable) a' b'
|
||||||
recur (Fixed a') (Fixed b') | length a' == length b' = annotate . Fixed $ Prelude.zipWith (interpret comparable) a' b'
|
recur (Fixed a') (Fixed b') | length a' == length b' = annotate . Fixed $ zipWith (interpret comparable) a' b'
|
||||||
recur (Keyed a') (Keyed b') | Map.keys a' == bKeys = annotate . Keyed . Map.fromList . fmap repack $ bKeys
|
recur (Keyed a') (Keyed b') | Map.keys a' == bKeys = annotate . Keyed . Map.fromList . fmap repack $ bKeys
|
||||||
where
|
where
|
||||||
bKeys = Map.keys b'
|
bKeys = Map.keys b'
|
||||||
|
@ -16,8 +16,8 @@ zipTerms (annotation1 :< a) (annotation2 :< b) = annotate $ zipUnwrap a b
|
|||||||
where
|
where
|
||||||
annotate = fmap (Both (annotation1, annotation2) :<)
|
annotate = fmap (Both (annotation1, annotation2) :<)
|
||||||
zipUnwrap (Leaf _) (Leaf b') = Just $ Leaf b'
|
zipUnwrap (Leaf _) (Leaf b') = Just $ Leaf b'
|
||||||
zipUnwrap (Indexed a') (Indexed b') = Just . Indexed . catMaybes $ Prelude.zipWith zipTerms a' b'
|
zipUnwrap (Indexed a') (Indexed b') = Just . Indexed . catMaybes $ zipWith zipTerms a' b'
|
||||||
zipUnwrap (Fixed a') (Fixed b') = Just . Fixed . catMaybes $ Prelude.zipWith zipTerms a' b'
|
zipUnwrap (Fixed a') (Fixed b') = Just . Fixed . catMaybes $ zipWith zipTerms a' b'
|
||||||
zipUnwrap (Keyed a') (Keyed b') | keys a' == keys b' = Just . Keyed . fromList . catMaybes $ zipUnwrapMaps a' b' <$> keys a'
|
zipUnwrap (Keyed a') (Keyed b') | keys a' == keys b' = Just . Keyed . fromList . catMaybes $ zipUnwrapMaps a' b' <$> keys a'
|
||||||
zipUnwrap _ _ = Nothing
|
zipUnwrap _ _ = Nothing
|
||||||
zipUnwrapMaps a' b' key = (,) key <$> zipTerms (a' ! key) (b' ! key)
|
zipUnwrapMaps a' b' key = (,) key <$> zipTerms (a' ! key) (b' ! key)
|
||||||
|
@ -69,7 +69,7 @@ spec = parallel $ do
|
|||||||
\ a b -> adjoinRows alignRows (pure (Closed [a])) [ b ] `shouldBe` [ pure (Closed [a]), b :: Row Char ]
|
\ a b -> adjoinRows alignRows (pure (Closed [a])) [ b ] `shouldBe` [ pure (Closed [a]), b :: Row Char ]
|
||||||
|
|
||||||
-- it "aligns closed lines" $
|
-- it "aligns closed lines" $
|
||||||
-- foldr (adjoinRows alignRows) [] (Prelude.zipWith both (pureBy (/= '\n') <$> "[ bar ]\nquux") (pureBy (/= '\n') <$> "[\nbar\n]\nquux")) `shouldBe`
|
-- foldr (adjoinRows alignRows) [] (zipWith both (pureBy (/= '\n') <$> "[ bar ]\nquux") (pureBy (/= '\n') <$> "[\nbar\n]\nquux")) `shouldBe`
|
||||||
-- [ both (Closed "[ bar ]\n") (Closed "[\n")
|
-- [ both (Closed "[ bar ]\n") (Closed "[\n")
|
||||||
-- , both (Closed "") (Closed "bar\n")
|
-- , both (Closed "") (Closed "bar\n")
|
||||||
-- , both (Closed "") (Closed "]\n")
|
-- , both (Closed "") (Closed "]\n")
|
||||||
|
@ -66,7 +66,7 @@ examples directory = do
|
|||||||
where
|
where
|
||||||
globFor :: String -> IO [FilePath]
|
globFor :: String -> IO [FilePath]
|
||||||
globFor p = globDir1 (compile p) directory
|
globFor p = globDir1 (compile p) directory
|
||||||
toDict list = Map.fromList ((normalizeName <$> list) `Prelude.zip` list)
|
toDict list = Map.fromList ((normalizeName <$> list) `zip` list)
|
||||||
|
|
||||||
-- | Given a test name like "foo.A.js", return "foo.js".
|
-- | Given a test name like "foo.A.js", return "foo.js".
|
||||||
normalizeName :: FilePath -> FilePath
|
normalizeName :: FilePath -> FilePath
|
||||||
|
Loading…
Reference in New Issue
Block a user