Shlomi Fish wrote (on 29-06-02 17:30 +0300):
> 
> I'm trying to write a counter function that would return a tuple whose
> first element is the current value and whose second element is a new
> counter.

John Hughes showed how to do this. Here is a closely related, more abstract
solution which employs existential types. First let me give a paradigmatic
example which is slightly different from what you want: streams.

  data Stream a = forall x. Stm x (x -> a) (x -> x)

Note that we hide the state type x. This lets us keep the implementation
hidden from the client.

  value (Stm state val next) = val state
  next (Stm state val next) = Stm (next state) val next
  both s = (value s, next s)
  
  unfold :: x -> (x -> a) -> (x -> x) -> Stream a
  unfold state val next = Stm state val next
  
  -- the naturals
  nats1 = unfold 0 id succ
  -- value nats1 = 0
  -- value (next nats1) = 1
  -- value (next (next nats1)) = 2 ...

In the example above, we use an integer for the state, project it out when we
need a value, and increment it to get the next state. Here's another way to do
it, using a state which is not an integer.

  nats2 = unfold [0..] head tail

Here we just used an infinite list for the state. head :: List Int -> Int, so
the state type is now different from "method" result type.

And here's an example where we use a step of 100 when we create the stream.

  -- step 100
  stm1 = unfold 5 id (+ 100)

But you wanted an object where we can choose the step at each "point in
time". OK:

  data MyStream a = forall x. MyStm x (x -> a) (a -> x -> x)
  
  myValue (MyStm state val next) = val state
  myNext arg (MyStm state val next) = MyStm (next arg state) val next
  myBoth arg s = (myValue s, myNext arg s)
  
  myUnfold :: x -> (x -> a) -> (a -> x -> x) -> MyStream a
  myUnfold state val next = MyStm state val next
  
  counter n = myUnfold n id (+)

Now the state-transforming function accepts an extra argument along with the
state. And in fact we were able to generalize the idea of "stepping", since we
never had to mention integers or addition till the last line.

Easy, right? You can see the pattern for defining similar sorts datatypes
now. Hide the state type x with a forall, and, for each way of observing and/or
transforming the state, include a function of type x -> ...

OO people call this a (functional) object. Mathematicians call it a
coalgebra. There is a notion of coalgebraic (or coinductive) datatype which is
dual to the notion of algebraic datatypes in Haskell; sometimes they're called
codatatypes. The analog of unfold is fold, of methods (sometimes called
destructors or observors) are data constructors, and of the state type is the
"accumulator" type which is the result of a fold. Some languages like Charity
support codatatypes directly, but in Haskell we can get the same effect with a
local forall.

Actually, you can make this even more OO-like using type classes, but things
seem to get messy if we keep the result type polymorphic so I'll fix it to
Integer:

  class CounterState x where
    sValue :: x -> Integer
    sNext :: Integer -> x -> x
  
  data Counter = forall x. CounterState x => Counter x
  
  instance CounterState Integer where
    sValue = id
    sNext step state = step + state
  
  mkCounter :: Integer -> Counter
  mkCounter n = Counter n

A disadvantage of this approach is that now you can only have one
implementation for each state type; with unfold, where we stored the functions
in the data constructor fields, we could give many implementations of the
methods for each state type. In OO terms, the type class approach is
"class-based" whereas the unfold approach is "object-based".

The advantage, of course, is that you can use inheritance via the type class
inheritance now.

BTW, I hope that this note will not encourage the OO readers on this list to
"objectify" _everything_ now, because that leads (IMO) to twisted programs
which often emphasize the wrong sort of flexibility.

Both datatypes and codatatypes have their place:

  * A datatype is called for when you need a collection of finite-sized values
    (lists, trees, etc.), and want to be able to traverse them easily. The
    fold for a datatype does this for you, and is guaranteed to terminate.

  * A codatatype is called for when you have a collection of infinite-sized or
    circular values (streams, automata, etc.) and you want to be able to index
    arbitrarily into (grab subparts of) them, without possibility of error or
    exposing the representation.

Note that you cannot generally traverse a value of a codatatype: if you try
to "fold" a stream, the computation will diverge.

On the other hand, you cannot index arbitrarily deeply into a value of a
datatype. Remember our stream example? We could have called the "value"
function "head" and the "next" function "tail". You can always apply these to
a stream, and they will never fail. But if you try that with lists, you will
raise an error once you get to the end of it.

-- 
Frank Atanassow, Information & Computing Sciences, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-3261 Fax +31 (030) 251-379
_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to