arrayfire-0.1.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.Arith

Description

Arithmetic functions over Array

module Main where

import qualified ArrayFire as A

main :: IO ()
main = print $ A.scalar @Int 1 `A.add` A.scalar @Int 1
-- 2
Synopsis

Documentation

add Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of add

Adds two Array objects

>>> A.scalar @Int 1 `A.add` A.scalar @Int 1
ArrayFire Array
[1 1 1 1]
        2

addBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of add

Adds two Array objects

>>> (A.scalar @Int 1 `A.addBatched` A.scalar @Int 1) True
ArrayFire Array
[1 1 1 1]
        2

sub Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of sub

Subtracts two Array objects

>>> A.scalar @Int 1 `A.sub` A.scalar @Int 1
ArrayFire Array
[1 1 1 1]
        0

subBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of sub

Subtracts two Array objects

>>> (A.scalar @Int 1 `subBatched` A.scalar @Int 1) True
ArrayFire Array
[1 1 1 1]
        0

mul Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of mul

Multiply two Array objects

>>> A.scalar @Int 2 `mul` A.scalar @Int 2
ArrayFire Array
[1 1 1 1]
        4

mulBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of mul

Multiply two Array objects

>>> (A.scalar @Int 2 `mulBatched` A.scalar @Int 2) True
ArrayFire Array
[1 1 1 1]
        4

div Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of div

Divide two Array objects

>>> A.scalar @Int 6 `A.div` A.scalar @Int 3
ArrayFire Array
[1 1 1 1]
        2

divBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of div

Divide two Array objects

>>> (A.scalar @Int 6 `A.divBatched` A.scalar @Int 3) True
ArrayFire Array
[1 1 1 1]
        2

lt Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of less than

Test if on Array is less than another Array

>>> A.scalar @Int 1 `A.lt` A.scalar @Int 1
ArrayFire Array
[1 1 1 1]
        0
>>> A.scalar @Int 1 < A.scalar @Int 1
False

ltBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of less than

Test if on Array is less than another Array

>>> (A.scalar @Int 1 `A.ltBatched` A.scalar @Int 1) True
ArrayFire Array
[1 1 1 1]
        0
>>> A.scalar @Int 1 < A.scalar @Int 1
False

gt Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of gt

Test if an Array is greater than another Array

>>> A.scalar @Int 1 `A.gt` A.scalar @Int 1
ArrayFire Array
[1 1 1 1]
        0
>>> A.scalar @Int 1 > A.scalar @Int 2
False

gtBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of gt

Test if an Array is greater than another Array

>>> (A.scalar @Int 1 `gtBatched` A.scalar @Int 1) True
False

le Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of less than or equal

Test if one Array is less than or equal to another Array

>>> A.scalar @Int 1 `A.le` A.scalar @Int 1
ArrayFire Array
[1 1 1 1]
        1
>>> A.scalar @Int 1 <= A.scalar @Int 1
False

leBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of less than or equal

Test if one Array is less than or equal to another Array

>>> (A.scalar @Int 1 `A.leBatched` A.scalar @Int 1) True
ArrayFire Array
[1 1 1 1]
        1
>>> A.scalar @Int 1 <= A.scalar @Int 1
True

ge Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of greater than or equal

Test if one Array is greater than or equal to another Array

>>> A.scalar @Int 1 `A.ge` A.scalar @Int 1
ArrayFire Array
[1 1 1 1]
        1
>>> A.scalar @Int 1 >= A.scalar @Int 1
True

geBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of greater than or equal

Test if one Array is greater than or equal to another Array

>>> (A.scalar @Int 1 `A.geBatched` A.scalar @Int 1) True

eq Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of equal

Test if one Array is equal to another Array

>>> A.scalar @Int 1 `A.eq` A.scalar @Int 1
ArrayFire Array
[1 1 1 1]
        1
>>> A.scalar @Int 1 == A.scalar @Int 1
True

eqBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of equal

Test if one Array is equal to another Array

>>> (A.scalar @Int 1 `A.eqBatched` A.scalar @Int 1) True

