module Test.Data.List.Reverse.StrictSpine where import qualified Data.List.Reverse.StrictSpine as Rev import qualified Data.List.Match as Match import qualified Data.List as List import Data.Tuple.HT (mapFst, mapPair, swap, ) import Test.QuickCheck (Testable, quickCheck, ) import Prelude hiding (takeWhile, dropWhile, span, ) takeWhile :: (Ord a) => (a -> Bool) -> [a] -> Bool takeWhile p xs = Rev.takeWhile p xs == reverse (List.takeWhile p (reverse xs)) dropWhile :: (Ord a) => (a -> Bool) -> [a] -> Bool dropWhile p xs = Rev.dropWhile p xs == reverse (List.dropWhile p (reverse xs)) span :: (Ord a) => (a -> Bool) -> [a] -> Bool span p xs = Rev.span p xs == swap (mapPair (reverse, reverse) (List.span p (reverse xs))) spanTakeDrop :: (Ord a) => (a -> Bool) -> [a] -> Bool spanTakeDrop p xs = Rev.span p xs == (Rev.dropWhile p xs, Rev.takeWhile p xs) takeWhileBottom :: (Ord a) => a -> [a] -> [a] -> Bool takeWhileBottom x xs pad = let ys = Rev.takeWhile (x/=) $ Match.replicate pad undefined ++ x:xs in ys==ys dropWhileBottom :: (Ord a) => a -> [a] -> [a] -> Bool dropWhileBottom x xs pad = let n = length $ Rev.dropWhile (x/=) $ Match.replicate pad undefined ++ x:xs in n==n spanBottom :: (Ord a) => a -> [a] -> [a] -> Bool spanBottom x xs pad = let (n,ys) = mapFst length $ Rev.span (x/=) $ Match.replicate pad undefined ++ x:xs in n==n && ys==ys simple :: (Testable test) => (Float -> [Float] -> test) -> IO () simple = quickCheck tests :: [(String, IO ())] tests = ("takeWhile", simple (\a -> takeWhile (a>=))) : ("dropWhile", simple (\a -> dropWhile (a>=))) : ("span", simple (\a -> span (a>=))) : ("spanTakeDrop", simple (\a -> spanTakeDrop (a>=))) : ("takeWhileBottom", simple takeWhileBottom) : ("dropWhileBottom", simple dropWhileBottom) : ("spanBottom", simple spanBottom) : []