module Data.Array.Repa.Specialised.Dim2
        ( isInside2
        , isOutside2
        , clampToBorder2
        , makeBordered2)
where
import Data.Array.Repa.Index
import Data.Array.Repa.Base
import Data.Array.Repa.Repr.Partitioned
import Data.Array.Repa.Repr.Undefined
isInside2
        :: DIM2         
        -> DIM2         
        -> Bool
isInside2 ex    = not . isOutside2 ex
isOutside2
        :: DIM2         
        -> DIM2         
        -> Bool
isOutside2 (_ :. yLen :. xLen) (_ :. yy :. xx)
        | xx < 0        = True
        | xx >= xLen    = True
        | yy < 0        = True
        | yy >= yLen    = True
        | otherwise     = False
clampToBorder2
        :: DIM2         
        -> DIM2         
        -> DIM2
clampToBorder2 (_ :. yLen :. xLen) (sh :. j :. i)
 = clampX j i
 where  
        clampX !y !x
          | x < 0       = clampY y 0
          | x >= xLen   = clampY y (xLen  1)
          | otherwise   = clampY y x
        
        clampY !y !x
          | y < 0       = sh :. 0          :. x
          | y >= yLen   = sh :. (yLen  1) :. x
          | otherwise   = sh :. y          :. x
makeBordered2
        :: (Source r1 a, Source r2 a)
        => DIM2                 
        -> Int                  
        -> Array r1 DIM2 a      
        -> Array r2 DIM2 a      
        -> Array (P r1 (P r2 (P r2 (P r2 (P r2 X))))) DIM2 a
makeBordered2 sh@(_ :. aHeight :. aWidth) bWidth arrInternal arrBorder
 = checkDims `seq` 
   let
        
        !inX            = bWidth
        !inY            = bWidth
        !inW            = aWidth   2 * bWidth 
        !inH            = aHeight  2 * bWidth
        inInternal (Z :. y :. x)
                =  x >= inX && x < (inX + inW)
                && y >= inY && y < (inY + inH)
        
        inBorder        = not . inInternal
        
   in   
    
        APart sh (Range (Z :. inY     :. inX)       (Z :. inH :. inW )    inInternal) arrInternal
    
    $   APart sh (Range (Z :. 0         :. 0)         (Z :. bWidth :. aWidth) inBorder) arrBorder
    $   APart sh (Range (Z :. inY + inH :. 0)         (Z :. bWidth :. aWidth) inBorder) arrBorder
    $   APart sh (Range (Z :. inY       :. 0)         (Z :. inH    :. bWidth) inBorder) arrBorder
    $   APart sh (Range (Z :. inY       :. inX + inW) (Z :. inH    :. bWidth) inBorder) arrBorder
    $   AUndefined sh
 where
        checkDims
         = if (extent arrInternal) == (extent arrBorder)
                then ()
                else error "makeBordered2: internal and border arrays have different extents"