On 12/5/07, Ben Franksen <ben.franksen@online.de> wrote:
data Command = Skip

class Java block command where
block_ :: [command] -> block

compBlock :: [Command] -> block
--compBlock = block_ . map compCommand

compCommand :: Command -> command

This compiles ok. But when I ask ghci for the type of the body of the
default definition of compBlock I get

*Main> :t block_ . map compCommand
block_ . map compCommand :: forall block block1 command.
(Java block command, Java block1 command) =>
[Command] -> block
 
Lets look at the type of "compCommand".
 
compCommand :: Java block command => Command -> command
 
The block type is not used at all in this declaration, but the block type can influence which implementation "compCommand" is chosen.  This means that it's actually almost impossible to ever call this function, as given a type for  "command" there could be multiple implementations of "Java block command" for different block types, and there's no way to ever determine which function to call unless the instance declaration admits any type.

{-# OPTIONS_GHC -fglasgow-exts #-}
module BrokenTypeClass where

class Broken a b where
    broken :: String -> b

{-
instance Broken Bool String where
    broken = id

instance Broken String String where
    broken = reverse
-} -- which instance of "broken" do you choose in "test" below?

instance Broken a String where
    broken = id

test :: String
test = broken "hello"

You would have to use functional dependencies or associated types to eliminate this error.  Alternatively, you can add a dummy argument of type "block" and pass "undefined :: BlockType" in to help choose the instance declaration.
 
Still, I agree with Brent here; whenever I have written code like this I soon realize that I didn't need a typeclass in the first place, and I would have been better off not using them; they're not like OO classes.
 
  -- ryan