module Data.Array.Repa.Index.Outside where
import Control.Applicative
import Control.DeepSeq
import Data.Array.Repa.Index
import Data.Array.Repa.Shape
import GHC.Base (quotInt, remInt)
import Test.QuickCheck
import Test.QuickCheck.All
import qualified Data.Vector.Unboxed as VU
import Data.Vector.Unboxed.Deriving
import Data.Array.Repa.ExtShape
import Data.Array.Repa.Index.Subword hiding (upperTri, subwordIndex, subwordFromIndex)
import qualified Data.Array.Repa.Index.Subword as SW
stage = "Data.Array.Repa.Index.Outside"
newtype Outside = Outside (Int:.Int)
deriving (Eq,Ord,Show)
derivingUnbox "Outside"
[t| Outside -> (Int,Int) |]
[| \ (Outside (i:.j)) -> (i,j) |]
[| \ (i,j) -> Outside (i:.j) |]
outside :: Int -> Int -> Outside
outside i j = Outside (i:.j)
upperTri :: Outside -> Int
upperTri (Outside (i:.j)) = triangularNumber $ ji
subwordIndex :: Outside -> Outside -> Int
subwordIndex (Outside (l:.n)) (Outside (i:.j)) = adr n (i,j)
where
adr n (i,j) = n*i triangularNumber i + j
subwordFromIndex :: Outside -> Int -> Outside
subwordFromIndex = error "not implemented"
instance Shape sh => Shape (sh :. Outside) where
rank (sh :. _)
= rank sh + 1
zeroDim = zeroDim :. Outside (0:.0)
unitDim = unitDim :. Outside (0:.1)
intersectDim (sh1 :. Outside (i:.j)) (sh2 :. Outside (k:.l))
= (intersectDim sh1 sh2 :. Outside (max i k :. min j l))
addDim (sh1 :. Outside (i:.j)) (sh2 :. Outside (k:.l))
= addDim sh1 sh2 :. Outside (i+k:.j+l)
size (sh1 :. sw) = size sh1 * upperTri sw
sizeIsValid (sh1 :. Outside (i:.j))
| size sh1 > 0
= i>=0 && i<=j && j <= maxBound `div` size sh1
| otherwise
= False
toIndex (sh1 :. sh2) (sh1' :. sh2')
= toIndex sh1 sh1' * upperTri sh2 + subwordIndex sh2 sh2'
fromIndex (ds :. d) n = undefined
where
r = subwordFromIndex d n
inShapeRange (zs :. Outside (_:._)) (sh1 :. Outside (l:.n)) (sh2 :. Outside (i:.j))
= i<=j && l<=i && j<n && (inShapeRange zs sh1 sh2)
listOfShape (sh :. Outside (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 :. Outside (i:.j)
deepSeq (sh :. n) x = deepSeq sh (n `seq` x)
instance ExtShape sh => ExtShape (sh:.Outside) where
subDim (sh1:.Outside (i:.j)) (sh2:.Outside (k:.l)) = subDim sh1 sh2 :. Outside (ik:.jl)
rangeList (sh1:.Outside (i:.j)) (sh2:.Outside (k:.l)) = error "not implemented"
instance NFData Outside where
rnf (Outside (i:.j)) = i `seq` rnf j
instance Arbitrary Outside where
arbitrary = do
a <- choose (0,100)
b <- choose (0,100)
return $ Outside (min a b :. max a b)
shrink (Outside (i:.j))
| i<j = [Outside (i:.j1)]
| otherwise = []
instance Arbitrary z => Arbitrary (z:.Outside) where
arbitrary = (:.) <$> arbitrary <*> arbitrary
shrink (z:.s) = (:.) <$> shrink z <*> shrink s