module Data.Array.Repa.Index.Points where
import Control.Applicative
import Control.DeepSeq
import Data.Array.Repa.Index
import Data.Array.Repa.Shape
import Data.Vector.Unboxed.Deriving
import GHC.Base (quotInt, remInt)
import qualified Data.Vector.Unboxed as VU
import Test.QuickCheck
import Test.QuickCheck.All
import Data.Array.Repa.ExtShape
import Data.Array.Repa.Index.Subword
newtype PointL = PointL (Int:.Int)
deriving (Eq,Read,Show)
pointL :: Int -> Int -> PointL
pointL i j = PointL (i:.j)
newtype PointR = PointR (Int:.Int)
pointR :: Int -> Int -> PointR
pointR i j = PointR (i:.j)
derivingUnbox "PointL"
[t| PointL -> (Int,Int) |]
[| \ (PointL (i:.j)) -> (i,j) |]
[| \ (i,j) -> PointL (i:.j) |]
derivingUnbox "PointR"
[t| PointR -> (Int,Int) |]
[| \ (PointR (i:.j)) -> (i,j) |]
[| \ (i,j) -> PointR (i:.j) |]
instance Shape sh => Shape (sh :. PointL) where
rank (sh :. _)
= rank sh + 1
zeroDim = zeroDim :. PointL (0:.0)
unitDim = unitDim :. PointL (0:.1)
intersectDim (sh1 :. PointL (i:.j)) (sh2 :. PointL (k:.l))
= (intersectDim sh1 sh2 :. PointL (max i k :. min j l))
addDim (sh1 :. PointL (i:.j)) (sh2 :. PointL (k:.l))
= addDim sh1 sh2 :. PointL (i+k:.j+l)
size (sh1 :. PointL (i:.j)) = size sh1 * (ji)
sizeIsValid (sh1 :. PointL (i:.j))
| size sh1 > 0
= i>=0 && i<=j && j <= maxBound `div` size sh1
| otherwise
= False
toIndex (sh1 :. PointL(l:.r)) (sh1' :. PointL(i:.j))
= toIndex sh1 sh1' * (rl) + (jl)
fromIndex (ds :. d) n = undefined
where
r = undefined
inShapeRange (zs :. PointL (_:._)) (sh1 :. PointL (l:.n)) (sh2 :. PointL (i:.j))
= i<=j && l<=i && j<n && (inShapeRange zs sh1 sh2)
listOfShape (sh :. PointL (i:.j)) = i : j : listOfShape sh
shapeOfList xx
= case xx of
[] -> error $ stage ++ ".toList: empty list when converting to (_ :. Int)"
[x] -> error $ stage ++ ".toList: only single element remaining!"
i:j:xs -> shapeOfList xs :. PointL (i:.j)
deepSeq (sh :. n) x = deepSeq sh (n `seq` x)
instance ExtShape sh => ExtShape (sh:.PointL) where
subDim (sh1:.PointL (i:.j)) (sh2:.PointL (k:.l)) = subDim sh1 sh2 :. PointL (ik:.jl)
rangeList _ _ = error "PointL:rangeList not implemented"
instance NFData PointL where
rnf (PointL (i:.j)) = i `seq` rnf j
instance Arbitrary PointL where
arbitrary = do
b <- choose (0,100)
return $ pointL 0 b
shrink (PointL (i:.j))
| i<j = [pointL i $ j1]
| otherwise = []
instance Arbitrary z => Arbitrary (z:.PointL) where
arbitrary = (:.) <$> arbitrary <*> arbitrary
shrink (z:.s) = (:.) <$> shrink z <*> shrink s