Copyright | (c) Alexey Kuleshevich 2018 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- type Ix1 = Int
- pattern Ix1 :: Int -> Ix1
- data Ix2 = (:.) !Int !Int
- pattern Ix2 :: Int -> Int -> Ix2
- type Ix3 = IxN 3
- pattern Ix3 :: Int -> Int -> Int -> Ix3
- type Ix4 = IxN 4
- pattern Ix4 :: Int -> Int -> Int -> Int -> Ix4
- type Ix5 = IxN 5
- pattern Ix5 :: Int -> Int -> Int -> Int -> Int -> Ix5
- data IxN (n :: Nat) where
- type family Ix (n :: Nat) = r | r -> n where ...
- toIx2 :: Ix2T -> Ix2
- fromIx2 :: Ix2 -> Ix2T
- toIx3 :: Ix3T -> Ix3
- fromIx3 :: Ix3 -> Ix3T
- toIx4 :: Ix4T -> Ix4
- fromIx4 :: Ix4 -> Ix4T
- toIx5 :: Ix5T -> Ix5
- fromIx5 :: Ix5 -> Ix5T
- data Border e
- handleBorderIndex :: Index ix => Border e -> ix -> (ix -> e) -> ix -> e
- newtype Dim = Dim Int
- data Ix0 = Ix0
- type Ix1T = Int
- type Ix2T = (Int, Int)
- type Ix3T = (Int, Int, Int)
- type Ix4T = (Int, Int, Int, Int)
- type Ix5T = (Int, Int, Int, Int, Int)
- type family Lower ix :: *
- class (Eq ix, Ord ix, Show ix, NFData ix) => Index ix where
- errorIx :: (Show ix, Show ix') => String -> ix -> ix' -> a
- errorSizeMismatch :: (Show ix, Show ix') => String -> ix -> ix' -> a
- isSafeSize :: Index ix => ix -> Bool
- isNonEmpty :: Index ix => ix -> Bool
- headDim :: Index ix => ix -> Int
- tailDim :: Index ix => ix -> Lower ix
- lastDim :: Index ix => ix -> Int
- initDim :: Index ix => ix -> Lower ix
- iterLinearM :: (Index ix, Monad m) => ix -> Int -> Int -> Int -> (Int -> Int -> Bool) -> a -> (Int -> ix -> a -> m a) -> m a
- iterLinearM_ :: (Index ix, Monad m) => ix -> Int -> Int -> Int -> (Int -> Int -> Bool) -> (Int -> ix -> m ()) -> m ()
- loop :: Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> a) -> a
- loopM :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a
- loopM_ :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> (Int -> m a) -> m ()
- loopDeepM :: Monad m => Int -> (Int -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a
Documentation
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)
2-dimensional index. This also a base index for higher dimensions.
Bounded Ix2 Source # | |
Eq Ix2 Source # | |
Num Ix2 Source # | |
Ord Ix2 Source # | |
Show Ix2 Source # | |
NFData Ix2 Source # | |
Unbox Ix2 Source # | Unboxing of a |
Index Ix2 Source # | |
Vector Vector Ix2 Source # | |
MVector MVector Ix2 Source # | |
Load DW Ix2 e Source # | |
data Vector Ix2 Source # | |
type Rank Ix2 Source # | |
type Lower Ix2 Source # | |
data MVector s Ix2 Source # | |
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)
.
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)
.
pattern Ix4 :: Int -> Int -> Int -> Int -> Ix4 Source #
4-dimensional index constructor. (Ix4 i j k l) == (i :> j :> k :. l)
.
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) where Source #
n-dimensional index. Needs a base case, which is the Ix2
.
Bounded Ix3 Source # | |
Num Ix3 Source # | |
((<=) 3 n, Unbox (Ix ((-) n 1))) => Vector Vector (IxN n) Source # | |
((<=) 3 n, Unbox (Ix ((-) n 1))) => MVector MVector (IxN n) Source # | |
((<=) 4 n, KnownNat n, Index (Ix ((-) n 1)), (~) * (IxN ((-) n 1)) (Ix ((-) n 1))) => Bounded (IxN n) Source # | |
Eq (Ix ((-) n 1)) => Eq (IxN n) Source # | |
((<=) 4 n, KnownNat n, Index (Ix ((-) n 1)), (~) * (IxN ((-) n 1)) (Ix ((-) n 1))) => Num (IxN n) Source # | |
Ord (Ix ((-) n 1)) => Ord (IxN n) Source # | |
Show (Ix ((-) n 1)) => Show (IxN n) Source # | |
NFData (IxN n) Source # | |
((<=) 3 n, Unbox (Ix ((-) n 1))) => Unbox (IxN n) Source # | Unboxing of a |
((<=) 4 n, KnownNat n, Index (Ix ((-) n 1)), (~) * (IxN ((-) n 1)) (Ix ((-) n 1))) => Index (IxN n) Source # | |
Index (IxN 3) Source # | |
type Rank Ix3 Source # | |
data MVector s (IxN n) Source # | |
data Vector (IxN n) Source # | |
type Rank (IxN n) Source # | |
type Lower (IxN n) Source # | |
type family Ix (n :: Nat) = r | r -> n where ... Source #
Defines n-dimensional index by relating a general IxN
with few base cases.
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.
Fill e | Fill in a constant element. outside | Array | outside
( |
Wrap | Wrap around from the opposite border of the array. outside | Array | outside
|
Edge | Replicate the element at the edge. outside | Array | outside
|
Reflect | Mirror like reflection. outside | Array | outside
|
Continue | Also mirror like reflection, but without repeating the edge element. outside | Array | outside
|
:: 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
A way to select Array dimension.
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.
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.
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.
rank, totalElem, consDim, unconsDim, snocDim, unsnocDim, dropDim, getIndex, setIndex, pureIndex, liftIndex2
Rank 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
getIndex :: ix -> Dim -> Maybe Int Source #
Extract the value index has at specified dimension.
setIndex :: ix -> Dim -> Int -> Maybe 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.
liftIndex2 :: (Int -> Int -> Int) -> ix -> ix -> ix Source #
Zip together two indices with a function
Index with all zeros
liftIndex :: (Int -> Int) -> ix -> ix Source #
Map a function over an index
:: ix | Size |
-> ix | Index |
-> Bool |
Check whether index is within the size.
Check whether index is within the size.
:: ix | Size |
-> ix | Index |
-> Int |
Convert linear index from size and index
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.
:: 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)
:: 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 -> Int -> (Int -> Int -> Bool) -> a -> (ix -> a -> a) -> a Source #
Iterator for the index. Same as iterM
, but pure.
:: Monad m | |
=> ix | Start index |
-> ix | End index |
-> Int | 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.
:: (Index (Lower ix), Monad m) | |
=> ix | Start index |
-> ix | End index |
-> Int | 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 -> Int -> (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 -> Int -> (Int -> Int -> Bool) -> (ix -> m a) -> m () Source #
Same as iterM
, but don't bother with accumulator and return value.
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
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.
:: (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 from start to end with 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