massiv-1.0.4.0: Massiv (Массив) is an Array Library.
Copyright(c) Alexey Kuleshevich 2018-2022
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Massiv.Array.Numeric

Description

 
Synopsis

Numeric

class FoldNumeric r e => Numeric r e Source #

Minimal complete definition

unsafeLiftArray, unsafeLiftArray2

Instances

Instances details
Num e => Numeric D e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

plusScalar :: Index ix => Array D ix e -> e -> Array D ix e Source #

minusScalar :: Index ix => Array D ix e -> e -> Array D ix e Source #

scalarMinus :: Index ix => e -> Array D ix e -> Array D ix e Source #

multiplyScalar :: Index ix => Array D ix e -> e -> Array D ix e Source #

absPointwise :: Index ix => Array D ix e -> Array D ix e Source #

additionPointwise :: Index ix => Array D ix e -> Array D ix e -> Array D ix e Source #

subtractionPointwise :: Index ix => Array D ix e -> Array D ix e -> Array D ix e Source #

multiplicationPointwise :: Index ix => Array D ix e -> Array D ix e -> Array D ix e Source #

powerPointwise :: Index ix => Array D ix e -> Int -> Array D ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array D ix e -> Array D ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array D ix e -> Array D ix e -> Array D ix e Source #

Num e => Numeric B e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

plusScalar :: Index ix => Array B ix e -> e -> Array B ix e Source #

minusScalar :: Index ix => Array B ix e -> e -> Array B ix e Source #

scalarMinus :: Index ix => e -> Array B ix e -> Array B ix e Source #

multiplyScalar :: Index ix => Array B ix e -> e -> Array B ix e Source #

absPointwise :: Index ix => Array B ix e -> Array B ix e Source #

additionPointwise :: Index ix => Array B ix e -> Array B ix e -> Array B ix e Source #

subtractionPointwise :: Index ix => Array B ix e -> Array B ix e -> Array B ix e Source #

multiplicationPointwise :: Index ix => Array B ix e -> Array B ix e -> Array B ix e Source #

powerPointwise :: Index ix => Array B ix e -> Int -> Array B ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array B ix e -> Array B ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array B ix e -> Array B ix e -> Array B ix e Source #

Num e => Numeric BL e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

plusScalar :: Index ix => Array BL ix e -> e -> Array BL ix e Source #

minusScalar :: Index ix => Array BL ix e -> e -> Array BL ix e Source #

scalarMinus :: Index ix => e -> Array BL ix e -> Array BL ix e Source #

multiplyScalar :: Index ix => Array BL ix e -> e -> Array BL ix e Source #

absPointwise :: Index ix => Array BL ix e -> Array BL ix e Source #

additionPointwise :: Index ix => Array BL ix e -> Array BL ix e -> Array BL ix e Source #

subtractionPointwise :: Index ix => Array BL ix e -> Array BL ix e -> Array BL ix e Source #

multiplicationPointwise :: Index ix => Array BL ix e -> Array BL ix e -> Array BL ix e Source #

powerPointwise :: Index ix => Array BL ix e -> Int -> Array BL ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array BL ix e -> Array BL ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array BL ix e -> Array BL ix e -> Array BL ix e Source #

(NFData e, Num e) => Numeric BN e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

plusScalar :: Index ix => Array BN ix e -> e -> Array BN ix e Source #

minusScalar :: Index ix => Array BN ix e -> e -> Array BN ix e Source #

scalarMinus :: Index ix => e -> Array BN ix e -> Array BN ix e Source #

multiplyScalar :: Index ix => Array BN ix e -> e -> Array BN ix e Source #

absPointwise :: Index ix => Array BN ix e -> Array BN ix e Source #

additionPointwise :: Index ix => Array BN ix e -> Array BN ix e -> Array BN ix e Source #

subtractionPointwise :: Index ix => Array BN ix e -> Array BN ix e -> Array BN ix e Source #

multiplicationPointwise :: Index ix => Array BN ix e -> Array BN ix e -> Array BN ix e Source #

powerPointwise :: Index ix => Array BN ix e -> Int -> Array BN ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array BN ix e -> Array BN ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array BN ix e -> Array BN ix e -> Array BN ix e Source #

(Prim e, Num e) => Numeric P e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

plusScalar :: Index ix => Array P ix e -> e -> Array P ix e Source #

minusScalar :: Index ix => Array P ix e -> e -> Array P ix e Source #

