Haskell Platform proposal: Add the vector package

Roman Leshchinskiy rl at cse.unsw.edu.au
Tue Jun 19 01:09:36 CEST 2012


On 19/06/2012, at 00:03, Johan Tibell wrote:

> On Mon, Jun 18, 2012 at 3:53 PM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
>> 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.
> 
> (This is off-topic as far as the proposal.)
> 
> ByteString has an extra Ptr field so that accessing the data is fast,
> given that ForeignPtrs can't be unpacked.

ForeignPtrs can be unpacked, just not manually (which is a GHC bug, IMO, I should report it):

data Vector a = Vector {-# UNPACK #-} !Int
                       {-# UNPACK #-} !(ForeignPtr a)

ByteString just has some room for optimisation here ;-)

Roman





More information about the Libraries mailing list