[Haskell-cafe] OOP < parametric polymorphism

Steve Downey sdowney at gmail.com
Sun Jan 28 15:13:00 EST 2007


Well, it depends what you mean by OO. In a proper OO system, equality
means not just are these two things in the same state, but do they
refer to a single object. Invoking behavior on one will affect the
other, and the equality relation will still hold.
There are three properties that entities have in a OO model:
1 Identity
2 State
3 Behavior

objects are not values. Values don't have identity. This 7 is the same
as that 7, with no way of distinguishing them. They also don't have
state.You don't add 1 to 7 and turn it into 8 (unless you're in a very
old FORTRAN, where constants weren't). The result is a new value.
Values also don't do things. Functions map values to new values.

Of course, when most people are looking for OO, they're looking for
encapsulation, subtyping, inheritance, polymorphism, dynamic dispatch
and so on. Many of those are dead simple in Haskell. Others less so.

Unfortunately, it seems that most people trying to get these answers
are also trying to apply a design that is suboptimal for the language.

By the way, equality is a particularly nasty example given subtyping.
There is no good way to define equality that is fully polymorphic that
is also transitive and reflexive. Which is annoying no end.



On 1/28/07, apfelmus at quantentunnel.de <apfelmus at quantentunnel.de> wrote:
> Donald Bruce Stewart wrote:
> > deliverable:
> >> ...In the tradition of the "letters of an ignorant newbie"...
> >>
> >> What's the consensus on the OOP in Haskell *now*?  There're some
> >> libraries such as OOHaskell, O'Haskell, and Haskell~98's own qualified
> >> type system with inheritance.
> >>
> >> If I have GHC, which way to do anything OOP-like is considered "right"
> >> today?
> >
> > Using existentials and typeclasses to do some OO things wouldn't be
> > considered unidiomatic (particularly, using existentials to package up
> > interfaces to values).
> >
> > In general though, using a functional approach will produce better
> > (simpler) Haskell code, and make it more likely others will understand it.
> > Personally, I run in fear from OO Haskell ;)
>
> Instead of OOP, Haskell uses (parametric) polymorphism which is more
> powerful than OOP. For instance, the function
>
>    length :: [a] -> Int
>
> or, with an explicit forall
>
>    length :: forall a . [a] -> Int
>
> counts the number of elements in a list "[a]", regardless of what type
> "a" those elements have. Moreover, it is guaranteed that "length" does
> not inspect or change the elements, because it must work for all types
> "a" the same way (this is called "parametricity"). Another example is
>
>    map :: (a -> b) -> [a] -> [b]
>
> which maps a function over all elements in the list.
>
> In addition, Haskell has type classes (which are similar to "interfaces"
> in OOP). The most basic example is
>
>    class Eq a where
>       (==) :: a -> a -> Bool
>
> Thus, you have an equality test available on all types that are
> instances of this class. For example, you can test whether two Strings
> are equal, because String is an instance of Eq. More generally, you say
> whether two lists are equal if you know how to test elements for equality:
>
>    instance Eq a => Eq [a] where
>       []     == []     = True
>       (x:xs) == (y:ys) = (x == y) && (xs == ys)
>       _      == _      = False
>
>
>
> The important thing I want to point out in this post is that parametric
> polymorphism is indeed more powerful than OOP: already a concept like Eq
> is impossible to implement in OOP. The problem is best illustrated with
> the class Ord (*), which provides an ordering relation. Let's
> concentrate on the "smaller than" function
>
>    (<) :: Ord a => a -> a -> Bool
>
> Can I create an interface that expresses the same thing?
>
>    public interface Comparable {
>         boolean smaller_than(?? y);
>    }
>
> No, because there is no type I can attribute to the second argument of
> "smaller_than". The problem is that I can only compare to values of the
> *same* type, i.e. the type which implements the interface.
>
> Can I create a class the expresses the same thing?
>
>    public class Comparable {
>         boolean smaller_than(Comparable y);
>    }
>
> This seems like a solution, but it is not. The problem is subtyping: if
> i make integers and strings members of this class, i would be able to
> compare the number 1 against the string "hello", which should be
> reported as a type error.
>
> I have no formal proof, but I think that the "<" function cannot be
> expressed in a type correct way in OOP. AFAIK, only Java Generics can
> express the requirement we want:
>
>    interface Ord<A> {
>         boolean smaller_than(A x, A y);
>    }
>
>    class String implements Ord<String> { ... }
>
> But Generics are a considerable extension to OOP. In fact, there is
> nothing really object oriented in here anymore, we're just on our way to
> parametric polymorphism.
>
>
> My final remark is about what this means for the existential quantifier
> in Haskell. Because of the injection
>
>    inject :: forall a . a -> (exists a . a)
>
> the existential quantifier can be thought of as implementing some form
> of subtyping, i.e. (exists a . a) is a supertype of every a. The point
> now is: given
>
>    type ExistsOrd = exists a . Ord a => a
>
> there is *no*
>
>    instance Ord ExistsOrd where ...
>
> because we could compare arbitrary subtypes of ExistsOrd then. In the
> end, the existental quantifier has limited use for data abstraction,
> it's "forall" that makes things happen.
>
>
>
> Regards,
> apfelmus
>
>
> (*) We don't consider Eq because given a test on type equality, we can
> generalize the signature of (==)
>
>    (==) :: (Eq a, Eq b) => a -> b -> Bool
>
> Indeed, this is what OOP equality does.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list