arrayfire-0.6.0.0: Haskell bindings to the ArrayFire general-purpose GPU library

CopyrightDavid Johnson (c) 2019-2020
LicenseBSD 3
MaintainerDavid Johnson <djohnson.m@gmail.com>
StabilityExperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

ArrayFire.Algorithm

Description

Functions for aggregation, manipulation of Array

module Main where

import qualified ArrayFire as A

main :: IO ()
main = print $ A.sum (A.vector @Double 10 [1..]) 0
-- ArrayFire Array
-- [1 1 1 1]
--   55.0000
Synopsis

Documentation

sum Source #

Arguments

:: AFType a 
=> Array a

Array to sum

-> Int

0-based Dimension along which to perform sum

-> Array a

Will return the sum of all values in the input array along the specified dimension

Sum all of the elements in Array along the specified dimension

>>> A.sum (A.vector @Double 10 [1..]) 0
ArrayFire Array
[1 1 1 1]
   55.0000
>>> A.sum (A.matrix @Double (10,10) $ replicate 10 [1..]) 1
ArrayFire Array
[10 1 1 1]
   10.0000
   20.0000
   30.0000
   40.0000
   50.0000
   60.0000
   70.0000
   80.0000
   90.0000
  100.0000

sumNaN Source #

Arguments

:: (Fractional a, AFType a) 
=> Array a

Array to sum

-> Int

Dimension along which to perform sum

-> Double

Default value to use in the case of NaN

-> Array a

Will return the sum of all values in the input array along the specified dimension, substituted with the default value

Sum all of the elements in Array along the specified dimension, using a default value for NaN

>>> A.sumNaN (A.vector @Double 10 [1..]) 0 0.0
ArrayFire Array
[1 1 1 1]
  55.0000

product Source #

Arguments

:: AFType a 
=> Array a

Array to product

-> Int

Dimension along which to perform product

-> Array a

Will return the product of all values in the input array along the specified dimension

Product all of the elements in Array along the specified dimension

>>> A.product (A.vector @Double 10 [1..]) 0
ArrayFire Array
[1 1 1 1]
3628800.0000

productNaN Source #

Arguments

:: (AFType a, Fractional a) 
=> Array a

Array to product

-> Int

Dimension along which to perform product

-> Double

Default value to use in the case of NaN

-> Array a

Will return the product of all values in the input array along the specified dimension, substituted with the default value

Product all of the elements in Array along the specified dimension, using a default value for NaN

>>> A.productNaN (A.vector @Double 10 [1..]) 0 0.0
ArrayFire Array
[1 1 1 1]
3628800.0000

min Source #

Arguments

:: AFType a 
=> Array a

Array input

-> Int

Dimension along which to retrieve the min element

-> Array a

Will contain the minimum of all values in the input array along dim

Take the minimum of an Array along a specific dimension

>>> A.min (A.vector @Double 10 [1..]) 0
ArrayFire Array
[1 1 1 1]
   1.0000

max Source #

Arguments

:: AFType a 
=> Array a

Array input

-> Int

Dimension along which to retrieve the max element

-> Array a

Will contain the maximum of all values in the input array along dim

Take the maximum of an Array along a specific dimension

>>> A.max (A.vector @Double 10 [1..]) 0
ArrayFire Array
[1 1 1 1]
  10.0000

allTrue Source #

Arguments

:: AFType a 
=> Array a

Array input

-> Int

Dimension along which to see if all elements are True

-> Array a

Will contain the maximum of all values in the input array along dim

Find if all elements in an Array are True along a dimension

>>> A.allTrue (A.vector @CBool 10 (repeat 0)) 0
ArrayFire Array
[1 1 1 1]
        0

anyTrue Source #

Arguments

:: AFType a 
=> Array a

Array input

-> Int

Dimension along which to see if all elements are True

-> Array a

Returns if all elements are true

Find if any elements in an Array are True along a dimension

>>> A.anyTrue (A.vector @CBool 10 (repeat 0)) 0
ArrayFire Array
[1 1 1 1]
        0

count Source #

Arguments

:: AFType a 
=> Array a

Array input

-> Int

Dimension along which to count

-> Array Int

Count of all elements along dimension

Count elements in an Array along a dimension

>>> A.count (A.vector @Double 10 [1..]) 0
ArrayFire Array
[1 1 1 1]
       10

sumAll Source #

Arguments

:: AFType a 
=> Array a

Input array

-> (Double, Double)

imaginary and real part

Sum all elements in an Array along all dimensions

>>> A.sumAll (A.vector @Double 10 [1..])
(55.0,0.0)

sumNaNAll Source #

Arguments

:: (AFType a, Fractional a) 
=> Array a

Input array

-> Double

NaN substitute

-> (Double, Double)

