fixed-storable-array-0.3.1.1: Fixed-size wrapper for StorableArray, providing a Storable instance. Deprecated - use storable-static-array instead.

Safe HaskellNone

Foreign.Marshal.FixedStorableArray

Description

Deprecated - use storable-static-array instead.

This module defines FixedStorableArray, a simple wrapper around StorableArray with its dimensions encoded in the type. FixedStorableArray provides a Storable instance that uses the type-level dimensions, and significantly eases writing FFI bindings to fixed-size native arrays. For example, FixedStorableArray 10 CInt has a Storable instance that is directly compatible with int foo[10] in native code.

Multidimensional native arrays are also supported. FixedStorableArray '(10,20,100) CUChar is compatible with unsigned char foo[10][20][100]. Note the leading ' before the tuple containing the dimensions. It marks it as a DataKinds lifted tuple, necessary to store the dimensions.

To operate on the contents of a FixedStorableArray, use toStorableArray. toStorableArray returns a StorableArray with the correct type and index values already in place. For example, the result of toStorableArray on a FixedStorableArray '(10,20,100) CUChar is a StorableArray (Int, Int, Int) CUChar with its bounds set to ((0,0,0),(9,19,99)).

Synopsis

Documentation

data FixedStorableArray dimensions e Source

A minimal wrapper for StorableArray that encodes the full dimensions of the array in the type. Intended for interfacing with (possibly-)multidimensional arrays of fixed size in native code.

Instances

(HasBounds k d, Ix (Bound k d), Storable e) => Storable (FixedStorableArray k d e) 

newFixedStorableArray :: (HasBounds d, Ix (Bound d), Storable e) => e -> IO (FixedStorableArray d e)Source

Create a FixedStorableArray and populate it with copies of the element passed in. Dimensions will be determined from the return type.

newFixedStorableArray_ :: (HasBounds d, Ix (Bound d), Storable e) => IO (FixedStorableArray d e)Source

Create a FixedStorableArray and don't populate it with anything in particular. Contents may or may not be initialized to anything at all. Dimensions will be determined from the return type.

toStorableArray :: FixedStorableArray dimensions e -> StorableArray (Bound dimensions) eSource

Returns the backing StorableArray of this FixedStorableArray. The backing array is shared such that modifications to it will be seen across all uses of this FixedStorableArray.

class HasBounds d whereSource

This class connects dimension description types with StorableArray index types and values. Instances are provided for up to 13 dimensions. More can be added if there's any need.

Associated Types

type Bound d :: *Source

The bounding type for this dimension description

Methods

bounds :: FixedStorableArray d e -> (Bound d, Bound d)Source

The concrete bounds for this dimension

Instances

SingI Nat a => HasBounds Nat a 
(SingI Nat n, HasBounds [Nat] (: Nat n2 ns)) => HasBounds [Nat] (: Nat n (: Nat n2 ns)) 
SingI Nat n => HasBounds [Nat] (: Nat n ([] Nat)) 
(SingI Nat a, SingI Nat b) => HasBounds ((,) Nat Nat) ((,) Nat Nat a b) 
(SingI Nat a, SingI Nat b, SingI Nat c) => HasBounds ((,,) Nat Nat Nat) ((,,) Nat Nat Nat a b c) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d) => HasBounds ((,,,) 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) => HasBounds ((,,,,) Nat Nat Nat Nat Nat) ((,,,,) Nat Nat Nat Nat Nat a b c d e) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e, SingI Nat f) => HasBounds ((,,,,,) Nat Nat Nat Nat Nat Nat) ((,,,,,) Nat Nat Nat Nat Nat Nat a b c d e f) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e, SingI Nat f, SingI Nat g) => HasBounds ((,,,,,,) Nat Nat Nat Nat Nat Nat Nat) ((,,,,,,) Nat Nat Nat Nat Nat Nat Nat a b c d e f g) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e, SingI Nat f, SingI Nat g, SingI Nat h) => HasBounds ((,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat) ((,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat a b c d e f g h) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e, SingI Nat f, SingI Nat g, SingI Nat h, SingI Nat i) => HasBounds ((,,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat Nat) ((,,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat Nat a b c d e f g h i) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e, SingI Nat f, SingI Nat g, SingI Nat h, SingI Nat i, SingI Nat j) => HasBounds ((,,,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat) ((,,,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat a b c d e f g h i j) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e, SingI Nat f, SingI Nat g, SingI Nat h, SingI Nat i, SingI Nat j, SingI Nat k) => HasBounds ((,,,,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat) ((,,,,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat a b c d e f g h i j k) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e, SingI Nat f, SingI Nat g, SingI Nat h, SingI Nat i, SingI Nat j, SingI Nat k, SingI Nat l) => HasBounds ((,,,,,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat) ((,,,,,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat a b c d e f g h i j k l) 
(SingI Nat a, SingI Nat b, SingI Nat c, SingI Nat d, SingI Nat e, SingI Nat f, SingI Nat g, SingI Nat h, SingI Nat i, SingI Nat j, SingI Nat k, SingI Nat l, SingI Nat m) => HasBounds ((,,,,,,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat) ((,,,,,,,,,,,,) Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat Nat a b c d e f g h i j k l m) 

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 HasBounds 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.