{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Array.Accelerate.IO.Codec.Picture (
imageOfArray,
arrayOfImage,
module Data.Array.Accelerate.IO.Codec.Picture.Types,
) where
import Data.Array.Accelerate hiding ( Vector )
import Data.Array.Accelerate.Sugar.Elt
import Data.Array.Accelerate.IO.Codec.Picture.Types
import Data.Array.Accelerate.IO.Data.Vector.Storable
import Data.Vector.Storable ( Vector )
imageOfArray
:: (Elt pixel, Vector (PixelBaseComponent pixel) ~ Vectors (EltR pixel))
=> Array DIM2 pixel
-> Image pixel
imageOfArray arr =
let Z :. imageHeight :. imageWidth = arrayShape arr
imageData = toVectors arr
in
Image{..}
arrayOfImage
:: (Elt pixel, Vector (PixelBaseComponent pixel) ~ Vectors (EltR pixel))
=> Image pixel
-> Array DIM2 pixel
arrayOfImage Image{..} =
fromVectors (Z :. imageHeight :. imageWidth) imageData