
[Gregory: Sorry about duplicate, accidentally took it off-list.] On 2010 Oct 14, at 09:46, Gregory Collins wrote:
Jacek Generowicz
writes: Could you explain this a bit more? heterogeneousProcessor was extremely boring: its only interesting feature was the dot between "datum" and "method()" Here it is again:
def heterogeneousProcessor(data): return [datum.method() for datum in data]
Typically we use an existential type for this:
{-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE RankNTypes #-}
data A = A data B = B
class HasFooMethod a where foo :: a -> String
instance HasFooMethod A where foo _ = "This is A's foo method"
instance HasFooMethod B where foo _ = "This is B's foo method"
data SomeFoo = forall a . (HasFooMethod a) => SomeFoo a
printFoo :: SomeFoo -> IO () printFoo (SomeFoo x) = putStrLn $ foo x
---------------------------------------------------------------------- main :: IO () main = do let foos = [SomeFoo A, SomeFoo B, SomeFoo A]
mapM_ printFoo foos
Running main:
*Main> main This is A's foo method This is B's foo method This is A's foo method
Yes, I've now understood that ExistentialQuantification can help with this, and I've even got as far coming up with almost exactly this example of its use. But it's good to have confirmation that I'm doing it right. So thanks for this code sample.
There is more information about the different ways of doing this kind of thing in Haskell in the OOHaskell paper: http://homepages.cwi.nl/~ralf/OOHaskell/
Abstract looks good. On the one hand I want to explore how Haskell allows me to do things in a way that doesn't resemble OO at all. On the other, it's good to see how OO-like things might be done in Haskell.
Unfortunately, this model of programming is a little awkward in Haskell which is why (for the most part) it isn't used as much as it could or should be. N.B. that the Control.Exception module from the standard library (from GHC 6.8 on at least) uses this technique to provide extensible exceptions.
Hope this helps,
Yes. Thanks. Only problem is, that you (plural) have, in about half-a-dozen responses, given me sufficient food for thought to occupy my brain for the next couple of months! :-)