carray-0.1.6.5: A C-compatible array library.

Copyright(c) 2001 The University of Glasgow (c) 2008 Jed Brown
LicenseBSD-style
Maintainerjed@59A2.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Data.Array.CArray.Base

Description

This module provides both the immutable CArray and mutable IOCArray. The underlying storage is exactly the same - 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.

IOCArray is equivalent to StorableArray and similar to IOUArray but slower. IOCArray has O(1) versions of unsafeFreeze and unsafeThaw when converting to/from CArray.

Synopsis

Documentation

data CArray i e Source #

The immutable array type.

Constructors

CArray !i !i Int !(ForeignPtr e) 

Instances

Storable e => IArray CArray e Source # 

Methods

bounds :: Ix i => CArray i e -> (i, i) #

numElements :: Ix i => CArray i e -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, e)] -> CArray i e

unsafeAt :: Ix i => CArray i e -> Int -> e

unsafeReplace :: Ix i => CArray i e -> [(Int, e)] -> CArray i e

unsafeAccum :: Ix i => (e -> e' -> e) -> CArray i e -> [(Int, e')] -> CArray i e

unsafeAccumArray :: Ix i => (e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> CArray i e

(Ix ix, Eq e, Storable e) => Eq (CArray ix e) Source # 

Methods

(==) :: CArray ix e -> CArray ix e -> Bool #

(/=) :: CArray ix e -> CArray ix e -> Bool #

(Data i, Data e) => Data (CArray i e) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CArray i e -> c (CArray i e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CArray i e) #

toConstr :: CArray i e -> Constr #

dataTypeOf :: CArray i e -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CArray i e)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d a. (Data d, Data a) => c (t d a)) -> Maybe (c (CArray i e)) #

gmapT :: (forall b. Data b => b -> b) -> CArray i e -> CArray i e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CArray i e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CArray i e -> r #