scalarMinus :: Index ix => e -> Array P ix e -> Array P ix e Source #

multiplyScalar :: Index ix => Array P ix e -> e -> Array P ix e Source #

absPointwise :: Index ix => Array P ix e -> Array P ix e Source #

additionPointwise :: Index ix => Array P ix e -> Array P ix e -> Array P ix e Source #

subtractionPointwise :: Index ix => Array P ix e -> Array P ix e -> Array P ix e Source #

multiplicationPointwise :: Index ix => Array P ix e -> Array P ix e -> Array P ix e Source #

powerPointwise :: Index ix => Array P ix e -> Int -> Array P ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array P ix e -> Array P ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array P ix e -> Array P ix e -> Array P ix e Source #

(Storable e, Num e) => Numeric S e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

plusScalar :: Index ix => Array S ix e -> e -> Array S ix e Source #

minusScalar :: Index ix => Array S ix e -> e -> Array S ix e Source #

scalarMinus :: Index ix => e -> Array S ix e -> Array S ix e Source #

multiplyScalar :: Index ix => Array S ix e -> e -> Array S ix e Source #

absPointwise :: Index ix => Array S ix e -> Array S ix e Source #

additionPointwise :: Index ix => Array S ix e -> Array S ix e -> Array S ix e Source #

subtractionPointwise :: Index ix => Array S ix e -> Array S ix e -> Array S ix e Source #

multiplicationPointwise :: Index ix => Array S ix e -> Array S ix e -> Array S ix e Source #

powerPointwise :: Index ix => Array S ix e -> Int -> Array S ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array S ix e -> Array S ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array S ix e -> Array S ix e -> Array S ix e Source #

(Unbox e, Num e) => Numeric U e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

plusScalar :: Index ix => Array U ix e -> e -> Array U ix e Source #

minusScalar :: Index ix => Array U ix e -> e -> Array U ix e Source #

scalarMinus :: Index ix => e -> Array U ix e -> Array U ix e Source #

multiplyScalar :: Index ix => Array U ix e -> e -> Array U ix e Source #

absPointwise :: Index ix => Array U ix e -> Array U ix e Source #

additionPointwise :: Index ix => Array U ix e -> Array U ix e -> Array U ix e Source #

subtractionPointwise :: Index ix => Array U ix e -> Array U ix e -> Array U ix e Source #

multiplicationPointwise :: Index ix => Array U ix e -> Array U ix e -> Array U ix e Source #

powerPointwise :: Index ix => Array U ix e -> Int -> Array U ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array U ix e -> Array U ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array U ix e -> Array U ix e -> Array U ix e Source #

class (Numeric r e, Floating e) => NumericFloat r e Source #

Instances

Instances details
Floating e => NumericFloat D e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

divideScalar :: Index ix => Array D ix e -> e -> Array D ix e Source #

scalarDivide :: Index ix => e -> Array D ix e -> Array D ix e Source #

divisionPointwise :: Index ix => Array D ix e -> Array D ix e -> Array D ix e Source #

recipPointwise :: Index ix => Array D ix e -> Array D ix e Source #

sqrtPointwise :: Index ix => Array D ix e -> Array D ix e Source #

(Prim e, Floating e) => NumericFloat P e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

divideScalar :: Index ix => Array P ix e -> e -> Array P ix e Source #

scalarDivide :: Index ix => e -> Array P ix e -> Array P ix e Source #

divisionPointwise :: Index ix => Array P ix e -> Array P ix e -> Array P ix e Source #

recipPointwise :: Index ix => Array P ix e -> Array P ix e Source #

sqrtPointwise :: Index ix => Array P ix e -> Array P ix e Source #

(Storable e, Floating e) => NumericFloat S e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

divideScalar :: Index ix => Array S ix e -> e -> Array S ix e Source #

scalarDivide :: Index ix => e -> Array S ix e -> Array S ix e Source #

divisionPointwise :: Index ix => Array S ix e -> Array S ix e -> Array S ix e Source #

recipPointwise :: Index ix => Array S ix e -> Array S ix e Source #

sqrtPointwise :: Index ix => Array S ix e -> Array S ix e Source #

liftNumArray2M :: (Index ix, Numeric r e, MonadThrow m) => (e -> e -> e) -> Array r ix e -> Array r ix e -> m (Array r ix e) Source #

Similar to liftArray2M, except it can be applied only to representations with Numeric instance and result representation stays the same.

Since: 1.0.0

