carray-0.1.5.2: A C-compatible array library.

Portabilitynon-portable
Stabilityexperimental
Maintainerjed@59A2.org
Safe HaskellSafe-Infered

Data.Array.CArray

Contents

Description

This module provides the immutable CArray which uses pinned memory on the GC'd heap. Elements are stored according to the class Storable. You can obtain a pointer to the array contents to manipulate elements from languages like C.

CArray is 16-byte aligned by default. If you create a CArray with unsafeForeignPtrToCArray then it may not be aligned. This will be an issue if you intend to use SIMD instructions.

CArray is similar to UArray but slower if you stay within Haskell. CArray can handle more types and can be used by external libraries.

CArray has an instance of Binary.

Synopsis

CArray type

data CArray i e Source

The immutable array type.

Instances

Typeable2 CArray 
Storable e => IArray CArray e 
(Ix ix, Eq e, Storable e) => Eq (CArray ix e) 
(Data i, Data e) => Data (CArray i e) 
(Ix ix, Ord e, Storable e) => Ord (CArray ix e) 
(Ix ix, Show ix, Show e, Storable e) => Show (CArray ix e) 
(Ix i, Binary i, Binary e, Storable e) => Binary (CArray i e) 

Multi-dimensional

Fast reshaping

reshape :: (Ix i, Ix j) => (j, j) -> CArray i e -> CArray j eSource

O(1) reshape an array. The number of elements in the new shape must not exceed the number in the old shape. The elements are in C-style ordering.

flatten :: Ix i => CArray i e -> CArray Int eSource

O(1) make a rank 1 array from an arbitrary shape. It has the property that 'reshape (0, size a - 1) a == flatten a'.

Query

rank :: (Shapable i, Ix i, IArray a e) => a i e -> Int

Determine the rank of an array.

shape :: (Shapable i, Ix i, IArray a e) => a i e -> [Int]

Canonical representation of the shape. The following properties hold: 'length . shape = rank' 'product . shape = size'

size :: (Ix i, IArray a e) => a i e -> Int

Number of elements in the Array.

Mapping

General

ixmapWithIndP :: (Ix i, Ix i', IArray a e, IArray a' e') => (i', i') -> (i' -> i) -> (i -> e -> i' -> e') -> a i e -> a' i' e'Source

Generic slice and map. This takes the new range, the inverse map on indices, and function to produce the next element. It is the most general operation in its class.

