storable-static-array-0.6.0.1: Statically-sized array wrappers with Storable instances for FFI marshaling

Safe HaskellNone

Data.Ix.Static

Description

IxStatic is a class that uses type-level constraints to generate the values used by an Ix instance.

This module contains instances of IxStatic for types of kind Nat, types of the promoted kind '[Nat], and promoted tuples of Nat up to 5 elements. This is the largest size of tuple that has an Ix instance.

There are also data types provided to simulate promoted tuples and lists. These are less syntactically pleasant to use, but are sometimes helpful. In particular, the single ' used by promoted types can interfere with CPP operation, so alternate means of specifying multiple dimensions are provided.

Synopsis

Documentation

class Ix (Index d) => IxStatic d whereSource

This class connects dimension description types with Ix index types and values.

Associated Types

type Index d :: *Source

The index type for this dimension description

Methods

taggedBounds :: Tagged d (Index d, Index d)Source

The concrete bounds for an array of this dimensionality, tagged with the dimensionality.

Instances

SingI Nat a => IxStatic Nat a 
(SingI Nat a, SingI Nat b) => IxStatic * (D2 a b) 
(SingI Nat a, SingI Nat b, SingI Nat c) => IxStatic * (D3 a b c) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d) => IxStatic * (D4 a b c d) 
(SingI Nat n, IxStatic * (:. k k1 n2 ns)) => IxStatic * (:. Nat * n (:. k k1 n2 ns)) 
SingI Nat n => IxStatic * (:. Nat * n Nil) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e) => IxStatic * (D5 a b c d e) 
(SingI Nat n, IxStatic [Nat] (: Nat n2 ns)) => IxStatic [Nat] (: Nat n (: Nat n2 ns)) 
SingI Nat n => IxStatic [Nat] (: Nat n ([] Nat)) 
(SingI Nat a, SingI Nat b) => IxStatic ((,) Nat Nat) ((,) Nat Nat a b) 
(SingI Nat a, SingI Nat b, SingI Nat c) => IxStatic ((,,) Nat Nat Nat) ((,,) Nat Nat Nat a b c) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d) => IxStatic ((,,,) Nat Nat Nat Nat) ((,,,) Nat Nat Nat Nat a b c d) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e) => IxStatic ((,,,,) Nat Nat Nat Nat Nat) ((,,,,) Nat Nat Nat Nat Nat a b c d e) 

fromNat :: forall proxy n. SingI n => proxy n -> IntSource

A conversion function for converting type-level naturals to value-level. This is being exposed to aid in the creation of additional IxStatic instances for those who might desire to do so.

Haddock is currently eating the important qualification that the type variable n must have the kind Nat. The SingI instance is automatically fulfilled for all types of kind Nat. Its explicit presence in the signature is an artifact of how GHC implements dictionary passing and type erasure.

data a :. b Source

:. is provided as an alternative means of constructing a type-level list of dimensions. DataKinds-promoted lists are also supported and easier to use in almost all cases. The exception is when CPP is involved, when a single ' on a line causes CPP to fail.

With TypeOperators and DataKinds enabled, StaticArray UArray (2:.10:.25:.Nil) Int is equivalent to StaticArray UArray '[2,10,25] Int and both wrap a UArray (Int,(Int,Int)) Int with bounds ((0,(0,0)),(1,(9,24))).

Neither promoted lists nor this approach support creating 0-dimensional arrays, because they make no sense with Storable.

Instances

(SingI Nat n, IxStatic * (:. k k1 n2 ns)) => IxStatic * (:. Nat * n (:. k k1 n2 ns)) 
SingI Nat n => IxStatic * (:. Nat * n Nil) 

data Nil Source

Nil is the terminator for type-level lists created with :.

Instances

SingI Nat n => IxStatic * (:. Nat * n Nil) 

data D2 a b Source

An alternative dimension type to promoted pairs, provided for syntactic compatibility with CPP.

Instances

(SingI Nat a, SingI Nat b) => IxStatic * (D2 a b) 

data D3 a b c Source

An alternative dimension type to promoted triples, provided for syntactic compatibility with CPP.

Instances

(SingI Nat a, SingI Nat b, SingI Nat c) => IxStatic * (D3 a b c) 

data D4 a b c d Source

An alternative dimension type to promoted 4-tuples, provided for syntactic compatibility with CPP.

Instances

(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d) => IxStatic * (D4 a b c d) 

data D5 a b c d e Source

An alternative dimension type to promoted 5-tuples, provided for syntactic compatibility with CPP.

Instances

(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e) => IxStatic * (D5 a b c d e)