[Haskell-cafe] reifying typeclasses
oleg at okmij.org
oleg at okmij.org
Sun Sep 15 11:16:22 CEST 2013
Evan Laforge wrote:
> I have a typeclass which is instantiated across a closed set of 3
> types. It has an ad-hoc set of methods, and I'm not too happy with
> them because being a typeclass forces them to all be defined in one
> place, breaking modularity. A sum type, of course, wouldn't have that
> problem. But in other places I want the type-safety that separate
> types provide, and packing everything into a sum type would destroy
> that. So, expression problem-like, I guess.
>
> It seems to me like I should be able to replace a typeclass with
> arbitrary methods with just two, to reify the type and back. This
> seems to work when the typeclass dispatches on an argument, but not on
> a return value. E.g.:
If the universe (the set of types of interest to instantiate the type
class to) is closed, GADTs spring to mind immediately. See, for
example, the enclosed code. It is totally unproblematic (one should
remember to always write type signatures when programming with
GADTs. Weird error messages otherwise ensue.)
One of the most notable differences between GADT and type-class--based
programming is that GADTs are closed and type classes are open (that
is, new instances can be added at will). In fact, a less popular
technique of implementing type classes (which has been used in some Haskell
systems -- but not GHC)) is intensional type analysis, or typecase.
It is quite similar to the GADT solution.
The main drawback of the intensional type analysis as shown in the
enclosed code is that it breaks parametricity. The constraint Eq a
does not let one find out what the type 'a' is and so what other
operations it may support. (Eq a) says that the type a supports (==),
and does not say any more than that. OTH, Representable a tells quite
a lot about type a, essentially, everything.
> types. It has an ad-hoc set of methods, and I'm not too happy with
> them because being a typeclass forces them to all be defined in one
> place, breaking modularity. A sum type, of course, wouldn't have that
Why not to introduce several type classes, even a type class for each
method if necessary. Grouping methods under one type class is
appropriate when such a grouping makes sense. Otherwise, Haskell won't
lose in expressiveness if a type class could have only one method.
{-# LANGUAGE GADTs #-}
module G where
data TRep a where
TInt :: TRep Int
TChar :: TRep Char
class Representable a where
repr :: TRep a
instance Representable Int where
repr = TInt
instance Representable Char where
repr = TChar
argument :: Representable a => a -> Int
argument x = go repr x
where
-- For GADTs, signatures are important!
go :: TRep a -> a -> Int
go TInt x = x
go TChar x = fromEnum x
-- just the `mirror inverse'
result :: Representable a => Int -> a
result x = go repr x
where
-- For GADTs, signatures are important!
go :: TRep a -> Int -> a
go TInt x = x
go TChar x = toEnum x
t1 = argument 'a'
t2 = show (result 98 :: Char)
More information about the Haskell-Cafe
mailing list