Easily generating efficient instances for classes
Christian Höner zu Siederdissen
choener at tbi.univie.ac.at
Wed Feb 24 19:57:44 EST 2010
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)]]
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20100224/e2d13756/attachment.bin
More information about the Glasgow-haskell-users
mailing list