neq Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of not equal

Test if one Array is not equal to another Array

>>> A.scalar @Int 1 `A.neq` A.scalar @Int 1
ArrayFire Array
[1 1 1 1]
        0
>>> A.scalar @Int 1 /= A.scalar @Int 1
False

neqBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of not equal

Test if one Array is not equal to another Array

>>> (A.scalar @Int 1 `A.neqBatched` A.scalar @Int 1) True
False

and Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of and

Logical and one Array with another

>>> A.scalar @Int 1 `A.and` A.scalar @Int 1
ArrayFire Array
[1 1 1 1]
         1

andBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of and

Logical and one Array with another

>>> (A.scalar @Int 1 `andBatched` A.scalar @Int 1) True
ArrayFire Array
[1 1 1 1]
        1

or Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of or

Logical or one Array with another

>>> A.scalar @Int 1 `A.or` A.scalar @Int 1
ArrayFire Array
[1 1 1 1]
        1

orBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of or

Logical or one Array with another

>>> (A.scalar @Int 1 `A.orBatched` A.scalar @Int 1) True
ArrayFire Array
[1 1 1 1]
        1

not Source #

Arguments

:: AFType a 
=> Array a

Input Array

-> Array a

Result of not on an Array

Not the values of an Array

>>> A.not (A.scalar @Int 1)
ArrayFire Array
[1 1 1 1]
        0

bitAnd Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of bitwise and

Bitwise and the values in one Array against another Array

>>> A.bitAnd (A.scalar @Int 1) (A.scalar @Int 1)
ArrayFire Array
[1 1 1 1]
        1

bitAndBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of bitwise and

Bitwise and the values in one Array against another Array

bitOr Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of bit or

Bitwise or the values in one Array against another Array

>>> A.bitOr (A.scalar @Int 1) (A.scalar @Int 1)
ArrayFire Array
[1 1 1 1]
        1

bitOrBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of bit or

Bitwise or the values in one Array against another Array

>>> A.bitOrBatched (A.scalar @Int 1) (A.scalar @Int 1) False
ArrayFire Array
[1 1 1 1]
        1

bitXor Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of bit xor

Bitwise xor the values in one Array against another Array

>>> A.bitXor (A.scalar @Int 1) (A.scalar @Int 1)
ArrayFire Array
[1 1 1 1]
        0

bitXorBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of bit xor

Bitwise xor the values in one Array against another Array

>>> A.bitXorBatched (A.scalar @Int 1) (A.scalar @Int 1) False
ArrayFire Array
[1 1 1 1]
        0

bitShiftL Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of bit shift left

Left bit shift the values in one Array against another Array

>>> A.bitShiftL (A.scalar @Int 1) (A.scalar @Int 1)
ArrayFire Array
[1 1 1 1]
        2

bitShiftLBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of bit shift left

Left bit shift the values in one Array against another Array

>>> A.bitShiftLBatched (A.scalar @Int 1) (A.scalar @Int 1) False
ArrayFire Array
[1 1 1 1]
        2

bitShiftR Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of bit shift right

Right bit shift the values in one Array against another Array

>>> A.bitShiftR (A.scalar @Int 1) (A.scalar @Int 1)
ArrayFire Array
[1 1 1 1]
        0

bitShiftRBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of bit shift left

Right bit shift the values in one Array against another Array

>>> A.bitShiftRBatched (A.scalar @Int 1) (A.scalar @Int 1) False
ArrayFire Array
[1 1 1 1]
        0

cast Source #

Arguments

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

Input array to cast

-> Array b

Result of cast

Cast one Array into another

>>> A.cast (A.scalar @Int 1) :: Array Double
ArrayFire Array
[1 1 1 1]
   1.0000

minOf Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of minimum of

Find the minimum of two Arrays

>>> A.minOf (A.scalar @Int 1) (A.scalar @Int 0)
ArrayFire Array
[1 1 1 1]
        0

minOfBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of minimum of

Find the minimum of two Arrays

