
Hello Haskellers, http://lpaste.net/119693 ~~~ {-# LANGUAGE TemplateHaskell #-} import Test.Tasty import Test.Tasty.TH import Test.Tasty.QuickCheck main :: IO () main = defaultMain tests tests = $(testGroupGenerator) -- Problem 15 -- -- (**) Replicate the elements of a list a given number of times. -- -- Example: -- -- * (repli '(a b c) 3) -- (A A A B B B C C C) -- -- Example in Haskell: -- -- >>> repli "abc" 3 -- "aaabbbccc" prop_repli xs n = a && b where types = ((xs::[Int]), (n::Int)) ys = repli xs n ys' = groupByN ys n where groupByN [] _ = [] groupByN zs m = take m zs : groupByN (drop m zs) m a = and $ fmap ((==n).length) ys' b = and $ fmap f ys' where f (x:xs) = all (==x) xs repli :: [a] -> Int -> [a] repli [] _ = [] repli (x:xs) n | n <= 1 = (x:xs) | otherwise = repli' x n ++ repli xs n where repli' x' 0 = [] repli' x' n' = x':repli' x' (n'-1) ~~~
prop_repli xs n = a && b
If I set 'n' as ' n>=1', it's ok. But with just n, does not terminate. Any advice would be appreciated. Thanks. -- YCH

On Sat, Jan 31, 2015 at 10:39 PM, YCH
ys' = groupByN ys n where groupByN [] _ = [] groupByN zs m = take m zs : groupByN (drop m zs) m
This groupByN doesn't look like it'll terminate for negative n. So ys' becomes an infinite list. Which causes divergence downstream. -- Kim-Ee

2015. 2. 1. 오전 2:03에 "Kim-Ee Yeoh"
On Sat, Jan 31, 2015 at 10:39 PM, YCH
wrote: ys' = groupByN ys n where groupByN [] _ = [] groupByN zs m = take m zs : groupByN (drop m zs) m
This groupByN doesn't look like it'll terminate for negative n. So ys'
becomes an infinite list. Which causes divergence downstream.
-- Kim-Ee
Thanks, Kim-Ee. Now I can see.
participants (2)
-
Kim-Ee Yeoh
-
YCH