[vector] #95: Some tuple elements not unboxed in certain cases
vector
vector at projects.haskell.org
Fri Jun 7 02:12:28 BST 2013
#95: Some tuple elements not unboxed in certain cases
--------------------+-------------------------------------------------------
Reporter: sanketr | Owner:
Type: defect | Status: new
Priority: minor | Milestone:
Version: 0.7 | Keywords:
--------------------+-------------------------------------------------------
For the code below, the append function doesn't unbox the third element of
the tuple.
{{{
{-# LANGUAGE BangPatterns #-}
module Test
where
import Data.Vector.Unboxed.Mutable as MU
import Control.Monad.ST as ST
import Control.Monad.Primitive (PrimState)
data Snakev s = S {-# UNPACK #-}!Int
!(MVector (PrimState (ST s))
(Int,Int,Int))
append :: Snakev s -> (Int,Int,Int) -> ST s (Snakev s)
append (S i v) x = if i < MU.length v then MU.unsafeWrite v i x >> return
(S (i+1) v)
else MU.unsafeGrow v (2 * (MU.length v)) >>= (\y ->
MU.unsafeWrite y i x >> return (S (i+1) y))
gridWalk :: Snakev s -> Int -> ST s (Snakev s)
gridWalk snakesv !k = do
append snakesv (k,k,k)
}}}
If the tuple is of two elements, it is not unboxed at all. For three and
four element tuples that I tried, the last element is always unboxed
unless explicitly forced through a bang pattern like !@x(_,_,!_). The core
for `append` wrapper function has this function signature:
{{{
$wa
:: forall s.
Int#
-> MVector (PrimState (ST s)) (Int, Int, Int)
-> Int#
-> Int#
-> Int
-> State# s
-> (# State# s, Snakev s #)
}}}
Not sure if this is GHC bug, or something specific to vector library
implementation. So, I am filing it here first. I noticed that I need
unsafeGrow function in else block to reproduce the issue.
I am using version 0.10, with ghc 7.6.1
--
Ticket URL: <http://trac.haskell.org/vector/ticket/95>
vector <http://trac.haskell.org/vector>
Package vector
More information about the vector
mailing list