Pointwise addition

(.+) :: (Index ix, Numeric r e) => Array r ix e -> e -> Array r ix e infixl 6 Source #

Add a scalar to each element of the array. Array is on the left.

Since: 0.1.0

(+.) :: (Index ix, Numeric r e) => e -> Array r ix e -> Array r ix e infixl 6 Source #

Add a scalar to each element of the array. Array is on the right.

Since: 0.4.0

(.+.) :: (Index ix, Numeric r e, MonadThrow m) => Array r ix e -> Array r ix e -> m (Array r ix e) infixl 6 Source #

Add two arrays together pointwise. Same as !+! but produces monadic computation that allows for handling failure.

Throws Exception: SizeMismatchException when array sizes do not match.

Since: 0.4.0

(!+!) :: (HasCallStack, Index ix, Numeric r e) => Array r ix e -> Array r ix e -> Array r ix e infixl 6 Source #

Add two arrays together pointwise. Prefer to use monadic version of this function .+. whenever possible, because it is better to avoid partial functions.

Partial
Mismatched array sizes will result in an impure exception being thrown.

Example

Expand
>>> let a1 = Ix1 0 ... 10
>>> let a2 = Ix1 20 ... 30
>>> a1 !+! a2
Array D Seq (Sz1 11)
  [ 20, 22, 24, 26, 28, 30, 32, 34, 36, 38, 40 ]

Since: 0.5.6

sumArraysM :: (Foldable t, Load r ix e, Numeric r e, MonadThrow m) => t (Array r ix e) -> m (Array r ix e) Source #

Compute sum of arrays pointwise. All arrays must have the same size.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> sumArraysM [] :: IO (Array P Ix3 Int)
Array P Seq (Sz (0 :> 0 :. 0))
  [  ]
>>> arr = A.makeArrayR P Seq (Sz3 4 5 6) $ \(i :> j :. k) -> i + j * k
>>> arr
Array P Seq (Sz (4 :> 5 :. 6))
  [ [ [ 0, 0, 0, 0, 0, 0 ]
    , [ 0, 1, 2, 3, 4, 5 ]
    , [ 0, 2, 4, 6, 8, 10 ]
    , [ 0, 3, 6, 9, 12, 15 ]
    , [ 0, 4, 8, 12, 16, 20 ]
    ]
  , [ [ 1, 1, 1, 1, 1, 1 ]
    , [ 1, 2, 3, 4, 5, 6 ]
    , [ 1, 3, 5, 7, 9, 11 ]
    , [ 1, 4, 7, 10, 13, 16 ]
    , [ 1, 5, 9, 13, 17, 21 ]
    ]
  , [ [ 2, 2, 2, 2, 2, 2 ]
    , [ 2, 3, 4, 5, 6, 7 ]
    , [ 2, 4, 6, 8, 10, 12 ]
    , [ 2, 5, 8, 11, 14, 17 ]
    , [ 2, 6, 10, 14, 18, 22 ]
    ]
  , [ [ 3, 3, 3, 3, 3, 3 ]
    , [ 3, 4, 5, 6, 7, 8 ]
    , [ 3, 5, 7, 9, 11, 13 ]
    , [ 3, 6, 9, 12, 15, 18 ]
    , [ 3, 7, 11, 15, 19, 23 ]
    ]
  ]
>>> sumArraysM $ outerSlices arr
Array P Seq (Sz (5 :. 6))
  [ [ 6, 6, 6, 6, 6, 6 ]
  , [ 6, 10, 14, 18, 22, 26 ]
  , [ 6, 14, 22, 30, 38, 46 ]
  , [ 6, 18, 30, 42, 54, 66 ]
  , [ 6, 22, 38, 54, 70, 86 ]
  ]
>>> sumArraysM $ innerSlices arr
Array D Seq (Sz (4 :. 5))
  [ [ 0, 15, 30, 45, 60 ]
  , [ 6, 21, 36, 51, 66 ]
  , [ 12, 27, 42, 57, 72 ]
  , [ 18, 33, 48, 63, 78 ]
  ]

Since: 1.0.0

sumArrays' :: (HasCallStack, Foldable t, Load r ix e, Numeric r e) => t (Array r ix e) -> Array r ix e Source #

Same as sumArraysM, compute sum of arrays pointwise. All arrays must have the same size, otherwise it will result in an error.

Since: 1.0.0

Pointwise subtraction

