Patrick Perry wrote:
I have the following code:
IOVector n e = IOVector !ConjEnum !Int (ForeignPtr e)! (Ptr e)! Int!
newtype Vector n e = IOVector n e
unsafeAtVector :: Vector n e -> Int -> e
unsafeAtVector (Vector (IOVector c _ f p inc)) i =
let g = if c == Conj then conjugate else id
in inlinePerformIO $ do
e <- peekElemOff p (i*inc)
io <- touchForeignPtr f
let e' = g e
e' `seq` io `seq` return e'
{-# INLINE unsafeAtVector #-}
The Ptr, 'p' is derived from the ForeignPtr, 'f'. For some offset, 'o', it
is defined as:
p = unsafeForeignPtrToPtr f `advancePtr` o
The "touchForeignPtr" is there to keep the garbage collector from
deallocating
the memory before we have a chance to read 'e'. My question is the
following:
Is the `seq` on `io` necessary (from a safety standpoint)? Or am I just
being paranoid?
You're just being paranoid - touchForeignPtr returns a (), so seqing it is
a no-op.
Cheers,
Simon
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe