carray-0.1.6.8: A C-compatible array library.

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

Data.Array.IOCArray

Contents

Description

This module provides both the mutable IOCArray 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.

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

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

IOCArray type

data IOCArray i e Source #

Absolutely equivalent representation, but used for the mutable interface.

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 e, Data i) => 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) #

Foreign support

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.

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.

The overloaded mutable array interface