Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 3 additions & 3 deletions repa-algorithms/Data/Array/Repa/Algorithms/DFT/Center.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ import Data.Array.Repa.Algorithms.Complex as R

-- | Apply the centering transform to a vector.
center1d
:: Source r Complex
:: Source r DIM1 Complex
=> Array r DIM1 Complex -> Array D DIM1 Complex
{-# INLINE center1d #-}
center1d arr
Expand All @@ -21,7 +21,7 @@ center1d arr

-- | Apply the centering transform to a matrix.
center2d
:: Source r Complex
:: Source r DIM2 Complex
=> Array r DIM2 Complex -> Array D DIM2 Complex
{-# INLINE center2d #-}
center2d arr
Expand All @@ -31,7 +31,7 @@ center2d arr

-- | Apply the centering transform to a 3d array.
center3d
:: Source r Complex
:: Source r DIM3 Complex
=> Array r DIM3 Complex -> Array D DIM3 Complex
{-# INLINE center3d #-}
center3d arr
Expand Down
16 changes: 8 additions & 8 deletions repa-algorithms/Data/Array/Repa/Algorithms/FFT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ isPowerOfTwo n

-- 3D Transform -----------------------------------------------------------------------------------
-- | Compute the DFT of a 3d array. Array dimensions must be powers of two else `error`.
fft3dP :: (Source r Complex, Monad m)
fft3dP :: (Source r DIM3 Complex, Monad m)
=> Mode
-> Array r DIM3 Complex
-> m (Array U DIM3 Complex)
Expand All @@ -76,7 +76,7 @@ fft3dP mode arr


fftTrans3d
:: Source r Complex
:: Source r DIM3 Complex
=> Double
-> Array r DIM3 Complex
-> Array U DIM3 Complex
Expand All @@ -88,7 +88,7 @@ fftTrans3d sign arr


rotate3d
:: Source r Complex
:: Source r DIM3 Complex
=> Array r DIM3 Complex -> Array D DIM3 Complex
rotate3d arr
= backpermute (sh :. m :. k :. l) f arr
Expand All @@ -100,7 +100,7 @@ rotate3d arr

-- Matrix Transform -------------------------------------------------------------------------------
-- | Compute the DFT of a matrix. Array dimensions must be powers of two else `error`.
fft2dP :: (Source r Complex, Monad m)
fft2dP :: (Source r DIM2 Complex, Monad m)
=> Mode
-> Array r DIM2 Complex
-> m (Array U DIM2 Complex)
Expand All @@ -124,7 +124,7 @@ fft2dP mode arr


fftTrans2d
:: Source r Complex
:: Source r DIM2 Complex
=> Double
-> Array r DIM2 Complex
-> Array U DIM2 Complex
Expand All @@ -137,7 +137,7 @@ fftTrans2d sign arr

-- Vector Transform -------------------------------------------------------------------------------
-- | Compute the DFT of a vector. Array dimensions must be powers of two else `error`.
fft1dP :: (Source r Complex, Monad m)
fft1dP :: (Source r DIM1 Complex, Monad m)
=> Mode
-> Array r DIM1 Complex
-> m (Array U DIM1 Complex)
Expand All @@ -161,7 +161,7 @@ fft1dP mode arr


fftTrans1d
:: Source r Complex
:: Source r DIM1 Complex
=> Double
-> Array r DIM1 Complex
-> Array U DIM1 Complex
Expand All @@ -173,7 +173,7 @@ fftTrans1d sign arr


-- Rank Generalised Worker ------------------------------------------------------------------------
fft :: (Shape sh, Source r Complex)
fft :: (Source r (sh :. Int) Complex)
=> Double -> sh -> Int
-> Array r (sh :. Int) Complex
-> Array U (sh :. Int) Complex
Expand Down
2 changes: 1 addition & 1 deletion repa/Data/Array/Repa/Arbitrary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ instance (Shape a, CoArbitrary a)
=> CoArbitrary (a :. Int) where
coarbitrary (a :. b) = coarbitrary a . coarbitrary b

instance (CoArbitrary sh, CoArbitrary a, Source r a, Shape sh)
instance (CoArbitrary sh, CoArbitrary a, Source r sh a)
=> CoArbitrary (Array r sh a) where
coarbitrary arr
= (coarbitrary . extent $ arr) . (coarbitrary . toList $ arr)
Expand Down
21 changes: 8 additions & 13 deletions repa/Data/Array/Repa/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,18 +8,17 @@ import Data.Array.Repa.Shape

-- Source -----------------------------------------------------------------------
-- | Class of array representations that we can read elements from.
class Source r e where
class Shape sh => Source r sh e where
-- Arrays with a representation tag, shape, and element type.
-- Use one of the type tags like `D`, `U` and so on for @r@,
-- one of `DIM1`, `DIM2` ... for @sh@.
data Array r sh e

-- | O(1). Take the extent (size) of an array.
extent :: Shape sh => Array r sh e -> sh
extent :: Array r sh e -> sh

-- | O(1). Shape polymorphic indexing.
index, unsafeIndex
:: Shape sh => Array r sh e -> sh -> e
index, unsafeIndex :: Array r sh e -> sh -> e

{-# INLINE index #-}
index arr ix = arr `linearIndex` toIndex (extent arr) ix
Expand All @@ -28,25 +27,22 @@ class Source r e where
unsafeIndex arr ix = arr `unsafeLinearIndex` toIndex (extent arr) ix

-- | O(1). Linear indexing into underlying, row-major, array representation.
linearIndex, unsafeLinearIndex
:: Shape sh => Array r sh e -> Int -> e
linearIndex, unsafeLinearIndex :: Array r sh e -> Int -> e

{-# INLINE unsafeLinearIndex #-}
unsafeLinearIndex = linearIndex

-- | Ensure an array's data structure is fully evaluated.
deepSeqArray
:: Shape sh =>Array r sh e -> b -> b
deepSeqArray :: Array r sh e -> b -> b


-- | O(1). Alias for `index`
(!) :: Shape sh => Source r e => Array r sh e -> sh -> e
(!) :: Source r sh e => Array r sh e -> sh -> e
(!) = index


-- | O(n). Convert an array to a list.
toList :: Shape sh => Source r e
=> Array r sh e -> [e]
toList :: Source r sh e => Array r sh e -> [e]
{-# INLINE toList #-}
toList arr
= go 0
Expand Down Expand Up @@ -90,8 +86,7 @@ toList arr
-- If you're not sure, then just follow the example code above.
--
deepSeqArrays
:: Shape sh => Source r e
=> [Array r sh e] -> b -> b
:: Source r sh e => [Array r sh e] -> b -> b
{-# INLINE deepSeqArrays #-}
deepSeqArrays arrs x
= case arrs of
Expand Down
20 changes: 10 additions & 10 deletions repa/Data/Array/Repa/Eval.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,15 +62,15 @@ import System.IO.Unsafe
--
computeP
:: ( Load r1 sh e
, Target r2 e, Source r2 e, Monad m)
, Target r2 sh e, Source r2 sh e, Monad m)
=> Array r1 sh e -> m (Array r2 sh e)
computeP arr = now $ suspendedComputeP arr
{-# INLINE [4] computeP #-}


-- | Sequential computation of array elements.
computeS
:: (Load r1 sh e, Target r2 e)
:: (Load r1 sh e, Target r2 sh e)
=> Array r1 sh e -> Array r2 sh e
computeS arr1
= arr1 `deepSeqArray`
Expand All @@ -93,7 +93,7 @@ computeS arr1
-- that each array is fully evaluated before continuing.
--
suspendedComputeP
:: (Load r1 sh e, Target r2 e)
:: (Load r1 sh e, Target r2 sh e)
=> Array r1 sh e -> Array r2 sh e
suspendedComputeP arr1
= arr1 `deepSeqArray`
Expand All @@ -110,26 +110,26 @@ suspendedComputeP arr1
--
-- * You can use it to copy manifest arrays between representations.
--
copyP :: ( Source r1 e, Source r2 e
, Load D sh e, Target r2 e
copyP :: ( Source r1 sh e, Source r2 sh e
, Load D sh e, Target r2 sh e
, Monad m)
=> Array r1 sh e -> m (Array r2 sh e)
copyP arr = now $ suspendedCopyP arr
{-# INLINE [4] copyP #-}


-- | Sequential copying of arrays.
copyS :: ( Source r1 e
, Load D sh e, Target r2 e)
copyS :: ( Source r1 sh e
, Load D sh e, Target r2 sh e)
=> Array r1 sh e -> Array r2 sh e
copyS arr1 = computeS $ delay arr1
{-# INLINE [4] copyS #-}


-- | Suspended parallel copy of array elements.
suspendedCopyP
:: ( Source r1 e
, Load D sh e, Target r2 e)
:: ( Source r1 sh e
, Load D sh e, Target r2 sh e)
=> Array r1 sh e -> Array r2 sh e
suspendedCopyP arr1 = suspendedComputeP $ delay arr1
{-# INLINE [4] suspendedCopyP #-}
Expand All @@ -146,7 +146,7 @@ suspendedCopyP arr1 = suspendedComputeP $ delay arr1
-- ...
-- @
--
now :: (Shape sh, Source r e, Monad m)
now :: (Shape sh, Source r sh e, Monad m)
=> Array r sh e -> m (Array r sh e)
now arr
= do arr `deepSeqArray` return ()
Expand Down
12 changes: 6 additions & 6 deletions repa/Data/Array/Repa/Eval/Load.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,23 +14,23 @@ import Data.Array.Repa.Base
-- Note that instances require that the source array to have a delayed
-- representation such as `D` or `C`. If you want to use a pre-existing
-- manifest array as the source then `delay` it first.
class (Source r1 e, Shape sh) => Load r1 sh e where
class Source r1 sh e => Load r1 sh e where
-- | Fill an entire array sequentially.
loadS :: Target r2 e => Array r1 sh e -> MVec r2 e -> IO ()
loadS :: Target r2 sh e => Array r1 sh e -> MVec r2 sh e -> IO ()

-- | Fill an entire array in parallel.
loadP :: Target r2 e => Array r1 sh e -> MVec r2 e -> IO ()
loadP :: Target r2 sh e => Array r1 sh e -> MVec r2 sh e -> IO ()


-- FillRange ------------------------------------------------------------------
-- | Compute a range of elements defined by an array and write them to a fillable
-- representation.
class (Source r1 e, Shape sh) => LoadRange r1 sh e where
class Source r1 sh e => LoadRange r1 sh e where
-- | Fill a range of an array sequentially.
loadRangeS :: Target r2 e => Array r1 sh e -> MVec r2 e -> sh -> sh -> IO ()
loadRangeS :: Target r2 sh e => Array r1 sh e -> MVec r2 sh e -> sh -> sh -> IO ()

-- | Fill a range of an array in parallel.
loadRangeP :: Target r2 e => Array r1 sh e -> MVec r2 e -> sh -> sh -> IO ()
loadRangeP :: Target r2 sh e => Array r1 sh e -> MVec r2 sh e -> sh -> sh -> IO ()



17 changes: 8 additions & 9 deletions repa/Data/Array/Repa/Eval/Target.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,31 +11,30 @@ import System.IO.Unsafe

-- Target ---------------------------------------------------------------------
-- | Class of manifest array representations that can be constructed in parallel.
class Target r e where
class Shape sh => Target r sh e where

-- | Mutable version of the representation.
data MVec r e
data MVec r sh e

-- | Allocate a new mutable array of the given size.
newMVec :: Int -> IO (MVec r e)
newMVec :: Int -> IO (MVec r sh e)

-- | Write an element into the mutable array.
unsafeWriteMVec :: MVec r e -> Int -> e -> IO ()
unsafeWriteMVec :: MVec r sh e -> Int -> e -> IO ()

-- | Freeze the mutable array into an immutable Repa array.
unsafeFreezeMVec :: sh -> MVec r e -> IO (Array r sh e)
unsafeFreezeMVec :: sh -> MVec r sh e -> IO (Array r sh e)

-- | Ensure the strucure of a mutable array is fully evaluated.
deepSeqMVec :: MVec r e -> a -> a
deepSeqMVec :: MVec r sh e -> a -> a

-- | Ensure the array is still live at this point.
-- Needed when the mutable array is a ForeignPtr with a finalizer.
touchMVec :: MVec r e -> IO ()
touchMVec :: MVec r sh e -> IO ()


-- | O(n). Construct a manifest array from a list.
fromList :: (Shape sh, Target r e)
=> sh -> [e] -> Array r sh e
fromList :: Target r sh e => sh -> [e] -> Array r sh e
fromList sh xx
= unsafePerformIO
$ do let len = length xx
Expand Down
22 changes: 10 additions & 12 deletions repa/Data/Array/Repa/Operators/IndexSpace.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,8 +24,8 @@ stage = "Data.Array.Repa.Operators.IndexSpace"
-- Index space transformations ------------------------------------------------
-- | Impose a new shape on the elements of an array.
-- The new extent must be the same size as the original, else `error`.
reshape :: ( Shape sh1, Shape sh2
, Source r1 e)
reshape :: ( Shape sh2
, Source r1 sh1 e)
=> sh2
-> Array r1 sh1 e
-> Array D sh2 e
Expand All @@ -43,8 +43,7 @@ reshape sh2 arr

-- | Append two arrays.
append, (++)
:: ( Shape sh
, Source r1 e, Source r2 e)
:: (Source r1 (sh :. Int) e, Source r2 (sh :. Int) e)
=> Array r1 (sh :. Int) e
-> Array r2 (sh :. Int) e
-> Array D (sh :. Int) e
Expand All @@ -70,7 +69,7 @@ append arr1 arr2
-- | Transpose the lowest two dimensions of an array.
-- Transposing an array twice yields the original.
transpose
:: (Shape sh, Source r e)
:: (Source r (sh :. Int :. Int) e)
=> Array r (sh :. Int :. Int) e
-> Array D (sh :. Int :. Int) e

Expand All @@ -82,7 +81,7 @@ transpose arr


-- | Extract a sub-range of elements from an array.
extract :: (Shape sh, Source r e)
extract :: (Source r sh e)
=> sh -- ^ Starting index.
-> sh -- ^ Size of result.
-> Array r sh e
Expand All @@ -95,8 +94,8 @@ extract start sz arr
-- | Backwards permutation of an array's elements.
backpermute, unsafeBackpermute
:: forall r sh1 sh2 e
. ( Shape sh1, Shape sh2
, Source r e)
. ( Shape sh2
, Source r sh1 e)
=> sh2 -- ^ Extent of result array.
-> (sh2 -> sh1) -- ^ Function mapping each index in the result array
-- to an index of the source array.
Expand All @@ -117,8 +116,7 @@ unsafeBackpermute newExtent perm arr
-- from the default array (@arrDft@)
backpermuteDft, unsafeBackpermuteDft
:: forall r1 r2 sh1 sh2 e
. ( Shape sh1, Shape sh2
, Source r1 e, Source r2 e)
. (Source r1 sh1 e, Source r2 sh2 e)
=> Array r2 sh2 e -- ^ Default values (@arrDft@)
-> (sh2 -> Maybe sh1) -- ^ Function mapping each index in the result array
-- to an index in the source array.
Expand Down Expand Up @@ -153,7 +151,7 @@ extend, unsafeExtend
:: ( Slice sl
, Shape (SliceShape sl)
, Shape (FullShape sl)
, Source r e)
, Source r (SliceShape sl) e)
=> sl
-> Array r (SliceShape sl) e
-> Array D (FullShape sl) e
Expand Down Expand Up @@ -188,7 +186,7 @@ slice, unsafeSlice
:: ( Slice sl
, Shape (FullShape sl)
, Shape (SliceShape sl)
, Source r e)
, Source r (FullShape sl) e)
=> Array r (FullShape sl) e
-> sl
-> Array D (SliceShape sl) e
Expand Down
Loading