massiv-1.0.2.0: Massiv (Массив) is an Array Library.
Copyright(c) Alexey Kuleshevich 2018-2022
LicenseBSD3
MaintainerAlexey Kuleshevich <alexey@kuleshevi.ch>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Massiv.Core.Index

Description

 
Synopsis

Documentation

data Ix0 Source #

Zero-dimension, i.e. a scalar. Can't really be used directly as there is no instance of Index for it, and is included for completeness.

Constructors

Ix0 

Instances

Instances details
Eq Ix0 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

(==) :: Ix0 -> Ix0 -> Bool #

(/=) :: Ix0 -> Ix0 -> Bool #

Ord Ix0 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

compare :: Ix0 -> Ix0 -> Ordering #

(<) :: Ix0 -> Ix0 -> Bool #

(<=) :: Ix0 -> Ix0 -> Bool #

(>) :: Ix0 -> Ix0 -> Bool #

(>=) :: Ix0 -> Ix0 -> Bool #

max :: Ix0 -> Ix0 -> Ix0 #

min :: Ix0 -> Ix0 -> Ix0 #

Show Ix0 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

showsPrec :: Int -> Ix0 -> ShowS #

show :: Ix0 -> String #

showList :: [Ix0] -> ShowS #

NFData Ix0 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

rnf :: Ix0 -> () #

type Ix1 = Int Source #

A type synonym for 1-dimensional index, i.e. Int.

>>> 5 :: Ix1
5

Since: 0.1.0

pattern Ix1 :: Int -> Ix1 Source #

This is a very handy pattern synonym to indicate that any arbitrary Integral literal is an Int, e.g. a 1-dimensional index: (Ix1 5) == (5 :: Int)

>>> Ix1 5
5
>>> :t Ix1 5
Ix1 5 :: Ix1

Since: 0.1.0

data Ix2 Source #

2-dimensional index. This is also a base index for higher dimensions.

Since: 0.1.0

Constructors

!Int :. !Int infixr 5 

Bundled Patterns

pattern Ix2 :: Int -> Int -> Ix2

2-dimensional index constructor. Useful when infix notation is inconvenient. (Ix2 i j) == (i :. j)

Since: 0.1.0

Instances

Instances details
Bounded Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

minBound :: Ix2 #

maxBound :: Ix2 #

Eq Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

(==) :: Ix2 -> Ix2 -> Bool #

(/=) :: Ix2 -> Ix2 -> Bool #

Num Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

(+) :: Ix2 -> Ix2 -> Ix2 #

(-) :: Ix2 -> Ix2 -> Ix2 #

(*) :: Ix2 -> Ix2 -> Ix2 #

negate :: Ix2 -> Ix2 #

abs :: Ix2 -> Ix2 #

signum :: Ix2 -> Ix2 #

fromInteger :: Integer -> Ix2 #

Ord Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

compare :: Ix2 -> Ix2 -> Ordering #

(<) :: Ix2 -> Ix2 -> Bool #

(<=) :: Ix2 -> Ix2 -> Bool #

(>) :: Ix2 -> Ix2 -> Bool #

(>=) :: Ix2 -> Ix2 -> Bool #

max :: Ix2 -> Ix2 -> Ix2 #

min :: Ix2 -> Ix2 -> Ix2 #

Show Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

showsPrec :: Int -> Ix2 -> ShowS #

show :: Ix2 -> String #

showList :: [Ix2] -> ShowS #

Ix Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

range :: (Ix2, Ix2) -> [Ix2] #

index :: (Ix2, Ix2) -> Ix2 -> Int #

unsafeIndex :: (Ix2, Ix2) -> Ix2 -> Int #

inRange :: (Ix2, Ix2) -> Ix2 -> Bool #

rangeSize :: (Ix2, Ix2) -> Int #

unsafeRangeSize :: (Ix2, Ix2) -> Int #

NFData Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

rnf :: Ix2 -> () #

Random Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

randomR :: RandomGen g => (Ix2, Ix2) -> g -> (Ix2, g) #

random :: RandomGen g => g -> (Ix2, g) #

randomRs :: RandomGen g => (Ix2, Ix2) -> g -> [Ix2] #

randoms :: RandomGen g => g -> [Ix2] #

Uniform Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

uniformM :: StatefulGen g m => g -> m Ix2 #

UniformRange Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

uniformRM :: StatefulGen g m => (Ix2, Ix2) -> g -> m Ix2 #

Unbox Ix2 Source #

Unboxing of a Ix2.

Instance details

Defined in Data.Massiv.Core.Index.Ix

Index Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Associated Types

type Dimensions Ix2 :: Nat Source #

Methods

dimensions :: proxy Ix2 -> Dim Source #

totalElem :: Sz Ix2 -> Int Source #

consDim :: Int -> Lower Ix2 -> Ix2 Source #

unconsDim :: Ix2 -> (Int, Lower Ix2) Source #

snocDim :: Lower Ix2 -> Int -> Ix2 Source #

unsnocDim :: Ix2 -> (Lower Ix2, Int) Source #

pullOutDimM :: MonadThrow m => Ix2 -> Dim -> m (Int, Lower Ix2) Source #

insertDimM :: MonadThrow m => Lower Ix2 -> Dim -> Int -> m Ix2 Source #

getDimM :: MonadThrow m => Ix2 -> Dim -> m Int Source #

setDimM :: MonadThrow m => Ix2 -> Dim -> Int -> m Ix2 Source #

modifyDimM :: MonadThrow m => Ix2 -> Dim -> (Int -> Int) -> m (Int, Ix2) Source #

pureIndex :: Int -> Ix2 Source #

liftIndex2 :: (Int -> Int -> Int) -> Ix2 -> Ix2 -> Ix2 Source #

liftIndex :: (Int -> Int) -> Ix2 -> Ix2 Source #

foldlIndex :: (a -> Int -> a) -> a -> Ix2 -> a Source #

isSafeIndex :: Sz Ix2 -> Ix2 -> Bool Source #

toLinearIndex :: Sz Ix2 -> Ix2 -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> Ix2 -> Ix2 -> Ix1 Source #

fromLinearIndex :: Sz Ix2 -> Ix1 -> Ix2 Source #

fromLinearIndexAcc :: Ix2 -> Ix1 -> (Int, Ix2) Source #

repairIndex :: Sz Ix2 -> Ix2 -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Ix2 Source #

