arrayfire-0.5.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.Array

Description

Functions for constructing and querying metadata from Array

module Main where

import ArrayFire

main :: IO ()
main = print (matrix @Double (2,2) [ [1..], [1..] ])
ArrayFire Array
[2 2 1 1]
    1.0000     1.0000
    2.0000     2.0000
Synopsis

Documentation

scalar :: AFType a => a -> Array a Source #

Smart constructor for creating a scalar Array

>>> scalar @Double 2.0
ArrayFire Array
[1 1 1 1]
   2.0000

vector :: AFType a => Int -> [a] -> Array a Source #

Smart constructor for creating a vector Array

>>> vector @Double 10 [1..]
ArrayFire Array
[10 1 1 1]
    1.0000
    2.0000
    3.0000
    4.0000
    5.0000
    6.0000
    7.0000
    8.0000
    9.0000
   10.0000

matrix :: AFType a => (Int, Int) -> [[a]] -> Array a Source #

Smart constructor for creating a matrix Array

>>> A.matrix @Double (3,2) [[1,2,3],[4,5,6]]
ArrayFire Array
[3 2 1 1]
   1.0000     4.0000
   2.0000     5.0000
   3.0000     6.0000

cube :: AFType a => (Int, Int, Int) -> [[[a]]] -> Array a Source #

Smart constructor for creating a cubic Array

>>> cube @Double (2,2,2) [[[2,2],[2,2]],[[2,2],[2,2]]]
ArrayFire Array
[2 2 2 1]
   2.0000     2.0000
   2.0000     2.0000

   2.0000     2.0000
   2.0000     2.0000

tensor :: AFType a => (Int, Int, Int, Int) -> [[[[a]]]] -> Array a Source #

Smart constructor for creating a tensor Array

>>> tensor @Double (2,2,2,2) [[[[2,2],[2,2]],[[2,2],[2,2]]], [[[2,2],[2,2]],[[2,2],[2,2]]]]
ArrayFire Array
[2 2 2 2]
    2.0000     2.0000
    2.0000     2.0000

    2.0000     2.0000
    2.0000     2.0000


    2.0000     2.0000
    2.0000     2.0000

    2.0000     2.0000
    2.0000     2.0000

mkArray Source #

Arguments

:: AFType array 
=> [Int]

Dimensions

-> [array]

Array elements

-> Array array

Returned array

Internal function for Array construction

>>> mkArray @Double [10] [1.0 .. 10.0]
ArrayFire Array
[10 1 1 1]
    1.0000
    2.0000
    3.0000
    4.0000
    5.0000
    6.0000
    7.0000
    8.0000
    9.0000
   10.0000

copyArray Source #

Arguments

:: AFType a 
=> Array a

Array to be copied

-> Array a

Newly copied Array

Copies an Array to a new Array

>>> copyArray (scalar @Double 10)
ArrayFire Array
[1 1 1 1]
  10.0000

retainArray Source #

Arguments

:: AFType a 
=> Array a

Input Array

-> Array a 

Retains an Array, increases reference count

>>> retainArray (scalar @Double 10)
ArrayFire Array
[1 1 1 1]
  10.0000

getDataRefCount Source #

Arguments

:: AFType a 
=> Array a

Input Array

-> Int

Reference count

Retrieves Array reference count

>>> initialArray = scalar @Double 10
>>> retainedArray = retain initialArray
>>> getDataRefCount retainedArray
2

setManualEvalFlag Source #

Arguments

:: Bool

Whether or not to perform manual evaluation

-> IO () 

Should manual evaluation occur

>>> setManualEvalFlag True
()

getManualEvalFlag :: IO Bool Source #

Retrieve manual evaluation status

>>> setManualEvalFlag False
>>> getManualEvalFlag
False

getElements Source #

Arguments

:: AFType a 
=> Array a

Input Array

-> Int

Count of elements in Array

Retrieve element count

>>> getElements (vector @Double 10 [1..])
10

getType :: AFType a => Array a -> AFDType Source #

Retrieve type of Array

>>> getType (vector @Double 10 [1..])
F64

getDims :: AFType a => Array a -> (Int, Int, Int, Int) Source #

Retrieves dimensions of Array

>>> getDims (vector @Double 10 [1..])
(10,1,1,1)

getNumDims :: AFType a => Array a -> Int Source #

Retrieves number of dimensions in Array

>>> getNumDims (matrix @Double (2,2) [[1..],[1..]])
2

isEmpty :: AFType a => Array a -> Bool Source #

Checks if an Array is empty

>>> isEmpty (matrix @Double (2,2) [[1..],[1..]])
False

isScalar :: AFType a => Array a -> Bool Source #

Checks if an Array is a scalar (contains only one element)

>>> isScalar (matrix @Double (2,2) [[1..],[1..]])
False
>>> isScalar (1.0 :: Array Double)
True

isRow :: AFType a => Array a -> Bool Source #

Checks if an Array is row-oriented

>>> isRow (matrix @Double (2,2) [[1..],[1..]])
False

isColumn :: AFType a => Array a -> Bool Source #

Checks if an Array is a column-oriented

>>> isColumn (vector @Double 10 [1..])
True

isVector :: AFType a => Array a -> Bool Source #

Checks if an Array is a vector

>>> isVector (vector @Double 10 [1..])
True
>>> isVector (1.0 :: Array Double)
False

isComplex :: AFType a => Array a -> Bool Source #

Checks if an Array is a Complex

>>> isComplex (scalar (1.0 :+ 1.0) :: Array (Complex Double))
True

isReal :: AFType a => Array a -> Bool Source #

Checks if an Array is Real

>>> isReal (scalar 1.0 :: Array Double)
True

isDouble :: AFType a => Array a -> Bool Source #

Checks if an Array is Double

>>> isDouble (scalar 1.0 :: Array Double)
True

isSingle :: AFType a => Array a -> Bool Source #

Checks if an Array is Float

>>> isSingle (scalar 1.0 :: Array Float)
True

isRealFloating :: AFType a => Array a -> Bool Source #

Checks if an Array is Double, Float, Complex Double, or Complex Float

>>> isRealFloating (scalar 1.0 :: Array Double)
True

isFloating :: AFType a => Array a -> Bool Source #

Checks if an Array is Double or Float

>>> isFloating (scalar 1.0 :: Array Double)
True

isInteger :: AFType a => Array a -> Bool Source #

Checks if an Array is of type Int16, Int32, or Int64

>>> isInteger (scalar 1 :: Array Int16)
True

isBool :: AFType a => Array a -> Bool Source #

Checks if an Array is of type CBool

>>> isBool (scalar 1 :: Array CBool)
True

isSparse :: AFType a => Array a -> Bool Source #

Checks if an Array is sparse

>>> isSparse (scalar 1 :: Array Double)
False

toVector :: forall a. AFType a => Array a -> Vector a Source #

Converts an Array to a Storable Vector

>>> toVector (vector @Double 10 [1..])
[1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0]

toList :: forall a. AFType a => Array a -> [a] Source #

Converts an Array to [a]

>>> toList (vector @Double 10 [1..])
[1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0]

getScalar :: forall a b. (Storable a, AFType b) => Array b -> a Source #

Retrieves single scalar value from an Array

>>> getScalar (scalar @Double 22.0) :: Double
22.0