[Haskell-beginners] interface/abstract class: what is the haskell way?

Daniel Trstenjak daniel.trstenjak at gmail.com
Fri Feb 8 12:43:50 CET 2013


Hi Emmanuel,

On Fri, Feb 08, 2013 at 10:50:30AM +0100, Emmanuel Touzery wrote:
>  The "obvious" way to do in haskell what I would do in OO would be through
> type classes. However I realize type classes are not quite interfaces. I'm
> wondering what would be the "haskell way" to solve this problem?
> 
>  For sure type classes do the job. But is it the idiomatic way of solving
> this problem?

The problem is, that without the use of extensions it's not possible to have something like:

class EventProvider a where
   events :: a -> IO [Event]

instance EventProvider Prov1 where ...
instance EventProvider Prov2 where ...

-- won't compile, because Prov1 and Prov2 have different types
providers :: EventProvider a => [a]
providers = [Prov1, Prov2]


To express something like this you need existential quantification:

{-# LANGUAGE ExistentialQuantification #-}

data AnyProvider = forall a. (EventProvider a) => AnyProvider a

providers :: [AnyProvider]
providers = [AnyProvider Prov1, AnyProvider Prov2]


But after trying ExistentialQuantification I got the impression, that
it just doesn't fit nicely into the language, that you can get quite
fast to a point where your head explodes by looking at the type errors ;).

So, like others already said (thanks Oleg ;), a record of functions can get you quite far.


In your case youd could have something like:

data EventProvider = EventProvider {events = IO [Event]}


mkProv1 prov1 = EventProvider {events = do
   -- read from prov1
   }

mkProv2 prov2 = EventProvider {events = do
   -- read from prov2
   }


Greetings,
Daniel



More information about the Beginners mailing list