{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ExplicitNamespaces #-}
module Data.Massiv.Core.Index
( Ix0(..)
, type Ix1
, pattern Ix1
, type Ix2(Ix2, (:.))
, IxN((:>), Ix3, Ix4, Ix5)
, HighIxN
, type Ix3
, type Ix4
, type Ix5
, Ix
, type Sz1
, type Sz2
, type Sz3
, type Sz4
, type Sz5
, Sz(Sz, Sz1, Sz2, Sz3, Sz4, Sz5)
, unSz
, zeroSz
, oneSz
, liftSz
, liftSz2
, consSz
, unconsSz
, snocSz
, unsnocSz
, setSzM
, insertSzM
, pullOutSzM
, toLinearSz
, mkSzM
, Dim(..)
, Dimension(Dim1, Dim2, Dim3, Dim4, Dim5, DimN)
, IsIndexDimension
, IsDimValid
, ReportInvalidDim
, Stride(Stride)
, unStride
, toLinearIndexStride
, strideStart
, strideSize
, oneStride
, Border(..)
, handleBorderIndex
, Lower
, Index(..)
, zeroIndex
, oneIndex
, isZeroSz
, isNotZeroSz
, headDim
, tailDim
, lastDim
, initDim
, getDim'
, setDim'
, modifyDim'
, dropDimM
, dropDim'
, pullOutDim'
, insertDim'
, fromDimension
, getDimension
, setDimension
, modifyDimension
, dropDimension
, pullOutDimension
, insertDimension
, iter
, iterLinearM
, iterLinearM_
, module Data.Massiv.Core.Iterator
, module Data.Massiv.Core.Index.Tuple
, IndexException(..)
, SizeException(..)
, ShapeException(..)
, guardNumberOfElements
, indexWith
) where
import Control.DeepSeq
import Control.Monad.Catch (MonadThrow(..))
import Data.Coerce
import Data.Functor.Identity (runIdentity)
import Data.Massiv.Core.Exception
import Data.Massiv.Core.Index.Internal
import Data.Massiv.Core.Index.Ix
import Data.Massiv.Core.Index.Stride
import Data.Massiv.Core.Index.Tuple
import Data.Massiv.Core.Iterator
import GHC.TypeLits
type Sz1 = Sz Ix1
type Sz2 = Sz Ix2
type Sz3 = Sz Ix3
type Sz4 = Sz Ix4
type Sz5 = Sz Ix5
data Border e =
Fill e
| Wrap
| Edge
| Reflect
| Continue
deriving (Border e -> Border e -> Bool
(Border e -> Border e -> Bool)
-> (Border e -> Border e -> Bool) -> Eq (Border e)
forall e. Eq e => Border e -> Border e -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Border e -> Border e -> Bool
$c/= :: forall e. Eq e => Border e -> Border e -> Bool
== :: Border e -> Border e -> Bool
$c== :: forall e. Eq e => Border e -> Border e -> Bool
Eq, Int -> Border e -> ShowS
[Border e] -> ShowS
Border e -> String
(Int -> Border e -> ShowS)
-> (Border e -> String) -> ([Border e] -> ShowS) -> Show (Border e)
forall e. Show e => Int -> Border e -> ShowS
forall e. Show e => [Border e] -> ShowS
forall e. Show e => Border e -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Border e] -> ShowS
$cshowList :: forall e. Show e => [Border e] -> ShowS
show :: Border e -> String
$cshow :: forall e. Show e => Border e -> String
showsPrec :: Int -> Border e -> ShowS
$cshowsPrec :: forall e. Show e => Int -> Border e -> ShowS
Show)
instance NFData e => NFData (Border e) where
rnf :: Border e -> ()
rnf Border e
b = case Border e
b of
Fill e
e -> e -> ()
forall a. NFData a => a -> ()
rnf e
e
Border e
Wrap -> ()
Border e
Edge -> ()
Border e
Reflect -> ()
Border e
Continue -> ()
handleBorderIndex ::
Index ix
=> Border e
-> Sz ix
-> (ix -> e)
-> ix
-> e
handleBorderIndex :: Border e -> Sz ix -> (ix -> e) -> ix -> e
handleBorderIndex Border e
border !Sz ix
sz ix -> e
getVal !ix
ix =
case Border e
border of
Fill e
val -> if Sz ix -> ix -> Bool
forall ix. Index ix => Sz ix -> ix -> Bool
isSafeIndex Sz ix
sz ix
ix then ix -> e
getVal ix
ix else e
val
Border e
Wrap -> ix -> e
getVal (Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
repairIndex Sz ix
sz ix
ix Sz Int -> Int -> Int
forall a. Integral a => Sz a -> a -> a
wrap Sz Int -> Int -> Int
forall a. Integral a => Sz a -> a -> a
wrap)
Border e
Edge -> ix -> e
getVal (Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
repairIndex Sz ix
sz ix
ix ((Int -> Int) -> Sz Int -> Int -> Int
forall a b. a -> b -> a
const (Int -> Int -> Int
forall a b. a -> b -> a
const Int
0)) (\ (SafeSz Int
k) Int
_ -> Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1))
Border e
Reflect -> ix -> e
getVal (Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
repairIndex Sz ix
sz ix
ix (\ (SafeSz Int
k) !Int
i -> (Int -> Int
forall a. Num a => a -> a
abs Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
k)
(\ (SafeSz Int
k) !Int
i -> (-Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
k))
Border e
Continue -> ix -> e
getVal (Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
repairIndex Sz ix
sz ix
ix (\ (SafeSz Int
k) !Int
i -> Int -> Int
forall a. Num a => a -> a
abs Int
i Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
k)
(\ (SafeSz Int
k) !Int
i -> (-Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
k))
where wrap :: Sz a -> a -> a
wrap (SafeSz a
k) a
i = a
i a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
k
{-# INLINE [1] wrap #-}
{-# INLINE [1] handleBorderIndex #-}
zeroIndex :: Index ix => ix
zeroIndex :: ix
zeroIndex = Int -> ix
forall ix. Index ix => Int -> ix
pureIndex Int
0
{-# INLINE [1] zeroIndex #-}
oneIndex :: Index ix => ix
oneIndex :: ix
oneIndex = Int -> ix
forall ix. Index ix => Int -> ix
pureIndex Int
1
{-# INLINE [1] oneIndex #-}
isNotZeroSz :: Index ix => Sz ix -> Bool
isNotZeroSz :: Sz ix -> Bool
isNotZeroSz !Sz ix
sz = Sz ix -> ix -> Bool
forall ix. Index ix => Sz ix -> ix -> Bool
isSafeIndex Sz ix
sz ix
forall ix. Index ix => ix
zeroIndex
{-# INLINE [1] isNotZeroSz #-}
isZeroSz :: Index ix => Sz ix -> Bool
isZeroSz :: Sz ix -> Bool
isZeroSz = Bool -> Bool
not (Bool -> Bool) -> (Sz ix -> Bool) -> Sz ix -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sz ix -> Bool
forall ix. Index ix => Sz ix -> Bool
isNotZeroSz
{-# INLINE [1] isZeroSz #-}
toLinearSz :: Index ix => Sz ix -> Sz1
toLinearSz :: Sz ix -> Sz Int
toLinearSz = Int -> Sz Int
coerce (Int -> Sz Int) -> (Sz ix -> Int) -> Sz ix -> Sz Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sz ix -> Int
forall ix. Index ix => Sz ix -> Int
totalElem
{-# INLINE [1] toLinearSz #-}
headDim :: Index ix => ix -> Int
headDim :: ix -> Int
headDim = (Int, Lower ix) -> Int
forall a b. (a, b) -> a
fst ((Int, Lower ix) -> Int) -> (ix -> (Int, Lower ix)) -> ix -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> (Int, Lower ix)
forall ix. Index ix => ix -> (Int, Lower ix)
unconsDim
{-# INLINE [1] headDim #-}
tailDim :: Index ix => ix -> Lower ix
tailDim :: ix -> Lower ix
tailDim = (Int, Lower ix) -> Lower ix
forall a b. (a, b) -> b
snd ((Int, Lower ix) -> Lower ix)
-> (ix -> (Int, Lower ix)) -> ix -> Lower ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> (Int, Lower ix)
forall ix. Index ix => ix -> (Int, Lower ix)
unconsDim
{-# INLINE [1] tailDim #-}
lastDim :: Index ix => ix -> Int
lastDim :: ix -> Int
lastDim = (Lower ix, Int) -> Int
forall a b. (a, b) -> b
snd ((Lower ix, Int) -> Int) -> (ix -> (Lower ix, Int)) -> ix -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> (Lower ix, Int)
forall ix. Index ix => ix -> (Lower ix, Int)
unsnocDim
{-# INLINE [1] lastDim #-}
initDim :: Index ix => ix -> Lower ix
initDim :: ix -> Lower ix
initDim = (Lower ix, Int) -> Lower ix
forall a b. (a, b) -> a
fst ((Lower ix, Int) -> Lower ix)
-> (ix -> (Lower ix, Int)) -> ix -> Lower ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> (Lower ix, Int)
forall ix. Index ix => ix -> (Lower ix, Int)
unsnocDim
{-# INLINE [1] initDim #-}
setDim' :: (HasCallStack, Index ix) => ix -> Dim -> Int -> ix
setDim' :: ix -> Dim -> Int -> ix
setDim' ix
ix Dim
dim = Either SomeException ix -> ix
forall a. HasCallStack => Either SomeException a -> a
throwEither (Either SomeException ix -> ix)
-> (Int -> Either SomeException ix) -> Int -> ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> Dim -> Int -> Either SomeException ix
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> Int -> m ix
setDimM ix
ix Dim
dim
{-# INLINE [1] setDim' #-}
getDim' :: (HasCallStack, Index ix) => ix -> Dim -> Int
getDim' :: ix -> Dim -> Int
getDim' ix
ix = Either SomeException Int -> Int
forall a. HasCallStack => Either SomeException a -> a
throwEither (Either SomeException Int -> Int)
-> (Dim -> Either SomeException Int) -> Dim -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> Dim -> Either SomeException Int
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m Int
getDimM ix
ix
{-# INLINE [1] getDim' #-}
modifyDim' :: (HasCallStack, Index ix) => ix -> Dim -> (Int -> Int) -> (Int, ix)
modifyDim' :: ix -> Dim -> (Int -> Int) -> (Int, ix)
modifyDim' ix
ix Dim
dim = Either SomeException (Int, ix) -> (Int, ix)
forall a. HasCallStack => Either SomeException a -> a
throwEither (Either SomeException (Int, ix) -> (Int, ix))
-> ((Int -> Int) -> Either SomeException (Int, ix))
-> (Int -> Int)
-> (Int, ix)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> Dim -> (Int -> Int) -> Either SomeException (Int, ix)
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> (Int -> Int) -> m (Int, ix)
modifyDimM ix
ix Dim
dim
{-# INLINE [1] modifyDim' #-}
dropDimM :: (MonadThrow m, Index ix) => ix -> Dim -> m (Lower ix)
dropDimM :: ix -> Dim -> m (Lower ix)
dropDimM ix
ix = ((Int, Lower ix) -> Lower ix) -> m (Int, Lower ix) -> m (Lower ix)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int, Lower ix) -> Lower ix
forall a b. (a, b) -> b
snd (m (Int, Lower ix) -> m (Lower ix))
-> (Dim -> m (Int, Lower ix)) -> Dim -> m (Lower ix)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> Dim -> m (Int, Lower ix)
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m (Int, Lower ix)
pullOutDimM ix
ix
{-# INLINE [1] dropDimM #-}
dropDim' :: (HasCallStack, Index ix) => ix -> Dim -> Lower ix
dropDim' :: ix -> Dim -> Lower ix
dropDim' ix
ix = Either SomeException (Lower ix) -> Lower ix
forall a. HasCallStack => Either SomeException a -> a
throwEither (Either SomeException (Lower ix) -> Lower ix)
-> (Dim -> Either SomeException (Lower ix)) -> Dim -> Lower ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> Dim -> Either SomeException (Lower ix)
forall (m :: * -> *) ix.
(MonadThrow m, Index ix) =>
ix -> Dim -> m (Lower ix)
dropDimM ix
ix
{-# INLINE [1] dropDim' #-}
pullOutDim' :: (HasCallStack, Index ix) => ix -> Dim -> (Int, Lower ix)
pullOutDim' :: ix -> Dim -> (Int, Lower ix)
pullOutDim' ix
ix = Either SomeException (Int, Lower ix) -> (Int, Lower ix)
forall a. HasCallStack => Either SomeException a -> a
throwEither (Either SomeException (Int, Lower ix) -> (Int, Lower ix))
-> (Dim -> Either SomeException (Int, Lower ix))
-> Dim
-> (Int, Lower ix)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> Dim -> Either SomeException (Int, Lower ix)
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m (Int, Lower ix)
pullOutDimM ix
ix
{-# INLINE [1] pullOutDim' #-}
insertDim' :: (HasCallStack, Index ix) => Lower ix -> Dim -> Int -> ix
insertDim' :: Lower ix -> Dim -> Int -> ix
insertDim' Lower ix
ix Dim
dim = Either SomeException ix -> ix
forall a. HasCallStack => Either SomeException a -> a
throwEither (Either SomeException ix -> ix)
-> (Int -> Either SomeException ix) -> Int -> ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lower ix -> Dim -> Int -> Either SomeException ix
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
Lower ix -> Dim -> Int -> m ix
insertDimM Lower ix
ix Dim
dim
{-# INLINE [1] insertDim' #-}
fromDimension :: KnownNat n => Dimension n -> Dim
fromDimension :: Dimension n -> Dim
fromDimension = Integer -> Dim
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Dim) -> (Dimension n -> Integer) -> Dimension n -> Dim
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dimension n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal
{-# INLINE [1] fromDimension #-}
setDimension :: IsIndexDimension ix n => ix -> Dimension n -> Int -> ix
setDimension :: ix -> Dimension n -> Int -> ix
setDimension ix
ix = ix -> Dim -> Int -> ix
forall ix. (HasCallStack, Index ix) => ix -> Dim -> Int -> ix
setDim' ix
ix (Dim -> Int -> ix)
-> (Dimension n -> Dim) -> Dimension n -> Int -> ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dimension n -> Dim
forall (n :: Nat). KnownNat n => Dimension n -> Dim
fromDimension
{-# INLINE [1] setDimension #-}
modifyDimension :: IsIndexDimension ix n => ix -> Dimension n -> (Int -> Int) -> (Int, ix)
modifyDimension :: ix -> Dimension n -> (Int -> Int) -> (Int, ix)
modifyDimension ix
ix = ix -> Dim -> (Int -> Int) -> (Int, ix)
forall ix.
(HasCallStack, Index ix) =>
ix -> Dim -> (Int -> Int) -> (Int, ix)
modifyDim' ix
ix (Dim -> (Int -> Int) -> (Int, ix))
-> (Dimension n -> Dim) -> Dimension n -> (Int -> Int) -> (Int, ix)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dimension n -> Dim
forall (n :: Nat). KnownNat n => Dimension n -> Dim
fromDimension
{-# INLINE [1] modifyDimension #-}
getDimension :: IsIndexDimension ix n => ix -> Dimension n -> Int
getDimension :: ix -> Dimension n -> Int
getDimension ix
ix = ix -> Dim -> Int
forall ix. (HasCallStack, Index ix) => ix -> Dim -> Int
getDim' ix
ix (Dim -> Int) -> (Dimension n -> Dim) -> Dimension n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dimension n -> Dim
forall (n :: Nat). KnownNat n => Dimension n -> Dim
fromDimension
{-# INLINE [1] getDimension #-}
dropDimension :: IsIndexDimension ix n => ix -> Dimension n -> Lower ix
dropDimension :: ix -> Dimension n -> Lower ix
dropDimension ix
ix = ix -> Dim -> Lower ix
forall ix. (HasCallStack, Index ix) => ix -> Dim -> Lower ix
dropDim' ix
ix (Dim -> Lower ix)
-> (Dimension n -> Dim) -> Dimension n -> Lower ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dimension n -> Dim
forall (n :: Nat). KnownNat n => Dimension n -> Dim
fromDimension
{-# INLINE [1] dropDimension #-}
pullOutDimension :: IsIndexDimension ix n => ix -> Dimension n -> (Int, Lower ix)
pullOutDimension :: ix -> Dimension n -> (Int, Lower ix)
pullOutDimension ix
ix = ix -> Dim -> (Int, Lower ix)
forall ix. (HasCallStack, Index ix) => ix -> Dim -> (Int, Lower ix)
pullOutDim' ix
ix (Dim -> (Int, Lower ix))
-> (Dimension n -> Dim) -> Dimension n -> (Int, Lower ix)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dimension n -> Dim
forall (n :: Nat). KnownNat n => Dimension n -> Dim
fromDimension
{-# INLINE [1] pullOutDimension #-}
insertDimension :: IsIndexDimension ix n => Lower ix -> Dimension n -> Int -> ix
insertDimension :: Lower ix -> Dimension n -> Int -> ix
insertDimension Lower ix
ix = Lower ix -> Dim -> Int -> ix
forall ix. (HasCallStack, Index ix) => Lower ix -> Dim -> Int -> ix
insertDim' Lower ix
ix (Dim -> Int -> ix)
-> (Dimension n -> Dim) -> Dimension n -> Int -> ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dimension n -> Dim
forall (n :: Nat). KnownNat n => Dimension n -> Dim
fromDimension
{-# INLINE [1] insertDimension #-}
iter :: Index ix
=> ix
-> ix
-> ix
-> (Int -> Int -> Bool)
-> a
-> (ix -> a -> a)
-> a
iter :: ix -> ix -> ix -> (Int -> Int -> Bool) -> a -> (ix -> a -> a) -> a
iter ix
sIx ix
eIx ix
incIx Int -> Int -> Bool
cond a
acc ix -> a -> a
f =
Identity a -> a
forall a. Identity a -> a
runIdentity (Identity a -> a) -> Identity a -> a
forall a b. (a -> b) -> a -> b
$ ix
-> ix
-> ix
-> (Int -> Int -> Bool)
-> a
-> (ix -> a -> Identity a)
-> Identity a
forall ix (m :: * -> *) a.
(Index ix, Monad m) =>
ix
-> ix -> ix -> (Int -> Int -> Bool) -> a -> (ix -> a -> m a) -> m a
iterM ix
sIx ix
eIx ix
incIx Int -> Int -> Bool
cond a
acc (\ix
ix -> a -> Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Identity a) -> (a -> a) -> a -> Identity a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> a -> a
f ix
ix)
{-# INLINE iter #-}
iterLinearM :: (Index ix, Monad m)
=> Sz ix
-> Int
-> Int
-> Int
-> (Int -> Int -> Bool)
-> a
-> (Int -> ix -> a -> m a)
-> m a
iterLinearM :: Sz ix
-> Int
-> Int
-> Int
-> (Int -> Int -> Bool)
-> a
-> (Int -> ix -> a -> m a)
-> m a
iterLinearM !Sz ix
sz !Int
k0 !Int
k1 !Int
inc Int -> Int -> Bool
cond !a
acc Int -> ix -> a -> m a
f =
Int
-> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a
forall (m :: * -> *) a.
Monad m =>
Int
-> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a
loopM Int
k0 (Int -> Int -> Bool
`cond` Int
k1) (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
inc) a
acc ((Int -> a -> m a) -> m a) -> (Int -> a -> m a) -> m a
forall a b. (a -> b) -> a -> b
$ \ !Int
i !a
acc0 -> Int -> ix -> a -> m a
f Int
i (Sz ix -> Int -> ix
forall ix. Index ix => Sz ix -> Int -> ix
fromLinearIndex Sz ix
sz Int
i) a
acc0
{-# INLINE iterLinearM #-}
iterLinearM_ :: (Index ix, Monad m) =>
Sz ix
-> Int
-> Int
-> Int
-> (Int -> Int -> Bool)
-> (Int -> ix -> m ())
-> m ()
iterLinearM_ :: Sz ix
-> Int
-> Int
-> Int
-> (Int -> Int -> Bool)
-> (Int -> ix -> m ())
-> m ()
iterLinearM_ Sz ix
sz !Int
k0 !Int
k1 !Int
inc Int -> Int -> Bool
cond Int -> ix -> m ()
f =
Int -> (Int -> Bool) -> (Int -> Int) -> (Int -> m ()) -> m ()
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> Bool) -> (Int -> Int) -> (Int -> m a) -> m ()
loopM_ Int
k0 (Int -> Int -> Bool
`cond` Int
k1) (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
inc) ((Int -> m ()) -> m ()) -> (Int -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \ !Int
i -> Int -> ix -> m ()
f Int
i (Sz ix -> Int -> ix
forall ix. Index ix => Sz ix -> Int -> ix
fromLinearIndex Sz ix
sz Int
i)
{-# INLINE iterLinearM_ #-}
indexWith ::
Index ix
=> String
-> Int
-> String
-> (arr -> Sz ix)
-> (arr -> ix -> e)
-> arr
-> ix
-> e
indexWith :: String
-> Int
-> String
-> (arr -> Sz ix)
-> (arr -> ix -> e)
-> arr
-> ix
-> e
indexWith String
fileName Int
lineNo String
funName arr -> Sz ix
getSize arr -> ix -> e
f arr
arr ix
ix
| Sz ix -> ix -> Bool
forall ix. Index ix => Sz ix -> ix -> Bool
isSafeIndex Sz ix
sz ix
ix = arr -> ix -> e
f arr
arr ix
ix
| Bool
otherwise = String -> Sz ix -> ix -> e
forall ix ix' a. (Show ix, Show ix') => String -> ix -> ix' -> a
errorIx (String
"<" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
fileName String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
lineNo String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"> " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
funName) Sz ix
sz ix
ix
where
sz :: Sz ix
sz = arr -> Sz ix
getSize arr
arr
errorIx :: (Show ix, Show ix') => String -> ix -> ix' -> a
errorIx :: String -> ix -> ix' -> a
errorIx String
fName ix
sz ix'
ix =
String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$
String
fName String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
": Index out of bounds: (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ix' -> String
forall a. Show a => a -> String
show ix'
ix String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
") for Array of size: (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ix -> String
forall a. Show a => a -> String
show ix
sz String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
{-# NOINLINE errorIx #-}