repa-stream-4.2.3.1: Stream functions not present in the vector library.

Safe HaskellNone
LanguageHaskell98

Data.Repa.Vector.Unboxed

Contents

Synopsis

Stream operators

Compacting

compact Source #

Arguments

:: (Unbox a, Unbox b) 
=> (s -> a -> (s, Maybe b))

Worker function

-> s

Starting state

-> Vector a

Input vector

-> Vector b 

Combination of fold and filter.

We walk over the stream front to back, maintaining an accumulator. At each point we can chose to emit an element (or not)

compactIn Source #

Arguments

:: Unbox a 
=> (a -> a -> (a, Maybe a))

Worker function.

-> Vector a

Input elements.

-> Vector a 

Like compact but use the first value of the stream as the initial state, and add the final state to the end of the output.

Dicing

findSegments Source #

Arguments

:: Unbox a 
=> (a -> Bool)

Predicate to check for start of segment.

-> (a -> Bool)

Predicate to check for end of segment.

-> Vector a

Input vector.

-> (Vector Int, Vector Int) 

Given predicates that detect the beginning and end of some interesting segment of information, scan through a vector looking for when these segments begin and end. Return vectors of the segment starting positions and lengths.

  • As each segment must end on a element where the ending predicate returns True, the miniumum segment length returned is 1.

findSegmentsFrom Source #

Arguments

:: (a -> Bool)

Predicate to check for start of segment.

-> (a -> Bool)

Predicate to check for end of segment.

-> Int

Input length.

-> (Int -> a)

Get an element from the input.

-> (Vector Int, Vector Int) 

Given predicates that detect the beginning and end of some interesting segment of information, scan through a vector looking for when these segments begin and end. Return vectors of the segment starting positions and lengths.

diceSep Source #

Arguments

:: Unbox a 
=> (a -> Bool)

Detect the end of a column.

-> (a -> Bool)

Detect the end of a row.

-> Vector a 
-> (Vector (Int, Int), Vector (Int, Int))

Segment starts and lengths

Dice a vector stream into rows and columns.

Extracting

extract Source #

Arguments

:: Unbox a 
=> (Int -> a)

Function to get elements from the source.

-> Vector (Int, Int)

Segment starts and lengths.

-> Vector a

Result elements.

Extract segments from some source array and concatenate them.

   let arr = [10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20]
   in  extractS (index arr) [(0, 1), (3, 3), (2, 6)]
   
    => [10, 13, 14, 15, 12, 13, 14, 15, 16, 17]

Inserting

insert Source #

Arguments

:: Unbox a 
=> (Int -> Maybe a)

Produce a new element for this index.

-> Vector a

Source vector.

-> Vector a 

Insert elements produced by the given function into a vector.

Merging

merge Source #

Arguments

:: (Ord k, Unbox k, Unbox a, Unbox b, Unbox c) 
=> (k -> a -> b -> c)

Combine two values with the same key.

-> (k -> a -> c)

Handle a left value without a right value.

-> (k -> b -> c)

Handle a right value without a left value.

-> Vector (k, a)

Vector of keys and left values.

-> Vector (k, b)

Vector of keys and right values.

-> Vector (k, c)

Vector of keys and results.

Merge two pre-sorted key-value streams.

mergeMaybe Source #

Arguments

:: (Ord k, Unbox k, Unbox a, Unbox b, Unbox c) 
=> (k -> a -> b -> Maybe c)

Combine two values with the same key.

-> (k -> a -> Maybe c)

Handle a left value without a right value.

-> (k -> b -> Maybe c)

Handle a right value without a left value.

-> Vector (k, a)

Vector of keys and left values.

-> Vector (k, b)

Vector of keys and right values.

-> Vector (k, c)

Vector of keys and results.

Like merge, but only produce the elements where the worker functions return Just.

Padding

padForward Source #

Arguments

:: (Unbox k, Unbox v, Ord k) 
=> (k -> k)

Successor function.

-> Vector (k, v)

Input keys and values.

-> Vector (k, v) 

Given a stream of keys and values, and a successor function for keys, if the stream is has keys missing in the sequence then insert the missing key, copying forward the the previous value.

Ratcheting

ratchet Source #

Arguments

:: Vector (Int, Int)

Starting and ending values.

-> (Vector Int, Vector Int)

Elements and Lengths vectors.

Interleaved enumFromTo.

Given a vector of starting values, and a vector of stopping values, produce an stream of elements where we increase each of the starting values to the stopping values in a round-robin order. Also produce a vector of result segment lengths.

 unsafeRatchetS [10,20,30,40] [15,26,33,47]
 =  [10,20,30,40       -- 4
    ,11,21,31,41       -- 4
    ,12,22,32,42       -- 4
    ,13,23   ,43       -- 3
    ,14,24   ,44       -- 3
       ,25   ,45       -- 2
             ,46]      -- 1

        ^^^^             ^^^
      Elements         Lengths

Chain operators

unchainToVector :: (PrimMonad m, Unbox a) => Chain m s a -> m (Vector a, s) Source #

Compute a chain into a vector.

unchainToMVector :: (PrimMonad m, Unbox a) => Chain m s a -> m (MVector (PrimState m) a, s) Source #

Compute a chain into a mutable vector.

Folding

folds Source #

Arguments

:: (Unbox n, Unbox a, Unbox b) 
=> (a -> b -> b)

Worker function to fold each segment.

-> b

Initial state when folding segments.

-> Option3 n Int b

Length and initial state for first segment.

-> Vector (n, Int)

Segment names and lengths.

-> Vector a

Elements.

-> (Vector (n, b), Folds Int Int n a b) 

Segmented fold over vectors of segment lengths and input values.

The total lengths of all segments need not match the length of the input elements vector. The returned Folds state can be inspected to determine whether all segments were completely folded, or the vector of segment lengths or elements was too short relative to the other. In the resulting state, foldLensState is the index into the lengths vector *after* the last one that was consumed. If this equals the length of the lengths vector then all segment lengths were consumed. Similarly for the elements vector.

data Folds sLens sVals n a b Source #

Return state of a folds operation.

Constructors

Folds 

Fields

Instances

(Show sLens, Show sVals, Show n, Show b) => Show (Folds sLens sVals n a b) Source # 

Methods

showsPrec :: Int -> Folds sLens sVals n a b -> ShowS #

show :: Folds sLens sVals n a b -> String #

showList :: [Folds sLens sVals n a b] -> ShowS #

Scanning

scanMaybe Source #

Arguments

:: (Unbox a, Unbox b) 
=> (s -> a -> (s, Maybe b))

Worker function.

-> s

Initial state for scan.

-> Vector a

Input elements.

-> (Vector b, s)

Output elements.

Perform a left-to-right scan through an input vector, maintaining a state value between each element. For each element of input we may or may not produce an element of output.

groupsBy Source #

Arguments

:: Unbox a 
=> (a -> a -> Bool)

Comparison function.

-> Maybe (a, Int)

Starting element and count.

-> Vector a

Input elements.

-> (Vector (a, Int), Maybe (a, Int)) 

From a stream of values which has consecutive runs of idential values, produce a stream of the lengths of these runs.

 groupsBy (==) (Just (a, 4)) 
               ['a', 'a', 'a', 'b', 'b', 'c', 'd', 'd'] 
  => ([(a, 7), (b, 2), (c, 1)], Just ('d', 2))

Conversion

chainOfVector :: (Monad m, Unbox a) => Vector a -> Chain m Int a Source #

Produce a chain from a generic vector.