(.-) :: (Index ix, Numeric r e) => Array r ix e -> e -> Array r ix e infixl 6 Source #

Subtract a scalar from each element of the array. Array is on the left.

Since: 0.4.0

(-.) :: (Index ix, Numeric r e) => e -> Array r ix e -> Array r ix e infixl 6 Source #

Subtract each element of the array from a scalar. Array is on the right.

Since: 0.5.6

(.-.) :: (Index ix, Numeric r e, MonadThrow m) => Array r ix e -> Array r ix e -> m (Array r ix e) infixl 6 Source #

Subtract two arrays pointwise. Same as !-! but produces monadic computation that allows for handling failure.

Throws Exception: SizeMismatchException when array sizes do not match.

Since: 0.4.0

(!-!) :: (Index ix, Numeric r e) => Array r ix e -> Array r ix e -> Array r ix e infixl 6 Source #

Subtract one array from another pointwise. Prefer to use monadic version of this function .-. whenever possible, because it is better to avoid partial functions.

Partial
Mismatched array sizes will result in an impure exception being thrown.

Example

Expand
>>> let a1 = Ix1 0 ... 10
>>> let a2 = Ix1 20 ... 30
>>> a1 !-! a2
Array D Seq (Sz1 11)
  [ -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20 ]

Since: 0.5.6

Pointwise multiplication

(.*) :: (Index ix, Numeric r e) => Array r ix e -> e -> Array r ix e infixl 7 Source #

Multiply each element of the array by a scalar value. Scalar is on the right.

Example

Expand
>>> let arr = Ix1 20 ..: 25
>>> arr
Array D Seq (Sz1 5)
  [ 20, 21, 22, 23, 24 ]
>>> arr .* 10
Array D Seq (Sz1 5)
  [ 200, 210, 220, 230, 240 ]

Since: 0.4.0

(*.) :: (Index ix, Numeric r e) => e -> Array r ix e -> Array r ix e infixl 7 Source #

Multiply each element of the array by a scalar value. Scalar is on the left.

Example

Expand
>>> let arr = Ix1 20 ..: 25
>>> arr
Array D Seq (Sz1 5)
  [ 20, 21, 22, 23, 24 ]
>>> 10 *. arr
Array D Seq (Sz1 5)
  [ 200, 210, 220, 230, 240 ]

Since: 0.4.0

(.*.) :: (Index ix, Numeric r e, MonadThrow m) => Array r ix e -> Array r ix e -> m (Array r ix e) infixl 7 Source #

Multiply two arrays together pointwise. Same as !*! but produces monadic computation that allows for handling failure.

Throws Exception: SizeMismatchException when array sizes do not match.

Since: 0.4.0

(!*!) :: (Index ix, Numeric r e) => Array r ix e -> Array r ix e -> Array r ix e infixl 7 Source #

Multiplication of two arrays pointwise, i.e. Hadamard product. Prefer to use monadic version of this function .*. whenever possible, because it is better to avoid partial functions.

Partial
Mismatched array sizes will result in an impure exception being thrown.

Example

Expand
>>> let a1 = Ix1 0 ... 10
>>> let a2 = Ix1 20 ... 30
>>> a1 !*! a2
Array D Seq (Sz1 11)
  [ 0, 21, 44, 69, 96, 125, 156, 189, 224, 261, 300 ]

Since: 0.5.6

(.^) :: (Index ix, Numeric r e) => Array r ix e -> Int -> Array r ix e infixr 8 Source #

Raise each element of the array to a power.

Example

Expand
>>> let arr = Ix1 20 ..: 25
>>> arr
Array D Seq (Sz1 5)
  [ 20, 21, 22, 23, 24 ]
>>> arr .^ 3
Array D Seq (Sz1 5)
  [ 8000, 9261, 10648, 12167, 13824 ]

Since: 0.4.0

productArraysM :: (Foldable t, Load r ix e, Numeric r e, MonadThrow m) => t (Array r ix e) -> m (Array r ix e) Source #

Compute product of arrays pointwise. All arrays must have the same size.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> productArraysM [] :: IO (Array P Ix3 Int)
Array P Seq (Sz (0 :> 0 :. 0))
  [  ]
