[Haskell-cafe] Fwd: ANN: vector-buffer package 0.1

Markus Läll markus.l2ll at gmail.com
Tue Feb 15 15:58:08 CET 2011


Hi, Alexander

Here's my take on why the code isnt "right":

In the "let" the "v1" and "v2" get lazyly bound to code that calls
unsafePerformIO. unsafePerformIO does side-effectful things, but works
outside the IO monad and thus outside the main order of IO actions.

If you create a buffer, push something in and make two lists of it -- "v1"
and "v2" -- then they don't get evaluated to concrete lists (weak head
normal form?) right away, but when they are actually needed. So if you print
"v1", "buf" is read and converted into a list (and printed). "v2" stays
unevaluated, but bound to the value of "buf". So if you change "buf", then
"v2" is bound to be different too.

This breaks referential transperency because "v1" and "v2" by theire
definitions should be exactly the same. And the breakage can only happen
because of using unsafePerformIO, which allowes you to go out in the IO
world and get stuff, but bypass the order of evaluation that IO monad forces
you to otherwise have.


Someone correct me if I'm wrong :)


--
Markus Läll


On Tue, Feb 15, 2011 at 8:08 AM, Alexander McPhail <
haskell.vivian.mcphail at gmail.com> wrote:

> Hi list,
>
> Could someone explain why the error pointed out by Luke occurred?
>
> From: Luke Palmer <lrpalmer at gmail.com>
>
> I think this would be a very good question for the list.  Don't worry,
> they're nice helpful folks.
>
> On Mon, Feb 14, 2011 at 10:10 PM, Alexander McPhail
> <haskell.vivian.mcphail at gmail.com> wrote:
> > Hi Roman,
> >
> >
> > Can you explain why the following code doesn't work?  'unsafePerformIO'
> is
> > used all the time in hmatrix.  For example, adding two vectors, we create
> a
> > new Vector then use that as the target for an FFI C call.
> >
> > Is the difference because I'm using mutable Storable Vectors?  I would
> have
> > thought that unsafeFreeze (at the end) would make sure the problem
> reported
> > by Luke wouldn't occur.
> >
> > Is there a problem with laziness in the let binding of Luke's example?
> >
> > I note that in Data.Vector.Storable there is a pure 'convert' function,
> > which is essentially what I am trying to emulate.
> >
> > -- | convert to a vector
> > toVector :: Storable a => Buffer a -> (V.Vector a)
> > toVector (B o n v) = unsafePerformIO $ do
> >    w <- M.new n
> >    i <- readIORef o
> >    M.unsafeWith v $ \p ->
> >        M.unsafeWith w $ \q -> do
> >          let n' = n-i
> >          copyArray q (p `advancePtr` i) n'
> >          if i /= 0
> >             then copyArray (q `advancePtr` n') p i
> >             else return ()
> >    V.unsafeFreeze w
> > {-# INLINE toVector #-}
> >
> >
> > Vivian
> >
> > From: Luke Palmer <lrpalmer at gmail.com>
>
> >
> > This interface is an outlaw.
> >
> > main = do
> >    buf <- newBuffer 10 :: IO (Buffer Int)
> >    pushNextElement buf 1
> >    let v1 = V.toList (toVector buf)
> >        v2 = V.toList (toVector buf)
> >    print v1
> >    pushNextElement buf 2
> >    print v2
> >
> > Despite v1 and v2 being defined to equal the exact same thing, this
> > program prints two distinct lines.
> >
> > toVector depends on the current state of the buffer.  If this is to be
> > a law-abiding interface, toVector must return a value in IO:
> >
> >    toVector :: (Storable a) => Buffer a -> IO (Vector a)
> >
> > Luke
> >
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110215/69f60de8/attachment.htm>


More information about the Haskell-Cafe mailing list