Copyright | David Johnson (c) 2019-2020 |
---|---|
License | BSD 3 |
Maintainer | David Johnson <djohnson.m@gmail.com> |
Stability | Experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
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 -- 55
Synopsis
- sum :: AFType a => Array a -> Int -> a
- sumNaN :: (Fractional a, AFType a) => Array a -> Int -> Double -> a
- product :: AFType a => Array a -> Int -> a
- productNaN :: (AFType a, Fractional a) => Array a -> Int -> Double -> a
- min :: AFType a => Array a -> Int -> a
- max :: AFType a => Array a -> Int -> a
- allTrue :: forall a. AFType a => Array a -> Int -> Bool
- anyTrue :: forall a. AFType a => Array a -> Int -> Bool
- count :: forall a. AFType a => Array a -> Int -> Int
- sumAll :: AFType a => Array a -> (Double, Double)
- sumNaNAll :: (AFType a, Fractional a) => Array a -> Double -> (Double, Double)
- productAll :: AFType a => Array a -> (Double, Double)
- productNaNAll :: (AFType a, Fractional a) => Array a -> Double -> (Double, Double)
- minAll :: AFType a => Array a -> (Double, Double)
- maxAll :: AFType a => Array a -> (Double, Double)
- allTrueAll :: AFType a => Array a -> (Double, Double)
- anyTrueAll :: AFType a => Array a -> (Double, Double)
- countAll :: AFType a => Array a -> (Double, Double)
- imin :: AFType a => Array a -> Int -> (Array a, Array a)
- imax :: AFType a => Array a -> Int -> (Array a, Array a)
- iminAll :: AFType a => Array a -> (Double, Double, Int)
- imaxAll :: AFType a => Array a -> (Double, Double, Int)
- accum :: AFType a => Array a -> Int -> Array a
- scan :: AFType a => Array a -> Int -> BinaryOp -> Bool -> Array a
- scanByKey :: (AFType a, AFType k) => Array k -> Array a -> Int -> BinaryOp -> Bool -> Array a
- where' :: AFType a => Array a -> Array a
- diff1 :: AFType a => Array a -> Int -> Array a
- diff2 :: AFType a => Array a -> Int -> Array a
- sort :: AFType a => Array a -> Int -> Bool -> Array a
- sortIndex :: AFType a => Array a -> Int -> Bool -> (Array a, Array a)
- sortByKey :: AFType a => Array a -> Array a -> Int -> Bool -> (Array a, Array a)
- setUnique :: AFType a => Array a -> Bool -> Array a
- setUnion :: AFType a => Array a -> Array a -> Bool -> Array a
- setIntersect :: AFType a => Array a -> Array a -> Bool -> Array a
Documentation
:: AFType a | |
=> Array a | Array to sum |
-> Int | Dimension along which to perform sum |
-> 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
55.0
>>>
A.sum (A.matrix @Double (10,10) [[2..],[2..]]) 0
65.0
:: (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 |
-> 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
55
:: AFType a | |
=> Array a | Array to product |
-> Int | Dimension along which to perform product |
-> 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
3628800.0
:: (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 |
-> 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
3628800.0
:: AFType a | |
=> Array a | Array input |
-> Int | Dimension along which to retrieve the min element |
-> 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
1.0
:: AFType a | |
=> Array a | Array input |
-> Int | Dimension along which to retrieve the max element |
-> 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
10
:: AFType a | |
=> Array a | Array input |
-> Int | Dimension along which to count |
-> Int | Count of all elements along dimension |
Count elements in an Array
along a dimension
>>>
A.count (A.vector @Double 10 [1..]) 0
10
Sum all elements in an Array
along all dimensions
>>>
A.sumAll (A.vector @Double 10 [1..])
(55.0,0.0)
:: (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)
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)
:: (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)
Take the minimum across all elements along all dimensions in Array
>>>
A.minAll (A.vector @Double 10 [1..])
(1.0,0.0)
Take the maximum across all elements along all dimensions in Array
>>>
A.maxAll (A.vector @Double 10 [1..])
(10.0,0.0)
Decide if all elements along all dimensions in Array
are True
>>>
A.allTrueAll (A.vector @CBool 10 (repeat 1))
(1.0, 0.0)
Decide if any elements along all dimensions in Array
are True
>>>
A.anyTrueAll $ A.vector @CBool 10 (repeat 0)
(0.0,0.0)
Count all elements along all dimensions in Array
>>>
A.countAll (A.matrix @Double (100,100) (replicate 100 [1..]))
(10000.0,0.0)
:: 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 )
:: 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 )
:: 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)
:: 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)
:: 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
:: 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>
:: 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
:: 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
:: AFType a | |
=> Array a | Input array |
-> Int | Dimension along |
-> 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
:: AFType a | |
=> Array a | Input array |
-> Int | Dimension along |
-> 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 )
:: 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 )
:: 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