comfort-array-0.5.2.1: Arrays where the index type is a function of the shape type
Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Array.Comfort.Shape

Synopsis

Documentation

class C sh where Source #

Methods

size :: sh -> Int Source #

Instances

Instances details
C Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Zero -> Int Source #

C () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: () -> Int Source #

C f => C (Shape f) Source # 
Instance details

Defined in Data.Array.Comfort.Container

Methods

size :: Shape f -> Int Source #

C (Constructed tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Constructed tag -> Int Source #

C sh => C (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Cube sh -> Int Source #

Integral n => C (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Cyclic n -> Int Source #

C sh => C (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Deferred sh -> Int Source #

(Enum n, Bounded n) => C (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Enumeration n -> Int Source #

Integral n => C (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: OneBased n -> Int Source #

Ix n => C (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Range n -> Int Source #

Foldable f => C (Record f) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Record f -> Int Source #

Integral n => C (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Shifted n -> Int Source #

C sh => C (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Square sh -> Int Source #

Integral n => C (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: ZeroBased n -> Int Source #

Ord n => C (Set n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Set n -> Int Source #

(C sh0, C sh1) => C (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: (sh0 ::+ sh1) -> Int Source #

ElementTuple tuple => C (NestedTuple ixtype tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: NestedTuple ixtype tuple -> Int Source #

(TriangularPart part, C size) => C (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Triangular part size -> Int Source #

(Ord k, C shape) => C (Map k shape) Source #

Concatenate many arrays according to the shapes stored in a Map.

Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Map k shape -> Int Source #

(C sh0, C sh1) => C (sh0, sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: (sh0, sh1) -> Int Source #

C sh => C (Tagged s sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Tagged s sh -> Int Source #

(C sh0, C sh1, C sh2) => C (sh0, sh1, sh2) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: (sh0, sh1, sh2) -> Int Source #

(SimplexOrderC order, CollisionC coll, Traversable f, C size) => C (Simplex order coll f size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Simplex order coll f size -> Int Source #

class C sh => Indexed sh where Source #

Minimal complete definition

indices, (unifiedOffset | unifiedSizeOffset)

Associated Types

type Index sh Source #

Methods

indices :: sh -> [Index sh] Source #

offset :: sh -> Index sh -> Int Source #

uncheckedOffset :: sh -> Index sh -> Int Source #

unifiedOffset :: Checking check => sh -> Index sh -> Result check Int Source #

inBounds :: sh -> Index sh -> Bool Source #

sizeOffset :: sh -> (Int, Index sh -> Int) Source #

uncheckedSizeOffset :: sh -> (Int, Index sh -> Int) Source #

unifiedSizeOffset :: Checking check => sh -> (Int, Index sh -> Result check Int) Source #

Instances

Instances details
Indexed () Source #
>>> Shape.indices ()
[()]
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index () Source #

Methods

indices :: () -> [Index ()] Source #

offset :: () -> Index () -> Int Source #

uncheckedOffset :: () -> Index () -> Int Source #

unifiedOffset :: Checking check => () -> Index () -> Result check Int Source #

inBounds :: () -> Index () -> Bool Source #

sizeOffset :: () -> (Int, Index () -> Int) Source #

uncheckedSizeOffset :: () -> (Int, Index () -> Int) Source #

unifiedSizeOffset :: Checking check => () -> (Int, Index () -> Result check Int) Source #

Indexed f => Indexed (Shape f) Source # 
Instance details

Defined in Data.Array.Comfort.Container

Associated Types

type Index (Shape f) Source #

Indexed (Constructed tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Constructed tag) Source #

Indexed sh => Indexed (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Cube sh) Source #

Methods

indices :: Cube sh -> [Index (Cube sh)] Source #

offset :: Cube sh -> Index (Cube sh) -> Int Source #

uncheckedOffset :: Cube sh -> Index (Cube sh) -> Int Source #

unifiedOffset :: Checking check => Cube sh -> Index (Cube sh) -> Result check Int Source #

inBounds :: Cube sh -> Index (Cube sh) -> Bool Source #

sizeOffset :: Cube sh -> (Int, Index (Cube sh) -> Int) Source #

uncheckedSizeOffset :: Cube sh -> (Int, Index (Cube sh) -> Int) Source #

unifiedSizeOffset :: Checking check => Cube sh -> (Int, Index (Cube sh) -> Result check Int) Source #

Integral n => Indexed (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Cyclic n) Source #

C sh => Indexed (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Deferred sh) Source #

(Enum n, Bounded n) => Indexed (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Enumeration n) Source #

Integral n => Indexed (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (OneBased n) Source #

Ix n => Indexed (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Range n) Source #

Foldable f => Indexed (Record f) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Record f) Source #

Integral n => Indexed (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Shifted n) Source #

Indexed sh => Indexed (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Square sh) Source #

Methods

indices :: Square sh -> [Index (Square sh)] Source #

offset :: Square sh -> Index (Square sh) -> Int Source #

uncheckedOffset :: Square sh -> Index (Square sh) -> Int Source #

unifiedOffset :: Checking check => Square sh -> Index (Square sh) -> Result check Int Source #

inBounds :: Square sh -> Index (Square sh) -> Bool Source #

sizeOffset :: Square sh -> (Int, Index (Square sh) -> Int) Source #

uncheckedSizeOffset :: Square sh -> (Int, Index (Square sh) -> Int) Source #

unifiedSizeOffset :: Checking check => Square sh -> (Int, Index (Square sh) -> Result check Int) Source #

Integral n => Indexed (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (ZeroBased n) Source #

Ord n => Indexed (Set n) Source #

You can use an arbitrary Set of indices as shape. The array elements are ordered according to the index order in the Set.

An Array (Set k) a is isomorphic to a Map k a, however it is missing most Map operations like insert, delete and union. An Array (Set k, Set j) a has a cartesian structure and thus is not isomorphic to Map (k,j) a. This means, if the array has two elements with indices (k0,j0) and (k1,j1) it has also an element with index (k0,j1).

Disadvantage is that combinators of different Set indexed arrays have to compare whole sets. However, the Set implementation may have low-level optimizations for pointer equality.

>>> Shape.indices (Set.fromList "comfort")
"cfmort"
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Set n) Source #

Methods

indices :: Set n -> [Index (Set n)] Source #

offset :: Set n -> Index (Set n) -> Int Source #

uncheckedOffset :: Set n -> Index (Set n) -> Int Source #

unifiedOffset :: Checking check => Set n -> Index (Set n) -> Result check Int Source #

inBounds :: Set n -> Index (Set n) -> Bool Source #

sizeOffset :: Set n -> (Int, Index (Set n) -> Int) Source #

uncheckedSizeOffset :: Set n -> (Int, Index (Set n) -> Int) Source #

unifiedSizeOffset :: Checking check => Set n -> (Int, Index (Set n) -> Result check Int) Source #

(Indexed sh0, Indexed sh1) => Indexed (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (sh0 ::+ sh1) Source #

Methods

indices :: (sh0 ::+ sh1) -> [Index (sh0 ::+ sh1)] Source #

offset :: (sh0 ::+ sh1) -> Index (sh0 ::+ sh1) -> Int Source #

uncheckedOffset :: (sh0 ::+ sh1) -> Index (sh0 ::+ sh1) -> Int Source #

unifiedOffset :: Checking check => (sh0 ::+ sh1) -> Index (sh0 ::+ sh1) -> Result check Int Source #

inBounds :: (sh0 ::+ sh1) -> Index (sh0 ::+ sh1) -> Bool Source #

sizeOffset :: (sh0 ::+ sh1) -> (Int, Index (sh0 ::+ sh1) -> Int) Source #

uncheckedSizeOffset :: (sh0 ::+ sh1) -> (Int, Index (sh0 ::+ sh1) -> Int) Source #

unifiedSizeOffset :: Checking check => (sh0 ::+ sh1) -> (Int, Index (sh0 ::+ sh1) -> Result check Int) Source #

AccessorTuple tuple => Indexed (NestedTuple TupleAccessor tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (NestedTuple TupleAccessor tuple) Source #

ElementTuple tuple => Indexed (NestedTuple TupleIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (NestedTuple TupleIndex tuple) Source #

(TriangularPart part, Indexed size) => Indexed (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Triangular part size) Source #

Methods

indices :: Triangular part size -> [Index (Triangular part size)] Source #

offset :: Triangular part size -> Index (Triangular part size) -> Int Source #

uncheckedOffset :: Triangular part size -> Index (Triangular part size) -> Int Source #

unifiedOffset :: Checking check => Triangular part size -> Index (Triangular part size) -> Result check Int Source #

inBounds :: Triangular part size -> Index (Triangular part size) -> Bool Source #

sizeOffset :: Triangular part size -> (Int, Index (Triangular part size) -> Int) Source #

uncheckedSizeOffset :: Triangular part size -> (Int, Index (Triangular part size) -> Int) Source #

unifiedSizeOffset :: Checking check => Triangular part size -> (Int, Index (Triangular part size) -> Result check Int) Source #

(Ord k, Indexed shape) => Indexed (Map k shape) Source #

The implementations of offset et.al. are optimized for frequent calls with respect to the same shape.

>>> Shape.indices $ fmap Shape.ZeroBased $ Map.fromList [('b', (0::Int)), ('a', 5), ('c', 2)]
[('a',0),('a',1),('a',2),('a',3),('a',4),('c',0),('c',1)]
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Map k shape) Source #

Methods

indices :: Map k shape -> [Index (Map k shape)] Source #

offset :: Map k shape -> Index (Map k shape) -> Int Source #

uncheckedOffset :: Map k shape -> Index (Map k shape) -> Int Source #

unifiedOffset :: Checking check => Map k shape -> Index (Map k shape) -> Result check Int Source #

inBounds :: Map k shape -> Index (Map k shape) -> Bool Source #

sizeOffset :: Map k shape -> (Int, Index (Map k shape) -> Int) Source #

uncheckedSizeOffset :: Map k shape -> (Int, Index (Map k shape) -> Int) Source #

unifiedSizeOffset :: Checking check => Map k shape -> (Int, Index (Map k shape) -> Result check Int) Source #

(Indexed sh0, Indexed sh1) => Indexed (sh0, sh1) Source #

Row-major composition of two dimensions.

>>> Shape.indices (Shape.ZeroBased (3::Int), Shape.ZeroBased (3::Int))
[(0,0),(0,1),(0,2),(1,0),(1,1),(1,2),(2,0),(2,1),(2,2)]
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (sh0, sh1) Source #

Methods

indices :: (sh0, sh1) -> [Index (sh0, sh1)] Source #

offset :: (sh0, sh1) -> Index (sh0, sh1) -> Int Source #

uncheckedOffset :: (sh0, sh1) -> Index (sh0, sh1) -> Int Source #

unifiedOffset :: Checking check => (sh0, sh1) -> Index (sh0, sh1) -> Result check Int Source #

inBounds :: (sh0, sh1) -> Index (sh0, sh1) -> Bool Source #

sizeOffset :: (sh0, sh1) -> (Int, Index (sh0, sh1) -> Int) Source #

uncheckedSizeOffset :: (sh0, sh1) -> (Int, Index (sh0, sh1) -> Int) Source #

unifiedSizeOffset :: Checking check => (sh0, sh1) -> (Int, Index (sh0, sh1) -> Result check Int) Source #

Indexed sh => Indexed (Tagged s sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Tagged s sh) Source #

Methods

indices :: Tagged s sh -> [Index (Tagged s sh)] Source #

offset :: Tagged s sh -> Index (Tagged s sh) -> Int Source #

uncheckedOffset :: Tagged s sh -> Index (Tagged s sh) -> Int Source #

unifiedOffset :: Checking check => Tagged s sh -> Index (Tagged s sh) -> Result check Int Source #

inBounds :: Tagged s sh -> Index (Tagged s sh) -> Bool Source #

sizeOffset :: Tagged s sh -> (Int, Index (Tagged s sh) -> Int) Source #

uncheckedSizeOffset :: Tagged s sh -> (Int, Index (Tagged s sh) -> Int) Source #

unifiedSizeOffset :: Checking check => Tagged s sh -> (Int, Index (Tagged s sh) -> Result check Int) Source #

(Indexed sh0, Indexed sh1, Indexed sh2) => Indexed (sh0, sh1, sh2) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (sh0, sh1, sh2) Source #

Methods

indices :: (sh0, sh1, sh2) -> [Index (sh0, sh1, sh2)] Source #

offset :: (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> Int Source #

uncheckedOffset :: (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> Int Source #

unifiedOffset :: Checking check => (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> Result check Int Source #

inBounds :: (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> Bool Source #

sizeOffset :: (sh0, sh1, sh2) -> (Int, Index (sh0, sh1, sh2) -> Int) Source #

uncheckedSizeOffset :: (sh0, sh1, sh2) -> (Int, Index (sh0, sh1, sh2) -> Int) Source #

unifiedSizeOffset :: Checking check => (sh0, sh1, sh2) -> (Int, Index (sh0, sh1, sh2) -> Result check Int) Source #

(SimplexOrderC order, CollisionC coll, Traversable f, Eq1 f, Indexed size) => Indexed (Simplex order coll f size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Simplex order coll f size) Source #

Methods

indices :: Simplex order coll f size -> [Index (Simplex order coll f size)] Source #

offset :: Simplex order coll f size -> Index (Simplex order coll f size) -> Int Source #

uncheckedOffset :: Simplex order coll f size -> Index (Simplex order coll f size) -> Int Source #

unifiedOffset :: Checking check => Simplex order coll f size -> Index (Simplex order coll f size) -> Result check Int Source #

inBounds :: Simplex order coll f size -> Index (Simplex order coll f size) -> Bool Source #

sizeOffset :: Simplex order coll f size -> (Int, Index (Simplex order coll f size) -> Int) Source #

uncheckedSizeOffset :: Simplex order coll f size -> (Int, Index (Simplex order coll f size) -> Int) Source #

unifiedSizeOffset :: Checking check => Simplex order coll f size -> (Int, Index (Simplex order coll f size) -> Result check Int) Source #

class Indexed sh => InvIndexed sh where Source #

Minimal complete definition

unifiedIndexFromOffset

Methods

indexFromOffset :: sh -> Int -> Index sh Source #

It should hold indexFromOffset sh k == indices sh !! k, but indexFromOffset should generally be faster.

uncheckedIndexFromOffset :: sh -> Int -> Index sh Source #

unifiedIndexFromOffset :: Checking check => sh -> Int -> Result check (Index sh) Source #

Instances

Instances details
InvIndexed () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: () -> Int -> Index () Source #

uncheckedIndexFromOffset :: () -> Int -> Index () Source #

unifiedIndexFromOffset :: Checking check => () -> Int -> Result check (Index ()) Source #

InvIndexed (Constructed tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

InvIndexed sh => InvIndexed (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Integral n => InvIndexed (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

C sh => InvIndexed (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

(Enum n, Bounded n) => InvIndexed (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Integral n => InvIndexed (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Ix n => InvIndexed (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Integral n => InvIndexed (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

InvIndexed sh => InvIndexed (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Integral n => InvIndexed (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Ord n => InvIndexed (Set n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

(InvIndexed sh0, InvIndexed sh1) => InvIndexed (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: (sh0 ::+ sh1) -> Int -> Index (sh0 ::+ sh1) Source #

uncheckedIndexFromOffset :: (sh0 ::+ sh1) -> Int -> Index (sh0 ::+ sh1) Source #

unifiedIndexFromOffset :: Checking check => (sh0 ::+ sh1) -> Int -> Result check (Index (sh0 ::+ sh1)) Source #

(TriangularPart part, InvIndexed size) => InvIndexed (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: Triangular part size -> Int -> Index (Triangular part size) Source #

uncheckedIndexFromOffset :: Triangular part size -> Int -> Index (Triangular part size) Source #

unifiedIndexFromOffset :: Checking check => Triangular part size -> Int -> Result check (Index (Triangular part size)) Source #

(Ord k, InvIndexed shape) => InvIndexed (Map k shape) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: Map k shape -> Int -> Index (Map k shape) Source #

uncheckedIndexFromOffset :: Map k shape -> Int -> Index (Map k shape) Source #

unifiedIndexFromOffset :: Checking check => Map k shape -> Int -> Result check (Index (Map k shape)) Source #

(InvIndexed sh0, InvIndexed sh1) => InvIndexed (sh0, sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: (sh0, sh1) -> Int -> Index (sh0, sh1) Source #

uncheckedIndexFromOffset :: (sh0, sh1) -> Int -> Index (sh0, sh1) Source #

unifiedIndexFromOffset :: Checking check => (sh0, sh1) -> Int -> Result check (Index (sh0, sh1)) Source #

InvIndexed sh => InvIndexed (Tagged s sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: Tagged s sh -> Int -> Index (Tagged s sh) Source #

uncheckedIndexFromOffset :: Tagged s sh -> Int -> Index (Tagged s sh) Source #

unifiedIndexFromOffset :: Checking check => Tagged s sh -> Int -> Result check (Index (Tagged s sh)) Source #

(InvIndexed sh0, InvIndexed sh1, InvIndexed sh2) => InvIndexed (sh0, sh1, sh2) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: (sh0, sh1, sh2) -> Int -> Index (sh0, sh1, sh2) Source #

uncheckedIndexFromOffset :: (sh0, sh1, sh2) -> Int -> Index (sh0, sh1, sh2) Source #

unifiedIndexFromOffset :: Checking check => (sh0, sh1, sh2) -> Int -> Result check (Index (sh0, sh1, sh2)) Source #

(SimplexOrderC order, CollisionC coll, Traversable f, Eq1 f, InvIndexed size) => InvIndexed (Simplex order coll f size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: Simplex order coll f size -> Int -> Index (Simplex order coll f size) Source #

uncheckedIndexFromOffset :: Simplex order coll f size -> Int -> Index (Simplex order coll f size) Source #

unifiedIndexFromOffset :: Checking check => Simplex order coll f size -> Int -> Result check (Index (Simplex order coll f size)) Source #

assertIndexFromOffset :: Checking check => String -> Int -> Bool -> Result check () Source #

class (C sh, Eq sh) => Static sh where Source #

Methods

static :: sh Source #

Instances

Instances details
Static Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Zero Source #

Static () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: () Source #

Static sh => Static (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Deferred sh Source #

(Enum n, Bounded n) => Static (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

(Applicative f, Traversable f) => Static (Record f) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Record f Source #

(Static sh0, Static sh1) => Static (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: sh0 ::+ sh1 Source #

StaticTuple tuple => Static (NestedTuple ixtype tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: NestedTuple ixtype tuple Source #

(TriangularPart part, Static size) => Static (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Triangular part size Source #

(Static sh0, Static sh1) => Static (sh0, sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: (sh0, sh1) Source #

Static sh => Static (Tagged s sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Tagged s sh Source #

(Static sh0, Static sh1, Static sh2) => Static (sh0, sh1, sh2) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: (sh0, sh1, sh2) Source #

class Indexed sh => Pattern sh where Source #

Associated Types

type DataPattern sh x Source #

Methods

indexPattern :: (Index sh -> x) -> sh -> DataPattern sh x Source #

Instances

Instances details
Pattern () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern () x Source #

Methods

indexPattern :: (Index () -> x) -> () -> DataPattern () x Source #

Pattern sh => Pattern (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (Square sh) x Source #

Methods

indexPattern :: (Index (Square sh) -> x) -> Square sh -> DataPattern (Square sh) x Source #

Integral n => Pattern (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (ZeroBased n) x Source #

Methods

indexPattern :: (Index (ZeroBased n) -> x) -> ZeroBased n -> DataPattern (ZeroBased n) x Source #

(Pattern sh0, Pattern sh1) => Pattern (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (sh0 ::+ sh1) x Source #

Methods

indexPattern :: (Index (sh0 ::+ sh1) -> x) -> (sh0 ::+ sh1) -> DataPattern (sh0 ::+ sh1) x Source #

ElementTuple tuple => Pattern (NestedTuple TupleIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (NestedTuple TupleIndex tuple) x Source #

(Pattern sh0, Pattern sh1) => Pattern (sh0, sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (sh0, sh1) x Source #

Methods

indexPattern :: (Index (sh0, sh1) -> x) -> (sh0, sh1) -> DataPattern (sh0, sh1) x Source #

Pattern sh => Pattern (Tagged s sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (Tagged s sh) x Source #

Methods

indexPattern :: (Index (Tagged s sh) -> x) -> Tagged s sh -> DataPattern (Tagged s sh) x Source #

requireCheck :: CheckSingleton check -> Result check a -> Result check a Source #

data CheckSingleton check where Source #

Constructors

Checked :: CheckSingleton Checked 
Unchecked :: CheckSingleton Unchecked 

class Checking check where Source #

Associated Types

data Result check a Source #

Methods

switchCheck :: f Checked -> f Unchecked -> f check Source #

runChecked :: String -> Result Checked a -> a Source #

runUnchecked :: Result Unchecked a -> a Source #

assert :: Checking check => String -> Bool -> Result check () Source #

throwOrError :: Checking check => String -> Result check a Source #

data Zero Source #

Constructors

Zero 

Instances

Instances details
Show Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Zero -> ShowS #

show :: Zero -> String #

showList :: [Zero] -> ShowS #

C Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Zero -> Int Source #

Static Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Zero Source #

Eq Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

Ord Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

compare :: Zero -> Zero -> Ordering #

(<) :: Zero -> Zero -> Bool #

(<=) :: Zero -> Zero -> Bool #

(>) :: Zero -> Zero -> Bool #

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

max :: Zero -> Zero -> Zero #

min :: Zero -> Zero -> Zero #

newtype ZeroBased n Source #

ZeroBased denotes a range starting at zero and has a certain length.

>>> Shape.indices (Shape.ZeroBased (7::Int))
[0,1,2,3,4,5,6]

Constructors

ZeroBased 

Fields

Instances

Instances details
Applicative ZeroBased Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

pure :: a -> ZeroBased a #

(<*>) :: ZeroBased (a -> b) -> ZeroBased a -> ZeroBased b #

liftA2 :: (a -> b -> c) -> ZeroBased a -> ZeroBased b -> ZeroBased c #

(*>) :: ZeroBased a -> ZeroBased b -> ZeroBased b #

(<*) :: ZeroBased a -> ZeroBased b -> ZeroBased a #

Functor ZeroBased Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

fmap :: (a -> b) -> ZeroBased a -> ZeroBased b #

(<$) :: a -> ZeroBased b -> ZeroBased a #

Storable n => Storable (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

sizeOf :: ZeroBased n -> Int #

alignment :: ZeroBased n -> Int #

peekElemOff :: Ptr (ZeroBased n) -> Int -> IO (ZeroBased n) #

pokeElemOff :: Ptr (ZeroBased n) -> Int -> ZeroBased n -> IO () #

peekByteOff :: Ptr b -> Int -> IO (ZeroBased n) #

pokeByteOff :: Ptr b -> Int -> ZeroBased n -> IO () #

peek :: Ptr (ZeroBased n) -> IO (ZeroBased n) #

poke :: Ptr (ZeroBased n) -> ZeroBased n -> IO () #

Show n => Show (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Integral n => C (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: ZeroBased n -> Int Source #

Integral n => Indexed (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (ZeroBased n) Source #

Integral n => InvIndexed (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Integral n => Pattern (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (ZeroBased n) x Source #

Methods

indexPattern :: (Index (ZeroBased n) -> x) -> ZeroBased n -> DataPattern (ZeroBased n) x Source #

NFData n => NFData (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: ZeroBased n -> () #

Eq n => Eq (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: ZeroBased n -> ZeroBased n -> Bool #

(/=) :: ZeroBased n -> ZeroBased n -> Bool #

type Index (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (ZeroBased n) = n
type DataPattern (ZeroBased n) x Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type DataPattern (ZeroBased n) x = n -> x

newtype OneBased n Source #

OneBased denotes a range starting at one and has a certain length.

>>> Shape.indices (Shape.OneBased (7::Int))
[1,2,3,4,5,6,7]

Constructors

OneBased 

Fields

Instances

Instances details
Applicative OneBased Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

pure :: a -> OneBased a #

(<*>) :: OneBased (a -> b) -> OneBased a -> OneBased b #

liftA2 :: (a -> b -> c) -> OneBased a -> OneBased b -> OneBased c #

(*>) :: OneBased a -> OneBased b -> OneBased b #

(<*) :: OneBased a -> OneBased b -> OneBased a #

Functor OneBased Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

fmap :: (a -> b) -> OneBased a -> OneBased b #

(<$) :: a -> OneBased b -> OneBased a #

Storable n => Storable (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

sizeOf :: OneBased n -> Int #

alignment :: OneBased n -> Int #

peekElemOff :: Ptr (OneBased n) -> Int -> IO (OneBased n) #

pokeElemOff :: Ptr (OneBased n) -> Int -> OneBased n -> IO () #

peekByteOff :: Ptr b -> Int -> IO (OneBased n) #

pokeByteOff :: Ptr b -> Int -> OneBased n -> IO () #

peek :: Ptr (OneBased n) -> IO (OneBased n) #

poke :: Ptr (OneBased n) -> OneBased n -> IO () #

Show n => Show (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> OneBased n -> ShowS #

show :: OneBased n -> String #

showList :: [OneBased n] -> ShowS #

Integral n => C (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: OneBased n -> Int Source #

Integral n => Indexed (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (OneBased n) Source #

Integral n => InvIndexed (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

NFData n => NFData (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: OneBased n -> () #

Eq n => Eq (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: OneBased n -> OneBased n -> Bool #

(/=) :: OneBased n -> OneBased n -> Bool #

type Index (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (OneBased n) = n

data Range n Source #

Range denotes an inclusive range like those of the Haskell 98 standard Array type from the array package. E.g. the shape type (Range Int32, Range Int64) is equivalent to the ix type (Int32, Int64) for Arrays.

>>> Shape.indices (Shape.Range (-5) (5::Int))
[-5,-4,-3,-2,-1,0,1,2,3,4,5]
>>> Shape.indices (Shape.Range (-1,-1) (1::Int,1::Int))
[(-1,-1),(-1,0),(-1,1),(0,-1),(0,0),(0,1),(1,-1),(1,0),(1,1)]

Constructors

Range 

Fields

Instances

Instances details
Functor Range Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

fmap :: (a -> b) -> Range a -> Range b #

(<$) :: a -> Range b -> Range a #

Storable n => Storable (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

sizeOf :: Range n -> Int #

alignment :: Range n -> Int #

peekElemOff :: Ptr (Range n) -> Int -> IO (Range n) #

pokeElemOff :: Ptr (Range n) -> Int -> Range n -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Range n) #

pokeByteOff :: Ptr b -> Int -> Range n -> IO () #

peek :: Ptr (Range n) -> IO (Range n) #

poke :: Ptr (Range n) -> Range n -> IO () #

Show n => Show (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Range n -> ShowS #

show :: Range n -> String #

showList :: [Range n] -> ShowS #

Ix n => C (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Range n -> Int Source #

Ix n => Indexed (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Range n) Source #

Ix n => InvIndexed (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

NFData n => NFData (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Range n -> () #

Eq n => Eq (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Range n -> Range n -> Bool #

(/=) :: Range n -> Range n -> Bool #

type Index (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Range n) = n

data Shifted n Source #

Shifted denotes a range defined by the start index and the length.

>>> Shape.indices (Shape.Shifted (-4) (8::Int))
[-4,-3,-2,-1,0,1,2,3]

Constructors

Shifted 

Instances

Instances details
Functor Shifted Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

fmap :: (a -> b) -> Shifted a -> Shifted b #

(<$) :: a -> Shifted b -> Shifted a #

Storable n => Storable (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

sizeOf :: Shifted n -> Int #

alignment :: Shifted n -> Int #

peekElemOff :: Ptr (Shifted n) -> Int -> IO (Shifted n) #

pokeElemOff :: Ptr (Shifted n) -> Int -> Shifted n -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Shifted n) #

pokeByteOff :: Ptr b -> Int -> Shifted n -> IO () #

peek :: Ptr (Shifted n) -> IO (Shifted n) #

poke :: Ptr (Shifted n) -> Shifted n -> IO () #

Show n => Show (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Shifted n -> ShowS #

show :: Shifted n -> String #

showList :: [Shifted n] -> ShowS #

Integral n => C (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Shifted n -> Int Source #

Integral n => Indexed (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Shifted n) Source #

Integral n => InvIndexed (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

NFData n => NFData (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Shifted n -> () #

Eq n => Eq (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Shifted n -> Shifted n -> Bool #

(/=) :: Shifted n -> Shifted n -> Bool #

type Index (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Shifted n) = n

data Enumeration n Source #

Enumeration denotes a shape of fixed size that is defined by Enum and Bounded methods. For correctness it is necessary that the Enum and Bounded instances are properly implemented. Automatically derived instances are fine.

>>> Shape.indices (Shape.Enumeration :: Shape.Enumeration Ordering)
[LT,EQ,GT]

Constructors

Enumeration 

Instances

Instances details
Storable (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Show (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

(Enum n, Bounded n) => C (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Enumeration n -> Int Source #

(Enum n, Bounded n) => Indexed (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Enumeration n) Source #

(Enum n, Bounded n) => InvIndexed (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

(Enum n, Bounded n) => Static (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

NFData (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Enumeration n -> () #

Eq (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Enumeration n) = n

newtype Deferred sh Source #

This data type wraps another array shape. Its index type is a wrapped Int. The advantages are: No conversion forth and back Int and Index sh. You can convert once using deferIndex and revealIndex whenever you need your application specific index type. No need for e.g. Storable (Index sh), because Int is already Storable. You get Indexed and InvIndexed instances without the need for an Index type. The disadvantage is: A deferred index should be bound to a specific shape, but this is not checked. That is, you may obtain a deferred index for one shape and accidentally abuse it for another shape without a warning.

Example:

>>> :{
let sh2 = (Shape.ZeroBased (2::Int), Shape.ZeroBased (2::Int)) in
let sh3 = (Shape.ZeroBased (3::Int), Shape.ZeroBased (3::Int)) in
(Shape.offset sh3 $ Shape.indexFromOffset sh2 3,
 Shape.offset (Shape.Deferred sh3) $
   Shape.indexFromOffset (Shape.Deferred sh2) 3)
:}
(4,3)

Constructors

Deferred sh 

Instances

Instances details
Show sh => Show (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Deferred sh -> ShowS #

show :: Deferred sh -> String #

showList :: [Deferred sh] -> ShowS #

C sh => C (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Deferred sh -> Int Source #

C sh => Indexed (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Deferred sh) Source #

C sh => InvIndexed (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Static sh => Static (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Deferred sh Source #

NFData sh => NFData (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Deferred sh -> () #

Eq sh => Eq (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Deferred sh -> Deferred sh -> Bool #

(/=) :: Deferred sh -> Deferred sh -> Bool #

type Index (Deferred sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

newtype DeferredIndex sh Source #

DeferredIndex has an Ord instance that is based on the storage order in memory. This way, you can put DeferredIndex values in a Set or use them as keys in a Map even if Index sh has no Ord instance. The downside is, that the ordering of DeferredIndex sh may differ from the one of Index sh.

Constructors

DeferredIndex Int 

Instances

Instances details
Storable (DeferredIndex sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Show (DeferredIndex sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Eq (DeferredIndex sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Ord (DeferredIndex sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

deferIndex :: (Indexed sh, Index sh ~ ix) => sh -> ix -> DeferredIndex sh Source #

revealIndex :: (InvIndexed sh, Index sh ~ ix) => sh -> DeferredIndex sh -> ix Source #

data sh0 ::+ sh1 infixr 5 Source #

Row-major composition of two dimensions.

>>> Shape.indices (Shape.ZeroBased (3::Int) ::+ Shape.Range 'a' 'c')
[Left 0,Left 1,Left 2,Right 'a',Right 'b',Right 'c']

Constructors

sh0 ::+ sh1 infixr 5 

Instances

Instances details
(Show sh0, Show sh1) => Show (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> (sh0 ::+ sh1) -> ShowS #

show :: (sh0 ::+ sh1) -> String #

showList :: [sh0 ::+ sh1] -> ShowS #

(C sh0, C sh1) => C (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: (sh0 ::+ sh1) -> Int Source #

(Indexed sh0, Indexed sh1) => Indexed (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (sh0 ::+ sh1) Source #

Methods

indices :: (sh0 ::+ sh1) -> [Index (sh0 ::+ sh1)] Source #

offset :: (sh0 ::+ sh1) -> Index (sh0 ::+ sh1) -> Int Source #

uncheckedOffset :: (sh0 ::+ sh1) -> Index (sh0 ::+ sh1) -> Int Source #

unifiedOffset :: Checking check => (sh0 ::+ sh1) -> Index (sh0 ::+ sh1) -> Result check Int Source #

inBounds :: (sh0 ::+ sh1) -> Index (sh0 ::+ sh1) -> Bool Source #

sizeOffset :: (sh0 ::+ sh1) -> (Int, Index (sh0 ::+ sh1) -> Int) Source #

uncheckedSizeOffset :: (sh0 ::+ sh1) -> (Int, Index (sh0 ::+ sh1) -> Int) Source #

unifiedSizeOffset :: Checking check => (sh0 ::+ sh1) -> (Int, Index (sh0 ::+ sh1) -> Result check Int) Source #

(InvIndexed sh0, InvIndexed sh1) => InvIndexed (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: (sh0 ::+ sh1) -> Int -> Index (sh0 ::+ sh1) Source #

uncheckedIndexFromOffset :: (sh0 ::+ sh1) -> Int -> Index (sh0 ::+ sh1) Source #

unifiedIndexFromOffset :: Checking check => (sh0 ::+ sh1) -> Int -> Result check (Index (sh0 ::+ sh1)) Source #

(Pattern sh0, Pattern sh1) => Pattern (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (sh0 ::+ sh1) x Source #

Methods

indexPattern :: (Index (sh0 ::+ sh1) -> x) -> (sh0 ::+ sh1) -> DataPattern (sh0 ::+ sh1) x Source #

(Static sh0, Static sh1) => Static (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: sh0 ::+ sh1 Source #

(NFData sh0, NFData sh1) => NFData (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: (sh0 ::+ sh1) -> () #

(Eq sh0, Eq sh1) => Eq (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: (sh0 ::+ sh1) -> (sh0 ::+ sh1) -> Bool #

(/=) :: (sh0 ::+ sh1) -> (sh0 ::+ sh1) -> Bool #

type Index (sh0 ::+ sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (sh0 ::+ sh1) = Either (Index sh0) (Index sh1)
type DataPattern (sh0 ::+ sh1) x Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type DataPattern (sh0 ::+ sh1) x = DataPattern sh0 x ::+ DataPattern sh1 x

newtype Square sh Source #

Square is like a Cartesian product, but it is statically asserted that both dimension shapes match.

>>> Shape.indices $ Shape.Square $ Shape.ZeroBased (3::Int)
[(0,0),(0,1),(0,2),(1,0),(1,1),(1,2),(2,0),(2,1),(2,2)]

Constructors

Square 

Fields

Instances

Instances details
Applicative Square Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

pure :: a -> Square a #

(<*>) :: Square (a -> b) -> Square a -> Square b #

liftA2 :: (a -> b -> c) -> Square a -> Square b -> Square c #

(*>) :: Square a -> Square b -> Square b #

(<*) :: Square a -> Square b -> Square a #

Functor Square Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

fmap :: (a -> b) -> Square a -> Square b #

(<$) :: a -> Square b -> Square a #

Storable sh => Storable (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

sizeOf :: Square sh -> Int #

alignment :: Square sh -> Int #

peekElemOff :: Ptr (Square sh) -> Int -> IO (Square sh) #

pokeElemOff :: Ptr (Square sh) -> Int -> Square sh -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Square sh) #

pokeByteOff :: Ptr b -> Int -> Square sh -> IO () #

peek :: Ptr (Square sh) -> IO (Square sh) #

poke :: Ptr (Square sh) -> Square sh -> IO () #

Show sh => Show (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Square sh -> ShowS #

show :: Square sh -> String #

showList :: [Square sh] -> ShowS #

C sh => C (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Square sh -> Int Source #

Indexed sh => Indexed (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Square sh) Source #

Methods

indices :: Square sh -> [Index (Square sh)] Source #

offset :: Square sh -> Index (Square sh) -> Int Source #

uncheckedOffset :: Square sh -> Index (Square sh) -> Int Source #

unifiedOffset :: Checking check => Square sh -> Index (Square sh) -> Result check Int Source #

inBounds :: Square sh -> Index (Square sh) -> Bool Source #

sizeOffset :: Square sh -> (Int, Index (Square sh) -> Int) Source #

uncheckedSizeOffset :: Square sh -> (Int, Index (Square sh) -> Int) Source #

unifiedSizeOffset :: Checking check => Square sh -> (Int, Index (Square sh) -> Result check Int) Source #

InvIndexed sh => InvIndexed (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Pattern sh => Pattern (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (Square sh) x Source #

Methods

indexPattern :: (Index (Square sh) -> x) -> Square sh -> DataPattern (Square sh) x Source #

NFData sh => NFData (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Square sh -> () #

Eq sh => Eq (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Square sh -> Square sh -> Bool #

(/=) :: Square sh -> Square sh -> Bool #

type Index (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Square sh) = (Index sh, Index sh)
type DataPattern (Square sh) x Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type DataPattern (Square sh) x

newtype Cube sh Source #

Cube is like a Cartesian product, but it is statically asserted that both dimension shapes match.

>>> Shape.indices $ Shape.Cube $ Shape.ZeroBased (2::Int)
[(0,0,0),(0,0,1),(0,1,0),(0,1,1),(1,0,0),(1,0,1),(1,1,0),(1,1,1)]

Constructors

Cube 

Fields

Instances

Instances details
Applicative Cube Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

pure :: a -> Cube a #

(<*>) :: Cube (a -> b) -> Cube a -> Cube b #

liftA2 :: (a -> b -> c) -> Cube a -> Cube b -> Cube c #

(*>) :: Cube a -> Cube b -> Cube b #

(<*) :: Cube a -> Cube b -> Cube a #

Functor Cube Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

fmap :: (a -> b) -> Cube a -> Cube b #

(<$) :: a -> Cube b -> Cube a #

Storable sh => Storable (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

sizeOf :: Cube sh -> Int #

alignment :: Cube sh -> Int #

peekElemOff :: Ptr (Cube sh) -> Int -> IO (Cube sh) #

pokeElemOff :: Ptr (Cube sh) -> Int -> Cube sh -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Cube sh) #

pokeByteOff :: Ptr b -> Int -> Cube sh -> IO () #

peek :: Ptr (Cube sh) -> IO (Cube sh) #

poke :: Ptr (Cube sh) -> Cube sh -> IO () #

Show sh => Show (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Cube sh -> ShowS #

show :: Cube sh -> String #

showList :: [Cube sh] -> ShowS #

C sh => C (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Cube sh -> Int Source #

Indexed sh => Indexed (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Cube sh) Source #

Methods

indices :: Cube sh -> [Index (Cube sh)] Source #

offset :: Cube sh -> Index (Cube sh) -> Int Source #

uncheckedOffset :: Cube sh -> Index (Cube sh) -> Int Source #

unifiedOffset :: Checking check => Cube sh -> Index (Cube sh) -> Result check Int Source #

inBounds :: Cube sh -> Index (Cube sh) -> Bool Source #

sizeOffset :: Cube sh -> (Int, Index (Cube sh) -> Int) Source #

uncheckedSizeOffset :: Cube sh -> (Int, Index (Cube sh) -> Int) Source #

unifiedSizeOffset :: Checking check => Cube sh -> (Int, Index (Cube sh) -> Result check Int) Source #

InvIndexed sh => InvIndexed (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

NFData sh => NFData (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Cube sh -> () #

Eq sh => Eq (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Cube sh -> Cube sh -> Bool #

(/=) :: Cube sh -> Cube sh -> Bool #

type Index (Cube sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Cube sh) = (Index sh, Index sh, Index sh)

data Triangular part size Source #

>>> Shape.indices $ Shape.Triangular Shape.Upper $ Shape.ZeroBased (3::Int)
[(0,0),(0,1),(0,2),(1,1),(1,2),(2,2)]
>>> Shape.indices $ Shape.Triangular Shape.Lower $ Shape.ZeroBased (3::Int)
[(0,0),(1,0),(1,1),(2,0),(2,1),(2,2)]

Constructors

Triangular 

Fields

Instances

Instances details
(Show part, Show size) => Show (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Triangular part size -> ShowS #

show :: Triangular part size -> String #

showList :: [Triangular part size] -> ShowS #

(TriangularPart part, C size) => C (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Triangular part size -> Int Source #

(TriangularPart part, Indexed size) => Indexed (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Triangular part size) Source #

Methods

indices :: Triangular part size -> [Index (Triangular part size)] Source #

offset :: Triangular part size -> Index (Triangular part size) -> Int Source #

uncheckedOffset :: Triangular part size -> Index (Triangular part size) -> Int Source #

unifiedOffset :: Checking check => Triangular part size -> Index (Triangular part size) -> Result check Int Source #

inBounds :: Triangular part size -> Index (Triangular part size) -> Bool Source #

sizeOffset :: Triangular part size -> (Int, Index (Triangular part size) -> Int) Source #

uncheckedSizeOffset :: Triangular part size -> (Int, Index (Triangular part size) -> Int) Source #

unifiedSizeOffset :: Checking check => Triangular part size -> (Int, Index (Triangular part size) -> Result check Int) Source #

(TriangularPart part, InvIndexed size) => InvIndexed (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: Triangular part size -> Int -> Index (Triangular part size) Source #

uncheckedIndexFromOffset :: Triangular part size -> Int -> Index (Triangular part size) Source #

unifiedIndexFromOffset :: Checking check => Triangular part size -> Int -> Result check (Index (Triangular part size)) Source #

(TriangularPart part, Static size) => Static (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Triangular part size Source #

(TriangularPart part, NFData size) => NFData (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Triangular part size -> () #

(TriangularPart part, Eq size) => Eq (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Triangular part size -> Triangular part size -> Bool #

(/=) :: Triangular part size -> Triangular part size -> Bool #

type Index (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Triangular part size) = (Index size, Index size)

data Lower Source #

Constructors

Lower 

Instances

Instances details
Show Lower Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Lower -> ShowS #

show :: Lower -> String #

showList :: [Lower] -> ShowS #

Eq Lower Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

data Upper Source #

Constructors

Upper 

Instances

Instances details
Show Upper Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Upper -> ShowS #

show :: Upper -> String #

showList :: [Upper] -> ShowS #

Eq Upper Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

triangleRoot :: Floating a => a -> a Source #

data Simplex order coll f size Source #

Simplex is a generalization of Triangular to more than two dimensions. Indices are tuples of fixed size with elements ordered in ascending, strictly ascending, descending or strictly descending order. "Order" refers to the index order in indices. In order to avoid confusion we suggest that the order of indices is consistent with <=.

Obviously, offset implements ranking and indexFromOffset implements unranking of combinations (in the combinatorial sense) with or without repetitions.

>>> Shape.indices $ Shape.simplexAscending (replicate 3 Shape.AllDistinct) $ Shape.ZeroBased (4::Int)
[[0,1,2],[0,1,3],[0,2,3],[1,2,3]]
>>> Shape.indices $ Shape.simplexAscending (replicate 3 Shape.SomeRepetitive) $ Shape.ZeroBased (3::Int)
[[0,0,0],[0,0,1],[0,0,2],[0,1,1],[0,1,2],[0,2,2],[1,1,1],[1,1,2],[1,2,2],[2,2,2]]
>>> Shape.indices $ Shape.simplexAscending [Shape.Repetitive,Shape.Distinct,Shape.Repetitive] $ Shape.ZeroBased (4::Int)
[[0,0,1],[0,0,2],[0,0,3],[0,1,2],[0,1,3],[0,2,3],[1,1,2],[1,1,3],[1,2,3],[2,2,3]]
>>> Shape.indices $ Shape.simplexAscending [Shape.Repetitive,Shape.Distinct,Shape.Distinct] $ Shape.ZeroBased (4::Int)
[[0,0,1],[0,0,2],[0,0,3],[0,1,2],[0,1,3],[0,2,3],[1,1,2],[1,1,3],[1,2,3],[2,2,3]]
>>> Shape.indices $ Shape.simplexDescending (replicate 3 Shape.AllDistinct) $ Shape.ZeroBased (4::Int)
[[2,1,0],[3,1,0],[3,2,0],[3,2,1]]
>>> Shape.indices $ Shape.simplexDescending (replicate 3 Shape.SomeRepetitive) $ Shape.ZeroBased (3::Int)
[[0,0,0],[1,0,0],[1,1,0],[1,1,1],[2,0,0],[2,1,0],[2,1,1],[2,2,0],[2,2,1],[2,2,2]]
>>> Shape.indices $ Shape.simplexDescending [Shape.Repetitive,Shape.Distinct,Shape.Repetitive] $ Shape.ZeroBased (4::Int)
[[1,1,0],[2,1,0],[2,2,0],[2,2,1],[3,1,0],[3,2,0],[3,2,1],[3,3,0],[3,3,1],[3,3,2]]
>>> Shape.indices $ Shape.simplexDescending [Shape.Repetitive,Shape.Distinct,Shape.Distinct] $ Shape.ZeroBased (4::Int)
[[1,1,0],[2,1,0],[2,2,0],[2,2,1],[3,1,0],[3,2,0],[3,2,1],[3,3,0],[3,3,1],[3,3,2]]

Constructors

Simplex 

Fields

Instances

Instances details
(SimplexOrderC order, Show coll, Show1 f, Show size) => Show (Simplex order coll f size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Simplex order coll f size -> ShowS #

show :: Simplex order coll f size -> String #

showList :: [Simplex order coll f size] -> ShowS #

(SimplexOrderC order, CollisionC coll, Traversable f, C size) => C (Simplex order coll f size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Simplex order coll f size -> Int Source #

(SimplexOrderC order, CollisionC coll, Traversable f, Eq1 f, Indexed size) => Indexed (Simplex order coll f size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Simplex order coll f size) Source #

Methods

indices :: Simplex order coll f size -> [Index (Simplex order coll f size)] Source #

offset :: Simplex order coll f size -> Index (Simplex order coll f size) -> Int Source #

uncheckedOffset :: Simplex order coll f size -> Index (Simplex order coll f size) -> Int Source #

unifiedOffset :: Checking check => Simplex order coll f size -> Index (Simplex order coll f size) -> Result check Int Source #

inBounds :: Simplex order coll f size -> Index (Simplex order coll f size) -> Bool Source #

sizeOffset :: Simplex order coll f size -> (Int, Index (Simplex order coll f size) -> Int) Source #

uncheckedSizeOffset :: Simplex order coll f size -> (Int, Index (Simplex order coll f size) -> Int) Source #

unifiedSizeOffset :: Checking check => Simplex order coll f size -> (Int, Index (Simplex order coll f size) -> Result check Int) Source #

(SimplexOrderC order, CollisionC coll, Traversable f, Eq1 f, InvIndexed size) => InvIndexed (Simplex order coll f size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

indexFromOffset :: Simplex order coll f size -> Int -> Index (Simplex order coll f size) Source #

uncheckedIndexFromOffset :: Simplex order coll f size -> Int -> Index (Simplex order coll f size) Source #

unifiedIndexFromOffset :: Checking check => Simplex order coll f size -> Int -> Result check (Index (Simplex order coll f size)) Source #

type Index (Simplex order coll f size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Simplex order coll f size) = f (Index size)

simplexAscending :: f coll -> size -> SimplexAscending coll f size Source #

simplexDescending :: f coll -> size -> SimplexDescending coll f size Source #

data Ascending Source #

Instances

Instances details
SimplexOrderC Ascending Source # 
Instance details

Defined in Data.Array.Comfort.Shape

data Descending Source #

Instances

Instances details
SimplexOrderC Descending Source # 
Instance details

Defined in Data.Array.Comfort.Shape

data SimplexOrder order where Source #

Instances

Instances details
Show (SimplexOrder order) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> SimplexOrder order -> ShowS #

show :: SimplexOrder order -> String #

showList :: [SimplexOrder order] -> ShowS #

Eq (SimplexOrder order) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: SimplexOrder order -> SimplexOrder order -> Bool #

(/=) :: SimplexOrder order -> SimplexOrder order -> Bool #

class SimplexOrderC order Source #

Instances

Instances details
SimplexOrderC Ascending Source # 
Instance details

Defined in Data.Array.Comfort.Shape

SimplexOrderC Descending Source # 
Instance details

Defined in Data.Array.Comfort.Shape

data AllDistinct Source #

Constructors

AllDistinct 

Instances

Instances details
Show AllDistinct Source # 
Instance details

Defined in Data.Array.Comfort.Shape

CollisionC AllDistinct Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Eq AllDistinct Source # 
Instance details

Defined in Data.Array.Comfort.Shape

class CollisionC coll Source #

Minimal complete definition

repetitionAllowed

Instances

Instances details
CollisionC AllDistinct Source # 
Instance details

Defined in Data.Array.Comfort.Shape

CollisionC Collision Source # 
Instance details

Defined in Data.Array.Comfort.Shape

CollisionC SomeRepetitive Source # 
Instance details

Defined in Data.Array.Comfort.Shape

newtype Cyclic n Source #

Cyclic is a shape, where the indices wrap around at the array boundaries. E.g.

let shape = Shape.Cyclic (10::Int) in Shape.offset shape (-1) == Shape.offset shape 9

This also means that there are multiple indices that address the same array element.

>>> Shape.indices (Shape.Cyclic (7::Int))
[0,1,2,3,4,5,6]

Constructors

Cyclic 

Fields

Instances

Instances details
Applicative Cyclic Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

pure :: a -> Cyclic a #

(<*>) :: Cyclic (a -> b) -> Cyclic a -> Cyclic b #

liftA2 :: (a -> b -> c) -> Cyclic a -> Cyclic b -> Cyclic c #

(*>) :: Cyclic a -> Cyclic b -> Cyclic b #

(<*) :: Cyclic a -> Cyclic b -> Cyclic a #

Functor Cyclic Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

fmap :: (a -> b) -> Cyclic a -> Cyclic b #

(<$) :: a -> Cyclic b -> Cyclic a #

Storable n => Storable (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

sizeOf :: Cyclic n -> Int #

alignment :: Cyclic n -> Int #

peekElemOff :: Ptr (Cyclic n) -> Int -> IO (Cyclic n) #

pokeElemOff :: Ptr (Cyclic n) -> Int -> Cyclic n -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Cyclic n) #

pokeByteOff :: Ptr b -> Int -> Cyclic n -> IO () #

peek :: Ptr (Cyclic n) -> IO (Cyclic n) #

poke :: Ptr (Cyclic n) -> Cyclic n -> IO () #

Show n => Show (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Cyclic n -> ShowS #

show :: Cyclic n -> String #

showList :: [Cyclic n] -> ShowS #

Integral n => C (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Cyclic n -> Int Source #

Integral n => Indexed (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Cyclic n) Source #

Integral n => InvIndexed (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

NFData n => NFData (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Cyclic n -> () #

Eq n => Eq (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Cyclic n -> Cyclic n -> Bool #

(/=) :: Cyclic n -> Cyclic n -> Bool #

type Index (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Cyclic n) = n

newtype NestedTuple ixtype tuple Source #

Shape for arrays that hold elements that can alternatively be stored in nested tuples.

Constructors

NestedTuple 

Fields

Instances

Instances details
Show tuple => Show (NestedTuple ixtype tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> NestedTuple ixtype tuple -> ShowS #

show :: NestedTuple ixtype tuple -> String #

showList :: [NestedTuple ixtype tuple] -> ShowS #

ElementTuple tuple => C (NestedTuple ixtype tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: NestedTuple ixtype tuple -> Int Source #

AccessorTuple tuple => Indexed (NestedTuple TupleAccessor tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (NestedTuple TupleAccessor tuple) Source #

ElementTuple tuple => Indexed (NestedTuple TupleIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (NestedTuple TupleIndex tuple) Source #

ElementTuple tuple => Pattern (NestedTuple TupleIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (NestedTuple TupleIndex tuple) x Source #

StaticTuple tuple => Static (NestedTuple ixtype tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: NestedTuple ixtype tuple Source #

ElementTuple tuple => NFData (NestedTuple ixtype tuple) Source #
>>> rnf (Shape.NestedTuple (Shape.Element 1, Shape.Element 2))
()
>>> rnf (Shape.NestedTuple (Shape.Element 1, (Shape.Element 2, Shape.Element 3)))
()
>>> isBottom $ rnf (Shape.NestedTuple (Shape.Element undefined, Shape.Element 2))
True
>>> isBottom $ rnf (Shape.NestedTuple (Shape.Element undefined, (Shape.Element 2, Shape.Element 3)))
True
>>> isBottom $ rnf (Shape.NestedTuple (Shape.Element 1, (Shape.Element undefined, Shape.Element 3)))
True
>>> isBottom $ rnf (Shape.NestedTuple (Shape.Element 1, (Shape.Element 2, Shape.Element undefined)))
True
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: NestedTuple ixtype tuple -> () #

Eq tuple => Eq (NestedTuple ixtype tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: NestedTuple ixtype tuple -> NestedTuple ixtype tuple -> Bool #

(/=) :: NestedTuple ixtype tuple -> NestedTuple ixtype tuple -> Bool #

type Index (NestedTuple TupleAccessor tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (NestedTuple TupleAccessor tuple) = tuple -> Element
type Index (NestedTuple TupleIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type DataPattern (NestedTuple TupleIndex tuple) x Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type DataPattern (NestedTuple TupleIndex tuple) x = DataTuple tuple x

class ElementTuple tuple => AccessorTuple tuple where Source #

Methods

tupleAccessors :: tuple -> [tuple -> Element] Source #

Instances

Instances details
AccessorTuple Element Source # 
Instance details

Defined in Data.Array.Comfort.Shape

AccessorTuple () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

tupleAccessors :: () -> [() -> Element] Source #

(AccessorTuple a, RealFloat a) => AccessorTuple (Complex a) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

(AccessorTuple a, AccessorTuple b) => AccessorTuple (a, b) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

tupleAccessors :: (a, b) -> [(a, b) -> Element] Source #

(AccessorTuple a, AccessorTuple b, AccessorTuple c) => AccessorTuple (a, b, c) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

tupleAccessors :: (a, b, c) -> [(a, b, c) -> Element] Source #

(AccessorTuple a, AccessorTuple b, AccessorTuple c, AccessorTuple d) => AccessorTuple (a, b, c, d) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

tupleAccessors :: (a, b, c, d) -> [(a, b, c, d) -> Element] Source #

class (ElementTuple tuple, Eq tuple) => StaticTuple tuple where Source #

Methods

staticTuple :: State Element tuple Source #

Instances

Instances details
StaticTuple Element Source # 
Instance details

Defined in Data.Array.Comfort.Shape

StaticTuple () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

StaticTuple a => StaticTuple (Complex a) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

(StaticTuple a, StaticTuple b) => StaticTuple (a, b) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

staticTuple :: State Element (a, b) Source #

(StaticTuple a, StaticTuple b, StaticTuple c) => StaticTuple (a, b, c) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

staticTuple :: State Element (a, b, c) Source #

(StaticTuple a, StaticTuple b, StaticTuple c, StaticTuple d) => StaticTuple (a, b, c, d) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

staticTuple :: State Element (a, b, c, d) Source #

newtype Element Source #

Constructors

Element Int 

Instances

Instances details
Show Element Source # 
Instance details

Defined in Data.Array.Comfort.Shape

AccessorTuple Element Source # 
Instance details

Defined in Data.Array.Comfort.Shape

ElementTuple Element Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataTuple Element x Source #

Methods

indexTupleA :: Applicative f => (Element -> f a) -> Element -> f (DataTuple Element a) Source #

StaticTuple Element Source # 
Instance details

Defined in Data.Array.Comfort.Shape

NFData Element Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Element -> () #

Eq Element Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

type DataTuple Element x Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type DataTuple Element x = x

data TupleIndex Source #

Instances

Instances details
ElementTuple tuple => Indexed (NestedTuple TupleIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (NestedTuple TupleIndex tuple) Source #

ElementTuple tuple => Pattern (NestedTuple TupleIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataPattern (NestedTuple TupleIndex tuple) x Source #

type Index (NestedTuple TupleIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type DataPattern (NestedTuple TupleIndex tuple) x Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type DataPattern (NestedTuple TupleIndex tuple) x = DataTuple tuple x

data ElementIndex tuple Source #

Instances

Instances details
Show (ElementIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> ElementIndex tuple -> ShowS #

show :: ElementIndex tuple -> String #

showList :: [ElementIndex tuple] -> ShowS #

Eq (ElementIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: ElementIndex tuple -> ElementIndex tuple -> Bool #

(/=) :: ElementIndex tuple -> ElementIndex tuple -> Bool #

Ord (ElementIndex tuple) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

compare :: ElementIndex tuple -> ElementIndex tuple -> Ordering #

(<) :: ElementIndex tuple -> ElementIndex tuple -> Bool #

(<=) :: ElementIndex tuple -> ElementIndex tuple -> Bool #

(>) :: ElementIndex tuple -> ElementIndex tuple -> Bool #

(>=) :: ElementIndex tuple -> ElementIndex tuple -> Bool #

max :: ElementIndex tuple -> ElementIndex tuple -> ElementIndex tuple #

min :: ElementIndex tuple -> ElementIndex tuple -> ElementIndex tuple #

class ElementTuple tuple where Source #

Associated Types

type DataTuple tuple x Source #

Methods

indexTupleA :: Applicative f => (Element -> f a) -> tuple -> f (DataTuple tuple a) Source #

Instances

Instances details
ElementTuple Element Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataTuple Element x Source #

Methods

indexTupleA :: Applicative f => (Element -> f a) -> Element -> f (DataTuple Element a) Source #

ElementTuple () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataTuple () x Source #

Methods

indexTupleA :: Applicative f => (Element -> f a) -> () -> f (DataTuple () a) Source #

ElementTuple a => ElementTuple (Complex a) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataTuple (Complex a) x Source #

Methods

indexTupleA :: Applicative f => (Element -> f a0) -> Complex a -> f (DataTuple (Complex a) a0) Source #

(ElementTuple a, ElementTuple b) => ElementTuple (a, b) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataTuple (a, b) x Source #

Methods

indexTupleA :: Applicative f => (Element -> f a0) -> (a, b) -> f (DataTuple (a, b) a0) Source #

(ElementTuple a, ElementTuple b, ElementTuple c) => ElementTuple (a, b, c) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataTuple (a, b, c) x Source #

Methods

indexTupleA :: Applicative f => (Element -> f a0) -> (a, b, c) -> f (DataTuple (a, b, c) a0) Source #

(ElementTuple a, ElementTuple b, ElementTuple c, ElementTuple d) => ElementTuple (a, b, c, d) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type DataTuple (a, b, c, d) x Source #

Methods

indexTupleA :: Applicative f => (Element -> f a0) -> (a, b, c, d) -> f (DataTuple (a, b, c, d) a0) Source #

newtype Record f Source #

Shape for arrays that hold elements that can alternatively be stored in a Traversable record.

Constructors

Record 

Fields

Instances

Instances details
Foldable f => C (Record f) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Record f -> Int Source #

Foldable f => Indexed (Record f) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Record f) Source #

(Applicative f, Traversable f) => Static (Record f) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Record f Source #

Foldable f => Eq (Record f) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Record f -> Record f -> Bool #

(/=) :: Record f -> Record f -> Bool #

type Index (Record f) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Record f) = FieldIndex f

data FieldIndex (f :: * -> *) Source #

Instances

Instances details
Show (FieldIndex f) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Eq (FieldIndex f) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: FieldIndex f -> FieldIndex f -> Bool #

(/=) :: FieldIndex f -> FieldIndex f -> Bool #

data Constructed tag Source #

Instances

Instances details
Show (Constructed tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Constructed tag -> ShowS #

show :: Constructed tag -> String #

showList :: [Constructed tag] -> ShowS #

C (Constructed tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: Constructed tag -> Int Source #

Indexed (Constructed tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Constructed tag) Source #

InvIndexed (Constructed tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Eq (Constructed tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Constructed tag -> Constructed tag -> Bool #

(/=) :: Constructed tag -> Constructed tag -> Bool #

type Index (Constructed tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Constructed tag) = ConsIndex tag

data ConsIndex tag Source #

Instances

Instances details
Show (ConsIndex tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> ConsIndex tag -> ShowS #

show :: ConsIndex tag -> String #

showList :: [ConsIndex tag] -> ShowS #

Eq (ConsIndex tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: ConsIndex tag -> ConsIndex tag -> Bool #

(/=) :: ConsIndex tag -> ConsIndex tag -> Bool #

data Construction tag a Source #

Instances

Instances details
Applicative (Construction tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

pure :: a -> Construction tag a #

(<*>) :: Construction tag (a -> b) -> Construction tag a -> Construction tag b #

liftA2 :: (a -> b -> c) -> Construction tag a -> Construction tag b -> Construction tag c #

(*>) :: Construction tag a -> Construction tag b -> Construction tag b #

(<*) :: Construction tag a -> Construction tag b -> Construction tag a #

Functor (Construction tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

fmap :: (a -> b) -> Construction tag a -> Construction tag b #

(<$) :: a -> Construction tag b -> Construction tag a #

Monad (Construction tag) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(>>=) :: Construction tag a -> (a -> Construction tag b) -> Construction tag b #

(>>) :: Construction tag a -> Construction tag b -> Construction tag b #

return :: a -> Construction tag a #