Re: [Haskell-cafe] unboxed arrays restricted to simple types (Int, Float, ..)

2009-11-16 Thread Henning Thielemann


On Wed, 11 Nov 2009, Tom Nielsen wrote:


There's a couple of things going on here:

-If you use storablevector and storable-tuple, or uvector, you can
store tuples of things. So your stupidArrayElement could be mimicked
by (Int, Int).


Btw. there is Data.Array.Storable. Maybe I should just add a conversion 
from StorableArray to StorableVector and back.

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


[Haskell-cafe] unboxed arrays restricted to simple types (Int, Float, ..)

2009-11-11 Thread Tillmann Vogt

Hi,

I tried to use unboxed arrays for generating an antialiased texture. To 
make it easier to understand, here is the stripped down code that 
produces an error:


import Control.Monad.ST
import Data.Array.ST
import Data.Array.Unboxed
import Data.Word
type BitMask = UArray Int Word16 -- for determining the grey value of 
a pixel

type Pixels = (Int, Int, T)
data T = N | B BitMask -- this does not work
-- type T = Int -- this works if int the next line N is replaced by 
..lets say 0

f = newArray (0,10) N :: (ST s (STUArray s Int T))

http://hackage.haskell.org/packages/archive/array/0.2.0.0/doc/html/Data-Array-MArray.html#t%3AMArray
shows that mutable/unboxed arrays only allow simple types:
i.e.  MArray (STUArray s) Int32 (ST s)

Isn't this ugly? Imagine this would be the case in C:


struct stupidArrayElement{
  int a;
  int b; // not allowed!
}

stupidArrayElement s[10];


Wouldn't it be nice to have something like: MArray (STUArray s) e (ST s)
with e being a non-recursive data type (like data T = N | B Bitmask).
My understanding of Haskell isn't deep enough to know if I have 
overlooked something or if the problem is solvable without a language 
extension. With a language extension I guess that it is not hard to find 
out if an abstract data type is non-recursive. Then this type should be 
serializable automatically.


What do you think?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] unboxed arrays restricted to simple types (Int, Float, ..)

2009-11-11 Thread Svein Ove Aas
On Wed, Nov 11, 2009 at 12:58 PM, Tillmann Vogt
tillmann.v...@rwth-aachen.de wrote:
 Hi,

 I tried to use unboxed arrays for generating an antialiased texture. To make
 it easier to understand, here is the stripped down code that produces an
 error:

*snip*

 What do you think?

It is generally acknowledged that the array types bundled with GHC
have serious shortcomings, such as for example the one you just
pointed out. There is not, however, a consensus on how to change them.

To solve your particular problem, I would suggest looking up the
storablevector package on Hackage, which I know can handle arbitrary
unboxed elements.

That said, I'm sure someone will be along shortly to give you the full
story. :-)


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


Re: [Haskell-cafe] unboxed arrays restricted to simple types (Int, Float, ..)

2009-11-11 Thread Hemanth Kapila
On Wed, Nov 11, 2009 at 5:28 PM, Tillmann Vogt tillmann.v...@rwth-aachen.de
 wrote:

 Hi,

 I tried to use unboxed arrays for generating an antialiased texture. To
 make it easier to understand, here is the stripped down code that produces
 an error:

 import Control.Monad.ST
 import Data.Array.ST
 import Data.Array.Unboxed
 import Data.Word
 type BitMask = UArray Int Word16 -- for determining the grey value of a
 pixel
 type Pixels = (Int, Int, T)
 data T = N | B BitMask -- this does not work
 -- type T = Int -- this works if int the next line N is replaced by ..lets
 say 0
 f = newArray (0,10) N :: (ST s (STUArray s Int T))


 http://hackage.haskell.org/packages/archive/array/0.2.0.0/doc/html/Data-Array-MArray.html#t%3AMArray
 shows that mutable/unboxed arrays only allow simple types:
 i.e.  MArray (STUArray s) Int32 (ST s)

 Isn't this ugly? Imagine this would be the case in C:


 struct stupidArrayElement{
  int a;
  int b; // not allowed!
 }

 stupidArrayElement s[10];


 Wouldn't it be nice to have something like: MArray (STUArray s) e (ST s)
 with e being a non-recursive data type (like data T = N | B Bitmask).
 My understanding of Haskell isn't deep enough to know if I have overlooked
 something or if the problem is solvable without a language extension. With a
 language extension I guess that it is not hard to find out if an abstract
 data type is non-recursive. Then this type should be serializable
 automatically.

 What do you think?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


