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

Copyright(c) Alexey Kuleshevich 2018
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Massiv.Core.Index

Description

 
Synopsis

Documentation

type Ix1 = Int Source #

Another type synonym for 1-dimensional index, i.e. Int and Ix1T. Provided here purely for consistency.

pattern Ix1 :: Int -> Ix1 Source #

This is a very handy pattern synonym to indicate that any arbitrary whole number is an Int, i.e. a 1-dimensional index: (Ix1 i) == (i :: Int)

data Ix2 Source #

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

Constructors

(:.) !Int !Int infixr 5 
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 :: Ix2 -> Dim Source #

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

dropDim :: Ix2 -> Dim -> Maybe (Lower Ix2) Source #

pullOutDim :: Ix2 -> Dim -> Maybe (Int, Lower Ix2) Source #

insertDim :: Lower Ix2 -> Dim -> Int -> Maybe Ix2 Source #

getDim :: Ix2 -> Dim -> Maybe Int Source #

setDim :: Ix2 -> Dim -> Int -> Maybe Ix2 Source #

getIndex :: Ix2 -> Dim -> Maybe Int Source #

setIndex :: Ix2 -> Dim -> Int -> Maybe 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 :: Ix2 -> Ix2 -> Bool Source #

toLinearIndex :: Ix2 -> Ix2 -> Int Source #

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

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

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

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

iter :: Ix2 -> Ix2 -> Ix2 -> (Int -> Int -> Bool) -> a -> (Ix2 -> a -> a) -> a 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

Load DW Ix2 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

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

loadP :: [Int] -> Array DW Ix2 e -> (Int -> IO e) -> (Int -> e -> IO ()) -> IO () Source #

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

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

data Vector Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

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
data MVector s Ix2 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

pattern Ix2 :: Int -> Int -> Ix2 Source #

2-dimensional index constructor. Useful when TypeOperators extension isn't enabled, or simply infix notation is inconvenient. (Ix2 i j) == (i :. j).

type Ix3 = IxN 3 Source #

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

pattern Ix3 :: Int -> Int -> Int -> Ix3 Source #

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

type Ix4 = IxN 4 Source #

4-dimensional type synonym.

pattern Ix4 :: Int -> Int -> Int -> Int -> Ix4 Source #

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

type Ix5 = IxN 5 Source #

5-dimensional type synonym.

pattern Ix5 :: Int -> Int -> Int -> Int -> Int -> Ix5 Source #

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

data IxN (n :: Nat) Source #

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

Constructors

(:>) !Int !(Ix (n - 1)) infixr 5 
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), Load DW (Ix (n - 1)) e) => Load DW (IxN n) e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

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

loadP :: [Int] -> Array DW (IxN n) e -> (Int -> IO e) -> (Int -> e -> IO ()) -> IO () Source #

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

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

