module Test.Data.ListMatch where import qualified Data.List.Match.Private as Match import qualified Data.List as List import Test.Utility (equalLists, ) import Test.QuickCheck (Testable, quickCheck, ) import Prelude hiding (iterate, take, drop, splitAt, ) laxTail :: (Eq a) => [a] -> Bool laxTail xs = Match.laxTail xs == Match.laxTail0 xs take :: (Eq a) => [b] -> [a] -> Bool take xs ys = Match.take xs ys == List.take (length xs) ys drop :: (Eq a) => [b] -> [a] -> Bool drop xs ys = Match.drop xs ys == List.drop (length xs) ys dropAlt :: (Eq a) => [b] -> [a] -> Bool dropAlt xs ys = equalLists $ Match.drop xs ys : Match.drop0 xs ys : Match.drop1 xs ys : Match.drop2 xs ys : Match.dropRec xs ys : [] takeDrop :: (Eq a) => [b] -> [a] -> Bool takeDrop xs ys = Match.take xs ys ++ Match.drop xs ys == ys splitAt :: (Eq a) => [b] -> [a] -> Bool splitAt xs ys = (Match.take xs ys, Match.drop xs ys) == Match.splitAt xs ys compareLength :: [a] -> [b] -> Bool compareLength xs ys = Match.compareLength xs ys == Match.compareLength0 xs ys && Match.compareLength xs ys == Match.compareLength1 xs ys test1 :: Testable test => ([Int] -> test) -> IO () test1 = quickCheck test2 :: Testable test => ([Int] -> [Integer] -> test) -> IO () test2 = quickCheck tests :: [(String, IO ())] tests = ("laxTail", test1 laxTail) : ("take", test2 take) : ("drop", test2 drop) : ("dropAlt", test2 dropAlt) : ("takeDrop", test2 takeDrop) : ("splitAt", test2 splitAt) : ("compareLength", test2 compareLength) : []