massiv-0.3.2.0: Massiv (Массив) is an Array Library.

Copyright(c) Alexey Kuleshevich 2018-2019
LicenseBSD3
MaintainerAlexey Kuleshevich <alexey@kuleshevi.ch>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Massiv.Core.Index

Contents

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
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 TypeOperators extension isn't enabled, or simply infix notation is inconvenient. (Ix2 i j) == (i :. j).

Since: 0.1.0

Instances
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 #

NFData Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

rnf :: 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 #

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 -> Int Source #

toLinearIndexAcc :: Int -> Ix2 -> Ix2 -> Int Source #

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

fromLinearIndexAcc :: Ix2 -> Int -> (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 #

iterM_ :: Monad m => Ix2 -> Ix2 -> Ix2 -> (Int -> Int -> Bool) -> (Ix2 -> m a) -> m () 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

StrideLoad DW Ix2 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

loadArrayWithStrideM :: Monad m => Scheduler m () -> Stride Ix2 -> Sz Ix2 -> Array DW Ix2 e -> (Int -> e -> m ()) -> m () Source #

Load DW Ix2 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

getComp :: Array DW Ix2 e -> Comp Source #

size :: Array DW Ix2 e -> Sz Ix2 Source #

loadArrayM :: Monad m => Scheduler m () -> Array DW Ix2 e -> (Int -> e -> m ()) -> m () Source #

defaultElement :: Array DW Ix2 e -> Maybe e

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
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 :: PrimMonad m => Mutable Vector (PrimState m) (IxN n) -> m (Vector (IxN n)) #

basicUnsafeThaw :: PrimMonad m => Vector (IxN n) -> m (Mutable Vector (PrimState m) (IxN n)) #

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

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

basicUnsafeIndexM :: Monad m => Vector (IxN n) -> Int -> m (IxN n) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (IxN n) -> Vector (IxN n) -> m () #

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (IxN n)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (IxN n) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> IxN n -> m (MVector (PrimState m) (IxN n)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (IxN n) -> Int -> m (IxN n) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (IxN n) -> Int -> IxN n -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (IxN n) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (IxN n) -> IxN n -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (IxN n) -> MVector (PrimState m) (IxN n) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (IxN n) -> MVector (PrimState m) (IxN n) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (IxN n) -> Int -> m (MVector (PrimState m) (IxN n)) #

(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

loadArrayWithStrideM :: Monad m => Scheduler m () -> Stride (IxN n) -> Sz (IxN n) -> Array DW (IxN n) e -> (Int -> e -> m ()) -> m () 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

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

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

loadArrayM :: Monad m => Scheduler m () -> Array DW (IxN n) e -> (Int -> e -> m ()) -> m () Source #

defaultElement :: Array DW (IxN n) e -> Maybe e

(4 <= n, KnownNat n, Index (Ix (n - 1)), IxN (n - 1) ~ Ix (n - 1)) => 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 #

(4 <= n, KnownNat n, Index (Ix (n - 1)), IxN (n - 1) ~ Ix (n - 1)) => 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 #

NFData (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

Methods

rnf :: 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

(4 <= n, KnownNat n, Index (Ix (n - 1)), IxN (n - 1) ~ Ix (n - 1)) => 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 #

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 -> Int Source #

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

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

fromLinearIndexAcc :: IxN n -> Int -> (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 #

iterM_ :: Monad m => IxN n -> IxN n -> IxN n -> (Int -> Int -> Bool) -> (IxN n -> m a) -> m () 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 #

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 -> Int Source #

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

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

fromLinearIndexAcc :: IxN 3 -> Int -> (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 #

iterM_ :: Monad m => IxN 3 -> IxN 3 -> IxN 3 -> (Int -> Int -> Bool) -> (IxN 3 -> m a) -> m () 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 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 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 Sz construction that will make sure that none of the size elements are negative.

Since: 0.3.0

pattern Sz1 :: Ix1 -> Sz1

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

Since: 0.3.0

pattern Sz2 :: Int -> Int -> Sz2

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

Since: 0.3.0

pattern Sz3 :: Int -> Int -> Int -> Sz3

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

Since: 0.3.0

pattern Sz4 :: Int -> Int -> Int -> Int -> Sz4

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 -> Sz5

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

Since: 0.3.0

Instances
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 # 
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 -> () #

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

consSz :: Index ix => Sz1 -> 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 -> (Sz1, 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) -> Sz1 -> 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), Sz1) 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

newtype Dim Source #

A way to select Array dimension at a value level.

Since: 0.1.0

Constructors

Dim 

Fields

Instances
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 #

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 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 # 
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, Eq (Lower ix), Ord (Lower ix), Show (Lower ix), NFData (Lower 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.

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

isSafeIndex Source #

Arguments

:: Sz ix

Size

-> ix

Index

-> Bool 

Check whether index is positive and is within the size.

Since: 0.1.0

isSafeIndex Source #

Arguments

:: Index (Lower ix) 
=> Sz ix

Size

-> ix

Index

-> Bool 

Check whether index is positive and is within the size.

Since: 0.1.0

toLinearIndex Source #

Arguments

:: Sz ix

Size

-> ix

Index

-> Int 

Convert linear index from size and index

Since: 0.1.0

toLinearIndex Source #

Arguments

:: Index (Lower ix) 
=> Sz ix

Size

-> ix

Index

-> Int 

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

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

repairIndex Source #

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

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

iterM Source #

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
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 #

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 -> Int Source #

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

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

fromLinearIndexAcc :: Ix1 -> Int -> (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 #

iterM_ :: Monad m => Ix1 -> Ix1 -> Ix1 -> (Int -> Int -> Bool) -> (Ix1 -> m a) -> m () 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 #

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 -> Int Source #

toLinearIndexAcc :: Int -> Ix2 -> Ix2 -> Int Source #

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

fromLinearIndexAcc :: Ix2 -> Int -> (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 #

iterM_ :: Monad m => Ix2 -> Ix2 -> Ix2 -> (Int -> Int -> Bool) -> (Ix2 -> m a) -> m () 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 #

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 -> Int Source #

toLinearIndexAcc :: Int -> Ix5T -> Ix5T -> Int Source #

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

fromLinearIndexAcc :: Ix5T -> Int -> (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 #

iterM_ :: Monad m => Ix5T -> Ix5T -> Ix5T -> (Int -> Int -> Bool) -> (Ix5T -> m a) -> m () 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 #

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 -> Int Source #

toLinearIndexAcc :: Int -> Ix4T -> Ix4T -> Int Source #

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

fromLinearIndexAcc :: Ix4T -> Int -> (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 #

iterM_ :: Monad m => Ix4T -> Ix4T -> Ix4T -> (Int -> Int -> Bool) -> (Ix4T -> m a) -> m () 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 #

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 -> Int Source #

toLinearIndexAcc :: Int -> Ix3T -> Ix3T -> Int Source #

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

fromLinearIndexAcc :: Ix3T -> Int -> (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 #

iterM_ :: Monad m => Ix3T -> Ix3T -> Ix3T -> (Int -> Int -> Bool) -> (Ix3T -> m a) -> m () 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 #

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 -> Int Source #

toLinearIndexAcc :: Int -> Ix2T -> Ix2T -> Int Source #

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

fromLinearIndexAcc :: Ix2T -> Int -> (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 #

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

(4 <= n, KnownNat n, Index (Ix (n - 1)), IxN (n - 1) ~ Ix (n - 1)) => 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 #

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 -> Int Source #

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

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

fromLinearIndexAcc :: IxN n -> Int -> (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 #

iterM_ :: Monad m => IxN n -> IxN n -> IxN n -> (Int -> Int -> Bool) -> (IxN n -> m a) -> m () 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 #

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 -> Int Source #

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

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

fromLinearIndexAcc :: IxN 3 -> Int -> (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 #

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

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).

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.

Instances
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 -> () #

unStride :: Stride ix -> ix Source #

Just a helper function for unwrapping Stride.

toLinearIndexStride Source #

Arguments

:: Index ix 
=> Stride ix

Stride

-> Sz ix

Size

-> ix

Index

-> Int 

Compute an index with stride using the original size and index

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

Adjust starting index according to the stride

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

Adjust size according to the stride.

oneStride :: Index ix => Stride ix Source #

A default stride of 1, where all elements are kept

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
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

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

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

Checks whether array with this size can hold at least one element.

Examples

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

Since: 0.1.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' :: 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

Expand
>>> getDim' (2 :> 3 :> 4 :. 5) 3
3
>>> getDim' (2 :> 3 :> 4 :. 5) 0
*** Exception: IndexDimensionException: (Dim 0) for 3 :> 4 :. 5

Since: 0.2.4

getDim :: Index ix => ix -> Dim -> Maybe Int Source #

Deprecated: In favor of more general getDimM

See getDimM

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

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

Since: 0.2.4

setDim :: Index ix => ix -> Dim -> Int -> Maybe ix Source #

Deprecated: In favor of more general setDimM

See setDimM

Since: 0.2.4

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' :: Index ix => ix -> Dim -> Lower ix Source #

Remove a dimension from the index.

Examples

Expand
>>> dropDim' (2 :> 3 :> 4 :. 5) 3
2 :> 4 :. 5
>>> dropDim' (2 :> 3 :> 4 :. 5) 6
*** Exception: IndexDimensionException: (Dim 6) for 3 :> 4 :. 5

Since: 0.2.4

dropDim :: Index ix => ix -> Dim -> Maybe (Lower ix) Source #

Deprecated: In favor of more general dropDimM

See dropDimM

Since: 0.1.0

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

Expand

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

Since: 0.2.4

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

Deprecated: In favor of more general pullOutDimM

See pullOutDimM

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

Expand
>>> insertDim' (2 :> 3 :> 4 :. 5) 3 10 :: Ix5
2 :> 3 :> 10 :> 4 :. 5
>>> insertDim' (2 :> 3 :> 4 :. 5) 11 10 :: Ix5
*** Exception: IndexDimensionException: (Dim 11) for 4 :. 5

Since: 0.2.4

insertDim :: Index ix => Lower ix -> Dim -> Int -> Maybe ix Source #

Deprecated: In favor of more general insertDimM

See insertDimM

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

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 confition

-> 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

iterLinearM Source #

Arguments

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

Size

-> Int

Linear start

-> Int

Linear end

-> Int

Increment

-> (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 -> print (fromLinearIndex sz k == ix) >> pure (acc + k)
True
True
True
103

Since: 0.1.0

iterLinearM_ Source #

Arguments

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

Size

-> Int

Start

-> Int

End

-> Int

Increment

-> (Int -> Int -> Bool)

Continuation condition

-> (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

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

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

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

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 :: (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.

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