{-# LANGUAGE TypeFamilies, TypeOperators, FlexibleInstances #-}
module Data.Array.Repa.Slice
( All (..)
, Any (..)
, FullShape
, SliceShape
, Slice (..))
where
import Data.Array.Repa.Index
import Prelude hiding (replicate, drop)
data All = All
data Any sh = Any
type family FullShape ss
type instance FullShape Z = Z
type instance FullShape (Any sh) = sh
type instance FullShape (sl :. Int) = FullShape sl :. Int
type instance FullShape (sl :. All) = FullShape sl :. Int
type family SliceShape ss
type instance SliceShape Z = Z
type instance SliceShape (Any sh) = sh
type instance SliceShape (sl :. Int) = SliceShape sl
type instance SliceShape (sl :. All) = SliceShape sl :. Int
class Slice ss where
sliceOfFull :: ss -> FullShape ss -> SliceShape ss
fullOfSlice :: ss -> SliceShape ss -> FullShape ss
instance Slice Z where
{-# INLINE [1] sliceOfFull #-}
sliceOfFull _ _ = Z
{-# INLINE [1] fullOfSlice #-}
fullOfSlice _ _ = Z
instance Slice (Any sh) where
{-# INLINE [1] sliceOfFull #-}
sliceOfFull _ sh = sh
{-# INLINE [1] fullOfSlice #-}
fullOfSlice _ sh = sh
instance Slice sl => Slice (sl :. Int) where
{-# INLINE [1] sliceOfFull #-}
sliceOfFull (fsl :. _) (ssl :. _)
= sliceOfFull fsl ssl
{-# INLINE [1] fullOfSlice #-}
fullOfSlice (fsl :. n) ssl
= fullOfSlice fsl ssl :. n
instance Slice sl => Slice (sl :. All) where
{-# INLINE [1] sliceOfFull #-}
sliceOfFull (fsl :. All) (ssl :. s)
= sliceOfFull fsl ssl :. s
{-# INLINE [1] fullOfSlice #-}
fullOfSlice (fsl :. All) (ssl :. s)
= fullOfSlice fsl ssl :. s