[vector] #31: Bug in unsafeToForeignPtr/unsafeFromForeignPtr
vector
vector at projects.haskell.org
Sat Aug 21 00:43:18 EDT 2010
#31: Bug in unsafeToForeignPtr/unsafeFromForeignPtr
-------------------------------+--------------------------------------------
Reporter: patperry at gmail.com | Owner:
Type: defect | Status: new
Priority: critical | Milestone:
Version: 0.6 | Keywords:
-------------------------------+--------------------------------------------
"unsafeToForeignPtr" and "unsafeFromForeignPtr" disagree on the definition
of the offset. This leads to bugs when these functions are used in
combination with "slice".
Using vector-0.6.0.2 in ghci 6.12.3 on Mac OS 10.6:
{{{
GHCi, version 6.12.3: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude> :m + Data.Vector.Storable
Prelude Data.Vector.Storable> let x = fromList [ 0..3 ]
Loading package primitive-0.3 ... linking ... done.
Loading package array-0.3.0.1 ... linking ... done.
Loading package containers-0.3.0.0 ... linking ... done.
Loading package filepath-1.1.0.4 ... linking ... done.
Loading package old-locale-1.0.0.2 ... linking ... done.
Loading package old-time-1.0.0.5 ... linking ... done.
Loading package unix-2.4.0.2 ... linking ... done.
Loading package directory-1.0.1.1 ... linking ... done.
Loading package pretty-1.0.1.1 ... linking ... done.
Loading package process-1.0.1.3 ... linking ... done.
Loading package Cabal-1.8.0.6 ... linking ... done.
Loading package bytestring-0.9.1.7 ... linking ... done.
Loading package ghc-binary-0.5.0.2 ... linking ... done.
Loading package bin-package-db-0.0.0.0 ... linking ... done.
Loading package hpc-0.5.0.5 ... linking ... done.
Loading package template-haskell ... linking ... done.
Loading package ghc-6.12.3 ... linking ... done.
Loading package vector-0.6.0.2 ... linking ... done.
Prelude Data.Vector.Storable> let y = slice 1 3 x
Prelude Data.Vector.Storable> let (f,o,n) = unsafeToForeignPtr y
Prelude Data.Vector.Storable> let y' = unsafeFromForeignPtr f o n
Prelude Data.Vector.Storable> y
fromList [1.0,2.0,3.0] :: Data.Vector.Storable.Vector
Prelude Data.Vector.Storable> y'
fromList [1.6984055785e-313,0.0,1.0] :: Data.Vector.Storable.Vector
Prelude Data.Vector.Storable> unsafeToForeignPtr y
(0x03188580,-1,3)
Prelude Data.Vector.Storable> unsafeToForeignPtr y'
(0x03188580,1,3)
}}}
The *real* source of the bug is that offsetToPtr and ptrToOffset disagree.
The fix is easy: change the definition of ptrToOffset in
Data.Vector.Storable.Internal from
{{{
ptrToOffset :: Storable a => ForeignPtr a -> Ptr a -> Int
{-# INLINE ptrToOffset #-}
ptrToOffset fp q = unsafeInlineIO
$ withForeignPtr fp $ \p -> return (distance p q)
}}}
to
{{{
ptrToOffset :: Storable a => ForeignPtr a -> Ptr a -> Int
{-# INLINE ptrToOffset #-}
ptrToOffset fp q = unsafeInlineIO
$ withForeignPtr fp $ \p -> return (distance q p)
}}}
--
Ticket URL: <http://trac.haskell.org/vector/ticket/31>
vector <http://trac.haskell.org/vector>
Package vector
More information about the vector
mailing list