| Copyright | (c) Christopher Chalmers | 
|---|---|
| License | BSD3 | 
| Maintainer | Christopher Chalmers | 
| Stability | provisional | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Dense.Index
Description
This module provides a class for types that can be converted to and from linear indexes.
The default instances are defined in row-major order.
Synopsis
- type Layout f = f Int
- class (Eq1 f, Additive f, Traversable f) => Shape f where- shapeToIndex :: Layout f -> f Int -> Int
- shapeFromIndex :: Layout f -> Int -> f Int
- shapeIntersect :: Layout f -> Layout f -> Layout f
- unsafeShapeStep :: Layout f -> f Int -> f Int
- shapeStep :: Layout f -> f Int -> Maybe (f Int)
- shapeStepBetween :: f Int -> Layout f -> f Int -> Maybe (f Int)
- shapeInRange :: Layout f -> f Int -> Bool
- shapeSize :: Layout f -> Int
 
- indexIso :: Shape f => Layout f -> Iso' (f Int) Int
- shapeIndexes :: Shape f => IndexedFold Int (Layout f) (f Int)
- shapeIndexesFrom :: Shape f => f Int -> IndexedFold Int (Layout f) (f Int)
- shapeIndexesBetween :: Shape f => f Int -> f Int -> IndexedFold Int (Layout f) (f Int)
- class Shape f => HasLayout f a | a -> f where
- extent :: HasLayout f a => a -> f Int
- size :: HasLayout f a => a -> Int
- indexes :: HasLayout f a => IndexedFold Int a (f Int)
- indexesBetween :: HasLayout f a => f Int -> f Int -> IndexedFold Int a (f Int)
- indexesFrom :: HasLayout f a => f Int -> IndexedFold Int a (f Int)
- data ArrayException = IndexOutOfBounds String
- _IndexOutOfBounds :: AsArrayException t => Prism' t String
- boundsCheck :: Shape l => Layout l -> l Int -> a -> a
- data SizeMissmatch = SizeMissmatch String
- class AsSizeMissmatch t where- _SizeMissmatch :: Prism' t String
 
- sizeMissmatch :: Int -> Int -> String -> a -> a
- showShape :: Shape f => f Int -> String
Shape class
type Layout f = f Int Source #
A Layout is the full size of an array. This alias is used to help
   distinguish between the layout of an array and an index (usually
   just l Int) in a type signature.
class (Eq1 f, Additive f, Traversable f) => Shape f where Source #
Class for types that can be converted to and from linear indexes.
Minimal complete definition
Nothing
Methods
shapeToIndex :: Layout f -> f Int -> Int Source #
Convert a shape to its linear index using the Layout.
shapeFromIndex :: Layout f -> Int -> f Int Source #
Convert a linear index to a shape the Layout.
shapeIntersect :: Layout f -> Layout f -> Layout f Source #
Calculate the intersection of two shapes.
unsafeShapeStep :: Layout f -> f Int -> f Int Source #
Increment a shape by one. It is assumed that the provided index
   is inRange.
shapeStep :: Layout f -> f Int -> Maybe (f Int) Source #
Increment a shape by one. It is assumed that the provided index
   is inRange.
shapeStepBetween :: f Int -> Layout f -> f Int -> Maybe (f Int) Source #
Increment a shape by one between the two bounds
shapeInRange :: Layout f -> f Int -> Bool Source #
inRange ex i checks i < ex for every coordinate of f.
shapeSize :: Layout f -> Int Source #
The number of elements in a shape.
Instances
indexIso :: Shape f => Layout f -> Iso' (f Int) Int Source #
toIndex lfromIndex l
shapeIndexes :: Shape f => IndexedFold Int (Layout f) (f Int) Source #
shapeIndexesFrom :: Shape f => f Int -> IndexedFold Int (Layout f) (f Int) Source #
indexesFrom for a Shape.
shapeIndexesBetween :: Shape f => f Int -> f Int -> IndexedFold Int (Layout f) (f Int) Source #
indexesBetween for a Shape.
HasLayout
class Shape f => HasLayout f a | a -> f where Source #
Class of things that have a Layout. This means we can use the
   same functions for the various different arrays in the library.
