Search code examples
haskellunboxing

Converting a type to unboxed type


I am having trouble converting a type to unboxed type using derivingUnbox. I have tried below code but its giving error "parse error on input '->'" on line [t | Color -> Word32 |]

    type Color = (Word8,Word8,Word8)


    colorToWord32 :: Color -> Word32
    colorToWord32 (r,g,b) = 0 .|. 
                           (shift (fromIntegral r) 24) .|. 
                           (shift (fromIntegral g) 16) .|. 
                           (shift (fromIntegral b) 8)

    word32ToColor :: Word32 -> Color
    word32ToColor color = (r,g,b)
        where
            r = fromIntegral (shift (color .&. 0xFF000000) (-24))
            g = fromIntegral (shift (color .&. 0x00FF0000) (-16))
            b = fromIntegral (shift (color .&. 0x0000FF00) (-8))


    derivingUnbox "Color"
        [t | Color -> Word32 |]
        colorToWord32
        word32ToColor

Solution

  • First, let's fix the quote syntax:

    {-# LANGUAGE
      MultiParamTypeClasses, TemplateHaskell, TypeFamilies, FlexibleInstances #-}
    
    derivingUnbox "Color"
        [t| Color -> Word32 |]
        [| colorToWord32 |]
        [| word32ToColor |]
    

    Second, note that this is still not right, since there is already an unbox instance for (Word8, Word8, Word8). We have to create a new data or newtype if we are to define a new unbox instance.

    import Data.Vector.Unboxed.Deriving
    import Data.Word
    import Data.Bits
    
    data Color = Color !Word8 !Word8 !Word8
    
    colorToWord32 :: Color -> Word32
    colorToWord32 (Color r g b) = 0 .|. 
                           (shift (fromIntegral r) 24) .|. 
                           (shift (fromIntegral g) 16) .|. 
                           (shift (fromIntegral b) 8)
    
    word32ToColor :: Word32 -> Color
    word32ToColor color = Color r g b where
      r = fromIntegral (shift (color .&. 0xFF000000) (-24))
      g = fromIntegral (shift (color .&. 0x00FF0000) (-16))
      b = fromIntegral (shift (color .&. 0x0000FF00) (-8))
    

    Here we rely on the pre-existing unbox instance for Word32. Alternatively, we could just use the unbox instance for (Word8, Word8, Word8):

    import qualified Data.Vector.Unboxed as UV
    type Color = (Word8, Word8, Word8)
    

    Now we can simply use UV.Vector Color.

    Note that the default unbox instance for tuples uses multiple unboxed vectors for the fields instead of using one vector and packing all the fields together (as we've done earlier). It depends on lookup patterns which configuration is faster in practice.