imaginary and real part

Sum all elements in an Array along all dimensions, using a default value for NaN

>>> A.sumNaNAll (A.vector @Double 10 [1..]) 0.0
(55.0,0.0)

productAll Source #

Arguments

:: AFType a 
=> Array a

Input array

-> (Double, Double)

imaginary and real part

Product all elements in an Array along all dimensions, using a default value for NaN

>>> A.productAll (A.vector @Double 10 [1..])
(3628800.0,0.0)

productNaNAll Source #

Arguments

:: (AFType a, Fractional a) 
=> Array a

Input array

-> Double

NaN substitute

-> (Double, Double)

imaginary and real part

Product all elements in an Array along all dimensions, using a default value for NaN

>>> A.productNaNAll (A.vector @Double 10 [1..]) 1.0
(3628800.0,0.0)

minAll Source #

Arguments

:: AFType a 
=> Array a

Input array

-> (Double, Double)

imaginary and real part

Take the minimum across all elements along all dimensions in Array

>>> A.minAll (A.vector @Double 10 [1..])
(1.0,0.0)

maxAll Source #

Arguments

:: AFType a 
=> Array a

Input array

-> (Double, Double)

imaginary and real part

Take the maximum across all elements along all dimensions in Array

>>> A.maxAll (A.vector @Double 10 [1..])
(10.0,0.0)

allTrueAll Source #

Arguments

:: AFType a 
=> Array a

Input array

-> (Double, Double)

imaginary and real part

Decide if all elements along all dimensions in Array are True

>>> A.allTrueAll (A.vector @CBool 10 (repeat 1))
(1.0, 0.0)

anyTrueAll Source #

Arguments

:: AFType a 
=> Array a

Input array

-> (Double, Double)

imaginary and real part

Decide if any elements along all dimensions in Array are True

>>> A.anyTrueAll $ A.vector @CBool 10 (repeat 0)
(0.0,0.0)

countAll Source #

Arguments

:: AFType a 
=> Array a

Input array

-> (Double, Double)

imaginary and real part

Count all elements along all dimensions in Array

>>> A.countAll (A.matrix @Double (100,100) (replicate 100 [1..]))
(10000.0,0.0)

imin Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Int

The dimension along which the minimum value is extracted

-> (Array a, Array a)

will contain the minimum of all values along dim, will also contain the location of minimum of all values in in along dim

Find the minimum element along a specified dimension in Array

>>> A.imin (A.vector @Double 10 [1..]) 0
(ArrayFire Array
[1 1 1 1]
   1.0000
,ArrayFire Array
[1 1 1 1]
        0
)

imax Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Int

The dimension along which the minimum value is extracted

-> (Array a, Array a)

will contain the maximum of all values in in along dim, will also contain the location of maximum of all values in in along dim

Find the maximum element along a specified dimension in Array

>>> A.imax (A.vector @Double 10 [1..]) 0
(ArrayFire Array
[1 1 1 1]
  10.0000
,ArrayFire Array
[1 1 1 1]
        9
)

iminAll Source #

Arguments

:: AFType a 
=> Array a

Input array

-> (Double, Double, Int)

will contain the real part of minimum value of all elements in input in, also will contain the imaginary part of minimum value of all elements in input in, will contain the location of minimum of all values in

Find the minimum element along all dimensions in Array

>>> A.iminAll (A.vector @Double 10 [1..])
(1.0,0.0,0)

imaxAll Source #

Arguments

:: AFType a 
=> Array a

Input array

-> (Double, Double, Int)

will contain the real part of maximum value of all elements in input in, also will contain the imaginary part of maximum value of all elements in input in, will contain the location of maximum of all values in

Find the maximum element along all dimensions in Array

>>> A.imaxAll (A.vector @Double 10 [1..])
(10.0,0.0,9)

accum Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Int

Dimension along which to calculate the sum

-> Array a

Contains inclusive sum

Calculate sum of Array across specified dimension

>>> A.accum (A.vector @Double 10 [1..]) 0
ArrayFire Array
[10 1 1 1]
    1.0000
    3.0000
    6.0000
   10.0000
   15.0000
   21.0000
   28.0000
   36.0000
   45.0000
   55.0000

scan Source #

Arguments

:: AFType a 
=> Array a

The input array

-> Int

The dimension along which the scan is performed

-> BinaryOp

Binary operation to be used

-> Bool

Should the scan be inclusive or not

-> Array a

The scan of the input

Scan elements of an Array across a dimension, using a BinaryOp, specifying inclusivity.

>>> A.scan (A.vector @Double 10 [1..]) 0 Add True
ArrayFire Array
[10 1 1 1]
    1.0000
    3.0000
    6.0000
   10.0000
   15.0000
   21.0000
   28.0000
   36.0000
   45.0000
   55.0000

