indices-1.5.0: indices

Safe HaskellNone
LanguageHaskell98

Data.Index

Contents

Description

The indices supplied by this module are static type and value-level linked lists. Since their type gives us information about them, recursion on indices can be unrolled easily.

Indices look like x:.y:.Z :: i:.j:.Z . The value is the actual index used, and the type is the upper-bound on that index.

For instance, one index of a 4x4 matrix is 2:.2:.Z :: 3:.3:.Z , and another index for a 1024x1024x1024 cube is 512:.512:.512:.Z :: 1024:.1024:.1024:.Z

Parts of this module are alternatively under Static and Runtime headings. Functions under Static headings should be inlined completely, and functions under Runtime will not. If you do not compile with optimisations on, ghc will not inline the "static" functions, which will then perform very poorly compared to their "runtime" counterparts.

Synopsis

Core

class (Bounded n, Integral n, Show n, Read n, Ix n, Dim n) => Index n Source

A single class encompassing all the instances an index should have.

Instances

(Bounded n, Integral n, Show n, Read n, Ix n, Dim n) => Index n 

class Ord n => Dim n where Source

Minimal complete definition

zero, unit, rank, size, reflect', next, prev, next', prev', toIndex, fromIndex', correct, correctOnce, overHead, lastDim, zipMin

Methods

zero :: n Source

All zeros

unit :: n Source

All ones

rank :: n -> Int Source

The number of dimensions in an index

size :: Proxy n -> Int Source

The size of the index

next' :: n -> n Source

Same as succ, but there are no boundary checks, so when maxBound is hit, it will wrap around to minBound / zero.

prev' :: n -> n Source

Same as pred, but there are no boundary checks, so when minBound / zero is hit, it will wrap around to maxBound.

toIndex :: n -> Int Source

Create an Int index.

fromIndex :: Int -> n Source

Create an index from its Int representation.

correct :: n -> n Source

Ensure an index is within its bounds.

zipMin :: n -> n -> n Source

Get the minimum values of two indices at each dimension

Instances

Dim Z 
(KnownNat x, Dim xs) => Dim ((:.) Nat x xs) 

class Rank a b where Source

Methods

setBound :: a -> b Source

Retain the rank, but change the upper bound

Instances

Rank Z Z 
Rank xs ys => Rank ((:.) k x xs) ((:.) k y ys)

Rank

data a :. b infixr 9 Source

Index constructor, analogous to :

The Applicative and Monad instances multiply in their bind operations, and their 'return'/'pure' creates an index whose first dimension is 1.

Constructors

!Int :. !b infixr 9 

Instances

KnownNat s => Monad ((:.) Nat s) 
Functor ((:.) k a) 
KnownNat s => Applicative ((:.) Nat s) 
Foldable ((:.) k a) 
Traversable ((:.) k a) 
Dim ((:.) k x xs) => Bounded ((:.) k x xs) 
(Dim ((:.) k x xs), Num xs) => Enum ((:.) k x xs) 
Eq b => Eq ((:.) k a b) 
(Integral xs, Dim ((:.) k x xs)) => Integral ((:.) k x xs) 
(Num xs, Dim ((:.) k x xs)) => Num ((:.) k x xs) 
Ord b => Ord ((:.) k a b) 
Read b => Read ((:.) k a b) 
(Num ((:.) k x xs), Dim ((:.) k x xs)) => Real ((:.) k x xs) 
Show b => Show ((:.) k a b) 
(Dim ((:.) k x xs), Num xs) => Ix ((:.) k x xs) 
Generic ((:.) k a b) 
(Dim ((:.) k x xs), Monoid xs) => Monoid ((:.) k x xs) 
(KnownNat x, Dim xs) => Dim ((:.) Nat x xs) 
Rank xs ys => Rank ((:.) k x xs) ((:.) k y ys)

Rank

type Rep ((:.) k a b) 

data Z Source

The zero index, used to end indices, just as '[]' ends a list.

Constructors

Z 

