{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Massiv.Core.Index.Ix
( Ix
, IxN((:>))
, type Sz
, pattern Sz
, type Ix1
, pattern Ix1
, pattern Sz1
, type Ix2(Ix2, (:.))
, pattern Sz2
, type Ix3
, pattern Ix3
, pattern Sz3
, type Ix4
, pattern Ix4
, pattern Sz4
, type Ix5
, pattern Ix5
, pattern Sz5
, HighIxN
) where
import Control.Monad.Catch (MonadThrow(..))
import Control.DeepSeq
import Data.Massiv.Core.Index.Internal
import Data.Proxy
import qualified GHC.Arr as I
import qualified Data.Vector.Generic as V
import qualified Data.Vector.Generic.Mutable as VM
import qualified Data.Vector.Unboxed as VU
import GHC.TypeLits
import System.Random.Stateful
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup
#endif
infixr 5 :>, :.
data Ix2 = {-# UNPACK #-} !Int :. {-# UNPACK #-} !Int
pattern Ix2 :: Int -> Int -> Ix2
pattern $bIx2 :: Int -> Int -> Ix2
$mIx2 :: forall r. Ix2 -> (Int -> Int -> r) -> (Void# -> r) -> r
Ix2 i2 i1 = i2 :. i1
{-# COMPLETE Ix2 #-}
pattern Sz2 :: Int -> Int -> Sz Ix2
pattern $bSz2 :: Int -> Int -> Sz Ix2
$mSz2 :: forall r. Sz Ix2 -> (Int -> Int -> r) -> (Void# -> r) -> r
Sz2 i2 i1 = Sz (i2 :. i1)
{-# COMPLETE Sz2 #-}
type Ix3 = IxN 3
pattern Ix3 :: Int -> Int -> Int -> Ix3
pattern $bIx3 :: Int -> Int -> Int -> Ix3
$mIx3 :: forall r. Ix3 -> (Int -> Int -> Int -> r) -> (Void# -> r) -> r
Ix3 i3 i2 i1 = i3 :> i2 :. i1
{-# COMPLETE Ix3 #-}
pattern Sz3 :: Int -> Int -> Int -> Sz Ix3
pattern $bSz3 :: Int -> Int -> Int -> Sz Ix3
$mSz3 :: forall r. Sz Ix3 -> (Int -> Int -> Int -> r) -> (Void# -> r) -> r
Sz3 i3 i2 i1 = Sz (i3 :> i2 :. i1)
{-# COMPLETE Sz3 #-}
type Ix4 = IxN 4
pattern Ix4 :: Int -> Int -> Int -> Int -> Ix4
pattern $bIx4 :: Int -> Int -> Int -> Int -> Ix4
$mIx4 :: forall r.
Ix4 -> (Int -> Int -> Int -> Int -> r) -> (Void# -> r) -> r
Ix4 i4 i3 i2 i1 = i4 :> i3 :> i2 :. i1
{-# COMPLETE Ix4 #-}
pattern Sz4 :: Int -> Int -> Int -> Int -> Sz Ix4
pattern $bSz4 :: Int -> Int -> Int -> Int -> Sz Ix4
$mSz4 :: forall r.
Sz Ix4 -> (Int -> Int -> Int -> Int -> r) -> (Void# -> r) -> r
Sz4 i4 i3 i2 i1 = Sz (i4 :> i3 :> i2 :. i1)
{-# COMPLETE Sz4 #-}
type Ix5 = IxN 5
pattern Ix5 :: Int -> Int -> Int -> Int -> Int -> Ix5
pattern $bIx5 :: Int -> Int -> Int -> Int -> Int -> Ix5
$mIx5 :: forall r.
Ix5 -> (Int -> Int -> Int -> Int -> Int -> r) -> (Void# -> r) -> r
Ix5 i5 i4 i3 i2 i1 = i5 :> i4 :> i3 :> i2 :. i1
{-# COMPLETE Ix5 #-}
pattern Sz5 :: Int -> Int -> Int -> Int -> Int -> Sz Ix5
pattern $bSz5 :: Int -> Int -> Int -> Int -> Int -> Sz Ix5
$mSz5 :: forall r.
Sz Ix5
-> (Int -> Int -> Int -> Int -> Int -> r) -> (Void# -> r) -> r
Sz5 i5 i4 i3 i2 i1 = Sz (i5 :> i4 :> i3 :> i2 :. i1)
{-# COMPLETE Sz5 #-}
data IxN (n :: Nat) = {-# UNPACK #-} !Int :> !(Ix (n - 1))
type family Ix (n :: Nat) = r | r -> n where
Ix 0 = Ix0
Ix 1 = Ix1
Ix 2 = Ix2
Ix n = IxN n
type instance Lower Ix2 = Ix1
type instance Lower (IxN n) = Ix (n - 1)
instance Show Ix2 where
showsPrec :: Int -> Ix2 -> ShowS
showsPrec Int
n (Int
i :. Int
j) = Int -> ShowS -> ShowS
showsPrecWrapped Int
n (Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
i ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
" :. " String -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
j)
instance Show (Ix (n - 1)) => Show (IxN n) where
showsPrec :: Int -> IxN n -> ShowS
showsPrec Int
n (Int
i :> Ix (n - 1)
ix) = Int -> ShowS -> ShowS
showsPrecWrapped Int
n (Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
i ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
" :> " String -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ix (n - 1) -> ShowS
forall a. Show a => a -> ShowS
shows Ix (n - 1)
ix)
instance Uniform Ix2 where
uniformM :: g -> m Ix2
uniformM g
g = Int -> Int -> Ix2
(:.) (Int -> Int -> Ix2) -> m Int -> m (Int -> Ix2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> g -> m Int
forall a g (m :: * -> *). (Uniform a, StatefulGen g m) => g -> m a
uniformM g
g m (Int -> Ix2) -> m Int -> m Ix2
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g -> m Int
forall a g (m :: * -> *). (Uniform a, StatefulGen g m) => g -> m a
uniformM g
g
{-# INLINE uniformM #-}
instance UniformRange Ix2 where
uniformRM :: (Ix2, Ix2) -> g -> m Ix2
uniformRM (Int
l1 :. Int
l2, Int
u1 :. Int
u2) g
g = Int -> Int -> Ix2
(:.) (Int -> Int -> Ix2) -> m Int -> m (Int -> Ix2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int, Int) -> g -> m Int
forall a g (m :: * -> *).
(UniformRange a, StatefulGen g m) =>
(a, a) -> g -> m a
uniformRM (Int
l1, Int
u1) g
g m (Int -> Ix2) -> m Int -> m Ix2
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Int, Int) -> g -> m Int
forall a g (m :: * -> *).
(UniformRange a, StatefulGen g m) =>
(a, a) -> g -> m a
uniformRM (Int
l2, Int
u2) g
g
{-# INLINE uniformRM #-}
instance Random Ix2
instance Uniform (Ix (n - 1)) => Uniform (IxN n) where
uniformM :: g -> m (IxN n)
uniformM g
g = Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
(:>) (Int -> Ix (n - 1) -> IxN n) -> m Int -> m (Ix (n - 1) -> IxN n)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> g -> m Int
forall a g (m :: * -> *). (Uniform a, StatefulGen g m) => g -> m a
uniformM g
g m (Ix (n - 1) -> IxN n) -> m (Ix (n - 1)) -> m (IxN n)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g -> m (Ix (n - 1))
forall a g (m :: * -> *). (Uniform a, StatefulGen g m) => g -> m a
uniformM g
g
{-# INLINE uniformM #-}
instance UniformRange (Ix (n - 1)) => UniformRange (IxN n) where
uniformRM :: (IxN n, IxN n) -> g -> m (IxN n)
uniformRM (Int
l1 :> Ix (n - 1)
l2, Int
u1 :> Ix (n - 1)
u2) g
g = Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
(:>) (Int -> Ix (n - 1) -> IxN n) -> m Int -> m (Ix (n - 1) -> IxN n)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int, Int) -> g -> m Int
forall a g (m :: * -> *).
(UniformRange a, StatefulGen g m) =>
(a, a) -> g -> m a
uniformRM (Int
l1, Int
u1) g
g m (Ix (n - 1) -> IxN n) -> m (Ix (n - 1)) -> m (IxN n)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Ix (n - 1), Ix (n - 1)) -> g -> m (Ix (n - 1))
forall a g (m :: * -> *).
(UniformRange a, StatefulGen g m) =>
(a, a) -> g -> m a
uniformRM (Ix (n - 1)
l2, Ix (n - 1)
u2) g
g
{-# INLINE uniformRM #-}
instance Random (Ix (n - 1)) => Random (IxN n) where
random :: g -> (IxN n, g)
random g
g =
case g -> (Int, g)
forall a g. (Random a, RandomGen g) => g -> (a, g)
random g
g of
(Int
i, g
g') ->
case g -> (Ix (n - 1), g)
forall a g. (Random a, RandomGen g) => g -> (a, g)
random g
g' of
(Ix (n - 1)
n, g
g'') -> (Int
i Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Ix (n - 1)
n, g
g'')
{-# INLINE random #-}
randomR :: (IxN n, IxN n) -> g -> (IxN n, g)
randomR (Int
l1 :> Ix (n - 1)
l2, Int
u1 :> Ix (n - 1)
u2) g
g =
case (Int, Int) -> g -> (Int, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (Int
l1, Int
u1) g
g of
(Int
i, g
g') ->
case (Ix (n - 1), Ix (n - 1)) -> g -> (Ix (n - 1), g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (Ix (n - 1)
l2, Ix (n - 1)
u2) g
g' of
(Ix (n - 1)
n, g
g'') -> (Int
i Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Ix (n - 1)
n, g
g'')
{-# INLINE randomR #-}
instance I.Ix Ix2 where
range :: (Ix2, Ix2) -> [Ix2]
range (Int
i1 :. Int
j1, Int
i2 :. Int
j2) = [Int
i Int -> Int -> Ix2
:. Int
j | Int
i <- [Int
i1 .. Int
i2], Int
j <- [Int
j1 .. Int
j2]]
{-# INLINE range #-}
unsafeIndex :: (Ix2, Ix2) -> Ix2 -> Int
unsafeIndex (Int
l1 :. Int
l2, Int
u1 :. Int
u2) (Int
i1 :. Int
i2) =
(Int, Int) -> Int -> Int
forall a. Ix a => (a, a) -> a -> Int
I.unsafeIndex (Int
l1, Int
u1) Int
i1 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int, Int) -> Int
forall a. Ix a => (a, a) -> Int
I.unsafeRangeSize (Int
l2, Int
u2) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int, Int) -> Int -> Int
forall a. Ix a => (a, a) -> a -> Int
I.unsafeIndex (Int
l2, Int
u2) Int
i2
{-# INLINE unsafeIndex #-}
inRange :: (Ix2, Ix2) -> Ix2 -> Bool
inRange (Int
l1 :. Int
l2, Int
u1 :. Int
u2) (Int
i1 :. Int
i2) = (Int, Int) -> Int -> Bool
forall a. Ix a => (a, a) -> a -> Bool
I.inRange (Int
l1, Int
u1) Int
i1 Bool -> Bool -> Bool
&& (Int, Int) -> Int -> Bool
forall a. Ix a => (a, a) -> a -> Bool
I.inRange (Int
l2, Int
u2) Int
i2
{-# INLINE inRange #-}
instance I.Ix (Ix (n - 1)) => I.Ix (IxN n) where
range :: (IxN n, IxN n) -> [IxN n]
range (Int
i1 :> Ix (n - 1)
j1, Int
i2 :> Ix (n - 1)
j2) = [Int
i Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Ix (n - 1)
j | Int
i <- [Int
i1 .. Int
i2], Ix (n - 1)
j <- (Ix (n - 1), Ix (n - 1)) -> [Ix (n - 1)]
forall a. Ix a => (a, a) -> [a]
I.range (Ix (n - 1)
j1, Ix (n - 1)
j2)]
{-# INLINE range #-}
unsafeIndex :: (IxN n, IxN n) -> IxN n -> Int
unsafeIndex (Int
l1 :> Ix (n - 1)
l2, Int
u1 :> Ix (n - 1)
u2) (Int
i1 :> Ix (n - 1)
i2) =
(Int, Int) -> Int -> Int
forall a. Ix a => (a, a) -> a -> Int
I.unsafeIndex (Int
l1, Int
u1) Int
i1 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Ix (n - 1), Ix (n - 1)) -> Int
forall a. Ix a => (a, a) -> Int
I.unsafeRangeSize (Ix (n - 1)
l2, Ix (n - 1)
u2) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Ix (n - 1), Ix (n - 1)) -> Ix (n - 1) -> Int
forall a. Ix a => (a, a) -> a -> Int
I.unsafeIndex (Ix (n - 1)
l2, Ix (n - 1)
u2) Ix (n - 1)
i2
{-# INLINE unsafeIndex #-}
inRange :: (IxN n, IxN n) -> IxN n -> Bool
inRange (Int
l1 :> Ix (n - 1)
l2, Int
u1 :> Ix (n - 1)
u2) (Int
i1 :> Ix (n - 1)
i2) = (Int, Int) -> Int -> Bool
forall a. Ix a => (a, a) -> a -> Bool
I.inRange (Int
l1, Int
u1) Int
i1 Bool -> Bool -> Bool
&& (Ix (n - 1), Ix (n - 1)) -> Ix (n - 1) -> Bool
forall a. Ix a => (a, a) -> a -> Bool
I.inRange (Ix (n - 1)
l2, Ix (n - 1)
u2) Ix (n - 1)
i2
{-# INLINE inRange #-}
instance Num Ix2 where
+ :: Ix2 -> Ix2 -> Ix2
(+) = (Int -> Int -> Int) -> Ix2 -> Ix2 -> Ix2
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 Int -> Int -> Int
forall a. Num a => a -> a -> a
(+)
{-# INLINE [1] (+) #-}
(-) = (Int -> Int -> Int) -> Ix2 -> Ix2 -> Ix2
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 (-)
{-# INLINE [1] (-) #-}
* :: Ix2 -> Ix2 -> Ix2
(*) = (Int -> Int -> Int) -> Ix2 -> Ix2 -> Ix2
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 Int -> Int -> Int
forall a. Num a => a -> a -> a
(*)
{-# INLINE [1] (*) #-}
negate :: Ix2 -> Ix2
negate = (Int -> Int) -> Ix2 -> Ix2
forall ix. Index ix => (Int -> Int) -> ix -> ix
liftIndex Int -> Int
forall a. Num a => a -> a
negate
{-# INLINE [1] negate #-}
abs :: Ix2 -> Ix2
abs = (Int -> Int) -> Ix2 -> Ix2
forall ix. Index ix => (Int -> Int) -> ix -> ix
liftIndex Int -> Int
forall a. Num a => a -> a
abs
{-# INLINE [1] abs #-}
signum :: Ix2 -> Ix2
signum = (Int -> Int) -> Ix2 -> Ix2
forall ix. Index ix => (Int -> Int) -> ix -> ix
liftIndex Int -> Int
forall a. Num a => a -> a
signum
{-# INLINE [1] signum #-}
fromInteger :: Integer -> Ix2
fromInteger = Int -> Ix2
forall ix. Index ix => Int -> ix
pureIndex (Int -> Ix2) -> (Integer -> Int) -> Integer -> Ix2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a. Num a => Integer -> a
fromInteger
{-# INLINE [1] fromInteger #-}
instance Num Ix3 where
+ :: Ix3 -> Ix3 -> Ix3
(+) = (Int -> Int -> Int) -> Ix3 -> Ix3 -> Ix3
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 Int -> Int -> Int
forall a. Num a => a -> a -> a
(+)
{-# INLINE [1] (+) #-}
(-) = (Int -> Int -> Int) -> Ix3 -> Ix3 -> Ix3
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 (-)
{-# INLINE [1] (-) #-}
* :: Ix3 -> Ix3 -> Ix3
(*) = (Int -> Int -> Int) -> Ix3 -> Ix3 -> Ix3
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 Int -> Int -> Int
forall a. Num a => a -> a -> a
(*)
{-# INLINE [1] (*) #-}
negate :: Ix3 -> Ix3
negate = (Int -> Int) -> Ix3 -> Ix3
forall ix. Index ix => (Int -> Int) -> ix -> ix
liftIndex Int -> Int
forall a. Num a => a -> a
negate
{-# INLINE [1] negate #-}
abs :: Ix3 -> Ix3
abs = (Int -> Int) -> Ix3 -> Ix3
forall ix. Index ix => (Int -> Int) -> ix -> ix
liftIndex Int -> Int
forall a. Num a => a -> a
abs
{-# INLINE [1] abs #-}
signum :: Ix3 -> Ix3
signum = (Int -> Int) -> Ix3 -> Ix3
forall ix. Index ix => (Int -> Int) -> ix -> ix
liftIndex Int -> Int
forall a. Num a => a -> a
signum
{-# INLINE [1] signum #-}
fromInteger :: Integer -> Ix3
fromInteger = Int -> Ix3
forall ix. Index ix => Int -> ix
pureIndex (Int -> Ix3) -> (Integer -> Int) -> Integer -> Ix3
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a. Num a => Integer -> a
fromInteger
{-# INLINE [1] fromInteger #-}
instance {-# OVERLAPPABLE #-} HighIxN n => Num (IxN n) where
+ :: IxN n -> IxN n -> IxN n
(+) = (Int -> Int -> Int) -> IxN n -> IxN n -> IxN n
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 Int -> Int -> Int
forall a. Num a => a -> a -> a
(+)
{-# INLINE [1] (+) #-}
(-) = (Int -> Int -> Int) -> IxN n -> IxN n -> IxN n
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 (-)
{-# INLINE [1] (-) #-}
* :: IxN n -> IxN n -> IxN n
(*) = (Int -> Int -> Int) -> IxN n -> IxN n -> IxN n
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 Int -> Int -> Int
forall a. Num a => a -> a -> a
(*)
{-# INLINE [1] (*) #-}
negate :: IxN n -> IxN n
negate = (Int -> Int) -> IxN n -> IxN n
forall ix. Index ix => (Int -> Int) -> ix -> ix
liftIndex Int -> Int
forall a. Num a => a -> a
negate
{-# INLINE [1] negate #-}
abs :: IxN n -> IxN n
abs = (Int -> Int) -> IxN n -> IxN n
forall ix. Index ix => (Int -> Int) -> ix -> ix
liftIndex Int -> Int
forall a. Num a => a -> a
abs
{-# INLINE [1] abs #-}
signum :: IxN n -> IxN n
signum = (Int -> Int) -> IxN n -> IxN n
forall ix. Index ix => (Int -> Int) -> ix -> ix
liftIndex Int -> Int
forall a. Num a => a -> a
signum
{-# INLINE [1] signum #-}
fromInteger :: Integer -> IxN n
fromInteger = Int -> IxN n
forall ix. Index ix => Int -> ix
pureIndex (Int -> IxN n) -> (Integer -> Int) -> Integer -> IxN n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a. Num a => Integer -> a
fromInteger
{-# INLINE [1] fromInteger #-}
instance Bounded Ix2 where
minBound :: Ix2
minBound = Int -> Ix2
forall ix. Index ix => Int -> ix
pureIndex Int
forall a. Bounded a => a
minBound
{-# INLINE minBound #-}
maxBound :: Ix2
maxBound = Int -> Ix2
forall ix. Index ix => Int -> ix
pureIndex Int
forall a. Bounded a => a
maxBound
{-# INLINE maxBound #-}
instance Bounded Ix3 where
minBound :: Ix3
minBound = Int -> Ix3
forall ix. Index ix => Int -> ix
pureIndex Int
forall a. Bounded a => a
minBound
{-# INLINE minBound #-}
maxBound :: Ix3
maxBound = Int -> Ix3
forall ix. Index ix => Int -> ix
pureIndex Int
forall a. Bounded a => a
maxBound
{-# INLINE maxBound #-}
instance {-# OVERLAPPABLE #-} HighIxN n => Bounded (IxN n) where
minBound :: IxN n
minBound = Int -> IxN n
forall ix. Index ix => Int -> ix
pureIndex Int
forall a. Bounded a => a
minBound
{-# INLINE minBound #-}
maxBound :: IxN n
maxBound = Int -> IxN n
forall ix. Index ix => Int -> ix
pureIndex Int
forall a. Bounded a => a
maxBound
{-# INLINE maxBound #-}
instance NFData Ix2 where
rnf :: Ix2 -> ()
rnf Ix2
ix = Ix2
ix Ix2 -> () -> ()
`seq` ()
instance NFData (IxN n) where
rnf :: IxN n -> ()
rnf IxN n
ix = IxN n
ix IxN n -> () -> ()
`seq` ()
instance Eq Ix2 where
(Int
i1 :. Int
j1) == :: Ix2 -> Ix2 -> Bool
== (Int
i2 :. Int
j2) = Int
i1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
i2 Bool -> Bool -> Bool
&& Int
j1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
j2
instance Eq (Ix (n - 1)) => Eq (IxN n) where
(Int
i1 :> Ix (n - 1)
ix1) == :: IxN n -> IxN n -> Bool
== (Int
i2 :> Ix (n - 1)
ix2) = Int
i1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
i2 Bool -> Bool -> Bool
&& Ix (n - 1)
ix1 Ix (n - 1) -> Ix (n - 1) -> Bool
forall a. Eq a => a -> a -> Bool
== Ix (n - 1)
ix2
instance Ord Ix2 where
compare :: Ix2 -> Ix2 -> Ordering
compare (Int
i1 :. Int
j1) (Int
i2 :. Int
j2) = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
i1 Int
i2 Ordering -> Ordering -> Ordering
forall a. Semigroup a => a -> a -> a
<> Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
j1 Int
j2
instance Ord (Ix (n - 1)) => Ord (IxN n) where
compare :: IxN n -> IxN n -> Ordering
compare (Int
i1 :> Ix (n - 1)
ix1) (Int
i2 :> Ix (n - 1)
ix2) = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
i1 Int
i2 Ordering -> Ordering -> Ordering
forall a. Semigroup a => a -> a -> a
<> Ix (n - 1) -> Ix (n - 1) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Ix (n - 1)
ix1 Ix (n - 1)
ix2
instance Index Ix2 where
type Dimensions Ix2 = 2
dimensions :: proxy Ix2 -> Dim
dimensions proxy Ix2
_ = Dim
2
{-# INLINE [1] dimensions #-}
totalElem :: Sz Ix2 -> Int
totalElem (SafeSz (Int
k2 :. Int
k1)) = Int
k2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
k1
{-# INLINE [1] totalElem #-}
isSafeIndex :: Sz Ix2 -> Ix2 -> Bool
isSafeIndex (SafeSz (Int
k2 :. Int
k1)) (Int
i2 :. Int
i1) = Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i2 Bool -> Bool -> Bool
&& Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i1 Bool -> Bool -> Bool
&& Int
i2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
k2 Bool -> Bool -> Bool
&& Int
i1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
k1
{-# INLINE [1] isSafeIndex #-}
toLinearIndex :: Sz Ix2 -> Ix2 -> Int
toLinearIndex (SafeSz (Int
_ :. Int
k1)) (Int
i2 :. Int
i1) = Int
k1 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
i2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i1
{-# INLINE [1] toLinearIndex #-}
fromLinearIndex :: Sz Ix2 -> Int -> Ix2
fromLinearIndex (SafeSz (Int
_ :. Int
k1)) Int
i = case Int
i Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
k1 of
(Int
i2, Int
i1) -> Int
i2 Int -> Int -> Ix2
:. Int
i1
{-# INLINE [1] fromLinearIndex #-}
consDim :: Int -> Lower Ix2 -> Ix2
consDim = Int -> Int -> Ix2
Int -> Lower Ix2 -> Ix2
(:.)
{-# INLINE [1] consDim #-}
unconsDim :: Ix2 -> (Int, Lower Ix2)
unconsDim (Int
i2 :. Int
i1) = (Int
i2, Int
Lower Ix2
i1)
{-# INLINE [1] unconsDim #-}
snocDim :: Lower Ix2 -> Int -> Ix2
snocDim Lower Ix2
i2 Int
i1 = Int
Lower Ix2
i2 Int -> Int -> Ix2
:. Int
i1
{-# INLINE [1] snocDim #-}
unsnocDim :: Ix2 -> (Lower Ix2, Int)
unsnocDim (Int
i2 :. Int
i1) = (Int
Lower Ix2
i2, Int
i1)
{-# INLINE [1] unsnocDim #-}
getDimM :: Ix2 -> Dim -> m Int
getDimM (Int
i2 :. Int
_) Dim
2 = Int -> m Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
i2
getDimM ( Int
_ :. Int
i1) Dim
1 = Int -> m Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
i1
getDimM Ix2
ix Dim
d = IndexException -> m Int
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m Int) -> IndexException -> m Int
forall a b. (a -> b) -> a -> b
$ Ix2 -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException Ix2
ix Dim
d
{-# INLINE [1] getDimM #-}
setDimM :: Ix2 -> Dim -> Int -> m Ix2
setDimM ( Int
_ :. Int
i1) Dim
2 Int
i2 = Ix2 -> m Ix2
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i2 Int -> Int -> Ix2
:. Int
i1)
setDimM (Int
i2 :. Int
_) Dim
1 Int
i1 = Ix2 -> m Ix2
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i2 Int -> Int -> Ix2
:. Int
i1)
setDimM Ix2
ix Dim
d Int
_ = IndexException -> m Ix2
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m Ix2) -> IndexException -> m Ix2
forall a b. (a -> b) -> a -> b
$ Ix2 -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException Ix2
ix Dim
d
{-# INLINE [1] setDimM #-}
pullOutDimM :: Ix2 -> Dim -> m (Int, Lower Ix2)
pullOutDimM (Int
i2 :. Int
i1) Dim
2 = (Int, Int) -> m (Int, Int)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i2, Int
i1)
pullOutDimM (Int
i2 :. Int
i1) Dim
1 = (Int, Int) -> m (Int, Int)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i1, Int
i2)
pullOutDimM Ix2
ix Dim
d = IndexException -> m (Int, Int)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m (Int, Int)) -> IndexException -> m (Int, Int)
forall a b. (a -> b) -> a -> b
$ Ix2 -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException Ix2
ix Dim
d
{-# INLINE [1] pullOutDimM #-}
insertDimM :: Lower Ix2 -> Dim -> Int -> m Ix2
insertDimM Lower Ix2
i1 Dim
2 Int
i2 = Ix2 -> m Ix2
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i2 Int -> Int -> Ix2
:. Int
Lower Ix2
i1)
insertDimM Lower Ix2
i2 Dim
1 Int
i1 = Ix2 -> m Ix2
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
Lower Ix2
i2 Int -> Int -> Ix2
:. Int
i1)
insertDimM Lower Ix2
ix Dim
d Int
_ = IndexException -> m Ix2
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m Ix2) -> IndexException -> m Ix2
forall a b. (a -> b) -> a -> b
$ Int -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException Int
Lower Ix2
ix Dim
d
{-# INLINE [1] insertDimM #-}
pureIndex :: Int -> Ix2
pureIndex Int
i = Int
i Int -> Int -> Ix2
:. Int
i
{-# INLINE [1] pureIndex #-}
liftIndex :: (Int -> Int) -> Ix2 -> Ix2
liftIndex Int -> Int
f (Int
i2 :. Int
i1) = Int -> Int
f Int
i2 Int -> Int -> Ix2
:. Int -> Int
f Int
i1
{-# INLINE [1] liftIndex #-}
liftIndex2 :: (Int -> Int -> Int) -> Ix2 -> Ix2 -> Ix2
liftIndex2 Int -> Int -> Int
f (Int
i2 :. Int
i1) (Int
i2' :. Int
i1') = Int -> Int -> Int
f Int
i2 Int
i2' Int -> Int -> Ix2
:. Int -> Int -> Int
f Int
i1 Int
i1'
{-# INLINE [1] liftIndex2 #-}
repairIndex :: Sz Ix2
-> Ix2 -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Ix2
repairIndex (SafeSz (Int
k :. Int
szL)) (Int
i :. Int
ixL) Sz Int -> Int -> Int
rBelow Sz Int -> Int -> Int
rOver =
Sz Int
-> Int -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Int
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
repairIndex (Int -> Sz Int
forall ix. ix -> Sz ix
SafeSz Int
k) Int
i Sz Int -> Int -> Int
rBelow Sz Int -> Int -> Int
rOver Int -> Int -> Ix2
:. Sz Int
-> Int -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Int
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
repairIndex (Int -> Sz Int
forall ix. ix -> Sz ix
SafeSz Int
szL) Int
ixL Sz Int -> Int -> Int
rBelow Sz Int -> Int -> Int
rOver
{-# INLINE [1] repairIndex #-}
instance {-# OVERLAPPING #-} Index (IxN 3) where
type Dimensions Ix3 = 3
dimensions :: proxy Ix3 -> Dim
dimensions proxy Ix3
_ = Dim
3
{-# INLINE [1] dimensions #-}
totalElem :: Sz Ix3 -> Int
totalElem (SafeSz (Int
k3 :> k2 :. k1)) = Int
k3 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
k2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
k1
{-# INLINE [1] totalElem #-}
isSafeIndex :: Sz Ix3 -> Ix3 -> Bool
isSafeIndex (SafeSz (Int
k3 :> k2 :. k1)) (Int
i3 :> i2 :. i1) =
Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i3 Bool -> Bool -> Bool
&& Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i2 Bool -> Bool -> Bool
&& Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i1 Bool -> Bool -> Bool
&& Int
i3 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
k3 Bool -> Bool -> Bool
&& Int
i2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
k2 Bool -> Bool -> Bool
&& Int
i1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
k1
{-# INLINE [1] isSafeIndex #-}
toLinearIndex :: Sz Ix3 -> Ix3 -> Int
toLinearIndex (SafeSz (Int
_ :> k2 :. k1)) (Int
i3 :> i2 :. i1) = (Int
k2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
i3 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i2) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
k1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i1
{-# INLINE [1] toLinearIndex #-}
fromLinearIndex :: Sz Ix3 -> Int -> Ix3
fromLinearIndex (SafeSz (Int
_ :> Ix (3 - 1)
ix)) Int
i = let !(Int
q, Ix2
ixL) = Ix2 -> Int -> (Int, Ix2)
forall ix. Index ix => ix -> Int -> (Int, ix)
fromLinearIndexAcc Ix (3 - 1)
Ix2
ix Int
i in Int
q Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Ix (3 - 1)
Ix2
ixL
{-# INLINE [1] fromLinearIndex #-}
consDim :: Int -> Lower Ix3 -> Ix3
consDim = Int -> Lower Ix3 -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
(:>)
{-# INLINE [1] consDim #-}
unconsDim :: Ix3 -> (Int, Lower Ix3)
unconsDim (Int
i3 :> Ix (3 - 1)
ix) = (Int
i3, Lower Ix3
Ix (3 - 1)
ix)
{-# INLINE [1] unconsDim #-}
snocDim :: Lower Ix3 -> Int -> Ix3
snocDim (i3 :. i2) Int
i1 = Int
i3 Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Int
i2 Int -> Int -> Ix2
:. Int
i1
{-# INLINE [1] snocDim #-}
unsnocDim :: Ix3 -> (Lower Ix3, Int)
unsnocDim (Int
i3 :> i2 :. i1) = (Int
i3 Int -> Int -> Ix2
:. Int
i2, Int
i1)
{-# INLINE [1] unsnocDim #-}
getDimM :: Ix3 -> Dim -> m Int
getDimM (Int
i3 :> _ :. _) Dim
3 = Int -> m Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
i3
getDimM ( Int
_ :> i2 :. _) Dim
2 = Int -> m Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
i2
getDimM ( Int
_ :> _ :. i1) Dim
1 = Int -> m Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
i1
getDimM Ix3
ix Dim
d = IndexException -> m Int
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m Int) -> IndexException -> m Int
forall a b. (a -> b) -> a -> b
$ Ix3 -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException Ix3
ix Dim
d
{-# INLINE [1] getDimM #-}
setDimM :: Ix3 -> Dim -> Int -> m Ix3
setDimM ( Int
_ :> i2 :. i1) Dim
3 Int
i3 = Ix3 -> m Ix3
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i3 Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Int
i2 Int -> Int -> Ix2
:. Int
i1)
setDimM (Int
i3 :> _ :. i1) Dim
2 Int
i2 = Ix3 -> m Ix3
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i3 Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Int
i2 Int -> Int -> Ix2
:. Int
i1)
setDimM (Int
i3 :> i2 :. _) Dim
1 Int
i1 = Ix3 -> m Ix3
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i3 Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Int
i2 Int -> Int -> Ix2
:. Int
i1)
setDimM Ix3
ix Dim
d Int
_ = IndexException -> m Ix3
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m Ix3) -> IndexException -> m Ix3
forall a b. (a -> b) -> a -> b
$ Ix3 -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException Ix3
ix Dim
d
{-# INLINE [1] setDimM #-}
pullOutDimM :: Ix3 -> Dim -> m (Int, Lower Ix3)
pullOutDimM (Int
i3 :> i2 :. i1) Dim
3 = (Int, Ix2) -> m (Int, Ix2)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i3, Int
i2 Int -> Int -> Ix2
:. Int
i1)
pullOutDimM (Int
i3 :> i2 :. i1) Dim
2 = (Int, Ix2) -> m (Int, Ix2)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i2, Int
i3 Int -> Int -> Ix2
:. Int
i1)
pullOutDimM (Int
i3 :> i2 :. i1) Dim
1 = (Int, Ix2) -> m (Int, Ix2)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i1, Int
i3 Int -> Int -> Ix2
:. Int
i2)
pullOutDimM Ix3
ix Dim
d = IndexException -> m (Int, Ix2)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m (Int, Ix2)) -> IndexException -> m (Int, Ix2)
forall a b. (a -> b) -> a -> b
$ Ix3 -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException Ix3
ix Dim
d
{-# INLINE [1] pullOutDimM #-}
insertDimM :: Lower Ix3 -> Dim -> Int -> m Ix3
insertDimM (i2 :. i1) Dim
3 Int
i3 = Ix3 -> m Ix3
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i3 Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Int
i2 Int -> Int -> Ix2
:. Int
i1)
insertDimM (i3 :. i1) Dim
2 Int
i2 = Ix3 -> m Ix3
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i3 Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Int
i2 Int -> Int -> Ix2
:. Int
i1)
insertDimM (i3 :. i2) Dim
1 Int
i1 = Ix3 -> m Ix3
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i3 Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Int
i2 Int -> Int -> Ix2
:. Int
i1)
insertDimM Lower Ix3
ix Dim
d Int
_ = IndexException -> m Ix3
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m Ix3) -> IndexException -> m Ix3
forall a b. (a -> b) -> a -> b
$ Ix2 -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException Lower Ix3
Ix2
ix Dim
d
{-# INLINE [1] insertDimM #-}
pureIndex :: Int -> Ix3
pureIndex Int
i = Int
i Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Int
i Int -> Int -> Ix2
:. Int
i
{-# INLINE [1] pureIndex #-}
liftIndex :: (Int -> Int) -> Ix3 -> Ix3
liftIndex Int -> Int
f (Int
i3 :> i2 :. i1) = Int -> Int
f Int
i3 Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Int -> Int
f Int
i2 Int -> Int -> Ix2
:. Int -> Int
f Int
i1
{-# INLINE [1] liftIndex #-}
liftIndex2 :: (Int -> Int -> Int) -> Ix3 -> Ix3 -> Ix3
liftIndex2 Int -> Int -> Int
f (Int
i3 :> i2 :. i1) (Int
i3' :> i2' :. i1') = Int -> Int -> Int
f Int
i3 Int
i3' Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Int -> Int -> Int
f Int
i2 Int
i2' Int -> Int -> Ix2
:. Int -> Int -> Int
f Int
i1 Int
i1'
{-# INLINE [1] liftIndex2 #-}
repairIndex :: Sz Ix3
-> Ix3 -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Ix3
repairIndex (SafeSz (Int
n :> Ix (3 - 1)
szL)) (Int
i :> Ix (3 - 1)
ixL) Sz Int -> Int -> Int
rBelow Sz Int -> Int -> Int
rOver =
Sz Int
-> Int -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Int
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
repairIndex (Int -> Sz Int
forall ix. ix -> Sz ix
SafeSz Int
n) Int
i Sz Int -> Int -> Int
rBelow Sz Int -> Int -> Int
rOver Int -> Ix (3 - 1) -> Ix3
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Sz Ix2
-> Ix2 -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Ix2
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
repairIndex (Ix2 -> Sz Ix2
forall ix. ix -> Sz ix
SafeSz Ix (3 - 1)
Ix2
szL) Ix (3 - 1)
Ix2
ixL Sz Int -> Int -> Int
rBelow Sz Int -> Int -> Int
rOver
{-# INLINE [1] repairIndex #-}
type HighIxN n
= (4 <= n, KnownNat n, KnownNat (n - 1), Index (IxN (n - 1)), IxN (n - 1) ~ Ix (n - 1))
instance {-# OVERLAPPABLE #-} HighIxN n => Index (IxN n) where
type Dimensions (IxN n) = n
dimensions :: proxy (IxN n) -> Dim
dimensions proxy (IxN n)
_ = Integer -> Dim
forall a. Num a => Integer -> a
fromInteger (Integer -> Dim) -> Integer -> Dim
forall a b. (a -> b) -> a -> b
$ Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
{-# INLINE [1] dimensions #-}
totalElem :: Sz (IxN n) -> Int
totalElem (SafeSz (Int
i :> Ix (n - 1)
ixl)) = (Int -> Int -> Int) -> Int -> IxN (n - 1) -> Int
forall ix a. Index ix => (a -> Int -> a) -> a -> ix -> a
foldlIndex Int -> Int -> Int
forall a. Num a => a -> a -> a
(*) Int
i Ix (n - 1)
IxN (n - 1)
ixl
{-# INLINE [1] totalElem #-}
consDim :: Int -> Lower (IxN n) -> IxN n
consDim = Int -> Lower (IxN n) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
(:>)
{-# INLINE [1] consDim #-}
unconsDim :: IxN n -> (Int, Lower (IxN n))
unconsDim (Int
i :> Ix (n - 1)
ixl) = (Int
i, Lower (IxN n)
Ix (n - 1)
ixl)
{-# INLINE [1] unconsDim #-}
snocDim :: Lower (IxN n) -> Int -> IxN n
snocDim (i :> ixl) Int
i1 = Int
i Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Lower (IxN (n - 1)) -> Int -> IxN (n - 1)
forall ix. Index ix => Lower ix -> Int -> ix
snocDim Lower (IxN (n - 1))
Ix ((n - 1) - 1)
ixl Int
i1
{-# INLINE [1] snocDim #-}
unsnocDim :: IxN n -> (Lower (IxN n), Int)
unsnocDim (Int
i :> Ix (n - 1)
ixl) =
case IxN (n - 1) -> (Lower (IxN (n - 1)), Int)
forall ix. Index ix => ix -> (Lower ix, Int)
unsnocDim Ix (n - 1)
IxN (n - 1)
ixl of
(Lower (IxN (n - 1))
ix, Int
i1) -> (Int
i Int -> Ix ((n - 1) - 1) -> IxN (n - 1)
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Lower (IxN (n - 1))
Ix ((n - 1) - 1)
ix, Int
i1)
{-# INLINE [1] unsnocDim #-}
getDimM :: IxN n -> Dim -> m Int
getDimM ix :: IxN n
ix@(Int
i :> Ix (n - 1)
ixl) Dim
d
| Dim
d Dim -> Dim -> Bool
forall a. Eq a => a -> a -> Bool
== Proxy (IxN n) -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
dimensions (Proxy (IxN n)
forall k (t :: k). Proxy t
Proxy :: Proxy (IxN n)) = Int -> m Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
i
| Bool
otherwise = m Int -> (Int -> m Int) -> Maybe Int -> m Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (IndexException -> m Int
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m Int) -> IndexException -> m Int
forall a b. (a -> b) -> a -> b
$ IxN n -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException IxN n
ix Dim
d) Int -> m Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IxN (n - 1) -> Dim -> Maybe Int
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m Int
getDimM Ix (n - 1)
IxN (n - 1)
ixl Dim
d)
{-# INLINE [1] getDimM #-}
setDimM :: IxN n -> Dim -> Int -> m (IxN n)
setDimM ix :: IxN n
ix@(Int
i :> Ix (n - 1)
ixl) Dim
d Int
di
| Dim
d Dim -> Dim -> Bool
forall a. Eq a => a -> a -> Bool
== Proxy (IxN n) -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
dimensions (Proxy (IxN n)
forall k (t :: k). Proxy t
Proxy :: Proxy (IxN n)) = IxN n -> m (IxN n)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
di Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Ix (n - 1)
ixl)
| Bool
otherwise = m (IxN n)
-> (IxN (n - 1) -> m (IxN n)) -> Maybe (IxN (n - 1)) -> m (IxN n)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (IndexException -> m (IxN n)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m (IxN n)) -> IndexException -> m (IxN n)
forall a b. (a -> b) -> a -> b
$ IxN n -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException IxN n
ix Dim
d) (IxN n -> m (IxN n)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IxN n -> m (IxN n))
-> (IxN (n - 1) -> IxN n) -> IxN (n - 1) -> m (IxN n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
i Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:>)) (IxN (n - 1) -> Dim -> Int -> Maybe (IxN (n - 1))
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> Int -> m ix
setDimM Ix (n - 1)
IxN (n - 1)
ixl Dim
d Int
di)
{-# INLINE [1] setDimM #-}
pullOutDimM :: IxN n -> Dim -> m (Int, Lower (IxN n))
pullOutDimM ix :: IxN n
ix@(Int
i :> Ix (n - 1)
ixl) Dim
d
| Dim
d Dim -> Dim -> Bool
forall a. Eq a => a -> a -> Bool
== Proxy (IxN n) -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
dimensions (Proxy (IxN n)
forall k (t :: k). Proxy t
Proxy :: Proxy (IxN n)) = (Int, IxN (n - 1)) -> m (Int, IxN (n - 1))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
i, Ix (n - 1)
IxN (n - 1)
ixl)
| Bool
otherwise =
m (Int, IxN (n - 1))
-> ((Int, Ix ((n - 1) - 1)) -> m (Int, IxN (n - 1)))
-> Maybe (Int, Ix ((n - 1) - 1))
-> m (Int, IxN (n - 1))
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (IndexException -> m (Int, IxN (n - 1))
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m (Int, IxN (n - 1)))
-> IndexException -> m (Int, IxN (n - 1))
forall a b. (a -> b) -> a -> b
$ IxN n -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException IxN n
ix Dim
d) ((Int, IxN (n - 1)) -> m (Int, IxN (n - 1))
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Int, IxN (n - 1)) -> m (Int, IxN (n - 1)))
-> ((Int, Ix ((n - 1) - 1)) -> (Int, IxN (n - 1)))
-> (Int, Ix ((n - 1) - 1))
-> m (Int, IxN (n - 1))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ix ((n - 1) - 1) -> IxN (n - 1))
-> (Int, Ix ((n - 1) - 1)) -> (Int, IxN (n - 1))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int
i Int -> Ix ((n - 1) - 1) -> IxN (n - 1)
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:>)) (IxN (n - 1) -> Dim -> Maybe (Int, Lower (IxN (n - 1)))
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m (Int, Lower ix)
pullOutDimM Ix (n - 1)
IxN (n - 1)
ixl Dim
d)
{-# INLINE [1] pullOutDimM #-}
insertDimM :: Lower (IxN n) -> Dim -> Int -> m (IxN n)
insertDimM ix :: Lower (IxN n)
ix@(i :> ixl) Dim
d Int
di
| Dim
d Dim -> Dim -> Bool
forall a. Eq a => a -> a -> Bool
== Proxy (IxN n) -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
dimensions (Proxy (IxN n)
forall k (t :: k). Proxy t
Proxy :: Proxy (IxN n)) = IxN n -> m (IxN n)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
di Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Lower (IxN n)
Ix (n - 1)
ix)
| Bool
otherwise =
m (IxN n)
-> (IxN (n - 1) -> m (IxN n)) -> Maybe (IxN (n - 1)) -> m (IxN n)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (IndexException -> m (IxN n)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (IndexException -> m (IxN n)) -> IndexException -> m (IxN n)
forall a b. (a -> b) -> a -> b
$ IxN (n - 1) -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException Lower (IxN n)
IxN (n - 1)
ix Dim
d) (IxN n -> m (IxN n)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IxN n -> m (IxN n))
-> (IxN (n - 1) -> IxN n) -> IxN (n - 1) -> m (IxN n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
i Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:>)) (Lower (IxN (n - 1)) -> Dim -> Int -> Maybe (IxN (n - 1))
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
Lower ix -> Dim -> Int -> m ix
insertDimM Lower (IxN (n - 1))
Ix ((n - 1) - 1)
ixl Dim
d Int
di)
{-# INLINE [1] insertDimM #-}
pureIndex :: Int -> IxN n
pureIndex Int
i = Int
i Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> (Int -> IxN (n - 1)
forall ix. Index ix => Int -> ix
pureIndex Int
i :: Ix (n - 1))
{-# INLINE [1] pureIndex #-}
liftIndex :: (Int -> Int) -> IxN n -> IxN n
liftIndex Int -> Int
f (Int
i :> Ix (n - 1)
ix) = Int -> Int
f Int
i Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> (Int -> Int) -> IxN (n - 1) -> IxN (n - 1)
forall ix. Index ix => (Int -> Int) -> ix -> ix
liftIndex Int -> Int
f Ix (n - 1)
IxN (n - 1)
ix
{-# INLINE [1] liftIndex #-}
liftIndex2 :: (Int -> Int -> Int) -> IxN n -> IxN n -> IxN n
liftIndex2 Int -> Int -> Int
f (Int
i :> Ix (n - 1)
ix) (Int
i' :> Ix (n - 1)
ix') = Int -> Int -> Int
f Int
i Int
i' Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> (Int -> Int -> Int) -> IxN (n - 1) -> IxN (n - 1) -> IxN (n - 1)
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 Int -> Int -> Int
f Ix (n - 1)
IxN (n - 1)
ix Ix (n - 1)
IxN (n - 1)
ix'
{-# INLINE [1] liftIndex2 #-}
repairIndex :: Sz (IxN n)
-> IxN n
-> (Sz Int -> Int -> Int)
-> (Sz Int -> Int -> Int)
-> IxN n
repairIndex (SafeSz (Int
n :> Ix (n - 1)
szL)) (Int
i :> Ix (n - 1)
ixL) Sz Int -> Int -> Int
rBelow Sz Int -> Int -> Int
rOver =
Sz Int
-> Int -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Int
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
repairIndex (Int -> Sz Int
forall ix. ix -> Sz ix
SafeSz Int
n) Int
i Sz Int -> Int -> Int
rBelow Sz Int -> Int -> Int
rOver Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Sz (IxN (n - 1))
-> IxN (n - 1)
-> (Sz Int -> Int -> Int)
-> (Sz Int -> Int -> Int)
-> IxN (n - 1)
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
repairIndex (IxN (n - 1) -> Sz (IxN (n - 1))
forall ix. ix -> Sz ix
SafeSz Ix (n - 1)
IxN (n - 1)
szL) Ix (n - 1)
IxN (n - 1)
ixL Sz Int -> Int -> Int
rBelow Sz Int -> Int -> Int
rOver
{-# INLINE [1] repairIndex #-}
instance VU.Unbox Ix2
newtype instance VU.MVector s Ix2 = MV_Ix2 (VU.MVector s (Int, Int))
instance VM.MVector VU.MVector Ix2 where
basicLength :: MVector s Ix2 -> Int
basicLength (MV_Ix2 mvec) = MVector s (Int, Int) -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
VM.basicLength MVector s (Int, Int)
mvec
{-# INLINE basicLength #-}
basicUnsafeSlice :: Int -> Int -> MVector s Ix2 -> MVector s Ix2
basicUnsafeSlice Int
idx Int
len (MV_Ix2 mvec) = MVector s (Int, Int) -> MVector s Ix2
forall s. MVector s (Int, Int) -> MVector s Ix2
MV_Ix2 (Int -> Int -> MVector s (Int, Int) -> MVector s (Int, Int)
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
VM.basicUnsafeSlice Int
idx Int
len MVector s (Int, Int)
mvec)
{-# INLINE basicUnsafeSlice #-}
basicOverlaps :: MVector s Ix2 -> MVector s Ix2 -> Bool
basicOverlaps (MV_Ix2 mvec) (MV_Ix2 mvec') = MVector s (Int, Int) -> MVector s (Int, Int) -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
VM.basicOverlaps MVector s (Int, Int)
mvec MVector s (Int, Int)
mvec'
{-# INLINE basicOverlaps #-}
basicUnsafeNew :: Int -> m (MVector (PrimState m) Ix2)
basicUnsafeNew Int
len = MVector (PrimState m) (Int, Int) -> MVector (PrimState m) Ix2
forall s. MVector s (Int, Int) -> MVector s Ix2
MV_Ix2 (MVector (PrimState m) (Int, Int) -> MVector (PrimState m) Ix2)
-> m (MVector (PrimState m) (Int, Int))
-> m (MVector (PrimState m) Ix2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> m (MVector (PrimState m) (Int, Int))
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
VM.basicUnsafeNew Int
len
{-# INLINE basicUnsafeNew #-}
basicUnsafeReplicate :: Int -> Ix2 -> m (MVector (PrimState m) Ix2)
basicUnsafeReplicate Int
len (Int
i :. Int
j) = MVector (PrimState m) (Int, Int) -> MVector (PrimState m) Ix2
forall s. MVector s (Int, Int) -> MVector s Ix2
MV_Ix2 (MVector (PrimState m) (Int, Int) -> MVector (PrimState m) Ix2)
-> m (MVector (PrimState m) (Int, Int))
-> m (MVector (PrimState m) Ix2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> (Int, Int) -> m (MVector (PrimState m) (Int, Int))
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> a -> m (v (PrimState m) a)
VM.basicUnsafeReplicate Int
len (Int
i, Int
j)
{-# INLINE basicUnsafeReplicate #-}
basicUnsafeRead :: MVector (PrimState m) Ix2 -> Int -> m Ix2
basicUnsafeRead (MV_Ix2 mvec) Int
idx = (Int -> Int -> Ix2) -> (Int, Int) -> Ix2
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> Ix2
(:.) ((Int, Int) -> Ix2) -> m (Int, Int) -> m Ix2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState m) (Int, Int) -> Int -> m (Int, Int)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
VM.basicUnsafeRead MVector (PrimState m) (Int, Int)
mvec Int
idx
{-# INLINE basicUnsafeRead #-}
basicUnsafeWrite :: MVector (PrimState m) Ix2 -> Int -> Ix2 -> m ()
basicUnsafeWrite (MV_Ix2 mvec) Int
idx (Int
i :. Int
j) = MVector (PrimState m) (Int, Int) -> Int -> (Int, Int) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
VM.basicUnsafeWrite MVector (PrimState m) (Int, Int)
mvec Int
idx (Int
i, Int
j)
{-# INLINE basicUnsafeWrite #-}
basicClear :: MVector (PrimState m) Ix2 -> m ()
basicClear (MV_Ix2 mvec) = MVector (PrimState m) (Int, Int) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
VM.basicClear MVector (PrimState m) (Int, Int)
mvec
{-# INLINE basicClear #-}
basicSet :: MVector (PrimState m) Ix2 -> Ix2 -> m ()
basicSet (MV_Ix2 mvec) (Int
i :. Int
j) = MVector (PrimState m) (Int, Int) -> (Int, Int) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> a -> m ()
VM.basicSet MVector (PrimState m) (Int, Int)
mvec (Int
i, Int
j)
{-# INLINE basicSet #-}
basicUnsafeCopy :: MVector (PrimState m) Ix2 -> MVector (PrimState m) Ix2 -> m ()
basicUnsafeCopy (MV_Ix2 mvec) (MV_Ix2 mvec') = MVector (PrimState m) (Int, Int)
-> MVector (PrimState m) (Int, Int) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
VM.basicUnsafeCopy MVector (PrimState m) (Int, Int)
mvec MVector (PrimState m) (Int, Int)
mvec'
{-# INLINE basicUnsafeCopy #-}
basicUnsafeMove :: MVector (PrimState m) Ix2 -> MVector (PrimState m) Ix2 -> m ()
basicUnsafeMove (MV_Ix2 mvec) (MV_Ix2 mvec') = MVector (PrimState m) (Int, Int)
-> MVector (PrimState m) (Int, Int) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
VM.basicUnsafeMove MVector (PrimState m) (Int, Int)
mvec MVector (PrimState m) (Int, Int)
mvec'
{-# INLINE basicUnsafeMove #-}
basicUnsafeGrow :: MVector (PrimState m) Ix2 -> Int -> m (MVector (PrimState m) Ix2)
basicUnsafeGrow (MV_Ix2 mvec) Int
len = MVector (PrimState m) (Int, Int) -> MVector (PrimState m) Ix2
forall s. MVector s (Int, Int) -> MVector s Ix2
MV_Ix2 (MVector (PrimState m) (Int, Int) -> MVector (PrimState m) Ix2)
-> m (MVector (PrimState m) (Int, Int))
-> m (MVector (PrimState m) Ix2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState m) (Int, Int)
-> Int -> m (MVector (PrimState m) (Int, Int))
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m (v (PrimState m) a)
VM.basicUnsafeGrow MVector (PrimState m) (Int, Int)
mvec Int
len
{-# INLINE basicUnsafeGrow #-}
#if MIN_VERSION_vector(0,11,0)
basicInitialize :: MVector (PrimState m) Ix2 -> m ()
basicInitialize (MV_Ix2 mvec) = MVector (PrimState m) (Int, Int) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
VM.basicInitialize MVector (PrimState m) (Int, Int)
mvec
{-# INLINE basicInitialize #-}
#endif
newtype instance VU.Vector Ix2 = V_Ix2 (VU.Vector (Int, Int))
instance V.Vector VU.Vector Ix2 where
basicUnsafeFreeze :: Mutable Vector (PrimState m) Ix2 -> m (Vector Ix2)
basicUnsafeFreeze (MV_Ix2 mvec) = Vector (Int, Int) -> Vector Ix2
V_Ix2 (Vector (Int, Int) -> Vector Ix2)
-> m (Vector (Int, Int)) -> m (Vector Ix2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector (PrimState m) (Int, Int) -> m (Vector (Int, Int))
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
V.basicUnsafeFreeze MVector (PrimState m) (Int, Int)
Mutable Vector (PrimState m) (Int, Int)
mvec
{-# INLINE basicUnsafeFreeze #-}
basicUnsafeThaw :: Vector Ix2 -> m (Mutable Vector (PrimState m) Ix2)
basicUnsafeThaw (V_Ix2 vec) = MVector (PrimState m) (Int, Int) -> MVector (PrimState m) Ix2
forall s. MVector s (Int, Int) -> MVector s Ix2
MV_Ix2 (MVector (PrimState m) (Int, Int) -> MVector (PrimState m) Ix2)
-> m (MVector (PrimState m) (Int, Int))
-> m (MVector (PrimState m) Ix2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector (Int, Int) -> m (Mutable Vector (PrimState m) (Int, Int))
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
V.basicUnsafeThaw Vector (Int, Int)
vec
{-# INLINE basicUnsafeThaw #-}
basicLength :: Vector Ix2 -> Int
basicLength (V_Ix2 vec) = Vector (Int, Int) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
V.basicLength Vector (Int, Int)
vec
{-# INLINE basicLength #-}
basicUnsafeSlice :: Int -> Int -> Vector Ix2 -> Vector Ix2
basicUnsafeSlice Int
idx Int
len (V_Ix2 vec) = Vector (Int, Int) -> Vector Ix2
V_Ix2 (Int -> Int -> Vector (Int, Int) -> Vector (Int, Int)
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
V.basicUnsafeSlice Int
idx Int
len Vector (Int, Int)
vec)
{-# INLINE basicUnsafeSlice #-}
basicUnsafeIndexM :: Vector Ix2 -> Int -> m Ix2
basicUnsafeIndexM (V_Ix2 vec) Int
idx = (Int -> Int -> Ix2) -> (Int, Int) -> Ix2
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> Ix2
(:.) ((Int, Int) -> Ix2) -> m (Int, Int) -> m Ix2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector (Int, Int) -> Int -> m (Int, Int)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
V.basicUnsafeIndexM Vector (Int, Int)
vec Int
idx
{-# INLINE basicUnsafeIndexM #-}
basicUnsafeCopy :: Mutable Vector (PrimState m) Ix2 -> Vector Ix2 -> m ()
basicUnsafeCopy (MV_Ix2 mvec) (V_Ix2 vec) = Mutable Vector (PrimState m) (Int, Int)
-> Vector (Int, Int) -> m ()
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> v a -> m ()
V.basicUnsafeCopy MVector (PrimState m) (Int, Int)
Mutable Vector (PrimState m) (Int, Int)
mvec Vector (Int, Int)
vec
{-# INLINE basicUnsafeCopy #-}
elemseq :: Vector Ix2 -> Ix2 -> b -> b
elemseq Vector Ix2
_ = Ix2 -> b -> b
seq
{-# INLINE elemseq #-}
instance (3 <= n, VU.Unbox (Ix (n - 1))) => VU.Unbox (IxN n)
newtype instance VU.MVector s (IxN n) = MV_IxN (VU.MVector s Int, VU.MVector s (Ix (n-1)))
instance (3 <= n, VU.Unbox (Ix (n - 1))) => VM.MVector VU.MVector (IxN n) where
basicLength :: MVector s (IxN n) -> Int
basicLength (MV_IxN (_, mvec)) = MVector s (Ix (n - 1)) -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
VM.basicLength MVector s (Ix (n - 1))
mvec
{-# INLINE basicLength #-}
basicUnsafeSlice :: Int -> Int -> MVector s (IxN n) -> MVector s (IxN n)
basicUnsafeSlice Int
idx Int
len (MV_IxN (mvec1, mvec)) =
(MVector s Int, MVector s (Ix (n - 1))) -> MVector s (IxN n)
forall s (n :: Nat).
(MVector s Int, MVector s (Ix (n - 1))) -> MVector s (IxN n)
MV_IxN (Int -> Int -> MVector s Int -> MVector s Int
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
VM.basicUnsafeSlice Int
idx Int
len MVector s Int
mvec1, Int -> Int -> MVector s (Ix (n - 1)) -> MVector s (Ix (n - 1))
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
VM.basicUnsafeSlice Int
idx Int
len MVector s (Ix (n - 1))
mvec)
{-# INLINE basicUnsafeSlice #-}
basicOverlaps :: MVector s (IxN n) -> MVector s (IxN n) -> Bool
basicOverlaps (MV_IxN (mvec1, mvec)) (MV_IxN (mvec1', mvec')) =
MVector s Int -> MVector s Int -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
VM.basicOverlaps MVector s Int
mvec1 MVector s Int
mvec1' Bool -> Bool -> Bool
&& MVector s (Ix (n - 1)) -> MVector s (Ix (n - 1)) -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
VM.basicOverlaps MVector s (Ix (n - 1))
mvec MVector s (Ix (n - 1))
mvec'
{-# INLINE basicOverlaps #-}
basicUnsafeNew :: Int -> m (MVector (PrimState m) (IxN n))
basicUnsafeNew Int
len = do
MVector (PrimState m) Int
iv <- Int -> m (MVector (PrimState m) Int)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
VM.basicUnsafeNew Int
len
MVector (PrimState m) (Ix (n - 1))
ivs <- Int -> m (MVector (PrimState m) (Ix (n - 1)))
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
VM.basicUnsafeNew Int
len
MVector (PrimState m) (IxN n) -> m (MVector (PrimState m) (IxN n))
forall (m :: * -> *) a. Monad m => a -> m a
return (MVector (PrimState m) (IxN n)
-> m (MVector (PrimState m) (IxN n)))
-> MVector (PrimState m) (IxN n)
-> m (MVector (PrimState m) (IxN n))
forall a b. (a -> b) -> a -> b
$ (MVector (PrimState m) Int, MVector (PrimState m) (Ix (n - 1)))
-> MVector (PrimState m) (IxN n)
forall s (n :: Nat).
(MVector s Int, MVector s (Ix (n - 1))) -> MVector s (IxN n)
MV_IxN (MVector (PrimState m) Int
iv, MVector (PrimState m) (Ix (n - 1))
ivs)
{-# INLINE basicUnsafeNew #-}
basicUnsafeReplicate :: Int -> IxN n -> m (MVector (PrimState m) (IxN n))
basicUnsafeReplicate Int
len (Int
i :> Ix (n - 1)
ix) = do
MVector (PrimState m) Int
iv <- Int -> Int -> m (MVector (PrimState m) Int)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> a -> m (v (PrimState m) a)
VM.basicUnsafeReplicate Int
len Int
i
MVector (PrimState m) (Ix (n - 1))
ivs <- Int -> Ix (n - 1) -> m (MVector (PrimState m) (Ix (n - 1)))
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> a -> m (v (PrimState m) a)
VM.basicUnsafeReplicate Int
len Ix (n - 1)
ix
MVector (PrimState m) (IxN n) -> m (MVector (PrimState m) (IxN n))
forall (m :: * -> *) a. Monad m => a -> m a
return (MVector (PrimState m) (IxN n)
-> m (MVector (PrimState m) (IxN n)))
-> MVector (PrimState m) (IxN n)
-> m (MVector (PrimState m) (IxN n))
forall a b. (a -> b) -> a -> b
$ (MVector (PrimState m) Int, MVector (PrimState m) (Ix (n - 1)))
-> MVector (PrimState m) (IxN n)
forall s (n :: Nat).
(MVector s Int, MVector s (Ix (n - 1))) -> MVector s (IxN n)
MV_IxN (MVector (PrimState m) Int
iv, MVector (PrimState m) (Ix (n - 1))
ivs)
{-# INLINE basicUnsafeReplicate #-}
basicUnsafeRead :: MVector (PrimState m) (IxN n) -> Int -> m (IxN n)
basicUnsafeRead (MV_IxN (mvec1, mvec)) Int
idx = do
Int
i <- MVector (PrimState m) Int -> Int -> m Int
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
VM.basicUnsafeRead MVector (PrimState m) Int
mvec1 Int
idx
Ix (n - 1)
ix <- MVector (PrimState m) (Ix (n - 1)) -> Int -> m (Ix (n - 1))
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
VM.basicUnsafeRead MVector (PrimState m) (Ix (n - 1))
mvec Int
idx
IxN n -> m (IxN n)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
i Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Ix (n - 1)
ix)
{-# INLINE basicUnsafeRead #-}
basicUnsafeWrite :: MVector (PrimState m) (IxN n) -> Int -> IxN n -> m ()
basicUnsafeWrite (MV_IxN (mvec1, mvec)) Int
idx (Int
i :> Ix (n - 1)
ix) = do
MVector (PrimState m) Int -> Int -> Int -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
VM.basicUnsafeWrite MVector (PrimState m) Int
mvec1 Int
idx Int
i
MVector (PrimState m) (Ix (n - 1)) -> Int -> Ix (n - 1) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
VM.basicUnsafeWrite MVector (PrimState m) (Ix (n - 1))
mvec Int
idx Ix (n - 1)
ix
{-# INLINE basicUnsafeWrite #-}
basicClear :: MVector (PrimState m) (IxN n) -> m ()
basicClear (MV_IxN (mvec1, mvec)) = MVector (PrimState m) Int -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
VM.basicClear MVector (PrimState m) Int
mvec1 m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MVector (PrimState m) (Ix (n - 1)) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
VM.basicClear MVector (PrimState m) (Ix (n - 1))
mvec
{-# INLINE basicClear #-}
basicSet :: MVector (PrimState m) (IxN n) -> IxN n -> m ()
basicSet (MV_IxN (mvec1, mvec)) (Int
i :> Ix (n - 1)
ix) = MVector (PrimState m) Int -> Int -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> a -> m ()
VM.basicSet MVector (PrimState m) Int
mvec1 Int
i m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MVector (PrimState m) (Ix (n - 1)) -> Ix (n - 1) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> a -> m ()
VM.basicSet MVector (PrimState m) (Ix (n - 1))
mvec Ix (n - 1)
ix
{-# INLINE basicSet #-}
basicUnsafeCopy :: MVector (PrimState m) (IxN n)
-> MVector (PrimState m) (IxN n) -> m ()
basicUnsafeCopy (MV_IxN (mvec1, mvec)) (MV_IxN (mvec1', mvec')) =
MVector (PrimState m) Int -> MVector (PrimState m) Int -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
VM.basicUnsafeCopy MVector (PrimState m) Int
mvec1 MVector (PrimState m) Int
mvec1' m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MVector (PrimState m) (Ix (n - 1))
-> MVector (PrimState m) (Ix (n - 1)) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
VM.basicUnsafeCopy MVector (PrimState m) (Ix (n - 1))
mvec MVector (PrimState m) (Ix (n - 1))
mvec'
{-# INLINE basicUnsafeCopy #-}
basicUnsafeMove :: MVector (PrimState m) (IxN n)
-> MVector (PrimState m) (IxN n) -> m ()
basicUnsafeMove (MV_IxN (mvec1, mvec)) (MV_IxN (mvec1', mvec')) =
MVector (PrimState m) Int -> MVector (PrimState m) Int -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
VM.basicUnsafeMove MVector (PrimState m) Int
mvec1 MVector (PrimState m) Int
mvec1' m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MVector (PrimState m) (Ix (n - 1))
-> MVector (PrimState m) (Ix (n - 1)) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
VM.basicUnsafeMove MVector (PrimState m) (Ix (n - 1))
mvec MVector (PrimState m) (Ix (n - 1))
mvec'
{-# INLINE basicUnsafeMove #-}
basicUnsafeGrow :: MVector (PrimState m) (IxN n)
-> Int -> m (MVector (PrimState m) (IxN n))
basicUnsafeGrow (MV_IxN (mvec1, mvec)) Int
len = do
MVector (PrimState m) Int
iv <- MVector (PrimState m) Int -> Int -> m (MVector (PrimState m) Int)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m (v (PrimState m) a)
VM.basicUnsafeGrow MVector (PrimState m) Int
mvec1 Int
len
MVector (PrimState m) (Ix (n - 1))
ivs <- MVector (PrimState m) (Ix (n - 1))
-> Int -> m (MVector (PrimState m) (Ix (n - 1)))
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m (v (PrimState m) a)
VM.basicUnsafeGrow MVector (PrimState m) (Ix (n - 1))
mvec Int
len
MVector (PrimState m) (IxN n) -> m (MVector (PrimState m) (IxN n))
forall (m :: * -> *) a. Monad m => a -> m a
return (MVector (PrimState m) (IxN n)
-> m (MVector (PrimState m) (IxN n)))
-> MVector (PrimState m) (IxN n)
-> m (MVector (PrimState m) (IxN n))
forall a b. (a -> b) -> a -> b
$ (MVector (PrimState m) Int, MVector (PrimState m) (Ix (n - 1)))
-> MVector (PrimState m) (IxN n)
forall s (n :: Nat).
(MVector s Int, MVector s (Ix (n - 1))) -> MVector s (IxN n)
MV_IxN (MVector (PrimState m) Int
iv, MVector (PrimState m) (Ix (n - 1))
ivs)
{-# INLINE basicUnsafeGrow #-}
#if MIN_VERSION_vector(0,11,0)
basicInitialize :: MVector (PrimState m) (IxN n) -> m ()
basicInitialize (MV_IxN (mvec1, mvec)) =
MVector (PrimState m) Int -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
VM.basicInitialize MVector (PrimState m) Int
mvec1 m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MVector (PrimState m) (Ix (n - 1)) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
VM.basicInitialize MVector (PrimState m) (Ix (n - 1))
mvec
{-# INLINE basicInitialize #-}
#endif
newtype instance VU.Vector (IxN n) = V_IxN (VU.Vector Int, VU.Vector (Ix (n-1)))
instance (3 <= n, VU.Unbox (Ix (n - 1))) => V.Vector VU.Vector (IxN n) where
basicUnsafeFreeze :: Mutable Vector (PrimState m) (IxN n) -> m (Vector (IxN n))
basicUnsafeFreeze (MV_IxN (mvec1, mvec)) = do
Vector Int
iv <- Mutable Vector (PrimState m) Int -> m (Vector Int)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
V.basicUnsafeFreeze MVector (PrimState m) Int
Mutable Vector (PrimState m) Int
mvec1
Vector (Ix (n - 1))
ivs <- Mutable Vector (PrimState m) (Ix (n - 1))
-> m (Vector (Ix (n - 1)))
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
V.basicUnsafeFreeze MVector (PrimState m) (Ix (n - 1))
Mutable Vector (PrimState m) (Ix (n - 1))
mvec
Vector (IxN n) -> m (Vector (IxN n))
forall (m :: * -> *) a. Monad m => a -> m a
return (Vector (IxN n) -> m (Vector (IxN n)))
-> Vector (IxN n) -> m (Vector (IxN n))
forall a b. (a -> b) -> a -> b
$ (Vector Int, Vector (Ix (n - 1))) -> Vector (IxN n)
forall (n :: Nat).
(Vector Int, Vector (Ix (n - 1))) -> Vector (IxN n)
V_IxN (Vector Int
iv, Vector (Ix (n - 1))
ivs)
{-# INLINE basicUnsafeFreeze #-}
basicUnsafeThaw :: Vector (IxN n) -> m (Mutable Vector (PrimState m) (IxN n))
basicUnsafeThaw (V_IxN (vec1, vec)) = do
MVector (PrimState m) Int
imv <- Vector Int -> m (Mutable Vector (PrimState m) Int)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
V.basicUnsafeThaw Vector Int
vec1
MVector (PrimState m) (Ix (n - 1))
imvs <- Vector (Ix (n - 1))
-> m (Mutable Vector (PrimState m) (Ix (n - 1)))
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
V.basicUnsafeThaw Vector (Ix (n - 1))
vec
MVector (PrimState m) (IxN n) -> m (MVector (PrimState m) (IxN n))
forall (m :: * -> *) a. Monad m => a -> m a
return (MVector (PrimState m) (IxN n)
-> m (MVector (PrimState m) (IxN n)))
-> MVector (PrimState m) (IxN n)
-> m (MVector (PrimState m) (IxN n))
forall a b. (a -> b) -> a -> b
$ (MVector (PrimState m) Int, MVector (PrimState m) (Ix (n - 1)))
-> MVector (PrimState m) (IxN n)
forall s (n :: Nat).
(MVector s Int, MVector s (Ix (n - 1))) -> MVector s (IxN n)
MV_IxN (MVector (PrimState m) Int
imv, MVector (PrimState m) (Ix (n - 1))
imvs)
{-# INLINE basicUnsafeThaw #-}
basicLength :: Vector (IxN n) -> Int
basicLength (V_IxN (_, vec)) = Vector (Ix (n - 1)) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
V.basicLength Vector (Ix (n - 1))
vec
{-# INLINE basicLength #-}
basicUnsafeSlice :: Int -> Int -> Vector (IxN n) -> Vector (IxN n)
basicUnsafeSlice Int
idx Int
len (V_IxN (vec1, vec)) =
(Vector Int, Vector (Ix (n - 1))) -> Vector (IxN n)
forall (n :: Nat).
(Vector Int, Vector (Ix (n - 1))) -> Vector (IxN n)
V_IxN (Int -> Int -> Vector Int -> Vector Int
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
V.basicUnsafeSlice Int
idx Int
len Vector Int
vec1, Int -> Int -> Vector (Ix (n - 1)) -> Vector (Ix (n - 1))
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
V.basicUnsafeSlice Int
idx Int
len Vector (Ix (n - 1))
vec)
{-# INLINE basicUnsafeSlice #-}
basicUnsafeIndexM :: Vector (IxN n) -> Int -> m (IxN n)
basicUnsafeIndexM (V_IxN (vec1, vec)) Int
idx = do
Int
i <- Vector Int -> Int -> m Int
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
V.basicUnsafeIndexM Vector Int
vec1 Int
idx
Ix (n - 1)
ix <- Vector (Ix (n - 1)) -> Int -> m (Ix (n - 1))
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
V.basicUnsafeIndexM Vector (Ix (n - 1))
vec Int
idx
IxN n -> m (IxN n)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
i Int -> Ix (n - 1) -> IxN n
forall (n :: Nat). Int -> Ix (n - 1) -> IxN n
:> Ix (n - 1)
ix)
{-# INLINE basicUnsafeIndexM #-}
basicUnsafeCopy :: Mutable Vector (PrimState m) (IxN n) -> Vector (IxN n) -> m ()
basicUnsafeCopy (MV_IxN (mvec1, mvec)) (V_IxN (vec1, vec)) =
Mutable Vector (PrimState m) Int -> Vector Int -> m ()
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> v a -> m ()
V.basicUnsafeCopy MVector (PrimState m) Int
Mutable Vector (PrimState m) Int
mvec1 Vector Int
vec1 m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Mutable Vector (PrimState m) (Ix (n - 1))
-> Vector (Ix (n - 1)) -> m ()
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> v a -> m ()
V.basicUnsafeCopy MVector (PrimState m) (Ix (n - 1))
Mutable Vector (PrimState m) (Ix (n - 1))
mvec Vector (Ix (n - 1))
vec
{-# INLINE basicUnsafeCopy #-}
elemseq :: Vector (IxN n) -> IxN n -> b -> b
elemseq Vector (IxN n)
_ = IxN n -> b -> b
seq
{-# INLINE elemseq #-}