[Haskell-beginners] type signature error in a where clause

Chaddaï Fouché chaddai.fouche at gmail.com
Sat Nov 24 15:46:55 CET 2012


Basically your "a" in the signature in your where-clause is not the
same as the "a" from the signature of your whole function so it like
you're writing :

mergesort :: (a -> a -> Ordering) -> [a] -> [a]
mergesort cmp xs = mergeAll (map (\x -> [x]) xs)
    where
      mergeAll :: [[b]] -> [b]
      mergeAll [x] = x
      mergeAll xs = mergeAll (mergePairs xs)

      mergePairs :: [[c]] -> [[c]]
      mergePairs (a:b:xs) = merge a b : mergePairs xs
      mergePairs xs = xs

      merge :: [d] -> [d] -> [d]
      merge as@(a:as') bs@(b:bs')
          | cmp a b == GT = b : merge as bs'
          | otherwise     = a : merge as' bs
      merge [] bs = bs
      merge as [] = as

And since you use "cmp" in "merge" and "cmp" only works with the "a"
from your whole function... There is a conflict : you're saying that
merge can work for any type but cmp only work for the type with which
this mergesort was called.


Now  I suppose you wanted your "a" in the where-clause to refer to the
same "a" as the signature of mergesort, but to do that you'll have to
explicitly introduce the "a" type variable with a forall so :

mergesort :: forall a . (a -> a -> Ordering) -> [a] -> [a]

Then the scope of the "a" type variable will extend to the whole
function declaration (where-clause included) instead of being only the
signature in which it appears as is the case by default.

Note that you'll need to authorize the use of the forall keywords by adding :

{-# LANGUAGE ExplicitForall #-}

to the beginning of your file.

--
Jedaï



More information about the Beginners mailing list