Actually, there's a cool package called  storable record. Could it be of
some use to you? (Perhaps you *might* be able to use it if the BitMasks  are
of uniform length). Am not 100% sure though.

Isn't this ugly?

I am not sure if it is really *ugly*...and if am allowed to nit-pick,
the analogy with C  is not appropriate either.
Arrays are just different.  (At least thats how I console myself, when am
looking for a high performance strict array). Also, on an approximately
related issue,
 I was suggested to look into data parallel arrays.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] unboxed arrays restricted to simple types (Int, Float, ..)

2009-11-11 Thread Eugene Kirpichov
You might also look at how Data Parallel Haskell implements its arrays.
IIRC, it implements an array of n-field records as n arrays. You can
easily do that with typeclasses and type families.

2009/11/11 Tillmann Vogt tillmann.v...@rwth-aachen.de:
 Hi,

 I tried to use unboxed arrays for generating an antialiased texture. To make
 it easier to understand, here is the stripped down code that produces an
 error:

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Unboxed
import Data.Word
type BitMask = UArray Int Word16 -- for determining the grey value of a
 pixel
type Pixels = (Int, Int, T)
data T = N | B BitMask -- this does not work
-- type T = Int -- this works if int the next line N is replaced by ..lets
 say 0
f = newArray (0,10) N :: (ST s (STUArray s Int T))

 http://hackage.haskell.org/packages/archive/array/0.2.0.0/doc/html/Data-Array-MArray.html#t%3AMArray
 shows that mutable/unboxed arrays only allow simple types:
 i.e.  MArray (STUArray s) Int32 (ST s)

 Isn't this ugly? Imagine this would be the case in C:


 struct stupidArrayElement{
  int a;
  int b; // not allowed!
 }

 stupidArrayElement s[10];


 Wouldn't it be nice to have something like: MArray (STUArray s) e (ST s)
 with e being a non-recursive data type (like data T = N | B Bitmask).
 My understanding of Haskell isn't deep enough to know if I have overlooked
 something or if the problem is solvable without a language extension. With a
 language extension I guess that it is not hard to find out if an abstract
 data type is non-recursive. Then this type should be serializable
 automatically.

 What do you think?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] unboxed arrays restricted to simple types (Int, Float, ..)

2009-11-11 Thread Tom Nielsen
There's a couple of things going on here:

-If you use storablevector and storable-tuple, or uvector, you can
store tuples of things. So your stupidArrayElement could be mimicked
by (Int, Int).

-But what you want to do is store a variable-sized data type. How
would you do that in C? If you can spare another bit of memory, it
might be better to define type T = (Bool, Bitmask) and use
storablevector. Or maybe you want a sparse array of Bitmasks?

-Yes it is a shame that Haskell does not have good support for
unbounded polymorphic arrays. What if I want an array of functions?
Here's a little trick that can make it a bit easier to store any data
type in an unboxed array. I don't know, for instance, of any other way
to define unrestricted functor/applicative for unboxed arrays. This
trick should work with any other array library.

{-# LANGUAGE GADTs#-}

module FArray where

import Data.StorableVector
import Foreign.Storable
import Control.Applicative

data EqOrF a b where
Eq :: EqOrF a a
F :: (a-b) - EqOrF a b

data FArray a where
FArray :: Storable a = Vector a - EqOrF a b - FArray b
ConstArr :: a - FArray a

instance Functor FArray where
fmap f (ConstArr x) = ConstArr $ f x
fmap f (FArray sv Eq) = FArray sv $ F f
fmap f (FArray sv (F g)) = FArray sv $ F $ f . g

instance Applicative FArray where
pure x = ConstArr x
(ConstArr f) * farr = fmap f farr
-- other cases left as an exercise. Which is to say, my bladder is
bursting and I also need lunch.

arrayOfInts = FArray (pack [1..10]) Eq
arrayOfAdders = (+) `fmap` arrayOfInts

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