repa-series-1.0.0.1: Series Expressionss API

Safe HaskellNone

Data.Array.Repa.Series

Contents

Synopsis

Series

data Series k a Source

A Series is an abstract source of element data and is consumed by series processes. The elements of a series must be consumed sequentially, so they don't support random access indexing.

The rate parameter k represents the abstract length of the series.

Constructors

Series 

Fields

seriesLength :: Int#
 
seriesVector :: !(Vector a)
 

Vectors

data Vector a Source

Abstract mutable vector type that supports random access indexing.

Use fromUnboxed and toUnboxed to convert to and from regular immutable unboxed vectors.

Instances

(Unbox a, Show a) => Show (Vector a) 

fromUnboxed :: Unbox a => Vector a -> IO (Vector a)Source

O(1). Convert from an Unboxed vector.

toUnboxed :: Unbox a => Vector a -> IO (Vector a)Source

O(1). Convert to an Unboxed vector.

Running series expressions

runSeriesSource

Arguments

:: Unbox a 
=> Vector a 
-> (forall k. Series k a -> b)

worker function

-> b 

Evaluate a series expression, feeding it an unboxed vector.

The rate variable k represents the length of the series.

runSeries2Source

Arguments

:: (Unbox a, Unbox b) 
=> Vector a 
-> Vector b 
-> (forall k. Series k a -> Series k b -> c)

worker function

-> Maybe c 

Evaluate a series expression, feeding it two unboxed vectors of the same length.

runSeries3Source

Arguments

:: (Unbox a, Unbox b, Unbox c) 
=> Vector a 
-> Vector b 
-> Vector c 
-> (forall k. Series k a -> Series k b -> Series k c -> d)

worker function

-> Maybe d 

Three!

runSeries4Source

Arguments

:: (Unbox a, Unbox b, Unbox c, Unbox d) 
=> Vector a 
-> Vector b 
-> Vector c 
-> Vector d 
-> (forall k. Series k a -> Series k b -> Series k c -> Series k d -> e)

worker function

-> Maybe e 

Four!

Selectors

data Sel1 k1 k2 Source

Selectors.

Constructors

Sel1 

Fields

sel1Length :: Int#
 
sel1Flags :: !(Vector Bool)
 

mkSel1 :: Series k1 Bool -> (forall k2. Sel1 k1 k2 -> a) -> aSource

Create a new selector from a series of flags.

Series operators

map :: forall k a b. (Unbox a, Unbox b) => (a -> b) -> Series k a -> Series k bSource

Apply a function to all elements of a series.

map2 :: forall k a b c. (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Series k a -> Series k b -> Series k cSource

Like zipWith, but for equal-length series

fold :: forall k a b. Unbox b => (a -> b -> a) -> a -> Series k b -> aSource

Combine all elements of a series with an associative operator.

foldIndex :: forall k a b. Unbox b => (Int# -> a -> b -> a) -> a -> Series k b -> aSource

Combine all elements of a series with an associative operator. The worker function is given the current index into the series.

pack :: forall k1 k2 a. Unbox a => Sel1 k1 k2 -> Series k1 a -> Series k2 aSource

Pack elements of a series using a selector.

Primitives used by the Repa plugin

data Primitives Source

Primitives needed by the repa-plugin.

Constructors

Primitives 

Fields

prim_Series :: forall k a. Series k a
 
prim_Vector :: forall a. Vector a
 
prim_Ref :: forall a. Ref a
 
prim_addInt :: Int# -> Int# -> Int#
 
prim_subInt :: Int# -> Int# -> Int#
 
prim_mulInt :: Int# -> Int# -> Int#
 
prim_divInt :: Int# -> Int# -> Int#
 
prim_modInt :: Int# -> Int# -> Int#
 
prim_remInt :: Int# -> Int# -> Int#
 
prim_eqInt :: Int# -> Int# -> Bool
 
prim_neqInt :: Int# -> Int# -> Bool
 
prim_gtInt :: Int# -> Int# -> Bool
 
prim_geInt :: Int# -> Int# -> Bool
 
prim_ltInt :: Int# -> Int# -> Bool
 
prim_leInt :: Int# -> Int# -> Bool
 
prim_newRefInt :: Int# -> World -> (#World, Ref Int#)
 
prim_readRefInt :: Ref Int -> World -> (#World, Int##)
 
prim_writeRefInt :: Ref Int -> Int# -> World -> World
 
prim_newRefInt_T2 :: (#Int#, Int##) -> World -> (#World, Ref (Int, Int)#)
 
prim_readRefInt_T2 :: Ref (Int, Int) -> World -> (#World, (#Int#, Int##)#)
 
prim_writeRefInt_T2 :: Ref (Int, Int) -> (#Int#, Int##) -> World -> World
 
prim_newVectorInt :: Int# -> World -> (#World, Vector Int#)
 
prim_readVectorInt :: Vector Int -> Int# -> World -> (#World, Int##)
 
prim_writeVectorInt :: Vector Int -> Int# -> Int# -> World -> World
 
prim_sliceVectorInt :: Int# -> Vector Int -> World -> (#World, Vector Int#)
 
prim_rateOfSeries :: forall k a. Series k a -> Int#
 
prim_loop :: Int# -> (Int# -> World -> World) -> World -> World
 
prim_guard :: Ref Int -> Bool -> (Int# -> World -> World) -> World -> World
 
prim_nextInt :: forall k. Series k Int -> Int# -> World -> (#World, Int##)
 
prim_nextInt_T2 :: forall k. Series k (Int, Int) -> Int# -> World -> (#World, (#Int#, Int##)#)
 

primitives :: PrimitivesSource

Table of primitives used by the repa-plugin.