forsyde-shallow-3.4.0.0: ForSyDe's Haskell-embedded Domain Specific Language.

Copyright(c) ForSyDe Group KTH 2007-2019
LicenseBSD-style (see the file LICENSE)
Maintainerforsyde-dev@kth.se
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

ForSyDe.Shallow.Core.Vector

Contents

Description

This module defines the data type Vector and the corresponding functions. It is a development of the module defined by Reekie. The Vector data type is a shallow interpretation of arrays and is used for quick prototyping of array algorithms and skeletons, whereas in fact it is implemented as an infinite list itself. For a type-checked fixed-size data type for representing vectors, see FSVec or REPA.

OBS: The lengths in the API documentation for function arguments are not type-safe, but rather suggestions for usage in designing vector algorithms or skeletons.

Synopsis

Documentation

data Vector a Source #

The data type Vector is modeled similar to a list. It has two data type constructors. NullV constructs the empty vector, while :> constructsa vector by adding an value to an existing vector..

Vector is an instance of the classes Read and Show. This means that the vector

1:>2:>3:>NullV

is shown as

<1,2,3>

Constructors

NullV 
a :> (Vector a) infixr 5 
Instances
Eq a => Eq (Vector a) Source # 
Instance details

Defined in ForSyDe.Shallow.Core.Vector

Methods

(==) :: Vector a -> Vector a -> Bool #

(/=) :: Vector a -> Vector a -> Bool #

Read a => Read (Vector a) Source # 
Instance details

Defined in ForSyDe.Shallow.Core.Vector

Show a => Show (Vector a) Source # 
Instance details

Defined in ForSyDe.Shallow.Core.Vector

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

(<+>) infixr 5 Source #

Arguments

:: Vector a

length = la

-> Vector a

length = lb

-> Vector a

length = la + lb

The operator <+> concatenates two vectors.

(<:) infixl 5 Source #

Arguments

:: Vector a

length = la

-> a 
-> Vector a

length = la + 1

The operator '(<:)' appends an element at the end of a vector.

Queries

nullV :: Vector a -> Bool Source #

The function nullV returns True if a vector is empty.

lengthV :: Vector a -> Int Source #

The function lengthV returns the number of elements in a value.

Generators

vector :: [a] -> Vector a Source #

The function vector converts a list into a vector.

fromVector :: Vector a -> [a] Source #

The function fromVector converts a vector into a list.

unitV Source #

Arguments

:: a 
-> Vector a

length = 1

The function unitV creates a vector with one element.

iterateV Source #

Arguments

:: (Num a, Eq a) 
=> a

number of elements = n

-> (b -> b)

generator function (last_element -> next_element)

-> b

initial element

-> Vector b

generated vector; length = n

The function iterateV generates a vector with a given number of elements starting from an initial element using a supplied function for the generation of elements.

>>> iterateV 5 (+1) 1
<1,2,3,4,5>

generateV Source #

Arguments

:: (Num a, Eq a) 
=> a

number of elements = n

-> (b -> b)

generator function (last_element -> next_element)

-> b

initial element

-> Vector b

generated vector; length = n

The function generateV behaves in the same way as iterateV, but starts with the application of the supplied function to the supplied value.

>>> generateV 5 (+1) 1
<2,3,4,5,6>

copyV Source #

Arguments

:: (Num a, Eq a) 
=> a

number of elements = n

-> b

element to be copied

-> Vector b

length = n

The function copyV generates a vector with a given number of copies of the same element.

>>> copyV 7 5
<5,5,5,5,5,5,5>

Functional skeletons

mapV Source #

Arguments

:: (a -> b) 
-> Vector a

length = la

-> Vector b

length = la

The higher-order function mapV applies a function on all elements of a vector.

zipWithV Source #

Arguments

:: (a -> b -> c) 
-> Vector a

length = la

-> Vector b

length = lb

-> Vector c

length = minimum [la,lb]

The higher-order function zipWithV applies a function pairwise on two vectors.

zipWith3V Source #

Arguments

:: (a -> b -> c -> d) 
-> Vector a

length = la

-> Vector b

length = lb

-> Vector c

length = lc

-> Vector d

length = minimum [la,lb,lc]

The higher-order function zipWithV3 applies a function 3-tuple-wise on three vectors.

reduceV :: (a -> a -> a) -> Vector a -> a Source #

Reduces a vector of elements to a single element based on a binary function.

>>> reduceV (+) $ vector [1,2,3,4,5]
15

pipeV :: Vector (a -> a) -> a -> a Source #

Pipes an element through a vector of functions.

>>> vector [(*2), (+1), (/3)] `pipeV` 3      -- is the same as ((*2) . (+1) . (/3)) 3
4.0

foldlV :: (a -> b -> a) -> a -> Vector b -> a Source #

The higher-order functions foldlV folds a function from the right to the left over a vector using an initial value.

>>> foldlV (-) 8 $ vector [4,2,1]   -- is the same as (((8 - 4) - 2) - 1)
1

foldrV :: (b -> a -> a) -> a -> Vector b -> a Source #

The higher-order functions foldrV folds a function from the left to the right over a vector using an initial value.

>>> foldrV (-) 8 $ vector [4,2,1]   -- is the same as (4 - (2 - (1 - 8)))
-5

scanlV Source #

Arguments

:: (a -> b -> a)

funtion to generate next element

-> a

initial element

-> Vector b

input vector; length = l

-> Vector a

output vector; length = l

Performs the parallel prefix operation on a vector.

>>> scanlV (+) 0 $ vector [1,1,1,1,1,1]
<1,2,3,4,5,6>

scanrV Source #

Arguments

:: (b -> a -> a)

funtion to generate next element

-> a

initial element

-> Vector b

input vector; length = l

-> Vector a

output vector; length = l

Performs the parallel suffix operation on a vector.

>>> scanrV (+) 0 $ vector [1,1,1,1,1,1]
<6,5,4,3,2,1>

Selectors

atV :: Integral a => Vector b -> a -> b Source #

The function atV returns the n-th element in a vector, starting from zero.

>>> vector [1,2,3,4,5] `atV` 3
4

headV :: Vector a -> a Source #

The functions headV returns the first element of a vector.

tailV Source #

Arguments

:: Vector a

length = la

-> Vector a

length = la-1

The functions tailV returns all, but the first element of a vector.

lastV :: Vector a -> a Source #

The function lastV returns the last element of a vector.

initV Source #

Arguments

:: Vector a

length = la

-> Vector a

length = la-1

The function initV returns all but the last elements of a vector.

headsV Source #

Arguments

:: Vector a

length = la

-> Vector (Vector a)

length = la + 1

Returns a vector containing all the possible prefixes of an input vector.

>>> let v = vector [1,2,3,4,5,6]
>>> headsV v
<<1>,<1,2>,<1,2,3>,<1,2,3,4>,<1,2,3,4,5>,<1,2,3,4,5,6>,<1,2,3,4,5,6>>

tailsV Source #

Arguments

:: Vector a

length = la

-> Vector (Vector a)

length = la + 1

Returns a vector containing all the possible suffixes of an input vector.

>>> let v = vector [1,2,3,4,5,6]
>>> tailsV v
<<1,2,3,4,5,6>,<2,3,4,5,6>,<3,4,5,6>,<4,5,6>,<5,6>,<6>,<>>

takeV Source #

Arguments

:: (Num a, Ord a) 
=> a
= n
-> Vector b

length = la

-> Vector b

length = minimum [n,la]

The function takeV returns the first n elements of a vector.

>>> takeV 2 $ vector [1,2,3,4,5]
<1,2>

dropV Source #

Arguments

:: (Num a, Ord a) 
=> a
= n
-> Vector b

length = la

-> Vector b

length = maximum [0,la-n]

The function dropV drops the first n elements of a vector.

>>> dropV 2 $ vector [1,2,3,4,5]
<3,4,5>

selectV Source #

Arguments

:: Int

the initial element, starting from zero

-> Int

stepsize between elements

-> Int

number of elements = n

-> Vector a

length = la

-> Vector a

length = n

The function selectV selects elements in the vector based on a regular stride.

groupV Source #

Arguments

:: Int
= n
-> Vector a

length = la

-> Vector (Vector a)

length = la div n

The function groupV groups a vector into a vector of vectors of size n.

>>> groupV 3 $ vector [1,2,3,4,5,6,7,8]
<<1,2,3>,<4,5,6>>

filterV Source #

Arguments

:: (a -> Bool)

predicate function

-> Vector a

length = la

-> Vector a

length <= la (*)

The higher-function filterV takes a predicate function and a vector and creates a new vector with the elements for which the predicate is true.

>>> filterV odd $ vector [1,2,3,4,5,6,7,8]
<1,3,5,7>

(*) however, the length is unknown, because it is dependent on the data contained inside the vector. Try avoiding filterV in designs where the size of the data is crucial.

stencilV Source #

Arguments

:: Int

stencil size = n

-> Vector a

length = la

-> Vector (Vector a)

length = la - n + 1

Returns a stencil of n neighboring elements for each possible element in a vector.

>>> stencilV 3 $ vector [1..5]
<<1,2,3>,<2,3,4>,<3,4,5>>

Permutators

replaceV Source #

Arguments

:: Vector a

input vector; length = la

-> Int

position of the element to be replaced

-> a

new element

-> Vector a

altered vector; length = la

The function replaceV replaces an element in a vector.

>>> replaceV (vector [1..5]) 2 100
<1,2,100,4,5>

zipV Source #

Arguments

:: Vector a

length = la

-> Vector b

length = lb

-> Vector (a, b)

length = minimum [la,lb]

The function zipV zips two vectors into a vector of tuples.

unzipV Source #

Arguments

:: Vector (a, b)

length = la

-> (Vector a, Vector b)

length = la

The function unzipV unzips a vector of tuples into two vectors.

concatV :: Vector (Vector a) -> Vector a Source #

The function concatV transforms a vector of vectors to a single vector.

reverseV :: Vector a -> Vector a Source #

The function reverseV reverses the order of elements in a vector.

shiftlV :: Vector a -> a -> Vector a Source #

The function shiftlV shifts a value from the left into a vector.

>>> vector [1..5] `shiftlV` 100
<100,1,2,3,4>

shiftrV :: Vector a -> a -> Vector a Source #

The function shiftrV shifts a value from the right into a vector.

>>> vector [1..5] `shiftrV` 100
<2,3,4,5,100>

rotrV :: Vector a -> Vector a Source #

The function rotrV rotates a vector to the right. Note that this fuction does not change the size of a vector.

>>> rotrV $ vector [1..5]
<2,3,4,5,1>

rotlV :: Vector a -> Vector a Source #

The function rotlV rotates a vector to the left. Note that this fuctions does not change the size of a vector.

>>> rotlV $ vector [1..5]
<5,1,2,3,4>

rotateV :: Int -> Vector a -> Vector a Source #

The function rotateV rotates a vector based on an index offset.

  • (> 0) : rotates the vector left with the corresponding number of positions.
  • (= 0) : does not modify the vector.
  • (< 0) : rotates the vector right with the corresponding number of positions.