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] Compiling dph package with ghc-7.4.0.20111219

2012-01-22 Thread Atsuro Hoshino
I don't know so much about ghc-7.4,  but if loading dph codes in ghci
is the main matter here, below might help:

  http://warmfuzzything.posterous.com/loading-dph-codes-in-ghci


Best,
--
Atsuro Hoshino

On Sun, Jan 22, 2012 at 2:58 AM, Brandon Allbery allber...@gmail.com wrote:
 On Sat, Jan 21, 2012 at 12:50, mukesh tiwari mukeshtiwari.ii...@gmail.com
 wrote:

 Hi Brandon
 Thank you for reply. Could you please tell me how to install dph
 because cabal install is not working with ghc-7.4.0.20111219 and I
 have issue with ghc-7.2.1 and dph


 Sorry, but I don't know.  I don't follow or use DPH, I just know how the GHC
 repo works, and that they had a problem with including additional library
 sub-repos which just happened to include (probably out of date, since DPH is
 developed separately) DPH libraries.  As such, I would not expect DPH to be
 included in the official 7.4 release unless the DPH folks submit an updated
 version (and probably not even then since GHC is in the release candidates
 phase, so it's a bit too late to add a newer DPH into it).

 --
 brandon s allbery                                      allber...@gmail.com
 wandering unix systems administrator (available)     (412) 475-9364 vm/sms


 ___
 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] Error in converting List of Lists into PArray ( Parray a )

2012-01-18 Thread Atsuro Hoshino
Hi Mukesh,

Below is a naive implementation of converting `[[(Int,Double)]]' to
`PArray (PArray (Int, Double))' .
There's no instance for `PA [a]', I've explicitly separated the inner
and outer conversion.
Though, when reading data from a file and converting, it might be
better to use `hGet' in:

  
http://hackage.haskell.org/packages/archive/dph-prim-par/0.5.1.1/doc/html/Data-Array-Parallel-Unlifted.html

-- 
module Main where

import Data.Array.Parallel
import Data.Array.Parallel.PArray ()
import qualified Data.Array.Parallel.PArray as P

mat_li :: [[(Int, Double)]]
mat_li =
  [ zip [1..] [ 1, 2, 3, 0, 0, 0, 0, 0, 4 ]
  , zip [1..] [ 0, 0, 0, 0, 0, 0, 0, 0, 0 ]
  , zip [1..] [ 0, 0, 0, 0, 0, 0, 1, 2, 0 ] ]

mat_pa_1 :: PArray (PArray (Int, Double))
mat_pa_1 = P.fromList (fmap P.fromList mat_li)

mat_pa_2 :: PArray (PArray (Int, Double))
mat_pa_2 = conv_outer (conv_inner mat_li)

conv_inner :: P.PA a = [[a]] - [PArray a]
conv_inner = map P.fromList

conv_outer :: P.PA a = [PArray a] - PArray (PArray a)
conv_outer xs = case xs of
  [] - P.empty
  (x:xs) - P.singleton x P.+:+ conv_outer xs

main :: IO ()
main =
  -- Printing `mat_pa_1' shows an error:
  --
  --  No instance nor default method for class operation
  --  Data.Array.Parallel.PArray.PData.fromListPR
  --
  -- print mat_pa_1
  print mat_pa_2



Hope this well help.


Regards,
 --
Atsuro Hoshino

On Thu, Jan 19, 2012 at 4:47 AM, mukesh tiwari
mukeshtiwari.ii...@gmail.com wrote:
 Hello all
 I am trying to convert List of Lists ( [[(Int , Double )]] ) into PArray (
 PArray ( Int , Double )) but getting run time error. This code works fine
 and print list of PArray ( Int , Double ) but when i put print $ P.fromList
 ( map P.fromList c ) then i am getting runtime error. It says Main:
 Data/Array/Parallel/PArray/PDataInstances.hs:337:10-30: No instance nor
 default method for class operation
 Data.Array.Parallel.PArray.PData.fromListPR. Could some one please tell me
 how to resolve this issue.
 Thank you


 --import ParallelMat
 import Data.List
 import System.Environment
 import Data.Array.Parallel
 import qualified Data.Array.Parallel.PArray as P


 processMatrix :: [ [ Double ] ] - [ [ Double ] ] - [ ( [ ( Int , Double )
 ] , [ ( Int , Double ) ]) ]
 processMatrix [] [] = []
 processMatrix ( x : xs ) ( y : ys )
   | ( all ( == 0 ) x )  Prelude.|| (  all ( == 0 ) y ) = processMatrix xs ys
   | otherwise = ( filter ( \( x , y ) - y /= 0 ) . zip [ 1..]  $ x ,filter
 (  \( x , y ) - y /= 0 ) . zip [1..] $ y  ) : processMatrix xs ys

 main = do
     [ first , second ] - getArgs
     a - readFile first
     b - readFile second
     let a' = transpose . tail . map ( map ( read :: String - Double ) .
 words ) . lines $ a
     b' = tail . map ( map ( read :: String - Double ) . words ) . lines
 $ b
     ( c , d )   = unzip $ processMatrix a' b'
     print $   (  map P.fromList c )
    --print d

 Macintosh-0026bb610428:Haskell mukesh$ ghc --make  -Odph -fdph-par  Main.hs
 [1 of 1] Compiling Main             ( Main.hs, Main.o )
 Linking Main ...
 Macintosh-0026bb610428:Haskell mukesh$ ./Main  A.in A.in
 [fromListPArray [(1,1.0),(6,1.0)],fromListPArray
 [(4,11.0),(9,11.0)],fromListPArray [(1,4.0),(4,2.0),(6,4.0),(9,2.0)]]

 Putting print $ P.fromList ( map P.fromList c )

 Macintosh-0026bb610428:Haskell mukesh$ ghc --make  -Odph -fdph-par  Main.hs
 [1 of 1] Compiling Main             ( Main.hs, Main.o )
 Linking Main ...
 Macintosh-0026bb610428:Haskell mukesh$ ./Main  A.in A.in
 Main: Data/Array/Parallel/PArray/PDataInstances.hs:337:10-30: No instance
 nor default method for class operation
 Data.Array.Parallel.PArray.PData.fromListPR

 Input file A.in
 10 10
 1 2 3 0 0 0 0 0 0 4
 0 0 0 0 0 0 0 0 0 0
 0 0 0 0 0 0 0 0 0 0
 0 0 0 0 0 0 1 2 11 2
 0 1 2 0 0 0 0 0 0 0
 1 2 3 0 0 0 0 0 0 4
 0 0 0 0 0 0 0 0 0 0
 0 0 0 0 0 0 0 0 0 0
 0 0 0 0 0 0 1 2 11 2
 0 1 2 0 0 0 0 0 0 0
 ___
 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