Re: [Haskell-cafe] Library API design: functional objects VS type classes

2013-03-05 Thread Atsuro Hoshino
Hi Rob,

I usually prefer type class approach for early stage of development.

Type class approach is more flexible, less works required.
One might get a function with lots of constraints, and quite a lot of
language extensions may appear, though it works.

Once things got settled down, I reconsider API.


The type signatures shown in your example::

  class FooC a where
mkFooC :: IO a
readFooC :: a - IO Int
incrFooC :: a - IO ()

and:

  data FooT a = FooT {
  readFooT :: IO a
, incrFooT :: IO ()
}

Resulting type of 'readFooC' is fixed to 'Int' within the type class.
On the other hand, resulting type of 'readFooT' is type variable 'a'.

Made slight modification to the type class shown in your
example. Changed result type of 'readFooC' to take associated
type:

http://hpaste.org/83507

Once criteria for comparison I can think is performance.

For compilation time, I guess functional object approach give better
performance, since some of the works done by compiler are already done
manually. Though, I haven't done benchmark of compilation time, and
not sure how much interest exist in performance of compilation.

For runtime performance, one can do benchmark in its concrete usecase.
I suppose, generally, functions defined with type class are slower
than functions having concrete type. See SPECIALIZE pragam in GHC[1].

Another criteria I can think is extensibility.

Suppose that we want to have new member function, 'incrTwice'. If we
have chance to change the source of 'FooC', adding new member function
to 'FooC' type class directly is possible, with default function body
filled in.

  class FooC a where
type FooCVal a :: *
mkFooC :: IO a
readFooC :: a - IO (FooCVal a)
incrFooC :: a - IO ()
incrTwiceC :: a - IO ()
incrTwiceC a = incrFooC a  incrFooC a

Though, having reasonable default is not always possible.

For additional source of inspiration, might worth looking the
classic[2], and scrap your type classes article[3].


[1]:
http://www.haskell.org/ghc/docs/7.6.1/html/users_guide/pragmas.html#specialize-pragma
[2]: http://homepages.inf.ed.ac.uk/wadler/papers/class/class.ps
[3]: http://www.haskellforall.com/2012/05/scrap-your-type-classes.html

Hope these help.


Regards,
--
Atsuro



On Tue, Mar 5, 2013 at 7:50 AM, Rob Stewart robstewar...@gmail.com wrote:

 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

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

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


Re: [Haskell-cafe] Library API design: functional objects VS type classes

2013-03-05 Thread Edsko de Vries
What is the advance of using type classes? A function of the form

  f :: Show a = ...

really has an implicit argument

  f :: Show__Dict a - ...

that the compiler infers for us. So, the advantage of type classes is one
of convenience: we don't have to pass dictionaries around, or even figure
out which dictionaries we need; the compiler does that for us. But if we
have a type class of the form

  class Foo a where
mkFoo :: IO FooToken
otherFun1 :: FooToken - ...
otherFun2 :: FooToken - ...

then this advantage is mostly lost; we still need to pass around an
explicit FooToken object. In a case like this, I don't see the advantage of
using a type class over using a data type

  data Foo = Foo { otherFun1 :: ... , otherFun2 :: ... }
  mkFoo :: .. - Foo

There are exceptions; for instance, if you want to encode 'inheritance' in
some way then type classes might still be useful; for instance, see the
Gtk2Hs library, which uses this extensively.

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


Re: [Haskell-cafe] Library API design: functional objects VS type classes

2013-03-05 Thread Joey Adams
On Mon, Mar 4, 2013 at 5:50 PM, Rob Stewart robstewar...@gmail.com wrote:

 ...
 -
 import Control.Concurrent

 -- API approach 1: Using type classes
 class FooC a where
   mkFooC :: IO a
   readFooC :: a - IO Int
   incrFooC :: a - IO ()


I recommend taking 'mkFooC' out of the typeclass.  It keeps you from being
able to (easily) construct a 'FooC' from dynamic data, e.g.:

mkFoo :: Host - Port - IO MyFoo

After this change, the typeclass approach and the data constructor approach
are nearly equivalent, except:

 * With the typeclass approach, the compiler passes the dictionary
implicitly, which can be more convenient to use (e.g. `readFooC a` instead
of `readFooC (getFoo a)`).

 * With the typeclass approach, you have to define a Foo type to contain
the environment needed for Foo methods.  With the record approach, you can
just construct and use a FooT record directly.

Either way, don't forget about simple encapsulation:

data LineDevice -- abstract

-- Some LineDevice constructors for common tasks
stdio :: LineDevice
openFile :: FilePath - IO LineDevice
connectTo :: HostName - PortId - IO LineDevice

getLine :: LineDevice - Int - IO ByteString
putLine :: LineDevice - ByteString - IO ()

This interface is very easy to understand.  If you want to let users make
their own LineDevice objects, you can still provide an internal module
with something like this:

data Driver = Driver
{ getLine :: Int - IO ByteString
, putLine :: ByteString - IO ()
}

newLineDevice :: Driver - IO LineDevice

Hope this helps,
-Joey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe