module Data.Array.Repa.Base
( Source (..), (!), toList
, deepSeqArrays)
where
import Data.Array.Repa.Shape
class Source r e where
data Array r sh e
extent :: Shape sh => Array r sh e -> sh
index, unsafeIndex
:: Shape sh => Array r sh e -> sh -> e
{-# INLINE index #-}
index Array r sh e
arr sh
ix = Array r sh e
arr Array r sh e -> Int -> e
forall r e sh. (Source r e, Shape sh) => Array r sh e -> Int -> e
`linearIndex` sh -> sh -> Int
forall sh. Shape sh => sh -> sh -> Int
toIndex (Array r sh e -> sh
forall r e sh. (Source r e, Shape sh) => Array r sh e -> sh
extent Array r sh e
arr) sh
ix
{-# INLINE unsafeIndex #-}
unsafeIndex Array r sh e
arr sh
ix = Array r sh e
arr Array r sh e -> Int -> e
forall r e sh. (Source r e, Shape sh) => Array r sh e -> Int -> e
`unsafeLinearIndex` sh -> sh -> Int
forall sh. Shape sh => sh -> sh -> Int
toIndex (Array r sh e -> sh
forall r e sh. (Source r e, Shape sh) => Array r sh e -> sh
extent Array r sh e
arr) sh
ix
linearIndex, unsafeLinearIndex
:: Shape sh => Array r sh e -> Int -> e
{-# INLINE unsafeLinearIndex #-}
unsafeLinearIndex = Array r sh e -> Int -> e
forall r e sh. (Source r e, Shape sh) => Array r sh e -> Int -> e
linearIndex
deepSeqArray
:: Shape sh =>Array r sh e -> b -> b
(!) :: Shape sh => Source r e => Array r sh e -> sh -> e
(!) = Array r sh e -> sh -> e
forall r e sh. (Source r e, Shape sh) => Array r sh e -> sh -> e
index
toList :: Shape sh => Source r e
=> Array r sh e -> [e]
{-# INLINE toList #-}
toList :: Array r sh e -> [e]
toList Array r sh e
arr
= Int -> [e]
go Int
0
where len :: Int
len = sh -> Int
forall sh. Shape sh => sh -> Int
size (Array r sh e -> sh
forall r e sh. (Source r e, Shape sh) => Array r sh e -> sh
extent Array r sh e
arr)
go :: Int -> [e]
go Int
ix
| Int
ix Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
len = []
| Bool
otherwise = Array r sh e -> Int -> e
forall r e sh. (Source r e, Shape sh) => Array r sh e -> Int -> e
unsafeLinearIndex Array r sh e
arr Int
ix e -> [e] -> [e]
forall a. a -> [a] -> [a]
: Int -> [e]
go (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
deepSeqArrays
:: Shape sh => Source r e
=> [Array r sh e] -> b -> b
{-# INLINE deepSeqArrays #-}
deepSeqArrays :: [Array r sh e] -> b -> b
deepSeqArrays [Array r sh e]
arrs b
x
= case [Array r sh e]
arrs of
[] -> b
x
[Array r sh e
a1]
-> Array r sh e
a1 Array r sh e -> b -> b
forall r e sh b. (Source r e, Shape sh) => Array r sh e -> b -> b
`deepSeqArray` b
x
[Array r sh e
a1, Array r sh e
a2]
-> Array r sh e
a1 Array r sh e -> Array r sh e -> Array r sh e
forall r e sh b. (Source r e, Shape sh) => Array r sh e -> b -> b
`deepSeqArray` Array r sh e
a2 Array r sh e -> b -> b
forall r e sh b. (Source r e, Shape sh) => Array r sh e -> b -> b
`deepSeqArray` b
x
[Array r sh e
a1, Array r sh e
a2, Array r sh e
a3]
-> Array r sh e
a1 Array r sh e -> Array r sh e -> Array r sh e
forall r e sh b. (Source r e, Shape sh) => Array r sh e -> b -> b
`deepSeqArray` Array r sh e
a2 Array r sh e -> Array r sh e -> Array r sh e
forall r e sh b. (Source r e, Shape sh) => Array r sh e -> b -> b
`deepSeqArray` Array r sh e
a3 Array r sh e -> b -> b
forall r e sh b. (Source r e, Shape sh) => Array r sh e -> b -> b
`deepSeqArray` b
x
[Array r sh e
a1, Array r sh e
a2, Array r sh e
a3, Array r sh e
a4]
-> Array r sh e
a1 Array r sh e -> Array r sh e -> Array r sh e
forall r e sh b. (Source r e, Shape sh) => Array r sh e -> b -> b
`deepSeqArray` Array r sh e
a2 Array r sh e -> Array r sh e -> Array r sh e
forall r e sh b. (Source r e, Shape sh) => Array r sh e -> b -> b
`deepSeqArray` Array r sh e
a3 Array r sh e -> Array r sh e -> Array r sh e
forall r e sh b. (Source r e, Shape sh) => Array r sh e -> b -> b
`deepSeqArray` Array r sh e
a4 Array r sh e -> b -> b
forall r e sh b. (Source r e, Shape sh) => Array r sh e -> b -> b
`deepSeqArray` b
x
[Array r sh e]
_ -> [Char] -> b
forall a. HasCallStack => [Char] -> a
error [Char]
"deepSeqArrays: only works for up to four arrays"