{-# LANGUAGE BangPatterns
           , CPP
           , FlexibleInstances
           , TypeFamilies, MultiParamTypeClasses, FlexibleContexts
           , TypeOperators #-}
module Vision.Primitive.Shape (
      Shape (..), Z (..), (:.) (..)
    
    , DIM0, DIM1, DIM2, DIM3, DIM4, DIM5, DIM6, DIM7, DIM8, DIM9
    
    , ix1, ix2, ix3, ix4, ix5, ix6, ix7, ix8, ix9
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
import Data.Word
#endif
import Foreign.Storable (Storable (..))
import Foreign.Ptr (castPtr, plusPtr)
import Data.Vector.Unboxed (Unbox)
import qualified Data.Vector.Unboxed as VU
import Data.Vector.Generic.Mutable (MVector(..))
import qualified Data.Vector.Generic as VG
class Eq sh => Shape sh where
    
    shapeRank :: sh -> Int
    
    shapeLength :: sh -> Int
    
    shapeZero :: sh
    
    shapeSucc :: sh 
              -> sh 
              -> sh
    
    toLinearIndex :: sh  
                  -> sh  
                  -> Int
    
    fromLinearIndex :: sh  
                    -> Int 
                    -> sh
    
    shapeList :: sh -> [sh]
    
    inShape :: sh   
            -> sh   
            -> Bool
data Z = Z deriving (Int -> Z -> ShowS
[Z] -> ShowS
Z -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Z] -> ShowS
$cshowList :: [Z] -> ShowS
show :: Z -> String
$cshow :: Z -> String
showsPrec :: Int -> Z -> ShowS
$cshowsPrec :: Int -> Z -> ShowS
Show, ReadPrec [Z]
ReadPrec Z
Int -> ReadS Z
ReadS [Z]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Z]
$creadListPrec :: ReadPrec [Z]
readPrec :: ReadPrec Z
$creadPrec :: ReadPrec Z
readList :: ReadS [Z]
$creadList :: ReadS [Z]
readsPrec :: Int -> ReadS Z
$creadsPrec :: Int -> ReadS Z
Read, Z -> Z -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Z -> Z -> Bool
$c/= :: Z -> Z -> Bool
== :: Z -> Z -> Bool
$c== :: Z -> Z -> Bool
Eq, Eq Z
Z -> Z -> Bool
Z -> Z -> Ordering
Z -> Z -> Z
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Z -> Z -> Z
$cmin :: Z -> Z -> Z
max :: Z -> Z -> Z
$cmax :: Z -> Z -> Z
>= :: Z -> Z -> Bool
$c>= :: Z -> Z -> Bool
> :: Z -> Z -> Bool
$c> :: Z -> Z -> Bool
<= :: Z -> Z -> Bool
$c<= :: Z -> Z -> Bool
< :: Z -> Z -> Bool
$c< :: Z -> Z -> Bool
compare :: Z -> Z -> Ordering
$ccompare :: Z -> Z -> Ordering
Ord)
infixl 3 :.
data tail :. head = !tail :. !head
    deriving (Int -> (tail :. head) -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall tail head.
(Show tail, Show head) =>
Int -> (tail :. head) -> ShowS
forall tail head. (Show tail, Show head) => [tail :. head] -> ShowS
forall tail head.
(Show tail, Show head) =>
(tail :. head) -> String
showList :: [tail :. head] -> ShowS
$cshowList :: forall tail head. (Show tail, Show head) => [tail :. head] -> ShowS
show :: (tail :. head) -> String
$cshow :: forall tail head.
(Show tail, Show head) =>
(tail :. head) -> String
showsPrec :: Int -> (tail :. head) -> ShowS
$cshowsPrec :: forall tail head.
(Show tail, Show head) =>
Int -> (tail :. head) -> ShowS
Show, ReadPrec [tail :. head]
ReadPrec (tail :. head)
ReadS [tail :. head]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall tail head. (Read tail, Read head) => ReadPrec [tail :. head]
forall tail head. (Read tail, Read head) => ReadPrec (tail :. head)
forall tail head.
(Read tail, Read head) =>
Int -> ReadS (tail :. head)
forall tail head. (Read tail, Read head) => ReadS [tail :. head]
readListPrec :: ReadPrec [tail :. head]
$creadListPrec :: forall tail head. (Read tail, Read head) => ReadPrec [tail :. head]
readPrec :: ReadPrec (tail :. head)
$creadPrec :: forall tail head. (Read tail, Read head) => ReadPrec (tail :. head)
readList :: ReadS [tail :. head]
$creadList :: forall tail head. (Read tail, Read head) => ReadS [tail :. head]
readsPrec :: Int -> ReadS (tail :. head)
$creadsPrec :: forall tail head.
(Read tail, Read head) =>
Int -> ReadS (tail :. head)
Read, (tail :. head) -> (tail :. head) -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall tail head.
(Eq tail, Eq head) =>
(tail :. head) -> (tail :. head) -> Bool
/= :: (tail :. head) -> (tail :. head) -> Bool
$c/= :: forall tail head.
(Eq tail, Eq head) =>
(tail :. head) -> (tail :. head) -> Bool
== :: (tail :. head) -> (tail :. head) -> Bool
$c== :: forall tail head.
(Eq tail, Eq head) =>
(tail :. head) -> (tail :. head) -> Bool
Eq, (tail :. head) -> (tail :. head) -> Bool
(tail :. head) -> (tail :. head) -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {tail} {head}. (Ord tail, Ord head) => Eq (tail :. head)
forall tail head.
(Ord tail, Ord head) =>
(tail :. head) -> (tail :. head) -> Bool
forall tail head.
(Ord tail, Ord head) =>
(tail :. head) -> (tail :. head) -> Ordering
forall tail head.
(Ord tail, Ord head) =>
(tail :. head) -> (tail :. head) -> tail :. head
min :: (tail :. head) -> (tail :. head) -> tail :. head
$cmin :: forall tail head.
(Ord tail, Ord head) =>
(tail :. head) -> (tail :. head) -> tail :. head
max :: (tail :. head) -> (tail :. head) -> tail :. head
$cmax :: forall tail head.
(Ord tail, Ord head) =>
(tail :. head) -> (tail :. head) -> tail :. head
>= :: (tail :. head) -> (tail :. head) -> Bool
$c>= :: forall tail head.
(Ord tail, Ord head) =>
(tail :. head) -> (tail :. head) -> Bool
> :: (tail :. head) -> (tail :. head) -> Bool
$c> :: forall tail head.
(Ord tail, Ord head) =>
(tail :. head) -> (tail :. head) -> Bool
<= :: (tail :. head) -> (tail :. head) -> Bool
$c<= :: forall tail head.
(Ord tail, Ord head) =>
(tail :. head) -> (tail :. head) -> Bool
< :: (tail :. head) -> (tail :. head) -> Bool
$c< :: forall tail head.
(Ord tail, Ord head) =>
(tail :. head) -> (tail :. head) -> Bool
compare :: (tail :. head) -> (tail :. head) -> Ordering
$ccompare :: forall tail head.
(Ord tail, Ord head) =>
(tail :. head) -> (tail :. head) -> Ordering
Ord)
newtype instance VU.MVector s Z = MV_Z (VU.MVector s ())
newtype instance VU.Vector    Z = V_Z  (VU.Vector    ())
instance MVector VU.MVector Z where
  {-# INLINE basicLength #-}
  basicLength :: forall s. MVector s Z -> Int
basicLength (MV_Z MVector s ()
v)          = forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
basicLength MVector s ()
v
  basicUnsafeSlice :: forall s. Int -> Int -> MVector s Z -> MVector s Z
basicUnsafeSlice Int
s Int
e (MV_Z MVector s ()
v) = forall s. MVector s () -> MVector s Z
MV_Z forall a b. (a -> b) -> a -> b
$ forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
basicUnsafeSlice Int
s Int
e MVector s ()
v
  basicUnsafeRead :: forall s. MVector s Z -> Int -> ST s Z
basicUnsafeRead (MV_Z MVector s ()
v) Int
i    = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s a
basicUnsafeRead  MVector s ()
v Int
i forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \()
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Z
Z
  basicUnsafeNew :: forall s. Int -> ST s (MVector s Z)
basicUnsafeNew   Int
i            = forall s. MVector s () -> MVector s Z
MV_Z forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (v :: * -> * -> *) a s. MVector v a => Int -> ST s (v s a)
basicUnsafeNew Int
i
  basicUnsafeWrite :: forall s. MVector s Z -> Int -> Z -> ST s ()
basicUnsafeWrite (MV_Z MVector s ()
v) Int
i Z
a = Z
a seq :: forall a b. a -> b -> b
`seq` forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> a -> ST s ()
basicUnsafeWrite MVector s ()
v Int
i ()
  basicOverlaps :: forall s. MVector s Z -> MVector s Z -> Bool
basicOverlaps (MV_Z MVector s ()
a) (MV_Z MVector s ()
b) = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
basicOverlaps MVector s ()
a MVector s ()
b
instance VG.Vector VU.Vector Z where
  {-# INLINE basicLength #-}
  basicLength :: Vector Z -> Int
basicLength (V_Z Vector ()
v)          = forall (v :: * -> *) a. Vector v a => v a -> Int
VG.basicLength Vector ()
v
  basicUnsafeFreeze :: forall s. Mutable Vector s Z -> ST s (Vector Z)
basicUnsafeFreeze (MV_Z MVector s ()
v)   = Vector () -> Vector Z
V_Z forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (v :: * -> *) a s. Vector v a => Mutable v s a -> ST s (v a)
VG.basicUnsafeFreeze MVector s ()
v
  basicUnsafeThaw :: forall s. Vector Z -> ST s (Mutable Vector s Z)
basicUnsafeThaw (V_Z Vector ()
v)      = forall s. MVector s () -> MVector s Z
MV_Z forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (v :: * -> *) a s. Vector v a => v a -> ST s (Mutable v s a)
VG.basicUnsafeThaw Vector ()
v
  basicUnsafeSlice :: Int -> Int -> Vector Z -> Vector Z
basicUnsafeSlice Int
s Int
e (V_Z Vector ()
v) = Vector () -> Vector Z
V_Z forall a b. (a -> b) -> a -> b
$ forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
VG.basicUnsafeSlice Int
s Int
e Vector ()
v
  basicUnsafeIndexM :: Vector Z -> Int -> Box Z
basicUnsafeIndexM (V_Z Vector ()
v) Int
i  = forall (v :: * -> *) a. Vector v a => v a -> Int -> Box a
VG.basicUnsafeIndexM Vector ()
v Int
i forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \()
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Z
Z
instance Unbox Z
newtype instance VU.MVector s (t :. h) = MV_Dim (VU.MVector s (t , h))
newtype instance VU.Vector    (t :. h) = V_Dim  (VU.Vector    (t , h))
instance (Unbox t, Unbox h) => MVector VU.MVector (t :. h) where
  {-# INLINE basicLength #-}
  basicLength :: forall s. MVector s (t :. h) -> Int
basicLength (MV_Dim MVector s (t, h)
v)          = forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
basicLength MVector s (t, h)
v
  basicUnsafeSlice :: forall s. Int -> Int -> MVector s (t :. h) -> MVector s (t :. h)
basicUnsafeSlice Int
s Int
e (MV_Dim MVector s (t, h)
v) = forall s t h. MVector s (t, h) -> MVector s (t :. h)
MV_Dim forall a b. (a -> b) -> a -> b
$ forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
basicUnsafeSlice Int
s Int
e MVector s (t, h)
v
  basicUnsafeRead :: forall s. MVector s (t :. h) -> Int -> ST s (t :. h)
basicUnsafeRead (MV_Dim MVector s (t, h)
v) Int
i    = forall tail head. (tail, head) -> tail :. head
pairToPoint forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s a
basicUnsafeRead  MVector s (t, h)
v Int
i
  basicUnsafeNew :: forall s. Int -> ST s (MVector s (t :. h))
basicUnsafeNew   Int
i              = forall s t h. MVector s (t, h) -> MVector s (t :. h)
MV_Dim forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (v :: * -> * -> *) a s. MVector v a => Int -> ST s (v s a)
basicUnsafeNew Int
i
  basicUnsafeWrite :: forall s. MVector s (t :. h) -> Int -> (t :. h) -> ST s ()
basicUnsafeWrite (MV_Dim MVector s (t, h)
v) Int
i t :. h
a = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> a -> ST s ()
basicUnsafeWrite MVector s (t, h)
v Int
i (forall tail head. (tail :. head) -> (tail, head)
pointToPair t :. h
a)
  basicOverlaps :: forall s. MVector s (t :. h) -> MVector s (t :. h) -> Bool
basicOverlaps (MV_Dim MVector s (t, h)
a) (MV_Dim MVector s (t, h)
b) = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
basicOverlaps MVector s (t, h)
a MVector s (t, h)
b
instance (Unbox t, Unbox h) => VG.Vector VU.Vector (t :. h) where
  {-# INLINE basicLength #-}
  basicLength :: Vector (t :. h) -> Int
basicLength (V_Dim Vector (t, h)
v) = forall (v :: * -> *) a. Vector v a => v a -> Int
VG.basicLength Vector (t, h)
v
  basicUnsafeFreeze :: forall s. Mutable Vector s (t :. h) -> ST s (Vector (t :. h))
basicUnsafeFreeze (MV_Dim MVector s (t, h)
v)   = forall t h. Vector (t, h) -> Vector (t :. h)
V_Dim forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (v :: * -> *) a s. Vector v a => Mutable v s a -> ST s (v a)
VG.basicUnsafeFreeze MVector s (t, h)
v
  basicUnsafeThaw :: forall s. Vector (t :. h) -> ST s (Mutable Vector s (t :. h))
basicUnsafeThaw (V_Dim Vector (t, h)
v)      = forall s t h. MVector s (t, h) -> MVector s (t :. h)
MV_Dim forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (v :: * -> *) a s. Vector v a => v a -> ST s (Mutable v s a)
VG.basicUnsafeThaw Vector (t, h)
v
  basicUnsafeSlice :: Int -> Int -> Vector (t :. h) -> Vector (t :. h)
basicUnsafeSlice Int
s Int
e (V_Dim Vector (t, h)
v) = forall t h. Vector (t, h) -> Vector (t :. h)
V_Dim forall a b. (a -> b) -> a -> b
$ forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
VG.basicUnsafeSlice Int
s Int
e Vector (t, h)
v
  basicUnsafeIndexM :: Vector (t :. h) -> Int -> Box (t :. h)
basicUnsafeIndexM (V_Dim Vector (t, h)
v) Int
i  = forall tail head. (tail, head) -> tail :. head
pairToPoint forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (v :: * -> *) a. Vector v a => v a -> Int -> Box a
VG.basicUnsafeIndexM Vector (t, h)
v Int
i
instance (Unbox t, Unbox h) => Unbox (t :. h)
pairToPoint :: (tail, head) -> tail :. head
pairToPoint :: forall tail head. (tail, head) -> tail :. head
pairToPoint (tail
a,head
b) = tail
a forall tail head. tail -> head -> tail :. head
:. head
b
pointToPair :: tail :. head -> (tail, head)
pointToPair :: forall tail head. (tail :. head) -> (tail, head)
pointToPair (tail
a :. head
b) = (tail
a,head
b)
type DIM0 = Z
type DIM1 = DIM0 :. Int
type DIM2 = DIM1 :. Int
type DIM3 = DIM2 :. Int
type DIM4 = DIM3 :. Int
type DIM5 = DIM4 :. Int
type DIM6 = DIM5 :. Int
type DIM7 = DIM6 :. Int
type DIM8 = DIM7 :. Int
type DIM9 = DIM8 :. Int
instance Shape Z where
    shapeRank :: Z -> Int
shapeRank Z
Z = Int
0
    {-# INLINE shapeRank #-}
    shapeLength :: Z -> Int
shapeLength Z
Z = Int
1
    {-# INLINE shapeLength #-}
    shapeZero :: Z
shapeZero = Z
Z
    {-# INLINE shapeZero #-}
    shapeSucc :: Z -> Z -> Z
shapeSucc Z
_ Z
_= Z
Z
    {-# INLINE shapeSucc #-}
    toLinearIndex :: Z -> Z -> Int
toLinearIndex Z
Z Z
_ = Int
0
    {-# INLINE toLinearIndex #-}
    fromLinearIndex :: Z -> Int -> Z
fromLinearIndex Z
Z Int
_ = Z
Z
    {-# INLINE fromLinearIndex #-}
    
    
    
    shapeList :: Z -> [Z]
shapeList Z
Z = [Z
Z]
    {-# INLINE shapeList #-}
    inShape :: Z -> Z -> Bool
inShape Z
Z Z
Z = Bool
True
    {-# INLINE inShape #-}
instance Storable Z where
    sizeOf :: Z -> Int
sizeOf Z
_ = Int
0
    {-# INLINE sizeOf #-}
    alignment :: Z -> Int
alignment Z
_ = Int
0
    {-# INLINE alignment #-}
    peek :: Ptr Z -> IO Z
peek Ptr Z
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Z
Z
    {-# INLINE peek #-}
    poke :: Ptr Z -> Z -> IO ()
poke Ptr Z
_ Z
_ = forall (m :: * -> *) a. Monad m => a -> m a
return ()
    {-# INLINE poke #-}
instance Shape sh => Shape (sh :. Int) where
    shapeRank :: (sh :. Int) -> Int
shapeRank (sh
sh  :. Int
_) = forall sh. Shape sh => sh -> Int
shapeRank sh
sh forall a. Num a => a -> a -> a
+ Int
1
    {-# INLINE shapeRank #-}
    shapeLength :: (sh :. Int) -> Int
shapeLength (sh
sh :. Int
n) = forall sh. Shape sh => sh -> Int
shapeLength sh
sh forall a. Num a => a -> a -> a
* Int
n
    {-# INLINE shapeLength #-}
    shapeZero :: sh :. Int
shapeZero = forall sh. Shape sh => sh
shapeZero forall tail head. tail -> head -> tail :. head
:. Int
0
    {-# INLINE shapeZero #-}
    shapeSucc :: (sh :. Int) -> (sh :. Int) -> sh :. Int
shapeSucc (sh
sh :. Int
n) (sh
sh' :. Int
ix)
        | Int
ix' forall a. Ord a => a -> a -> Bool
>= Int
n  = forall sh. Shape sh => sh -> sh -> sh
shapeSucc sh
sh sh
sh' forall tail head. tail -> head -> tail :. head
:. Int
0
        | Bool
otherwise = sh
sh'              forall tail head. tail -> head -> tail :. head
:. Int
ix'
      where
        !ix' :: Int
ix' = Int
ix forall a. Num a => a -> a -> a
+ Int
1
    {-# INLINE shapeSucc #-}
    toLinearIndex :: (sh :. Int) -> (sh :. Int) -> Int
toLinearIndex (sh
sh :. Int
n) (sh
sh' :. Int
ix) =   forall sh. Shape sh => sh -> sh -> Int
toLinearIndex sh
sh sh
sh' forall a. Num a => a -> a -> a
* Int
n
                                          forall a. Num a => a -> a -> a
+ Int
ix
    {-# INLINE toLinearIndex #-}
    fromLinearIndex :: (sh :. Int) -> Int -> sh :. Int
fromLinearIndex (sh
sh :. Int
n) Int
ix
        | forall sh. Shape sh => sh -> Int
shapeRank sh
sh forall a. Eq a => a -> a -> Bool
== Int
0 = forall sh. Shape sh => sh -> Int -> sh
fromLinearIndex sh
sh Int
0 forall tail head. tail -> head -> tail :. head
:. Int
ix
        | Bool
otherwise         = let (Int
q, Int
r) = Int
ix forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
n
                              in forall sh. Shape sh => sh -> Int -> sh
fromLinearIndex sh
sh Int
q forall tail head. tail -> head -> tail :. head
:. Int
r
    {-# INLINE fromLinearIndex #-}
    shapeList :: (sh :. Int) -> [sh :. Int]
shapeList (sh
sh :. Int
n) = [ sh
sh' forall tail head. tail -> head -> tail :. head
:. Int
i | sh
sh' <- forall sh. Shape sh => sh -> [sh]
shapeList sh
sh, Int
i <- [Int
0..Int
nforall a. Num a => a -> a -> a
-Int
1] ]
    {-# INLINE shapeList #-}
    inShape :: (sh :. Int) -> (sh :. Int) -> Bool
inShape (sh
sh :. Int
n) (sh
sh' :. Int
ix) = forall a. Integral a => a -> Word
word Int
ix forall a. Ord a => a -> a -> Bool
< forall a. Integral a => a -> Word
word Int
n Bool -> Bool -> Bool
&& forall sh. Shape sh => sh -> sh -> Bool
inShape sh
sh sh
sh'
    {-# INLINE inShape #-}
instance Storable sh => Storable (sh :. Int) where
    sizeOf :: (sh :. Int) -> Int
sizeOf ~(sh
sh :. Int
_) = forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int) forall a. Num a => a -> a -> a
+ forall a. Storable a => a -> Int
sizeOf sh
sh
    {-# INLINE sizeOf #-}
    alignment :: (sh :. Int) -> Int
alignment sh :. Int
_ = forall a. Storable a => a -> Int
alignment (forall a. HasCallStack => a
undefined :: Int)
    {-# INLINE alignment #-}
    peek :: Ptr (sh :. Int) -> IO (sh :. Int)
peek !Ptr (sh :. Int)
ptr = do
        let !ptr' :: Ptr Int
ptr' = forall a b. Ptr a -> Ptr b
castPtr Ptr (sh :. Int)
ptr
        forall tail head. tail -> head -> tail :. head
(:.) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek (forall a b. Ptr a -> Ptr b
castPtr forall a b. (a -> b) -> a -> b
$! Ptr Int
ptr' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int)) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr Int
ptr'
    {-# INLINE peek #-}
    poke :: Ptr (sh :. Int) -> (sh :. Int) -> IO ()
poke !Ptr (sh :. Int)
ptr (sh
sh :. Int
n) = do
        let !ptr' :: Ptr Int
ptr' = forall a b. Ptr a -> Ptr b
castPtr Ptr (sh :. Int)
ptr
        forall a. Storable a => Ptr a -> a -> IO ()
poke (forall a b. Ptr a -> Ptr b
castPtr forall a b. (a -> b) -> a -> b
$! Ptr Int
ptr' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` forall a. Storable a => a -> Int
sizeOf Int
n) sh
sh forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Int
ptr' Int
n
    {-# INLINE poke #-}
ix1 :: Int -> DIM1
ix1 :: Int -> DIM1
ix1 Int
x = Z
Z forall tail head. tail -> head -> tail :. head
:. Int
x
{-# INLINE ix1 #-}
ix2 :: Int -> Int -> DIM2
ix2 :: Int -> Int -> DIM2
ix2 Int
y Int
x = Z
Z forall tail head. tail -> head -> tail :. head
:. Int
y forall tail head. tail -> head -> tail :. head
:. Int
x
{-# INLINE ix2 #-}
ix3 :: Int -> Int -> Int -> DIM3
ix3 :: Int -> Int -> Int -> DIM3
ix3 Int
z Int
y Int
x = Z
Z forall tail head. tail -> head -> tail :. head
:. Int
z forall tail head. tail -> head -> tail :. head
:. Int
y forall tail head. tail -> head -> tail :. head
:. Int
x
{-# INLINE ix3 #-}
ix4 :: Int -> Int -> Int -> Int -> DIM4
ix4 :: Int -> Int -> Int -> Int -> DIM4
ix4 Int
a Int
z Int
y Int
x = Z
Z forall tail head. tail -> head -> tail :. head
:. Int
a forall tail head. tail -> head -> tail :. head
:. Int
z forall tail head. tail -> head -> tail :. head
:. Int
y forall tail head. tail -> head -> tail :. head
:. Int
x
{-# INLINE ix4 #-}
ix5 :: Int -> Int -> Int -> Int -> Int -> DIM5
ix5 :: Int -> Int -> Int -> Int -> Int -> DIM5
ix5 Int
b Int
a Int
z Int
y Int
x = Z
Z forall tail head. tail -> head -> tail :. head
:. Int
b forall tail head. tail -> head -> tail :. head
:. Int
a forall tail head. tail -> head -> tail :. head
:. Int
z forall tail head. tail -> head -> tail :. head
:. Int
y forall tail head. tail -> head -> tail :. head
:. Int
x
{-# INLINE ix5 #-}
ix6 :: Int -> Int -> Int -> Int -> Int -> Int -> DIM6
ix6 :: Int -> Int -> Int -> Int -> Int -> Int -> DIM6
ix6 Int
c Int
b Int
a Int
z Int
y Int
x = Z
Z forall tail head. tail -> head -> tail :. head
:. Int
c forall tail head. tail -> head -> tail :. head
:. Int
b forall tail head. tail -> head -> tail :. head
:. Int
a forall tail head. tail -> head -> tail :. head
:. Int
z forall tail head. tail -> head -> tail :. head
:. Int
y forall tail head. tail -> head -> tail :. head
:. Int
x
{-# INLINE ix6 #-}
ix7 :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> DIM7
ix7 :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> DIM7
ix7 Int
d Int
c Int
b Int
a Int
z Int
y Int
x = Z
Z forall tail head. tail -> head -> tail :. head
:. Int
d forall tail head. tail -> head -> tail :. head
:. Int
c forall tail head. tail -> head -> tail :. head
:. Int
b forall tail head. tail -> head -> tail :. head
:. Int
a forall tail head. tail -> head -> tail :. head
:. Int
z forall tail head. tail -> head -> tail :. head
:. Int
y forall tail head. tail -> head -> tail :. head
:. Int
x
{-# INLINE ix7 #-}
ix8 :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> DIM8
ix8 :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> DIM8
ix8 Int
e Int
d Int
c Int
b Int
a Int
z Int
y Int
x = Z
Z forall tail head. tail -> head -> tail :. head
:. Int
e forall tail head. tail -> head -> tail :. head
:. Int
d forall tail head. tail -> head -> tail :. head
:. Int
c forall tail head. tail -> head -> tail :. head
:. Int
b forall tail head. tail -> head -> tail :. head
:. Int
a forall tail head. tail -> head -> tail :. head
:. Int
z forall tail head. tail -> head -> tail :. head
:. Int
y forall tail head. tail -> head -> tail :. head
:. Int
x
{-# INLINE ix8 #-}
ix9 :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> DIM9
ix9 :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> DIM9
ix9 Int
f Int
e Int
d Int
c Int
b Int
a Int
z Int
y Int
x = Z
Z forall tail head. tail -> head -> tail :. head
:. Int
f forall tail head. tail -> head -> tail :. head
:. Int
e forall tail head. tail -> head -> tail :. head
:. Int
d forall tail head. tail -> head -> tail :. head
:. Int
c forall tail head. tail -> head -> tail :. head
:. Int
b forall tail head. tail -> head -> tail :. head
:. Int
a forall tail head. tail -> head -> tail :. head
:. Int
z forall tail head. tail -> head -> tail :. head
:. Int
y forall tail head. tail -> head -> tail :. head
:. Int
x
{-# INLINE ix9 #-}
word :: Integral a => a -> Word
word :: forall a. Integral a => a -> Word
word = forall a b. (Integral a, Num b) => a -> b
fromIntegral