>>> A.minOfBatched (A.scalar @Int 1) (A.scalar @Int 0) False
ArrayFire Array
[1 1 1 1]
        0

maxOf Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of maximum of

Find the maximum of two Arrays

>>> A.maxOf (A.scalar @Int 1) (A.scalar @Int 0)
ArrayFire Array
[1 1 1 1]
        1

maxOfBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of maximum of

Find the maximum of two Arrays

>>> A.maxOfBatched (A.scalar @Int 1) (A.scalar @Int 0) False
ArrayFire Array
[1 1 1 1]
        1

clamp Source #

Arguments

:: Array a

input

-> Array a

lower bound

-> Array a

upper bound

-> Array a

Result of clamp

Should take the clamp

>>> clamp (A.scalar @Int 2) (A.scalar @Int 1) (A.scalar @Int 3)
ArrayFire Array
[1 1 1 1]
         2

clampBatched Source #

Arguments

:: Array a

First input

-> Array a

Second input

-> Array a

Third input

-> Bool

Use batch

-> Array a

Result of clamp

Should take the clamp

>>> (clampBatched (A.scalar @Int 2) (A.scalar @Int 1) (A.scalar @Int 3)) True
ArrayFire Array
[1 1 1 1]
         2

rem Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of remainder

Find the remainder of two Arrays

