comfort-array-0.4.1: Arrays where the index type is a function of the shape type
Safe HaskellNone
LanguageHaskell98

Data.Array.Comfort.Shape

Synopsis

Documentation

class C sh where Source #

Minimal complete definition

size

Methods

size :: sh -> Int Source #

uncheckedSize :: sh -> Int Source #

Instances

Instances details
C () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

size :: () -> Int Source #

uncheckedSize :: () -> Int Source #

C Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

Methods

size :: Set n -> Int Source #

uncheckedSize :: Set n -> Int Source #

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

Methods

size :: Cube sh -> Int Source #

uncheckedSize :: Cube sh -> Int Source #

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

Defined in Data.Array.Comfort.Shape

Methods

size :: Square sh -> Int Source #

uncheckedSize :: Square sh -> Int Source #

C sh => C (Deferred sh) 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

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Container

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

Defined in Data.Array.Comfort.Shape

Methods

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

uncheckedSize :: (sh0, sh1) -> 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 #

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

uncheckedSize :: (sh0 :+: sh1) -> 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 #

uncheckedSize :: Triangular part size -> 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 #

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

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

Defined in Data.Array.Comfort.Shape

Methods

size :: Tagged s sh -> Int Source #

uncheckedSize :: Tagged s sh -> Int Source #

class C sh => Indexed sh where Source #

Minimal complete definition

indices, (sizeOffset | offset), inBounds

Associated Types

type Index sh :: * Source #

Methods

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

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

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

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

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

uncheckedSizeOffset :: sh -> (Int, Index sh -> 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 #

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

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

uncheckedSizeOffset :: () -> (Int, Index () -> Int) 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.

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

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 #

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Cyclic n) 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 #

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 #

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Square sh) 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 (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Shifted n) Source #

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Range n) Source #

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (OneBased n) Source #

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (ZeroBased n) 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 #

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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 #

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 #

class Indexed sh => InvIndexed sh where Source #

Minimal complete definition

indexFromOffset

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 #

Instances

Instances details
InvIndexed () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

InvIndexed sh => InvIndexed (Square sh) 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 (Shifted 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 (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Integral n => InvIndexed (ZeroBased 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 #

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

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

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

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

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

Defined in Data.Array.Comfort.Shape

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

Methods

static :: sh Source #

Instances

Instances details
Static () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: () Source #

Static Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Zero 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

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

Defined in Data.Array.Comfort.Shape

Methods

static :: (sh0, sh1) Source #

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

Defined in Data.Array.Comfort.Shape

Methods

static :: sh0 :+: sh1 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 sh2) => Static (sh0, sh1, sh2) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

Defined in Data.Array.Comfort.Shape

Methods

static :: Tagged s sh Source #

data Zero Source #

Constructors

Zero 

Instances

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

Show Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Zero -> ShowS #

show :: Zero -> String #

showList :: [Zero] -> ShowS #

Static Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

static :: Zero Source #

C Zero Source # 
Instance details

Defined in Data.Array.Comfort.Shape

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
Functor ZeroBased Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

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 #

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 #

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

Defined in Data.Array.Comfort.Shape

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

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

Defined in Data.Array.Comfort.Shape

Methods

rnf :: ZeroBased n -> () #

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (ZeroBased n) Source #

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

Defined in Data.Array.Comfort.Shape

type Index (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (ZeroBased n) = n

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
Functor OneBased Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

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 #

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 #

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 #

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

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

Defined in Data.Array.Comfort.Shape

Methods

rnf :: OneBased n -> () #

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (OneBased n) Source #

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

Defined in Data.Array.Comfort.Shape

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 #

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 #

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 #

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

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

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Range n -> () #

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Range n) Source #

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

Defined in Data.Array.Comfort.Shape

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 #

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 #

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 #

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

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

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Shifted n -> () #

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Shifted n) Source #

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

Defined in Data.Array.Comfort.Shape

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
Eq (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Show (Enumeration n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

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

(Enum n, Bounded n) => Static (Enumeration n) 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

(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) => C (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
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 #

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 #

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

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Deferred sh -> () #

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

Defined in Data.Array.Comfort.Shape

Methods

static :: Deferred sh Source #

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Deferred sh) Source #

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

Defined in Data.Array.Comfort.Shape

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
Eq (DeferredIndex sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Ord (DeferredIndex sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Show (DeferredIndex sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

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

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

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

Defined in Data.Array.Comfort.Shape

Methods

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

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

Defined in Data.Array.Comfort.Shape

Methods

static :: sh0 :+: sh1 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 #

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

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 #

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

Defined in Data.Array.Comfort.Shape

Methods

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

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

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

Defined in Data.Array.Comfort.Shape

type Index (sh0 :+: sh1) = Either (Index sh0) (Index sh1)

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
Functor Square Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

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 #

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 #

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 #

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

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

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Square sh -> () #

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Square sh) Source #

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

Defined in Data.Array.Comfort.Shape

Methods

size :: Square sh -> Int Source #

uncheckedSize :: Square sh -> Int Source #

type Index (Square sh) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Square sh) = (Index sh, Index sh)

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
Functor Cube Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

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 #

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 #

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 #

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

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

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Cube sh -> () #

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

Defined in Data.Array.Comfort.Shape

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 #

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 #

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

Defined in Data.Array.Comfort.Shape

Methods

size :: Cube sh -> Int Source #

uncheckedSize :: Cube sh -> Int Source #

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

(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, NFData size) => NFData (Triangular part size) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Triangular part size -> () #

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

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

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 #

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

Defined in Data.Array.Comfort.Shape

Methods

size :: Triangular part size -> Int Source #

uncheckedSize :: Triangular part size -> Int Source #

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
Eq Lower Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

Show Lower Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Lower -> ShowS #

show :: Lower -> String #

showList :: [Lower] -> ShowS #

data Upper Source #

Constructors

Upper 

Instances

Instances details
Eq Upper Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

Show Upper Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Upper -> ShowS #

show :: Upper -> String #

showList :: [Upper] -> ShowS #

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

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
Functor Cyclic Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

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

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

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 #

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 #

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 #

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

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

Defined in Data.Array.Comfort.Shape

Methods

rnf :: Cyclic n -> () #

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

Defined in Data.Array.Comfort.Shape

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

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Cyclic n) Source #

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

Defined in Data.Array.Comfort.Shape

type Index (Cyclic n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Cyclic n) = n