[Haskell-cafe] Library API design: functional objects VS type classes
Rob Stewart
robstewart57 at gmail.com
Mon Mar 4 23:50:14 CET 2013
Hi,
I have a question about API design for Haskell libraries. It is a simple one:
functional object data structures encapsulating mutable state VS type
classes encapsulating mutable state
Here is a simple example. I present an API: using a type class `FooC`,
and aso as a data structure `FooT`. Both are stateful, in the form of
an MVar holding an Integer, with an operation `incrFoo` to increment
this value by one, and another `readFoo` to read the Integer value.
-----
import Control.Concurrent
-- API approach 1: Using type classes
class FooC a where
mkFooC :: IO a
readFooC :: a -> IO Int
incrFooC :: a -> IO ()
newtype Bar = Bar (MVar Int)
instance FooC Bar where
mkFooC = newMVar 0 >>= \i -> return $ Bar i
readFooC (Bar mv) = readMVar mv
incrFooC (Bar mv) =
modifyMVar_ mv $ \i -> return (i+1)
-- API approach 2: Using direct field records
data FooT a = FooT {
readFooT :: IO a
, incrFooT :: IO ()
}
mkBar :: IO (FooT Int)
mkBar = do
mv <- newMVar 0
return FooT {
readFooT = readMVar mv
, incrFooT = modifyMVar_ mv $ \i -> return (i+1)
}
-- Tests the type class API
testTypeClass :: IO ()
testTypeClass = do
bar <- mkBar
incrFooT bar
incrFooT bar
i <- readFooT bar
print i -- prints 2
-- Tests the direct data structure API
testDataStruct :: IO ()
testDataStruct = do
bar <- (mkFooC :: IO Bar)
incrFooC bar
incrFooC bar
i <- readFooC bar
print i -- prints 2
----
With that, I now ask: which is more common? Which is the better API
design for a library? The APIs are almost identical. Under what
conditions is the type classes preferred over the "mutable object"
style data structure? There are two related resources that provides
additional context here, that favour the functional objects approach:
- Section 3.4 "Mutable Objects" in "Haskell's Overlooked Object
System" http://goo.gl/gnZXL
- A similar question (data structures vs type classes) in "Haskell
Antipattern: Existential Typeclass"
http://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/
Thanks!
--
Rob
More information about the Haskell-Cafe
mailing list