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

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Material.Nested

Contents

Synopsis

Documentation

data N Source

Nested array represented as a flat array of elements, and a segment descriptor that describes how the elements are partitioned into the sub-arrays. Using this representation for multidimentional arrays is significantly more efficient than using a boxed array of arrays, as there is no need to allocate the sub-arrays individually in the heap.

With a nested type like: Array N (Array N (Array U Int)), the concrete representation consists of five flat unboxed vectors: two for each of the segment descriptors associated with each level of nesting, and one unboxed vector to hold all the integer elements.

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

Constructors

Nested 

Fields

nestedLength :: !Int
 

Instances

Eq N 
Show N 
Layout N

Nested arrays.

(BulkI l a, Windowable l a) => Bulk N (Array l a)

Nested arrays.

(BulkI l a, Windowable l a) => Windowable N (Array l a)

Windowing Nested arrays.

(Bulk l a, Target l a, (~) * (Index l) Int) => Target N (Array l a) 
Convert r1 a1 r2 a2 => Convert N (Array r1 a1) A (Array r2 a2) 
Convert r1 a1 r2 a2 => Convert A (Array r1 a1) N (Array r2 a2) 
Eq (Name N) 
Show (Name N) 
Show (Array l a) => Show (Array N (Array l a)) 
Unpack (Buffer N (Array l a)) (IOVector (Array l a)) 
data Name N = N 
type Index N = Int 
data Array N (Array l a) = NArray {} 
data Buffer N (Array l a) = NBuffer !(IOVector (Array l 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) 

Conversion

fromLists :: TargetI l a => Name l -> [[a]] -> Array N (Array l a) Source

O(size src) Convert some lists to a nested array.

fromListss :: TargetI l a => Name l -> [[[a]]] -> Array N (Array N (Array l a)) Source

O(size src) Convert a triply nested list to a triply nested array.

Mapping

mapElems :: (Array l1 a -> Array l2 b) -> Array N (Array l1 a) -> Array N (Array l2 b) Source

Apply a function to all the elements of a doubly nested array, preserving the nesting structure.

Slicing

slices Source

Arguments

:: Array F Int

Segment starting positions.

-> Array F Int

Segment lengths.

-> Array l a

Array elements.

-> Array N (Array l a) 

O(1). Produce a nested array by taking slices from some array of elements.

This is a constant time operation, as the representation for nested vectors just wraps the starts, lengths and elements vectors.

Concatenation

concats :: Array N (Array N (Array l a)) -> Array N (Array l a) Source

Segmented concatenation. Concatenate triply nested vector, producing a doubly nested vector.

  • Unlike the plain concat function, this operation is performed entirely on the segment descriptors of the nested arrays, and does not require the inner array elements to be copied.
> import Data.Repa.Nice
> nice $ concats $ fromListss U [["red", "green", "blue"], ["grey", "white"], [], ["black"]]
["red","green","blue","grey","white","black"]

Splitting

segment Source

Arguments

:: (BulkI l a, Unbox a) 
=> (a -> Bool)

Detect the start of a segment.

-> (a -> Bool)

Detect the end of a segment.

-> Array l a

Vector to segment.

-> Array N (Array l a) 

O(len src). Given predicates which detect the start and end of a segment, split an vector into the indicated segments.

segmentOn Source

Arguments

:: (BulkI l a, Eq a, Unbox a) 
=> (a -> Bool)

Detect the end of a segment.

-> Array l a

Vector to segment.

-> Array N (Array l a) 

O(len src). Given a terminating value, split an vector into segments.

The result segments do not include the terminator.

> import Data.Repa.Nice
> nice $ segmentOn (== ' ') (fromList U "fresh   fried fish  ") 
["fresh "," "," ","fried ","fish "," "]

dice Source

Arguments

:: (BulkI l a, Windowable l a, Unbox a) 
=> (a -> Bool)

Detect the start of an inner segment.

-> (a -> Bool)

Detect the end of an inner segment.

-> (a -> Bool)

Detect the start of an outer segment.

-> (a -> Bool)

Detect the end of an outer segment.

-> Array l a

Array to dice.

-> Array N (Array N (Array l a)) 

O(len src). Like segment, but cut the source array twice.

diceSep Source

Arguments

:: (BulkI l a, Windowable l a, Unbox a, Eq a) 
=> a

Terminating element for inner segments.

-> a

Terminating element for outer segments.

-> Array l a

Vector to dice.

-> Array N (Array N (Array l a)) 

O(len src). Given field and row terminating values, split an array into rows and fields.

Trimming

trims :: BulkI l a => (a -> Bool) -> Array N (Array l a) -> Array N (Array l a) Source

For each segment of a nested array, trim elements off the start and end of the segment that match the given predicate.

trimEnds :: BulkI l a => (a -> Bool) -> Array N (Array l a) -> Array N (Array l a) Source

For each segment of a nested array, trim elements off the end of the segment that match the given predicate.

trimStarts :: BulkI l a => (a -> Bool) -> Array N (Array l a) -> Array N (Array l a) Source

For each segment of a nested array, trim elements off the start of the segment that match the given predicate.

Transpose

ragspose3 :: Array N (Array N (Array l a)) -> Array N (Array N (Array l a)) Source

Ragged transpose of a triply nested array.

  • This operation is performed entirely on the segment descriptors of the nested arrays, and does not require the inner array elements to be copied.