gmapQ :: (forall d. Data d => d -> u) -> CArray i e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CArray i e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CArray i e -> m (CArray i e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CArray i e -> m (CArray i e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CArray i e -> m (CArray i e) #

(Ix ix, Ord e, Storable e) => Ord (CArray ix e) Source # 

Methods

compare :: CArray ix e -> CArray ix e -> Ordering #

(<) :: CArray ix e -> CArray ix e -> Bool #

(<=) :: CArray ix e -> CArray ix e -> Bool #

(>) :: CArray ix e -> CArray ix e -> Bool #

(>=) :: CArray ix e -> CArray ix e -> Bool #

max :: CArray ix e -> CArray ix e -> CArray ix e #

min :: CArray ix e -> CArray ix e -> CArray ix e #

(Ix ix, Show ix, Show e, Storable e) => Show (CArray ix e) Source # 

Methods

showsPrec :: Int -> CArray ix e -> ShowS #

show :: CArray ix e -> String #

showList :: [CArray ix e] -> ShowS #

(Ix i, Arbitrary i, Storable e, Arbitrary e) => Arbitrary (CArray i e) Source # 

Methods

arbitrary :: Gen (CArray i e) #

shrink :: CArray i e -> [CArray i e] #

(Ix i, CoArbitrary i, Storable e, CoArbitrary e) => CoArbitrary (CArray i e) Source # 

Methods

coarbitrary :: CArray i e -> Gen b -> Gen b #

(Ix i, Binary i, Binary e, Storable e) => Binary (CArray i e) Source # 

Methods

put :: CArray i e -> Put #

get :: Get (CArray i e) #

putList :: [CArray i e] -> Put #

data IOCArray i e Source #

Absolutely equivalent representation, but used for the mutable interface.

Constructors

IOCArray !i !i Int !(ForeignPtr e) 

Instances

Storable e => MArray IOCArray e IO Source # 

Methods

getBounds :: Ix i => IOCArray i e -> IO (i, i) #

getNumElements :: Ix i => IOCArray i e -> IO Int

newArray :: Ix i => (i, i) -> e -> IO (IOCArray i e) #

newArray_ :: Ix i => (i, i) -> IO (IOCArray i e) #

unsafeNewArray_ :: Ix i => (i, i) -> IO (IOCArray i e)

unsafeRead :: Ix i => IOCArray i e -> Int -> IO e

unsafeWrite :: Ix i => IOCArray i e -> Int -> e -> IO ()

(Data i, Data e) => Data (IOCArray i e) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IOCArray i e -> c (IOCArray i e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IOCArray i e) #

toConstr :: IOCArray i e -> Constr #

dataTypeOf :: IOCArray i e -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (IOCArray i e)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d a. (Data d, Data a) => c (t d a)) -> Maybe (c (IOCArray i e)) #

gmapT :: (forall b. Data b => b -> b) -> IOCArray i e -> IOCArray i e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IOCArray i e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IOCArray i e -> r #

gmapQ :: (forall d. Data d => d -> u) -> IOCArray i e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IOCArray i e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IOCArray i e -> m (IOCArray i e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IOCArray i e -> m (IOCArray i e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IOCArray i e -> m (IOCArray i e) #

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

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.

withIOCArray :: IOCArray i e -> (Ptr e -> IO a) -> IO a Source #

touchIOCArray :: IOCArray i e -> IO () Source #

If you want to use it afterwards, ensure that you touchCArray after the last use of the pointer, so the array is not freed too early.

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.

unsafeForeignPtrToIOCArray :: Ix i => ForeignPtr e -> (i, i) -> IO (IOCArray 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 -> ByteString Source #

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

copy :: (Ix i, Storable e) => CArray i e -> IO (CArray i e) Source #

freezeIOCArray :: (Ix i, Storable e) => IOCArray i e -> IO (CArray i e) Source #

thawIOCArray :: (Ix i, Storable e) => CArray i e -> IO (IOCArray i e) Source #

zeroElem :: Storable a => a -> a Source #

Hackish way to get the zero element for a Storable type.

unsafeArrayCArray :: (Storable e, Ix i) => (i, i) -> [(Int, e)] -> e -> IO (CArray i e) Source #

unsafeReplaceCArray :: (Storable e, Ix i) => CArray i e -> [(Int, e)] -> IO (CArray i e) Source #

unsafeAccumCArray :: (Storable e, Ix i) => (e -> e' -> e) -> CArray i e -> [(Int, e')] -> IO (CArray i e) Source #

unsafeAccumArrayCArray :: (Storable e, Ix i) => (e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> IO (CArray i e) Source #

eqCArray :: (Storable e, Ix i, Eq e) => CArray i e -> CArray i e -> Bool Source #

cmpCArray :: (Storable e, Ix i, Ord e) => CArray i e -> CArray i e -> Ordering Source #

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

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 e Source #

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

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' e Source #

More polymorphic version of ixmap.

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' e Source #

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' e Source #

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' e Source #

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' e Source #

Less polymorphic version.

mapCArrayInPlace :: (Ix i, Storable e) => (e -> e) -> CArray i e -> CArray i e Source #

In-place map on CArray. Note that this is IN PLACE so you should not retain any reference to the original. It flagrantly breaks referential transparency!

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

offsetShapeFromThenTo :: [Int] -> [Int] -> [Int] -> [Int] -> [Int] Source #

offsetShapeFromTo :: [Int] -> [Int] -> [Int] -> [Int] Source #

offsetShapeFromTo' :: ([[Int]] -> [[Int]]) -> [Int] -> [Int] -> [Int] -> [Int] Source #

offsets :: (Ix a, Shapable a) => (a, a) -> a -> [Int] Source #

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

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

Polymorphic version of amap.

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

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 e2 Source #

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 e2 Source #

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 e3 Source #

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 e3 Source #

Less polymorphic version.

class Abs a b | a -> b where Source #

Hack so that norms have a sensible type.

Minimal complete definition

abs_

Methods

abs_ :: a -> b Source #

mallocForeignPtrArrayAligned :: Storable a => Int -> IO (ForeignPtr a) Source #

Allocate an array which is 16-byte aligned. Essential for SIMD instructions.

mallocForeignPtrBytesAligned :: Int -> IO (ForeignPtr a) Source #

Allocate memory which is 16-byte aligned. This is essential for SIMD instructions. We know that mallocPlainForeignPtrBytes will give word-aligned memory, so we pad enough to be able to return the desired amount of memory after aligning our pointer.

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

Make a new CArray with an IO action.

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