(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 :: IxN n -> Dim Source #

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

dropDim :: IxN n -> Dim -> Maybe (Lower (IxN n)) Source #

pullOutDim :: IxN n -> Dim -> Maybe (Int, Lower (IxN n)) Source #

insertDim :: Lower (IxN n) -> Dim -> Int -> Maybe (IxN n) Source #

getDim :: IxN n -> Dim -> Maybe Int Source #

setDim :: IxN n -> Dim -> Int -> Maybe (IxN n) Source #

getIndex :: IxN n -> Dim -> Maybe Int Source #

setIndex :: IxN n -> Dim -> Int -> Maybe (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 :: IxN n -> IxN n -> Bool Source #

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

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

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

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

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

iter :: IxN n -> IxN n -> IxN n -> (Int -> Int -> Bool) -> a -> (IxN n -> a -> a) -> a 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 :: IxN 3 -> Dim Source #

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

dropDim :: IxN 3 -> Dim -> Maybe (Lower (IxN 3)) Source #

pullOutDim :: IxN 3 -> Dim -> Maybe (Int, Lower (IxN 3)) Source #

insertDim :: Lower (IxN 3) -> Dim -> Int -> Maybe (IxN 3) Source #

getDim :: IxN 3 -> Dim -> Maybe Int Source #

setDim :: IxN 3 -> Dim -> Int -> Maybe (IxN 3) Source #

getIndex :: IxN 3 -> Dim -> Maybe Int Source #

setIndex :: IxN 3 -> Dim -> Int -> Maybe (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 :: IxN 3 -> IxN 3 -> Bool Source #

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

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

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

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

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

iter :: IxN 3 -> IxN 3 -> IxN 3 -> (Int -> Int -> Bool) -> a -> (IxN 3 -> a -> a) -> a 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
data MVector s (IxN n) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Ix

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

Defined in Data.Massiv.Core.Index.Ix

data 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 family Ix (n :: Nat) = r | r -> n where ... Source #

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

Equations

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

toIx2 :: Ix2T -> Ix2 Source #

Convert a Int tuple to Ix2

fromIx2 :: Ix2 -> Ix2T Source #

Convert an Ix2 to Int tuple

toIx3 :: Ix3T -> Ix3 Source #

Convert a Int 3-tuple to Ix3

fromIx3 :: Ix3 -> Ix3T Source #

Convert an Ix3 to Int 3-tuple

toIx4 :: Ix4T -> Ix4 Source #

Convert a Int 4-tuple to Ix4

fromIx4 :: Ix4 -> Ix4T Source #

Convert an Ix4 to Int 4-tuple

toIx5 :: Ix5T -> Ix5 Source #

Convert a Int 5-tuple to Ix5

fromIx5 :: Ix5 -> Ix5T Source #

Convert an Ix5 to Int 5-tuple

data Stride ix 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).
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 -> () #

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

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

unStride :: Stride ix -> ix Source #

Just a helper function for unwrapping Stride.

toLinearIndexStride Source #

Arguments

:: Index ix 
=> Stride ix

Stride

-> 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 strating index according to the stride

strideSize :: Index ix => Stride ix -> ix -> 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

-> ix

Size

-> (ix -> e)

Index function that produces an element

-> ix

Index

-> e 

Apply a border resolution technique to an index

newtype Dim Source #

A way to select Array dimension at a value level.

Constructors

Dim Int 
Instances
Enum Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Class

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

Methods

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

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

Integral Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Class

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

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

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

Methods

toRational :: Dim -> Rational #

Show Dim Source # 
Instance details

Defined in Data.Massiv.Core.Index.Class

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.

Constructors

Dim1 :: Dimension 1 
Dim2 :: Dimension 2 
Dim3 :: Dimension 3 
Dim4 :: Dimension 4 
Dim5 :: Dimension 5 
DimN :: (6 <= n, KnownNat n) => Dimension n 

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.

data Ix0 Source #

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

Constructors

Ix0 
Instances
Eq Ix0 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Class

Methods

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

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

Ord Ix0 Source # 
Instance details

Defined in Data.Massiv.Core.Index.Class

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

Methods

showsPrec :: Int -> Ix0 -> ShowS #

show :: Ix0 -> String #

showList :: [Ix0] -> ShowS #

type Ix1T = Int Source #

1-dimensional index. Synonym for Int and Ix1.

type Ix2T = (Int, Int) Source #

2-dimensional index as tuple of Ints.

type Ix3T = (Int, Int, Int) Source #

3-dimensional index as 3-tuple of Ints.

type Ix4T = (Int, Int, Int, Int) Source #

4-dimensional index as 4-tuple of Ints.

type Ix5T = (Int, Int, Int, Int, Int) Source #

5-dimensional index as 5-tuple of Ints.

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.

Instances
type Lower Ix5T Source # 
Instance details

Defined in Data.Massiv.Core.Index.Class

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

Defined in Data.Massiv.Core.Index.Class

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

Defined in Data.Massiv.Core.Index.Class

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

Defined in Data.Massiv.Core.Index.Class

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

Defined in Data.Massiv.Core.Index.Class

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

Defined in Data.Massiv.Core.Index.Ix

type Lower Ix2 = Ix1
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) => 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 #

Methods

dimensions :: ix -> Dim Source #

Dimensions of an array that has this index type, i.e. what is the dimensionality.

totalElem :: ix -> Int Source #

Total number of elements in an array of this size.

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

Prepend a dimension to the index

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

Take a dimension from the index from the outside

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

Apppend a dimension to the index

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

Take a dimension from the index from the inside

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

Remove a dimension from the index

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

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

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

Insert a dimension into the index

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

Extract the value index has at specified dimension.

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

Set the value for an index at specified dimension.

getIndex :: ix -> Dim -> Maybe Int Source #

Extract the value index has at specified dimension. To be deprecated.

setIndex :: ix -> Dim -> Int -> Maybe ix Source #

Set the value for an index at specified dimension. To be deprecated.

pureIndex :: Int -> ix Source #

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

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

Zip together two indices with a function

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

Map a function over an index

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

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

isSafeIndex Source #

Arguments

:: ix

Size

-> ix

Index

-> Bool 

Check whether index is within the size.

isSafeIndex Source #

Arguments

:: Index (Lower ix) 
=> ix

Size

-> ix

Index

-> Bool 

Check whether index is within the size.

toLinearIndex Source #

Arguments

:: ix

Size

-> ix

Index

-> Int 

Convert linear index from size and index

toLinearIndex Source #

Arguments

:: Index (Lower ix) 
=> ix

Size

-> ix

Index

-> Int 

Convert linear index from size and index

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.

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.

fromLinearIndex :: ix -> Int -> ix Source #

Compute an index from size and linear index

fromLinearIndex :: Index (Lower ix) => ix -> Int -> ix Source #

Compute an index from size and linear index

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.

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.

repairIndex Source #

Arguments

:: ix

Size

-> ix

Index

-> (Int -> Int -> Int)

Repair when below zero

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

repairIndex Source #

Arguments

:: Index (Lower ix) 
=> ix

Size

-> ix

Index

-> (Int -> Int -> Int)

Repair when below zero

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

iter :: ix -> ix -> ix -> (Int -> Int -> Bool) -> a -> (ix -> a -> a) -> a Source #

Iterator for the index. Same as iterM, but pure.

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.

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.

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.

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.

Instances
Index Ix5T Source # 
Instance details

Defined in Data.Massiv.Core.Index.Class

Associated Types

type Dimensions Ix5T :: Nat Source #

Methods

dimensions :: Ix5T -> Dim Source #

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

dropDim :: Ix5T -> Dim -> Maybe (Lower Ix5T) Source #

pullOutDim :: Ix5T -> Dim -> Maybe (Int, Lower Ix5T) Source #

insertDim :: Lower Ix5T -> Dim -> Int -> Maybe Ix5T Source #

getDim :: Ix5T -> Dim -> Maybe Int Source #

setDim :: Ix5T -> Dim -> Int -> Maybe Ix5T Source #

getIndex :: Ix5T -> Dim -> Maybe Int Source #

setIndex :: Ix5T -> Dim -> Int -> Maybe 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 :: Ix5T -> Ix5T -> Bool Source #

toLinearIndex :: Ix5T -> Ix5T -> Int Source #

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

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

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

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

iter :: Ix5T -> Ix5T -> Ix5T -> (Int -> Int -> Bool) -> a -> (Ix5T -> a -> a) -> a 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.Class

Associated Types

type Dimensions Ix4T :: Nat Source #

Methods

dimensions :: Ix4T -> Dim Source #

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

dropDim :: Ix4T -> Dim -> Maybe (Lower Ix4T) Source #

pullOutDim :: Ix4T -> Dim -> Maybe (Int, Lower Ix4T) Source #

insertDim :: Lower Ix4T -> Dim -> Int -> Maybe Ix4T Source #

getDim :: Ix4T -> Dim -> Maybe Int Source #

setDim :: Ix4T -> Dim -> Int -> Maybe Ix4T Source #

getIndex :: Ix4T -> Dim -> Maybe Int Source #

setIndex :: Ix4T -> Dim -> Int -> Maybe 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 :: Ix4T -> Ix4T -> Bool Source #

toLinearIndex :: Ix4T -> Ix4T -> Int Source #

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

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

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

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

iter :: Ix4T -> Ix4T -> Ix4T -> (Int -> Int -> Bool) -> a -> (Ix4T -> a -> a) -> a 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 # 
Instance details

Defined in Data.Massiv.Core.Index.Class

Associated Types

type Dimensions Ix3T :: Nat Source #

Methods

dimensions :: Ix3T -> Dim Source #

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

dropDim :: Ix3T -> Dim -> Maybe (Lower Ix3T) Source #

pullOutDim :: Ix3T -> Dim -> Maybe (Int, Lower Ix3T) Source #

insertDim :: Lower Ix3T -> Dim -> Int -> Maybe Ix3T Source #

getDim :: Ix3T -> Dim -> Maybe Int Source #

setDim :: Ix3T -> Dim -> Int -> Maybe Ix3T Source #

getIndex :: Ix3T -> Dim -> Maybe Int Source #

setIndex :: Ix3T -> Dim -> Int -> Maybe 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 :: Ix3T -> Ix3T -> Bool Source #

toLinearIndex :: Ix3T -> Ix3T -> Int Source #

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

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

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

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

iter :: Ix3T -> Ix3T -> Ix3T -> (Int -> Int -> Bool) -> a -> (Ix3T -> a -> a) -> a 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 # 
Instance details

Defined in Data.Massiv.Core.Index.Class

Associated Types

type Dimensions Ix2T :: Nat Source #

Methods

dimensions :: Ix2T -> Dim Source #

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

dropDim :: Ix2T -> Dim -> Maybe (Lower Ix2T) Source #

pullOutDim :: Ix2T -> Dim -> Maybe (Int, Lower Ix2T) Source #

insertDim :: Lower Ix2T -> Dim -> Int -> Maybe Ix2T Source #

getDim :: Ix2T -> Dim -> Maybe Int Source #

setDim :: Ix2T -> Dim -> Int -> Maybe Ix2T Source #

getIndex :: Ix2T -> Dim -> Maybe Int Source #

setIndex :: Ix2T -> Dim -> Int -> Maybe 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 :: Ix2T -> Ix2T -> Bool Source #

toLinearIndex :: Ix2T -> Ix2T -> Int Source #

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

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

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

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

iter :: Ix2T -> Ix2T -> Ix2T -> (Int -> Int -> Bool) -> a -> (Ix2T -> a -> a) -> a 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 #

Index Ix1T Source # 
Instance details

Defined in Data.Massiv.Core.Index.Class

Associated Types

type Dimensions Ix1T :: Nat Source #

Methods

dimensions :: Ix1T -> Dim Source #

totalElem :: Ix1T -> Int Source #

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

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

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

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

dropDim :: Ix1T -> Dim -> Maybe (Lower Ix1T) Source #

pullOutDim :: Ix1T -> Dim -> Maybe (Int, Lower Ix1T) Source #

insertDim :: Lower Ix1T -> Dim -> Int -> Maybe Ix1T Source #

getDim :: Ix1T -> Dim -> Maybe Int Source #

setDim :: Ix1T -> Dim -> Int -> Maybe Ix1T Source #

getIndex :: Ix1T -> Dim -> Maybe Int Source #

setIndex :: Ix1T -> Dim -> Int -> Maybe Ix1T Source #

pureIndex :: Int -> Ix1T Source #

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

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

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

isSafeIndex :: Ix1T -> Ix1T -> Bool Source #

toLinearIndex :: Ix1T -> Ix1T -> Int Source #

toLinearIndexAcc :: Int -> Ix1T -> Ix1T -> Int Source #

fromLinearIndex :: Ix1T -> Int -> Ix1T Source #

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

repairIndex :: Ix1T -> Ix1T -> (Int -> Int -> Int) -> (Int -> Int -> Int) -> Ix1T Source #

iter :: Ix1T -> Ix1T -> Ix1T -> (Int -> Int -> Bool) -> a -> (Ix1T -> a -> a) -> a Source #

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

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

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

dropDim :: Ix2 -> Dim -> Maybe (Lower Ix2) Source #

pullOutDim :: Ix2 -> Dim -> Maybe (Int, Lower Ix2) Source #

insertDim :: Lower Ix2 -> Dim -> Int -> Maybe Ix2 Source #

getDim :: Ix2 -> Dim -> Maybe Int Source #

setDim :: Ix2 -> Dim -> Int -> Maybe Ix2 Source #

getIndex :: Ix2 -> Dim -> Maybe Int Source #

setIndex :: Ix2 -> Dim -> Int -> Maybe 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 :: Ix2 -> Ix2 -> Bool Source #

toLinearIndex :: Ix2 -> Ix2 -> Int Source #

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

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

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

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

iter :: Ix2 -> Ix2 -> Ix2 -> (Int -> Int -> Bool) -> a -> (Ix2 -> a -> a) -> a 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 #

(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 :: IxN n -> Dim Source #

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

dropDim :: IxN n -> Dim -> Maybe (Lower (IxN n)) Source #

pullOutDim :: IxN n -> Dim -> Maybe (Int, Lower (IxN n)) Source #

insertDim :: Lower (IxN n) -> Dim -> Int -> Maybe (IxN n) Source #

getDim :: IxN n -> Dim -> Maybe Int Source #

setDim :: IxN n -> Dim -> Int -> Maybe (IxN n) Source #

getIndex :: IxN n -> Dim -> Maybe Int Source #

setIndex :: IxN n -> Dim -> Int -> Maybe (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 :: IxN n -> IxN n -> Bool Source #

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

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

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

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

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

iter :: IxN n -> IxN n -> IxN n -> (Int -> Int -> Bool) -> a -> (IxN n -> a -> a) -> a 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 :: IxN 3 -> Dim Source #

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

dropDim :: IxN 3 -> Dim -> Maybe (Lower (IxN 3)) Source #

pullOutDim :: IxN 3 -> Dim -> Maybe (Int, Lower (IxN 3)) Source #

insertDim :: Lower (IxN 3) -> Dim -> Int -> Maybe (IxN 3) Source #

getDim :: IxN 3 -> Dim -> Maybe Int Source #

setDim :: IxN 3 -> Dim -> Int -> Maybe (IxN 3) Source #

getIndex :: IxN 3 -> Dim -> Maybe Int Source #

setIndex :: IxN 3 -> Dim -> Int -> Maybe (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 :: IxN 3 -> IxN 3 -> Bool Source #

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

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

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

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

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

iter :: IxN 3 -> IxN 3 -> IxN 3 -> (Int -> Int -> Bool) -> a -> (IxN 3 -> a -> a) -> a 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 #

errorIx :: (Show ix, Show ix') => String -> ix -> ix' -> a Source #

Helper function for throwing out of bounds errors

errorSizeMismatch :: (Show ix, Show ix') => String -> ix -> ix' -> a Source #

Helper function for throwing error when sizes do not match

zeroIndex :: Index ix => ix Source #

Index with all zeros

isSafeSize :: Index ix => ix -> Bool Source #

Checks whether the size is valid.

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

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

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

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

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

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

getIndex' :: Index ix => ix -> Dim -> Int Source #

To be deprecated in favor of getDim'.

setIndex' :: Index ix => ix -> Dim -> Int -> ix Source #

To be deprecated in favor of setDim'.

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

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

dropDim' :: Index ix => ix -> Dim -> Lower ix Source #

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

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

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

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

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.

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.

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.

Since: 0.2.4

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

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

Since: 0.2.4

iterLinearM Source #

Arguments

:: (Index ix, Monad m) 
=> 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 lenarly from start to end in row-major fashion with an accumulator

iterLinearM_ Source #

Arguments

:: (Index ix, Monad m) 
=> 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.

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

Efficient loop with an accumulator

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

Very efficient monadic loop with an accumulator

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

Efficient monadic loop. Result of each iteration is discarded.

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

Less efficient monadic loop with an accumulator that reverses the direction of action application

splitLinearly :: Int -> Int -> (Int -> Int -> a) -> a Source #

splitLinearlyWith_ :: Monad m => Int -> (m () -> m a) -> Int -> (Int -> b) -> (Int -> b -> m ()) -> m a Source #