Easily generating efficient instances for classes

2010-02-24 Thread Christian Höner zu Siederdissen
Hi,

I am thinking about how to easily generate instances for a class. Each
instance is a tuple with 1 or more elements. In addition there is a
second tuple with the same number of elements but different type. This
means getting longer and longer chains of something like (...,x3*x2,x2,0).

- template haskell?
- CPP and macros?

Consider arrays with fast access like Data.Vector, but with higher
dimensionality. Basically, I want (!) to fuse when used in Data.Vector
code.

A code abstract follows -- I will put this on hackage if there is
insterest. And please comment if you think of something how to improve
here.


Viele Gruesse,
Christian



-- | Primitive multidimensional tables without bounds-checking. Internally, we
-- used unboxed vectors. Construction expects the highest possible index in
-- each dimension, not the length (which is highest index +1). This choice
-- allows for easier construction using bounded types. Consider: "fromList True
-- False [] :: PrimTable Bool Bool" which creates a 2-element table.

-- | Fast lookup table: `a` encodes the storage index type, while (!) only
-- requires that the index value is (Enum).

data PrimTable a b = PrimTable
  {-# UNPACK #-} !a -- ^ the highest indices (every index starts at 
0 (or 0,0 ...))
  {-# UNPACK #-} !a -- ^ precalculated multiplication values
  {-# UNPACK #-} !(V.Vector b)  -- ^ storage space



-- | mutable fast lookup table

data MPrimTable s a b = MPrimTable
  {-# UNPACK #-} !a
  {-# UNPACK #-} !a
  {-# UNPACK #-} !(V.MVector s b)



class (V.Unbox b) => PrimTableOperations a b e where

  -- | Fast index operation using precomputed multiplication data. Does
  -- bounds-checking only using assert.
  (!) :: PrimTable a b -> e -> b
  {-# INLINE (!) #-}

  new :: (PrimMonad s) => e -> s (MPrimTable (PrimState s) a b)
  {-# INLINE new #-}

  newWith :: (PrimMonad s) => e -> b -> s (MPrimTable (PrimState s) a b)
  {-# INLINE newWith #-}

  read :: (PrimMonad s) => MPrimTable (PrimState s) a b -> e -> s b
  {-# INLINE read #-}

  write :: (PrimMonad s) => MPrimTable (PrimState s) a b -> e -> b -> s ()
  {-# INLINE write #-}

  fromList :: e -> b -> [(e,b)] -> PrimTable a b
  fromList dim init xs = runST $ do
mpt <- newWith dim init
mapM_ (\(k,v) -> write mpt k v) xs
unsafeFreeze mpt
  {-# INLINE fromList #-}






-- | Two-dimensional tables.

instance (Enum e, V.Unbox b) => PrimTableOperations (Int,Int) b (e,e) where

  (PrimTable (z2,z1) (n2,n1) arr) ! (k2,k1) =
arr `V.unsafeIndex` (fromEnum k2 * n2 + fromEnum k1)
  {-# INLINE (!) #-}

  new (z2',z1') = do
let z2 = fromEnum z2' +1
let z1 = fromEnum z1' +1
marr <- M.new $ z2 * z1
return $ MPrimTable (z2,z1) (z1,0) marr

  newWith (z2,z1) v = do
mpt <- new (z2,z1)
mapM_ (\k -> write mpt k v) [(k2,k1) | k2 <- [toEnum 0..z2], k1 <- [toEnum 
0..z1]]
return mpt

  read (MPrimTable (z2,z1) (n2,_) marr) (k2,k1) =
M.read marr (fromEnum k2 * n2 + fromEnum k1)

  write (MPrimTable (z2,z1) (n2,_) marr) (k2,k1) v =
M.write marr (fromEnum k2 * n2 + fromEnum k1) v



-- example

jarr :: PrimTable (Int,Int) Double
jarr = fromList (2 :: Int,2 :: Int) 0.0 
[((0,0),1.0),((0,1),2.0),((1,0),3.0),((1,1),4.0)]
runj = [jarr ! (k :: (Int,Int)) | k <- [(0,0),(0,1),(1,0),(1,1)]]



pgpmQXnina3fi.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Easily generating efficient instances for classes

2010-02-25 Thread Bulat Ziganshin
Hello Christian,

Thursday, February 25, 2010, 3:57:44 AM, you wrote:

> I am thinking about how to easily generate instances for a class. Each

it's called generic programing. just a few overviews on this topic:

Libraries for Generic Programming in Haskell
http://www.cs.uu.nl/research/techreps/repo/CS-2008/2008-025.pdf

Comparing Approaches to Generic Programming in Haskell
http://www.cs.uu.nl/~johanj/publications/ComparingGP.pdf

Derive package is probably the easiest way

Template Haskell is also good although a bit too complex. my own pets:
http://www.haskell.org/bz/th3.htm
http://www.haskell.org/bz/thdoc.htm

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Easily generating efficient instances for classes

2010-02-28 Thread Neil Mitchell
As Bulat says, the Derive package might be a good way to go. I am
happy to accept any new derivations, and you get lots of things for
free - including writing your code using the nice haskell-src-exts
library, preprocessor support, TH support etc.

Thanks, Neil

On Thu, Feb 25, 2010 at 8:57 AM, Bulat Ziganshin
 wrote:
> Hello Christian,
>
> Thursday, February 25, 2010, 3:57:44 AM, you wrote:
>
>> I am thinking about how to easily generate instances for a class. Each
>
> it's called generic programing. just a few overviews on this topic:
>
> Libraries for Generic Programming in Haskell
> http://www.cs.uu.nl/research/techreps/repo/CS-2008/2008-025.pdf
>
> Comparing Approaches to Generic Programming in Haskell
> http://www.cs.uu.nl/~johanj/publications/ComparingGP.pdf
>
> Derive package is probably the easiest way
>
> Template Haskell is also good although a bit too complex. my own pets:
> http://www.haskell.org/bz/th3.htm
> http://www.haskell.org/bz/thdoc.htm
>
> --
> Best regards,
>  Bulat                            mailto:bulat.zigans...@gmail.com
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Easily generating efficient instances for classes

2010-03-01 Thread John Lato
> From: Christian H?ner zu Siederdissen
>
> Hi,
>
> I am thinking about how to easily generate instances for a class. Each
> instance is a tuple with 1 or more elements. In addition there is a
> second tuple with the same number of elements but different type. This
> means getting longer and longer chains of something like (...,x3*x2,x2,0).
>
> - template haskell?
> - CPP and macros?
>
> Consider arrays with fast access like Data.Vector, but with higher
> dimensionality. Basically, I want (!) to fuse when used in Data.Vector
> code.

(shameless plug) You may want to look at my AdaptiveTuple package,
which does something very similar to this.  I used Template Haskell
because AFAIK neither generic approaches nor DrIFT/Derive will
generate data decls.

If all you need are the instances, then DrIFT or Derive would be my
recommendations.

Cheers,
John
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Easily generating efficient instances for classes

2010-03-02 Thread Neil Mitchell
Hi

Derive generates declarations - they can be instances, classes, data
types, functions, type synonyms etc.

Thanks, Neil

On Mon, Mar 1, 2010 at 10:32 AM, John Lato  wrote:
>> From: Christian H?ner zu Siederdissen
>>
>> Hi,
>>
>> I am thinking about how to easily generate instances for a class. Each
>> instance is a tuple with 1 or more elements. In addition there is a
>> second tuple with the same number of elements but different type. This
>> means getting longer and longer chains of something like (...,x3*x2,x2,0).
>>
>> - template haskell?
>> - CPP and macros?
>>
>> Consider arrays with fast access like Data.Vector, but with higher
>> dimensionality. Basically, I want (!) to fuse when used in Data.Vector
>> code.
>
> (shameless plug) You may want to look at my AdaptiveTuple package,
> which does something very similar to this.  I used Template Haskell
> because AFAIK neither generic approaches nor DrIFT/Derive will
> generate data decls.
>
> If all you need are the instances, then DrIFT or Derive would be my
> recommendations.
>
> Cheers,
> John
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Easily generating efficient instances for classes

2010-03-02 Thread Christian Hoener zu Siederdissen
Thanks everybody for the answers.

Right now, it looks like this:
the indextype is abstracted out and I plan for Data.Ix and my own Data.FastIx 
(or however to call it).

As I don't plan on creating all instances myself, Neils derive package looks 
good -- once I
understand it completely; which I need to as I need instances of my own class. 
Is there a tutorial
on creating instances for own stuff, or should I go by the examples like 
Functor?

The code in AdaptiveTuple has one advantage: it looks easier to get started 
producing instances. (No
need to get to know another package).

Btw. it is a bit disappointing (for me) that Data.Ix is almost as fast as my 
FastIx ;-) (as in: most
people don't care about the difference)



Something else: was there a resource about library naming? otherwise it is 
going to be
vector-ixtables (someone a better idea?)


Thanks again,
Christian


On 03/02/2010 02:30 PM, Neil Mitchell wrote:
> Hi
> 
> Derive generates declarations - they can be instances, classes, data
> types, functions, type synonyms etc.
> 
> Thanks, Neil
> 
> On Mon, Mar 1, 2010 at 10:32 AM, John Lato  wrote:
>>> From: Christian H?ner zu Siederdissen
>>>
>>> Hi,
>>>
>>> I am thinking about how to easily generate instances for a class. Each
>>> instance is a tuple with 1 or more elements. In addition there is a
>>> second tuple with the same number of elements but different type. This
>>> means getting longer and longer chains of something like (...,x3*x2,x2,0).
>>>
>>> - template haskell?
>>> - CPP and macros?
>>>
>>> Consider arrays with fast access like Data.Vector, but with higher
>>> dimensionality. Basically, I want (!) to fuse when used in Data.Vector
>>> code.
>>
>> (shameless plug) You may want to look at my AdaptiveTuple package,
>> which does something very similar to this.  I used Template Haskell
>> because AFAIK neither generic approaches nor DrIFT/Derive will
>> generate data decls.
>>
>> If all you need are the instances, then DrIFT or Derive would be my
>> recommendations.
>>
>> Cheers,
>> John
>> ___
>> Glasgow-haskell-users mailing list
>> Glasgow-haskell-users@haskell.org
>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Easily generating efficient instances for classes

2010-03-02 Thread Neil Mitchell
Hi Christian,

No good examples I'm afraid. There are a few notes in README.txt (I
just pushed a few more notes). If you follow the process I'd welcome
any improvements to the documentation.

Thanks, Neil

On Tue, Mar 2, 2010 at 1:50 PM, Christian Hoener zu Siederdissen
 wrote:
> Thanks everybody for the answers.
>
> Right now, it looks like this:
> the indextype is abstracted out and I plan for Data.Ix and my own Data.FastIx 
> (or however to call it).
>
> As I don't plan on creating all instances myself, Neils derive package looks 
> good -- once I
> understand it completely; which I need to as I need instances of my own 
> class. Is there a tutorial
> on creating instances for own stuff, or should I go by the examples like 
> Functor?
>
> The code in AdaptiveTuple has one advantage: it looks easier to get started 
> producing instances. (No
> need to get to know another package).
>
> Btw. it is a bit disappointing (for me) that Data.Ix is almost as fast as my 
> FastIx ;-) (as in: most
> people don't care about the difference)
>
>
>
> Something else: was there a resource about library naming? otherwise it is 
> going to be
> vector-ixtables (someone a better idea?)
>
>
> Thanks again,
> Christian
>
>
> On 03/02/2010 02:30 PM, Neil Mitchell wrote:
>> Hi
>>
>> Derive generates declarations - they can be instances, classes, data
>> types, functions, type synonyms etc.
>>
>> Thanks, Neil
>>
>> On Mon, Mar 1, 2010 at 10:32 AM, John Lato  wrote:
 From: Christian H?ner zu Siederdissen

 Hi,

 I am thinking about how to easily generate instances for a class. Each
 instance is a tuple with 1 or more elements. In addition there is a
 second tuple with the same number of elements but different type. This
 means getting longer and longer chains of something like (...,x3*x2,x2,0).

 - template haskell?
 - CPP and macros?

 Consider arrays with fast access like Data.Vector, but with higher
 dimensionality. Basically, I want (!) to fuse when used in Data.Vector
 code.
>>>
>>> (shameless plug) You may want to look at my AdaptiveTuple package,
>>> which does something very similar to this.  I used Template Haskell
>>> because AFAIK neither generic approaches nor DrIFT/Derive will
>>> generate data decls.
>>>
>>> If all you need are the instances, then DrIFT or Derive would be my
>>> recommendations.
>>>
>>> Cheers,
>>> John
>>> ___
>>> Glasgow-haskell-users mailing list
>>> Glasgow-haskell-users@haskell.org
>>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>>
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users