repa-array-4.2.3.1: Bulk array representations and operators.

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Material.Foreign

Contents

Synopsis

Documentation

data F Source #

Layout for dense Foreign arrays.

UNSAFE: Indexing into raw material arrays is not bounds checked. You may want to wrap this with a Checked layout as well.

Constructors

Foreign 

Fields

Instances

Eq F Source # 

Methods

(==) :: F -> F -> Bool #

(/=) :: F -> F -> Bool #

Show F Source # 

Methods

showsPrec :: Int -> F -> ShowS #

show :: F -> String #

showList :: [F] -> ShowS #

Layout F Source #

Foreign arrays.

Associated Types

data Name F :: * Source #

type Index F :: * Source #

Storable a => Bulk F a Source #

Foreign arrays.

Associated Types

data Array F a :: * Source #

Methods

layout :: Array F a -> F Source #

index :: Array F a -> Index F -> a Source #

Storable a => Windowable F a Source #

Windowing Foreign arrays.

Methods

window :: Index F -> Index F -> Array F a -> Array F a Source #

Storable a => Target F a Source #

Foreign buffers

Eq (Name F) Source # 

Methods

(==) :: Name F -> Name F -> Bool #

(/=) :: Name F -> Name F -> Bool #

Show (Name F) Source # 

Methods

showsPrec :: Int -> Name F -> ShowS #

show :: Name F -> String #

showList :: [Name F] -> ShowS #

(Eq a, Storable a) => Eq (Array F a) Source # 

Methods

(==) :: Array F a -> Array F a -> Bool #

(/=) :: Array F a -> Array F a -> Bool #

(Storable a, Show a) => Show (Array F a) Source # 

Methods

showsPrec :: Int -> Array F a -> ShowS #

show :: Array F a -> String #

showList :: [Array F a] -> ShowS #

data Name F Source # 
data Name F = F
type Index F Source # 
type Index F = Int
data Array F Source # 
data Array F = FArray !(Vector a)
data Buffer F Source # 
data Buffer F = FBuffer !(IOVector a)

Format conversion

unsafeCast :: (Storable a, Storable b) => Array F a -> Array F b Source #

O(1). Cast a foreign array from one element type to another.

fromForeignPtr :: Storable a => Int -> ForeignPtr a -> Array F a Source #

O(1). Wrap a ForeignPtr as an array.

toForeignPtr :: Storable a => Array F a -> (Int, Int, ForeignPtr a) Source #

O(1). Unwrap a ForeignPtr from an array.

fromStorableVector :: Vector a -> Array F a Source #

O(1). Convert a storable Vector to a foreign Array

toStorableVector :: Array F a -> Vector a Source #

O(1). Convert a foreign array to a storable Vector.

fromByteString :: ByteString -> Array F Word8 Source #

O(1). Convert a ByteString to an foreign Array.

toByteString :: Array F Word8 -> ByteString Source #

O(1). Convert a foreign Vector to a ByteString.