>>> A.rem (A.vector @Int 10 [1..]) (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
        0          0          0          0          0          0          0          0          0          0

remBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of remainder

Find the remainder of two Arrays

>>> A.remBatched (A.vector @Int 10 [1..])  (vector @Int 10 [1..]) True

mod Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of mod

Take the mod of two Arrays

>>> A.mod (A.vector @Int 10 [1..]) (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
        0          0          0          0          0          0          0          0          0          0

modBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of mod

Take the mod of two Arrays

>>> A.modBatched (vector @Int 10 [1..]) (vector @Int 10 [1..]) True
ArrayFire Array
[10 1 1 1]
        0          0          0          0          0          0          0          0          0          0

abs Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling abs

Take the absolute value of an array

>>> A.abs (A.scalar @Int (-1))
ArrayFire Array
[1 1 1 1]
   1.0000

arg Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling arg

Find the arg of an array

>>> A.arg (vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
        0          0          0          0          0          0          0          0          0          0

sign Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling sign

Find the sign of two Arrays

>>> A.sign (vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
  0.0000     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000

round Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling round

Round the values in an Array

>>> A.round (A.vector @Int 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

trunc Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling trunc

Truncate the values of an Array

>>> A.trunc (A.vector @Int 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

floor Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling floor

Take the floor of all values in an Array

>>> A.floor (A.vector @Int 10 [10,9..])
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

ceil Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling ceil

Take the ceil of all values in an Array

>>> A.ceil (A.vector @Int 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

sin Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling sin

Take the sin of all values in an Array

>>> A.sin (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.8415     0.9093     0.1411    -0.7568    -0.9589    -0.2794     0.6570     0.9894     0.4121    -0.5440

cos Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling cos

Take the cos of all values in an Array

>>> A.cos (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.5403    -0.4161    -0.9900    -0.6536     0.2837     0.9602     0.7539    -0.1455    -0.9111    -0.8391

tan Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling tan

Take the tan of all values in an Array

>>> A.tan (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   1.5574    -2.1850    -0.1425     1.1578    -3.3805    -0.2910     0.8714    -6.7997    -0.4523     0.6484

asin Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling asin

Take the asin of all values in an Array

>>> A.asin (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   1.5708        nan        nan        nan        nan        nan        nan        nan        nan        nan

acos Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling acos

Take the acos of all values in an Array

>>> A.acos (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.0000        nan        nan        nan        nan        nan        nan        nan        nan        nan

atan Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling atan

Take the atan of all values in an Array

>>> A.atan (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.7854     1.1071     1.2490     1.3258     1.3734     1.4056     1.4289     1.4464     1.4601     1.4711

atan2 Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of atan2

Take the atan2 of all values in an Array

>>> A.atan2 (A.vector @Int 10 [1..]) (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.7854     0.7854     0.7854     0.7854     0.7854     0.7854     0.7854     0.7854     0.7854     0.7854

atan2Batched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of atan2

Take the atan2 of all values in an Array

>>> A.atan2Batched (A.vector @Int 10 [1..]) (A.vector @Int 10 [1..]) True
ArrayFire Array
[10 1 1 1]
   0.7854     0.7854     0.7854     0.7854     0.7854     0.7854     0.7854     0.7854     0.7854     0.7854

cplx2 Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of cplx2

Take the cplx2 of all values in an Array

>>> A.cplx2 (A.vector @Int 10 [1..]) (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
        (1.0000,1.0000)          (2.0000,2.0000)          (3.0000,3.0000)          (4.0000,4.0000)          (5.0000,5.0000)          (6.0000,6.0000)          (7.0000,7.0000)          (8.0000,8.0000)          (9.0000,9.0000)          (10.0000,10.0000)

cplx2Batched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of cplx2

Take the cplx2Batched of all values in an Array

>>> A.cplx2Batched (A..vector @Int 10 [1..]) (A.vector @Int 10 [1..]) True
ArrayFire Array
[10 1 1 1]
        (1.0000,1.0000)          (2.0000,2.0000)          (3.0000,3.0000)          (4.0000,4.0000)          (5.0000,5.0000)          (6.0000,6.0000)          (7.0000,7.0000)          (8.0000,8.0000)          (9.0000,9.0000)          (10.0000,10.0000)

cplx Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling atan

Execute cplx

>>> A.cplx (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
        (1.0000,0.0000)          (2.0000,0.0000)          (3.0000,0.0000)          (4.0000,0.0000)          (5.0000,0.0000)          (6.0000,0.0000)          (7.0000,0.0000)          (8.0000,0.0000)          (9.0000,0.0000)          (10.0000,0.0000)

real Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling real

Execute real

>>> A.real (A.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

imag Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling imag

Execute imag

>>> A.imag (A.vector @Double 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.0000     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000

conjg Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling conjg

Execute conjg

>>> A.conjg (A.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

sinh Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling sinh

Execute sinh

>>> A.sinh (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   1.1752     3.6269    10.0179    27.2899    74.2032   201.7132   548.3161  1490.4788  4051.5419 11013.2329

cosh Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling cosh

Execute cosh

>>> A.cosh (A.vector @Double 10 [1..])
ArrayFire Array
[10 1 1 1]
   1.5431     3.7622    10.0677    27.3082    74.2099   201.7156   548.3170  1490.4792  4051.5420 11013.2329

tanh Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling tanh

Execute tanh

>>> A.tanh (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.7616     0.9640     0.9951     0.9993     0.9999     1.0000     1.0000     1.0000     1.0000     1.0000

asinh Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling tanh

Execute asinh

>>> A.asinh (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.8814     1.4436     1.8184     2.0947     2.3124     2.4918     2.6441     2.7765     2.8934     2.9982 

acosh Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling tanh

Execute acosh

>>> A.acosh (A.vector @Double 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.0000     1.3170     1.7627     2.0634     2.2924     2.4779     2.6339     2.7687     2.8873     2.9932 

atanh Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling tanh

Execute atanh

>>> A.atanh (A.vector @Double 10 [1..])
ArrayFire Array
[10 1 1 1]
       inf        nan        nan        nan        nan        nan        nan        nan        nan        nan 

root Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of root

Execute root

>>> A.root (A.vector @Double 10 [1..]) (A.vector @Double 10 [1..])
ArrayFire Array
[10 1 1 1]
   1.0000     1.4142     1.4422     1.4142     1.3797     1.3480     1.3205     1.2968     1.2765     1.2589

rootBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of root

Execute rootBatched

>>> A.rootBatched (vector @Double 10 [1..]) (vector @Double 10 [1..]) True
ArrayFire Array
[10 1 1 1]
   1.0000     1.4142     1.4422     1.4142     1.3797     1.3480     1.3205     1.2968     1.2765     1.2589

pow Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Array a

Result of pow

Execute pow

>>> A.pow (A.vector @Int 10 [1..]) 2
ArrayFire Array
[10 1 1 1]
        1          4          9         16         25         36         49         64         81        100

powBatched Source #

Arguments

:: AFType a 
=> Array a

First input

-> Array a

Second input

-> Bool

Use batch

-> Array a

Result of powBatched

Execute powBatched

>>> A.powBatched (A.vector @Int 10 [1..]) (A.constant @Int [1] 2) True
ArrayFire Array
[10 1 1 1]
        1          4          9         16         25         36         49         64         81        100

pow2 Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling pow2

Raise an Array to the second power

>>> A.pow2 (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
        2          4          8         16         32         64        128        256        512       1024

exp Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling exp

Execute exp on Array

>>> A.exp (A.vector @Double 10 [1..])
ArrayFire Array
[10 1 1 1]
   2.7183     7.3891    20.0855    54.5982   148.4132   403.4288  1096.6332  2980.9580  8103.0839 22026.4658 

sigmoid Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling sigmoid

Execute sigmoid on Array

>>> A.sigmoid (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.7311     0.8808     0.9526     0.9820     0.9933     0.9975     0.9991     0.9997     0.9999     1.0000

expm1 Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling expm1

Execute expm1

>>> A.expm1 (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   1.7183     6.3891    19.0855    53.5981   147.4132   402.4288  1095.6332  2979.9580  8102.0840 22025.4648

erf Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling erf

Execute erf

>>> A.erf (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.8427     0.9953     1.0000     1.0000     1.0000     1.0000     1.0000     1.0000     1.0000     1.0000

erfc Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling erfc

Execute erfc

>>> A.erfc (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.1573     0.0047     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000     0.0000

log Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling log

Execute log

>>> A.log (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.0000     0.6931     1.0986     1.3863     1.6094     1.7918     1.9459     2.0794     2.1972     2.3026

log1p Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling log1p

Execute log1p

>>> A.log1p (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.6931     1.0986     1.3863     1.6094     1.7918     1.9459     2.0794     2.1972     2.3026     2.3979

log10 Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling log10

Execute log10

>>> A.log10 (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.0000     0.3010     0.4771     0.6021     0.6990     0.7782     0.8451     0.9031     0.9542     1.0000

log2 Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling log2

Execute log2

>>> A.log2 (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.0000     1.0000     1.5850     2.0000     2.3219     2.5850     2.8074     3.0000     3.1699     3.3219

sqrt Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling sqrt

Execute sqrt

>>> A.sqrt (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   1.0000     1.4142     1.7321     2.0000     2.2361     2.4495     2.6458     2.8284     3.0000     3.1623

cbrt Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling cbrt

Execute cbrt

>>> A.cbrt (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   1.0000     1.2599     1.4422     1.5874     1.7100     1.8171     1.9129     2.0000     2.0801     2.1544

factorial Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling factorial

Execute factorial1

>>> A.factorial1 (A.vector @Int 10 [1..])

tgamma Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling tgamma

Execute tgamma

>>> 'tgamma' (vector @Int 10 [1..])

lgamma Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling lgamma

Execute lgamma

>>> A.lgamma (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
   0.0000     0.0000     0.6931     1.7918     3.1781     4.7875     6.5793     8.5252    10.6046    12.8018

isZero Source #

Arguments

:: AFType a 
=> Array a

Input array

-> Array a

Result of calling isZero

Execute isZero

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

isInf Source #

Arguments

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

Input array

-> Array a

will contain 1's where input is Inf or -Inf, and 0 otherwise.

Execute isInf

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

isNaN Source #

Arguments

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

Input array

-> Array a

Will contain 1's where input is NaN, and 0 otherwise.

Execute isNaN

>>> A.isNaN $ A.acos (A.vector @Int 10 [1..])
ArrayFire Array
[10 1 1 1]
        0          1          1          1          1          1          1          1          1          1