>>> arr = A.makeArrayR P Seq (Sz3 4 5 6) $ \(i :> j :. k) -> i + j * k
>>> arr
Array P Seq (Sz (4 :> 5 :. 6))
  [ [ [ 0, 0, 0, 0, 0, 0 ]
    , [ 0, 1, 2, 3, 4, 5 ]
    , [ 0, 2, 4, 6, 8, 10 ]
    , [ 0, 3, 6, 9, 12, 15 ]
    , [ 0, 4, 8, 12, 16, 20 ]
    ]
  , [ [ 1, 1, 1, 1, 1, 1 ]
    , [ 1, 2, 3, 4, 5, 6 ]
    , [ 1, 3, 5, 7, 9, 11 ]
    , [ 1, 4, 7, 10, 13, 16 ]
    , [ 1, 5, 9, 13, 17, 21 ]
    ]
  , [ [ 2, 2, 2, 2, 2, 2 ]
    , [ 2, 3, 4, 5, 6, 7 ]
    , [ 2, 4, 6, 8, 10, 12 ]
    , [ 2, 5, 8, 11, 14, 17 ]
    , [ 2, 6, 10, 14, 18, 22 ]
    ]
  , [ [ 3, 3, 3, 3, 3, 3 ]
    , [ 3, 4, 5, 6, 7, 8 ]
    , [ 3, 5, 7, 9, 11, 13 ]
    , [ 3, 6, 9, 12, 15, 18 ]
    , [ 3, 7, 11, 15, 19, 23 ]
    ]
  ]
>>> productArraysM $ outerSlices arr
Array P Seq (Sz (5 :. 6))
  [ [ 0, 0, 0, 0, 0, 0 ]
  , [ 0, 24, 120, 360, 840, 1680 ]
  , [ 0, 120, 840, 3024, 7920, 17160 ]
  , [ 0, 360, 3024, 11880, 32760, 73440 ]
  , [ 0, 840, 7920, 32760, 93024, 212520 ]
  ]
>>> productArraysM $ innerSlices arr
Array D Seq (Sz (4 :. 5))
  [ [ 0, 0, 0, 0, 0 ]
  , [ 1, 720, 10395, 58240, 208845 ]
  , [ 64, 5040, 46080, 209440, 665280 ]
  , [ 729, 20160, 135135, 524880, 1514205 ]
  ]

Since: 1.0.0

productArrays' :: (HasCallStack, Foldable t, Load r ix e, Numeric r e) => t (Array r ix e) -> Array r ix e Source #

Same as productArraysM. Compute product of arrays pointwise. All arrays must have the same size, otherwise it will result in an error.

Since: 1.0.0

Dot product

(!.!) :: (Numeric r e, Source r e) => Vector r e -> Vector r e -> e Source #

Dot product of two vectors.

Partial
Throws an impure exception when lengths of vectors do not match

Since: 0.5.6

dotM :: (FoldNumeric r e, Source r e, MonadThrow m) => Vector r e -> Vector r e -> m e Source #

Dot product of two vectors.

Throws Exception: SizeMismatchException when lengths of vectors do not match

Since: 0.5.6

Matrix multiplication

(.><) Source #

Arguments

:: (MonadThrow m, FoldNumeric r e, Source r e) 
=> Matrix r e

Matrix

-> Vector r e

Column vector (Used many times, so make sure it is computed)

-> m (Vector D e) 

Multiply a matrix by a column vector. Same as !>< but produces monadic computation that allows for handling failure.

Throws Exception: SizeMismatchException when inner dimensions of arrays do not match.

Since: 0.5.6

(!><) Source #

Arguments

:: (Numeric r e, Source r e) 
=> Matrix r e

Matrix

-> Vector r e

Column vector (Used many times, so make sure it is computed)

-> Vector D e 

Multiply a matrix by a column vector

Partial
Throws impure exception when inner dimensions do not agree

Since: 0.5.6

multiplyMatrixByVector Source #

Arguments

:: (MonadThrow m, Numeric r e, Manifest r e) 
=> Matrix r e

Matrix

-> Vector r e

Column vector (Used many times, so make sure it is computed)

-> m (Vector r e) 

Multiply matrix by a column vector. Same as .>< but returns computed version of a vector

Throws Exception: SizeMismatchException when inner dimensions of arrays do not match.

Since: 0.5.7

(><.) Source #

Arguments

:: (MonadThrow m, Numeric r e, Manifest r e) 
=> Vector r e

Row vector

-> Matrix r e

Matrix

-> m (Vector r e) 

Multiply a row vector by a matrix. Same as ><! but produces monadic computation that allows for handling failure.

Throws Exception: SizeMismatchException when inner dimensions of arrays do not match.

