| Copyright | (c) Alexey Kuleshevich 2018-2019 | 
|---|---|
| License | BSD3 | 
| Maintainer | Alexey Kuleshevich <alexey@kuleshevi.ch> | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Massiv.Core.Index
Contents
Description
Synopsis
- data Ix0 = Ix0
- type Ix1 = Int
- pattern Ix1 :: Int -> Ix1
- data Ix2 where
- data IxN (n :: Nat) where
- type Ix3 = IxN 3
- type Ix4 = IxN 4
- type Ix5 = IxN 5
- type family Ix (n :: Nat) = r | r -> n where ...
- type Sz1 = Sz Ix1
- type Sz2 = Sz Ix2
- type Sz3 = Sz Ix3
- type Sz4 = Sz Ix4
- type Sz5 = Sz Ix5
- data Sz ix where
- unSz :: Sz ix -> ix
- zeroSz :: Index ix => Sz ix
- oneSz :: Index ix => Sz ix
- liftSz :: Index ix => (Int -> Int) -> Sz ix -> Sz ix
- consSz :: Index ix => Sz1 -> Sz (Lower ix) -> Sz ix
- unconsSz :: Index ix => Sz ix -> (Sz1, Sz (Lower ix))
- snocSz :: Index ix => Sz (Lower ix) -> Sz1 -> Sz ix
- unsnocSz :: Index ix => Sz ix -> (Sz (Lower ix), Sz1)
- setSzM :: (MonadThrow m, Index ix) => Sz ix -> Dim -> Sz Int -> m (Sz ix)
- insertSzM :: (MonadThrow m, Index ix) => Sz (Lower ix) -> Dim -> Sz Int -> m (Sz ix)
- pullOutSzM :: (MonadThrow m, Index ix) => Sz ix -> Dim -> m (Sz Ix1, Sz (Lower ix))
- newtype Dim = Dim {}
- data Dimension (n :: Nat) where
- type IsIndexDimension ix n = (1 <= n, n <= Dimensions ix, Index ix, KnownNat n)
- data Stride ix where
- unStride :: Stride ix -> ix
- toLinearIndexStride :: Index ix => Stride ix -> Sz ix -> ix -> Int
- strideStart :: Index ix => Stride ix -> ix -> ix
- strideSize :: Index ix => Stride ix -> Sz ix -> Sz ix
- oneStride :: Index ix => Stride ix
- data Border e
- handleBorderIndex :: Index ix => Border e -> Sz ix -> (ix -> e) -> ix -> e
- type family Lower ix :: *
- class (Eq ix, Ord ix, Show ix, NFData ix, Eq (Lower ix), Ord (Lower ix), Show (Lower ix), NFData (Lower ix), 1 <= Dimensions ix, KnownNat (Dimensions ix)) => Index ix where- type Dimensions ix :: Nat
- dimensions :: proxy ix -> Dim
- totalElem :: Sz ix -> Int
- consDim :: Int -> Lower ix -> ix
- unconsDim :: ix -> (Int, Lower ix)
- snocDim :: Lower ix -> Int -> ix
- unsnocDim :: ix -> (Lower ix, Int)
- pullOutDimM :: MonadThrow m => ix -> Dim -> m (Int, Lower ix)
- insertDimM :: MonadThrow m => Lower ix -> Dim -> Int -> m ix
- getDimM :: MonadThrow m => ix -> Dim -> m Int
- setDimM :: MonadThrow m => ix -> Dim -> Int -> m ix
- pureIndex :: Int -> ix
- liftIndex2 :: (Int -> Int -> Int) -> ix -> ix -> ix
- liftIndex :: (Int -> Int) -> ix -> ix
- foldlIndex :: (a -> Int -> a) -> a -> ix -> a
- isSafeIndex :: Sz ix -> ix -> Bool
- toLinearIndex :: Sz ix -> ix -> Int
- toLinearIndexAcc :: Int -> ix -> ix -> Int
- fromLinearIndex :: Sz ix -> Int -> ix
- fromLinearIndexAcc :: ix -> Int -> (Int, ix)
- repairIndex :: Sz ix -> ix -> (Sz Int -> Int -> Int) -> (Sz Int -> Int -> Int) -> ix
- iterM :: Monad m => ix -> ix -> ix -> (Int -> Int -> Bool) -> a -> (ix -> a -> m a) -> m a
- iterM_ :: Monad m => ix -> ix -> ix -> (Int -> Int -> Bool) -> (ix -> m a) -> m ()
 
