[Haskell-cafe] type class constraints headache

Marcus Uneson marcus.uneson at gmail.com
Thu Mar 4 02:32:17 EST 2010


Thanks, it did!

(For the record, here is a paraphrase of what first
confused me -- undefined was not the problem).

> enumerateMethodNames :: [String]
> enumerateMethodNames = map fst methodsNoConstr
> --enumerateMethodNames = map fst methodsConstr
>
> methodsConstr :: (Ord a) => [(String, [a] -> Int)]
> methodsConstr = [ ("method", methodConstr )]
>   where methodConstr :: (Ord a) => [a] -> Int
>         methodConstr xs = length . sort $ xs
>
>
> methodsNoConstr :: [(String, [a] -> Int)]
> methodsNoConstr = [ ("method", methodNoConstr )]
>   where methodNoConstr :: [a] -> Int
>         methodNoConstr = length
>
>
> --First enumerateMethodNames works as expected, second does not compile.

2010/3/4 Ryan Ingram <ryani.spam at gmail.com>

> Perhaps this thought exercise will make things clear:
>
> > class Show a => Foo a where
> >    toFoo :: String -> a
>
> > foos :: (Foo a) => [(String, a)]
> > foos = map (\f -> (show f, f)) [toFoo "a", toFoo "b", toFoo "c"]
>
> > data Foo1 = Foo1
> > instance Show Foo1 where show _ = "1"
> > instance Foo Foo1 where toFoo _ = Foo1
> > data Foo2 = Foo2
> > instance Show Foo2 where show _ = "2"
> > instance Foo Foo2 where toFoo _ = Foo2
>
> > exercise :: [String]
> > exercise = map fst foos
>
> Exercise for the reader: what should the contents of "exercise" be?
>
> Keep in mind that your question is exactly the same as this one, from
> the compiler's point of view.
>
>  -- ryan
>
> On Wed, Mar 3, 2010 at 10:48 PM, Marcus Uneson <marcus.uneson at gmail.com>
> wrote:
> > Thanks. I realize there are many ways to make it compile.
> > However, I am trying to understand the mechanism behind --
> > why does the first example compile and what constraints does
> > enumerateMethodNames add on a (which it does not inspect)?
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100304/152b2134/attachment.html


More information about the Haskell-Cafe mailing list