scanByKey Source #

Arguments

:: (AFType a, AFType k) 
=> Array k

The key array

-> Array a

The input array

-> Int

Dimension along which scan is performed

-> BinaryOp

Type of binary operation used

-> Bool

Is the scan incluside or not

-> Array a 

Scan elements of an Array across a dimension, by key, using a BinaryOp, specifying inclusivity.

>>> A.scanByKey (A.vector @Int 7 [2..]) (A.vector @Int 10 [1..]) 1 Add True
ArrayFire Array
[10 1 1 1]
         1
         2
         3
         4
         5
         6
         7
         8
         9
        10

where' Source #

Arguments

:: AFType a 
=> Array a

Is the input array.

-> Array a

will contain indices where input array is non-zero

Find indices where input Array is non zero

>>> A.where' (A.vector @Double 10 (repeat 0))
ArrayFire Array
[0 1 1 1]
<empty>

diff1 Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Int

Dimension along which numerical difference is performed

-> Array a

Will contain first order numerical difference

First order numerical difference along specified dimension.

>>> A.diff1 (A.vector @Double 4 [10,35,65,95]) 0
ArrayFire Array
[3 1 1 1]
   25.0000
   30.0000
   30.0000

diff2 Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Int

Dimension along which numerical difference is performed

-> Array a

Will contain second order numerical difference

Second order numerical difference along specified dimension.

>>> A.diff2 (A.vector @Double 5 [1.0,20,55,89,44]) 0
ArrayFire Array
[3 1 1 1]
   16.0000
   -1.0000
  -79.0000

sort Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Int

Dimension along sort is performed

-> Bool

Return results in ascending order

-> Array a

Will contain sorted input

Sort an Array along a specified dimension, specifying ordering of results (ascending / descending)

>>> A.sort (A.vector @Double 4 [ 2,4,3,1 ]) 0 True
ArrayFire Array
[4 1 1 1]
    1.0000
    2.0000
    3.0000
    4.0000
>>> A.sort (A.vector @Double 4 [ 2,4,3,1 ]) 0 False
ArrayFire Array
[4 1 1 1]
    4.0000
    3.0000
    2.0000
    1.0000

sortIndex Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Int

Dimension along sortIndex is performed

-> Bool

Return results in ascending order

-> (Array a, Array a)

Contains the sorted, contains indices for original input

Sort an Array along a specified dimension, specifying ordering of results (ascending / descending), returns indices of sorted results

>>> A.sortIndex (A.vector @Double 4 [3,2,1,4]) 0 True
(ArrayFire Array
[4 1 1 1]
    1.0000
    2.0000
    3.0000
    4.0000
,ArrayFire Array
[4 1 1 1]
         2
         1
         0
         3
)

sortByKey Source #

Arguments

:: AFType a 
=> Array a

Keys input array

-> Array a

Values input array

-> Int

Dimension along which to perform the operation

-> Bool

Return results in ascending order

-> (Array a, Array a) 

Sort an Array along a specified dimension by keys, specifying ordering of results (ascending / descending)

>>> A.sortByKey (A.vector @Double 4 [2,1,4,3]) (A.vector @Double 4 [10,9,8,7]) 0 True
(ArrayFire Array
[4 1 1 1]
    1.0000
    2.0000
    3.0000
    4.0000
,ArrayFire Array
[4 1 1 1]
    9.0000
   10.0000
    7.0000
    8.0000
)

setUnique Source #

Arguments

:: AFType a 
=> Array a

input array

-> Bool

if true, skips the sorting steps internally

-> Array a

Will contain the unique values from in

Finds the unique values in an Array, specifying if sorting should occur.

>>> A.setUnique (A.vector @Double 2 [1.0,1.0]) True
ArrayFire Array
[1 1 1 1]
   1.0000

setUnion Source #

Arguments

:: AFType a 
=> Array a

First input array

-> Array a

Second input array

-> Bool

If true, skips calling unique internally

-> Array a 

Takes the union of two Arrays, specifying if setUnique should be called first.

>>> A.setUnion (A.vector @Double 3 [3,4,5]) (A.vector @Double 3 [1,2,3]) True
ArrayFire Array
[5 1 1 1]
    1.0000
    2.0000
    3.0000
    4.0000
    5.0000

setIntersect Source #

Arguments

:: AFType a 
=> Array a

First input array

-> Array a

Second input array

-> Bool

If true, skips calling unique internally

-> Array a

Intersection of first and second array

Takes the intersection of two Arrays, specifying if setUnique should be called first.

>>> A.setIntersect (A.vector @Double 3 [3,4,5]) (A.vector @Double 3 [1,2,3]) True
ArrayFire Array
[1 1 1 1]
    3.0000