Using newtypes or any data with unboxed Vectors

I think I've managed to come up with an easy, useful, and sound way for mere mortals to use unboxed vectors with arbitrary datatypes, without using template Haskell. I had a need for this capability, googled about it, and I didn't find a satisfying way to do it. This technique seemed useful and simple enough to go into the vector library, but there's so much stuff going on in there I'm not ready to submit a patch. A user just needs to create an UnboxEquivalent instance for their type, and then they can work with what looks and acts like a vector of their type, but is in fact backed by a newtype-wrapped unboxed vector of the equivalent type. newtype SmallPos = Pos Int deriving (Eq, Ord, Show) smallPos :: Int -> SmallPos smallPos x | x > 0 && x < 100 = Pos x | otherwise = error "bad SmallPos" instance UnboxEquivalent SmallPos where type UnboxEquiv SmallPos = Word8 toUnbox (Pos x) = fromIntegral x fromUnbox x = (Pos (fromIntegral x)) test1 :: EVector SmallPos test1 = Data.Vector.Generic.fromList $ map smallPos [5..15] UnboxEquivalent.hs is at http://lpaste.net/136381 Some really simple test code is at http://lpaste.net/136382 I haven't performance tested it, or stuck {-# INLINE #-} annotations in, but I think everything should be optimizing away to nothing, except of course for the toUnbox and fromUnbox calls. What do you think? -Ken

On Sun, 12 Jul 2015, Ken Bateman wrote:
newtype SmallPos = Pos Int deriving (Eq, Ord, Show)
smallPos :: Int -> SmallPos smallPos x | x > 0 && x < 100 = Pos x | otherwise = error "bad SmallPos"
instance UnboxEquivalent SmallPos where type UnboxEquiv SmallPos = Word8 toUnbox (Pos x) = fromIntegral x fromUnbox x = (Pos (fromIntegral x))
I assume that something like this is already possible with the Unbox type class, but currently I cannot see how. :-(
participants (2)
-
Henning Thielemann
-
Ken Bateman