- zeroIndex :: Index ix => ix
- oneIndex :: Index ix => ix
- isNonEmpty :: Index ix => Sz ix -> Bool
- headDim :: Index ix => ix -> Int
- tailDim :: Index ix => ix -> Lower ix
- lastDim :: Index ix => ix -> Int
- initDim :: Index ix => ix -> Lower ix
- getDim' :: Index ix => ix -> Dim -> Int
- setDim' :: Index ix => ix -> Dim -> Int -> ix
- dropDimM :: (MonadThrow m, Index ix) => ix -> Dim -> m (Lower ix)
- dropDim' :: Index ix => ix -> Dim -> Lower ix
- pullOutDim' :: Index ix => ix -> Dim -> (Int, Lower ix)
- insertDim' :: Index ix => Lower ix -> Dim -> Int -> ix
- fromDimension :: KnownNat n => Dimension n -> Dim
- getDimension :: IsIndexDimension ix n => ix -> Dimension n -> Int
- setDimension :: IsIndexDimension ix n => ix -> Dimension n -> Int -> ix
- dropDimension :: IsIndexDimension ix n => ix -> Dimension n -> Lower ix
- pullOutDimension :: IsIndexDimension ix n => ix -> Dimension n -> (Int, Lower ix)
- insertDimension :: IsIndexDimension ix n => Lower ix -> Dimension n -> Int -> ix
- iter :: Index ix => ix -> ix -> ix -> (Int -> Int -> Bool) -> a -> (ix -> a -> a) -> a
- iterLinearM :: (Index ix, Monad m) => Sz ix -> Int -> Int -> Int -> (Int -> Int -> Bool) -> a -> (Int -> ix -> a -> m a) -> m a
- iterLinearM_ :: (Index ix, Monad m) => Sz ix -> Int -> Int -> Int -> (Int -> Int -> Bool) -> (Int -> ix -> m ()) -> m ()
- loop :: Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> a) -> a
- loopA_ :: Applicative f => Int -> (Int -> Bool) -> (Int -> Int) -> (Int -> f a) -> f ()
- loopM :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a
- loopM_ :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> (Int -> m a) -> m ()
- loopDeepM :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a
- splitLinearly :: Int -> Int -> (Int -> Int -> a) -> a
- splitLinearlyWith_ :: Monad m => Scheduler m () -> Int -> (Int -> b) -> (Int -> b -> m ()) -> m ()
- splitLinearlyWithM_ :: Monad m => Scheduler m () -> Int -> (Int -> m b) -> (Int -> b -> m c) -> m ()
- splitLinearlyWithStartAtM_ :: Monad m => Scheduler m () -> Int -> Int -> (Int -> m b) -> (Int -> b -> m c) -> m ()
- splitLinearlyWithStatefulM_ :: Monad m => SchedulerWS s m () -> Int -> (Int -> s -> m b) -> (Int -> b -> m c) -> m ()
- type Ix1T = Int
- type Ix2T = (Int, Int)
- toIx2 :: Ix2T -> Ix2
- fromIx2 :: Ix2 -> Ix2T
- type Ix3T = (Int, Int, Int)
- toIx3 :: Ix3T -> Ix3
- fromIx3 :: Ix3 -> Ix3T
- type Ix4T = (Int, Int, Int, Int)
- toIx4 :: Ix4T -> Ix4
- fromIx4 :: Ix4 -> Ix4T
- type Ix5T = (Int, Int, Int, Int, Int)
- toIx5 :: Ix5T -> Ix5
- fromIx5 :: Ix5 -> Ix5T
- data IndexException where- IndexZeroException :: Index ix => !ix -> IndexException
- IndexDimensionException :: (Show ix, Typeable ix) => !ix -> !Dim -> IndexException
- IndexOutOfBoundsException :: Index ix => !(Sz ix) -> !ix -> IndexException
 
