{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE CPP #-}
module Codec.Picture.VectorByteConversion( blitVector
                                         , toByteString
                                         , imageFromUnsafePtr ) where

import Data.Word( Word8 )
import Data.Vector.Storable( Vector, unsafeToForeignPtr, unsafeFromForeignPtr0 )
import Foreign.Storable( Storable, sizeOf )

#if !MIN_VERSION_base(4,8,0)
import Foreign.ForeignPtr.Safe( ForeignPtr, castForeignPtr )
#else
import Foreign.ForeignPtr( ForeignPtr, castForeignPtr )
#endif


import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as S

import Codec.Picture.Types

mkBS :: ForeignPtr Word8 -> Int -> Int -> S.ByteString
#if MIN_VERSION_bytestring(0,11,0)
mkBS fptr off = S.BS (fptr `S.plusForeignPtr` off)
#else
mkBS :: ForeignPtr Word8 -> Int -> Int -> ByteString
mkBS = ForeignPtr Word8 -> Int -> Int -> ByteString
S.PS
#endif

blitVector :: Vector Word8 -> Int -> Int -> B.ByteString
blitVector :: Vector Word8 -> Int -> Int -> ByteString
blitVector Vector Word8
vec Int
atIndex = ForeignPtr Word8 -> Int -> Int -> ByteString
mkBS ForeignPtr Word8
ptr (Int
offset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
atIndex)
  where (ForeignPtr Word8
ptr, Int
offset, Int
_length) = Vector Word8 -> (ForeignPtr Word8, Int, Int)
forall a. Storable a => Vector a -> (ForeignPtr a, Int, Int)
unsafeToForeignPtr Vector Word8
vec

toByteString :: forall a. (Storable a) => Vector a -> B.ByteString
toByteString :: Vector a -> ByteString
toByteString Vector a
vec = ForeignPtr Word8 -> Int -> Int -> ByteString
mkBS (ForeignPtr a -> ForeignPtr Word8
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr ForeignPtr a
ptr) Int
offset (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
size)
  where (ForeignPtr a
ptr, Int
offset, Int
len) = Vector a -> (ForeignPtr a, Int, Int)
forall a. Storable a => Vector a -> (ForeignPtr a, Int, Int)
unsafeToForeignPtr Vector a
vec
        size :: Int
size = a -> Int
forall a. Storable a => a -> Int
sizeOf (a
forall a. HasCallStack => a
undefined :: a)

-- | Import a image from an unsafe pointer

-- The pointer must have a size of width * height * componentCount px

imageFromUnsafePtr :: forall px
                    . (Pixel px, (PixelBaseComponent px) ~ Word8)
                   => Int -- ^ Width in pixels

                   -> Int -- ^ Height in pixels

                   -> ForeignPtr Word8 -- ^ Pointer to the raw data

                   -> Image px
imageFromUnsafePtr :: Int -> Int -> ForeignPtr Word8 -> Image px
imageFromUnsafePtr Int
width Int
height ForeignPtr Word8
ptr =
    Int -> Int -> Vector (PixelBaseComponent px) -> Image px
forall a. Int -> Int -> Vector (PixelBaseComponent a) -> Image a
Image Int
width Int
height (Vector (PixelBaseComponent px) -> Image px)
-> Vector (PixelBaseComponent px) -> Image px
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> Int -> Vector Word8
forall a. Storable a => ForeignPtr a -> Int -> Vector a
unsafeFromForeignPtr0 ForeignPtr Word8
ptr Int
size
      where compCount :: Int
compCount = px -> Int
forall a. Pixel a => a -> Int
componentCount (px
forall a. HasCallStack => a
undefined :: px)
            size :: Int
size = Int
width Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
compCount