Minimal complete definition
Nothing
Instances
| i ~ Int => HasLayout V0 (V0 i) Source # | |
| i ~ Int => HasLayout V4 (V4 i) Source # | |
| i ~ Int => HasLayout V3 (V3 i) Source # | |
| i ~ Int => HasLayout V2 (V2 i) Source # | |
| i ~ Int => HasLayout V1 (V1 i) Source # | |
| Shape f => HasLayout f (Focused f a) Source # | The  | 
| Shape f => HasLayout f (Delayed f a) Source # | The  | 
| Shape f => HasLayout f (Array v f a) Source # | The  | 
| Shape f => HasLayout f (MArray v f s a) Source # | |
indexes :: HasLayout f a => IndexedFold Int a (f Int) Source #
Indexed fold for all the indexes in the layout.
indexesBetween :: HasLayout f a => f Int -> f Int -> IndexedFold Int a (f Int) Source #
Indexed fold between the two indexes where the index is the linear index for the original layout.
indexesFrom :: HasLayout f a => f Int -> IndexedFold Int a (f Int) Source #
Indexed fold starting starting from some point, where the index is the linear index for the original layout.
Exceptions
data ArrayException #
Exceptions generated by array operations
Constructors
| IndexOutOfBounds String | An attempt was made to index an array outside its declared bounds. | 
Instances
_IndexOutOfBounds :: AsArrayException t => Prism' t String #
An attempt was made to index an array outside its declared bounds.
_IndexOutOfBounds≡_ArrayException._IndexOutOfBounds
_IndexOutOfBounds::Prism'ArrayExceptionString_IndexOutOfBounds::Prism'SomeExceptionString
boundsCheck :: Shape l => Layout l -> l Int -> a -> a Source #
boundsCheck l i performs a bounds check for index i and layout
   l. Throws an IndexOutOfBounds exception when out of range in
   the form (i, l). This can be caught with the _IndexOutOfBounds
   prism.
>>>boundsCheck (V2 3 5) (V2 1 4) "in range""in range"
>>>boundsCheck (V2 10 20) (V2 10 5) "in bounds""*** Exception: array index out of range: (V2 10 5, V2 10 20)
>>>catching _IndexOutOfBounds (boundsCheck (V1 2) (V1 2) (putStrLn "in range")) print"(V1 2, V1 2)"
The output format is suitable to be read using the _Show prism:
>>>trying (_IndexOutOfBounds . _Show) (boundsCheck (V1 2) (V1 20) (putStrLn "in range")) :: IO (Either (V1 Int, V1 Int) ())Left (V1 20,V1 2)
data SizeMissmatch Source #
Thrown when two sizes that should match, don't.
Constructors
| SizeMissmatch String | 
Instances
| Show SizeMissmatch Source # | |
| Defined in Data.Dense.Index Methods showsPrec :: Int -> SizeMissmatch -> ShowS # show :: SizeMissmatch -> String # showList :: [SizeMissmatch] -> ShowS # | |
| Exception SizeMissmatch Source # | |
| Defined in Data.Dense.Index Methods toException :: SizeMissmatch -> SomeException # fromException :: SomeException -> Maybe SizeMissmatch # displayException :: SizeMissmatch -> String # | |
| AsSizeMissmatch SizeMissmatch Source # | |
| Defined in Data.Dense.Index Methods | |
class AsSizeMissmatch t where Source #
Exception thown from missmatching sizes.
Methods
_SizeMissmatch :: Prism' t String Source #
Extract information about an SizeMissmatch.
_SizeMissmatch::Prism'SizeMissmatchString_SizeMissmatch::Prism'SomeExceptionString
Instances
| AsSizeMissmatch SomeException Source # | |
| Defined in Data.Dense.Index Methods | |
| AsSizeMissmatch SizeMissmatch Source # | |
| Defined in Data.Dense.Index Methods | |
sizeMissmatch :: Int -> Int -> String -> a -> a Source #
Check the sizes are equal. If not, throw SizeMissmatch.