ixmapWithInd :: (Ix i, Ix i', IArray a e, IArray a e') => (i', i') -> (i' -> i) -> (i -> e -> i' -> e') -> a i e -> a i' e'Source

Less polymorphic version.

ixmapWithP :: (Ix i, Ix i', IArray a e, IArray a' e') => (i', i') -> (i' -> i) -> (e -> e') -> a i e -> a' i' e'Source

Perform an operation on the elements, independent of their location.

ixmapWith :: (Ix i, Ix i', IArray a e, IArray a e') => (i', i') -> (i' -> i) -> (e -> e') -> a i e -> a i' e'Source

Less polymorphic version.

ixmapP :: (Ix i, Ix i', IArray a e, IArray a' e) => (i', i') -> (i' -> i) -> a i e -> a' i' eSource

More polymorphic version of ixmap.

Slicing

sliceStrideWithP :: (Ix i, Shapable i, Ix i', IArray a e, IArray a' e') => (i', i') -> (i, i, i) -> (e -> e') -> a i e -> a' i' e'Source

More friendly sub-arrays with element mapping.

sliceStrideWith :: (Ix i, Shapable i, Ix i', IArray a e, IArray a e') => (i', i') -> (i, i, i) -> (e -> e') -> a i e -> a i' e'Source

Less polymorphic version.

sliceStrideP :: (Ix i, Shapable i, Ix i', IArray a e, IArray a' e) => (i', i') -> (i, i, i) -> a i e -> a' i' eSource

Strided sub-array without element mapping.

sliceStride :: (Ix i, Shapable i, Ix i', IArray a e) => (i', i') -> (i, i, i) -> a i e -> a i' eSource

Less polymorphic version.

sliceWithP :: (Ix i, Shapable i, Ix i', IArray a e, IArray a' e') => (i', i') -> (i, i) -> (e -> e') -> a i e -> a' i' e'Source

Contiguous sub-array with element mapping.

sliceWith :: (Ix i, Shapable i, Ix i', IArray a e, IArray a e') => (i', i') -> (i, i) -> (e -> e') -> a i e -> a i' e'Source

Less polymorphic version.

sliceP :: (Ix i, Shapable i, Ix i', IArray a e, IArray a' e) => (i', i') -> (i, i) -> a i e -> a' i' eSource

Contiguous sub-array without element mapping.

slice :: (Ix i, Shapable i, Ix i', IArray a e) => (i', i') -> (i, i) -> a i e -> a i' eSource

Less polymorphic version.

Lifting

liftArrayP :: (Ix i, IArray a e, IArray a1 e1) => (e -> e1) -> a i e -> a1 i e1Source

Polymorphic version of amap.

liftArray :: (Ix i, IArray a e, IArray a e1) => (e -> e1) -> a i e -> a i e1Source

Equivalent to amap. Here for consistency only.

liftArray2P :: (Ix i, IArray a e, IArray a1 e1, IArray a2 e2) => (e -> e1 -> e2) -> a i e -> a1 i e1 -> a2 i e2Source

Polymorphic 2-array lift.

liftArray2 :: (Ix i, IArray a e, IArray a e1, IArray a e2) => (e -> e1 -> e2) -> a i e -> a i e1 -> a i e2Source

Less polymorphic version.

liftArray3P :: (Ix i, IArray a e, IArray a1 e1, IArray a2 e2, IArray a3 e3) => (e -> e1 -> e2 -> e3) -> a i e -> a1 i e1 -> a2 i e2 -> a3 i e3Source

Polymorphic 3-array lift.

liftArray3 :: (Ix i, IArray a e, IArray a e1, IArray a e2, IArray a e3) => (e -> e1 -> e2 -> e3) -> a i e -> a i e1 -> a i e2 -> a i e3Source

Less polymorphic version.

Norms

normp :: (Ix i, RealFloat e', Abs e e', IArray a e) => e' -> a i e -> e'Source

p-norm on the array taken as a vector

norm2 :: (Ix i, Floating e', Abs e e', IArray a e) => a i e -> e'Source

2-norm on the array taken as a vector (Frobenius norm for matrices)

normSup :: (Ix i, Num e', Ord e', Abs e e', IArray a e) => a i e -> e'Source

Sup norm on the array taken as a vector

Types

class Shapable i

We need this type class to distinguish between different tuples of Ix. There are Shapable instances for homogenous Int tuples, but may Haddock doesn't see them.

class Abs a b | a -> bSource

Hack so that norms have a sensible type.

Unsafe low-level

withCArray :: CArray i e -> (Ptr e -> IO a) -> IO aSource

The pointer to the array contents is obtained by withCArray. The idea is similar to ForeignPtr (used internally here). The pointer should be used only during execution of the IO action retured by the function passed as argument to withCArray.

unsafeForeignPtrToCArray :: Ix i => ForeignPtr e -> (i, i) -> IO (CArray i e)Source

O(1) Construct a CArray from an arbitrary ForeignPtr. It is the caller's responsibility to ensure that the ForeignPtr points to an area of memory sufficient for the specified bounds.

toForeignPtr :: CArray i e -> (Int, ForeignPtr e)Source

O(1) Extract ForeignPtr from a CArray.

unsafeCArrayToByteString :: Storable e => CArray i e -> ByteStringSource

O(1) Turn a CArray into a ByteString. Unsafe because it uses castForeignPtr and thus is not platform independent.

unsafeByteStringToCArray :: (Ix i, Storable e) => (i, i) -> ByteString -> Maybe (CArray i e)Source

O(1) Turn a ByteString into a CArray. Unsafe because it uses castForeignPtr and thus is not platform independent. Returns Nothing if the range specified is larger than the size of the ByteString or the start of the ByteString does not fulfil the alignment requirement of the resulting CArray (as specified by the Storable instance).

createCArray :: (Ix i, Storable e) => (i, i) -> (Ptr e -> IO ()) -> IO (CArray i e)Source

Make a new CArray with an IO action.

The overloaded immutable array interface