Tom Schrijvers wrote:
William Cook's Onward! essay is relevant here. He characterizes the
difference between objects and abstract data types nicely: the latter
allow binary methods that pattern match (to exploit the combined
knowledge of the internals of two different values) whereas objects
only know their own implementation.

Dictionaries by themselves are objects in Cook's sense: they are just
a record of functions that cannot be inspected. We can have an
infinite number of them (while we can only have one type class
instance per sem type).

I agree that dictionaries can be seen as objects. This is an interesting point of view.

At first glance, dictionaries seem to be not that interesting objects, becaus the observation functions never return new objects, but only plain values instead.

However, we can use the object-like nature of dictionaries to produce new dictionaries in creative ways. For example, we could produce a dictionary by performing the operations in two dictionaries in parallel:

  evalProduct eval1 eval2 = EvalDict valProduct addProduct
    where
      valProduct x = (val eval1 x, val eval2 x)
      addProduct (a, b) (c, d) = (add eval1 a c, add eval2 b d)

Of course, the same can be done with typeclass using a newtype.

In [1], we argue that this kind of code enables us to implement semantics of EDSLs as components, which can be composed etc. Since we used Scala, we had modelled dictionaries as objects. But with this point of view about dictionaries as objects, its the exact same story in Haskell, of course.

  [1] Hofer et al. Polymorphic embedding of DSLs. GPCE 2008.

For a type class function like add :: sem Int -> sem Int -> sem Int,
binary pattern matching seems essential for meaningful
implementations, and hence objects don't make much sense. Would you
agree?

Well, we could encode numbers as objects using church numerals, similar to how Cook uses characteristic functions for sets:

  data Number = Number (iter :: forall a . (a -> a) -> a -> a)

The val constructor:

  valNumber :: Int -> Number
  valNumber x = Number (\f -> iterate f !! x)

Addition:

  add :: Number -> Number -> Number
  add (Number iter1) (Number iter2) = Number (\f -> iter1 f . iter2 f)

the (sem a) values are not objects, and varying the dictionaries
while keeping the sem type the same does not seem very useful for
implementing different semantics.

We could use the Number objects to implement sem Int as follows. (Luckily, sem was always applied to Int in this reduced example, so we do not have to introduce non-parametric type-level functions):

  newtype Const a b = Const a

  evalAsObject :: EvalDict (Const NumberObject)
  evalAsObject = EvalDict valAsObject addAsObject
    where
      valAsObject x = Const (valNumber x)
      addAsObject (Const a) (Const b) = Const (add a b)

We can often (always?) provide a sufficiently rich interface to our objects to support the same operations as with an abstract data type.

I am not sure what laziness does to the picture in Cook's essay. Could a thunk be seen as an object with force as the only observing function? That would mean that in Haskell, even algebraic data types behave like objects because we are not handling them directly, but rather their thunks. From this point of view, Haskell is purely object-oriented.

  Tillmann
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to