
Hey all, I'm thoroughly confused by the type error produced by the following: applies a fun returning a tuple of lists to a list of values and then repeatedly applies it to the snd of the result, returning a list of the fst's of successive applications
iterT :: ([a] -> ([a], [a])) -> [a] -> [[a]] iterT f a = let (b, c) = f a in b : iterT f c
like break, but drops the separator
breakDrop :: (a -> Bool) -> [a] -> ([a], [a]) breakDrop p l = (takeWhile (not . p) l, drop 1 $ dropWhile (not . p) l)
like break, but returns a list of lists of values separated by the separator
sep :: (a -> Bool) -> [a] -> [[a]] sep p = takeWhile (/= "") . iterT (breakDrop p)
main = print $ sep (== 1) ""
compling with ghc --make returns this: test.hs:14:45: Couldn't match the rigid variable `a' against `Char' `a' is bound by the type signature for `sep' Expected type: Char -> Bool Inferred type: a -> Bool In the first argument of `breakDrop', namely `p' In the first argument of `iterT', namely `(breakDrop p)' Setting the type signature of sep to (Char -> Bool) -> [Char] -> [[Char]] fixes the problem but I don't get why the signature isn't as general as I think it should be. Something to do with defaulting perhaps? __________________________________________________ Do You Yahoo!? Tired of spam? Yahoo! Mail has the best spam protection around http://mail.yahoo.com

On Monday 20 November 2006 02:44, chris moline wrote:
sep :: (a -> Bool) -> [a] -> [[a]] sep p = takeWhile (/= "") . iterT (breakDrop p)
Setting the type signature of sep to (Char -> Bool) -> [Char] -> [[Char]] fixes the problem but I don't get why the signature isn't as general as I think it should be. Something to do with defaulting perhaps?
The problem is (I believe) 'takeWhile (/= "")'. That's a string, which causes everything to be specialized to Char. You want 'takeWhile (not . null)'. -- Dan

On Monday 20 November 2006 20:44, chris moline wrote:
Hey all, I'm thoroughly confused by the type error produced by the following:
sep :: (a -> Bool) -> [a] -> [[a]] sep p = takeWhile (/= "") . iterT (breakDrop p)
It'll be the "" in (/= ""). Maybe you want to be using (/= []) ? That will work for any type a in the Eq class. Daniel

Never use (/= "") or (/= []), use (not . null), which doesn't have the
Eq constraint.
On 20/11/06, Daniel McAllansmith
On Monday 20 November 2006 20:44, chris moline wrote:
Hey all, I'm thoroughly confused by the type error produced by the following:
sep :: (a -> Bool) -> [a] -> [[a]] sep p = takeWhile (/= "") . iterT (breakDrop p)
It'll be the "" in (/= "").
Maybe you want to be using (/= []) ? That will work for any type a in the Eq class.
Daniel _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Cale Gibbard
-
chris moline
-
Dan Doel
-
Daniel McAllansmith