Safe Haskell | None |
---|
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,
has a FixedStorableArray
10 CIntStorable
instance that is
directly compatible with int foo[10]
in native code.
Multidimensional native arrays are also
supported.
is compatible
with FixedStorableArray
'(10,20,100) CUCharunsigned 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
is a FixedStorableArray
'(10,20,100)
CUChar
with its bounds
set to StorableArray
(Int, Int, Int) CUChar((0,0,0),(9,19,99))
.
- data FixedStorableArray dimensions e
- newFixedStorableArray :: (HasBounds d, Ix (Bound d), Storable e) => e -> IO (FixedStorableArray d e)
- newFixedStorableArray_ :: (HasBounds d, Ix (Bound d), Storable e) => IO (FixedStorableArray d e)
- toStorableArray :: FixedStorableArray dimensions e -> StorableArray (Bound dimensions) e
- class HasBounds d where
- type Bound d :: *
- bounds :: FixedStorableArray d e -> (Bound d, Bound d)
- fromNat :: forall proxy n. SingI n => proxy n -> Int
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.
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
.
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.
bounds :: FixedStorableArray d e -> (Bound d, Bound d)Source
The concrete bounds for this dimension
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.