{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Graphics.Image.Interface.Repa (
fromRepaArrayS, fromRepaArrayP,
toRepaArray,
RSU(..), RPU(..), RSS(..), RPS(..)
) where
import Data.Array.Repa.Index
import qualified Data.Array.Repa as R
import qualified Data.Vector.Generic as VG
import Graphics.Image.Interface
import Graphics.Image.Interface.Repa.Generic
import Graphics.Image.Interface.Repa.Storable
import Graphics.Image.Interface.Repa.Unboxed
fromRepaArrayS :: R.Source r (Pixel cs e) => R.Array r DIM2 (Pixel cs e) -> Image RSU cs e
fromRepaArrayS = SUImage . fromRepaArrayR
fromRepaArrayP :: R.Source r (Pixel cs e) => R.Array r DIM2 (Pixel cs e) -> Image RPU cs e
fromRepaArrayP = PUImage . fromRepaArrayR
toRepaArray :: Array arr cs e => Image arr cs e -> R.Array R.U DIM2 (Pixel cs e)
toRepaArray img = R.fromUnboxed (ix2sh (dims img)) $ VG.convert $ toVector img