Since: 0.5.6

(><!) Source #

Arguments

:: (Numeric r e, Manifest r e) 
=> Vector r e

Row vector (Used many times, so make sure it is computed)

-> Matrix r e

Matrix

-> Vector r e 

Multiply a row vector by a matrix.

Partial
Throws impure exception when inner dimensions do not agree

Since: 0.5.6

multiplyVectorByMatrix Source #

Arguments

:: (MonadThrow m, Numeric r e, Manifest r e) 
=> Vector r e

Row vector

-> Matrix r e

Matrix

-> m (Vector r e) 

Multiply a row vector by a matrix. Same as ><. but returns computed vector instead of a delayed one.

Throws Exception: SizeMismatchException when inner dimensions of arrays do not match.

Since: 0.5.7

(.><.) :: (Numeric r e, Manifest r e, MonadThrow m) => Matrix r e -> Matrix r e -> m (Matrix r e) Source #

Matrix multiplication. Same as !><! but produces monadic computation that allows for handling failure.

Throws Exception: SizeMismatchException when inner dimensions of arrays do not match.

Since: 0.5.6

(!><!) :: (Numeric r e, Manifest r e) => Matrix r e -> Matrix r e -> Matrix r e Source #

Multiply two matrices together.

Partial
Inner dimension must agree

Examples

Expand
>>> import Data.Massiv.Array
>>> a1 = makeArrayR P Seq (Sz2 5 6) $ \(i :. j) -> i + j
>>> a2 = makeArrayR P Seq (Sz2 6 5) $ \(i :. j) -> i - j
>>> a1 !><! a2
Array P Seq (Sz (5 :. 5))
  [ [ 55, 40, 25, 10, -5 ]
  , [ 70, 49, 28, 7, -14 ]
  , [ 85, 58, 31, 4, -23 ]
  , [ 100, 67, 34, 1, -32 ]
  , [ 115, 76, 37, -2, -41 ]
  ]

Since: 0.5.6

multiplyMatrices :: (Numeric r e, Manifest r e, MonadThrow m) => Matrix r e -> Matrix r e -> m (Matrix r e) Source #

Synonym for .><.

Since: 0.5.6

multiplyMatricesTransposed :: (Numeric r e, Manifest r e, MonadThrow m) => Matrix r e -> Matrix r e -> m (Matrix D e) Source #

Computes the matrix-matrix multiplication where second matrix is transposed (i.e. M x N')

m1 .><. transpose m2 == multiplyMatricesTransposed m1 m2

Since: 0.5.6

Norms

normL2 :: (FoldNumeric r e, Source r e, Index ix, Floating e) => Array r ix e -> e Source #

Compute L2 norm of an array.

Since: 0.5.6

Simple matrices

identityMatrix :: Num e => Sz1 -> Matrix DL e Source #

Create an indentity matrix.

Example

Expand
>>> import Data.Massiv.Array
>>> identityMatrix 5
Array DL Seq (Sz (5 :. 5))
  [ [ 1, 0, 0, 0, 0 ]
  , [ 0, 1, 0, 0, 0 ]
  , [ 0, 0, 1, 0, 0 ]
  , [ 0, 0, 0, 1, 0 ]
  , [ 0, 0, 0, 0, 1 ]
  ]

Since: 0.3.6

lowerTriangular :: forall e. Num e => Comp -> Sz1 -> (Ix2 -> e) -> Matrix DL e Source #

Create a lower triangular (L in LU decomposition) matrix of size NxN

Example

Expand
>>> import Data.Massiv.Array
>>> lowerTriangular Seq 5 (\(i :. j) -> i + j)
Array DL Seq (Sz (5 :. 5))
  [ [ 0, 0, 0, 0, 0 ]
  , [ 1, 2, 0, 0, 0 ]
  , [ 2, 3, 4, 0, 0 ]
  , [ 3, 4, 5, 6, 0 ]
  , [ 4, 5, 6, 7, 8 ]
  ]

Since: 0.5.2

upperTriangular :: forall e. Num e => Comp -> Sz1 -> (Ix2 -> e) -> Matrix DL e Source #

Create an upper triangular (U in LU decomposition) matrix of size NxN

Example

Expand
>>> import Data.Massiv.Array
>>> upperTriangular Par 5 (\(i :. j) -> i + j)
Array DL Par (Sz (5 :. 5))
  [ [ 0, 1, 2, 3, 4 ]
  , [ 0, 2, 3, 4, 5 ]
  , [ 0, 0, 4, 5, 6 ]
  , [ 0, 0, 0, 6, 7 ]
  , [ 0, 0, 0, 0, 8 ]
  ]

Since: 0.5.2

negateA :: (Index ix, Numeric r e) => Array r ix e -> Array r ix e Source #

Negate each element of the array

Since: 0.4.0

absA :: (Index ix, Numeric r e) => Array r ix e -> Array r ix e Source #

Apply abs to each element of the array

Since: 0.4.0

signumA :: (Index ix, Numeric r e) => Array r ix e -> Array r ix e Source #

Apply signum to each element of the array

Since: 0.4.0

Integral

quotA :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e) => Array r1 ix e -> Array r2 ix e -> Array D ix e infixl 7 Source #

