
On 03/27/2014 11:28 AM, ke dou wrote:
Hi,
Sorry for the spam.
I am new to Haskell. I want to define my own typeclass which can convert from my own types like MyBool, MyInt, and MyString to according Haskell types.
As you've seen, this is actually a hard problem and it needs some of GHC's more advanced machinery. Mateusz's solution uses FunctionalDependencies; there is a similar extension called TypeFamilies which allow you to do many of the same things with (IMO) a nicer syntax. You can think of TypeFamilies as allowing you to define functions between types. And then, just like you can define functions between values in a typeclass, you can define functions between types. This allows you to say (in the instance declaration) which return type goes with MyBool, MyInt, etc. Here is a simple modification of your program (2.5 lines?) using type families. In the type class definition, the "type Return a..." line means that each instance declaration needs to define a type associated 'a' called 'Return a'. Then in the type signature of 'conversion', we can use that type, solving the problem that others have pointed out.
{-# LANGUAGE TypeFamilies #-}
module Conversion where
import qualified Prelude
class Conversion a where type Return a :: * conversion :: a -> (Return a)
data MyBool = MyTrue | MyFalse
instance Conversion MyBool where type Return MyBool = Prelude.Bool conversion MyTrue = Prelude.True conversion MyFalse = Prelude.False