module Data.Array.Repa.Repr.Vector
        ( V, Array (..)
        , computeVectorS,  computeVectorP
        , fromListVector
        , fromVector
        , toVector)
where
import Data.Array.Repa.Shape
import Data.Array.Repa.Base
import Data.Array.Repa.Eval
import qualified Data.Vector            as V
import qualified Data.Vector.Mutable    as VM
import Control.Monad
data V
        
instance Source V a where
 data Array V sh a
        = AVector !sh !(V.Vector a)
 linearIndex (AVector _ vec) ix
        = vec V.! ix
 
 unsafeLinearIndex (AVector _ vec) ix
        = vec `V.unsafeIndex` ix
 
 extent (AVector sh _)
        = sh
 
 deepSeqArray (AVector sh vec) x 
  = sh `deepSeq` vec `seq` x
 
deriving instance (Show sh, Show e)
        => Show (Array V sh e)
deriving instance (Read sh, Read e)
        => Read (Array V sh e)
instance Target V e where
 data MVec V e 
  = MVector (VM.IOVector e)
 newMVec n
  = liftM MVector (VM.new n)
 
 unsafeWriteMVec (MVector v) ix
  = VM.unsafeWrite v ix
 
 unsafeFreezeMVec sh (MVector mvec)     
  = do  vec     <- V.unsafeFreeze mvec
        return  $  AVector sh vec
 
 deepSeqMVec !_vec x
  = x
 
 touchMVec _ 
  = return ()
 
computeVectorS
        :: Load r1 sh e
        => Array r1 sh e -> Array V sh e
computeVectorS   = computeS
computeVectorP
        :: (Load r1 sh e, Monad m)
        => Array r1 sh e -> m (Array V sh e)
computeVectorP   = computeP
fromListVector :: Shape sh => sh -> [a] -> Array V sh a
fromListVector  = fromList
fromVector :: sh -> V.Vector e -> Array V sh e
fromVector sh vec
        = AVector sh vec
toVector   :: Array V sh e -> V.Vector e
toVector (AVector _ vec)
        = vec