Perform a pointwise quotient where first array contains numerators and the second one denominators

quotA arr1 arr2 == zipWith quot arr1 arr2
Partial
Mismatched array sizes will result in an impure exception being thrown.

Since: 0.1.0

remA :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e) => Array r1 ix e -> Array r2 ix e -> Array D ix e infixl 7 Source #

Perform a pointwise remainder computation

remA arr1 arr2 == zipWith rem arr1 arr2
Partial
Mismatched array sizes will result in an impure exception being thrown.

Since: 0.1.0

divA :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e) => Array r1 ix e -> Array r2 ix e -> Array D ix e infixl 7 Source #

Perform a pointwise integer division where first array contains numerators and the second one denominators

divA arr1 arr2 == zipWith div arr1 arr2
Partial
Mismatched array sizes will result in an impure exception being thrown.

Since: 0.1.0

modA :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e) => Array r1 ix e -> Array r2 ix e -> Array D ix e infixl 7 Source #

Perform a pointwise modulo computation

modA arr1 arr2 == zipWith mod arr1 arr2
Partial
Mismatched array sizes will result in an impure exception being thrown.

Since: 0.1.0

quotRemA :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e) => Array r1 ix e -> Array r2 ix e -> (Array D ix e, Array D ix e) Source #

Perform a pointwise quotient with remainder where first array contains numerators and the second one denominators

quotRemA arr1 arr2 == zipWith quotRem arr1 arr2
Partial
Mismatched array sizes will result in an impure exception being thrown.

Since: 0.1.0

divModA :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e) => Array r1 ix e -> Array r2 ix e -> (Array D ix e, Array D ix e) Source #

Perform a pointwise integer division with modulo where first array contains numerators and the second one denominators

divModA arr1 arr2 == zipWith divMod arr1 arr2
Partial
Mismatched array sizes will result in an impure exception being thrown.

Since: 0.1.0

Fractional

(./) :: (Index ix, NumericFloat r e) => Array r ix e -> e -> Array r ix e infixl 7 Source #

Divide each element of the array by a scalar value.

Example

Expand
>>> let arr = fromIntegral <$> (Ix1 20 ..: 25) :: Array D Ix1 Float
>>> arr
Array D Seq (Sz1 5)
  [ 20.0, 21.0, 22.0, 23.0, 24.0 ]
>>> arr ./ 100
Array D Seq (Sz1 5)
  [ 0.2, 0.21, 0.22, 0.23, 0.24 ]

Since: 0.4.0

(/.) :: (Index ix, NumericFloat r e) => e -> Array r ix e -> Array r ix e infixl 7 Source #

Divide a scalar value by each element of the array.

e /. arr == e *. recipA arr

Example

Expand
>>> let arr = fromIntegral <$> (Ix1 20 ..: 25) :: Array D Ix1 Float
>>> arr
Array D Seq (Sz1 5)
  [ 20.0, 21.0, 22.0, 23.0, 24.0 ]
>>> 100 /. arr
Array D Seq (Sz1 5)
  [ 5.0, 4.7619047, 4.5454545, 4.347826, 4.1666665 ]

Since: 0.5.6

(./.) :: (Index ix, NumericFloat r e, MonadThrow m) => Array r ix e -> Array r ix e -> m (Array r ix e) infixl 7 Source #

Divide each element of one array by another pointwise. Same as !/! but produces monadic computation that allows for handling failure.

Throws Exception: SizeMismatchException when array sizes do not match.

Since: 0.4.0

(!/!) :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e -> Array r ix e infixl 7 Source #

Divide two arrays pointwise. Prefer to use monadic version of this function ./. whenever possible, because it is better to avoid partial functions.

