[Haskell-cafe] Question related to Multi Param Type Classes

Sai Hemanth K saihemanth at gmail.com
Mon May 5 11:52:29 EDT 2008


Hi,

I declared a multi param type class as below:
*class MyString m c  where
      zIndex  :: m -> Int -> c
      zLength :: m -> Int
      zPack   :: [c] -> m
      zEquals :: c ->c -> Bool
      zWrap   :: [c] -> (m,AnExistingDataType)*

In the end I did not needed it for my program, but for those few minutes I
played with the idea, I came across a zillion questions.
Can some body help me here please?
When I defined a function like below,
\begin{code}
compareStr::(MyString m c) => (m,Int) ->(m,Int)->Int->Int
compareStr (s1,pos1) (s2,pos2) soFar
           | (pos1 < zLength  s1) &&  (pos2 < zLength s2) =  let
                                                                  c1 =
zIndex s1 pos1
                                                                  c2 =
zIndex s2 pos2
                                                                in
                                                                  if(zEquals
c1 c2)    then
                                      compareStr (s1,(pos1 + 1)) (s2, (pos2
+ 1)) (soFar + 1)
                                                                  else soFar

           | otherwise                                        = soFar
\end{code}

when I loaded it on ghci ( invoked with -XMultiParamTypeClasses ), I got an
essay in greek (or is it latin?), which started something like below:
    Could not deduce (MyString m c) from the context (MyString m c4)
      arising from a use of `zLength' at GenericZAlgo.lhs:42:21-31
    Possible fix:
      add (MyString m c) to the context of
        the type signature for `compareStr'
    In the second argument of `(<)', namely `zLength s1'
    In the first argument of `(&&)', namely `(pos1 < zLength s1)'
    In a pattern guard for
       the definition of `compareStr':
          (pos1 < zLength s1) && (pos2 < zLength s2)

And if I let the type inference run the show, the type it shows is :
compareStr :: (MyString t c2,
               MyString m c2,
               Num a,
               MyString t1 c2,
               MyString t c,
               MyString t1 c1) =>
              (t, Int) -> (t1, Int) -> a -> a

And puzzlingly, if I try the same thing myself and reload it on the ghci,I
still get similar error.  I can go on about other 'puzzles'.

Can some one please tell me whats going on here?

Apologies, if it is something that's been documented left to right, top to
bottom, but I could not get  anywhere readily. Any pointers to the right
documentation will be much appreciated.
On the surface it looks like something that n00bs like yours truly better
stay away. But  I have a feeling that this one may throw some more light on
type inference.

Many thanks
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080505/3fecb106/attachment.htm


More information about the Haskell-Cafe mailing list