{-# LANGUAGE UndecidableInstances #-}
module Data.Array.Repa.Eval
(
Elt (..)
, Target (..)
, Load (..)
, LoadRange (..)
, fromList
, computeS, computeP, suspendedComputeP
, copyS, copyP, suspendedCopyP
, now
, fillLinearS
, fillChunkedP
, fillChunkedIOP
, fillInterleavedP
, fillBlock2P
, fillBlock2S
, fillCursoredBlock2S
, fillCursoredBlock2P
, selectChunkedS
, selectChunkedP)
where
import Data.Array.Repa.Eval.Elt
import Data.Array.Repa.Eval.Target
import Data.Array.Repa.Eval.Load
import Data.Array.Repa.Eval.Chunked
import Data.Array.Repa.Eval.Interleaved
import Data.Array.Repa.Eval.Cursored
import Data.Array.Repa.Eval.Selection
import Data.Array.Repa.Repr.Delayed
import Data.Array.Repa.Base
import Data.Array.Repa.Shape
import System.IO.Unsafe
computeP
:: ( Load r1 sh e
, Target r2 e, Source r2 e, Monad m)
=> Array r1 sh e -> m (Array r2 sh e)
computeP arr = now $ suspendedComputeP arr
{-# INLINE [4] computeP #-}
computeS
:: (Load r1 sh e, Target r2 e)
=> Array r1 sh e -> Array r2 sh e
computeS arr1
= arr1 `deepSeqArray`
unsafePerformIO
$ do mvec2 <- newMVec (size $ extent arr1)
loadS arr1 mvec2
unsafeFreezeMVec (extent arr1) mvec2
{-# INLINE [4] computeS #-}
suspendedComputeP
:: (Load r1 sh e, Target r2 e)
=> Array r1 sh e -> Array r2 sh e
suspendedComputeP arr1
= arr1 `deepSeqArray`
unsafePerformIO
$ do mvec2 <- newMVec (size $ extent arr1)
loadP arr1 mvec2
unsafeFreezeMVec (extent arr1) mvec2
{-# INLINE [4] suspendedComputeP #-}
copyP :: ( Source r1 e, Source r2 e
, Load D sh e, Target r2 e
, Monad m)
=> Array r1 sh e -> m (Array r2 sh e)
copyP arr = now $ suspendedCopyP arr
{-# INLINE [4] copyP #-}
copyS :: ( Source r1 e
, Load D sh e, Target r2 e)
=> Array r1 sh e -> Array r2 sh e
copyS arr1 = computeS $ delay arr1
{-# INLINE [4] copyS #-}
suspendedCopyP
:: ( Source r1 e
, Load D sh e, Target r2 e)
=> Array r1 sh e -> Array r2 sh e
suspendedCopyP arr1 = suspendedComputeP $ delay arr1
{-# INLINE [4] suspendedCopyP #-}
now :: (Shape sh, Source r e, Monad m)
=> Array r sh e -> m (Array r sh e)
now arr
= do arr `deepSeqArray` return ()
return arr
{-# INLINE [4] now #-}