Partial
Mismatched array sizes will result in an impure exception being thrown.

Example

Expand
>>> let arr1 = fromIntegral <$> (Ix1 20 ..: 25) :: Array D Ix1 Float
>>> let arr2 = fromIntegral <$> (Ix1 100 ..: 105) :: Array D Ix1 Float
>>> arr1 !/! arr2
Array D Seq (Sz1 5)
  [ 0.2, 0.20792079, 0.21568628, 0.22330096, 0.23076923 ]

Since: 0.5.6

(.^^) :: (Index ix, Numeric r e, Fractional e, Integral b) => Array r ix e -> b -> Array r ix e infixr 8 Source #

recipA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply reciprocal to each element of the array.

recipA arr == 1 /. arr

Since: 0.4.0

Floating

expA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply exponent to each element of the array.

expA arr == map exp arr

Since: 0.4.0

logA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply logarithm to each element of the array.

logA arr == map log arr

Since: 0.4.0

sqrtA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply square root to each element of the array.

sqrtA arr == map sqrt arr

Since: 0.4.0

(.**) :: (Index ix, Source r1 e, Source r2 e, Floating e) => Array r1 ix e -> Array r2 ix e -> Array D ix e Source #

Apply power to each element of the array where the power value is in the same cell in the second array.

arr1 .** arr2 == zipWith (**) arr1 arr2
Partial
Throws an error when arrays do not have matching sizes

Since: 0.4.0

logBaseA :: (Index ix, Source r1 e, Source r2 e, Floating e) => Array r1 ix e -> Array r2 ix e -> Array D ix e Source #

Apply logarithm to each element of the array where the base is in the same cell in the second array.

logBaseA arr1 arr2 == zipWith logBase arr1 arr2
Partial
Throws an error when arrays do not have matching sizes

Since: 0.4.0

sinA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply sine function to each element of the array.

sinA arr == map sin arr

Since: 0.4.0

cosA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply cosine function to each element of the array.

cosA arr == map cos arr

Since: 0.4.0

tanA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply tangent function to each element of the array.

tanA arr == map tan arr

Since: 0.4.0

asinA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply arcsine function to each element of the array.

asinA arr == map asin arr

Since: 0.4.0

acosA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply arccosine function to each element of the array.

acosA arr == map acos arr

Since: 0.4.0

atanA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply arctangent function to each element of the array.

atanA arr == map atan arr

Since: 0.4.0

sinhA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply hyperbolic sine function to each element of the array.

sinhA arr == map sinh arr

Since: 0.4.0

coshA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply hyperbolic cosine function to each element of the array.

coshA arr == map cosh arr

Since: 0.4.0

tanhA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply hyperbolic tangent function to each element of the array.

tanhA arr == map tanh arr

Since: 0.4.0

asinhA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply inverse hyperbolic sine function to each element of the array.

asinhA arr == map asinh arr

Since: 0.4.0

acoshA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply inverse hyperbolic cosine function to each element of the array.

acoshA arr == map acosh arr

Since: 0.4.0

atanhA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e Source #

Apply inverse hyperbolic tangent function to each element of the array.

atanhA arr == map atanh arr

Since: 0.4.0

RealFrac

truncateA :: (Index ix, Source r a, RealFrac a, Integral e) => Array r ix a -> Array D ix e Source #

Truncate each element of the array.

truncateA arr == map truncate arr

Since: 0.1.0

roundA :: (Index ix, Source r a, RealFrac a, Integral e) => Array r ix a -> Array D ix e Source #

Round each element of the array.

truncateA arr == map truncate arr

Since: 0.1.0

ceilingA :: (Index ix, Source r a, RealFrac a, Integral e) => Array r ix a -> Array D ix e Source #

Ceiling of each element of the array.

truncateA arr == map truncate arr

Since: 0.1.0

floorA :: (Index ix, Source r a, RealFrac a, Integral e) => Array r ix a -> Array D ix e Source #

Floor each element of the array.

truncateA arr == map truncate arr

Since: 0.1.0

RealFloat

atan2A :: (Index ix, Numeric r e, RealFloat e, MonadThrow m) => Array r ix e -> Array r ix e -> m (Array r ix e) Source #

Perform atan2 pointwise

atan2A arr1 arr2 == zipWith atan2 arr1 arr2

Throws Exception: SizeMismatchException when array sizes do not match.

Since: 0.1.0