- data SizeException where- SizeMismatchException :: Index ix => !(Sz ix) -> !(Sz ix) -> SizeException
- SizeElementsMismatchException :: (Index ix, Index ix') => !(Sz ix) -> !(Sz ix') -> SizeException
- SizeSubregionException :: Index ix => !(Sz ix) -> !ix -> !(Sz ix) -> SizeException
- SizeEmptyException :: Index ix => !(Sz ix) -> SizeException
 
- data ShapeException
- guardNumberOfElements :: (MonadThrow m, Index ix, Index ix') => Sz ix -> Sz ix' -> m ()
- indexWith :: Index ix => String -> Int -> String -> (arr -> Sz ix) -> (arr -> ix -> e) -> arr -> ix -> e
Documentation
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 | 
2-dimensional index. This is also a base index for higher dimensions.
Since: 0.1.0
Bundled Patterns
| pattern Ix2 :: Int -> Int -> Ix2 | 2-dimensional index constructor. Useful when infix notation is inconvenient.  Since: 0.1.0 | 
Instances
n-dimensional index. Needs a base case, which is the Ix2.
Since: 0.1.0
Bundled Patterns
| pattern Ix3 :: Int -> Int -> Int -> Ix3 | 3-dimensional index constructor.  Since: 0.1.0 | 
| pattern Ix4 :: Int -> Int -> Int -> Int -> Ix4 | 4-dimensional index constructor.  Since: 0.1.0 | 
| pattern Ix5 :: Int -> Int -> Int -> Int -> Int -> Ix5 | 5-dimensional index constructor.   Since: 0.1.0 | 
Instances
3-dimensional type synonym. Useful as a alternative to enabling DataKinds and using type
 level Nats.
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
Size
Sz provides type safety guarantees preventing mixup with index, which is used for looking into
 array cells, from the size, that describes total number of elements along each dimension in the
 array. Moreover the Sz constructor will prevent creation of invalid sizes with negative numbers.
Since: 0.3.0
Bundled Patterns
| pattern Sz :: Index ix => ix -> Sz ix | A safe bidirectional pattern synonym for  Since: 0.3.0 | 
| pattern Sz1 :: Ix1 -> Sz1 | 1-dimensional size constructor. Especially useful with literals:  Since: 0.3.0 | 
| pattern Sz2 :: Int -> Int -> Sz2 | 2-dimensional size constructor.  Since: 0.3.0 | 
| pattern Sz3 :: Int -> Int -> Int -> Sz3 | 3-dimensional size constructor.  Since: 0.3.0 | 
| pattern Sz4 :: Int -> Int -> Int -> Int -> Sz4 | 4-dimensional size constructor.  Since: 0.3.0 | 
| pattern Sz5 :: Int -> Int -> Int -> Int -> Int -> Sz5 | 5-dimensional size constructor.   Since: 0.3.0 | 
Function for unwrapping Sz.
Example
>>>import Data.Massiv.Core.Index>>>unSz $ Sz3 1 2 31 :> 2 :. 3
Since: 0.3.0
zeroSz :: Index ix => Sz ix Source #
An empty size with all elements in size equal to 0.
Example
>>>import Data.Massiv.Core.Index>>>zeroSz :: Sz5Sz (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
>>>import Data.Massiv.Core.Index>>>oneSz :: Sz3Sz (1 :> 1 :. 1)
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
>>>import Data.Massiv.Core.Index>>>insertSzM (Sz2 2 3) 3 (Sz1 1) :: IO Sz3Sz (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
Dimension
A way to select Array dimension at a value level.
Since: 0.1.0
data Dimension (n :: Nat) where Source #
A way to select Array dimension at a type level.
Since: 0.2.4
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
Stride
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:
- Default and minimal stride of Stride(pureIndex1)
- If stride is Stride2
- 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  Since: 0.2.1 | 
Instances
| Eq ix => Eq (Stride ix) Source # | |
| Ord ix => Ord (Stride ix) Source # | |
| Index ix => Show (Stride ix) Source # | |
| NFData ix => NFData (Stride ix) Source # | |
| Defined in Data.Massiv.Core.Index.Stride | |
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
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
( | 
| Wrap | Wrap around from the opposite border of the array.            outside |  Array  | outside
 | 
| Edge | Replicate the element at the edge.            outside |  Array  | outside
 | 
| Reflect | Mirror like reflection.            outside |  Array  | outside
 | 
| Continue | Also mirror like reflection, but without repeating the edge element.            outside |  Array  | outside
 | 
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
>>>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 :: * 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
| type Lower Int Source # | |
| Defined in Data.Massiv.Core.Index.Internal | |
| type Lower Ix2 Source # | |
| Defined in Data.Massiv.Core.Index.Ix | |
| type Lower Ix5T Source # | |
| Defined in Data.Massiv.Core.Index.Tuple | |
| type Lower Ix4T Source # | |
| Defined in Data.Massiv.Core.Index.Tuple | |
| type Lower Ix3T Source # | |
| Defined in Data.Massiv.Core.Index.Tuple | |
| type Lower Ix2T Source # | |
| Defined in Data.Massiv.Core.Index.Tuple | |
| type Lower (IxN n) Source # | |
| Defined in Data.Massiv.Core.Index.Ix | |
class (Eq ix, Ord ix, Show ix, NFData ix, Eq (Lower ix), Ord (Lower ix), Show (Lower ix), NFData (Lower ix), 1 <= Dimensions 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.
Minimal complete definition
dimensions, totalElem, consDim, unconsDim, snocDim, unsnocDim, pullOutDimM, insertDimM, getDimM, setDimM, pureIndex, liftIndex2
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.
setDimM :: MonadThrow m => ix -> Dim -> Int -> m ix Source #
Set the value for an index at specified dimension.
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
foldlIndex :: Index (Lower ix) => (a -> Int -> a) -> a -> ix -> a Source #
Perform a left fold over the index
Check whether index is positive and is within the size.
Since: 0.1.0
Check whether index is positive and is within the size.
Since: 0.1.0
Convert linear index from size and index
Since: 0.1.0
Convert linear index from size and index
Since: 0.1.0
toLinearIndexAcc :: Int -> ix -> ix -> Int Source #
Convert linear index from size and index with an accumulator. Currently is useless and will likley be removed in future versions.
Since: 0.1.0
toLinearIndexAcc :: Index (Lower ix) => Int -> ix -> ix -> Int Source #
Convert linear index from size and index with an accumulator. Currently is useless and will likley be removed in future versions.
Since: 0.1.0
fromLinearIndex :: Sz ix -> Int -> ix Source #
Compute an index from size and linear index
Since: 0.1.0
fromLinearIndex :: Index (Lower ix) => Sz ix -> Int -> ix Source #
Compute an index from size and linear index
Since: 0.1.0
fromLinearIndexAcc :: ix -> Int -> (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
fromLinearIndexAcc :: Index (Lower ix) => ix -> Int -> (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
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
Arguments
| :: Index (Lower ix) | |
| => 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
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
Arguments
| :: (Index (Lower ix), 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
iterM_ :: Monad m => ix -> ix -> ix -> (Int -> Int -> Bool) -> (ix -> m a) -> m () Source #
Same as iterM, but don't bother with accumulator and return value.
Since: 0.1.0
iterM_ :: (Index (Lower ix), Monad m) => ix -> ix -> ix -> (Int -> Int -> Bool) -> (ix -> m a) -> m () Source #
Same as iterM, but don't bother with accumulator and return value.
Since: 0.1.0
Instances
zeroIndex :: Index ix => ix Source #
Index with all zeros
Examples
>>>zeroIndex :: Ix40 :> 0 :> 0 :. 0
Since: 0.1.0
isNonEmpty :: Index ix => Sz ix -> Bool Source #
Checks whether array with this size can hold at least one element.
Examples
>>>isNonEmpty (Sz3 1 0 2)False
Since: 0.1.0
headDim :: Index ix => ix -> Int Source #
Get the outmost dimension of the index.
Examples
>>>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
>>>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
>>>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
>>>initDim (2 :> 3 :> 4 :. 5)2 :> 3 :. 4
Since: 0.1.0
getDim' :: Index ix => ix -> Dim -> Int Source #
Change the value from a specific dimension within the index. Throws IndexException. See
 getDimM for a safer version and getDimension for a type safe version.
Examples
>>>getDim' (2 :> 3 :> 4 :. 5) 33>>>getDim' (2 :> 3 :> 4 :. 5) 0*** Exception: IndexDimensionException: (Dim 0) for (2 :> 3 :> 4 :. 5)
Since: 0.2.4
setDim' :: Index ix => ix -> Dim -> Int -> ix Source #
Change the value of a specific dimension within the index. Throws IndexException. See
 setDimM for a safer version and setDimension for a type safe version.
Examples
>>>setDim' (2 :> 3 :> 4 :. 5) 3 102 :> 10 :> 4 :. 5
Since: 0.2.4
dropDimM :: (MonadThrow m, Index ix) => ix -> Dim -> m (Lower ix) Source #
Remove a dimension from the index.
Examples
λ> 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' :: Index ix => ix -> Dim -> Lower ix Source #
Remove a dimension from the index.
Examples
>>>dropDim' (2 :> 3 :> 4 :. 5) 32 :> 4 :. 5>>>dropDim' (2 :> 3 :> 4 :. 5) 6*** Exception: IndexDimensionException: (Dim 6) for (2 :> 3 :> 4 :. 5)
Since: 0.2.4
pullOutDim' :: Index ix => ix -> Dim -> (Int, Lower ix) Source #
Lower the dimension of the index by pulling the specified dimension. Throws IndexException. See
 pullOutDimM for a safer version and pullOutDimension for a type safe version.
Examples
λ> pullOutDim' (2 :> 3 :> 4 :. 5) 3 (3,2 :> 4 :. 5)
Since: 0.2.4
insertDim' :: Index ix => Lower ix -> Dim -> Int -> ix Source #
Raise the dimension of the index by inserting one in the specified dimension. Throws
 IndexException. See insertDimM for a safer version and insertDimension for a type safe
 version.
Examples
>>>insertDim' (2 :> 3 :> 4 :. 5) 3 10 :: Ix52 :> 3 :> 10 :> 4 :. 5>>>insertDim' (2 :> 3 :> 4 :. 5) 11 10 :: Ix5*** Exception: IndexDimensionException: (Dim 11) for (2 :> 3 :> 4 :. 5)
Since: 0.2.4
fromDimension :: KnownNat n => Dimension n -> Dim Source #
Get the value level Dim from the type level equivalent.
Examples
>>>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
>>>getDimension (2 :> 3 :> 4 :. 5) Dim24
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
>>>setDimension (2 :> 3 :> 4 :. 5) Dim4 1010 :> 3 :> 4 :. 5
Since: 0.2.4
dropDimension :: IsIndexDimension ix n => ix -> Dimension n -> Lower ix Source #
Type safe way of dropping a particular dimension, thus lowering index dimensionality.
Examples
>>>dropDimension (2 :> 3 :> 4 :. 5) Dim22 :> 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
>>>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
>>>insertDimension (2 :> 3 :> 4 :. 5) Dim5 10 :: Ix510 :> 2 :> 3 :> 4 :. 5>>>insertDimension (2 :> 3 :> 4 :. 5) Dim4 10 :: Ix52 :> 10 :> 3 :> 4 :. 5>>>insertDimension (2 :> 3 :> 4 :. 5) Dim3 10 :: Ix52 :> 3 :> 10 :> 4 :. 5>>>insertDimension (2 :> 3 :> 4 :. 5) Dim2 10 :: Ix52 :> 3 :> 4 :> 10 :. 5>>>insertDimension (2 :> 3 :> 4 :. 5) Dim1 10 :: Ix52 :> 3 :> 4 :> 5 :. 10
Since: 0.2.5
Iterators
Arguments
| :: Index ix | |
| => ix | Start index | 
| -> ix | End index | 
| -> ix | Increment | 
| -> (Int -> Int -> Bool) | Continuation confition | 
| -> a | Accumulator | 
| -> (ix -> a -> a) | Iterating function | 
| -> a | 
Row-major iterator for the index. Same as iterM, but pure.
Examples
>>>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
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  | 
| -> Int | Increment (must not be zero) | 
| -> (Int -> Int -> Bool) | Continuation condition (continue if  | 
| -> 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
>>>sz = Sz2 3 4>>>iterLinearM sz 0 3 1 (<) 100 $ \ k ix acc -> print (fromLinearIndex sz k == ix) >> pure (acc + k)True True True 103
Since: 0.1.0
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  | 
| -> (Int -> ix -> m ()) | Monadic action that takes index in both forms | 
| -> m () | 
Same as iterLinearM, except without an accumulator.
Examples
>>>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
loopA_ :: Applicative f => Int -> (Int -> Bool) -> (Int -> Int) -> (Int -> f a) -> f () Source #
Efficient Applicative loop. Result of each iteration is discarded.
Since: 0.3.0
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 #
Efficient monadic loop. Result of each iteration is discarded.
Since: 0.1.0
loopDeepM :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a Source #
Similar to loopM, but slightly 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
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
splitLinearlyWith_ :: Monad m => Scheduler m () -> Int -> (Int -> b) -> (Int -> b -> m ()) -> m () Source #
Interator that can be used to split computation amongst different workers. For monadic
 generator see splitLinearlyWithM_.
Since: 0.2.1
splitLinearlyWithM_ :: Monad m => Scheduler m () -> Int -> (Int -> m b) -> (Int -> b -> m c) -> m () Source #
Interator that can be used to split computation jobs
Since: 0.2.6
splitLinearlyWithStartAtM_ :: Monad m => Scheduler m () -> Int -> Int -> (Int -> m b) -> (Int -> b -> m c) -> m () Source #
Interator that can be used to split computation jobs
Since: 0.3.0
splitLinearlyWithStatefulM_ Source #
Arguments
| :: Monad m | |
| => SchedulerWS s m () | |
| -> Int | Total linear length | 
| -> (Int -> s -> m b) | Element producing action | 
| -> (Int -> b -> m c) | Element storing action | 
| -> m () | 
Interator that can be used to split computation jobs, while using a stateful scheduler.
Since: 0.3.4
Tuple based indices
1-dimensional
2-dimensional
3-dimensional
4-dimensional
5-dimensional
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 :: (Show ix, Typeable ix) => !ix -> !Dim -> IndexException | Dimension is out of reach. | 
| IndexOutOfBoundsException :: Index ix => !(Sz ix) -> !ix -> IndexException | Index is out of bounds. | 
Instances
| Eq IndexException Source # | |
| Defined in Data.Massiv.Core.Index.Internal Methods (==) :: IndexException -> IndexException -> Bool # (/=) :: IndexException -> IndexException -> Bool # | |
| Show IndexException Source # | |
| Defined in Data.Massiv.Core.Index.Internal Methods showsPrec :: Int -> IndexException -> ShowS # show :: IndexException -> String # showList :: [IndexException] -> ShowS # | |
| Exception IndexException Source # | |
| Defined in Data.Massiv.Core.Index.Internal Methods toException :: IndexException -> SomeException # | |
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. | 
Instances
| Eq SizeException Source # | |
| Defined in Data.Massiv.Core.Index.Internal Methods (==) :: SizeException -> SizeException -> Bool # (/=) :: SizeException -> SizeException -> Bool # | |
| Show SizeException Source # | |
| Defined in Data.Massiv.Core.Index.Internal Methods showsPrec :: Int -> SizeException -> ShowS # show :: SizeException -> String # showList :: [SizeException] -> ShowS # | |
| Exception SizeException Source # | |
| Defined in Data.Massiv.Core.Index.Internal Methods toException :: SizeException -> SomeException # fromException :: SomeException -> Maybe SizeException # displayException :: SizeException -> String # | |
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 !Sz1 !Sz1 | |
| DimTooLongException | 
Instances
| Eq ShapeException Source # | |
| Defined in Data.Massiv.Core.Index.Internal Methods (==) :: ShapeException -> ShapeException -> Bool # (/=) :: ShapeException -> ShapeException -> Bool # | |
| Show ShapeException Source # | |
| Defined in Data.Massiv.Core.Index.Internal Methods showsPrec :: Int -> ShapeException -> ShowS # show :: ShapeException -> String # showList :: [ShapeException] -> ShowS # | |
| Exception ShapeException Source # | |
| Defined in Data.Massiv.Core.Index.Internal Methods toException :: ShapeException -> SomeException # | |
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
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