Instances

Ranges

class (Dim n, Range (ToPeano (Size n))) => Ranged n Source

Types that support static range operations

Instances

(Dim n, Range (ToPeano (Size n))) => Ranged n 

class Range n Source

Minimal complete definition

swithRange_, sfoldrRange_, sfoldlRange_, swithRangeIndices_, sfoldrRangeIndices_, sfoldlRangeIndices_

Instances

Range Zero 
Range n => Range (Succ n) 

data Peano Source

Peano numbers

Constructors

Zero 
Succ Peano 

type family ToPeano n :: Peano Source

Convert a Nat to a type-level Peano

Equations

ToPeano 0 = Zero 
ToPeano n = Succ (ToPeano (n - 1)) 

type family Size dim :: Nat Source

Compute the size of an index

Equations

Size (x :. Z) = x 
Size (x :. xs) = x * Size xs 

Static

sfoldlRange :: Ranged o => Proxy o -> (b -> o -> b) -> b -> b Source

See foldlRange

With optimisations, this compiles to an unrolled loop

sfoldrRange :: Ranged o => Proxy o -> (o -> b -> b) -> b -> b Source

See foldrRange

With optimisations, this compiles to an unrolled loop

swithRange :: (Applicative m, Ranged o) => Proxy o -> (o -> m ()) -> m () Source

See withRange

With optimisations, this compiles to an unrolled loop

Runtime

foldlRange :: Dim a => Proxy a -> (b -> a -> b) -> b -> b Source

Eager left fold over a range

 foldlRange r f z == foldl' f z (asProxyTypeOf range r)

foldrRange :: Dim a => Proxy a -> (a -> b -> b) -> b -> b Source

Lazy right fold over a range

 foldrRange r f z == foldr f z (asProxyTypeOf range r)

withRange :: (Applicative m, Dim a) => Proxy a -> (a -> m ()) -> m () Source

Compute something from a range

Over Int indices

Static

sfoldlRangeIndices :: Ranged o => Proxy o -> (b -> Int -> b) -> b -> b Source

See foldlRangeIndices

With optimisations, this compiles to an unrolled loop

sfoldrRangeIndices :: Ranged o => Proxy o -> (Int -> b -> b) -> b -> b Source

See foldrRangeIndices

With optimisations, this compiles to an unrolled loop

swithRangeIndices :: (Applicative m, Ranged o) => Proxy o -> (Int -> m ()) -> m () Source

See withRangeIndices

With optimisations, this compiles to an unrolled loop

Runtime

foldlRangeIndices :: Dim a => Proxy a -> (b -> Int -> b) -> b -> b Source

Strict left fold over the raw indices under a range

foldrRangeIndices :: Dim a => Proxy a -> (Int -> b -> b) -> b -> b Source

Lazy right fold over the raw indices under a range

withRangeIndices :: (Applicative m, Dim a) => Proxy a -> (Int -> m ()) -> m () Source

Compute something using the raw indices under a range

Utility

bounds :: (Dim a, Bounded a) => Proxy a -> (a, a) Source

Create a bound for use with e.g. "Data.Array.array"

range :: Dim n => [n] Source

The range of an index

 range = foldrRange Proxy (:) []

srange :: Ranged n => [n] Source

Statically generated range of an index

 srange = sfoldrRange Proxy (:) []

dimHead :: KnownNat x => (x :. xs) -> Int Source

dimTail :: (x :. xs) -> xs Source

pdimHead :: KnownNat x => Proxy (x :. xs) -> Int Source

pdimTail :: Proxy (x :. xs) -> Proxy xs Source

Syntax

dim :: QuasiQuoter Source

Expands to a Proxy with the phantom type being the dimension specified Works in types and expressions.

Examples:

 id [dim|3 4 5|] ==> id (Proxy :: Proxy (3:.4:.5:.Z))
 Proxy :: [dim|3 4 5|] ==> Proxy :: Proxy (3:.4:.5:.Z)

module Data.Proxy