iterM :: Monad m => Ix2 -> Ix2 -> Ix2 -> (Int -> Int -> Bool) -> a -> (Ix2 -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> Ix2 -> Ix2 -> Sz Ix2 -> a -> (a -> ST s (a, a)) -> (Ix2 -> a -> ST s a) -> ST s a Source #

iterF :: Ix2 -> Ix2 -> Ix2 -> (Int -> Int -> Bool) -> f a -> (Ix2 -> f a -> f a) -> f a Source #

stepNextMF :: Ix2 -> Ix2 -> Ix2 -> (Int -> Int -> Bool) -> (Maybe Ix2 -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz Ix2 -> Ix2 -> Ix2 -> (Ix1 -> Ix2 -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz Ix2 -> Ix2 -> Ix2 -> a -> (Ix1 -> Ix2 -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz Ix2 -> Ix2 -> Ix2 -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix2 -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz Ix2 -> Ix2 -> Ix2 -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix2 -> a -> ST s a) -> ST s () Source #

Vector Vector Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

MVector MVector Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Shape L Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.List

Ragged L Ix2 e Source # 
Instance details

Defined in Data.Massiv.Core.List

Methods

generateRaggedM :: Monad m => Comp -> Sz Ix2 -> (Ix2 -> m e) -> m (Array L Ix2 e)

flattenRagged :: Array L Ix2 e -> Vector L e

loadRaggedST :: Scheduler s () -> Array L Ix2 e -> (Ix1 -> e -> ST s ()) -> Ix1 -> Ix1 -> Sz Ix2 -> ST s ()

raggedFormat :: (e -> String) -> String -> Array L Ix2 e -> String

StrideLoad DW Ix2 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

iterArrayLinearWithStrideST_ :: Scheduler s () -> Stride Ix2 -> Sz Ix2 -> Array DW Ix2 e -> (Int -> e -> ST s ()) -> ST s () Source #

Load DW Ix2 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

makeArray :: Comp -> Sz Ix2 -> (Ix2 -> e) -> Array DW Ix2 e Source #

makeArrayLinear :: Comp -> Sz Ix2 -> (Int -> e) -> Array DW Ix2 e Source #

replicate :: Comp -> Sz Ix2 -> e -> Array DW Ix2 e Source #

iterArrayLinearST_ :: Scheduler s () -> Array DW Ix2 e -> (Int -> e -> ST s ()) -> ST s () Source #

iterArrayLinearWithSetST_ :: Scheduler s () -> Array DW Ix2 e -> (Ix1 -> e -> ST s ()) -> (Ix1 -> Sz1 -> e -> ST s ()) -> ST s () Source #

unsafeLoadIntoST :: Manifest r' e => MVector s r' e -> Array DW Ix2 e -> ST s (MArray s r' Ix2 e) Source #

unsafeLoadIntoIO :: Manifest r' e => MVector RealWorld r' e -> Array DW Ix2 e -> IO (MArray RealWorld r' Ix2 e) Source #

newtype Vector Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

newtype Vector Ix2 = V_Ix2 (Vector (Int, Int))
type Dimensions Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

type Dimensions Ix2 = 2
type Lower Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

type Lower Ix2 = Ix1
newtype MVector s Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

newtype MVector s Ix2 = MV_Ix2 (MVector s (Int, Int))

data IxN (n :: Nat) Source #

n-dimensional index. Needs a base case, which is the Ix2.

Since: 0.1.0

Constructors

!Int :> !(Ix (n - 1)) infixr 5 

Bundled Patterns

pattern Ix3 :: Int -> Int -> Int -> Ix3

3-dimensional index constructor. (Ix3 i j k) == (i :> j :. k)

Since: 0.1.0

pattern Ix4 :: Int -> Int -> Int -> Int -> Ix4

4-dimensional index constructor. (Ix4 i j k l) == (i :> j :> k :. l)

Since: 0.1.0

pattern Ix5 :: Int -> Int -> Int -> Int -> Int -> Ix5

5-dimensional index constructor. (Ix5 i j k l m) == (i :> j :> k :> l :. m)

Since: 0.1.0

Instances

Instances details
Bounded Ix3 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

minBound :: Ix3 #

maxBound :: Ix3 #

Num Ix3 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

(+) :: Ix3 -> Ix3 -> Ix3 #

(-) :: Ix3 -> Ix3 -> Ix3 #

(*) :: Ix3 -> Ix3 -> Ix3 #

negate :: Ix3 -> Ix3 #

abs :: Ix3 -> Ix3 #

signum :: Ix3 -> Ix3 #

fromInteger :: Integer -> Ix3 #

(3 <= n, Unbox (Ix (n - 1))) => Vector Vector (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

basicUnsafeFreeze :: Mutable Vector s (IxN n) -> ST s (Vector (IxN n)) #

basicUnsafeThaw :: Vector (IxN n) -> ST s (Mutable Vector s (IxN n)) #

basicLength :: Vector (IxN n) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (IxN n) -> Vector (IxN n) #

basicUnsafeIndexM :: Vector (IxN n) -> Int -> Box (IxN n) #

basicUnsafeCopy :: Mutable Vector s (IxN n) -> Vector (IxN n) -> ST s () #

elemseq :: Vector (IxN n) -> IxN n -> b -> b #

(3 <= n, Unbox (Ix (n - 1))) => MVector MVector (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

basicLength :: MVector s (IxN n) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (IxN n) -> MVector s (IxN n) #

basicOverlaps :: MVector s (IxN n) -> MVector s (IxN n) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (IxN n)) #

basicInitialize :: MVector s (IxN n) -> ST s () #

basicUnsafeReplicate :: Int -> IxN n -> ST s (MVector s (IxN n)) #

basicUnsafeRead :: MVector s (IxN n) -> Int -> ST s (IxN n) #

basicUnsafeWrite :: MVector s (IxN n) -> Int -> IxN n -> ST s () #

basicClear :: MVector s (IxN n) -> ST s () #

basicSet :: MVector s (IxN n) -> IxN n -> ST s () #

basicUnsafeCopy :: MVector s (IxN n) -> MVector s (IxN n) -> ST s () #

basicUnsafeMove :: MVector s (IxN n) -> MVector s (IxN n) -> ST s () #

basicUnsafeGrow :: MVector s (IxN n) -> Int -> ST s (MVector s (IxN n)) #

(Shape L (Ix (n - 1)), Index (IxN n)) => Shape L (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.List

(Shape L (IxN n), Ragged L (Ix (n - 1)) e, Coercible (Elt (Ix (n - 1)) e) (ListItem (Ix (n - 1)) e)) => Ragged L (IxN n) e Source # 
Instance details

Defined in Data.Massiv.Core.List

Methods

generateRaggedM :: Monad m => Comp -> Sz (IxN n) -> (IxN n -> m e) -> m (Array L (IxN n) e)

flattenRagged :: Array L (IxN n) e -> Vector L e

loadRaggedST :: Scheduler s () -> Array L (IxN n) e -> (Ix1 -> e -> ST s ()) -> Ix1 -> Ix1 -> Sz (IxN n) -> ST s ()

raggedFormat :: (e -> String) -> String -> Array L (IxN n) e -> String

(Index (IxN n), StrideLoad DW (Ix (n - 1)) e) => StrideLoad DW (IxN n) e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

iterArrayLinearWithStrideST_ :: Scheduler s () -> Stride (IxN n) -> Sz (IxN n) -> Array DW (IxN n) e -> (Int -> e -> ST s ()) -> ST s () Source #

(Index (IxN n), Load DW (Ix (n - 1)) e) => Load DW (IxN n) e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

makeArray :: Comp -> Sz (IxN n) -> (IxN n -> e) -> Array DW (IxN n) e Source #

makeArrayLinear :: Comp -> Sz (IxN n) -> (Int -> e) -> Array DW (IxN n) e Source #

replicate :: Comp -> Sz (IxN n) -> e -> Array DW (IxN n) e Source #

iterArrayLinearST_ :: Scheduler s () -> Array DW (IxN n) e -> (Int -> e -> ST s ()) -> ST s () Source #

iterArrayLinearWithSetST_ :: Scheduler s () -> Array DW (IxN n) e -> (Ix1 -> e -> ST s ()) -> (Ix1 -> Sz1 -> e -> ST s ()) -> ST s () Source #

unsafeLoadIntoST :: Manifest r' e => MVector s r' e -> Array DW (IxN n) e -> ST s (MArray s r' (IxN n) e) Source #

unsafeLoadIntoIO :: Manifest r' e => MVector RealWorld r' e -> Array DW (IxN n) e -> IO (MArray RealWorld r' (IxN n) e) Source #

HighIxN n => Bounded (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

minBound :: IxN n #

maxBound :: IxN n #

Eq (Ix (n - 1)) => Eq (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

(==) :: IxN n -> IxN n -> Bool #

(/=) :: IxN n -> IxN n -> Bool #

HighIxN n => Num (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

(+) :: IxN n -> IxN n -> IxN n #

(-) :: IxN n -> IxN n -> IxN n #

(*) :: IxN n -> IxN n -> IxN n #

negate :: IxN n -> IxN n #

abs :: IxN n -> IxN n #

signum :: IxN n -> IxN n #

fromInteger :: Integer -> IxN n #

Ord (Ix (n - 1)) => Ord (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

compare :: IxN n -> IxN n -> Ordering #

(<) :: IxN n -> IxN n -> Bool #

(<=) :: IxN n -> IxN n -> Bool #

(>) :: IxN n -> IxN n -> Bool #

(>=) :: IxN n -> IxN n -> Bool #

max :: IxN n -> IxN n -> IxN n #

min :: IxN n -> IxN n -> IxN n #

Show (Ix (n - 1)) => Show (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

showsPrec :: Int -> IxN n -> ShowS #

show :: IxN n -> String #

showList :: [IxN n] -> ShowS #

Ix (Ix (n - 1)) => Ix (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

range :: (IxN n, IxN n) -> [IxN n] #

index :: (IxN n, IxN n) -> IxN n -> Int #

unsafeIndex :: (IxN n, IxN n) -> IxN n -> Int #

inRange :: (IxN n, IxN n) -> IxN n -> Bool #

rangeSize :: (IxN n, IxN n) -> Int #

unsafeRangeSize :: (IxN n, IxN n) -> Int #

NFData (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

rnf :: IxN n -> () #

Random (Ix (n - 1)) => Random (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

randomR :: RandomGen g => (IxN n, IxN n) -> g -> (IxN n, g) #

random :: RandomGen g => g -> (IxN n, g) #

randomRs :: RandomGen g => (IxN n, IxN n) -> g -> [IxN n] #

randoms :: RandomGen g => g -> [IxN n] #

Uniform (Ix (n - 1)) => Uniform (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

uniformM :: StatefulGen g m => g -> m (IxN n) #

UniformRange (Ix (n - 1)) => UniformRange (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

uniformRM :: StatefulGen g m => (IxN n, IxN n) -> g -> m (IxN n) #

(3 <= n, Unbox (Ix (n - 1))) => Unbox (IxN n) Source #

Unboxing of a IxN.

Instance details

Defined in Data.Massiv.Core.Index.Ix

HighIxN n => Index (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Associated Types

type Dimensions (IxN n) :: Nat Source #

Methods

dimensions :: proxy (IxN n) -> Dim Source #

totalElem :: Sz (IxN n) -> Int Source #

consDim :: Int -> Lower (IxN n) -> IxN n Source #

unconsDim :: IxN n -> (Int, Lower (IxN n)) Source #

snocDim :: Lower (IxN n) -> Int -> IxN n Source #

unsnocDim :: IxN n -> (Lower (IxN n), Int) Source #

pullOutDimM :: MonadThrow m => IxN n -> Dim -> m (Int, Lower (IxN n)) Source #

insertDimM :: MonadThrow m => Lower (IxN n) -> Dim -> Int -> m (IxN n) Source #

getDimM :: MonadThrow m => IxN n -> Dim -> m Int Source #

setDimM :: MonadThrow m => IxN n -> Dim -> Int -> m (IxN n) Source #

modifyDimM :: MonadThrow m => IxN n -> Dim -> (Int -> Int) -> m (Int, IxN n) Source #

pureIndex :: Int -> IxN n Source #

liftIndex2 :: (Int -> Int -> Int) -> IxN n -> IxN n -> IxN n Source #

liftIndex :: (Int -> Int) -> IxN n -> IxN n Source #

foldlIndex :: (a -> Int -> a) -> a -> IxN n -> a Source #

isSafeIndex :: Sz (IxN n) -> IxN n -> Bool Source #

toLinearIndex :: Sz (IxN n) -> IxN n -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> IxN n -> IxN n -> Ix1 Source #

fromLinearIndex :: Sz (IxN n) -> Ix1 -> IxN n Source #

fromLinearIndexAcc :: IxN n -> Ix1 -> (Int, IxN n) Source #

repairIndex :: Sz (IxN n) -> IxN n -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> IxN n Source #

iterM :: Monad m => IxN n -> IxN n -> IxN n -> (Int -> Int -> Bool) -> a -> (IxN n -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> IxN n -> IxN n -> Sz (IxN n) -> a -> (a -> ST s (a, a)) -> (IxN n -> a -> ST s a) -> ST s a Source #

iterF :: IxN n -> IxN n -> IxN n -> (Int -> Int -> Bool) -> f a -> (IxN n -> f a -> f a) -> f a Source #

stepNextMF :: IxN n -> IxN n -> IxN n -> (Int -> Int -> Bool) -> (Maybe (IxN n) -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz (IxN n) -> IxN n -> IxN n -> (Ix1 -> IxN n -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz (IxN n) -> IxN n -> IxN n -> a -> (Ix1 -> IxN n -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz (IxN n) -> IxN n -> IxN n -> a -> (a -> ST s (a, a)) -> (Ix1 -> IxN n -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz (IxN n) -> IxN n -> IxN n -> a -> (a -> ST s (a, a)) -> (Ix1 -> IxN n -> a -> ST s a) -> ST s () Source #

Index (IxN 3) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Associated Types

type Dimensions (IxN 3) :: Nat Source #

Methods

dimensions :: proxy (IxN 3) -> Dim Source #

totalElem :: Sz (IxN 3) -> Int Source #

consDim :: Int -> Lower (IxN 3) -> IxN 3 Source #

unconsDim :: IxN 3 -> (Int, Lower (IxN 3)) Source #

snocDim :: Lower (IxN 3) -> Int -> IxN 3 Source #

unsnocDim :: IxN 3 -> (Lower (IxN 3), Int) Source #

pullOutDimM :: MonadThrow m => IxN 3 -> Dim -> m (Int, Lower (IxN 3)) Source #

insertDimM :: MonadThrow m => Lower (IxN 3) -> Dim -> Int -> m (IxN 3) Source #

getDimM :: MonadThrow m => IxN 3 -> Dim -> m Int Source #

setDimM :: MonadThrow m => IxN 3 -> Dim -> Int -> m (IxN 3) Source #

modifyDimM :: MonadThrow m => IxN 3 -> Dim -> (Int -> Int) -> m (Int, IxN 3) Source #

pureIndex :: Int -> IxN 3 Source #

liftIndex2 :: (Int -> Int -> Int) -> IxN 3 -> IxN 3 -> IxN 3 Source #

liftIndex :: (Int -> Int) -> IxN 3 -> IxN 3 Source #

foldlIndex :: (a -> Int -> a) -> a -> IxN 3 -> a Source #

isSafeIndex :: Sz (IxN 3) -> IxN 3 -> Bool Source #

toLinearIndex :: Sz (IxN 3) -> IxN 3 -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> IxN 3 -> IxN 3 -> Ix1 Source #

fromLinearIndex :: Sz (IxN 3) -> Ix1 -> IxN 3 Source #

fromLinearIndexAcc :: IxN 3 -> Ix1 -> (Int, IxN 3) Source #

repairIndex :: Sz (IxN 3) -> IxN 3 -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> IxN 3 Source #

iterM :: Monad m => IxN 3 -> IxN 3 -> IxN 3 -> (Int -> Int -> Bool) -> a -> (IxN 3 -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> IxN 3 -> IxN 3 -> Sz (IxN 3) -> a -> (a -> ST s (a, a)) -> (IxN 3 -> a -> ST s a) -> ST s a Source #

iterF :: IxN 3 -> IxN 3 -> IxN 3 -> (Int -> Int -> Bool) -> f a -> (IxN 3 -> f a -> f a) -> f a Source #

stepNextMF :: IxN 3 -> IxN 3 -> IxN 3 -> (Int -> Int -> Bool) -> (Maybe (IxN 3) -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz (IxN 3) -> IxN 3 -> IxN 3 -> (Ix1 -> IxN 3 -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz (IxN 3) -> IxN 3 -> IxN 3 -> a -> (Ix1 -> IxN 3 -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz (IxN 3) -> IxN 3 -> IxN 3 -> a -> (a -> ST s (a, a)) -> (Ix1 -> IxN 3 -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz (IxN 3) -> IxN 3 -> IxN 3 -> a -> (a -> ST s (a, a)) -> (Ix1 -> IxN 3 -> a -> ST s a) -> ST s () Source #

type Dimensions Ix3 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

type Dimensions Ix3 = 3
newtype MVector s (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

newtype MVector s (IxN n) = MV_IxN (MVector s Int, MVector s (Ix (n - 1)))
newtype Vector (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

newtype Vector (IxN n) = V_IxN (Vector Int, Vector (Ix (n - 1)))
type Dimensions (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

type Dimensions (IxN n) = n
type Lower (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

type Lower (IxN n) = Ix (n - 1)

type HighIxN n = (4 <= n, KnownNat n, KnownNat (n - 1), Index (IxN (n - 1)), IxN (n - 1) ~ Ix (n - 1)) Source #

Constraint synonym that encapsulates all constraints needed for dimension 4 and higher.

Since: 1.0.0

type Ix3 = IxN 3 Source #

3-dimensional type synonym. Useful as a alternative to enabling DataKinds and using type level Nats.

Since: 0.1.0

type Ix4 = IxN 4 Source #

4-dimensional type synonym.

Since: 0.1.0

type Ix5 = IxN 5 Source #

5-dimensional type synonym.

Since: 0.1.0

type family Ix (n :: Nat) = r | r -> n where ... Source #

Defines n-dimensional index by relating a general IxN with few base cases.

Since: 0.1.0

Equations

Ix 0 = Ix0 
Ix 1 = Ix1 
Ix 2 = Ix2 
Ix n = IxN n 

Size

type Sz1 = Sz Ix1 Source #

1-dimensional type synonym for size.

Since: 0.3.0

type Sz2 = Sz Ix2 Source #

2-dimensional size type synonym.

Since: 0.3.0

type Sz3 = Sz Ix3 Source #

3-dimensional size type synonym.

Since: 0.3.0

type Sz4 = Sz Ix4 Source #

4-dimensional size type synonym.

Since: 0.3.0

type Sz5 = Sz Ix5 Source #

5-dimensional size type synonym.

Since: 0.3.0

data Sz ix where Source #

Sz is the size of the array. It describes total number of elements along each dimension in the array. It is a wrapper around an index of the same dimension, however it provides type safety preventing mixup with index. Moreover the Sz constructor and others such as Sz1, Sz2, ... that are specialized to specific dimensions, prevent creation of invalid sizes with negative values by clamping them to zero.

Examples

Expand
>>> import Data.Massiv.Array
>>> Sz (1 :> 2 :. 3)
Sz (1 :> 2 :. 3)

Sz has a Num instance, which is very convenient:

>>> Sz (1 :> 2 :. 3) + 5
Sz (6 :> 7 :. 8)

However subtraction can sometimes lead to surprising behavior, because size is not allowed to take negative values it will be clamped at 0.

>>> Sz (1 :> 2 :. 3) - 2
Sz (0 :> 0 :. 1)

Warning: It is always wrong to negate a size, thus it will result in an error. For that reason also watch out for partially applied (- sz), which is deugared into negate sz. See more info about it in #114.

Since: 0.3.0

Bundled Patterns

pattern Sz :: Index ix => ix -> Sz ix

A safe bidirectional pattern synonym for Sz construction that will make sure that none of the size elements are negative.

Since: 0.3.0

pattern Sz1 :: Ix1 -> Sz Ix1

1-dimensional size constructor. Especially useful with literals: (Sz1 5) == Sz (5 :: Int).

Since: 0.3.0

pattern Sz2 :: Int -> Int -> Sz Ix2

2-dimensional size constructor. (Sz2 i j) == Sz (i :. j)

Since: 0.3.0

pattern Sz3 :: Int -> Int -> Int -> Sz Ix3

3-dimensional size constructor. (Sz3 i j k) == Sz (i :> j :. k)

Since: 0.3.0

pattern Sz4 :: Int -> Int -> Int -> Int -> Sz Ix4

4-dimensional size constructor. (Sz4 i j k l) == Sz (i :> j :> k :. l)

Since: 0.3.0

pattern Sz5 :: Int -> Int -> Int -> Int -> Int -> Sz Ix5

5-dimensional size constructor. (Sz5 i j k l m) == Sz (i :> j :> k :> l :. m)

Since: 0.3.0

Instances

Instances details
Eq ix => Eq (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

(==) :: Sz ix -> Sz ix -> Bool #

(/=) :: Sz ix -> Sz ix -> Bool #

(Num ix, Index ix) => Num (Sz ix) Source #

Calling negate is an error.

Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

(+) :: Sz ix -> Sz ix -> Sz ix #

(-) :: Sz ix -> Sz ix -> Sz ix #

(*) :: Sz ix -> Sz ix -> Sz ix #

negate :: Sz ix -> Sz ix #

abs :: Sz ix -> Sz ix #

signum :: Sz ix -> Sz ix #

fromInteger :: Integer -> Sz ix #

Ord ix => Ord (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

compare :: Sz ix -> Sz ix -> Ordering #

(<) :: Sz ix -> Sz ix -> Bool #

(<=) :: Sz ix -> Sz ix -> Bool #

(>) :: Sz ix -> Sz ix -> Bool #

(>=) :: Sz ix -> Sz ix -> Bool #

max :: Sz ix -> Sz ix -> Sz ix #

min :: Sz ix -> Sz ix -> Sz ix #

Index ix => Show (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

showsPrec :: Int -> Sz ix -> ShowS #

show :: Sz ix -> String #

showList :: [Sz ix] -> ShowS #

NFData ix => NFData (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

rnf :: Sz ix -> () #

(UniformRange ix, Index ix) => Random (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

randomR :: RandomGen g => (Sz ix, Sz ix) -> g -> (Sz ix, g) #

random :: RandomGen g => g -> (Sz ix, g) #

randomRs :: RandomGen g => (Sz ix, Sz ix) -> g -> [Sz ix] #

randoms :: RandomGen g => g -> [Sz ix] #

(UniformRange ix, Index ix) => Uniform (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

uniformM :: StatefulGen g m => g -> m (Sz ix) #

UniformRange ix => UniformRange (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

uniformRM :: StatefulGen g m => (Sz ix, Sz ix) -> g -> m (Sz ix) #

unSz :: Sz ix -> ix Source #

Function for unwrapping Sz.

Example

Expand
>>> import Data.Massiv.Core.Index
>>> unSz $ Sz3 1 2 3
1 :> 2 :. 3

Since: 0.3.0

zeroSz :: Index ix => Sz ix Source #

An empty size with all elements in size equal to 0.

Example

Expand
>>> import Data.Massiv.Core.Index
>>> zeroSz :: Sz5
Sz (0 :> 0 :> 0 :> 0 :. 0)

Since: 0.3.0

oneSz :: Index ix => Sz ix Source #

A singleton size with all elements in size equal to 1.

Example

Expand
>>> import Data.Massiv.Core.Index
>>> oneSz :: Sz3
Sz (1 :> 1 :. 1)

Since: 0.3.0

liftSz :: Index ix => (Int -> Int) -> Sz ix -> Sz ix Source #

Same as liftIndex, but for Sz

Example

Expand
>>> import Data.Massiv.Core.Index
>>> liftSz succ (Sz2 2 3)
Sz (3 :. 4)

Since: 0.4.0

liftSz2 :: Index ix => (Int -> Int -> Int) -> Sz ix -> Sz ix -> Sz ix Source #

Same as liftIndex2, but for Sz

Example

Expand
>>> import Data.Massiv.Core.Index
>>> liftSz2 (-) (Sz2 2 3) (Sz2 3 1)
Sz (0 :. 2)

Since: 0.4.3

consSz :: Index ix => Sz Ix1 -> Sz (Lower ix) -> Sz ix Source #

Same as consDim, but for Sz

Example

Expand
>>> import Data.Massiv.Core.Index
>>> consSz (Sz1 1) (Sz2 2 3) :: Sz3
Sz (1 :> 2 :. 3)

Since: 0.3.0

unconsSz :: Index ix => Sz ix -> (Sz Ix1, Sz (Lower ix)) Source #

Same as unconsDim, but for Sz

Example

Expand
>>> import Data.Massiv.Core.Index
>>> unconsSz $ Sz3 1 2 3
(Sz1 1,Sz (2 :. 3))

Since: 0.3.0

snocSz :: Index ix => Sz (Lower ix) -> Sz Ix1 -> Sz ix Source #

Same as snocDim, but for Sz

Example

Expand
>>> import Data.Massiv.Core.Index
>>> snocSz (Sz2 2 3) (Sz1 1) :: Sz3
Sz (2 :> 3 :. 1)

Since: 0.3.0

unsnocSz :: Index ix => Sz ix -> (Sz (Lower ix), Sz Ix1) Source #

Same as unsnocDim, but for Sz

Example

Expand
>>> import Data.Massiv.Core.Index
>>> unsnocSz $ Sz3 1 2 3
(Sz (1 :. 2),Sz1 3)

Since: 0.3.0

setSzM :: (MonadThrow m, Index ix) => Sz ix -> Dim -> Sz Int -> m (Sz ix) Source #

Same as setDimM, but for Sz

Example

Expand
>>> import Data.Massiv.Core.Index
>>> setSzM (Sz2 2 3) 2 (Sz1 1) :: IO Sz2
Sz (1 :. 3)
>>> setSzM (Sz2 2 3) 3 (Sz1 1) :: IO Sz2
*** Exception: IndexDimensionException: (Dim 3) for (2 :. 3)

Since: 0.3.0

insertSzM :: (MonadThrow m, Index ix) => Sz (Lower ix) -> Dim -> Sz Int -> m (Sz ix) Source #

Same as insertDimM, but for Sz

Example

Expand
>>> import Data.Massiv.Core.Index
>>> insertSzM (Sz2 2 3) 3 (Sz1 1) :: IO Sz3
Sz (1 :> 2 :. 3)
>>> insertSzM (Sz2 2 3) 4 (Sz1 1) :: IO Sz3
*** Exception: IndexDimensionException: (Dim 4) for (2 :. 3)

Since: 0.3.0

pullOutSzM :: (MonadThrow m, Index ix) => Sz ix -> Dim -> m (Sz Ix1, Sz (Lower ix)) Source #

Same as pullOutDim, but for Sz

>>> import Data.Massiv.Core.Index
>>> pullOutSzM (Sz3 1 2 3) 3
(Sz1 1,Sz (2 :. 3))
>>> pullOutSzM (Sz3 1 2 3) 0
*** Exception: IndexDimensionException: (Dim 0) for (1 :> 2 :. 3)

Since: 0.3.0

toLinearSz :: Index ix => Sz ix -> Sz1 Source #

Convert a size to a linear size.

Since: 0.5.8

mkSzM :: (Index ix, MonadThrow m) => ix -> m (Sz ix) Source #

Construct size from index while checking its correctness. Throws SizeNegativeException and SizeOverflowException.

Since: 0.6.0

Dimension

newtype Dim Source #

A way to select Array dimension at a value level.

Since: 0.1.0

Constructors

Dim 

Fields

Instances

Instances details
Enum Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

succ :: Dim -> Dim #

pred :: Dim -> Dim #

toEnum :: Int -> Dim #

fromEnum :: Dim -> Int #

enumFrom :: Dim -> [Dim] #

enumFromThen :: Dim -> Dim -> [Dim] #

enumFromTo :: Dim -> Dim -> [Dim] #

enumFromThenTo :: Dim -> Dim -> Dim -> [Dim] #

Eq Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

(==) :: Dim -> Dim -> Bool #

(/=) :: Dim -> Dim -> Bool #

Integral Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

quot :: Dim -> Dim -> Dim #

rem :: Dim -> Dim -> Dim #

div :: Dim -> Dim -> Dim #

mod :: Dim -> Dim -> Dim #

quotRem :: Dim -> Dim -> (Dim, Dim) #

divMod :: Dim -> Dim -> (Dim, Dim) #

toInteger :: Dim -> Integer #

Num Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

(+) :: Dim -> Dim -> Dim #

(-) :: Dim -> Dim -> Dim #

(*) :: Dim -> Dim -> Dim #

negate :: Dim -> Dim #

abs :: Dim -> Dim #

signum :: Dim -> Dim #

fromInteger :: Integer -> Dim #

Ord Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

compare :: Dim -> Dim -> Ordering #

(<) :: Dim -> Dim -> Bool #

(<=) :: Dim -> Dim -> Bool #

(>) :: Dim -> Dim -> Bool #

(>=) :: Dim -> Dim -> Bool #

max :: Dim -> Dim -> Dim #

min :: Dim -> Dim -> Dim #

Real Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

toRational :: Dim -> Rational #

Show Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

showsPrec :: Int -> Dim -> ShowS #

show :: Dim -> String #

showList :: [Dim] -> ShowS #

NFData Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

rnf :: Dim -> () #

Random Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

randomR :: RandomGen g => (Dim, Dim) -> g -> (Dim, g) #

random :: RandomGen g => g -> (Dim, g) #

randomRs :: RandomGen g => (Dim, Dim) -> g -> [Dim] #

randoms :: RandomGen g => g -> [Dim] #

Uniform Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

uniformM :: StatefulGen g m => g -> m Dim #

UniformRange Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

uniformRM :: StatefulGen g m => (Dim, Dim) -> g -> m Dim #

data Dimension (n :: Nat) where Source #

A way to select Array dimension at a type level.

Since: 0.2.4

Constructors

DimN :: (1 <= n, KnownNat n) => Dimension n 

Bundled Patterns

pattern Dim1 :: Dimension 1

Construct 1st dimension

Since: 0.2.4

pattern Dim2 :: Dimension 2

Construct 2nd dimension

Since: 0.2.4

pattern Dim3 :: Dimension 3

Construct 3rd dimension

Since: 0.2.4

pattern Dim4 :: Dimension 4

Construct 4th dimension

Since: 0.2.4

pattern Dim5 :: Dimension 5

Construct 5th dimension

Since: 0.2.4

type IsIndexDimension ix n = (1 <= n, n <= Dimensions ix, Index ix, KnownNat n) Source #

A type level constraint that ensures index is indeed valid and that supplied dimension can be safely used with it.

Since: 0.2.4

type family IsDimValid ix n :: Bool where ... Source #

Equations

IsDimValid ix n = ReportInvalidDim (Dimensions ix) n (1 <=? n) (n <=? Dimensions ix) 

type family ReportInvalidDim (dims :: Nat) (n :: Nat) isNotZero isLess :: Bool where ... Source #

Equations

ReportInvalidDim dims n True True = True 
ReportInvalidDim dims n True False = TypeError ((((Text "Dimension " :<>: ShowType n) :<>: Text " is higher than ") :<>: Text "the maximum expected ") :<>: ShowType dims) 
ReportInvalidDim dims n False isLess = TypeError (Text "Zero dimensional indices are not supported") 

Stride

data Stride ix where Source #

Stride provides a way to ignore elements of an array if an index is divisible by a corresponding value in a stride. So, for a Stride (i :. j) only elements with indices will be kept around:

( 0 :. 0) ( 0 :. j) ( 0 :. 2j) ( 0 :. 3j) ...
( i :. 0) ( i :. j) ( i :. 2j) ( i :. 3j) ...
(2i :. 0) (2i :. j) (2i :. 2j) (2i :. 3j) ...
...

Only positive strides make sense, so Stride pattern synonym constructor will prevent a user from creating a stride with negative or zero values, thus promoting safety of the library.

Examples:

Expand
  • Default and minimal stride of Stride (pureIndex 1) will have no affect and all elements will kept.
  • If stride is Stride 2, then every 2nd element (i.e. with index 1, 3, 5, ..) will be skipped and only elemnts with indices divisible by 2 will be kept around.
  • In case of two dimensions, if what you want is to keep all rows divisible by 5, but keep every column intact then you'd use Stride (5 :. 1).

Since: 0.2.1

Bundled Patterns

pattern Stride :: Index ix => ix -> Stride ix

A safe bidirectional pattern synonym for Stride construction that will make sure stride elements are always positive.

Since: 0.2.1

Instances

Instances details
Eq ix => Eq (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

(==) :: Stride ix -> Stride ix -> Bool #

(/=) :: Stride ix -> Stride ix -> Bool #

Ord ix => Ord (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

compare :: Stride ix -> Stride ix -> Ordering #

(<) :: Stride ix -> Stride ix -> Bool #

(<=) :: Stride ix -> Stride ix -> Bool #

(>) :: Stride ix -> Stride ix -> Bool #

(>=) :: Stride ix -> Stride ix -> Bool #

max :: Stride ix -> Stride ix -> Stride ix #

min :: Stride ix -> Stride ix -> Stride ix #

Index ix => Show (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

showsPrec :: Int -> Stride ix -> ShowS #

show :: Stride ix -> String #

showList :: [Stride ix] -> ShowS #

NFData ix => NFData (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

rnf :: Stride ix -> () #

(UniformRange ix, Index ix) => Random (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

randomR :: RandomGen g => (Stride ix, Stride ix) -> g -> (Stride ix, g) #

random :: RandomGen g => g -> (Stride ix, g) #

randomRs :: RandomGen g => (Stride ix, Stride ix) -> g -> [Stride ix] #

randoms :: RandomGen g => g -> [Stride ix] #

(UniformRange ix, Index ix) => Uniform (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

uniformM :: StatefulGen g m => g -> m (Stride ix) #

UniformRange ix => UniformRange (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

uniformRM :: StatefulGen g m => (Stride ix, Stride ix) -> g -> m (Stride ix) #

unStride :: Stride ix -> ix Source #

Just a helper function for unwrapping Stride.

Since: 0.2.1

toLinearIndexStride Source #

Arguments

:: Index ix 
=> Stride ix

Stride

-> Sz ix

Size

-> ix

Index

-> Int 

Compute linear index with stride using the original size and index

Since: 0.2.1

strideStart :: Index ix => Stride ix -> ix -> ix Source #

Adjust starting index according to the stride

Since: 0.2.1

strideSize :: Index ix => Stride ix -> Sz ix -> Sz ix Source #

Adjust size according to the stride.

Since: 0.2.1

oneStride :: Index ix => Stride ix Source #

A default stride of 1, where all elements are kept

Since: 0.2.1

Border

data Border e Source #

Approach to be used near the borders during various transformations. Whenever a function needs information not only about an element of interest, but also about it's neighbors, it will go out of bounds near the array edges, hence is this set of approaches that specify how to handle such situation.

Constructors

Fill e

Fill in a constant element.

           outside |  Array  | outside
(Fill 0) : 0 0 0 0 | 1 2 3 4 | 0 0 0 0
Wrap

Wrap around from the opposite border of the array.

           outside |  Array  | outside
Wrap :     1 2 3 4 | 1 2 3 4 | 1 2 3 4
Edge

Replicate the element at the edge.

           outside |  Array  | outside
Edge :     1 1 1 1 | 1 2 3 4 | 4 4 4 4
Reflect

Mirror like reflection.

           outside |  Array  | outside
Reflect :  4 3 2 1 | 1 2 3 4 | 4 3 2 1
Continue

Also mirror like reflection, but without repeating the edge element.

           outside |  Array  | outside
Continue : 1 4 3 2 | 1 2 3 4 | 3 2 1 4

Instances

Instances details
Eq e => Eq (Border e) Source # 
Instance details

Defined in Data.Massiv.Core.Index

Methods

(==) :: Border e -> Border e -> Bool #

(/=) :: Border e -> Border e -> Bool #

Show e => Show (Border e) Source # 
Instance details

Defined in Data.Massiv.Core.Index

Methods

showsPrec :: Int -> Border e -> ShowS #

show :: Border e -> String #

showList :: [Border e] -> ShowS #

NFData e => NFData (Border e) Source # 
Instance details

Defined in Data.Massiv.Core.Index

Methods

rnf :: Border e -> () #

handleBorderIndex Source #

Arguments

:: Index ix 
=> Border e

Broder resolution technique

-> Sz ix

Size

-> (ix -> e)

Index function that produces an element

-> ix

Index

-> e 

Apply a border resolution technique to an index

Examples

Expand
>>> handleBorderIndex (Fill 100) (Sz (2 :. 3)) id (2 :. 3)
100 :. 100
>>> handleBorderIndex Wrap (Sz (2 :. 3)) id (2 :. 3)
0 :. 0
>>> handleBorderIndex Edge (Sz (2 :. 3)) id (2 :. 3)
1 :. 2

Since: 0.1.0

Index functions

type family Lower ix :: Type Source #

This type family will always point to a type for a dimension that is one lower than the type argument.

Since: 0.1.0

Instances

Instances details
type Lower Int Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

type Lower Int = Ix0
type Lower Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

type Lower Ix2 = Ix1
type Lower Ix5T Source # 
Instance details

Defined in Data.Massiv.Core.Index.Tuple

type Lower Ix5T = Ix4T
type Lower Ix4T Source # 
Instance details

Defined in Data.Massiv.Core.Index.Tuple

type Lower Ix4T = Ix3T
type Lower Ix3T Source # 
Instance details

Defined in Data.Massiv.Core.Index.Tuple

type Lower Ix3T = Ix2T
type Lower Ix2T Source # 
Instance details

Defined in Data.Massiv.Core.Index.Tuple

type Lower Ix2T = Ix1T
type Lower (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

type Lower (IxN n) = Ix (n - 1)

class (Eq ix, Ord ix, Show ix, NFData ix, Typeable ix, Eq (Lower ix), Ord (Lower ix), Show (Lower ix), NFData (Lower ix), KnownNat (Dimensions ix)) => Index ix where Source #

This is bread and butter of multi-dimensional array indexing. It is unlikely that any of the functions in this class will be useful to a regular user, unless general algorithms are being implemented that do span multiple dimensions.

Associated Types

type Dimensions ix :: Nat Source #

Type level information on how many dimensions this index has.

Since: 0.2.0

Methods

dimensions :: proxy ix -> Dim Source #

What is the dimensionality of this index.

Since: 0.2.0

totalElem :: Sz ix -> Int Source #

Total number of elements in an array of this size.

Since: 0.1.0

consDim :: Int -> Lower ix -> ix Source #

Prepend a dimension to the index

Since: 0.1.0

unconsDim :: ix -> (Int, Lower ix) Source #

Take a dimension from the index from the outside

Since: 0.1.0

snocDim :: Lower ix -> Int -> ix Source #

Apppend a dimension to the index

Since: 0.1.0

unsnocDim :: ix -> (Lower ix, Int) Source #

Take a dimension from the index from the inside

Since: 0.1.0

pullOutDimM :: MonadThrow m => ix -> Dim -> m (Int, Lower ix) Source #

Pull out value at specified dimension from the index, thus also lowering it dimensionality.

Since: 0.2.5

insertDimM :: MonadThrow m => Lower ix -> Dim -> Int -> m ix Source #

Insert a dimension into the index

getDimM :: MonadThrow m => ix -> Dim -> m Int Source #

Extract the value index has at specified dimension.

Since: 0.3.0

setDimM :: MonadThrow m => ix -> Dim -> Int -> m ix Source #

Set the value for an index at specified dimension.

Since: 0.3.0

modifyDimM :: MonadThrow m => ix -> Dim -> (Int -> Int) -> m (Int, ix) Source #

Update the value for an index at specified dimension and return the old value as well as the updated index.

Since: 0.4.1

pureIndex :: Int -> ix Source #

Lift an Int to any index by replicating the value as many times as there are dimensions.

Since: 0.1.0

liftIndex2 :: (Int -> Int -> Int) -> ix -> ix -> ix Source #

Zip together two indices with a function

Since: 0.1.0

liftIndex :: (Int -> Int) -> ix -> ix Source #

Map a function over an index

Since: 0.1.0

foldlIndex :: (a -> Int -> a) -> a -> ix -> a Source #

Perform a left fold over the index

default foldlIndex :: Index (Lower ix) => (a -> Int -> a) -> a -> ix -> a Source #

isSafeIndex Source #

Arguments

:: Sz ix

Size

-> ix

Index

-> Bool 

Check whether index is positive and is within the size.

Since: 0.1.0

default isSafeIndex :: Index (Lower ix) => Sz ix -> ix -> Bool Source #

toLinearIndex Source #

Arguments

:: Sz ix

Size

-> ix

Index

-> Ix1 

Convert linear index from size and index

Since: 0.1.0

default toLinearIndex :: Index (Lower ix) => Sz ix -> ix -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> ix -> ix -> Ix1 Source #

Convert linear index from size and index with an accumulator. Currently is useless and will likely be removed in future versions.

Since: 0.1.0

default toLinearIndexAcc :: Index (Lower ix) => Ix1 -> ix -> ix -> Ix1 Source #

fromLinearIndex :: Sz ix -> Ix1 -> ix Source #

Compute an index from size and linear index

Since: 0.1.0

default fromLinearIndex :: Index (Lower ix) => Sz ix -> Ix1 -> ix Source #

fromLinearIndexAcc :: ix -> Ix1 -> (Int, ix) Source #

Compute an index from size and linear index using an accumulator, thus trying to optimize for tail recursion while getting the index computed.

Since: 0.1.0

default fromLinearIndexAcc :: Index (Lower ix) => ix -> Ix1 -> (Ix1, ix) Source #

repairIndex Source #

Arguments

:: Sz ix

Size

-> ix

Index

-> (Sz Int -> Int -> Int)

Repair when below zero

-> (Sz Int -> Int -> Int)

Repair when higher than size

-> ix 

A way to make sure index is withing the bounds for the supplied size. Takes two functions that will be invoked whenever index (2nd arg) is outsize the supplied size (1st arg)

Since: 0.1.0

default repairIndex :: Index (Lower ix) => Sz ix -> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix Source #

iterM Source #

Arguments

:: Monad m 
=> ix

Start index

-> ix

End index

-> ix

Increment

-> (Int -> Int -> Bool)

Continue iterating while predicate is True (eg. until end of row)

-> a

Initial value for an accumulator

-> (ix -> a -> m a)

Accumulator function

-> m a 

This function is what makes it possible to iterate over an array of any dimension.

Since: 0.1.0

default iterM :: (Index (Lower ix), Monad m) => ix -> ix -> ix -> (Int -> Int -> Bool) -> a -> (ix -> a -> m a) -> m a Source #

iterRowMajorST Source #

Arguments

:: Int

Scheduler multiplying factor. Must be positive

-> Scheduler s a

Scheduler to use

-> ix

Start index

-> ix

Stride

-> Sz ix

Size

-> a

Initial accumulator

-> (a -> ST s (a, a))

Function that splits accumulator for each scheduled job.

-> (ix -> a -> ST s a)

Action

-> ST s a 

default iterRowMajorST :: Index (Lower ix) => Int -> Scheduler s a -> ix -> ix -> Sz ix -> a -> (a -> ST s (a, a)) -> (ix -> a -> ST s a) -> ST s a Source #

iterF :: ix -> ix -> ix -> (Int -> Int -> Bool) -> f a -> (ix -> f a -> f a) -> f a Source #

Similar to iterM, but no restriction on a Monad.

Since: 1.0.2

default iterF :: Index (Lower ix) => ix -> ix -> ix -> (Int -> Int -> Bool) -> f a -> (ix -> f a -> f a) -> f a Source #

stepNextMF :: ix -> ix -> ix -> (Int -> Int -> Bool) -> (Maybe ix -> f a) -> f a Source #

A single step in iteration

Since: 0.1.0

default stepNextMF :: Index (Lower ix) => ix -> ix -> ix -> (Int -> Int -> Bool) -> (Maybe ix -> f a) -> f a Source #

iterTargetRowMajorA_ Source #

Arguments

:: Applicative f 
=> Int

Target linear index accumulator

-> Int

Target linear index start

-> Sz ix

Target size

-> ix

Source start index

-> ix

Source stride

-> (Ix1 -> ix -> f a)

Action that accepts a linear index of the target, multi-dimensional index of the source and accumulator

-> f () 

default iterTargetRowMajorA_ :: (Applicative f, Index (Lower ix)) => Int -> Int -> Sz ix -> ix -> ix -> (Ix1 -> ix -> f a) -> f () Source #

iterTargetRowMajorAccM Source #

Arguments

:: Monad m 
=> Int

Target linear index accumulator

-> Int

Target linear index start

-> Sz ix

Target size

-> ix

Source start index

-> ix

Source stride

-> a

Accumulator

-> (Ix1 -> ix -> a -> m a)

Action that accepts a linear index of the target, multi-dimensional index of the source and accumulator

-> m a 

default iterTargetRowMajorAccM :: (Monad m, Index (Lower ix)) => Int -> Int -> Sz ix -> ix -> ix -> a -> (Ix1 -> ix -> a -> m a) -> m a Source #

iterTargetRowMajorAccST Source #

Arguments

:: Int

Linear index accumulator

-> Int

Scheduler multiplying factor. Must be positive

-> Scheduler s a

Scheduler to use

-> Int

Target linear index start

-> Sz ix

Target size

-> ix

Source start index

-> ix

Source stride

-> a

Initial accumulator

-> (a -> ST s (a, a))

Function that splits accumulator for each scheduled job.

-> (Ix1 -> ix -> a -> ST s a)

Action

-> ST s a 

default iterTargetRowMajorAccST :: Index (Lower ix) => Int -> Int -> Scheduler s a -> Int -> Sz ix -> ix -> ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ Source #

Arguments

:: Int

Index accumulator

-> Int

Scheduler multiplying factor. Must be positive

-> Scheduler s ()

Scheduler to use

-> Int

Target linear start index

-> Sz ix

Target size

-> ix

Source start index

-> ix

Source stride

-> a

Initial accumulator

-> (a -> ST s (a, a))

Function that splits accumulator for each scheduled job.

-> (Ix1 -> ix -> a -> ST s a)

Action

-> ST s () 

default iterTargetRowMajorAccST_ :: Index (Lower ix) => Int -> Int -> Scheduler s () -> Int -> Sz ix -> ix -> ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

Instances

Instances details
Index Ix1 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Associated Types

type Dimensions Ix1 :: Nat Source #

Methods

dimensions :: proxy Ix1 -> Dim Source #

totalElem :: Sz Ix1 -> Int Source #

consDim :: Int -> Lower Ix1 -> Ix1 Source #

unconsDim :: Ix1 -> (Int, Lower Ix1) Source #

snocDim :: Lower Ix1 -> Int -> Ix1 Source #

unsnocDim :: Ix1 -> (Lower Ix1, Int) Source #

pullOutDimM :: MonadThrow m => Ix1 -> Dim -> m (Int, Lower Ix1) Source #

insertDimM :: MonadThrow m => Lower Ix1 -> Dim -> Int -> m Ix1 Source #

getDimM :: MonadThrow m => Ix1 -> Dim -> m Int Source #

setDimM :: MonadThrow m => Ix1 -> Dim -> Int -> m Ix1 Source #

modifyDimM :: MonadThrow m => Ix1 -> Dim -> (Int -> Int) -> m (Int, Ix1) Source #

pureIndex :: Int -> Ix1 Source #

liftIndex2 :: (Int -> Int -> Int) -> Ix1 -> Ix1 -> Ix1 Source #

liftIndex :: (Int -> Int) -> Ix1 -> Ix1 Source #

foldlIndex :: (a -> Int -> a) -> a -> Ix1 -> a Source #

isSafeIndex :: Sz Ix1 -> Ix1 -> Bool Source #

toLinearIndex :: Sz Ix1 -> Ix1 -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> Ix1 -> Ix1 -> Ix1 Source #

fromLinearIndex :: Sz Ix1 -> Ix1 -> Ix1 Source #

fromLinearIndexAcc :: Ix1 -> Ix1 -> (Int, Ix1) Source #

repairIndex :: Sz Ix1 -> Ix1 -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Ix1 Source #

iterM :: Monad m => Ix1 -> Ix1 -> Ix1 -> (Int -> Int -> Bool) -> a -> (Ix1 -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> Ix1 -> Ix1 -> Sz Ix1 -> a -> (a -> ST s (a, a)) -> (Ix1 -> a -> ST s a) -> ST s a Source #

iterF :: Ix1 -> Ix1 -> Ix1 -> (Int -> Int -> Bool) -> f a -> (Ix1 -> f a -> f a) -> f a Source #

stepNextMF :: Ix1 -> Ix1 -> Ix1 -> (Int -> Int -> Bool) -> (Maybe Ix1 -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz Ix1 -> Ix1 -> Ix1 -> (Ix1 -> Ix1 -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz Ix1 -> Ix1 -> Ix1 -> a -> (Ix1 -> Ix1 -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz Ix1 -> Ix1 -> Ix1 -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix1 -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz Ix1 -> Ix1 -> Ix1 -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix1 -> a -> ST s a) -> ST s () Source #

Index Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Associated Types

type Dimensions Ix2 :: Nat Source #

Methods

dimensions :: proxy Ix2 -> Dim Source #

totalElem :: Sz Ix2 -> Int Source #

consDim :: Int -> Lower Ix2 -> Ix2 Source #

unconsDim :: Ix2 -> (Int, Lower Ix2) Source #

snocDim :: Lower Ix2 -> Int -> Ix2 Source #

unsnocDim :: Ix2 -> (Lower Ix2, Int) Source #

pullOutDimM :: MonadThrow m => Ix2 -> Dim -> m (Int, Lower Ix2) Source #

insertDimM :: MonadThrow m => Lower Ix2 -> Dim -> Int -> m Ix2 Source #

getDimM :: MonadThrow m => Ix2 -> Dim -> m Int Source #

setDimM :: MonadThrow m => Ix2 -> Dim -> Int -> m Ix2 Source #

modifyDimM :: MonadThrow m => Ix2 -> Dim -> (Int -> Int) -> m (Int, Ix2) Source #

pureIndex :: Int -> Ix2 Source #

liftIndex2 :: (Int -> Int -> Int) -> Ix2 -> Ix2 -> Ix2 Source #

liftIndex :: (Int -> Int) -> Ix2 -> Ix2 Source #

foldlIndex :: (a -> Int -> a) -> a -> Ix2 -> a Source #

isSafeIndex :: Sz Ix2 -> Ix2 -> Bool Source #

toLinearIndex :: Sz Ix2 -> Ix2 -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> Ix2 -> Ix2 -> Ix1 Source #

fromLinearIndex :: Sz Ix2 -> Ix1 -> Ix2 Source #

fromLinearIndexAcc :: Ix2 -> Ix1 -> (Int, Ix2) Source #

repairIndex :: Sz Ix2 -> Ix2 -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Ix2 Source #

iterM :: Monad m => Ix2 -> Ix2 -> Ix2 -> (Int -> Int -> Bool) -> a -> (Ix2 -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> Ix2 -> Ix2 -> Sz Ix2 -> a -> (a -> ST s (a, a)) -> (Ix2 -> a -> ST s a) -> ST s a Source #

iterF :: Ix2 -> Ix2 -> Ix2 -> (Int -> Int -> Bool) -> f a -> (Ix2 -> f a -> f a) -> f a Source #

stepNextMF :: Ix2 -> Ix2 -> Ix2 -> (Int -> Int -> Bool) -> (Maybe Ix2 -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz Ix2 -> Ix2 -> Ix2 -> (Ix1 -> Ix2 -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz Ix2 -> Ix2 -> Ix2 -> a -> (Ix1 -> Ix2 -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz Ix2 -> Ix2 -> Ix2 -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix2 -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz Ix2 -> Ix2 -> Ix2 -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix2 -> a -> ST s a) -> ST s () Source #

Index Ix5T Source # 
Instance details

Defined in Data.Massiv.Core.Index.Tuple

Associated Types

type Dimensions Ix5T :: Nat Source #

Methods

dimensions :: proxy Ix5T -> Dim Source #

totalElem :: Sz Ix5T -> Int Source #

consDim :: Int -> Lower Ix5T -> Ix5T Source #

unconsDim :: Ix5T -> (Int, Lower Ix5T) Source #

snocDim :: Lower Ix5T -> Int -> Ix5T Source #

unsnocDim :: Ix5T -> (Lower Ix5T, Int) Source #

pullOutDimM :: MonadThrow m => Ix5T -> Dim -> m (Int, Lower Ix5T) Source #

insertDimM :: MonadThrow m => Lower Ix5T -> Dim -> Int -> m Ix5T Source #

getDimM :: MonadThrow m => Ix5T -> Dim -> m Int Source #

setDimM :: MonadThrow m => Ix5T -> Dim -> Int -> m Ix5T Source #

modifyDimM :: MonadThrow m => Ix5T -> Dim -> (Int -> Int) -> m (Int, Ix5T) Source #

pureIndex :: Int -> Ix5T Source #

liftIndex2 :: (Int -> Int -> Int) -> Ix5T -> Ix5T -> Ix5T Source #

liftIndex :: (Int -> Int) -> Ix5T -> Ix5T Source #

foldlIndex :: (a -> Int -> a) -> a -> Ix5T -> a Source #

isSafeIndex :: Sz Ix5T -> Ix5T -> Bool Source #

toLinearIndex :: Sz Ix5T -> Ix5T -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> Ix5T -> Ix5T -> Ix1 Source #

fromLinearIndex :: Sz Ix5T -> Ix1 -> Ix5T Source #

fromLinearIndexAcc :: Ix5T -> Ix1 -> (Int, Ix5T) Source #

repairIndex :: Sz Ix5T -> Ix5T -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Ix5T Source #

iterM :: Monad m => Ix5T -> Ix5T -> Ix5T -> (Int -> Int -> Bool) -> a -> (Ix5T -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> Ix5T -> Ix5T -> Sz Ix5T -> a -> (a -> ST s (a, a)) -> (Ix5T -> a -> ST s a) -> ST s a Source #

iterF :: Ix5T -> Ix5T -> Ix5T -> (Int -> Int -> Bool) -> f a -> (Ix5T -> f a -> f a) -> f a Source #

stepNextMF :: Ix5T -> Ix5T -> Ix5T -> (Int -> Int -> Bool) -> (Maybe Ix5T -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz Ix5T -> Ix5T -> Ix5T -> (Ix1 -> Ix5T -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz Ix5T -> Ix5T -> Ix5T -> a -> (Ix1 -> Ix5T -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz Ix5T -> Ix5T -> Ix5T -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix5T -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz Ix5T -> Ix5T -> Ix5T -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix5T -> a -> ST s a) -> ST s () Source #

Index Ix4T Source # 
Instance details

Defined in Data.Massiv.Core.Index.Tuple

Associated Types

type Dimensions Ix4T :: Nat Source #

Methods

dimensions :: proxy Ix4T -> Dim Source #

totalElem :: Sz Ix4T -> Int Source #

consDim :: Int -> Lower Ix4T -> Ix4T Source #

unconsDim :: Ix4T -> (Int, Lower Ix4T) Source #

snocDim :: Lower Ix4T -> Int -> Ix4T Source #

unsnocDim :: Ix4T -> (Lower Ix4T, Int) Source #

pullOutDimM :: MonadThrow m => Ix4T -> Dim -> m (Int, Lower Ix4T) Source #

insertDimM :: MonadThrow m => Lower Ix4T -> Dim -> Int -> m Ix4T Source #

getDimM :: MonadThrow m => Ix4T -> Dim -> m Int Source #

setDimM :: MonadThrow m => Ix4T -> Dim -> Int -> m Ix4T Source #

modifyDimM :: MonadThrow m => Ix4T -> Dim -> (Int -> Int) -> m (Int, Ix4T) Source #

pureIndex :: Int -> Ix4T Source #

liftIndex2 :: (Int -> Int -> Int) -> Ix4T -> Ix4T -> Ix4T Source #

liftIndex :: (Int -> Int) -> Ix4T -> Ix4T Source #

foldlIndex :: (a -> Int -> a) -> a -> Ix4T -> a Source #

isSafeIndex :: Sz Ix4T -> Ix4T -> Bool Source #

toLinearIndex :: Sz Ix4T -> Ix4T -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> Ix4T -> Ix4T -> Ix1 Source #

fromLinearIndex :: Sz Ix4T -> Ix1 -> Ix4T Source #

fromLinearIndexAcc :: Ix4T -> Ix1 -> (Int, Ix4T) Source #

repairIndex :: Sz Ix4T -> Ix4T -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Ix4T Source #

iterM :: Monad m => Ix4T -> Ix4T -> Ix4T -> (Int -> Int -> Bool) -> a -> (Ix4T -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> Ix4T -> Ix4T -> Sz Ix4T -> a -> (a -> ST s (a, a)) -> (Ix4T -> a -> ST s a) -> ST s a Source #

iterF :: Ix4T -> Ix4T -> Ix4T -> (Int -> Int -> Bool) -> f a -> (Ix4T -> f a -> f a) -> f a Source #

stepNextMF :: Ix4T -> Ix4T -> Ix4T -> (Int -> Int -> Bool) -> (Maybe Ix4T -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz Ix4T -> Ix4T -> Ix4T -> (Ix1 -> Ix4T -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz Ix4T -> Ix4T -> Ix4T -> a -> (Ix1 -> Ix4T -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz Ix4T -> Ix4T -> Ix4T -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix4T -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz Ix4T -> Ix4T -> Ix4T -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix4T -> a -> ST s a) -> ST s () Source #

Index Ix3T Source #

Since: 0.1.0

Instance details

Defined in Data.Massiv.Core.Index.Tuple

Associated Types

type Dimensions Ix3T :: Nat Source #

Methods

dimensions :: proxy Ix3T -> Dim Source #

totalElem :: Sz Ix3T -> Int Source #

consDim :: Int -> Lower Ix3T -> Ix3T Source #

unconsDim :: Ix3T -> (Int, Lower Ix3T) Source #

snocDim :: Lower Ix3T -> Int -> Ix3T Source #

unsnocDim :: Ix3T -> (Lower Ix3T, Int) Source #

pullOutDimM :: MonadThrow m => Ix3T -> Dim -> m (Int, Lower Ix3T) Source #

insertDimM :: MonadThrow m => Lower Ix3T -> Dim -> Int -> m Ix3T Source #

getDimM :: MonadThrow m => Ix3T -> Dim -> m Int Source #

setDimM :: MonadThrow m => Ix3T -> Dim -> Int -> m Ix3T Source #

modifyDimM :: MonadThrow m => Ix3T -> Dim -> (Int -> Int) -> m (Int, Ix3T) Source #

pureIndex :: Int -> Ix3T Source #

liftIndex2 :: (Int -> Int -> Int) -> Ix3T -> Ix3T -> Ix3T Source #

liftIndex :: (Int -> Int) -> Ix3T -> Ix3T Source #

foldlIndex :: (a -> Int -> a) -> a -> Ix3T -> a Source #

isSafeIndex :: Sz Ix3T -> Ix3T -> Bool Source #

toLinearIndex :: Sz Ix3T -> Ix3T -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> Ix3T -> Ix3T -> Ix1 Source #

fromLinearIndex :: Sz Ix3T -> Ix1 -> Ix3T Source #

fromLinearIndexAcc :: Ix3T -> Ix1 -> (Int, Ix3T) Source #

repairIndex :: Sz Ix3T -> Ix3T -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Ix3T Source #

iterM :: Monad m => Ix3T -> Ix3T -> Ix3T -> (Int -> Int -> Bool) -> a -> (Ix3T -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> Ix3T -> Ix3T -> Sz Ix3T -> a -> (a -> ST s (a, a)) -> (Ix3T -> a -> ST s a) -> ST s a Source #

iterF :: Ix3T -> Ix3T -> Ix3T -> (Int -> Int -> Bool) -> f a -> (Ix3T -> f a -> f a) -> f a Source #

stepNextMF :: Ix3T -> Ix3T -> Ix3T -> (Int -> Int -> Bool) -> (Maybe Ix3T -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz Ix3T -> Ix3T -> Ix3T -> (Ix1 -> Ix3T -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz Ix3T -> Ix3T -> Ix3T -> a -> (Ix1 -> Ix3T -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz Ix3T -> Ix3T -> Ix3T -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix3T -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz Ix3T -> Ix3T -> Ix3T -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix3T -> a -> ST s a) -> ST s () Source #

Index Ix2T Source #

Since: 0.1.0

Instance details

Defined in Data.Massiv.Core.Index.Tuple

Associated Types

type Dimensions Ix2T :: Nat Source #

Methods

dimensions :: proxy Ix2T -> Dim Source #

totalElem :: Sz Ix2T -> Int Source #

consDim :: Int -> Lower Ix2T -> Ix2T Source #

unconsDim :: Ix2T -> (Int, Lower Ix2T) Source #

snocDim :: Lower Ix2T -> Int -> Ix2T Source #

unsnocDim :: Ix2T -> (Lower Ix2T, Int) Source #

pullOutDimM :: MonadThrow m => Ix2T -> Dim -> m (Int, Lower Ix2T) Source #

insertDimM :: MonadThrow m => Lower Ix2T -> Dim -> Int -> m Ix2T Source #

getDimM :: MonadThrow m => Ix2T -> Dim -> m Int Source #

setDimM :: MonadThrow m => Ix2T -> Dim -> Int -> m Ix2T Source #

modifyDimM :: MonadThrow m => Ix2T -> Dim -> (Int -> Int) -> m (Int, Ix2T) Source #

pureIndex :: Int -> Ix2T Source #

liftIndex2 :: (Int -> Int -> Int) -> Ix2T -> Ix2T -> Ix2T Source #

liftIndex :: (Int -> Int) -> Ix2T -> Ix2T Source #

foldlIndex :: (a -> Int -> a) -> a -> Ix2T -> a Source #

isSafeIndex :: Sz Ix2T -> Ix2T -> Bool Source #

toLinearIndex :: Sz Ix2T -> Ix2T -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> Ix2T -> Ix2T -> Ix1 Source #

fromLinearIndex :: Sz Ix2T -> Ix1 -> Ix2T Source #

fromLinearIndexAcc :: Ix2T -> Ix1 -> (Int, Ix2T) Source #

repairIndex :: Sz Ix2T -> Ix2T -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> Ix2T Source #

iterM :: Monad m => Ix2T -> Ix2T -> Ix2T -> (Int -> Int -> Bool) -> a -> (Ix2T -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> Ix2T -> Ix2T -> Sz Ix2T -> a -> (a -> ST s (a, a)) -> (Ix2T -> a -> ST s a) -> ST s a Source #

iterF :: Ix2T -> Ix2T -> Ix2T -> (Int -> Int -> Bool) -> f a -> (Ix2T -> f a -> f a) -> f a Source #

stepNextMF :: Ix2T -> Ix2T -> Ix2T -> (Int -> Int -> Bool) -> (Maybe Ix2T -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz Ix2T -> Ix2T -> Ix2T -> (Ix1 -> Ix2T -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz Ix2T -> Ix2T -> Ix2T -> a -> (Ix1 -> Ix2T -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz Ix2T -> Ix2T -> Ix2T -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix2T -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz Ix2T -> Ix2T -> Ix2T -> a -> (a -> ST s (a, a)) -> (Ix1 -> Ix2T -> a -> ST s a) -> ST s () Source #

HighIxN n => Index (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Associated Types

type Dimensions (IxN n) :: Nat Source #

Methods

dimensions :: proxy (IxN n) -> Dim Source #

totalElem :: Sz (IxN n) -> Int Source #

consDim :: Int -> Lower (IxN n) -> IxN n Source #

unconsDim :: IxN n -> (Int, Lower (IxN n)) Source #

snocDim :: Lower (IxN n) -> Int -> IxN n Source #

unsnocDim :: IxN n -> (Lower (IxN n), Int) Source #

pullOutDimM :: MonadThrow m => IxN n -> Dim -> m (Int, Lower (IxN n)) Source #

insertDimM :: MonadThrow m => Lower (IxN n) -> Dim -> Int -> m (IxN n) Source #

getDimM :: MonadThrow m => IxN n -> Dim -> m Int Source #

setDimM :: MonadThrow m => IxN n -> Dim -> Int -> m (IxN n) Source #

modifyDimM :: MonadThrow m => IxN n -> Dim -> (Int -> Int) -> m (Int, IxN n) Source #

pureIndex :: Int -> IxN n Source #

liftIndex2 :: (Int -> Int -> Int) -> IxN n -> IxN n -> IxN n Source #

liftIndex :: (Int -> Int) -> IxN n -> IxN n Source #

foldlIndex :: (a -> Int -> a) -> a -> IxN n -> a Source #

isSafeIndex :: Sz (IxN n) -> IxN n -> Bool Source #

toLinearIndex :: Sz (IxN n) -> IxN n -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> IxN n -> IxN n -> Ix1 Source #

fromLinearIndex :: Sz (IxN n) -> Ix1 -> IxN n Source #

fromLinearIndexAcc :: IxN n -> Ix1 -> (Int, IxN n) Source #

repairIndex :: Sz (IxN n) -> IxN n -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> IxN n Source #

iterM :: Monad m => IxN n -> IxN n -> IxN n -> (Int -> Int -> Bool) -> a -> (IxN n -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> IxN n -> IxN n -> Sz (IxN n) -> a -> (a -> ST s (a, a)) -> (IxN n -> a -> ST s a) -> ST s a Source #

iterF :: IxN n -> IxN n -> IxN n -> (Int -> Int -> Bool) -> f a -> (IxN n -> f a -> f a) -> f a Source #

stepNextMF :: IxN n -> IxN n -> IxN n -> (Int -> Int -> Bool) -> (Maybe (IxN n) -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz (IxN n) -> IxN n -> IxN n -> (Ix1 -> IxN n -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz (IxN n) -> IxN n -> IxN n -> a -> (Ix1 -> IxN n -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz (IxN n) -> IxN n -> IxN n -> a -> (a -> ST s (a, a)) -> (Ix1 -> IxN n -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz (IxN n) -> IxN n -> IxN n -> a -> (a -> ST s (a, a)) -> (Ix1 -> IxN n -> a -> ST s a) -> ST s () Source #

Index (IxN 3) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Associated Types

type Dimensions (IxN 3) :: Nat Source #

Methods

dimensions :: proxy (IxN 3) -> Dim Source #

totalElem :: Sz (IxN 3) -> Int Source #

consDim :: Int -> Lower (IxN 3) -> IxN 3 Source #

unconsDim :: IxN 3 -> (Int, Lower (IxN 3)) Source #

snocDim :: Lower (IxN 3) -> Int -> IxN 3 Source #

unsnocDim :: IxN 3 -> (Lower (IxN 3), Int) Source #

pullOutDimM :: MonadThrow m => IxN 3 -> Dim -> m (Int, Lower (IxN 3)) Source #

insertDimM :: MonadThrow m => Lower (IxN 3) -> Dim -> Int -> m (IxN 3) Source #

getDimM :: MonadThrow m => IxN 3 -> Dim -> m Int Source #

setDimM :: MonadThrow m => IxN 3 -> Dim -> Int -> m (IxN 3) Source #

modifyDimM :: MonadThrow m => IxN 3 -> Dim -> (Int -> Int) -> m (Int, IxN 3) Source #

pureIndex :: Int -> IxN 3 Source #

liftIndex2 :: (Int -> Int -> Int) -> IxN 3 -> IxN 3 -> IxN 3 Source #

liftIndex :: (Int -> Int) -> IxN 3 -> IxN 3 Source #

foldlIndex :: (a -> Int -> a) -> a -> IxN 3 -> a Source #

isSafeIndex :: Sz (IxN 3) -> IxN 3 -> Bool Source #

toLinearIndex :: Sz (IxN 3) -> IxN 3 -> Ix1 Source #

toLinearIndexAcc :: Ix1 -> IxN 3 -> IxN 3 -> Ix1 Source #

fromLinearIndex :: Sz (IxN 3) -> Ix1 -> IxN 3 Source #

fromLinearIndexAcc :: IxN 3 -> Ix1 -> (Int, IxN 3) Source #

repairIndex :: Sz (IxN 3) -> IxN 3 -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> IxN 3 Source #

iterM :: Monad m => IxN 3 -> IxN 3 -> IxN 3 -> (Int -> Int -> Bool) -> a -> (IxN 3 -> a -> m a) -> m a Source #

iterRowMajorST :: Int -> Scheduler s a -> IxN 3 -> IxN 3 -> Sz (IxN 3) -> a -> (a -> ST s (a, a)) -> (IxN 3 -> a -> ST s a) -> ST s a Source #

iterF :: IxN 3 -> IxN 3 -> IxN 3 -> (Int -> Int -> Bool) -> f a -> (IxN 3 -> f a -> f a) -> f a Source #

stepNextMF :: IxN 3 -> IxN 3 -> IxN 3 -> (Int -> Int -> Bool) -> (Maybe (IxN 3) -> f a) -> f a Source #

iterTargetRowMajorA_ :: Applicative f => Int -> Int -> Sz (IxN 3) -> IxN 3 -> IxN 3 -> (Ix1 -> IxN 3 -> f a) -> f () Source #

iterTargetRowMajorAccM :: Monad m => Int -> Int -> Sz (IxN 3) -> IxN 3 -> IxN 3 -> a -> (Ix1 -> IxN 3 -> a -> m a) -> m a Source #

iterTargetRowMajorAccST :: Int -> Int -> Scheduler s a -> Int -> Sz (IxN 3) -> IxN 3 -> IxN 3 -> a -> (a -> ST s (a, a)) -> (Ix1 -> IxN 3 -> a -> ST s a) -> ST s a Source #

iterTargetRowMajorAccST_ :: Int -> Int -> Scheduler s () -> Int -> Sz (IxN 3) -> IxN 3 -> IxN 3 -> a -> (a -> ST s (a, a)) -> (Ix1 -> IxN 3 -> a -> ST s a) -> ST s () Source #

zeroIndex :: Index ix => ix Source #

Index with all zeros

Examples

Expand
>>> zeroIndex :: Ix4
0 :> 0 :> 0 :. 0

Since: 0.1.0

oneIndex :: Index ix => ix Source #

Index with all ones

Since: 0.3.0

isZeroSz :: Index ix => Sz ix -> Bool Source #

Checks whether size can hold at least one element.

Examples

Expand
>>> isZeroSz (Sz3 1 0 2)
True

Since: 1.0.0

isNotZeroSz :: Index ix => Sz ix -> Bool Source #

Checks whether size can hold at least one element.

Examples

Expand
>>> isNotZeroSz (Sz3 1 0 2)
False

Since: 1.0.0

headDim :: Index ix => ix -> Int Source #

Get the outmost dimension of the index.

Examples

Expand
>>> headDim (2 :> 3 :> 4 :. 5)
2

Since: 0.1.0

tailDim :: Index ix => ix -> Lower ix Source #

Drop the outmost dimension from the index

Examples

Expand
>>> tailDim (2 :> 3 :> 4 :. 5)
3 :> 4 :. 5

Since: 0.1.0

lastDim :: Index ix => ix -> Int Source #

Get the innermost dimension from the index

Examples

Expand
>>> lastDim (2 :> 3 :> 4 :. 5)
5

Since: 0.1.0

initDim :: Index ix => ix -> Lower ix Source #

Drop the innermost dimension from the index

Examples

Expand
>>> initDim (2 :> 3 :> 4 :. 5)
2 :> 3 :. 4

Since: 0.1.0

getDim' :: (HasCallStack, Index ix) => ix -> Dim -> Int Source #

Change the value from a specific dimension within the index. See getDimM for a safer version and getDimension for a type safe version.

Examples

Expand
>>> getDim' (2 :> 3 :> 4 :. 5) 3
3

Since: 0.2.4

setDim' :: (HasCallStack, Index ix) => ix -> Dim -> Int -> ix Source #

Change the value of a specific dimension within the index. See setDimM for a safer version and setDimension for a type safe version.

Examples

Expand
>>> setDim' (2 :> 3 :> 4 :. 5) 3 10
2 :> 10 :> 4 :. 5

Since: 0.2.4

modifyDim' :: (HasCallStack, Index ix) => ix -> Dim -> (Int -> Int) -> (Int, ix) Source #

Update the value of a specific dimension within the index. See modifyDimM for a safer version and modifyDimension for a type safe version.

Examples

Expand
>>> modifyDim' (2 :> 3 :> 4 :. 5) 2 (+ 10)
(4,2 :> 3 :> 14 :. 5)

Since: 0.4.1

dropDimM :: (MonadThrow m, Index ix) => ix -> Dim -> m (Lower ix) Source #

Remove a dimension from the index.

Examples

Expand
>>> dropDimM (2 :> 3 :> 4 :. 5) 3 :: Maybe Ix3
Just (2 :> 4 :. 5)
>>> dropDimM (2 :> 3 :> 4 :. 5) 6 :: Maybe Ix3
Nothing

Since: 0.3.0

dropDim' :: (HasCallStack, Index ix) => ix -> Dim -> Lower ix Source #

Remove a dimension from the index.

Examples

Expand
>>> dropDim' (2 :> 3 :> 4 :. 5) 3
2 :> 4 :. 5

Since: 0.2.4

pullOutDim' :: (HasCallStack, Index ix) => ix -> Dim -> (Int, Lower ix) Source #

Lower the dimension of the index by pulling the specified dimension. See pullOutDimM for a safer version and pullOutDimension for a type safe version.

Examples

Expand
>>> pullOutDim' (2 :> 3 :> 4 :. 5) 3
(3,2 :> 4 :. 5)

Since: 0.2.4

insertDim' :: (HasCallStack, Index ix) => Lower ix -> Dim -> Int -> ix Source #

Raise the dimension of the index by inserting one in the specified dimension. See insertDimM for a safer version and insertDimension for a type safe version.

Examples

Expand
>>> insertDim' (2 :> 3 :> 4 :. 5) 3 10 :: Ix5
2 :> 3 :> 10 :> 4 :. 5

Since: 0.2.4

fromDimension :: KnownNat n => Dimension n -> Dim Source #

Get the value level Dim from the type level equivalent.

Examples

Expand
>>> fromDimension Dim4
(Dim 4)
>>> :set -XDataKinds
>>> fromDimension (DimN :: Dimension 10)
(Dim 10)

Since: 0.2.4

getDimension :: IsIndexDimension ix n => ix -> Dimension n -> Int Source #

Type safe way to extract value of index at a particular dimension.

Examples

Expand
>>> getDimension (2 :> 3 :> 4 :. 5) Dim2
4

Since: 0.2.4

setDimension :: IsIndexDimension ix n => ix -> Dimension n -> Int -> ix Source #

Type safe way to set value of index at a particular dimension.

Examples

Expand
>>> setDimension (2 :> 3 :> 4 :. 5) Dim4 10
10 :> 3 :> 4 :. 5

Since: 0.2.4

modifyDimension :: IsIndexDimension ix n => ix -> Dimension n -> (Int -> Int) -> (Int, ix) Source #

Type safe way to set value of index at a particular dimension.

Examples

Expand
>>> modifyDimension (2 :> 3 :> 4 :. 5) Dim3 (+ 2)
(3,2 :> 5 :> 4 :. 5)

Since: 0.4.1

dropDimension :: IsIndexDimension ix n => ix -> Dimension n -> Lower ix Source #

Type safe way of dropping a particular dimension, thus lowering index dimensionality.

Examples

Expand
>>> dropDimension (2 :> 3 :> 4 :. 5) Dim2
2 :> 3 :. 5

Since: 0.2.4

pullOutDimension :: IsIndexDimension ix n => ix -> Dimension n -> (Int, Lower ix) Source #

Type safe way of pulling out a particular dimension, thus lowering index dimensionality and returning the value at specified dimension.

Examples

Expand
>>> pullOutDimension (2 :> 3 :> 4 :. 5) Dim2
(4,2 :> 3 :. 5)

Since: 0.2.4

insertDimension :: IsIndexDimension ix n => Lower ix -> Dimension n -> Int -> ix Source #

Type safe way of inserting a particular dimension, thus raising index dimensionality.

Examples

Expand
>>> insertDimension (2 :> 3 :> 4 :. 5) Dim5 10 :: Ix5
10 :> 2 :> 3 :> 4 :. 5
>>> insertDimension (2 :> 3 :> 4 :. 5) Dim4 10 :: Ix5
2 :> 10 :> 3 :> 4 :. 5
>>> insertDimension (2 :> 3 :> 4 :. 5) Dim3 10 :: Ix5
2 :> 3 :> 10 :> 4 :. 5
>>> insertDimension (2 :> 3 :> 4 :. 5) Dim2 10 :: Ix5
2 :> 3 :> 4 :> 10 :. 5
>>> insertDimension (2 :> 3 :> 4 :. 5) Dim1 10 :: Ix5
2 :> 3 :> 4 :> 5 :. 10

Since: 0.2.5

Iterators

iter Source #

Arguments

:: Index ix 
=> ix

Start index

-> ix

End index

-> ix

Increment

-> (Int -> Int -> Bool)

Continuation condition

-> a

Accumulator

-> (ix -> a -> a)

Iterating function

-> a 

Row-major iterator for the index. Same as iterM, but pure.

Examples

Expand
>>> iter (Ix1 0) 1000 1 (<) 0 (+)
499500
>>> iter (0 :. 0) (2 :. 3) oneIndex (<) 100 $ \ (i :. j) acc -> (acc + i) * (j + 1)
3615

Since: 0.1.0

iterA_ Source #

Arguments

:: forall ix f a. (Index ix, Applicative f) 
=> ix

Starting index

-> ix

Ending index (not included)

-> ix

Stepping index

-> (Int -> Int -> Bool)

Continuation function. Loop will stop on False

-> (ix -> f a)

Action applied to an index. Result is ignored.

-> f () 

Same as iterM, Iterate over a region with specific step, but using Applicative instead of a Monad and don't bother with accumulator or return value.

Since: 1.0.2

iterM_ :: (Index ix, Monad m) => ix -> ix -> ix -> (Int -> Int -> Bool) -> (ix -> m a) -> m () Source #

Deprecated: In favor of more lax iterA_

Same as iterM, but don't bother with accumulator and return value.

Since: 0.1.0

iterLinearM Source #

Arguments

:: (Index ix, Monad m) 
=> Sz ix

Size

-> Int

Linear start (must be non-negative)

-> Int

Linear end (must be less than or equal to totalElem sz)

-> Int

Increment (must not be zero)

-> (Int -> Int -> Bool)

Continuation condition (continue if True)

-> a

Accumulator

-> (Int -> ix -> a -> m a) 
-> m a 

Iterate over N-dimensional space linearly from start to end in row-major fashion with an accumulator

Examples

Expand
>>> sz = Sz2 3 4
>>> iterLinearM sz 0 3 1 (<) 100 $ \ k ix acc -> (acc + k) <$ print (fromLinearIndex sz k == ix)
True
True
True
103

Since: 0.1.0

iterLinearM_ Source #

Arguments

:: (Index ix, Monad m) 
=> Sz ix

Size

-> Int

Start (must be non-negative)

-> Int

End

-> Int

Increment (must not be zero)

-> (Int -> Int -> Bool)

Continuation condition (continue if True)

-> (Int -> ix -> m ())

Monadic action that takes index in both forms

-> m () 

Same as iterLinearM, except without an accumulator.

Examples

Expand
>>> sz = Sz2 3 4
>>> iterLinearM_ sz 0 3 1 (<) $ \ k ix -> print (toLinearIndex sz ix == k)
True
True
True

Since: 0.1.0

loop :: Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> a) -> a Source #

Efficient loop with an accumulator

Since: 0.1.0

loopF :: Int -> (Int -> Bool) -> (Int -> Int) -> f a -> (Int -> f a -> f a) -> f a Source #

nextMaybeF :: Int -> (Int -> Bool) -> (Int -> Int) -> (Maybe Int -> f a) -> f a Source #

loopA :: Applicative f => Int -> (Int -> Bool) -> (Int -> Int) -> f b -> (Int -> f (b -> b)) -> f b Source #

Applicative loop. Use monadic loopM when possible, since it will be more efficient.

Since: 0.3.0

loopA_ :: Applicative f => Int -> (Int -> Bool) -> (Int -> Int) -> (Int -> f a) -> f () Source #

Efficient Applicative loop. Result of each iteration is discarded.

loopA_ initial cond incr f === loopA initial cond incr (pure ()) (\i -> id <$ f i)

Since: 1.0.2

loopM :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a Source #

Efficient monadic loop with an accumulator

>>> loopM 1 (< 20) (+ 2) [] (\i a -> Just (i:a))
Just [19,17,15,13,11,9,7,5,3,1]

Since: 0.1.0

loopM_ :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> (Int -> m a) -> m () Source #

Deprecated: In favor of loopA_

Efficient monadic loop. Result of each iteration is discarded.

Since: 0.1.0

iloopM :: Monad m => Int -> Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> Int -> a -> m a) -> m a Source #

Efficient monadic loop with an accumulator and extra linear index incremented by 1.

>>> iloopM 100 1 (< 20) (+ 2) [] (\i ix a -> Just ((i, ix) : a))
Just [(109,19),(108,17),(107,15),(106,13),(105,11),(104,9),(103,7),(102,5),(101,3),(100,1)]

Since: 1.0.2

iloopA_ :: Applicative f => Int -> Int -> (Int -> Bool) -> (Int -> Int) -> (Int -> Int -> f a) -> f () Source #

Efficient monadic loop with extra linear index incremented by 1.

>>> iloopA_ 100 1 (< 10) (+ 2) (\i ix -> print (i, ix))
(100,1)
(101,3)
(102,5)
(103,7)
(104,9)

Since: 1.0.2

loopNextM :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> Int -> a -> m a) -> m a Source #

Similar to loopM_ except the action accepts not only the value for current step, but also for the next one as well.

Since: 1.0.2

loopNextA_ :: Applicative f => Int -> (Int -> Bool) -> (Int -> Int) -> (Int -> Int -> f a) -> f () Source #

Similar to loopM_ except the action accepts not only the value for current step, but also for the next one as well.

Since: 1.0.2

loopDeepM :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a Source #

Similar to loopM, but way less efficient monadic loop with an accumulator that reverses the direction of action application. eg:

>>> loopDeepM 1 (< 20) (+ 2) [] (\i a -> Just (i:a))
Just [1,3,5,7,9,11,13,15,17,19]

Equivalent to:

>>> loopM 19 (>= 1) (subtract 2) [] (\i a -> Just (i:a))
Just [1,3,5,7,9,11,13,15,17,19]

Since: 0.1.0

splitLinearly Source #

Arguments

:: Int

Number of chunks

-> Int

Total length

-> (Int -> Int -> a)

Function that accepts a chunk length and slack start index

-> a 

Divide length in chunks and apply a function to the computed results

Since: 0.2.1

splitLinearlyM :: MonadPrimBase s m => Scheduler s a -> Int -> (Int -> Int -> m a) -> m () Source #

Iterator that expects an action that accepts starting linear index as well as the ending

Since: 1.0.2

splitLinearlyM_ :: MonadPrimBase s m => Scheduler s () -> Int -> (Int -> Int -> m ()) -> m () Source #

Iterator that expects an action that accepts starting linear index as well as the ending

Since: 0.5.7

splitLinearlyWith_ :: MonadPrimBase s m => Scheduler s () -> Int -> (Int -> b) -> (Int -> b -> m ()) -> m () Source #

Iterator that can be used to split computation amongst different workers. For monadic generator see splitLinearlyWithM_.

Since: 0.2.1

splitLinearlyWithM_ :: MonadPrimBase s m => Scheduler s () -> Int -> (Int -> m b) -> (Int -> b -> m c) -> m () Source #

Iterator that can be used to split computation jobs

Since: 0.2.6

splitLinearlyWithStartAtM_ :: MonadPrimBase s m => Scheduler s () -> Int -> Int -> (Int -> m b) -> (Int -> b -> m c) -> m () Source #

Iterator that can be used to split computation jobs

Since: 0.3.0

splitLinearlyWithStatefulM_ Source #

Arguments

:: MonadUnliftIO m 
=> SchedulerWS ws () 
-> Int

Total linear length

-> (Int -> ws -> m b)

Element producing action

-> (Int -> b -> m c)

Element storing action

-> m () 

Iterator that can be used to split computation jobs, while using a stateful scheduler.

Since: 0.3.4

iterLinearST_ :: Int -> Scheduler s () -> Int -> Int -> Int -> (Int -> ST s a) -> ST s () Source #

Linear iterator that supports multiplying factor

Since: 1.0.2

iterLinearAccST_ :: Int -> Scheduler s () -> Int -> Int -> Int -> a -> (a -> ST s (a, a)) -> (Int -> a -> ST s a) -> ST s () Source #

Linear iterator that supports multiplying factor and accumulator, but the results are discarded.

Since: 1.0.2

iterLinearAccST Source #

Arguments

:: Int 
-> Scheduler s a 
-> Int 
-> Int

Step. Must be non-zero

-> Int 
-> a 
-> (a -> ST s (a, a)) 
-> (Int -> a -> ST s a) 
-> ST s a 

Linear iterator that supports multiplying factor and accumulator. Results of actions are stored in the scheduler.

Since: 1.0.2

splitNumChunks :: Int -> Int -> Int -> (Int, Int) Source #

Helper for figuring out the chunk length and slack start

stepStartAdjust :: Int -> Int -> Int Source #

Helper for adjusting stride of a chunk

Experimental

splitWorkWithFactorST Source #

Arguments

:: Int

Multiplying factor to be applied to number of workers for number of jobs to schedule. Higher the factor, more jobs will be scheduled. Only positive values are valid.

-> Scheduler s a 
-> Int

Starting index

-> Int

Stepping value. Can be negative, but must not be zero.

-> Int

Total number of steps to be taken

-> b

Initial value for an accumulator

-> (b -> ST s (b, b))

An action to split accumulator for multiple threads

-> (Int -> Int -> Int -> Int -> b -> ST s a)

A job to be scheduled. Accepts:

  • Chunk index start
  • Chunk length
  • Chunk start index adjusted for supplied start and stepping value
  • Chunk stop index adjusted for supplied start and stepping value
-> ST s b 

This is a major helper function for fair splitting and parallelization of work with ability to use some arbitrary accumulator and splittable seed

Since: 1.0.2

scheduleMassivWork :: PrimBase m => Scheduler (PrimState m) a -> m a -> m () Source #

Internal version of a scheduleWork that will be replaced by scheduleWork_ by the compiler whenever action produces ()

withMassivScheduler_ :: Comp -> (Scheduler RealWorld () -> IO ()) -> IO () Source #

Selects an optimal scheduler for the supplied strategy, but it works only in IO

Since: 1.0.0

class Iterator it where Source #

Methods

iterTargetA_ Source #

Arguments

:: (Index ix, Applicative f) 
=> it 
-> Int

Target linear index start

-> Sz ix

Target size

-> ix

Source start index

-> Stride ix

Source stride

-> (Ix1 -> ix -> f a)

Action that accepts a linear index of the target and multi-dimensional index of the source.

-> f () 

Iterate over a target region using linear index with access to the source index, which adjusted according to the stride. Use iterTargetM if you need an accumulator.

Since: 1.0.2

iterTargetM Source #

Arguments

:: (Index ix, Monad m) 
=> it 
-> Ix1

Target linear index start

-> Sz ix

Target size

-> ix

Source start index

-> Stride ix

Source stride

-> a

Accumulator

-> (Ix1 -> ix -> a -> m a)

Action that accepts a linear index of the target, multi-dimensional index of the source and accumulator

-> m a 

Iterate over a target region using linear index with access to the source index, which adjusted according to the stride.

Since: 1.0.2

iterTargetWithStrideAccST Source #

Arguments

:: Index ix 
=> it 
-> Scheduler s a

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> ix

Source start index

-> Stride ix

Source stride

-> a

Initial accumulator

-> (a -> ST s (a, a))

Splitting action that produces new accumulators for separate worker threads.

-> (Ix1 -> ix -> a -> ST s a)

Action

-> ST s a 

iterTargetWithStrideAccST_ Source #

Arguments

:: Index ix 
=> it 
-> Scheduler s ()

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> ix

Start

-> Stride ix

Stride

-> a

Initial accumulator

-> (a -> ST s (a, a))

Splitting action that produces new accumulators for separate worker threads.

-> (Ix1 -> ix -> a -> ST s a)

Action

-> ST s () 

iterFullM Source #

Arguments

:: (Index ix, Monad m) 
=> it 
-> ix

Source start index

-> Sz ix

Source size

-> a

Accumulator

-> (ix -> a -> m a)

Action that accepts a linear index of the target, multi-dimensional index of the source and accumulator

-> m a 

Iterate over a region with a monadic action and accumulator.

Since: 1.0.2

iterFullA_ Source #

Arguments

:: (Index ix, Applicative f) 
=> it 
-> ix

Source start index

-> Sz ix

Source size

-> (ix -> f a)

Action that accepts a linear index of the target, multi-dimensional index of the source and accumulator

-> f () 

Iterate over a region with an applicative action ignoring the result.

Since: 1.0.2

iterFullAccST Source #

Arguments

:: Index ix 
=> it

Scheduler multiplying factor. Must be positive

-> Scheduler s a

Scheduler to use

-> ix

Start index

-> Sz ix

Size

-> a

Initial accumulator

-> (a -> ST s (a, a))

Function that splits accumulator for each scheduled job.

-> (ix -> a -> ST s a)

Action

-> ST s a 

Iterate over a region in a ST monad with access to Scheduler.

iterTargetFullAccST Source #

Arguments

:: Index ix 
=> it 
-> Scheduler s a

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> a

Initial accumulator

-> (a -> ST s (a, a))

Function that splits accumulator for each scheduled job.

-> (Ix1 -> ix -> a -> ST s a)

Action

-> ST s a 

iterTargetFullAccST_ Source #

Arguments

:: Index ix 
=> it 
-> Scheduler s ()

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> a

Initial accumulator

-> (a -> ST s (a, a))

Function that splits accumulator for each scheduled job.

-> (Ix1 -> ix -> a -> ST s a)

Action

-> ST s () 

iterTargetFullST_ Source #

Arguments

:: Index ix 
=> it 
-> Scheduler s ()

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> (Ix1 -> ix -> ST s ())

Action

-> ST s () 

iterTargetWithStrideST_ Source #

Arguments

:: Index ix 
=> it 
-> Scheduler s ()

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> ix

Start

-> Stride ix

Stride

-> (Ix1 -> ix -> ST s a)

Action

-> ST s () 

Iterate over a target array with a stride without an accumulator

Instances

Instances details
Iterator RowMajorUnbalanced Source # 
Instance details

Defined in Data.Massiv.Core.Index.Iterator

Methods

iterTargetA_ :: (Index ix, Applicative f) => RowMajorUnbalanced -> Int -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> f a) -> f () Source #

iterTargetM :: (Index ix, Monad m) => RowMajorUnbalanced -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (Ix1 -> ix -> a -> m a) -> m a Source #

iterTargetWithStrideAccST :: Index ix => RowMajorUnbalanced -> Scheduler s a -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetWithStrideAccST_ :: Index ix => RowMajorUnbalanced -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterFullM :: (Index ix, Monad m) => RowMajorUnbalanced -> ix -> Sz ix -> a -> (ix -> a -> m a) -> m a Source #

iterFullA_ :: (Index ix, Applicative f) => RowMajorUnbalanced -> ix -> Sz ix -> (ix -> f a) -> f () Source #

iterFullAccST :: Index ix => RowMajorUnbalanced -> Scheduler s a -> ix -> Sz ix -> a -> (a -> ST s (a, a)) -> (ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST :: Index ix => RowMajorUnbalanced -> Scheduler s a -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST_ :: Index ix => RowMajorUnbalanced -> Scheduler s () -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterTargetFullST_ :: Index ix => RowMajorUnbalanced -> Scheduler s () -> Ix1 -> Sz ix -> (Ix1 -> ix -> ST s ()) -> ST s () Source #

iterTargetWithStrideST_ :: Index ix => RowMajorUnbalanced -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> ST s a) -> ST s () Source #

Iterator RowMajorLinear Source # 
Instance details

Defined in Data.Massiv.Core.Index.Iterator

Methods

iterTargetA_ :: (Index ix, Applicative f) => RowMajorLinear -> Int -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> f a) -> f () Source #

iterTargetM :: (Index ix, Monad m) => RowMajorLinear -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (Ix1 -> ix -> a -> m a) -> m a Source #

iterTargetWithStrideAccST :: Index ix => RowMajorLinear -> Scheduler s a -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetWithStrideAccST_ :: Index ix => RowMajorLinear -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterFullM :: (Index ix, Monad m) => RowMajorLinear -> ix -> Sz ix -> a -> (ix -> a -> m a) -> m a Source #

iterFullA_ :: (Index ix, Applicative f) => RowMajorLinear -> ix -> Sz ix -> (ix -> f a) -> f () Source #

iterFullAccST :: Index ix => RowMajorLinear -> Scheduler s a -> ix -> Sz ix -> a -> (a -> ST s (a, a)) -> (ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST :: Index ix => RowMajorLinear -> Scheduler s a -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST_ :: Index ix => RowMajorLinear -> Scheduler s () -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterTargetFullST_ :: Index ix => RowMajorLinear -> Scheduler s () -> Ix1 -> Sz ix -> (Ix1 -> ix -> ST s ()) -> ST s () Source #

iterTargetWithStrideST_ :: Index ix => RowMajorLinear -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> ST s a) -> ST s () Source #

Iterator RowMajor Source # 
Instance details

Defined in Data.Massiv.Core.Index.Iterator

Methods

iterTargetA_ :: (Index ix, Applicative f) => RowMajor -> Int -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> f a) -> f () Source #

iterTargetM :: (Index ix, Monad m) => RowMajor -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (Ix1 -> ix -> a -> m a) -> m a Source #

iterTargetWithStrideAccST :: Index ix => RowMajor -> Scheduler s a -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetWithStrideAccST_ :: Index ix => RowMajor -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterFullM :: (Index ix, Monad m) => RowMajor -> ix -> Sz ix -> a -> (ix -> a -> m a) -> m a Source #

iterFullA_ :: (Index ix, Applicative f) => RowMajor -> ix -> Sz ix -> (ix -> f a) -> f () Source #

iterFullAccST :: Index ix => RowMajor -> Scheduler s a -> ix -> Sz ix -> a -> (a -> ST s (a, a)) -> (ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST :: Index ix => RowMajor -> Scheduler s a -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST_ :: Index ix => RowMajor -> Scheduler s () -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterTargetFullST_ :: Index ix => RowMajor -> Scheduler s () -> Ix1 -> Sz ix -> (Ix1 -> ix -> ST s ()) -> ST s () Source #

iterTargetWithStrideST_ :: Index ix => RowMajor -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> ST s a) -> ST s () Source #

Extra iterator functions

iterTargetAccST Source #

Arguments

:: (Iterator it, Index ix) 
=> it 
-> Scheduler s a

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> ix

Source start

-> a 
-> (a -> ST s (a, a)) 
-> (Ix1 -> ix -> a -> ST s a)

Action

-> ST s a 

iterTargetAccST_ Source #

Arguments

:: (Iterator it, Index ix) 
=> it 
-> Scheduler s ()

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> ix

Source start

-> a 
-> (a -> ST s (a, a)) 
-> (Ix1 -> ix -> a -> ST s a)

Action

-> ST s () 

iterTargetFullWithStrideAccST Source #

Arguments

:: (Iterator it, Index ix) 
=> it 
-> Scheduler s a

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> Stride ix

Stride

-> a 
-> (a -> ST s (a, a)) 
-> (Ix1 -> ix -> a -> ST s a)

Action

-> ST s a 

iterTargetFullWithStrideAccST_ Source #

Arguments

:: (Iterator it, Index ix) 
=> it 
-> Scheduler s ()

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> Stride ix

Stride

-> a 
-> (a -> ST s (a, a)) 
-> (Ix1 -> ix -> a -> ST s a)

Action

-> ST s () 

iterTargetST_ Source #

Arguments

:: (Iterator it, Index ix) 
=> it 
-> Scheduler s ()

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> ix

Start

-> (Ix1 -> ix -> ST s ())

Action

-> ST s () 

iterTargetFullWithStrideST_ Source #

Arguments

:: (Iterator it, Index ix) 
=> it 
-> Scheduler s ()

Scheduler to use

-> Ix1

Target linear start index

-> Sz ix

Target size

-> Stride ix

Stride

-> (Ix1 -> ix -> ST s ())

Action

-> ST s () 

Iterator implementations

data RowMajor where Source #

Default iterator that parallelizes work in linear chunks. Supplied factor will be used to schedule that many jobs per capability.

Since: 1.0.2

Bundled Patterns

pattern RowMajor 

Fields

  • :: Int

    Multiplier that will be used to scale number of jobs.

  • -> RowMajor
     

Instances

Instances details
Iterator RowMajor Source # 
Instance details

Defined in Data.Massiv.Core.Index.Iterator

Methods

iterTargetA_ :: (Index ix, Applicative f) => RowMajor -> Int -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> f a) -> f () Source #

iterTargetM :: (Index ix, Monad m) => RowMajor -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (Ix1 -> ix -> a -> m a) -> m a Source #

iterTargetWithStrideAccST :: Index ix => RowMajor -> Scheduler s a -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetWithStrideAccST_ :: Index ix => RowMajor -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterFullM :: (Index ix, Monad m) => RowMajor -> ix -> Sz ix -> a -> (ix -> a -> m a) -> m a Source #

iterFullA_ :: (Index ix, Applicative f) => RowMajor -> ix -> Sz ix -> (ix -> f a) -> f () Source #

iterFullAccST :: Index ix => RowMajor -> Scheduler s a -> ix -> Sz ix -> a -> (a -> ST s (a, a)) -> (ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST :: Index ix => RowMajor -> Scheduler s a -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST_ :: Index ix => RowMajor -> Scheduler s () -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterTargetFullST_ :: Index ix => RowMajor -> Scheduler s () -> Ix1 -> Sz ix -> (Ix1 -> ix -> ST s ()) -> ST s () Source #

iterTargetWithStrideST_ :: Index ix => RowMajor -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> ST s a) -> ST s () Source #

defRowMajor :: RowMajor Source #

Default row major iterator with multiplying factor set to 8.

newtype RowMajorLinear Source #

Constructors

RowMajorLinear Int 

Instances

Instances details
Iterator RowMajorLinear Source # 
Instance details

Defined in Data.Massiv.Core.Index.Iterator

Methods

iterTargetA_ :: (Index ix, Applicative f) => RowMajorLinear -> Int -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> f a) -> f () Source #

iterTargetM :: (Index ix, Monad m) => RowMajorLinear -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (Ix1 -> ix -> a -> m a) -> m a Source #

iterTargetWithStrideAccST :: Index ix => RowMajorLinear -> Scheduler s a -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetWithStrideAccST_ :: Index ix => RowMajorLinear -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterFullM :: (Index ix, Monad m) => RowMajorLinear -> ix -> Sz ix -> a -> (ix -> a -> m a) -> m a Source #

iterFullA_ :: (Index ix, Applicative f) => RowMajorLinear -> ix -> Sz ix -> (ix -> f a) -> f () Source #

iterFullAccST :: Index ix => RowMajorLinear -> Scheduler s a -> ix -> Sz ix -> a -> (a -> ST s (a, a)) -> (ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST :: Index ix => RowMajorLinear -> Scheduler s a -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST_ :: Index ix => RowMajorLinear -> Scheduler s () -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterTargetFullST_ :: Index ix => RowMajorLinear -> Scheduler s () -> Ix1 -> Sz ix -> (Ix1 -> ix -> ST s ()) -> ST s () Source #

iterTargetWithStrideST_ :: Index ix => RowMajorLinear -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> ST s a) -> ST s () Source #

data RowMajorUnbalanced where Source #

Parallelizing unbalanced computation (i.e. computing some elements of the array is much more expensive then the others) it can be benefitial to interleave iteration. Perfect example of this would be a ray tracer or the Mandelbrot set.

iteration without parallelization is equivalent to RowMajor

Since: 1.0.2

Bundled Patterns

pattern RowMajorUnbalanced 

Fields

Instances

Instances details
Iterator RowMajorUnbalanced Source # 
Instance details

Defined in Data.Massiv.Core.Index.Iterator

Methods

iterTargetA_ :: (Index ix, Applicative f) => RowMajorUnbalanced -> Int -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> f a) -> f () Source #

iterTargetM :: (Index ix, Monad m) => RowMajorUnbalanced -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (Ix1 -> ix -> a -> m a) -> m a Source #

iterTargetWithStrideAccST :: Index ix => RowMajorUnbalanced -> Scheduler s a -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetWithStrideAccST_ :: Index ix => RowMajorUnbalanced -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterFullM :: (Index ix, Monad m) => RowMajorUnbalanced -> ix -> Sz ix -> a -> (ix -> a -> m a) -> m a Source #

iterFullA_ :: (Index ix, Applicative f) => RowMajorUnbalanced -> ix -> Sz ix -> (ix -> f a) -> f () Source #

iterFullAccST :: Index ix => RowMajorUnbalanced -> Scheduler s a -> ix -> Sz ix -> a -> (a -> ST s (a, a)) -> (ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST :: Index ix => RowMajorUnbalanced -> Scheduler s a -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s a Source #

iterTargetFullAccST_ :: Index ix => RowMajorUnbalanced -> Scheduler s () -> Ix1 -> Sz ix -> a -> (a -> ST s (a, a)) -> (Ix1 -> ix -> a -> ST s a) -> ST s () Source #

iterTargetFullST_ :: Index ix => RowMajorUnbalanced -> Scheduler s () -> Ix1 -> Sz ix -> (Ix1 -> ix -> ST s ()) -> ST s () Source #

iterTargetWithStrideST_ :: Index ix => RowMajorUnbalanced -> Scheduler s () -> Ix1 -> Sz ix -> ix -> Stride ix -> (Ix1 -> ix -> ST s a) -> ST s () Source #

Tuple based indices

1-dimensional

type Ix1T = Int Source #

Another 1-dimensional index type synonym for Int, same as Ix1 and is here just for consistency.

2-dimensional

type Ix2T = (Int, Int) Source #

2-dimensional index as tuple of Ints.

toIx2 :: Ix2T -> Ix2 Source #

Convert an Int tuple to Ix2

Example

Expand
>>> toIx2 (2, 3)
2 :. 3

Since: 0.1.0

fromIx2 :: Ix2 -> Ix2T Source #

Convert an Ix2 to Int tuple

Example

Expand
>>> fromIx2 (2 :. 3)
(2,3)

Since: 0.1.0

3-dimensional

type Ix3T = (Int, Int, Int) Source #

3-dimensional index as 3-tuple of Ints.

toIx3 :: Ix3T -> Ix3 Source #

Convert a Int 3-tuple to Ix3

Example

Expand
>>> toIx3 (1, 2, 3)
1 :> 2 :. 3

Since: 0.1.0

fromIx3 :: Ix3 -> Ix3T Source #

Convert an Ix3 to Int 3-tuple

Example

Expand
>>> fromIx3 (1 :>  2 :. 3)
(1,2,3)

Since: 0.1.0

4-dimensional

type Ix4T = (Int, Int, Int, Int) Source #

4-dimensional index as 4-tuple of Ints.

toIx4 :: Ix4T -> Ix4 Source #

Convert a Int 4-tuple to Ix4

Example

Expand
>>> toIx4 (1, 2, 3, 4)
1 :> 2 :> 3 :. 4

Since: 0.1.0

fromIx4 :: Ix4 -> Ix4T Source #

Convert an Ix4 to Int 4-tuple

Example

Expand
>>> fromIx4 (1 :> 2 :> 3 :. 4)
(1,2,3,4)

Since: 0.1.0

5-dimensional

type Ix5T = (Int, Int, Int, Int, Int) Source #

5-dimensional index as 5-tuple of Ints.

toIx5 :: Ix5T -> Ix5 Source #

Convert a Int 5-tuple to Ix5

Example

Expand
>>> toIx5 (1, 2, 3, 4, 5)
1 :> 2 :> 3 :> 4 :. 5

Since: 0.1.0

fromIx5 :: Ix5 -> Ix5T Source #

Convert an Ix5 to Int 5-tuple

Example

Expand
>>> fromIx5 (1 :> 2 :> 3 :> 4 :. 5)
(1,2,3,4,5)

Since: 0.1.0

Exceptions

data IndexException where Source #

Exceptions that get thrown when there is a problem with an index, size or dimension.

Since: 0.3.0

Constructors

IndexZeroException :: Index ix => !ix -> IndexException

Index contains a zero value along one of the dimensions.

IndexDimensionException :: (NFData ix, Eq ix, Show ix, Typeable ix) => !ix -> !Dim -> IndexException

Dimension is out of reach.

IndexOutOfBoundsException :: Index ix => !(Sz ix) -> !ix -> IndexException

Index is out of bounds.

data SizeException where Source #

Exception that indicates an issue with an array size.

Since: 0.3.0

Constructors

SizeMismatchException :: Index ix => !(Sz ix) -> !(Sz ix) -> SizeException

Two sizes are expected to be equal along some or all dimensions, but they are not.

SizeElementsMismatchException :: (Index ix, Index ix') => !(Sz ix) -> !(Sz ix') -> SizeException

Total number of elements does not match between the two sizes.

SizeSubregionException :: Index ix => !(Sz ix) -> !ix -> !(Sz ix) -> SizeException

Described subregion is too big for the specified size.

SizeEmptyException :: Index ix => !(Sz ix) -> SizeException

An array with the size cannot contain any elements.

SizeOverflowException :: Index ix => !(Sz ix) -> SizeException

Total number of elements is too large resulting in overflow.

Since: 0.6.0

SizeNegativeException :: Index ix => !(Sz ix) -> SizeException

At least one dimensions contain a negative value.

Since: 0.6.0

data ShapeException Source #

Exception that can happen upon conversion of a ragged type array into the rectangular kind. Which means conversion from lists is susceptible to this exception.

Since: 0.3.0

Constructors

DimTooShortException !Dim !(Sz Ix1) !(Sz Ix1)

Across a specific dimension there was not enough elements for the supplied size

DimTooLongException !Dim !(Sz Ix1) !(Sz Ix1)

Across a specific dimension there was too many elements for the supplied size

ShapeNonEmpty

Expected an empty size, but the shape was not empty.

guardNumberOfElements :: (MonadThrow m, Index ix, Index ix') => Sz ix -> Sz ix' -> m () Source #

Throw SizeElementsMismatchException whenever number of elements in both sizes do not match.

Since: 0.3.5

indexWith Source #

Arguments

:: Index ix 
=> String

Source file name, eg. FILE

-> Int

Line number in th source file, eg. LINE

-> String 
-> (arr -> Sz ix)

Get size of the array

-> (arr -> ix -> e)

Indexing function

-> arr

Array

-> ix

Index

-> e 

This is used by INDEX_CHECK macro and thus used whenever the unsafe-checks cabal flag is on.

Since: 0.4.0