{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Data.Array.Comfort.Shape (
C(..),
Indexed(..),
InvIndexed(..),
Static(..),
Zero(Zero),
ZeroBased(..), zeroBasedSplit,
OneBased(..),
Range(..),
Shifted(..),
Enumeration(..),
Deferred(..), DeferredIndex(..), deferIndex, revealIndex,
(:+:)(..),
Square(..),
Cube(..),
Triangular(..), Lower(Lower), Upper(Upper),
LowerTriangular, UpperTriangular,
lowerTriangular, upperTriangular,
triangleSize, triangleRoot,
Cyclic(..),
) where
import qualified Data.Array.Comfort.Shape.Set as ShapeSet
import Data.Array.Comfort.Shape.Utility (errorIndexFromOffset)
import qualified Foreign.Storable.Newtype as Store
import Foreign.Storable
(Storable, sizeOf, alignment, poke, peek, pokeElemOff, peekElemOff)
import Foreign.Ptr (Ptr, castPtr)
import qualified GHC.Arr as Ix
import qualified Control.Monad.Trans.State as MS
import qualified Control.Monad.HT as Monad
import qualified Control.Applicative.Backwards as Back
import Control.DeepSeq (NFData, rnf)
import Control.Applicative (Applicative, pure, liftA2, liftA3, (<*>))
import Control.Applicative (Const(Const, getConst))
import qualified Data.Traversable as Trav
import qualified Data.Foldable as Fold
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.NonEmpty as NonEmpty
import qualified Data.List as List
import Data.Functor.Identity (Identity(Identity), runIdentity)
import Data.Function.HT (compose2)
import Data.Tagged (Tagged(Tagged, unTagged))
import Data.Map (Map)
import Data.Set (Set)
import Data.List.HT (tails)
import Data.Maybe (fromMaybe)
import Data.Tuple.HT (mapSnd, mapPair, swap, fst3, snd3, thd3)
import Data.Eq.HT (equating)
class C sh where
size :: sh -> Int
uncheckedSize :: sh -> Int
uncheckedSize = sh -> Int
forall sh. C sh => sh -> Int
size
class C sh => Indexed sh where
{-# MINIMAL indices, (sizeOffset|offset), inBounds #-}
type Index sh :: *
indices :: sh -> [Index sh]
offset :: sh -> Index sh -> Int
offset sh
sh = (Int, Index sh -> Int) -> Index sh -> Int
forall a b. (a, b) -> b
snd ((Int, Index sh -> Int) -> Index sh -> Int)
-> (Int, Index sh -> Int) -> Index sh -> Int
forall a b. (a -> b) -> a -> b
$ sh -> (Int, Index sh -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh
sh
uncheckedOffset :: sh -> Index sh -> Int
uncheckedOffset = sh -> Index sh -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset
inBounds :: sh -> Index sh -> Bool
sizeOffset :: sh -> (Int, Index sh -> Int)
sizeOffset sh
sh = (sh -> Int
forall sh. C sh => sh -> Int
size sh
sh, sh -> Index sh -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset sh
sh)
uncheckedSizeOffset :: sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh
sh = (sh -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh
sh, sh -> Index sh -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset sh
sh)
class Indexed sh => InvIndexed sh where
indexFromOffset :: sh -> Int -> Index sh
uncheckedIndexFromOffset :: sh -> Int -> Index sh
uncheckedIndexFromOffset = sh -> Int -> Index sh
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset
class (C sh, Eq sh) => Static sh where
static :: sh
data Zero = Zero
deriving (Zero -> Zero -> Bool
(Zero -> Zero -> Bool) -> (Zero -> Zero -> Bool) -> Eq Zero
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Zero -> Zero -> Bool
$c/= :: Zero -> Zero -> Bool
== :: Zero -> Zero -> Bool
$c== :: Zero -> Zero -> Bool
Eq, Eq Zero
Eq Zero
-> (Zero -> Zero -> Ordering)
-> (Zero -> Zero -> Bool)
-> (Zero -> Zero -> Bool)
-> (Zero -> Zero -> Bool)
-> (Zero -> Zero -> Bool)
-> (Zero -> Zero -> Zero)
-> (Zero -> Zero -> Zero)
-> Ord Zero
Zero -> Zero -> Bool
Zero -> Zero -> Ordering
Zero -> Zero -> Zero
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 :: Zero -> Zero -> Zero
$cmin :: Zero -> Zero -> Zero
max :: Zero -> Zero -> Zero
$cmax :: Zero -> Zero -> Zero
>= :: Zero -> Zero -> Bool
$c>= :: Zero -> Zero -> Bool
> :: Zero -> Zero -> Bool
$c> :: Zero -> Zero -> Bool
<= :: Zero -> Zero -> Bool
$c<= :: Zero -> Zero -> Bool
< :: Zero -> Zero -> Bool
$c< :: Zero -> Zero -> Bool
compare :: Zero -> Zero -> Ordering
$ccompare :: Zero -> Zero -> Ordering
$cp1Ord :: Eq Zero
Ord, Int -> Zero -> ShowS
[Zero] -> ShowS
Zero -> String
(Int -> Zero -> ShowS)
-> (Zero -> String) -> ([Zero] -> ShowS) -> Show Zero
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Zero] -> ShowS
$cshowList :: [Zero] -> ShowS
show :: Zero -> String
$cshow :: Zero -> String
showsPrec :: Int -> Zero -> ShowS
$cshowsPrec :: Int -> Zero -> ShowS
Show)
instance C Zero where
size :: Zero -> Int
size Zero
Zero = Int
0
uncheckedSize :: Zero -> Int
uncheckedSize Zero
Zero = Int
0
instance Static Zero where
static :: Zero
static = Zero
Zero
instance C () where
size :: () -> Int
size () = Int
1
uncheckedSize :: () -> Int
uncheckedSize () = Int
1
instance Indexed () where
type Index () = ()
indices :: () -> [Index ()]
indices () = [()]
offset :: () -> Index () -> Int
offset () () = Int
0
uncheckedOffset :: () -> Index () -> Int
uncheckedOffset () () = Int
0
inBounds :: () -> Index () -> Bool
inBounds () () = Bool
True
instance InvIndexed () where
indexFromOffset :: () -> Int -> Index ()
indexFromOffset () Int
0 = ()
indexFromOffset () Int
k = String -> Int -> ()
forall a. String -> Int -> a
errorIndexFromOffset String
"()" Int
k
uncheckedIndexFromOffset :: () -> Int -> Index ()
uncheckedIndexFromOffset () Int
_ = ()
instance Static () where
static :: ()
static = ()
newtype ZeroBased n = ZeroBased {ZeroBased n -> n
zeroBasedSize :: n}
deriving (ZeroBased n -> ZeroBased n -> Bool
(ZeroBased n -> ZeroBased n -> Bool)
-> (ZeroBased n -> ZeroBased n -> Bool) -> Eq (ZeroBased n)
forall n. Eq n => ZeroBased n -> ZeroBased n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ZeroBased n -> ZeroBased n -> Bool
$c/= :: forall n. Eq n => ZeroBased n -> ZeroBased n -> Bool
== :: ZeroBased n -> ZeroBased n -> Bool
$c== :: forall n. Eq n => ZeroBased n -> ZeroBased n -> Bool
Eq, Int -> ZeroBased n -> ShowS
[ZeroBased n] -> ShowS
ZeroBased n -> String
(Int -> ZeroBased n -> ShowS)
-> (ZeroBased n -> String)
-> ([ZeroBased n] -> ShowS)
-> Show (ZeroBased n)
forall n. Show n => Int -> ZeroBased n -> ShowS
forall n. Show n => [ZeroBased n] -> ShowS
forall n. Show n => ZeroBased n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ZeroBased n] -> ShowS
$cshowList :: forall n. Show n => [ZeroBased n] -> ShowS
show :: ZeroBased n -> String
$cshow :: forall n. Show n => ZeroBased n -> String
showsPrec :: Int -> ZeroBased n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> ZeroBased n -> ShowS
Show)
instance Functor ZeroBased where
fmap :: (a -> b) -> ZeroBased a -> ZeroBased b
fmap a -> b
f (ZeroBased a
n) = b -> ZeroBased b
forall n. n -> ZeroBased n
ZeroBased (b -> ZeroBased b) -> b -> ZeroBased b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
n
instance Applicative ZeroBased where
pure :: a -> ZeroBased a
pure = a -> ZeroBased a
forall n. n -> ZeroBased n
ZeroBased
ZeroBased a -> b
f <*> :: ZeroBased (a -> b) -> ZeroBased a -> ZeroBased b
<*> ZeroBased a
n = b -> ZeroBased b
forall n. n -> ZeroBased n
ZeroBased (b -> ZeroBased b) -> b -> ZeroBased b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
n
instance (NFData n) => NFData (ZeroBased n) where
rnf :: ZeroBased n -> ()
rnf (ZeroBased n
n) = n -> ()
forall a. NFData a => a -> ()
rnf n
n
instance (Storable n) => Storable (ZeroBased n) where
sizeOf :: ZeroBased n -> Int
sizeOf = (ZeroBased n -> n) -> ZeroBased n -> Int
forall core wrapper.
Storable core =>
(wrapper -> core) -> wrapper -> Int
Store.sizeOf ZeroBased n -> n
forall n. ZeroBased n -> n
zeroBasedSize
alignment :: ZeroBased n -> Int
alignment = (ZeroBased n -> n) -> ZeroBased n -> Int
forall core wrapper.
Storable core =>
(wrapper -> core) -> wrapper -> Int
Store.alignment ZeroBased n -> n
forall n. ZeroBased n -> n
zeroBasedSize
peek :: Ptr (ZeroBased n) -> IO (ZeroBased n)
peek = (n -> ZeroBased n) -> Ptr (ZeroBased n) -> IO (ZeroBased n)
forall core wrapper.
Storable core =>
(core -> wrapper) -> Ptr wrapper -> IO wrapper
Store.peek n -> ZeroBased n
forall n. n -> ZeroBased n
ZeroBased
poke :: Ptr (ZeroBased n) -> ZeroBased n -> IO ()
poke = (ZeroBased n -> n) -> Ptr (ZeroBased n) -> ZeroBased n -> IO ()
forall core wrapper.
Storable core =>
(wrapper -> core) -> Ptr wrapper -> wrapper -> IO ()
Store.poke ZeroBased n -> n
forall n. ZeroBased n -> n
zeroBasedSize
instance (Integral n) => C (ZeroBased n) where
size :: ZeroBased n -> Int
size (ZeroBased n
len) = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
len
uncheckedSize :: ZeroBased n -> Int
uncheckedSize (ZeroBased n
len) = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
len
instance (Integral n) => Indexed (ZeroBased n) where
type Index (ZeroBased n) = n
indices :: ZeroBased n -> [Index (ZeroBased n)]
indices (ZeroBased n
len) = Shifted n -> [Index (Shifted n)]
forall sh. Indexed sh => sh -> [Index sh]
indices (Shifted n -> [Index (Shifted n)])
-> Shifted n -> [Index (Shifted n)]
forall a b. (a -> b) -> a -> b
$ n -> n -> Shifted n
forall n. n -> n -> Shifted n
Shifted n
0 n
len
offset :: ZeroBased n -> Index (ZeroBased n) -> Int
offset (ZeroBased n
len) = Shifted n -> Index (Shifted n) -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset (Shifted n -> Index (Shifted n) -> Int)
-> Shifted n -> Index (Shifted n) -> Int
forall a b. (a -> b) -> a -> b
$ n -> n -> Shifted n
forall n. n -> n -> Shifted n
Shifted n
0 n
len
uncheckedOffset :: ZeroBased n -> Index (ZeroBased n) -> Int
uncheckedOffset ZeroBased n
_ Index (ZeroBased n)
ix = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
Index (ZeroBased n)
ix
inBounds :: ZeroBased n -> Index (ZeroBased n) -> Bool
inBounds (ZeroBased n
len) Index (ZeroBased n)
ix = n
0n -> n -> Bool
forall a. Ord a => a -> a -> Bool
<=n
Index (ZeroBased n)
ix Bool -> Bool -> Bool
&& n
Index (ZeroBased n)
ixn -> n -> Bool
forall a. Ord a => a -> a -> Bool
<n
len
instance (Integral n) => InvIndexed (ZeroBased n) where
indexFromOffset :: ZeroBased n -> Int -> Index (ZeroBased n)
indexFromOffset (ZeroBased n
len) Int
k0 =
let k :: n
k = Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k0
in if n
0n -> n -> Bool
forall a. Ord a => a -> a -> Bool
<=n
k Bool -> Bool -> Bool
&& n
kn -> n -> Bool
forall a. Ord a => a -> a -> Bool
<n
len
then n
Index (ZeroBased n)
k
else String -> Int -> n
forall a. String -> Int -> a
errorIndexFromOffset String
"ZeroBased" Int
k0
uncheckedIndexFromOffset :: ZeroBased n -> Int -> Index (ZeroBased n)
uncheckedIndexFromOffset ZeroBased n
_ Int
k = Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k
zeroBasedSplit :: (Real n) => n -> ZeroBased n -> ZeroBased n :+: ZeroBased n
zeroBasedSplit :: n -> ZeroBased n -> ZeroBased n :+: ZeroBased n
zeroBasedSplit n
n (ZeroBased n
m) =
if n
nn -> n -> Bool
forall a. Ord a => a -> a -> Bool
<n
0
then String -> ZeroBased n :+: ZeroBased n
forall a. HasCallStack => String -> a
error String
"Shape.zeroBasedSplit: negative number of elements"
else let k :: n
k = n -> n -> n
forall a. Ord a => a -> a -> a
min n
n n
m in n -> ZeroBased n
forall n. n -> ZeroBased n
ZeroBased n
k ZeroBased n -> ZeroBased n -> ZeroBased n :+: ZeroBased n
forall sh0 sh1. sh0 -> sh1 -> sh0 :+: sh1
:+: n -> ZeroBased n
forall n. n -> ZeroBased n
ZeroBased (n
mn -> n -> n
forall a. Num a => a -> a -> a
-n
k)
newtype OneBased n = OneBased {OneBased n -> n
oneBasedSize :: n}
deriving (OneBased n -> OneBased n -> Bool
(OneBased n -> OneBased n -> Bool)
-> (OneBased n -> OneBased n -> Bool) -> Eq (OneBased n)
forall n. Eq n => OneBased n -> OneBased n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OneBased n -> OneBased n -> Bool
$c/= :: forall n. Eq n => OneBased n -> OneBased n -> Bool
== :: OneBased n -> OneBased n -> Bool
$c== :: forall n. Eq n => OneBased n -> OneBased n -> Bool
Eq, Int -> OneBased n -> ShowS
[OneBased n] -> ShowS
OneBased n -> String
(Int -> OneBased n -> ShowS)
-> (OneBased n -> String)
-> ([OneBased n] -> ShowS)
-> Show (OneBased n)
forall n. Show n => Int -> OneBased n -> ShowS
forall n. Show n => [OneBased n] -> ShowS
forall n. Show n => OneBased n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OneBased n] -> ShowS
$cshowList :: forall n. Show n => [OneBased n] -> ShowS
show :: OneBased n -> String
$cshow :: forall n. Show n => OneBased n -> String
showsPrec :: Int -> OneBased n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> OneBased n -> ShowS
Show)
instance Functor OneBased where
fmap :: (a -> b) -> OneBased a -> OneBased b
fmap a -> b
f (OneBased a
n) = b -> OneBased b
forall n. n -> OneBased n
OneBased (b -> OneBased b) -> b -> OneBased b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
n
instance Applicative OneBased where
pure :: a -> OneBased a
pure = a -> OneBased a
forall n. n -> OneBased n
OneBased
OneBased a -> b
f <*> :: OneBased (a -> b) -> OneBased a -> OneBased b
<*> OneBased a
n = b -> OneBased b
forall n. n -> OneBased n
OneBased (b -> OneBased b) -> b -> OneBased b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
n
instance (NFData n) => NFData (OneBased n) where
rnf :: OneBased n -> ()
rnf (OneBased n
n) = n -> ()
forall a. NFData a => a -> ()
rnf n
n
instance (Storable n) => Storable (OneBased n) where
sizeOf :: OneBased n -> Int
sizeOf = (OneBased n -> n) -> OneBased n -> Int
forall core wrapper.
Storable core =>
(wrapper -> core) -> wrapper -> Int
Store.sizeOf OneBased n -> n
forall n. OneBased n -> n
oneBasedSize
alignment :: OneBased n -> Int
alignment = (OneBased n -> n) -> OneBased n -> Int
forall core wrapper.
Storable core =>
(wrapper -> core) -> wrapper -> Int
Store.alignment OneBased n -> n
forall n. OneBased n -> n
oneBasedSize
peek :: Ptr (OneBased n) -> IO (OneBased n)
peek = (n -> OneBased n) -> Ptr (OneBased n) -> IO (OneBased n)
forall core wrapper.
Storable core =>
(core -> wrapper) -> Ptr wrapper -> IO wrapper
Store.peek n -> OneBased n
forall n. n -> OneBased n
OneBased
poke :: Ptr (OneBased n) -> OneBased n -> IO ()
poke = (OneBased n -> n) -> Ptr (OneBased n) -> OneBased n -> IO ()
forall core wrapper.
Storable core =>
(wrapper -> core) -> Ptr wrapper -> wrapper -> IO ()
Store.poke OneBased n -> n
forall n. OneBased n -> n
oneBasedSize
instance (Integral n) => C (OneBased n) where
size :: OneBased n -> Int
size (OneBased n
len) = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
len
uncheckedSize :: OneBased n -> Int
uncheckedSize (OneBased n
len) = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
len
instance (Integral n) => Indexed (OneBased n) where
type Index (OneBased n) = n
indices :: OneBased n -> [Index (OneBased n)]
indices (OneBased n
len) = Shifted n -> [Index (Shifted n)]
forall sh. Indexed sh => sh -> [Index sh]
indices (Shifted n -> [Index (Shifted n)])
-> Shifted n -> [Index (Shifted n)]
forall a b. (a -> b) -> a -> b
$ n -> n -> Shifted n
forall n. n -> n -> Shifted n
Shifted n
1 n
len
offset :: OneBased n -> Index (OneBased n) -> Int
offset (OneBased n
len) = Shifted n -> Index (Shifted n) -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset (Shifted n -> Index (Shifted n) -> Int)
-> Shifted n -> Index (Shifted n) -> Int
forall a b. (a -> b) -> a -> b
$ n -> n -> Shifted n
forall n. n -> n -> Shifted n
Shifted n
1 n
len
uncheckedOffset :: OneBased n -> Index (OneBased n) -> Int
uncheckedOffset OneBased n
_ Index (OneBased n)
ix = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
Index (OneBased n)
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
inBounds :: OneBased n -> Index (OneBased n) -> Bool
inBounds (OneBased n
len) Index (OneBased n)
ix = n
0n -> n -> Bool
forall a. Ord a => a -> a -> Bool
<n
Index (OneBased n)
ix Bool -> Bool -> Bool
&& n
Index (OneBased n)
ixn -> n -> Bool
forall a. Ord a => a -> a -> Bool
<=n
len
instance (Integral n) => InvIndexed (OneBased n) where
indexFromOffset :: OneBased n -> Int -> Index (OneBased n)
indexFromOffset (OneBased n
len) Int
k0 =
let k :: n
k = Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k0
in if n
0n -> n -> Bool
forall a. Ord a => a -> a -> Bool
<=n
k Bool -> Bool -> Bool
&& n
kn -> n -> Bool
forall a. Ord a => a -> a -> Bool
<n
len
then n
1n -> n -> n
forall a. Num a => a -> a -> a
+n
k
else String -> Int -> n
forall a. String -> Int -> a
errorIndexFromOffset String
"OneBased" Int
k0
uncheckedIndexFromOffset :: OneBased n -> Int -> Index (OneBased n)
uncheckedIndexFromOffset OneBased n
_ Int
k = n
1 n -> n -> n
forall a. Num a => a -> a -> a
+ Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k
data Range n = Range {Range n -> n
rangeFrom, Range n -> n
rangeTo :: n}
deriving (Range n -> Range n -> Bool
(Range n -> Range n -> Bool)
-> (Range n -> Range n -> Bool) -> Eq (Range n)
forall n. Eq n => Range n -> Range n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Range n -> Range n -> Bool
$c/= :: forall n. Eq n => Range n -> Range n -> Bool
== :: Range n -> Range n -> Bool
$c== :: forall n. Eq n => Range n -> Range n -> Bool
Eq, Int -> Range n -> ShowS
[Range n] -> ShowS
Range n -> String
(Int -> Range n -> ShowS)
-> (Range n -> String) -> ([Range n] -> ShowS) -> Show (Range n)
forall n. Show n => Int -> Range n -> ShowS
forall n. Show n => [Range n] -> ShowS
forall n. Show n => Range n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Range n] -> ShowS
$cshowList :: forall n. Show n => [Range n] -> ShowS
show :: Range n -> String
$cshow :: forall n. Show n => Range n -> String
showsPrec :: Int -> Range n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> Range n -> ShowS
Show)
instance Functor Range where
fmap :: (a -> b) -> Range a -> Range b
fmap a -> b
f (Range a
from a
to) = b -> b -> Range b
forall n. n -> n -> Range n
Range (a -> b
f a
from) (a -> b
f a
to)
instance (NFData n) => NFData (Range n) where
rnf :: Range n -> ()
rnf (Range n
from n
to) = (n, n) -> ()
forall a. NFData a => a -> ()
rnf (n
from,n
to)
instance (Ix.Ix n) => C (Range n) where
size :: Range n -> Int
size (Range n
from n
to) = (n, n) -> Int
forall a. Ix a => (a, a) -> Int
Ix.rangeSize (n
from,n
to)
uncheckedSize :: Range n -> Int
uncheckedSize (Range n
from n
to) = (n, n) -> Int
forall a. Ix a => (a, a) -> Int
Ix.unsafeRangeSize (n
from,n
to)
instance (Ix.Ix n) => Indexed (Range n) where
type Index (Range n) = n
indices :: Range n -> [Index (Range n)]
indices (Range n
from n
to) = (n, n) -> [n]
forall a. Ix a => (a, a) -> [a]
Ix.range (n
from,n
to)
offset :: Range n -> Index (Range n) -> Int
offset (Range n
from n
to) Index (Range n)
ix = (n, n) -> n -> Int
forall a. Ix a => (a, a) -> a -> Int
Ix.index (n
from,n
to) n
Index (Range n)
ix
uncheckedOffset :: Range n -> Index (Range n) -> Int
uncheckedOffset (Range n
from n
to) Index (Range n)
ix = (n, n) -> n -> Int
forall a. Ix a => (a, a) -> a -> Int
Ix.unsafeIndex (n
from,n
to) n
Index (Range n)
ix
inBounds :: Range n -> Index (Range n) -> Bool
inBounds (Range n
from n
to) Index (Range n)
ix = (n, n) -> n -> Bool
forall a. Ix a => (a, a) -> a -> Bool
Ix.inRange (n
from,n
to) n
Index (Range n)
ix
instance (Ix.Ix n) => InvIndexed (Range n) where
indexFromOffset :: Range n -> Int -> Index (Range n)
indexFromOffset (Range n
from n
to) Int
k =
if Int
0Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
k Bool -> Bool -> Bool
&& Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< (n, n) -> Int
forall a. Ix a => (a, a) -> Int
Ix.rangeSize (n
from,n
to)
then (n, n) -> [n]
forall a. Ix a => (a, a) -> [a]
Ix.range (n
from,n
to) [n] -> Int -> n
forall a. [a] -> Int -> a
!! Int
k
else String -> Int -> n
forall a. String -> Int -> a
errorIndexFromOffset String
"Range" Int
k
uncheckedIndexFromOffset :: Range n -> Int -> Index (Range n)
uncheckedIndexFromOffset (Range n
from n
to) Int
k = (n, n) -> [n]
forall a. Ix a => (a, a) -> [a]
Ix.range (n
from,n
to) [n] -> Int -> n
forall a. [a] -> Int -> a
!! Int
k
instance Storable n => Storable (Range n) where
{-# INLINE sizeOf #-}
{-# INLINE alignment #-}
{-# INLINE peek #-}
{-# INLINE poke #-}
sizeOf :: Range n -> Int
sizeOf ~(Range n
l n
r) = n -> Int
forall a. Storable a => a -> Int
sizeOf n
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int -> Int
forall a. Integral a => a -> a -> a
mod (- n -> Int
forall a. Storable a => a -> Int
sizeOf n
l) (n -> Int
forall a. Storable a => a -> Int
alignment n
r) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ n -> Int
forall a. Storable a => a -> Int
sizeOf n
r
alignment :: Range n -> Int
alignment ~(Range n
l n
_) = n -> Int
forall a. Storable a => a -> Int
alignment n
l
poke :: Ptr (Range n) -> Range n -> IO ()
poke Ptr (Range n)
p (Range n
l n
r) =
let q :: Ptr n
q = Ptr (Range n) -> Ptr n
forall (f :: * -> *) a. Ptr (f a) -> Ptr a
castToElemPtr Ptr (Range n)
p
in Ptr n -> n -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr n
q n
l IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr n -> Int -> n -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr n
q Int
1 n
r
peek :: Ptr (Range n) -> IO (Range n)
peek Ptr (Range n)
p =
let q :: Ptr n
q = Ptr (Range n) -> Ptr n
forall (f :: * -> *) a. Ptr (f a) -> Ptr a
castToElemPtr Ptr (Range n)
p
in (n -> n -> Range n) -> IO n -> IO n -> IO (Range n)
forall (m :: * -> *) a b r.
Monad m =>
(a -> b -> r) -> m a -> m b -> m r
Monad.lift2 n -> n -> Range n
forall n. n -> n -> Range n
Range (Ptr n -> IO n
forall a. Storable a => Ptr a -> IO a
peek Ptr n
q) (Ptr n -> Int -> IO n
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr n
q Int
1)
data Shifted n = Shifted {Shifted n -> n
shiftedOffset, Shifted n -> n
shiftedSize :: n}
deriving (Shifted n -> Shifted n -> Bool
(Shifted n -> Shifted n -> Bool)
-> (Shifted n -> Shifted n -> Bool) -> Eq (Shifted n)
forall n. Eq n => Shifted n -> Shifted n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Shifted n -> Shifted n -> Bool
$c/= :: forall n. Eq n => Shifted n -> Shifted n -> Bool
== :: Shifted n -> Shifted n -> Bool
$c== :: forall n. Eq n => Shifted n -> Shifted n -> Bool
Eq, Int -> Shifted n -> ShowS
[Shifted n] -> ShowS
Shifted n -> String
(Int -> Shifted n -> ShowS)
-> (Shifted n -> String)
-> ([Shifted n] -> ShowS)
-> Show (Shifted n)
forall n. Show n => Int -> Shifted n -> ShowS
forall n. Show n => [Shifted n] -> ShowS
forall n. Show n => Shifted n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Shifted n] -> ShowS
$cshowList :: forall n. Show n => [Shifted n] -> ShowS
show :: Shifted n -> String
$cshow :: forall n. Show n => Shifted n -> String
showsPrec :: Int -> Shifted n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> Shifted n -> ShowS
Show)
instance Functor Shifted where
fmap :: (a -> b) -> Shifted a -> Shifted b
fmap a -> b
f (Shifted a
from a
to) = b -> b -> Shifted b
forall n. n -> n -> Shifted n
Shifted (a -> b
f a
from) (a -> b
f a
to)
instance (NFData n) => NFData (Shifted n) where
rnf :: Shifted n -> ()
rnf (Shifted n
from n
to) = (n, n) -> ()
forall a. NFData a => a -> ()
rnf (n
from,n
to)
instance (Integral n) => C (Shifted n) where
size :: Shifted n -> Int
size (Shifted n
_offs n
len) = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
len
uncheckedSize :: Shifted n -> Int
uncheckedSize (Shifted n
_offs n
len) = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
len
instance (Integral n) => Indexed (Shifted n) where
type Index (Shifted n) = n
indices :: Shifted n -> [Index (Shifted n)]
indices (Shifted n
offs n
len) =
((n, n) -> n) -> [(n, n)] -> [n]
forall a b. (a -> b) -> [a] -> [b]
map (n, n) -> n
forall a b. (a, b) -> b
snd ([(n, n)] -> [n]) -> [(n, n)] -> [n]
forall a b. (a -> b) -> a -> b
$
((n, n) -> Bool) -> [(n, n)] -> [(n, n)]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile ((n -> n -> Bool
forall a. Ord a => a -> a -> Bool
>n
0) (n -> Bool) -> ((n, n) -> n) -> (n, n) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (n, n) -> n
forall a b. (a, b) -> a
fst) ([(n, n)] -> [(n, n)]) -> [(n, n)] -> [(n, n)]
forall a b. (a -> b) -> a -> b
$
[n] -> [n] -> [(n, n)]
forall a b. [a] -> [b] -> [(a, b)]
zip
((n -> n) -> n -> [n]
forall a. (a -> a) -> a -> [a]
iterate (n -> n -> n
forall a. Num a => a -> a -> a
subtract n
1) n
len)
((n -> n) -> n -> [n]
forall a. (a -> a) -> a -> [a]
iterate (n
1n -> n -> n
forall a. Num a => a -> a -> a
+) n
offs)
offset :: Shifted n -> Index (Shifted n) -> Int
offset (Shifted n
offs n
len) Index (Shifted n)
ix =
if n
Index (Shifted n)
ixn -> n -> Bool
forall a. Ord a => a -> a -> Bool
<n
offs
then String -> Int
forall a. HasCallStack => String -> a
error String
"Shape.Shifted: array index too small"
else
let k :: n
k = n
Index (Shifted n)
ixn -> n -> n
forall a. Num a => a -> a -> a
-n
offs
in if n
kn -> n -> Bool
forall a. Ord a => a -> a -> Bool
<n
len
then n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
k
else String -> Int
forall a. HasCallStack => String -> a
error String
"Shape.Shifted: array index too big"
uncheckedOffset :: Shifted n -> Index (Shifted n) -> Int
uncheckedOffset (Shifted n
offs n
_len) Index (Shifted n)
ix = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (n -> Int) -> n -> Int
forall a b. (a -> b) -> a -> b
$ n
Index (Shifted n)
ixn -> n -> n
forall a. Num a => a -> a -> a
-n
offs
inBounds :: Shifted n -> Index (Shifted n) -> Bool
inBounds (Shifted n
offs n
len) Index (Shifted n)
ix = n
offs n -> n -> Bool
forall a. Ord a => a -> a -> Bool
<= n
Index (Shifted n)
ix Bool -> Bool -> Bool
&& n
Index (Shifted n)
ix n -> n -> Bool
forall a. Ord a => a -> a -> Bool
< n
offsn -> n -> n
forall a. Num a => a -> a -> a
+n
len
instance (Integral n) => InvIndexed (Shifted n) where
indexFromOffset :: Shifted n -> Int -> Index (Shifted n)
indexFromOffset (Shifted n
offs n
len) Int
k0 =
let k :: n
k = Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k0
in if n
0n -> n -> Bool
forall a. Ord a => a -> a -> Bool
<=n
k Bool -> Bool -> Bool
&& n
kn -> n -> Bool
forall a. Ord a => a -> a -> Bool
<n
len
then n
offsn -> n -> n
forall a. Num a => a -> a -> a
+n
k
else String -> Int -> n
forall a. String -> Int -> a
errorIndexFromOffset String
"Shifted" Int
k0
uncheckedIndexFromOffset :: Shifted n -> Int -> Index (Shifted n)
uncheckedIndexFromOffset (Shifted n
offs n
_len) Int
k = n
offs n -> n -> n
forall a. Num a => a -> a -> a
+ Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k
instance Storable n => Storable (Shifted n) where
{-# INLINE sizeOf #-}
{-# INLINE alignment #-}
{-# INLINE peek #-}
{-# INLINE poke #-}
sizeOf :: Shifted n -> Int
sizeOf ~(Shifted n
l n
n) = n -> Int
forall a. Storable a => a -> Int
sizeOf n
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int -> Int
forall a. Integral a => a -> a -> a
mod (- n -> Int
forall a. Storable a => a -> Int
sizeOf n
l) (n -> Int
forall a. Storable a => a -> Int
alignment n
n) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ n -> Int
forall a. Storable a => a -> Int
sizeOf n
n
alignment :: Shifted n -> Int
alignment ~(Shifted n
l n
_) = n -> Int
forall a. Storable a => a -> Int
alignment n
l
poke :: Ptr (Shifted n) -> Shifted n -> IO ()
poke Ptr (Shifted n)
p (Shifted n
l n
n) =
let q :: Ptr n
q = Ptr (Shifted n) -> Ptr n
forall (f :: * -> *) a. Ptr (f a) -> Ptr a
castToElemPtr Ptr (Shifted n)
p
in Ptr n -> n -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr n
q n
l IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr n -> Int -> n -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr n
q Int
1 n
n
peek :: Ptr (Shifted n) -> IO (Shifted n)
peek Ptr (Shifted n)
p =
let q :: Ptr n
q = Ptr (Shifted n) -> Ptr n
forall (f :: * -> *) a. Ptr (f a) -> Ptr a
castToElemPtr Ptr (Shifted n)
p
in (n -> n -> Shifted n) -> IO n -> IO n -> IO (Shifted n)
forall (m :: * -> *) a b r.
Monad m =>
(a -> b -> r) -> m a -> m b -> m r
Monad.lift2 n -> n -> Shifted n
forall n. n -> n -> Shifted n
Shifted (Ptr n -> IO n
forall a. Storable a => Ptr a -> IO a
peek Ptr n
q) (Ptr n -> Int -> IO n
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr n
q Int
1)
{-# INLINE castToElemPtr #-}
castToElemPtr :: Ptr (f a) -> Ptr a
castToElemPtr :: Ptr (f a) -> Ptr a
castToElemPtr = Ptr (f a) -> Ptr a
forall a b. Ptr a -> Ptr b
castPtr
data Enumeration n = Enumeration
deriving (Enumeration n -> Enumeration n -> Bool
(Enumeration n -> Enumeration n -> Bool)
-> (Enumeration n -> Enumeration n -> Bool) -> Eq (Enumeration n)
forall n. Enumeration n -> Enumeration n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Enumeration n -> Enumeration n -> Bool
$c/= :: forall n. Enumeration n -> Enumeration n -> Bool
== :: Enumeration n -> Enumeration n -> Bool
$c== :: forall n. Enumeration n -> Enumeration n -> Bool
Eq, Int -> Enumeration n -> ShowS
[Enumeration n] -> ShowS
Enumeration n -> String
(Int -> Enumeration n -> ShowS)
-> (Enumeration n -> String)
-> ([Enumeration n] -> ShowS)
-> Show (Enumeration n)
forall n. Int -> Enumeration n -> ShowS
forall n. [Enumeration n] -> ShowS
forall n. Enumeration n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Enumeration n] -> ShowS
$cshowList :: forall n. [Enumeration n] -> ShowS
show :: Enumeration n -> String
$cshow :: forall n. Enumeration n -> String
showsPrec :: Int -> Enumeration n -> ShowS
$cshowsPrec :: forall n. Int -> Enumeration n -> ShowS
Show)
instance NFData (Enumeration n) where
rnf :: Enumeration n -> ()
rnf Enumeration n
Enumeration = ()
instance (Enum n, Bounded n) => C (Enumeration n) where
size :: Enumeration n -> Int
size = Enumeration n -> Int
forall sh. C sh => sh -> Int
uncheckedSize
uncheckedSize :: Enumeration n -> Int
uncheckedSize Enumeration n
sh = Enumeration n -> n -> Int
forall n. Enum n => Enumeration n -> n -> Int
intFromEnum Enumeration n
sh n
forall a. Bounded a => a
maxBound Int -> Int -> Int
forall a. Num a => a -> a -> a
- Enumeration n -> n -> Int
forall n. Enum n => Enumeration n -> n -> Int
intFromEnum Enumeration n
sh n
forall a. Bounded a => a
minBound Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
instance (Enum n, Bounded n) => Indexed (Enumeration n) where
type Index (Enumeration n) = n
indices :: Enumeration n -> [Index (Enumeration n)]
indices Enumeration n
sh = [Enumeration n -> n -> n
forall n. Enumeration n -> n -> n
asEnumType Enumeration n
sh n
forall a. Bounded a => a
minBound .. Enumeration n -> n -> n
forall n. Enumeration n -> n -> n
asEnumType Enumeration n
sh n
forall a. Bounded a => a
maxBound]
offset :: Enumeration n -> Index (Enumeration n) -> Int
offset = Enumeration n -> Index (Enumeration n) -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset
uncheckedOffset :: Enumeration n -> Index (Enumeration n) -> Int
uncheckedOffset Enumeration n
sh Index (Enumeration n)
ix = n -> Int
forall a. Enum a => a -> Int
fromEnum n
Index (Enumeration n)
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
- Enumeration n -> n -> Int
forall n. Enum n => Enumeration n -> n -> Int
intFromEnum Enumeration n
sh n
forall a. Bounded a => a
minBound
inBounds :: Enumeration n -> Index (Enumeration n) -> Bool
inBounds Enumeration n
_sh Index (Enumeration n)
_ix = Bool
True
instance (Enum n, Bounded n) => InvIndexed (Enumeration n) where
indexFromOffset :: Enumeration n -> Int -> Index (Enumeration n)
indexFromOffset Enumeration n
sh Int
k =
if Int
0Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
k Bool -> Bool -> Bool
&& Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Enumeration n -> n -> Int
forall n. Enum n => Enumeration n -> n -> Int
intFromEnum Enumeration n
sh n
forall a. Bounded a => a
maxBound Int -> Int -> Int
forall a. Num a => a -> a -> a
- Enumeration n -> n -> Int
forall n. Enum n => Enumeration n -> n -> Int
intFromEnum Enumeration n
sh n
forall a. Bounded a => a
minBound
then Enumeration n -> Int -> Index (Enumeration n)
forall sh. InvIndexed sh => sh -> Int -> Index sh
uncheckedIndexFromOffset Enumeration n
sh Int
k
else String -> Int -> n
forall a. String -> Int -> a
errorIndexFromOffset String
"Enumeration" Int
k
uncheckedIndexFromOffset :: Enumeration n -> Int -> Index (Enumeration n)
uncheckedIndexFromOffset Enumeration n
sh Int
k = Int -> n
forall a. Enum a => Int -> a
toEnum (Int -> n) -> Int -> n
forall a b. (a -> b) -> a -> b
$ Enumeration n -> n -> Int
forall n. Enum n => Enumeration n -> n -> Int
intFromEnum Enumeration n
sh n
forall a. Bounded a => a
minBound Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
k
asEnumType :: Enumeration n -> n -> n
asEnumType :: Enumeration n -> n -> n
asEnumType Enumeration n
Enumeration = n -> n
forall a. a -> a
id
intFromEnum :: (Enum n) => Enumeration n -> n -> Int
Enumeration n
Enumeration = n -> Int
forall a. Enum a => a -> Int
fromEnum
instance (Enum n, Bounded n) => Static (Enumeration n) where
static :: Enumeration n
static = Enumeration n
forall n. Enumeration n
Enumeration
instance Storable (Enumeration n) where
{-# INLINE sizeOf #-}
{-# INLINE alignment #-}
{-# INLINE peek #-}
{-# INLINE poke #-}
sizeOf :: Enumeration n -> Int
sizeOf ~Enumeration n
Enumeration = Int
0
alignment :: Enumeration n -> Int
alignment ~Enumeration n
Enumeration = Int
1
poke :: Ptr (Enumeration n) -> Enumeration n -> IO ()
poke Ptr (Enumeration n)
_p Enumeration n
Enumeration = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
peek :: Ptr (Enumeration n) -> IO (Enumeration n)
peek Ptr (Enumeration n)
_p = Enumeration n -> IO (Enumeration n)
forall (m :: * -> *) a. Monad m => a -> m a
return Enumeration n
forall n. Enumeration n
Enumeration
instance (Ord n) => C (Set n) where
size :: Set n -> Int
size = Set n -> Int
forall sh. C sh => sh -> Int
uncheckedSize
uncheckedSize :: Set n -> Int
uncheckedSize = Set n -> Int
forall a. Set a -> Int
Set.size
instance (Ord n) => Indexed (Set n) where
type Index (Set n) = n
indices :: Set n -> [Index (Set n)]
indices = Set n -> [Index (Set n)]
forall a. Set a -> [a]
Set.toAscList
offset :: Set n -> Index (Set n) -> Int
offset = Set n -> Index (Set n) -> Int
forall a. Ord a => Set a -> a -> Int
ShapeSet.offset
uncheckedOffset :: Set n -> Index (Set n) -> Int
uncheckedOffset = Set n -> Index (Set n) -> Int
forall a. Ord a => Set a -> a -> Int
ShapeSet.uncheckedOffset
inBounds :: Set n -> Index (Set n) -> Bool
inBounds = (n -> Set n -> Bool) -> Set n -> n -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip n -> Set n -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member
instance (Ord n) => InvIndexed (Set n) where
indexFromOffset :: Set n -> Int -> Index (Set n)
indexFromOffset = Set n -> Int -> Index (Set n)
forall a. Set a -> Int -> a
ShapeSet.indexFromOffset
uncheckedIndexFromOffset :: Set n -> Int -> Index (Set n)
uncheckedIndexFromOffset = Set n -> Int -> Index (Set n)
forall a. Set a -> Int -> a
ShapeSet.uncheckedIndexFromOffset
instance (Ord k, C shape) => C (Map k shape) where
size :: Map k shape -> Int
size = Map k Int -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
Fold.sum (Map k Int -> Int)
-> (Map k shape -> Map k Int) -> Map k shape -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (shape -> Int) -> Map k shape -> Map k Int
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map shape -> Int
forall sh. C sh => sh -> Int
size
uncheckedSize :: Map k shape -> Int
uncheckedSize = Map k Int -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
Fold.sum (Map k Int -> Int)
-> (Map k shape -> Map k Int) -> Map k shape -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (shape -> Int) -> Map k shape -> Map k Int
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map shape -> Int
forall sh. C sh => sh -> Int
uncheckedSize
instance (Ord k, Indexed shape) => Indexed (Map k shape) where
type Index (Map k shape) = (k, Index shape)
indices :: Map k shape -> [Index (Map k shape)]
indices =
Map k [(k, Index shape)] -> [(k, Index shape)]
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
Fold.fold (Map k [(k, Index shape)] -> [(k, Index shape)])
-> (Map k shape -> Map k [(k, Index shape)])
-> Map k shape
-> [(k, Index shape)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k -> shape -> [(k, Index shape)])
-> Map k shape -> Map k [(k, Index shape)]
forall k a b. (k -> a -> b) -> Map k a -> Map k b
Map.mapWithKey (\k
k shape
shape -> (Index shape -> (k, Index shape))
-> [Index shape] -> [(k, Index shape)]
forall a b. (a -> b) -> [a] -> [b]
map ((,) k
k) ([Index shape] -> [(k, Index shape)])
-> [Index shape] -> [(k, Index shape)]
forall a b. (a -> b) -> a -> b
$ shape -> [Index shape]
forall sh. Indexed sh => sh -> [Index sh]
indices shape
shape)
offset :: Map k shape -> Index (Map k shape) -> Int
offset Map k shape
m =
let mu :: Map k (Int, shape)
mu = (Int, Map k (Int, shape)) -> Map k (Int, shape)
forall a b. (a, b) -> b
snd ((Int, Map k (Int, shape)) -> Map k (Int, shape))
-> (Int, Map k (Int, shape)) -> Map k (Int, shape)
forall a b. (a -> b) -> a -> b
$ (Int -> shape -> (Int, (Int, shape)))
-> Int -> Map k shape -> (Int, Map k (Int, shape))
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
Trav.mapAccumL (\Int
l shape
sh -> (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ shape -> Int
forall sh. C sh => sh -> Int
size shape
sh, (Int
l,shape
sh))) Int
0 Map k shape
m
in \(k,ix) ->
case k -> Map k (Int, shape) -> Maybe (Int, shape)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup k
k Map k (Int, shape)
mu of
Maybe (Int, shape)
Nothing -> String -> Int
forall a. HasCallStack => String -> a
error String
"Shape.Map.offset: unknown key"
Just (Int
l,shape
sh) -> Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ shape -> Index shape -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset shape
sh Index shape
ix
uncheckedOffset :: Map k shape -> Index (Map k shape) -> Int
uncheckedOffset Map k shape
m =
let mu :: Map k (Int, shape)
mu =
(Int, Map k (Int, shape)) -> Map k (Int, shape)
forall a b. (a, b) -> b
snd ((Int, Map k (Int, shape)) -> Map k (Int, shape))
-> (Int, Map k (Int, shape)) -> Map k (Int, shape)
forall a b. (a -> b) -> a -> b
$ (Int -> shape -> (Int, (Int, shape)))
-> Int -> Map k shape -> (Int, Map k (Int, shape))
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
Trav.mapAccumL (\Int
l shape
sh -> (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ shape -> Int
forall sh. C sh => sh -> Int
uncheckedSize shape
sh, (Int
l,shape
sh))) Int
0 Map k shape
m
in \(k,ix) ->
case k -> Map k (Int, shape) -> Maybe (Int, shape)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup k
k Map k (Int, shape)
mu of
Maybe (Int, shape)
Nothing -> String -> Int
forall a. HasCallStack => String -> a
error String
"Shape.Map.uncheckedOffset: unknown key"
Just (Int
l,shape
sh) -> Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ shape -> Index shape -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset shape
sh Index shape
ix
inBounds :: Map k shape -> Index (Map k shape) -> Bool
inBounds Map k shape
m (k,ix) = (shape -> Bool) -> Maybe shape -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
Fold.any ((shape -> Index shape -> Bool) -> Index shape -> shape -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip shape -> Index shape -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds Index shape
ix) (Maybe shape -> Bool) -> Maybe shape -> Bool
forall a b. (a -> b) -> a -> b
$ k -> Map k shape -> Maybe shape
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup k
k Map k shape
m
sizeOffset :: Map k shape -> (Int, Index (Map k shape) -> Int)
sizeOffset = Map k (Int, Index shape -> Int) -> (Int, (k, Index shape) -> Int)
forall k i ix.
(Ord k, Num i) =>
Map k (i, ix -> i) -> (i, (k, ix) -> i)
mapSizeOffset (Map k (Int, Index shape -> Int) -> (Int, (k, Index shape) -> Int))
-> (Map k shape -> Map k (Int, Index shape -> Int))
-> Map k shape
-> (Int, (k, Index shape) -> Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (shape -> (Int, Index shape -> Int))
-> Map k shape -> Map k (Int, Index shape -> Int)
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map shape -> (Int, Index shape -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset
uncheckedSizeOffset :: Map k shape -> (Int, Index (Map k shape) -> Int)
uncheckedSizeOffset = Map k (Int, Index shape -> Int) -> (Int, (k, Index shape) -> Int)
forall k i ix.
(Ord k, Num i) =>
Map k (i, ix -> i) -> (i, (k, ix) -> i)
mapSizeOffset (Map k (Int, Index shape -> Int) -> (Int, (k, Index shape) -> Int))
-> (Map k shape -> Map k (Int, Index shape -> Int))
-> Map k shape
-> (Int, (k, Index shape) -> Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (shape -> (Int, Index shape -> Int))
-> Map k shape -> Map k (Int, Index shape -> Int)
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map shape -> (Int, Index shape -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset
{-# INLINE mapSizeOffset #-}
mapSizeOffset :: (Ord k, Num i) => Map k (i, ix -> i) -> (i, (k, ix) -> i)
mapSizeOffset :: Map k (i, ix -> i) -> (i, (k, ix) -> i)
mapSizeOffset Map k (i, ix -> i)
ms =
(Map k i -> i
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
Fold.sum (Map k i -> i) -> Map k i -> i
forall a b. (a -> b) -> a -> b
$ ((i, ix -> i) -> i) -> Map k (i, ix -> i) -> Map k i
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (i, ix -> i) -> i
forall a b. (a, b) -> a
fst Map k (i, ix -> i)
ms,
let mu :: Map k (ix -> i)
mu = (i, Map k (ix -> i)) -> Map k (ix -> i)
forall a b. (a, b) -> b
snd ((i, Map k (ix -> i)) -> Map k (ix -> i))
-> (i, Map k (ix -> i)) -> Map k (ix -> i)
forall a b. (a -> b) -> a -> b
$ (i -> (i, ix -> i) -> (i, ix -> i))
-> i -> Map k (i, ix -> i) -> (i, Map k (ix -> i))
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
Trav.mapAccumL (\i
l (i
sz,ix -> i
offs) -> (i
l i -> i -> i
forall a. Num a => a -> a -> a
+ i
sz, (i
li -> i -> i
forall a. Num a => a -> a -> a
+) (i -> i) -> (ix -> i) -> ix -> i
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> i
offs)) i
0 Map k (i, ix -> i)
ms
in \(k
k,ix
ix) ->
(ix -> i) -> Maybe (ix -> i) -> ix -> i
forall a. a -> Maybe a -> a
fromMaybe (String -> ix -> i
forall a. HasCallStack => String -> a
error String
"Shape.Map.sizeOffset: unknown key")
(k -> Map k (ix -> i) -> Maybe (ix -> i)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup k
k Map k (ix -> i)
mu) ix
ix)
instance (Ord k, InvIndexed shape) => InvIndexed (Map k shape) where
indexFromOffset :: Map k shape -> Int -> Index (Map k shape)
indexFromOffset Map k shape
m Int
i =
(\[(Int, (k, Index shape))]
xs ->
case [(Int, (k, Index shape))]
xs of
(Int
_u,(k, Index shape)
ix):[(Int, (k, Index shape))]
_ -> (k, Index shape)
ix
[] -> String -> Int -> (k, Index shape)
forall a. String -> Int -> a
errorIndexFromOffset String
"Map" Int
i) ([(Int, (k, Index shape))] -> (k, Index shape))
-> [(Int, (k, Index shape))] -> (k, Index shape)
forall a b. (a -> b) -> a -> b
$
((Int, (k, Index shape)) -> Bool)
-> [(Int, (k, Index shape))] -> [(Int, (k, Index shape))]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (\(Int
u,(k, Index shape)
_ix) -> Int
uInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
i) ([(Int, (k, Index shape))] -> [(Int, (k, Index shape))])
-> [(Int, (k, Index shape))] -> [(Int, (k, Index shape))]
forall a b. (a -> b) -> a -> b
$ (Int, [(Int, (k, Index shape))]) -> [(Int, (k, Index shape))]
forall a b. (a, b) -> b
snd ((Int, [(Int, (k, Index shape))]) -> [(Int, (k, Index shape))])
-> (Int, [(Int, (k, Index shape))]) -> [(Int, (k, Index shape))]
forall a b. (a -> b) -> a -> b
$
(Int -> (k, shape) -> (Int, (Int, (k, Index shape))))
-> Int -> [(k, shape)] -> (Int, [(Int, (k, Index shape))])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
List.mapAccumL
(\Int
l (k
k,shape
sh) ->
let u :: Int
u = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ shape -> Int
forall sh. C sh => sh -> Int
size shape
sh
in (Int
u, (Int
u, (k
k, shape -> Int -> Index shape
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset shape
sh (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l))))) Int
0 ([(k, shape)] -> (Int, [(Int, (k, Index shape))]))
-> [(k, shape)] -> (Int, [(Int, (k, Index shape))])
forall a b. (a -> b) -> a -> b
$
Map k shape -> [(k, shape)]
forall k a. Map k a -> [(k, a)]
Map.toAscList Map k shape
m
uncheckedIndexFromOffset :: Map k shape -> Int -> Index (Map k shape)
uncheckedIndexFromOffset Map k shape
m Int
i =
(\((Int
_u,(k, Index shape)
ix):[(Int, (k, Index shape))]
_) -> (k, Index shape)
ix) ([(Int, (k, Index shape))] -> (k, Index shape))
-> [(Int, (k, Index shape))] -> (k, Index shape)
forall a b. (a -> b) -> a -> b
$
((Int, (k, Index shape)) -> Bool)
-> [(Int, (k, Index shape))] -> [(Int, (k, Index shape))]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (\(Int
u,(k, Index shape)
_ix) -> Int
uInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
i) ([(Int, (k, Index shape))] -> [(Int, (k, Index shape))])
-> [(Int, (k, Index shape))] -> [(Int, (k, Index shape))]
forall a b. (a -> b) -> a -> b
$ (Int, [(Int, (k, Index shape))]) -> [(Int, (k, Index shape))]
forall a b. (a, b) -> b
snd ((Int, [(Int, (k, Index shape))]) -> [(Int, (k, Index shape))])
-> (Int, [(Int, (k, Index shape))]) -> [(Int, (k, Index shape))]
forall a b. (a -> b) -> a -> b
$
(Int -> (k, shape) -> (Int, (Int, (k, Index shape))))
-> Int -> [(k, shape)] -> (Int, [(Int, (k, Index shape))])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
List.mapAccumL
(\Int
l (k
k,shape
sh) ->
let u :: Int
u = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ shape -> Int
forall sh. C sh => sh -> Int
size shape
sh
in (Int
u, (Int
u, (k
k, shape -> Int -> Index shape
forall sh. InvIndexed sh => sh -> Int -> Index sh
uncheckedIndexFromOffset shape
sh (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l))))) Int
0 ([(k, shape)] -> (Int, [(Int, (k, Index shape))]))
-> [(k, shape)] -> (Int, [(Int, (k, Index shape))])
forall a b. (a -> b) -> a -> b
$
Map k shape -> [(k, shape)]
forall k a. Map k a -> [(k, a)]
Map.toAscList Map k shape
m
newtype Deferred sh = Deferred sh
deriving (Deferred sh -> Deferred sh -> Bool
(Deferred sh -> Deferred sh -> Bool)
-> (Deferred sh -> Deferred sh -> Bool) -> Eq (Deferred sh)
forall sh. Eq sh => Deferred sh -> Deferred sh -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Deferred sh -> Deferred sh -> Bool
$c/= :: forall sh. Eq sh => Deferred sh -> Deferred sh -> Bool
== :: Deferred sh -> Deferred sh -> Bool
$c== :: forall sh. Eq sh => Deferred sh -> Deferred sh -> Bool
Eq, Int -> Deferred sh -> ShowS
[Deferred sh] -> ShowS
Deferred sh -> String
(Int -> Deferred sh -> ShowS)
-> (Deferred sh -> String)
-> ([Deferred sh] -> ShowS)
-> Show (Deferred sh)
forall sh. Show sh => Int -> Deferred sh -> ShowS
forall sh. Show sh => [Deferred sh] -> ShowS
forall sh. Show sh => Deferred sh -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Deferred sh] -> ShowS
$cshowList :: forall sh. Show sh => [Deferred sh] -> ShowS
show :: Deferred sh -> String
$cshow :: forall sh. Show sh => Deferred sh -> String
showsPrec :: Int -> Deferred sh -> ShowS
$cshowsPrec :: forall sh. Show sh => Int -> Deferred sh -> ShowS
Show)
newtype DeferredIndex sh = DeferredIndex Int
deriving (DeferredIndex sh -> DeferredIndex sh -> Bool
(DeferredIndex sh -> DeferredIndex sh -> Bool)
-> (DeferredIndex sh -> DeferredIndex sh -> Bool)
-> Eq (DeferredIndex sh)
forall sh. DeferredIndex sh -> DeferredIndex sh -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeferredIndex sh -> DeferredIndex sh -> Bool
$c/= :: forall sh. DeferredIndex sh -> DeferredIndex sh -> Bool
== :: DeferredIndex sh -> DeferredIndex sh -> Bool
$c== :: forall sh. DeferredIndex sh -> DeferredIndex sh -> Bool
Eq, Eq (DeferredIndex sh)
Eq (DeferredIndex sh)
-> (DeferredIndex sh -> DeferredIndex sh -> Ordering)
-> (DeferredIndex sh -> DeferredIndex sh -> Bool)
-> (DeferredIndex sh -> DeferredIndex sh -> Bool)
-> (DeferredIndex sh -> DeferredIndex sh -> Bool)
-> (DeferredIndex sh -> DeferredIndex sh -> Bool)
-> (DeferredIndex sh -> DeferredIndex sh -> DeferredIndex sh)
-> (DeferredIndex sh -> DeferredIndex sh -> DeferredIndex sh)
-> Ord (DeferredIndex sh)
DeferredIndex sh -> DeferredIndex sh -> Bool
DeferredIndex sh -> DeferredIndex sh -> Ordering
DeferredIndex sh -> DeferredIndex sh -> DeferredIndex sh
forall sh. Eq (DeferredIndex sh)
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 sh. DeferredIndex sh -> DeferredIndex sh -> Bool
forall sh. DeferredIndex sh -> DeferredIndex sh -> Ordering
forall sh. DeferredIndex sh -> DeferredIndex sh -> DeferredIndex sh
min :: DeferredIndex sh -> DeferredIndex sh -> DeferredIndex sh
$cmin :: forall sh. DeferredIndex sh -> DeferredIndex sh -> DeferredIndex sh
max :: DeferredIndex sh -> DeferredIndex sh -> DeferredIndex sh
$cmax :: forall sh. DeferredIndex sh -> DeferredIndex sh -> DeferredIndex sh
>= :: DeferredIndex sh -> DeferredIndex sh -> Bool
$c>= :: forall sh. DeferredIndex sh -> DeferredIndex sh -> Bool
> :: DeferredIndex sh -> DeferredIndex sh -> Bool
$c> :: forall sh. DeferredIndex sh -> DeferredIndex sh -> Bool
<= :: DeferredIndex sh -> DeferredIndex sh -> Bool
$c<= :: forall sh. DeferredIndex sh -> DeferredIndex sh -> Bool
< :: DeferredIndex sh -> DeferredIndex sh -> Bool
$c< :: forall sh. DeferredIndex sh -> DeferredIndex sh -> Bool
compare :: DeferredIndex sh -> DeferredIndex sh -> Ordering
$ccompare :: forall sh. DeferredIndex sh -> DeferredIndex sh -> Ordering
$cp1Ord :: forall sh. Eq (DeferredIndex sh)
Ord, Int -> DeferredIndex sh -> ShowS
[DeferredIndex sh] -> ShowS
DeferredIndex sh -> String
(Int -> DeferredIndex sh -> ShowS)
-> (DeferredIndex sh -> String)
-> ([DeferredIndex sh] -> ShowS)
-> Show (DeferredIndex sh)
forall sh. Int -> DeferredIndex sh -> ShowS
forall sh. [DeferredIndex sh] -> ShowS
forall sh. DeferredIndex sh -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeferredIndex sh] -> ShowS
$cshowList :: forall sh. [DeferredIndex sh] -> ShowS
show :: DeferredIndex sh -> String
$cshow :: forall sh. DeferredIndex sh -> String
showsPrec :: Int -> DeferredIndex sh -> ShowS
$cshowsPrec :: forall sh. Int -> DeferredIndex sh -> ShowS
Show)
instance (NFData sh) => NFData (Deferred sh) where
rnf :: Deferred sh -> ()
rnf (Deferred sh
sh) = sh -> ()
forall a. NFData a => a -> ()
rnf sh
sh
instance (C sh) => C (Deferred sh) where
size :: Deferred sh -> Int
size (Deferred sh
sh) = sh -> Int
forall sh. C sh => sh -> Int
size sh
sh
uncheckedSize :: Deferred sh -> Int
uncheckedSize (Deferred sh
sh) = sh -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh
sh
instance (C sh) => Indexed (Deferred sh) where
type Index (Deferred sh) = DeferredIndex sh
indices :: Deferred sh -> [Index (Deferred sh)]
indices (Deferred sh
sh) = (Int -> DeferredIndex sh) -> [Int] -> [DeferredIndex sh]
forall a b. (a -> b) -> [a] -> [b]
map Int -> DeferredIndex sh
forall sh. Int -> DeferredIndex sh
DeferredIndex ([Int] -> [DeferredIndex sh]) -> [Int] -> [DeferredIndex sh]
forall a b. (a -> b) -> a -> b
$ Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take (sh -> Int
forall sh. C sh => sh -> Int
size sh
sh) [Int
0 ..]
offset :: Deferred sh -> Index (Deferred sh) -> Int
offset (Deferred sh
sh) (DeferredIndex k) = ZeroBased Int -> Index (ZeroBased Int) -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset (Int -> ZeroBased Int
forall n. n -> ZeroBased n
ZeroBased (Int -> ZeroBased Int) -> Int -> ZeroBased Int
forall a b. (a -> b) -> a -> b
$ sh -> Int
forall sh. C sh => sh -> Int
size sh
sh) Int
Index (ZeroBased Int)
k
uncheckedOffset :: Deferred sh -> Index (Deferred sh) -> Int
uncheckedOffset Deferred sh
_ (DeferredIndex k) = Int
k
sizeOffset :: Deferred sh -> (Int, Index (Deferred sh) -> Int)
sizeOffset (Deferred sh
sh) =
((Int -> Int) -> DeferredIndex sh -> Int)
-> (Int, Int -> Int) -> (Int, DeferredIndex sh -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd (\Int -> Int
offs (DeferredIndex Int
k) -> Int -> Int
offs Int
k) ((Int, Int -> Int) -> (Int, DeferredIndex sh -> Int))
-> (Int, Int -> Int) -> (Int, DeferredIndex sh -> Int)
forall a b. (a -> b) -> a -> b
$
ZeroBased Int -> (Int, Index (ZeroBased Int) -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset (Int -> ZeroBased Int
forall n. n -> ZeroBased n
ZeroBased (Int -> ZeroBased Int) -> Int -> ZeroBased Int
forall a b. (a -> b) -> a -> b
$ sh -> Int
forall sh. C sh => sh -> Int
size sh
sh)
uncheckedSizeOffset :: Deferred sh -> (Int, Index (Deferred sh) -> Int)
uncheckedSizeOffset (Deferred sh
sh) =
((Int -> Int) -> DeferredIndex sh -> Int)
-> (Int, Int -> Int) -> (Int, DeferredIndex sh -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd (\ Int -> Int
_offs (DeferredIndex Int
k) -> Int
k) ((Int, Int -> Int) -> (Int, DeferredIndex sh -> Int))
-> (Int, Int -> Int) -> (Int, DeferredIndex sh -> Int)
forall a b. (a -> b) -> a -> b
$
ZeroBased Int -> (Int, Index (ZeroBased Int) -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset (Int -> ZeroBased Int
forall n. n -> ZeroBased n
ZeroBased (Int -> ZeroBased Int) -> Int -> ZeroBased Int
forall a b. (a -> b) -> a -> b
$ sh -> Int
forall sh. C sh => sh -> Int
size sh
sh)
inBounds :: Deferred sh -> Index (Deferred sh) -> Bool
inBounds (Deferred sh
sh) (DeferredIndex k) =
ZeroBased Int -> Index (ZeroBased Int) -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds (Int -> ZeroBased Int
forall n. n -> ZeroBased n
ZeroBased (Int -> ZeroBased Int) -> Int -> ZeroBased Int
forall a b. (a -> b) -> a -> b
$ sh -> Int
forall sh. C sh => sh -> Int
size sh
sh) Int
Index (ZeroBased Int)
k
instance (C sh) => InvIndexed (Deferred sh) where
indexFromOffset :: Deferred sh -> Int -> Index (Deferred sh)
indexFromOffset (Deferred sh
sh) Int
k =
Int -> DeferredIndex sh
forall sh. Int -> DeferredIndex sh
DeferredIndex (Int -> DeferredIndex sh) -> Int -> DeferredIndex sh
forall a b. (a -> b) -> a -> b
$ ZeroBased Int -> Int -> Index (ZeroBased Int)
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset (Int -> ZeroBased Int
forall n. n -> ZeroBased n
ZeroBased (Int -> ZeroBased Int) -> Int -> ZeroBased Int
forall a b. (a -> b) -> a -> b
$ sh -> Int
forall sh. C sh => sh -> Int
size sh
sh) Int
k
uncheckedIndexFromOffset :: Deferred sh -> Int -> Index (Deferred sh)
uncheckedIndexFromOffset Deferred sh
_sh = Int -> Index (Deferred sh)
forall sh. Int -> DeferredIndex sh
DeferredIndex
deferIndex :: (Indexed sh, Index sh ~ ix) => sh -> ix -> DeferredIndex sh
deferIndex :: sh -> ix -> DeferredIndex sh
deferIndex sh
sh ix
ix = Int -> DeferredIndex sh
forall sh. Int -> DeferredIndex sh
DeferredIndex (Int -> DeferredIndex sh) -> Int -> DeferredIndex sh
forall a b. (a -> b) -> a -> b
$ sh -> Index sh -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset sh
sh ix
Index sh
ix
revealIndex :: (InvIndexed sh, Index sh ~ ix) => sh -> DeferredIndex sh -> ix
revealIndex :: sh -> DeferredIndex sh -> ix
revealIndex sh
sh (DeferredIndex Int
ix) = sh -> Int -> Index sh
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset sh
sh Int
ix
instance (Static sh) => Static (Deferred sh) where
static :: Deferred sh
static = sh -> Deferred sh
forall sh. sh -> Deferred sh
Deferred sh
forall sh. Static sh => sh
static
instance Storable (DeferredIndex sh) where
{-# INLINE sizeOf #-}
{-# INLINE alignment #-}
{-# INLINE peek #-}
{-# INLINE poke #-}
sizeOf :: DeferredIndex sh -> Int
sizeOf (DeferredIndex Int
k) = Int -> Int
forall a. Storable a => a -> Int
sizeOf Int
k
alignment :: DeferredIndex sh -> Int
alignment (DeferredIndex Int
k) = Int -> Int
forall a. Storable a => a -> Int
alignment Int
k
poke :: Ptr (DeferredIndex sh) -> DeferredIndex sh -> IO ()
poke Ptr (DeferredIndex sh)
p (DeferredIndex Int
k) = Ptr Int -> Int -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr (DeferredIndex sh) -> Ptr Int
forall a b. Ptr a -> Ptr b
castPtr Ptr (DeferredIndex sh)
p) Int
k
peek :: Ptr (DeferredIndex sh) -> IO (DeferredIndex sh)
peek Ptr (DeferredIndex sh)
p = (Int -> DeferredIndex sh) -> IO Int -> IO (DeferredIndex sh)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> DeferredIndex sh
forall sh. Int -> DeferredIndex sh
DeferredIndex (IO Int -> IO (DeferredIndex sh))
-> IO Int -> IO (DeferredIndex sh)
forall a b. (a -> b) -> a -> b
$ Ptr Int -> IO Int
forall a. Storable a => Ptr a -> IO a
peek (Ptr (DeferredIndex sh) -> Ptr Int
forall a b. Ptr a -> Ptr b
castPtr Ptr (DeferredIndex sh)
p)
instance (C sh) => C (Tagged s sh) where
size :: Tagged s sh -> Int
size (Tagged sh
sh) = sh -> Int
forall sh. C sh => sh -> Int
size sh
sh
uncheckedSize :: Tagged s sh -> Int
uncheckedSize (Tagged sh
sh) = sh -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh
sh
instance (Indexed sh) => Indexed (Tagged s sh) where
type Index (Tagged s sh) = Tagged s (Index sh)
indices :: Tagged s sh -> [Index (Tagged s sh)]
indices (Tagged sh
sh) = (Index sh -> Tagged s (Index sh))
-> [Index sh] -> [Tagged s (Index sh)]
forall a b. (a -> b) -> [a] -> [b]
map Index sh -> Tagged s (Index sh)
forall k (s :: k) b. b -> Tagged s b
Tagged ([Index sh] -> [Tagged s (Index sh)])
-> [Index sh] -> [Tagged s (Index sh)]
forall a b. (a -> b) -> a -> b
$ sh -> [Index sh]
forall sh. Indexed sh => sh -> [Index sh]
indices sh
sh
offset :: Tagged s sh -> Index (Tagged s sh) -> Int
offset (Tagged sh
sh) (Tagged k) = sh -> Index sh -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset sh
sh Index sh
k
uncheckedOffset :: Tagged s sh -> Index (Tagged s sh) -> Int
uncheckedOffset (Tagged sh
sh) (Tagged k) = sh -> Index sh -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset sh
sh Index sh
k
sizeOffset :: Tagged s sh -> (Int, Index (Tagged s sh) -> Int)
sizeOffset (Tagged sh
sh) = ((Index sh -> Int) -> Tagged s (Index sh) -> Int)
-> (Int, Index sh -> Int) -> (Int, Tagged s (Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> (Tagged s (Index sh) -> Index sh) -> Tagged s (Index sh) -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tagged s (Index sh) -> Index sh
forall k (s :: k) b. Tagged s b -> b
unTagged) ((Int, Index sh -> Int) -> (Int, Tagged s (Index sh) -> Int))
-> (Int, Index sh -> Int) -> (Int, Tagged s (Index sh) -> Int)
forall a b. (a -> b) -> a -> b
$ sh -> (Int, Index sh -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh
sh
uncheckedSizeOffset :: Tagged s sh -> (Int, Index (Tagged s sh) -> Int)
uncheckedSizeOffset (Tagged sh
sh) =
((Index sh -> Int) -> Tagged s (Index sh) -> Int)
-> (Int, Index sh -> Int) -> (Int, Tagged s (Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> (Tagged s (Index sh) -> Index sh) -> Tagged s (Index sh) -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tagged s (Index sh) -> Index sh
forall k (s :: k) b. Tagged s b -> b
unTagged) ((Int, Index sh -> Int) -> (Int, Tagged s (Index sh) -> Int))
-> (Int, Index sh -> Int) -> (Int, Tagged s (Index sh) -> Int)
forall a b. (a -> b) -> a -> b
$ sh -> (Int, Index sh -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh
sh
inBounds :: Tagged s sh -> Index (Tagged s sh) -> Bool
inBounds (Tagged sh
sh) (Tagged k) = sh -> Index sh -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds sh
sh Index sh
k
instance (InvIndexed sh) => InvIndexed (Tagged s sh) where
indexFromOffset :: Tagged s sh -> Int -> Index (Tagged s sh)
indexFromOffset (Tagged sh
sh) Int
k = Index sh -> Tagged s (Index sh)
forall k (s :: k) b. b -> Tagged s b
Tagged (Index sh -> Tagged s (Index sh))
-> Index sh -> Tagged s (Index sh)
forall a b. (a -> b) -> a -> b
$ sh -> Int -> Index sh
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset sh
sh Int
k
uncheckedIndexFromOffset :: Tagged s sh -> Int -> Index (Tagged s sh)
uncheckedIndexFromOffset (Tagged sh
sh) Int
k =
Index sh -> Tagged s (Index sh)
forall k (s :: k) b. b -> Tagged s b
Tagged (Index sh -> Tagged s (Index sh))
-> Index sh -> Tagged s (Index sh)
forall a b. (a -> b) -> a -> b
$ sh -> Int -> Index sh
forall sh. InvIndexed sh => sh -> Int -> Index sh
uncheckedIndexFromOffset sh
sh Int
k
instance (Static sh) => Static (Tagged s sh) where
static :: Tagged s sh
static = sh -> Tagged s sh
forall k (s :: k) b. b -> Tagged s b
Tagged sh
forall sh. Static sh => sh
static
instance (C sh0, C sh1) => C (sh0,sh1) where
size :: (sh0, sh1) -> Int
size (sh0
sh0,sh1
sh1) = sh0 -> Int
forall sh. C sh => sh -> Int
size sh0
sh0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* sh1 -> Int
forall sh. C sh => sh -> Int
size sh1
sh1
uncheckedSize :: (sh0, sh1) -> Int
uncheckedSize (sh0
sh0,sh1
sh1) = sh0 -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh0
sh0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* sh1 -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh1
sh1
instance (Indexed sh0, Indexed sh1) => Indexed (sh0,sh1) where
type Index (sh0,sh1) = (Index sh0, Index sh1)
indices :: (sh0, sh1) -> [Index (sh0, sh1)]
indices (sh0
sh0,sh1
sh1) = (Index sh0 -> Index sh1 -> (Index sh0, Index sh1))
-> [Index sh0] -> [Index sh1] -> [(Index sh0, Index sh1)]
forall (m :: * -> *) a b r.
Monad m =>
(a -> b -> r) -> m a -> m b -> m r
Monad.lift2 (,) (sh0 -> [Index sh0]
forall sh. Indexed sh => sh -> [Index sh]
indices sh0
sh0) (sh1 -> [Index sh1]
forall sh. Indexed sh => sh -> [Index sh]
indices sh1
sh1)
offset :: (sh0, sh1) -> Index (sh0, sh1) -> Int
offset (sh0
sh0,sh1
sh1) =
sh0 -> Index sh0 -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset sh0
sh0 (Index sh0 -> Int)
-> ((Index sh0, Index sh1) -> Index sh0)
-> (Index sh0, Index sh1)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Index sh0, Index sh1) -> Index sh0
forall a b. (a, b) -> a
fst
((Index sh0, Index sh1) -> Int)
-> (Int, (Index sh0, Index sh1) -> Int)
-> (Index sh0, Index sh1)
-> Int
forall a ix. Num a => (ix -> a) -> (a, ix -> a) -> ix -> a
`combineOffset`
((Index sh1 -> Int) -> (Index sh0, Index sh1) -> Int)
-> (Int, Index sh1 -> Int) -> (Int, (Index sh0, Index sh1) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh1 -> Int)
-> ((Index sh0, Index sh1) -> Index sh1)
-> (Index sh0, Index sh1)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1) -> Index sh1
forall a b. (a, b) -> b
snd) (sh1 -> (Int, Index sh1 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh1
sh1)
uncheckedOffset :: (sh0, sh1) -> Index (sh0, sh1) -> Int
uncheckedOffset (sh0
sh0,sh1
sh1) =
sh0 -> Index sh0 -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset sh0
sh0 (Index sh0 -> Int)
-> ((Index sh0, Index sh1) -> Index sh0)
-> (Index sh0, Index sh1)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Index sh0, Index sh1) -> Index sh0
forall a b. (a, b) -> a
fst
((Index sh0, Index sh1) -> Int)
-> (Int, (Index sh0, Index sh1) -> Int)
-> (Index sh0, Index sh1)
-> Int
forall a ix. Num a => (ix -> a) -> (a, ix -> a) -> ix -> a
`combineOffset`
((Index sh1 -> Int) -> (Index sh0, Index sh1) -> Int)
-> (Int, Index sh1 -> Int) -> (Int, (Index sh0, Index sh1) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh1 -> Int)
-> ((Index sh0, Index sh1) -> Index sh1)
-> (Index sh0, Index sh1)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1) -> Index sh1
forall a b. (a, b) -> b
snd) (sh1 -> (Int, Index sh1 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh1
sh1)
sizeOffset :: (sh0, sh1) -> (Int, Index (sh0, sh1) -> Int)
sizeOffset (sh0
sh0,sh1
sh1) =
((Index sh0 -> Int) -> (Index sh0, Index sh1) -> Int)
-> (Int, Index sh0 -> Int) -> (Int, (Index sh0, Index sh1) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh0 -> Int)
-> ((Index sh0, Index sh1) -> Index sh0)
-> (Index sh0, Index sh1)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1) -> Index sh0
forall a b. (a, b) -> a
fst) (sh0 -> (Int, Index sh0 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh0
sh0)
(Int, (Index sh0, Index sh1) -> Int)
-> (Int, (Index sh0, Index sh1) -> Int)
-> (Int, (Index sh0, Index sh1) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh1 -> Int) -> (Index sh0, Index sh1) -> Int)
-> (Int, Index sh1 -> Int) -> (Int, (Index sh0, Index sh1) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh1 -> Int)
-> ((Index sh0, Index sh1) -> Index sh1)
-> (Index sh0, Index sh1)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1) -> Index sh1
forall a b. (a, b) -> b
snd) (sh1 -> (Int, Index sh1 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh1
sh1)
uncheckedSizeOffset :: (sh0, sh1) -> (Int, Index (sh0, sh1) -> Int)
uncheckedSizeOffset (sh0
sh0,sh1
sh1) =
((Index sh0 -> Int) -> (Index sh0, Index sh1) -> Int)
-> (Int, Index sh0 -> Int) -> (Int, (Index sh0, Index sh1) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh0 -> Int)
-> ((Index sh0, Index sh1) -> Index sh0)
-> (Index sh0, Index sh1)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1) -> Index sh0
forall a b. (a, b) -> a
fst) (sh0 -> (Int, Index sh0 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh0
sh0)
(Int, (Index sh0, Index sh1) -> Int)
-> (Int, (Index sh0, Index sh1) -> Int)
-> (Int, (Index sh0, Index sh1) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh1 -> Int) -> (Index sh0, Index sh1) -> Int)
-> (Int, Index sh1 -> Int) -> (Int, (Index sh0, Index sh1) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh1 -> Int)
-> ((Index sh0, Index sh1) -> Index sh1)
-> (Index sh0, Index sh1)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1) -> Index sh1
forall a b. (a, b) -> b
snd) (sh1 -> (Int, Index sh1 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh1
sh1)
inBounds :: (sh0, sh1) -> Index (sh0, sh1) -> Bool
inBounds (sh0
sh0,sh1
sh1) (ix0,ix1) = sh0 -> Index sh0 -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds sh0
sh0 Index sh0
ix0 Bool -> Bool -> Bool
&& sh1 -> Index sh1 -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds sh1
sh1 Index sh1
ix1
instance (InvIndexed sh0, InvIndexed sh1) => InvIndexed (sh0,sh1) where
indexFromOffset :: (sh0, sh1) -> Int -> Index (sh0, sh1)
indexFromOffset (sh0
sh0,sh1
sh1) Int
k =
Int
-> Backwards (State Int) (Index sh0, Index sh1)
-> (Index sh0, Index sh1)
forall s a. s -> Backwards (State s) a -> a
runInvIndex Int
k (Backwards (State Int) (Index sh0, Index sh1)
-> (Index sh0, Index sh1))
-> Backwards (State Int) (Index sh0, Index sh1)
-> (Index sh0, Index sh1)
forall a b. (a -> b) -> a -> b
$ (Index sh0 -> Index sh1 -> (Index sh0, Index sh1))
-> Backwards (State Int) (Index sh0)
-> Backwards (State Int) (Index sh1)
-> Backwards (State Int) (Index sh0, Index sh1)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) (sh0 -> Backwards (State Int) (Index sh0)
forall sh. InvIndexed sh => sh -> Backwards (State Int) (Index sh)
pickLastIndex sh0
sh0) (sh1 -> Backwards (State Int) (Index sh1)
forall sh. InvIndexed sh => sh -> Backwards (State Int) (Index sh)
pickIndex sh1
sh1)
uncheckedIndexFromOffset :: (sh0, sh1) -> Int -> Index (sh0, sh1)
uncheckedIndexFromOffset (sh0
sh0,sh1
sh1) Int
k =
Int
-> Backwards (State Int) (Index sh0, Index sh1)
-> (Index sh0, Index sh1)
forall s a. s -> Backwards (State s) a -> a
runInvIndex Int
k (Backwards (State Int) (Index sh0, Index sh1)
-> (Index sh0, Index sh1))
-> Backwards (State Int) (Index sh0, Index sh1)
-> (Index sh0, Index sh1)
forall a b. (a -> b) -> a -> b
$ (Index sh0 -> Index sh1 -> (Index sh0, Index sh1))
-> Backwards (State Int) (Index sh0)
-> Backwards (State Int) (Index sh1)
-> Backwards (State Int) (Index sh0, Index sh1)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) (sh0 -> Backwards (State Int) (Index sh0)
forall sh. InvIndexed sh => sh -> Backwards (State Int) (Index sh)
uncheckedPickLastIndex sh0
sh0) (sh1 -> Backwards (State Int) (Index sh1)
forall sh. InvIndexed sh => sh -> Backwards (State Int) (Index sh)
pickIndex sh1
sh1)
instance (Static sh0, Static sh1) => Static (sh0,sh1) where
static :: (sh0, sh1)
static = (sh0
forall sh. Static sh => sh
static, sh1
forall sh. Static sh => sh
static)
instance (C sh0, C sh1, C sh2) => C (sh0,sh1,sh2) where
size :: (sh0, sh1, sh2) -> Int
size (sh0
sh0,sh1
sh1,sh2
sh2) = sh0 -> Int
forall sh. C sh => sh -> Int
size sh0
sh0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* sh1 -> Int
forall sh. C sh => sh -> Int
size sh1
sh1 Int -> Int -> Int
forall a. Num a => a -> a -> a
* sh2 -> Int
forall sh. C sh => sh -> Int
size sh2
sh2
uncheckedSize :: (sh0, sh1, sh2) -> Int
uncheckedSize (sh0
sh0,sh1
sh1,sh2
sh2) =
sh0 -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh0
sh0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* sh1 -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh1
sh1 Int -> Int -> Int
forall a. Num a => a -> a -> a
* sh2 -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh2
sh2
instance (Indexed sh0, Indexed sh1, Indexed sh2) => Indexed (sh0,sh1,sh2) where
type Index (sh0,sh1,sh2) = (Index sh0, Index sh1, Index sh2)
indices :: (sh0, sh1, sh2) -> [Index (sh0, sh1, sh2)]
indices (sh0
sh0,sh1
sh1,sh2
sh2) =
(Index sh0
-> Index sh1 -> Index sh2 -> (Index sh0, Index sh1, Index sh2))
-> [Index sh0]
-> [Index sh1]
-> [Index sh2]
-> [(Index sh0, Index sh1, Index sh2)]
forall (m :: * -> *) a b c r.
Monad m =>
(a -> b -> c -> r) -> m a -> m b -> m c -> m r
Monad.lift3 (,,) (sh0 -> [Index sh0]
forall sh. Indexed sh => sh -> [Index sh]
indices sh0
sh0) (sh1 -> [Index sh1]
forall sh. Indexed sh => sh -> [Index sh]
indices sh1
sh1) (sh2 -> [Index sh2]
forall sh. Indexed sh => sh -> [Index sh]
indices sh2
sh2)
uncheckedOffset :: (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> Int
uncheckedOffset (sh0
sh0,sh1
sh1,sh2
sh2) =
sh0 -> Index sh0 -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset sh0
sh0 (Index sh0 -> Int)
-> ((Index sh0, Index sh1, Index sh2) -> Index sh0)
-> (Index sh0, Index sh1, Index sh2)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Index sh0, Index sh1, Index sh2) -> Index sh0
forall a b c. (a, b, c) -> a
fst3
((Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Index sh0, Index sh1, Index sh2)
-> Int
forall a ix. Num a => (ix -> a) -> (a, ix -> a) -> ix -> a
`combineOffset`
((Index sh1 -> Int) -> (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, Index sh1 -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh1 -> Int)
-> ((Index sh0, Index sh1, Index sh2) -> Index sh1)
-> (Index sh0, Index sh1, Index sh2)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1, Index sh2) -> Index sh1
forall a b c. (a, b, c) -> b
snd3) (sh1 -> (Int, Index sh1 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh1
sh1)
(Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh2 -> Int) -> (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, Index sh2 -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh2 -> Int)
-> ((Index sh0, Index sh1, Index sh2) -> Index sh2)
-> (Index sh0, Index sh1, Index sh2)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1, Index sh2) -> Index sh2
forall a b c. (a, b, c) -> c
thd3) (sh2 -> (Int, Index sh2 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh2
sh2)
sizeOffset :: (sh0, sh1, sh2) -> (Int, Index (sh0, sh1, sh2) -> Int)
sizeOffset (sh0
sh0,sh1
sh1,sh2
sh2) =
((Index sh0 -> Int) -> (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, Index sh0 -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh0 -> Int)
-> ((Index sh0, Index sh1, Index sh2) -> Index sh0)
-> (Index sh0, Index sh1, Index sh2)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1, Index sh2) -> Index sh0
forall a b c. (a, b, c) -> a
fst3) (sh0 -> (Int, Index sh0 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh0
sh0)
(Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh1 -> Int) -> (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, Index sh1 -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh1 -> Int)
-> ((Index sh0, Index sh1, Index sh2) -> Index sh1)
-> (Index sh0, Index sh1, Index sh2)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1, Index sh2) -> Index sh1
forall a b c. (a, b, c) -> b
snd3) (sh1 -> (Int, Index sh1 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh1
sh1)
(Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh2 -> Int) -> (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, Index sh2 -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh2 -> Int)
-> ((Index sh0, Index sh1, Index sh2) -> Index sh2)
-> (Index sh0, Index sh1, Index sh2)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1, Index sh2) -> Index sh2
forall a b c. (a, b, c) -> c
thd3) (sh2 -> (Int, Index sh2 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh2
sh2)
uncheckedSizeOffset :: (sh0, sh1, sh2) -> (Int, Index (sh0, sh1, sh2) -> Int)
uncheckedSizeOffset (sh0
sh0,sh1
sh1,sh2
sh2) =
((Index sh0 -> Int) -> (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, Index sh0 -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh0 -> Int)
-> ((Index sh0, Index sh1, Index sh2) -> Index sh0)
-> (Index sh0, Index sh1, Index sh2)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1, Index sh2) -> Index sh0
forall a b c. (a, b, c) -> a
fst3) (sh0 -> (Int, Index sh0 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh0
sh0)
(Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh1 -> Int) -> (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, Index sh1 -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh1 -> Int)
-> ((Index sh0, Index sh1, Index sh2) -> Index sh1)
-> (Index sh0, Index sh1, Index sh2)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1, Index sh2) -> Index sh1
forall a b c. (a, b, c) -> b
snd3) (sh1 -> (Int, Index sh1 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh1
sh1)
(Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh2 -> Int) -> (Index sh0, Index sh1, Index sh2) -> Int)
-> (Int, Index sh2 -> Int)
-> (Int, (Index sh0, Index sh1, Index sh2) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh2 -> Int)
-> ((Index sh0, Index sh1, Index sh2) -> Index sh2)
-> (Index sh0, Index sh1, Index sh2)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh0, Index sh1, Index sh2) -> Index sh2
forall a b c. (a, b, c) -> c
thd3) (sh2 -> (Int, Index sh2 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh2
sh2)
inBounds :: (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> Bool
inBounds (sh0
sh0,sh1
sh1,sh2
sh2) (ix0,ix1,ix2) =
sh0 -> Index sh0 -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds sh0
sh0 Index sh0
ix0 Bool -> Bool -> Bool
&& sh1 -> Index sh1 -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds sh1
sh1 Index sh1
ix1 Bool -> Bool -> Bool
&& sh2 -> Index sh2 -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds sh2
sh2 Index sh2
ix2
instance
(InvIndexed sh0, InvIndexed sh1, InvIndexed sh2) =>
InvIndexed (sh0,sh1,sh2) where
indexFromOffset :: (sh0, sh1, sh2) -> Int -> Index (sh0, sh1, sh2)
indexFromOffset (sh0
sh0,sh1
sh1,sh2
sh2) Int
k =
Int
-> Backwards (State Int) (Index sh0, Index sh1, Index sh2)
-> (Index sh0, Index sh1, Index sh2)
forall s a. s -> Backwards (State s) a -> a
runInvIndex Int
k (Backwards (State Int) (Index sh0, Index sh1, Index sh2)
-> (Index sh0, Index sh1, Index sh2))
-> Backwards (State Int) (Index sh0, Index sh1, Index sh2)
-> (Index sh0, Index sh1, Index sh2)
forall a b. (a -> b) -> a -> b
$
(Index sh0
-> Index sh1 -> Index sh2 -> (Index sh0, Index sh1, Index sh2))
-> Backwards (State Int) (Index sh0)
-> Backwards (State Int) (Index sh1)
-> Backwards (State Int) (Index sh2)
-> Backwards (State Int) (Index sh0, Index sh1, Index sh2)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 (,,) (sh0 -> Backwards (State Int) (Index sh0)
forall sh. InvIndexed sh => sh -> Backwards (State Int) (Index sh)
pickLastIndex sh0
sh0) (sh1 -> Backwards (State Int) (Index sh1)
forall sh. InvIndexed sh => sh -> Backwards (State Int) (Index sh)
pickIndex sh1
sh1) (sh2 -> Backwards (State Int) (Index sh2)
forall sh. InvIndexed sh => sh -> Backwards (State Int) (Index sh)
pickIndex sh2
sh2)
uncheckedIndexFromOffset :: (sh0, sh1, sh2) -> Int -> Index (sh0, sh1, sh2)
uncheckedIndexFromOffset (sh0
sh0,sh1
sh1,sh2
sh2) Int
k =
Int
-> Backwards (State Int) (Index sh0, Index sh1, Index sh2)
-> (Index sh0, Index sh1, Index sh2)
forall s a. s -> Backwards (State s) a -> a
runInvIndex Int
k (Backwards (State Int) (Index sh0, Index sh1, Index sh2)
-> (Index sh0, Index sh1, Index sh2))
-> Backwards (State Int) (Index sh0, Index sh1, Index sh2)
-> (Index sh0, Index sh1, Index sh2)
forall a b. (a -> b) -> a -> b
$
(Index sh0
-> Index sh1 -> Index sh2 -> (Index sh0, Index sh1, Index sh2))
-> Backwards (State Int) (Index sh0)
-> Backwards (State Int) (Index sh1)
-> Backwards (State Int) (Index sh2)
-> Backwards (State Int) (Index sh0, Index sh1, Index sh2)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 (,,) (sh0 -> Backwards (State Int) (Index sh0)
forall sh. InvIndexed sh => sh -> Backwards (State Int) (Index sh)
uncheckedPickLastIndex sh0
sh0) (sh1 -> Backwards (State Int) (Index sh1)
forall sh. InvIndexed sh => sh -> Backwards (State Int) (Index sh)
pickIndex sh1
sh1) (sh2 -> Backwards (State Int) (Index sh2)
forall sh. InvIndexed sh => sh -> Backwards (State Int) (Index sh)
pickIndex sh2
sh2)
instance (Static sh0, Static sh1, Static sh2) => Static (sh0,sh1,sh2) where
static :: (sh0, sh1, sh2)
static = (sh0
forall sh. Static sh => sh
static, sh1
forall sh. Static sh => sh
static, sh2
forall sh. Static sh => sh
static)
runInvIndex :: s -> Back.Backwards (MS.State s) a -> a
runInvIndex :: s -> Backwards (State s) a -> a
runInvIndex s
k = (State s a -> s -> a) -> s -> State s a -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip State s a -> s -> a
forall s a. State s a -> s -> a
MS.evalState s
k (State s a -> a)
-> (Backwards (State s) a -> State s a)
-> Backwards (State s) a
-> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Backwards (State s) a -> State s a
forall k (f :: k -> *) (a :: k). Backwards f a -> f a
Back.forwards
pickLastIndex ::
(InvIndexed sh) => sh -> Back.Backwards (MS.State Int) (Index sh)
pickLastIndex :: sh -> Backwards (State Int) (Index sh)
pickLastIndex sh
sh =
StateT Int Identity (Index sh) -> Backwards (State Int) (Index sh)
forall k (f :: k -> *) (a :: k). f a -> Backwards f a
Back.Backwards (StateT Int Identity (Index sh)
-> Backwards (State Int) (Index sh))
-> StateT Int Identity (Index sh)
-> Backwards (State Int) (Index sh)
forall a b. (a -> b) -> a -> b
$ (Int -> Index sh) -> StateT Int Identity (Index sh)
forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
MS.gets ((Int -> Index sh) -> StateT Int Identity (Index sh))
-> (Int -> Index sh) -> StateT Int Identity (Index sh)
forall a b. (a -> b) -> a -> b
$ sh -> Int -> Index sh
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset sh
sh
uncheckedPickLastIndex ::
(InvIndexed sh) => sh -> Back.Backwards (MS.State Int) (Index sh)
uncheckedPickLastIndex :: sh -> Backwards (State Int) (Index sh)
uncheckedPickLastIndex sh
sh =
StateT Int Identity (Index sh) -> Backwards (State Int) (Index sh)
forall k (f :: k -> *) (a :: k). f a -> Backwards f a
Back.Backwards (StateT Int Identity (Index sh)
-> Backwards (State Int) (Index sh))
-> StateT Int Identity (Index sh)
-> Backwards (State Int) (Index sh)
forall a b. (a -> b) -> a -> b
$ (Int -> Index sh) -> StateT Int Identity (Index sh)
forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
MS.gets ((Int -> Index sh) -> StateT Int Identity (Index sh))
-> (Int -> Index sh) -> StateT Int Identity (Index sh)
forall a b. (a -> b) -> a -> b
$ sh -> Int -> Index sh
forall sh. InvIndexed sh => sh -> Int -> Index sh
uncheckedIndexFromOffset sh
sh
pickIndex :: (InvIndexed sh) => sh -> Back.Backwards (MS.State Int) (Index sh)
pickIndex :: sh -> Backwards (State Int) (Index sh)
pickIndex sh
sh =
(Int -> Index sh)
-> Backwards (State Int) Int -> Backwards (State Int) (Index sh)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (sh -> Int -> Index sh
forall sh. InvIndexed sh => sh -> Int -> Index sh
uncheckedIndexFromOffset sh
sh) (Backwards (State Int) Int -> Backwards (State Int) (Index sh))
-> Backwards (State Int) Int -> Backwards (State Int) (Index sh)
forall a b. (a -> b) -> a -> b
$
StateT Int Identity Int -> Backwards (State Int) Int
forall k (f :: k -> *) (a :: k). f a -> Backwards f a
Back.Backwards (StateT Int Identity Int -> Backwards (State Int) Int)
-> StateT Int Identity Int -> Backwards (State Int) Int
forall a b. (a -> b) -> a -> b
$ (Int -> (Int, Int)) -> StateT Int Identity Int
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
MS.state ((Int -> (Int, Int)) -> StateT Int Identity Int)
-> (Int -> (Int, Int)) -> StateT Int Identity Int
forall a b. (a -> b) -> a -> b
$ \Int
k -> (Int, Int) -> (Int, Int)
forall a b. (a, b) -> (b, a)
swap ((Int, Int) -> (Int, Int)) -> (Int, Int) -> (Int, Int)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod Int
k (Int -> (Int, Int)) -> Int -> (Int, Int)
forall a b. (a -> b) -> a -> b
$ sh -> Int
forall sh. C sh => sh -> Int
size sh
sh
infixr 7 `combineOffset`, `combineSizeOffset`
{-# INLINE combineOffset #-}
combineOffset :: Num a => (ix -> a) -> (a, ix -> a) -> ix -> a
combineOffset :: (ix -> a) -> (a, ix -> a) -> ix -> a
combineOffset ix -> a
offset0 (a
size1,ix -> a
offset1) ix
ix = ix -> a
offset0 ix
ix a -> a -> a
forall a. Num a => a -> a -> a
* a
size1 a -> a -> a
forall a. Num a => a -> a -> a
+ ix -> a
offset1 ix
ix
{-# INLINE combineSizeOffset #-}
combineSizeOffset :: Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
combineSizeOffset :: (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
combineSizeOffset (a
size0,ix -> a
offset0) (a
size1,ix -> a
offset1) =
(a
size0a -> a -> a
forall a. Num a => a -> a -> a
*a
size1, \ix
ix -> ix -> a
offset0 ix
ix a -> a -> a
forall a. Num a => a -> a -> a
* a
size1 a -> a -> a
forall a. Num a => a -> a -> a
+ ix -> a
offset1 ix
ix)
newtype Square sh = Square {Square sh -> sh
squareSize :: sh}
deriving (Square sh -> Square sh -> Bool
(Square sh -> Square sh -> Bool)
-> (Square sh -> Square sh -> Bool) -> Eq (Square sh)
forall sh. Eq sh => Square sh -> Square sh -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Square sh -> Square sh -> Bool
$c/= :: forall sh. Eq sh => Square sh -> Square sh -> Bool
== :: Square sh -> Square sh -> Bool
$c== :: forall sh. Eq sh => Square sh -> Square sh -> Bool
Eq, Int -> Square sh -> ShowS
[Square sh] -> ShowS
Square sh -> String
(Int -> Square sh -> ShowS)
-> (Square sh -> String)
-> ([Square sh] -> ShowS)
-> Show (Square sh)
forall sh. Show sh => Int -> Square sh -> ShowS
forall sh. Show sh => [Square sh] -> ShowS
forall sh. Show sh => Square sh -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Square sh] -> ShowS
$cshowList :: forall sh. Show sh => [Square sh] -> ShowS
show :: Square sh -> String
$cshow :: forall sh. Show sh => Square sh -> String
showsPrec :: Int -> Square sh -> ShowS
$cshowsPrec :: forall sh. Show sh => Int -> Square sh -> ShowS
Show)
instance Functor Square where
fmap :: (a -> b) -> Square a -> Square b
fmap a -> b
f (Square a
sh) = b -> Square b
forall sh. sh -> Square sh
Square (b -> Square b) -> b -> Square b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
sh
instance Applicative Square where
pure :: a -> Square a
pure = a -> Square a
forall sh. sh -> Square sh
Square
Square a -> b
f <*> :: Square (a -> b) -> Square a -> Square b
<*> Square a
sh = b -> Square b
forall sh. sh -> Square sh
Square (b -> Square b) -> b -> Square b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
sh
instance (NFData sh) => NFData (Square sh) where
rnf :: Square sh -> ()
rnf (Square sh
sh) = sh -> ()
forall a. NFData a => a -> ()
rnf sh
sh
instance (Storable sh) => Storable (Square sh) where
sizeOf :: Square sh -> Int
sizeOf = (Square sh -> sh) -> Square sh -> Int
forall core wrapper.
Storable core =>
(wrapper -> core) -> wrapper -> Int
Store.sizeOf Square sh -> sh
forall sh. Square sh -> sh
squareSize
alignment :: Square sh -> Int
alignment = (Square sh -> sh) -> Square sh -> Int
forall core wrapper.
Storable core =>
(wrapper -> core) -> wrapper -> Int
Store.alignment Square sh -> sh
forall sh. Square sh -> sh
squareSize
peek :: Ptr (Square sh) -> IO (Square sh)
peek = (sh -> Square sh) -> Ptr (Square sh) -> IO (Square sh)
forall core wrapper.
Storable core =>
(core -> wrapper) -> Ptr wrapper -> IO wrapper
Store.peek sh -> Square sh
forall sh. sh -> Square sh
Square
poke :: Ptr (Square sh) -> Square sh -> IO ()
poke = (Square sh -> sh) -> Ptr (Square sh) -> Square sh -> IO ()
forall core wrapper.
Storable core =>
(wrapper -> core) -> Ptr wrapper -> wrapper -> IO ()
Store.poke Square sh -> sh
forall sh. Square sh -> sh
squareSize
instance (C sh) => C (Square sh) where
size :: Square sh -> Int
size (Square sh
sh) = sh -> Int
forall sh. C sh => sh -> Int
size sh
sh Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
2::Int)
uncheckedSize :: Square sh -> Int
uncheckedSize (Square sh
sh) = sh -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh
sh Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
2::Int)
instance (Indexed sh) => Indexed (Square sh) where
type Index (Square sh) = (Index sh, Index sh)
indices :: Square sh -> [Index (Square sh)]
indices (Square sh
sh) = (sh, sh) -> [Index (sh, sh)]
forall sh. Indexed sh => sh -> [Index sh]
indices (sh
sh,sh
sh)
offset :: Square sh -> Index (Square sh) -> Int
offset (Square sh
sh) = (sh, sh) -> Index (sh, sh) -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset (sh
sh,sh
sh)
uncheckedOffset :: Square sh -> Index (Square sh) -> Int
uncheckedOffset (Square sh
sh) = (sh, sh) -> Index (sh, sh) -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset (sh
sh,sh
sh)
sizeOffset :: Square sh -> (Int, Index (Square sh) -> Int)
sizeOffset (Square sh
sh) =
let szo :: (Int, Index sh -> Int)
szo = sh -> (Int, Index sh -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh
sh
in ((Index sh -> Int) -> (Index sh, Index sh) -> Int)
-> (Int, Index sh -> Int) -> (Int, (Index sh, Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> ((Index sh, Index sh) -> Index sh)
-> (Index sh, Index sh)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh, Index sh) -> Index sh
forall a b. (a, b) -> a
fst) (Int, Index sh -> Int)
szo (Int, (Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset` ((Index sh -> Int) -> (Index sh, Index sh) -> Int)
-> (Int, Index sh -> Int) -> (Int, (Index sh, Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> ((Index sh, Index sh) -> Index sh)
-> (Index sh, Index sh)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh, Index sh) -> Index sh
forall a b. (a, b) -> b
snd) (Int, Index sh -> Int)
szo
uncheckedSizeOffset :: Square sh -> (Int, Index (Square sh) -> Int)
uncheckedSizeOffset (Square sh
sh) =
let szo :: (Int, Index sh -> Int)
szo = sh -> (Int, Index sh -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh
sh
in ((Index sh -> Int) -> (Index sh, Index sh) -> Int)
-> (Int, Index sh -> Int) -> (Int, (Index sh, Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> ((Index sh, Index sh) -> Index sh)
-> (Index sh, Index sh)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh, Index sh) -> Index sh
forall a b. (a, b) -> a
fst) (Int, Index sh -> Int)
szo (Int, (Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset` ((Index sh -> Int) -> (Index sh, Index sh) -> Int)
-> (Int, Index sh -> Int) -> (Int, (Index sh, Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> ((Index sh, Index sh) -> Index sh)
-> (Index sh, Index sh)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh, Index sh) -> Index sh
forall a b. (a, b) -> b
snd) (Int, Index sh -> Int)
szo
inBounds :: Square sh -> Index (Square sh) -> Bool
inBounds (Square sh
sh) = (sh, sh) -> Index (sh, sh) -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds (sh
sh,sh
sh)
instance (InvIndexed sh) => InvIndexed (Square sh) where
indexFromOffset :: Square sh -> Int -> Index (Square sh)
indexFromOffset (Square sh
sh) = (sh, sh) -> Int -> Index (sh, sh)
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset (sh
sh,sh
sh)
uncheckedIndexFromOffset :: Square sh -> Int -> Index (Square sh)
uncheckedIndexFromOffset (Square sh
sh) = (sh, sh) -> Int -> Index (sh, sh)
forall sh. InvIndexed sh => sh -> Int -> Index sh
uncheckedIndexFromOffset (sh
sh,sh
sh)
newtype Cube sh = Cube {Cube sh -> sh
cubeSize :: sh}
deriving (Cube sh -> Cube sh -> Bool
(Cube sh -> Cube sh -> Bool)
-> (Cube sh -> Cube sh -> Bool) -> Eq (Cube sh)
forall sh. Eq sh => Cube sh -> Cube sh -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cube sh -> Cube sh -> Bool
$c/= :: forall sh. Eq sh => Cube sh -> Cube sh -> Bool
== :: Cube sh -> Cube sh -> Bool
$c== :: forall sh. Eq sh => Cube sh -> Cube sh -> Bool
Eq, Int -> Cube sh -> ShowS
[Cube sh] -> ShowS
Cube sh -> String
(Int -> Cube sh -> ShowS)
-> (Cube sh -> String) -> ([Cube sh] -> ShowS) -> Show (Cube sh)
forall sh. Show sh => Int -> Cube sh -> ShowS
forall sh. Show sh => [Cube sh] -> ShowS
forall sh. Show sh => Cube sh -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cube sh] -> ShowS
$cshowList :: forall sh. Show sh => [Cube sh] -> ShowS
show :: Cube sh -> String
$cshow :: forall sh. Show sh => Cube sh -> String
showsPrec :: Int -> Cube sh -> ShowS
$cshowsPrec :: forall sh. Show sh => Int -> Cube sh -> ShowS
Show)
instance Functor Cube where
fmap :: (a -> b) -> Cube a -> Cube b
fmap a -> b
f (Cube a
sh) = b -> Cube b
forall sh. sh -> Cube sh
Cube (b -> Cube b) -> b -> Cube b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
sh
instance Applicative Cube where
pure :: a -> Cube a
pure = a -> Cube a
forall sh. sh -> Cube sh
Cube
Cube a -> b
f <*> :: Cube (a -> b) -> Cube a -> Cube b
<*> Cube a
sh = b -> Cube b
forall sh. sh -> Cube sh
Cube (b -> Cube b) -> b -> Cube b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
sh
instance (NFData sh) => NFData (Cube sh) where
rnf :: Cube sh -> ()
rnf (Cube sh
sh) = sh -> ()
forall a. NFData a => a -> ()
rnf sh
sh
instance (Storable sh) => Storable (Cube sh) where
sizeOf :: Cube sh -> Int
sizeOf = (Cube sh -> sh) -> Cube sh -> Int
forall core wrapper.
Storable core =>
(wrapper -> core) -> wrapper -> Int
Store.sizeOf Cube sh -> sh
forall sh. Cube sh -> sh
cubeSize
alignment :: Cube sh -> Int
alignment = (Cube sh -> sh) -> Cube sh -> Int
forall core wrapper.
Storable core =>
(wrapper -> core) -> wrapper -> Int
Store.alignment Cube sh -> sh
forall sh. Cube sh -> sh
cubeSize
peek :: Ptr (Cube sh) -> IO (Cube sh)
peek = (sh -> Cube sh) -> Ptr (Cube sh) -> IO (Cube sh)
forall core wrapper.
Storable core =>
(core -> wrapper) -> Ptr wrapper -> IO wrapper
Store.peek sh -> Cube sh
forall sh. sh -> Cube sh
Cube
poke :: Ptr (Cube sh) -> Cube sh -> IO ()
poke = (Cube sh -> sh) -> Ptr (Cube sh) -> Cube sh -> IO ()
forall core wrapper.
Storable core =>
(wrapper -> core) -> Ptr wrapper -> wrapper -> IO ()
Store.poke Cube sh -> sh
forall sh. Cube sh -> sh
cubeSize
instance (C sh) => C (Cube sh) where
size :: Cube sh -> Int
size (Cube sh
sh) = sh -> Int
forall sh. C sh => sh -> Int
size sh
sh Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
3::Int)
uncheckedSize :: Cube sh -> Int
uncheckedSize (Cube sh
sh) = sh -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh
sh Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
3::Int)
instance (Indexed sh) => Indexed (Cube sh) where
type Index (Cube sh) = (Index sh, Index sh, Index sh)
indices :: Cube sh -> [Index (Cube sh)]
indices (Cube sh
sh) = (sh, sh, sh) -> [Index (sh, sh, sh)]
forall sh. Indexed sh => sh -> [Index sh]
indices (sh
sh,sh
sh,sh
sh)
offset :: Cube sh -> Index (Cube sh) -> Int
offset (Cube sh
sh) = (sh, sh, sh) -> Index (sh, sh, sh) -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset (sh
sh,sh
sh,sh
sh)
uncheckedOffset :: Cube sh -> Index (Cube sh) -> Int
uncheckedOffset (Cube sh
sh) = (sh, sh, sh) -> Index (sh, sh, sh) -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset (sh
sh,sh
sh,sh
sh)
sizeOffset :: Cube sh -> (Int, Index (Cube sh) -> Int)
sizeOffset (Cube sh
sh) =
let szo :: (Int, Index sh -> Int)
szo = sh -> (Int, Index sh -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh
sh
in ((Index sh -> Int) -> (Index sh, Index sh, Index sh) -> Int)
-> (Int, Index sh -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> ((Index sh, Index sh, Index sh) -> Index sh)
-> (Index sh, Index sh, Index sh)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh, Index sh, Index sh) -> Index sh
forall a b c. (a, b, c) -> a
fst3) (Int, Index sh -> Int)
szo
(Int, (Index sh, Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh -> Int) -> (Index sh, Index sh, Index sh) -> Int)
-> (Int, Index sh -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> ((Index sh, Index sh, Index sh) -> Index sh)
-> (Index sh, Index sh, Index sh)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh, Index sh, Index sh) -> Index sh
forall a b c. (a, b, c) -> b
snd3) (Int, Index sh -> Int)
szo
(Int, (Index sh, Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh -> Int) -> (Index sh, Index sh, Index sh) -> Int)
-> (Int, Index sh -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> ((Index sh, Index sh, Index sh) -> Index sh)
-> (Index sh, Index sh, Index sh)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh, Index sh, Index sh) -> Index sh
forall a b c. (a, b, c) -> c
thd3) (Int, Index sh -> Int)
szo
uncheckedSizeOffset :: Cube sh -> (Int, Index (Cube sh) -> Int)
uncheckedSizeOffset (Cube sh
sh) =
let szo :: (Int, Index sh -> Int)
szo = sh -> (Int, Index sh -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh
sh
in ((Index sh -> Int) -> (Index sh, Index sh, Index sh) -> Int)
-> (Int, Index sh -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> ((Index sh, Index sh, Index sh) -> Index sh)
-> (Index sh, Index sh, Index sh)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh, Index sh, Index sh) -> Index sh
forall a b c. (a, b, c) -> a
fst3) (Int, Index sh -> Int)
szo
(Int, (Index sh, Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh -> Int) -> (Index sh, Index sh, Index sh) -> Int)
-> (Int, Index sh -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> ((Index sh, Index sh, Index sh) -> Index sh)
-> (Index sh, Index sh, Index sh)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh, Index sh, Index sh) -> Index sh
forall a b c. (a, b, c) -> b
snd3) (Int, Index sh -> Int)
szo
(Int, (Index sh, Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
forall a ix. Num a => (a, ix -> a) -> (a, ix -> a) -> (a, ix -> a)
`combineSizeOffset`
((Index sh -> Int) -> (Index sh, Index sh, Index sh) -> Int)
-> (Int, Index sh -> Int)
-> (Int, (Index sh, Index sh, Index sh) -> Int)
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd ((Index sh -> Int)
-> ((Index sh, Index sh, Index sh) -> Index sh)
-> (Index sh, Index sh, Index sh)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Index sh, Index sh, Index sh) -> Index sh
forall a b c. (a, b, c) -> c
thd3) (Int, Index sh -> Int)
szo
inBounds :: Cube sh -> Index (Cube sh) -> Bool
inBounds (Cube sh
sh) = (sh, sh, sh) -> Index (sh, sh, sh) -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds (sh
sh,sh
sh,sh
sh)
instance (InvIndexed sh) => InvIndexed (Cube sh) where
indexFromOffset :: Cube sh -> Int -> Index (Cube sh)
indexFromOffset (Cube sh
sh) = (sh, sh, sh) -> Int -> Index (sh, sh, sh)
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset (sh
sh,sh
sh,sh
sh)
uncheckedIndexFromOffset :: Cube sh -> Int -> Index (Cube sh)
uncheckedIndexFromOffset (Cube sh
sh) = (sh, sh, sh) -> Int -> Index (sh, sh, sh)
forall sh. InvIndexed sh => sh -> Int -> Index sh
uncheckedIndexFromOffset (sh
sh,sh
sh,sh
sh)
data Lower = Lower deriving (Lower -> Lower -> Bool
(Lower -> Lower -> Bool) -> (Lower -> Lower -> Bool) -> Eq Lower
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Lower -> Lower -> Bool
$c/= :: Lower -> Lower -> Bool
== :: Lower -> Lower -> Bool
$c== :: Lower -> Lower -> Bool
Eq, Int -> Lower -> ShowS
[Lower] -> ShowS
Lower -> String
(Int -> Lower -> ShowS)
-> (Lower -> String) -> ([Lower] -> ShowS) -> Show Lower
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Lower] -> ShowS
$cshowList :: [Lower] -> ShowS
show :: Lower -> String
$cshow :: Lower -> String
showsPrec :: Int -> Lower -> ShowS
$cshowsPrec :: Int -> Lower -> ShowS
Show)
data Upper = Upper deriving (Upper -> Upper -> Bool
(Upper -> Upper -> Bool) -> (Upper -> Upper -> Bool) -> Eq Upper
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Upper -> Upper -> Bool
$c/= :: Upper -> Upper -> Bool
== :: Upper -> Upper -> Bool
$c== :: Upper -> Upper -> Bool
Eq, Int -> Upper -> ShowS
[Upper] -> ShowS
Upper -> String
(Int -> Upper -> ShowS)
-> (Upper -> String) -> ([Upper] -> ShowS) -> Show Upper
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Upper] -> ShowS
$cshowList :: [Upper] -> ShowS
show :: Upper -> String
$cshow :: Upper -> String
showsPrec :: Int -> Upper -> ShowS
$cshowsPrec :: Int -> Upper -> ShowS
Show)
class TriangularPart part where
switchTriangularPart :: f Lower -> f Upper -> f part
instance TriangularPart Lower where switchTriangularPart :: f Lower -> f Upper -> f Lower
switchTriangularPart f Lower
f f Upper
_ = f Lower
f
instance TriangularPart Upper where switchTriangularPart :: f Lower -> f Upper -> f Upper
switchTriangularPart f Lower
_ f Upper
f = f Upper
f
getConstAs :: c -> Const a c -> a
getConstAs :: c -> Const a c -> a
getConstAs c
_ = Const a c -> a
forall a k (b :: k). Const a b -> a
getConst
caseTriangularPart :: (TriangularPart part) => part -> a -> a -> a
caseTriangularPart :: part -> a -> a -> a
caseTriangularPart part
part a
lo a
up =
part -> Const a part -> a
forall c a. c -> Const a c -> a
getConstAs part
part (Const a part -> a) -> Const a part -> a
forall a b. (a -> b) -> a -> b
$ Const a Lower -> Const a Upper -> Const a part
forall part (f :: * -> *).
TriangularPart part =>
f Lower -> f Upper -> f part
switchTriangularPart (a -> Const a Lower
forall k a (b :: k). a -> Const a b
Const a
lo) (a -> Const a Upper
forall k a (b :: k). a -> Const a b
Const a
up)
data Triangular part size =
Triangular {
Triangular part size -> part
triangularPart :: part,
Triangular part size -> size
triangularSize :: size
} deriving (Int -> Triangular part size -> ShowS
[Triangular part size] -> ShowS
Triangular part size -> String
(Int -> Triangular part size -> ShowS)
-> (Triangular part size -> String)
-> ([Triangular part size] -> ShowS)
-> Show (Triangular part size)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall part size.
(Show part, Show size) =>
Int -> Triangular part size -> ShowS
forall part size.
(Show part, Show size) =>
[Triangular part size] -> ShowS
forall part size.
(Show part, Show size) =>
Triangular part size -> String
showList :: [Triangular part size] -> ShowS
$cshowList :: forall part size.
(Show part, Show size) =>
[Triangular part size] -> ShowS
show :: Triangular part size -> String
$cshow :: forall part size.
(Show part, Show size) =>
Triangular part size -> String
showsPrec :: Int -> Triangular part size -> ShowS
$cshowsPrec :: forall part size.
(Show part, Show size) =>
Int -> Triangular part size -> ShowS
Show)
newtype Equal part = Equal {Equal part -> part -> part -> Bool
getEqual :: part -> part -> Bool}
equalPart :: (TriangularPart part) => part -> part -> Bool
equalPart :: part -> part -> Bool
equalPart = Equal part -> part -> part -> Bool
forall part. Equal part -> part -> part -> Bool
getEqual (Equal part -> part -> part -> Bool)
-> Equal part -> part -> part -> Bool
forall a b. (a -> b) -> a -> b
$ Equal Lower -> Equal Upper -> Equal part
forall part (f :: * -> *).
TriangularPart part =>
f Lower -> f Upper -> f part
switchTriangularPart ((Lower -> Lower -> Bool) -> Equal Lower
forall part. (part -> part -> Bool) -> Equal part
Equal Lower -> Lower -> Bool
forall a. Eq a => a -> a -> Bool
(==)) ((Upper -> Upper -> Bool) -> Equal Upper
forall part. (part -> part -> Bool) -> Equal part
Equal Upper -> Upper -> Bool
forall a. Eq a => a -> a -> Bool
(==))
instance (TriangularPart part, Eq size) => Eq (Triangular part size) where
Triangular part size
x== :: Triangular part size -> Triangular part size -> Bool
==Triangular part size
y = (part -> part -> Bool)
-> (Triangular part size -> part)
-> Triangular part size
-> Triangular part size
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
compose2 part -> part -> Bool
forall part. TriangularPart part => part -> part -> Bool
equalPart Triangular part size -> part
forall part size. Triangular part size -> part
triangularPart Triangular part size
x Triangular part size
y Bool -> Bool -> Bool
&& (Triangular part size -> size)
-> Triangular part size -> Triangular part size -> Bool
forall b a. Eq b => (a -> b) -> a -> a -> Bool
equating Triangular part size -> size
forall part size. Triangular part size -> size
triangularSize Triangular part size
x Triangular part size
y
type LowerTriangular = Triangular Lower
type UpperTriangular = Triangular Upper
lowerTriangular :: size -> LowerTriangular size
lowerTriangular :: size -> LowerTriangular size
lowerTriangular = Lower -> size -> LowerTriangular size
forall part size. part -> size -> Triangular part size
Triangular Lower
Lower
upperTriangular :: size -> UpperTriangular size
upperTriangular :: size -> UpperTriangular size
upperTriangular = Upper -> size -> UpperTriangular size
forall part size. part -> size -> Triangular part size
Triangular Upper
Upper
newtype Flip f b a = Flip {Flip f b a -> f a b
getFlip :: f a b}
instance
(TriangularPart part, NFData size) => NFData (Triangular part size) where
rnf :: Triangular part size -> ()
rnf (Triangular part
part size
sz) =
((), size) -> ()
forall a. NFData a => a -> ()
rnf
((Flip (->) () part -> part -> ())
-> part -> Flip (->) () part -> ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Flip (->) () part -> part -> ()
forall (f :: * -> * -> *) b a. Flip f b a -> f a b
getFlip part
part (Flip (->) () part -> ()) -> Flip (->) () part -> ()
forall a b. (a -> b) -> a -> b
$
Flip (->) () Lower -> Flip (->) () Upper -> Flip (->) () part
forall part (f :: * -> *).
TriangularPart part =>
f Lower -> f Upper -> f part
switchTriangularPart ((Lower -> ()) -> Flip (->) () Lower
forall (f :: * -> * -> *) b a. f a b -> Flip f b a
Flip ((Lower -> ()) -> Flip (->) () Lower)
-> (Lower -> ()) -> Flip (->) () Lower
forall a b. (a -> b) -> a -> b
$ \Lower
Lower -> ()) ((Upper -> ()) -> Flip (->) () Upper
forall (f :: * -> * -> *) b a. f a b -> Flip f b a
Flip ((Upper -> ()) -> Flip (->) () Upper)
-> (Upper -> ()) -> Flip (->) () Upper
forall a b. (a -> b) -> a -> b
$ \Upper
Upper -> ()),
size
sz)
instance (TriangularPart part, C size) => C (Triangular part size) where
size :: Triangular part size -> Int
size (Triangular part
_part size
sz) = Int -> Int
triangleSize (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ size -> Int
forall sh. C sh => sh -> Int
size size
sz
uncheckedSize :: Triangular part size -> Int
uncheckedSize (Triangular part
_part size
sz) = Int -> Int
triangleSize (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ size -> Int
forall sh. C sh => sh -> Int
uncheckedSize size
sz
instance
(TriangularPart part, Indexed size) =>
Indexed (Triangular part size) where
type Index (Triangular part size) = (Index size, Index size)
indices :: Triangular part size -> [Index (Triangular part size)]
indices (Triangular part
part size
sz) =
let ixs :: [Index size]
ixs = size -> [Index size]
forall sh. Indexed sh => sh -> [Index sh]
indices size
sz
in [[(Index size, Index size)]] -> [(Index size, Index size)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(Index size, Index size)]] -> [(Index size, Index size)])
-> [[(Index size, Index size)]] -> [(Index size, Index size)]
forall a b. (a -> b) -> a -> b
$
part
-> [[(Index size, Index size)]]
-> [[(Index size, Index size)]]
-> [[(Index size, Index size)]]
forall part a. TriangularPart part => part -> a -> a -> a
caseTriangularPart part
part
(([Index size] -> Index size -> [(Index size, Index size)])
-> [[Index size]] -> [Index size] -> [[(Index size, Index size)]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\[Index size]
cs Index size
r -> (Index size -> (Index size, Index size))
-> [Index size] -> [(Index size, Index size)]
forall a b. (a -> b) -> [a] -> [b]
map ((,) Index size
r) [Index size]
cs)
(T [] [Index size] -> [[Index size]]
forall (f :: * -> *) a. T f a -> f a
NonEmpty.tail (T [] [Index size] -> [[Index size]])
-> T [] [Index size] -> [[Index size]]
forall a b. (a -> b) -> a -> b
$ [Index size] -> T [] [Index size]
forall (f :: * -> *) (g :: * -> *) a.
(Traversable f, Snoc g, Empty g) =>
f a -> T f (g a)
NonEmpty.inits [Index size]
ixs) [Index size]
ixs)
((Index size -> [Index size] -> [(Index size, Index size)])
-> [Index size] -> [[Index size]] -> [[(Index size, Index size)]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Index size
r [Index size]
cs -> (Index size -> (Index size, Index size))
-> [Index size] -> [(Index size, Index size)]
forall a b. (a -> b) -> [a] -> [b]
map ((,) Index size
r) [Index size]
cs) [Index size]
ixs ([[Index size]] -> [[(Index size, Index size)]])
-> [[Index size]] -> [[(Index size, Index size)]]
forall a b. (a -> b) -> a -> b
$ [Index size] -> [[Index size]]
forall a. [a] -> [[a]]
tails [Index size]
ixs)
uncheckedOffset :: Triangular part size -> Index (Triangular part size) -> Int
uncheckedOffset Triangular part size
sh = (Int, (Index size, Index size) -> Int)
-> (Index size, Index size) -> Int
forall a b. (a, b) -> b
snd ((Int, (Index size, Index size) -> Int)
-> (Index size, Index size) -> Int)
-> (Int, (Index size, Index size) -> Int)
-> (Index size, Index size)
-> Int
forall a b. (a -> b) -> a -> b
$ Triangular part size -> (Int, Index (Triangular part size) -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset Triangular part size
sh
sizeOffset :: Triangular part size -> (Int, Index (Triangular part size) -> Int)
sizeOffset (Triangular part
part size
sz) =
let (Int
n, Index size -> Int
getOffset) = size -> (Int, Index size -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset size
sz
in (Int -> Int
triangleSize Int
n, \(rs,cs) ->
let r :: Int
r = Index size -> Int
getOffset Index size
rs
c :: Int
c = Index size -> Int
getOffset Index size
cs
in if part -> Int -> Int -> Bool
forall part a.
(TriangularPart part, Ord a) =>
part -> a -> a -> Bool
compareIndices part
part Int
r Int
c
then part -> Int -> (Int, Int) -> Int
forall part.
TriangularPart part =>
part -> Int -> (Int, Int) -> Int
triangleOffset part
part Int
n (Int
r,Int
c)
else String -> Int
forall a. HasCallStack => String -> a
error String
"Shape.Triangular.sizeOffset: wrong array part")
uncheckedSizeOffset :: Triangular part size -> (Int, Index (Triangular part size) -> Int)
uncheckedSizeOffset (Triangular part
part size
sz) =
let (Int
n, Index size -> Int
getOffset) = size -> (Int, Index size -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset size
sz
in (Int -> Int
triangleSize Int
n, \(rs,cs) ->
part -> Int -> (Int, Int) -> Int
forall part.
TriangularPart part =>
part -> Int -> (Int, Int) -> Int
triangleOffset part
part Int
n (Index size -> Int
getOffset Index size
rs, Index size -> Int
getOffset Index size
cs))
inBounds :: Triangular part size -> Index (Triangular part size) -> Bool
inBounds (Triangular part
part size
sz) ix :: Index (Triangular part size)
ix@(r,c) =
(size, size) -> Index (size, size) -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds (size
sz,size
sz) Index (size, size)
Index (Triangular part size)
ix
Bool -> Bool -> Bool
&&
let getOffset :: Index size -> Int
getOffset = size -> Index size -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset size
sz
in part -> Int -> Int -> Bool
forall part a.
(TriangularPart part, Ord a) =>
part -> a -> a -> Bool
compareIndices part
part (Index size -> Int
getOffset Index size
r) (Index size -> Int
getOffset Index size
c)
triangleOffset :: TriangularPart part => part -> Int -> (Int, Int) -> Int
triangleOffset :: part -> Int -> (Int, Int) -> Int
triangleOffset part
part Int
n (Int
r,Int
c) =
part -> Int -> Int -> Int
forall part a. TriangularPart part => part -> a -> a -> a
caseTriangularPart part
part
(Int -> Int
triangleSize Int
r Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
c)
(Int -> Int
triangleSize Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int -> Int
triangleSize (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
r) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
cInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
r)
compareIndices :: (TriangularPart part, Ord a) => part -> a -> a -> Bool
compareIndices :: part -> a -> a -> Bool
compareIndices part
part = part -> (a -> a -> Bool) -> (a -> a -> Bool) -> a -> a -> Bool
forall part a. TriangularPart part => part -> a -> a -> a
caseTriangularPart part
part a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(>=) a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
instance
(TriangularPart part, InvIndexed size) =>
InvIndexed (Triangular part size) where
indexFromOffset :: Triangular part size -> Int -> Index (Triangular part size)
indexFromOffset (Triangular part
part size
sz) Int
k =
(Int -> Index size, Int -> Index size)
-> (Int, Int) -> (Index size, Index size)
forall a c b d. (a -> c, b -> d) -> (a, b) -> (c, d)
mapPair (size -> Int -> Index size
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset size
sz, size -> Int -> Index size
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset size
sz) ((Int, Int) -> (Index size, Index size))
-> (Int, Int) -> (Index size, Index size)
forall a b. (a -> b) -> a -> b
$
part -> (Int, Int) -> (Int, Int) -> (Int, Int)
forall part a. TriangularPart part => part -> a -> a -> a
caseTriangularPart part
part
(let r :: Int
r = Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor (Int -> Double
triangleRootDouble Int
k)
in (Int
r, Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int -> Int
triangleSize Int
r))
(let n :: Int
n = size -> Int
forall sh. C sh => sh -> Int
size size
sz
triSize :: Int
triSize = Int -> Int
triangleSize Int
n
rr :: Int
rr = Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Int -> Double
triangleRootDouble (Int
triSizeInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
k))
r :: Int
r = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
rr
in (Int
r, Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
r Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
triSize Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int -> Int
triangleSize Int
rr)))
triangleSize :: Int -> Int
triangleSize :: Int -> Int
triangleSize Int
n = Int -> Int -> Int
forall a. Integral a => a -> a -> a
div (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
*(Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) Int
2
triangleRoot :: Floating a => a -> a
triangleRoot :: a -> a
triangleRoot a
sz = (a -> a
forall a. Floating a => a -> a
sqrt (a
8a -> a -> a
forall a. Num a => a -> a -> a
*a
sza -> a -> a
forall a. Num a => a -> a -> a
+a
1)a -> a -> a
forall a. Num a => a -> a -> a
-a
1)a -> a -> a
forall a. Fractional a => a -> a -> a
/a
2
triangleRootDouble :: Int -> Double
triangleRootDouble :: Int -> Double
triangleRootDouble = Double -> Double
forall a. Floating a => a -> a
triangleRoot (Double -> Double) -> (Int -> Double) -> Int -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance
(TriangularPart part, Static size) =>
Static (Triangular part size) where
static :: Triangular part size
static = part -> size -> Triangular part size
forall part size. part -> size -> Triangular part size
Triangular part
forall part. TriangularPart part => part
autoPart size
forall sh. Static sh => sh
static
autoPart :: (TriangularPart part) => part
autoPart :: part
autoPart = Identity part -> part
forall a. Identity a -> a
runIdentity (Identity part -> part) -> Identity part -> part
forall a b. (a -> b) -> a -> b
$ Identity Lower -> Identity Upper -> Identity part
forall part (f :: * -> *).
TriangularPart part =>
f Lower -> f Upper -> f part
switchTriangularPart (Lower -> Identity Lower
forall a. a -> Identity a
Identity Lower
Lower) (Upper -> Identity Upper
forall a. a -> Identity a
Identity Upper
Upper)
newtype Cyclic n = Cyclic {Cyclic n -> n
cyclicSize :: n}
deriving (Cyclic n -> Cyclic n -> Bool
(Cyclic n -> Cyclic n -> Bool)
-> (Cyclic n -> Cyclic n -> Bool) -> Eq (Cyclic n)
forall n. Eq n => Cyclic n -> Cyclic n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cyclic n -> Cyclic n -> Bool
$c/= :: forall n. Eq n => Cyclic n -> Cyclic n -> Bool
== :: Cyclic n -> Cyclic n -> Bool
$c== :: forall n. Eq n => Cyclic n -> Cyclic n -> Bool
Eq, Int -> Cyclic n -> ShowS
[Cyclic n] -> ShowS
Cyclic n -> String
(Int -> Cyclic n -> ShowS)
-> (Cyclic n -> String) -> ([Cyclic n] -> ShowS) -> Show (Cyclic n)
forall n. Show n => Int -> Cyclic n -> ShowS
forall n. Show n => [Cyclic n] -> ShowS
forall n. Show n => Cyclic n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cyclic n] -> ShowS
$cshowList :: forall n. Show n => [Cyclic n] -> ShowS
show :: Cyclic n -> String
$cshow :: forall n. Show n => Cyclic n -> String
showsPrec :: Int -> Cyclic n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> Cyclic n -> ShowS
Show)
instance Functor Cyclic where
fmap :: (a -> b) -> Cyclic a -> Cyclic b
fmap a -> b
f (Cyclic a
n) = b -> Cyclic b
forall n. n -> Cyclic n
Cyclic (b -> Cyclic b) -> b -> Cyclic b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
n
instance Applicative Cyclic where
pure :: a -> Cyclic a
pure = a -> Cyclic a
forall n. n -> Cyclic n
Cyclic
Cyclic a -> b
f <*> :: Cyclic (a -> b) -> Cyclic a -> Cyclic b
<*> Cyclic a
n = b -> Cyclic b
forall n. n -> Cyclic n
Cyclic (b -> Cyclic b) -> b -> Cyclic b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
n
instance (NFData n) => NFData (Cyclic n) where
rnf :: Cyclic n -> ()
rnf (Cyclic n
n) = n -> ()
forall a. NFData a => a -> ()
rnf n
n
instance (Storable n) => Storable (Cyclic n) where
sizeOf :: Cyclic n -> Int
sizeOf = (Cyclic n -> n) -> Cyclic n -> Int
forall core wrapper.
Storable core =>
(wrapper -> core) -> wrapper -> Int
Store.sizeOf Cyclic n -> n
forall n. Cyclic n -> n
cyclicSize
alignment :: Cyclic n -> Int
alignment = (Cyclic n -> n) -> Cyclic n -> Int
forall core wrapper.
Storable core =>
(wrapper -> core) -> wrapper -> Int
Store.alignment Cyclic n -> n
forall n. Cyclic n -> n
cyclicSize
peek :: Ptr (Cyclic n) -> IO (Cyclic n)
peek = (n -> Cyclic n) -> Ptr (Cyclic n) -> IO (Cyclic n)
forall core wrapper.
Storable core =>
(core -> wrapper) -> Ptr wrapper -> IO wrapper
Store.peek n -> Cyclic n
forall n. n -> Cyclic n
Cyclic
poke :: Ptr (Cyclic n) -> Cyclic n -> IO ()
poke = (Cyclic n -> n) -> Ptr (Cyclic n) -> Cyclic n -> IO ()
forall core wrapper.
Storable core =>
(wrapper -> core) -> Ptr wrapper -> wrapper -> IO ()
Store.poke Cyclic n -> n
forall n. Cyclic n -> n
cyclicSize
instance (Integral n) => C (Cyclic n) where
size :: Cyclic n -> Int
size (Cyclic n
len) = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
len
uncheckedSize :: Cyclic n -> Int
uncheckedSize (Cyclic n
len) = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
len
instance (Integral n) => Indexed (Cyclic n) where
type Index (Cyclic n) = n
indices :: Cyclic n -> [Index (Cyclic n)]
indices (Cyclic n
len) = ZeroBased n -> [Index (ZeroBased n)]
forall sh. Indexed sh => sh -> [Index sh]
indices (ZeroBased n -> [Index (ZeroBased n)])
-> ZeroBased n -> [Index (ZeroBased n)]
forall a b. (a -> b) -> a -> b
$ n -> ZeroBased n
forall n. n -> ZeroBased n
ZeroBased n
len
offset :: Cyclic n -> Index (Cyclic n) -> Int
offset = Cyclic n -> Index (Cyclic n) -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset
uncheckedOffset :: Cyclic n -> Index (Cyclic n) -> Int
uncheckedOffset (Cyclic n
len) Index (Cyclic n)
ix = n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (n -> Int) -> n -> Int
forall a b. (a -> b) -> a -> b
$ n -> n -> n
forall a. Integral a => a -> a -> a
mod n
Index (Cyclic n)
ix n
len
inBounds :: Cyclic n -> Index (Cyclic n) -> Bool
inBounds (Cyclic n
len) Index (Cyclic n)
_ix = n
lenn -> n -> Bool
forall a. Ord a => a -> a -> Bool
>n
0
instance (Integral n) => InvIndexed (Cyclic n) where
indexFromOffset :: Cyclic n -> Int -> Index (Cyclic n)
indexFromOffset (Cyclic n
len) Int
k0 =
let k :: n
k = Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k0
in if n
0n -> n -> Bool
forall a. Ord a => a -> a -> Bool
<=n
k Bool -> Bool -> Bool
&& n
kn -> n -> Bool
forall a. Ord a => a -> a -> Bool
<n
len
then n
Index (Cyclic n)
k
else String -> Int -> n
forall a. String -> Int -> a
errorIndexFromOffset String
"Cyclic" Int
k0
uncheckedIndexFromOffset :: Cyclic n -> Int -> Index (Cyclic n)
uncheckedIndexFromOffset Cyclic n
_ Int
k = Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k
infixr 5 :+:
data sh0:+:sh1 = sh0:+:sh1
deriving ((sh0 :+: sh1) -> (sh0 :+: sh1) -> Bool
((sh0 :+: sh1) -> (sh0 :+: sh1) -> Bool)
-> ((sh0 :+: sh1) -> (sh0 :+: sh1) -> Bool) -> Eq (sh0 :+: sh1)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall sh0 sh1.
(Eq sh0, Eq sh1) =>
(sh0 :+: sh1) -> (sh0 :+: sh1) -> Bool
/= :: (sh0 :+: sh1) -> (sh0 :+: sh1) -> Bool
$c/= :: forall sh0 sh1.
(Eq sh0, Eq sh1) =>
(sh0 :+: sh1) -> (sh0 :+: sh1) -> Bool
== :: (sh0 :+: sh1) -> (sh0 :+: sh1) -> Bool
$c== :: forall sh0 sh1.
(Eq sh0, Eq sh1) =>
(sh0 :+: sh1) -> (sh0 :+: sh1) -> Bool
Eq, Int -> (sh0 :+: sh1) -> ShowS
[sh0 :+: sh1] -> ShowS
(sh0 :+: sh1) -> String
(Int -> (sh0 :+: sh1) -> ShowS)
-> ((sh0 :+: sh1) -> String)
-> ([sh0 :+: sh1] -> ShowS)
-> Show (sh0 :+: sh1)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall sh0 sh1.
(Show sh0, Show sh1) =>
Int -> (sh0 :+: sh1) -> ShowS
forall sh0 sh1. (Show sh0, Show sh1) => [sh0 :+: sh1] -> ShowS
forall sh0 sh1. (Show sh0, Show sh1) => (sh0 :+: sh1) -> String
showList :: [sh0 :+: sh1] -> ShowS
$cshowList :: forall sh0 sh1. (Show sh0, Show sh1) => [sh0 :+: sh1] -> ShowS
show :: (sh0 :+: sh1) -> String
$cshow :: forall sh0 sh1. (Show sh0, Show sh1) => (sh0 :+: sh1) -> String
showsPrec :: Int -> (sh0 :+: sh1) -> ShowS
$cshowsPrec :: forall sh0 sh1.
(Show sh0, Show sh1) =>
Int -> (sh0 :+: sh1) -> ShowS
Show)
instance (NFData sh0, NFData sh1) => NFData (sh0:+:sh1) where
rnf :: (sh0 :+: sh1) -> ()
rnf (sh0
sh0:+:sh1
sh1) = (sh0, sh1) -> ()
forall a. NFData a => a -> ()
rnf (sh0
sh0,sh1
sh1)
instance (C sh0, C sh1) => C (sh0:+:sh1) where
size :: (sh0 :+: sh1) -> Int
size (sh0
sh0:+:sh1
sh1) = sh0 -> Int
forall sh. C sh => sh -> Int
size sh0
sh0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ sh1 -> Int
forall sh. C sh => sh -> Int
size sh1
sh1
uncheckedSize :: (sh0 :+: sh1) -> Int
uncheckedSize (sh0
sh0:+:sh1
sh1) = sh0 -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh0
sh0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ sh1 -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh1
sh1
instance (Indexed sh0, Indexed sh1) => Indexed (sh0:+:sh1) where
type Index (sh0:+:sh1) = Either (Index sh0) (Index sh1)
indices :: (sh0 :+: sh1) -> [Index (sh0 :+: sh1)]
indices (sh0
sh0:+:sh1
sh1) = (Index sh0 -> Either (Index sh0) (Index sh1))
-> [Index sh0] -> [Either (Index sh0) (Index sh1)]
forall a b. (a -> b) -> [a] -> [b]
map Index sh0 -> Either (Index sh0) (Index sh1)
forall a b. a -> Either a b
Left (sh0 -> [Index sh0]
forall sh. Indexed sh => sh -> [Index sh]
indices sh0
sh0) [Either (Index sh0) (Index sh1)]
-> [Either (Index sh0) (Index sh1)]
-> [Either (Index sh0) (Index sh1)]
forall a. [a] -> [a] -> [a]
++ (Index sh1 -> Either (Index sh0) (Index sh1))
-> [Index sh1] -> [Either (Index sh0) (Index sh1)]
forall a b. (a -> b) -> [a] -> [b]
map Index sh1 -> Either (Index sh0) (Index sh1)
forall a b. b -> Either a b
Right (sh1 -> [Index sh1]
forall sh. Indexed sh => sh -> [Index sh]
indices sh1
sh1)
offset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Int
offset (sh0
sh0:+:sh1
sh1) Index (sh0 :+: sh1)
ix =
case Index (sh0 :+: sh1)
ix of
Left ix0 -> sh0 -> Index sh0 -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset sh0
sh0 Index sh0
ix0
Right ix1 -> sh0 -> Int
forall sh. C sh => sh -> Int
size sh0
sh0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ sh1 -> Index sh1 -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
offset sh1
sh1 Index sh1
ix1
uncheckedOffset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Int
uncheckedOffset (sh0
sh0:+:sh1
sh1) Index (sh0 :+: sh1)
ix =
case Index (sh0 :+: sh1)
ix of
Left ix0 -> sh0 -> Index sh0 -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset sh0
sh0 Index sh0
ix0
Right ix1 -> sh0 -> Int
forall sh. C sh => sh -> Int
uncheckedSize sh0
sh0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ sh1 -> Index sh1 -> Int
forall sh. Indexed sh => sh -> Index sh -> Int
uncheckedOffset sh1
sh1 Index sh1
ix1
sizeOffset :: (sh0 :+: sh1) -> (Int, Index (sh0 :+: sh1) -> Int)
sizeOffset (sh0
sh0:+:sh1
sh1) =
let (Int
n0, Index sh0 -> Int
getOffset0) = sh0 -> (Int, Index sh0 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh0
sh0
(Int
n1, Index sh1 -> Int
getOffset1) = sh1 -> (Int, Index sh1 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
sizeOffset sh1
sh1
in (Int
n0Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n1, (Index sh0 -> Int)
-> (Index sh1 -> Int) -> Either (Index sh0) (Index sh1) -> Int
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Index sh0 -> Int
getOffset0 ((Int
n0Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> Int) -> (Index sh1 -> Int) -> Index sh1 -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index sh1 -> Int
getOffset1))
uncheckedSizeOffset :: (sh0 :+: sh1) -> (Int, Index (sh0 :+: sh1) -> Int)
uncheckedSizeOffset (sh0
sh0:+:sh1
sh1) =
let (Int
n0, Index sh0 -> Int
getOffset0) = sh0 -> (Int, Index sh0 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh0
sh0
(Int
n1, Index sh1 -> Int
getOffset1) = sh1 -> (Int, Index sh1 -> Int)
forall sh. Indexed sh => sh -> (Int, Index sh -> Int)
uncheckedSizeOffset sh1
sh1
in (Int
n0Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n1, (Index sh0 -> Int)
-> (Index sh1 -> Int) -> Either (Index sh0) (Index sh1) -> Int
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Index sh0 -> Int
getOffset0 ((Int
n0Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> Int) -> (Index sh1 -> Int) -> Index sh1 -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index sh1 -> Int
getOffset1))
inBounds :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Bool
inBounds (sh0
sh0:+:sh1
sh1) = (Index sh0 -> Bool)
-> (Index sh1 -> Bool) -> Either (Index sh0) (Index sh1) -> Bool
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (sh0 -> Index sh0 -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds sh0
sh0) (sh1 -> Index sh1 -> Bool
forall sh. Indexed sh => sh -> Index sh -> Bool
inBounds sh1
sh1)
instance (InvIndexed sh0, InvIndexed sh1) => InvIndexed (sh0:+:sh1) where
indexFromOffset :: (sh0 :+: sh1) -> Int -> Index (sh0 :+: sh1)
indexFromOffset (sh0
sh0:+:sh1
sh1) Int
k =
let pivot :: Int
pivot = sh0 -> Int
forall sh. C sh => sh -> Int
size sh0
sh0
in if Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
pivot
then Index sh0 -> Either (Index sh0) (Index sh1)
forall a b. a -> Either a b
Left (Index sh0 -> Either (Index sh0) (Index sh1))
-> Index sh0 -> Either (Index sh0) (Index sh1)
forall a b. (a -> b) -> a -> b
$ sh0 -> Int -> Index sh0
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset sh0
sh0 Int
k
else Index sh1 -> Either (Index sh0) (Index sh1)
forall a b. b -> Either a b
Right (Index sh1 -> Either (Index sh0) (Index sh1))
-> Index sh1 -> Either (Index sh0) (Index sh1)
forall a b. (a -> b) -> a -> b
$ sh1 -> Int -> Index sh1
forall sh. InvIndexed sh => sh -> Int -> Index sh
indexFromOffset sh1
sh1 (Int -> Index sh1) -> Int -> Index sh1
forall a b. (a -> b) -> a -> b
$ Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
pivot
uncheckedIndexFromOffset :: (sh0 :+: sh1) -> Int -> Index (sh0 :+: sh1)
uncheckedIndexFromOffset (sh0
sh0:+:sh1
sh1) Int
k =
let pivot :: Int
pivot = sh0 -> Int
forall sh. C sh => sh -> Int
size sh0
sh0
in if Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
pivot
then Index sh0 -> Either (Index sh0) (Index sh1)
forall a b. a -> Either a b
Left (Index sh0 -> Either (Index sh0) (Index sh1))
-> Index sh0 -> Either (Index sh0) (Index sh1)
forall a b. (a -> b) -> a -> b
$ sh0 -> Int -> Index sh0
forall sh. InvIndexed sh => sh -> Int -> Index sh
uncheckedIndexFromOffset sh0
sh0 Int
k
else Index sh1 -> Either (Index sh0) (Index sh1)
forall a b. b -> Either a b
Right (Index sh1 -> Either (Index sh0) (Index sh1))
-> Index sh1 -> Either (Index sh0) (Index sh1)
forall a b. (a -> b) -> a -> b
$ sh1 -> Int -> Index sh1
forall sh. InvIndexed sh => sh -> Int -> Index sh
uncheckedIndexFromOffset sh1
sh1 (Int -> Index sh1) -> Int -> Index sh1
forall a b. (a -> b) -> a -> b
$ Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
pivot
instance (Static sh0, Static sh1) => Static (sh0:+:sh1) where
static :: sh0 :+: sh1
static = sh0
forall sh. Static sh => sh
staticsh0 -> sh1 -> sh0 :+: sh1
forall sh0 sh1. sh0 -> sh1 -> sh0 :+: sh1
:+:sh1
forall sh. Static sh => sh
static