Haskell Platform proposal: Add the vector package

Bas van Dijk v.dijk.bas at gmail.com
Tue Jun 19 00:53:13 CEST 2012


On Jun 19, 2012 12:16 AM, "Henning Thielemann" <
lemming at henning-thielemann.de> wrote:
>
>
> On Mon, 18 Jun 2012, Roman Leshchinskiy wrote:
>
>> There are type families, rank-n types, unboxed types and other goodies
deep in the guts of vector so the Storable part is very much GHC-specific.
To be honest, I don't think being portable is feasible for high-performance
code at the moment, the language standard simply doesn't have enough tools
for this. Which is a shame, really.
>
>
> I am not mainly interested in the efficient implementation. I am
completely ok with having the definition of (Vector a) in a separate
package, such that it can be used by vector (GHC only) and storablevector
(portable).
>
> However, I have just looked into Vector.Storable and it looks like
>
>  data Vector a = Vector Int (ForeignPtr a)
>
> I thought it was
>
>  data Vector a = Vector {len :: Int, allocated :: ForeignPtr a, start ::
Ptr a}
>
> ByteString looks like:
>
>  data ByteString = PS {allocated :: ForeignPtr Word8, start, length ::
Int}
>
> Both forms allow efficient slicing.
> How do you perform efficient 'take' and 'drop' ?

Slicing is done by directly updating the pointer in the ForeignPtr:

{-# INLINE basicUnsafeSlice #-}
basicUnsafeSlice i n (Vector _ fp) =
    Vector n (updPtr (`advancePtr` i) fp)

{-# INLINE updPtr #-}
updPtr :: (Ptr a -> Ptr a) -> ForeignPtr a -> ForeignPtr a
updPtr f (ForeignPtr p c) =
    case f (Ptr p) of { Ptr q -> ForeignPtr q c }

This saves an Int.

Regards,

Bas
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20120619/553cdbac/attachment.htm>


More information about the Libraries mailing list