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

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Material.Unboxed

Contents

Synopsis

Documentation

data U Source #

Layout an array as a flat vector of unboxed elements.

This is the most efficient representation for numerical data.

The implementation uses Data.Vector.Unboxed which picks an efficient, specialised representation for every element type. In particular, unboxed vectors of pairs are represented as pairs of unboxed vectors.

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

Constructors

Unboxed 

Fields

Instances

Eq U Source # 

Methods

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

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

Show U Source # 

Methods

showsPrec :: Int -> U -> ShowS #

show :: U -> String #

showList :: [U] -> ShowS #

Layout U Source #

Unboxed arrays.

Associated Types

data Name U :: * Source #

type Index U :: * Source #

Unbox a => Bulk U a Source #

Unboxed arrays.

Associated Types

data Array U a :: * Source #

Methods

layout :: Array U a -> U Source #

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

Unbox a => Windowable U a Source #

Windowing Unboxed arrays.

Methods

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

Unbox a => Target U a Source #

Unboxed buffers.

Eq (Name U) Source # 

Methods

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

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

Show (Name U) Source # 

Methods

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

show :: Name U -> String #

showList :: [Name U] -> ShowS #

(Unbox a, Eq a) => Eq (Array U a) Source # 

Methods

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

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

(Show a, Unbox a) => Show (Array U a) Source # 

Methods

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

show :: Array U a -> String #

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

data Name U Source # 
data Name U = U
type Index U Source # 
type Index U = Int
data Array U Source # 
data Array U = UArray !(Vector a)
data Buffer U Source # 
data Buffer U = UBuffer !(IOVector a)

class (Vector Vector a, MVector MVector a) => Unbox a #

Instances

Unbox Bool 
Unbox Char 
Unbox Double 
Unbox Float 
Unbox Int 
Unbox Int8 
Unbox Int16 
Unbox Int32 
Unbox Int64 
Unbox Word 
Unbox Word8 
Unbox Word16 
Unbox Word32 
Unbox Word64 
Unbox () 
(RealFloat a, Unbox a) => Unbox (Complex a) 
(Unbox a, Unbox b) => Unbox (a, b) 
(Unbox a, Unbox b) => Unbox ((:*:) a b) 
(Unbox a, Unbox b, Unbox c) => Unbox (a, b, c) 
(Unbox a, Unbox b, Unbox c, Unbox d) => Unbox (a, b, c, d) 
(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Unbox (a, b, c, d, e) 
(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Unbox (a, b, c, d, e, f) 

Conversions

fromUnboxed :: Vector a -> Array U a Source #

O(1). Wrap an unboxed vector as an array.

toUnboxed :: Array U a -> Vector a Source #

O(1). Unwrap an unboxed vector from an array.