• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

lehins / massiv / 504

27 May 2025 12:58AM UTC coverage: 73.556% (+0.06%) from 73.501%
504

push

github

web-flow
Merge pull request #148 from lehins/add-fourmolu-to-ci

Add fourmolu to CI

53 of 68 new or added lines in 7 files covered. (77.94%)

115 existing lines in 7 files now uncovered.

4228 of 5748 relevant lines covered (73.56%)

1.42 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

87.75
/massiv/src/Data/Massiv/Array/Numeric.hs
1
{-# LANGUAGE BangPatterns #-}
2
{-# LANGUAGE FlexibleContexts #-}
3
{-# LANGUAGE MultiParamTypeClasses #-}
4
{-# LANGUAGE ScopedTypeVariables #-}
5
{-# LANGUAGE TypeFamilies #-}
6

7
-- |
8
-- Module      : Data.Massiv.Array.Numeric
9
-- Copyright   : (c) Alexey Kuleshevich 2018-2022
10
-- License     : BSD3
11
-- Maintainer  : Alexey Kuleshevich <lehins@yandex.ru>
12
-- Stability   : experimental
13
-- Portability : non-portable
14
module Data.Massiv.Array.Numeric (
15
  -- * Numeric
16
  Numeric,
17
  NumericFloat,
18
  liftNumArray2M,
19

20
  -- ** Pointwise addition
21
  (.+),
22
  (+.),
23
  (.+.),
24
  (!+!),
25
  sumArraysM,
26
  sumArrays',
27

28
  -- ** Pointwise subtraction
29
  (.-),
30
  (-.),
31
  (.-.),
32
  (!-!),
33

34
  -- ** Pointwise multiplication
35
  (.*),
36
  (*.),
37
  (.*.),
38
  (!*!),
39
  (.^),
40
  productArraysM,
41
  productArrays',
42

43
  -- ** Dot product
44
  (!.!),
45
  dotM,
46

47
  -- ** Matrix multiplication
48
  (.><),
49
  (!><),
50
  multiplyMatrixByVector,
51
  (><.),
52
  (><!),
53
  multiplyVectorByMatrix,
54
  (.><.),
55
  (!><!),
56
  multiplyMatrices,
57
  multiplyMatricesTransposed,
58

59
  -- * Norms
60
  normL2,
61

62
  -- * Simple matrices
63
  identityMatrix,
64
  lowerTriangular,
65
  upperTriangular,
66
  negateA,
67
  absA,
68
  signumA,
69

70
  -- * Integral
71
  quotA,
72
  remA,
73
  divA,
74
  modA,
75
  quotRemA,
76
  divModA,
77

78
  -- * Fractional
79
  (./),
80
  (/.),
81
  (./.),
82
  (!/!),
83
  (.^^),
84
  recipA,
85

86
  -- * Floating
87
  expA,
88
  logA,
89
  sqrtA,
90
  (.**),
91
  logBaseA,
92
  sinA,
93
  cosA,
94
  tanA,
95
  asinA,
96
  acosA,
97
  atanA,
98
  sinhA,
99
  coshA,
100
  tanhA,
101
  asinhA,
102
  acoshA,
103
  atanhA,
104

105
  -- * RealFrac
106
  truncateA,
107
  roundA,
108
  ceilingA,
109
  floorA,
110

111
  -- * RealFloat
112
  atan2A,
113
) where
114

115
import Control.Monad (when)
116
import Control.Scheduler
117
import qualified Data.Foldable as F
118
import Data.Function
119
import Data.Massiv.Array.Delayed.Pull
120
import Data.Massiv.Array.Delayed.Push
121
import Data.Massiv.Array.Manifest.Internal
122
import Data.Massiv.Array.Ops.Construct
123
import Data.Massiv.Array.Ops.Map as A
124
import Data.Massiv.Core
125
import Data.Massiv.Core.Common as A
126
import Data.Massiv.Core.Operations
127
import System.IO.Unsafe
128
import Prelude as P
129

130
infixr 8 .^, .^^
131

132
infixl 7 !*!, .*., .*, *., !/!, ./., ./, /., `quotA`, `remA`, `divA`, `modA`
133

134
infixl 6 !+!, .+., .+, +., !-!, .-., .-, -.
135

136
-- | Similar to `liftArray2M`, except it can be applied only to representations
137
-- with `Numeric` instance and result representation stays the same.
138
--
139
-- @since 1.0.0
140
liftNumArray2M
141
  :: (Index ix, Numeric r e, MonadThrow m)
142
  => (e -> e -> e)
143
  -> Array r ix e
144
  -> Array r ix e
145
  -> m (Array r ix e)
146
liftNumArray2M f a1 a2
2✔
147
  | size a1 == size a2 = pure $ unsafeLiftArray2 f a1 a2
1✔
148
  | isZeroSz sz1 && isZeroSz sz2 = pure $ unsafeResize zeroSz a1
×
149
  | otherwise = throwM $ SizeMismatchException sz1 sz2
×
150
  where
151
    !sz1 = size a1
2✔
152
    !sz2 = size a2
2✔
153
{-# INLINE liftNumArray2M #-}
154

155
applyExactSize2M
156
  :: (Index ix, Size r, MonadThrow m)
157
  => (Array r ix e -> Array r ix e -> Array r ix e)
158
  -> Array r ix e
159
  -> Array r ix e
160
  -> m (Array r ix e)
161
applyExactSize2M f a1 a2
2✔
162
  | size a1 == size a2 = pure $! f a1 a2
2✔
163
  | isZeroSz sz1 && isZeroSz sz2 = pure $! unsafeResize zeroSz a1
1✔
164
  | otherwise = throwM $! SizeMismatchException sz1 sz2
1✔
165
  where
166
    !sz1 = size a1
2✔
167
    !sz2 = size a2
2✔
168
{-# INLINE applyExactSize2M #-}
169

170
-- | Add two arrays together pointwise. Same as `!+!` but produces monadic computation
171
-- that allows for handling failure.
172
--
173
-- /__Throws Exception__/: `SizeMismatchException` when array sizes do not match.
174
--
175
-- @since 0.4.0
176
(.+.) :: (Index ix, Numeric r e, MonadThrow m) => Array r ix e -> Array r ix e -> m (Array r ix e)
177
(.+.) = applyExactSize2M additionPointwise
2✔
178
{-# INLINE (.+.) #-}
179

180
-- | Add two arrays together pointwise. Prefer to use monadic version of this function
181
-- `.+.` whenever possible, because it is better to avoid partial functions.
182
--
183
-- [Partial] Mismatched array sizes will result in an impure exception being thrown.
184
--
185
-- ====__Example__
186
--
187
-- >>> let a1 = Ix1 0 ... 10
188
-- >>> let a2 = Ix1 20 ... 30
189
-- >>> a1 !+! a2
190
-- Array D Seq (Sz1 11)
191
--   [ 20, 22, 24, 26, 28, 30, 32, 34, 36, 38, 40 ]
192
--
193
-- @since 0.5.6
194
(!+!) :: (HasCallStack, Index ix, Numeric r e) => Array r ix e -> Array r ix e -> Array r ix e
195
(!+!) a1 a2 = throwEither (a1 .+. a2)
2✔
196
{-# INLINE (!+!) #-}
197

198
-- | Add a scalar to each element of the array. Array is on the left.
199
--
200
-- @since 0.1.0
201
(.+) :: (Index ix, Numeric r e) => Array r ix e -> e -> Array r ix e
202
(.+) = plusScalar
2✔
203
{-# INLINE (.+) #-}
204

205
-- | Add a scalar to each element of the array. Array is on the right.
206
--
207
-- @since 0.4.0
208
(+.) :: (Index ix, Numeric r e) => e -> Array r ix e -> Array r ix e
209
(+.) = flip plusScalar
2✔
210
{-# INLINE (+.) #-}
211

212
-- | Subtract two arrays pointwise. Same as `!-!` but produces monadic computation that
213
-- allows for handling failure.
214
--
215
-- /__Throws Exception__/: `SizeMismatchException` when array sizes do not match.
216
--
217
-- @since 0.4.0
218
(.-.)
219
  :: (Index ix, Numeric r e, MonadThrow m) => Array r ix e -> Array r ix e -> m (Array r ix e)
220
(.-.) = applyExactSize2M subtractionPointwise
2✔
221
{-# INLINE (.-.) #-}
222

223
-- | Subtract one array from another pointwise. Prefer to use monadic version of this
224
-- function `.-.` whenever possible, because it is better to avoid partial functions.
225
--
226
-- [Partial] Mismatched array sizes will result in an impure exception being thrown.
227
--
228
-- ====__Example__
229
--
230
-- >>> let a1 = Ix1 0 ... 10
231
-- >>> let a2 = Ix1 20 ... 30
232
-- >>> a1 !-! a2
233
-- Array D Seq (Sz1 11)
234
--   [ -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20 ]
235
--
236
-- @since 0.5.6
237
(!-!) :: (Index ix, Numeric r e) => Array r ix e -> Array r ix e -> Array r ix e
238
(!-!) a1 a2 = throwEither (a1 .-. a2)
2✔
239
{-# INLINE (!-!) #-}
240

241
-- | Subtract a scalar from each element of the array. Array is on the left.
242
--
243
-- @since 0.4.0
244
(.-) :: (Index ix, Numeric r e) => Array r ix e -> e -> Array r ix e
245
(.-) = minusScalar
2✔
246
{-# INLINE (.-) #-}
247

248
-- | Subtract each element of the array from a scalar. Array is on the right.
249
--
250
-- @since 0.5.6
251
(-.) :: (Index ix, Numeric r e) => e -> Array r ix e -> Array r ix e
252
(-.) = scalarMinus
2✔
253
{-# INLINE (-.) #-}
254

255
-- | Multiply two arrays together pointwise. Same as `!*!` but produces monadic
256
-- computation that allows for handling failure.
257
--
258
-- /__Throws Exception__/: `SizeMismatchException` when array sizes do not match.
259
--
260
-- @since 0.4.0
261
(.*.)
262
  :: (Index ix, Numeric r e, MonadThrow m) => Array r ix e -> Array r ix e -> m (Array r ix e)
263
(.*.) = applyExactSize2M multiplicationPointwise
2✔
264
{-# INLINE (.*.) #-}
265

266
-- | Multiplication of two arrays pointwise,
267
-- i.e. <https://en.wikipedia.org/wiki/Hadamard_product_(matrices) Hadamard product>.
268
-- Prefer to use monadic version of this function `.*.` whenever possible,
269
-- because it is better to avoid partial functions.
270
--
271
-- [Partial] Mismatched array sizes will result in an impure exception being thrown.
272
--
273
-- ====__Example__
274
--
275
-- >>> let a1 = Ix1 0 ... 10
276
-- >>> let a2 = Ix1 20 ... 30
277
-- >>> a1 !*! a2
278
-- Array D Seq (Sz1 11)
279
--   [ 0, 21, 44, 69, 96, 125, 156, 189, 224, 261, 300 ]
280
--
281
-- @since 0.5.6
282
(!*!) :: (Index ix, Numeric r e) => Array r ix e -> Array r ix e -> Array r ix e
283
(!*!) a1 a2 = throwEither (a1 .*. a2)
2✔
284
{-# INLINE (!*!) #-}
285

286
-- | Multiply each element of the array by a scalar value. Scalar is on the right.
287
--
288
-- ====__Example__
289
--
290
-- >>> let arr = Ix1 20 ..: 25
291
-- >>> arr
292
-- Array D Seq (Sz1 5)
293
--   [ 20, 21, 22, 23, 24 ]
294
-- >>> arr .* 10
295
-- Array D Seq (Sz1 5)
296
--   [ 200, 210, 220, 230, 240 ]
297
--
298
-- @since 0.4.0
299
(.*) :: (Index ix, Numeric r e) => Array r ix e -> e -> Array r ix e
300
(.*) = multiplyScalar
2✔
301
{-# INLINE (.*) #-}
302

303
-- | Multiply each element of the array by a scalar value. Scalar is on the left.
304
--
305
-- ====__Example__
306
--
307
-- >>> let arr = Ix1 20 ..: 25
308
-- >>> arr
309
-- Array D Seq (Sz1 5)
310
--   [ 20, 21, 22, 23, 24 ]
311
-- >>> 10 *. arr
312
-- Array D Seq (Sz1 5)
313
--   [ 200, 210, 220, 230, 240 ]
314
--
315
-- @since 0.4.0
316
(*.) :: (Index ix, Numeric r e) => e -> Array r ix e -> Array r ix e
317
(*.) = flip multiplyScalar
2✔
318
{-# INLINE (*.) #-}
319

320
-- | Raise each element of the array to a power.
321
--
322
-- ====__Example__
323
--
324
-- >>> let arr = Ix1 20 ..: 25
325
-- >>> arr
326
-- Array D Seq (Sz1 5)
327
--   [ 20, 21, 22, 23, 24 ]
328
-- >>> arr .^ 3
329
-- Array D Seq (Sz1 5)
330
--   [ 8000, 9261, 10648, 12167, 13824 ]
331
--
332
-- @since 0.4.0
333
(.^) :: (Index ix, Numeric r e) => Array r ix e -> Int -> Array r ix e
334
(.^) = powerPointwise
2✔
335
{-# INLINE (.^) #-}
336

337
-- | Dot product of two vectors.
338
--
339
-- [Partial] Throws an impure exception when lengths of vectors do not match
340
--
341
-- @since 0.5.6
342
(!.!) :: (Numeric r e, Source r e) => Vector r e -> Vector r e -> e
343
(!.!) v1 v2 = throwEither $ dotM v1 v2
2✔
344
{-# INLINE (!.!) #-}
345

346
-- | Dot product of two vectors.
347
--
348
-- /__Throws Exception__/: `SizeMismatchException` when lengths of vectors do not match
349
--
350
-- @since 0.5.6
351
dotM :: (FoldNumeric r e, Source r e, MonadThrow m) => Vector r e -> Vector r e -> m e
352
dotM v1 v2
2✔
353
  | size v1 /= size v2 = throwM $ SizeMismatchException (size v1) (size v2)
2✔
354
  | comp == Seq = pure $! unsafeDotProduct v1 v2
2✔
355
  | otherwise = pure $! unsafePerformIO $ unsafeDotProductIO v1 v2
1✔
356
  where
357
    comp = getComp v1 <> getComp v2
2✔
358
{-# INLINE dotM #-}
359

360
unsafeDotProductIO
361
  :: (MonadUnliftIO m, Index ix, FoldNumeric r b, Source r b)
362
  => Array r ix b
363
  -> Array r ix b
364
  -> m b
365
unsafeDotProductIO v1 v2 = do
2✔
366
  results <-
367
    withScheduler comp $ \scheduler ->
2✔
368
      splitLinearly (numWorkers scheduler) totalLength $ \chunkLength slackStart -> liftIO $ do
2✔
369
        let n = SafeSz chunkLength
2✔
370
        loopA_ 0 (< slackStart) (+ chunkLength) $ \ !start ->
2✔
371
          scheduleWork scheduler $
2✔
372
            pure $!
2✔
373
              unsafeDotProduct (unsafeLinearSlice start n v1) (unsafeLinearSlice start n v2)
2✔
374
        when (slackStart < totalLength) $ do
2✔
375
          let k = SafeSz (totalLength - slackStart)
2✔
376
          scheduleWork scheduler $
2✔
377
            pure $!
2✔
378
              unsafeDotProduct (unsafeLinearSlice slackStart k v1) (unsafeLinearSlice slackStart k v2)
2✔
379
  pure $! F.foldl' (+) 0 results
2✔
380
  where
381
    totalLength = totalElem (size v1)
2✔
382
    comp = getComp v1 <> getComp v2
2✔
383
{-# INLINE unsafeDotProductIO #-}
384

385
-- | Compute L2 norm of an array.
386
--
387
-- @since 0.5.6
388
normL2 :: (FoldNumeric r e, Source r e, Index ix, Floating e) => Array r ix e -> e
389
normL2 v
2✔
390
  | getComp v == Seq = sqrt $! powerSumArray v 2
2✔
391
  | otherwise = sqrt $! unsafePerformIO $ powerSumArrayIO v 2
1✔
392
{-# INLINE normL2 #-}
393

394
powerSumArrayIO
395
  :: (MonadUnliftIO m, Index ix, FoldNumeric r b, Source r b)
396
  => Array r ix b
397
  -> Int
398
  -> m b
399
powerSumArrayIO v p = do
2✔
400
  results <-
401
    withScheduler (getComp v) $ \scheduler ->
2✔
402
      splitLinearly (numWorkers scheduler) totalLength $ \chunkLength slackStart -> liftIO $ do
2✔
403
        let n = SafeSz chunkLength
2✔
404
        loopA_ 0 (< slackStart) (+ chunkLength) $ \ !start ->
2✔
405
          scheduleWork scheduler $ pure $! powerSumArray (unsafeLinearSlice start n v) p
2✔
406
        when (slackStart < totalLength) $ do
2✔
407
          let k = SafeSz (totalLength - slackStart)
2✔
408
          scheduleWork scheduler $ pure $! powerSumArray (unsafeLinearSlice slackStart k v) p
2✔
409
  pure $! F.foldl' (+) 0 results
2✔
410
  where
411
    totalLength = totalElem (size v)
2✔
412
{-# INLINE powerSumArrayIO #-}
413

414
-- | Multiply a matrix by a column vector. Same as `!><` but produces monadic
415
-- computation that allows for handling failure.
416
--
417
-- /__Throws Exception__/: `SizeMismatchException` when inner dimensions of arrays do not match.
418
--
419
-- @since 0.5.6
420
(.><)
421
  :: (MonadThrow m, FoldNumeric r e, Source r e)
422
  => Matrix r e
423
  -- ^ Matrix
424
  -> Vector r e
425
  -- ^ Column vector (Used many times, so make sure it is computed)
426
  -> m (Vector D e)
427
(.><) mm v
2✔
428
  | mCols /= n = throwM $ SizeMismatchException (size mm) (Sz2 n 1)
2✔
429
  | mRows == 0 || mCols == 0 = pure $ setComp comp empty
2✔
430
  | otherwise = pure $ makeArray comp (Sz1 mRows) $ \i ->
1✔
431
      unsafeDotProduct (unsafeLinearSlice (i * n) sz mm) v
2✔
432
  where
433
    comp = getComp mm <> getComp v
2✔
434
    Sz2 mRows mCols = size mm
2✔
435
    sz@(Sz1 n) = size v
2✔
436
{-# INLINE (.><) #-}
437

438
-- | Multiply matrix by a column vector. Same as `.><` but returns computed version of a vector
439
--
440
-- /__Throws Exception__/: `SizeMismatchException` when inner dimensions of arrays do not match.
441
--
442
-- @since 0.5.7
443
multiplyMatrixByVector
444
  :: (MonadThrow m, Numeric r e, Manifest r e)
445
  => Matrix r e
446
  -- ^ Matrix
447
  -> Vector r e
448
  -- ^ Column vector (Used many times, so make sure it is computed)
449
  -> m (Vector r e)
450
multiplyMatrixByVector mm v = compute <$> mm .>< v
×
451
{-# INLINE multiplyMatrixByVector #-}
452

453
-- | Multiply a matrix by a column vector
454
--
455
-- [Partial] Throws impure exception when inner dimensions do not agree
456
--
457
-- @since 0.5.6
458
(!><)
459
  :: (Numeric r e, Source r e)
460
  => Matrix r e
461
  -- ^ Matrix
462
  -> Vector r e
463
  -- ^ Column vector (Used many times, so make sure it is computed)
464
  -> Vector D e
465
(!><) mm v = throwEither (mm .>< v)
2✔
466
{-# INLINE (!><) #-}
467

468
-- | Multiply a row vector by a matrix. Same as `><!` but produces monadic computation
469
-- that allows for handling failure.
470
--
471
-- /__Throws Exception__/: `SizeMismatchException` when inner dimensions of arrays do not match.
472
--
473
-- @since 0.5.6
474
(><.)
475
  :: (MonadThrow m, Numeric r e, Manifest r e)
476
  => Vector r e
477
  -- ^ Row vector
478
  -> Matrix r e
479
  -- ^ Matrix
480
  -> m (Vector r e)
481
(><.) = multiplyVectorByMatrix
2✔
482
{-# INLINE (><.) #-}
483

484
-- | Multiply a row vector by a matrix. Same as `><.` but returns computed vector instead of
485
-- a delayed one.
486
--
487
-- /__Throws Exception__/: `SizeMismatchException` when inner dimensions of arrays do not match.
488
--
489
-- @since 0.5.7
490
multiplyVectorByMatrix
491
  :: (MonadThrow m, Numeric r e, Manifest r e)
492
  => Vector r e
493
  -- ^ Row vector
494
  -> Matrix r e
495
  -- ^ Matrix
496
  -> m (Vector r e)
497
multiplyVectorByMatrix v mm
2✔
498
  | mRows /= n = throwM $ SizeMismatchException (Sz2 1 n) (size mm)
2✔
499
  | mRows == 0 || mCols == 0 = pure $ runST (unsafeFreeze comp =<< unsafeNew zeroSz)
2✔
500
  | otherwise =
×
501
      pure $!
2✔
502
        unsafePerformIO $ do
2✔
503
          mv <- newMArray (Sz mCols) 0
2✔
504
          withMassivScheduler_ comp $ \scheduler -> do
2✔
505
            let loopCols x ivto =
2✔
506
                  fix $ \go im iv ->
2✔
507
                    when (iv < ivto) $ do
2✔
508
                      _ <- unsafeLinearModify mv (\a -> pure $ a + unsafeLinearIndex mm im * x) iv
2✔
509
                      go (im + 1) (iv + 1)
2✔
510
                loopRows i0 from to =
2✔
511
                  flip fix i0 $ \go i ->
2✔
512
                    when (i < mRows) $ do
2✔
513
                      loopCols (unsafeLinearIndex v i) to (i * mCols + from) from
2✔
514
                      go (i + 1)
2✔
515
            splitLinearlyM_ scheduler mCols (loopRows 0)
2✔
516
          unsafeFreeze comp mv
2✔
517
  where
518
    comp = getComp mm <> getComp v
2✔
519
    Sz2 mRows mCols = size mm
2✔
520
    Sz1 n = size v
2✔
521
{-# INLINE multiplyVectorByMatrix #-}
522

523
-- | Multiply a row vector by a matrix.
524
--
525
-- [Partial] Throws impure exception when inner dimensions do not agree
526
--
527
-- @since 0.5.6
528
(><!)
529
  :: (Numeric r e, Manifest r e)
530
  => Vector r e
531
  -- ^ Row vector (Used many times, so make sure it is computed)
532
  -> Matrix r e
533
  -- ^ Matrix
534
  -> Vector r e
535
(><!) v mm = throwEither (v ><. mm)
2✔
536
{-# INLINE (><!) #-}
537

538
-- | Multiply two matrices together.
539
--
540
-- [Partial] Inner dimension must agree
541
--
542
-- ====__Examples__
543
--
544
-- >>> import Data.Massiv.Array
545
-- >>> a1 = makeArrayR P Seq (Sz2 5 6) $ \(i :. j) -> i + j
546
-- >>> a2 = makeArrayR P Seq (Sz2 6 5) $ \(i :. j) -> i - j
547
-- >>> a1 !><! a2
548
-- Array P Seq (Sz (5 :. 5))
549
--   [ [ 55, 40, 25, 10, -5 ]
550
--   , [ 70, 49, 28, 7, -14 ]
551
--   , [ 85, 58, 31, 4, -23 ]
552
--   , [ 100, 67, 34, 1, -32 ]
553
--   , [ 115, 76, 37, -2, -41 ]
554
--   ]
555
--
556
-- @since 0.5.6
557
(!><!) :: (Numeric r e, Manifest r e) => Matrix r e -> Matrix r e -> Matrix r e
558
(!><!) a1 a2 = throwEither (a1 `multiplyMatrices` a2)
2✔
559
{-# INLINE (!><!) #-}
560

561
-- | Matrix multiplication. Same as `!><!` but produces monadic computation that allows
562
-- for handling failure.
563
--
564
-- /__Throws Exception__/: `SizeMismatchException` when inner dimensions of arrays do not match.
565
--
566
-- @since 0.5.6
567
(.><.) :: (Numeric r e, Manifest r e, MonadThrow m) => Matrix r e -> Matrix r e -> m (Matrix r e)
568
(.><.) = multiplyMatrices
2✔
569
{-# INLINE (.><.) #-}
570

571
-- | Synonym for `.><.`
572
--
573
-- @since 0.5.6
574
multiplyMatrices
575
  :: (Numeric r e, Manifest r e, MonadThrow m) => Matrix r e -> Matrix r e -> m (Matrix r e)
576
multiplyMatrices arrA arrB
2✔
577
  -- mA == 1 = -- TODO: call multiplyVectorByMatrix
578
  -- nA == 1 = -- TODO: call multiplyMatrixByVector
579
  | nA /= mB = throwM $ SizeMismatchException (size arrA) (size arrB)
2✔
580
  | isEmpty arrA || isEmpty arrB = pure $ runST (unsafeFreeze comp =<< unsafeNew zeroSz)
2✔
581
  | otherwise = pure $! unsafePerformIO $ do
1✔
582
      marrC <- newMArray (SafeSz (mA :. nB)) 0
2✔
583
      withScheduler_ comp $ \scheduler -> do
2✔
584
        let withC00 iA jB f =
2✔
585
              let !ixC00 = iA * nB + jB
2✔
586
               in f ixC00 =<< unsafeLinearRead marrC ixC00
2✔
587
            withC01 ixC00 f =
2✔
588
              let !ixC01 = ixC00 + 1
2✔
589
               in f ixC01 =<< unsafeLinearRead marrC ixC01
2✔
590
            withC10 ixC00 f =
2✔
591
              let !ixC10 = ixC00 + nB
2✔
592
               in f ixC10 =<< unsafeLinearRead marrC ixC10
2✔
593
            withC11 ixC01 f =
2✔
594
              let !ixC11 = ixC01 + nB
2✔
595
               in f ixC11 =<< unsafeLinearRead marrC ixC11
2✔
596
            withB00 iB jB f =
2✔
597
              let !ixB00 = iB * nB + jB
2✔
598
               in f ixB00 $! unsafeLinearIndex arrB ixB00
2✔
599
            withB00B10 iB jB f =
2✔
600
              withB00 iB jB $ \ixB00 b00 ->
2✔
601
                let !ixB10 = ixB00 + nB
2✔
602
                 in f ixB00 b00 ixB10 $! unsafeLinearIndex arrB ixB10
2✔
603
            withA00 iA jA f =
2✔
604
              let !ixA00 = iA * nA + jA
2✔
605
               in f ixA00 $! unsafeLinearIndex arrA ixA00
2✔
606
            withA00A10 iA jA f =
2✔
607
              withA00 iA jA $ \ixA00 a00 ->
2✔
608
                let !ixA10 = ixA00 + nA
2✔
609
                 in f ixA00 a00 ixA10 $! unsafeLinearIndex arrA ixA10
2✔
610
        let loopColsB_UnRowBColA_UnRowA a00 a01 a10 a11 iA iB jB
2✔
611
              | jB < n2B = do
2✔
612
                  withB00B10 iB jB $ \ixB00 b00 ixB10 b10 -> do
2✔
613
                    let !b01 = unsafeLinearIndex arrB (ixB00 + 1)
2✔
614
                        !b11 = unsafeLinearIndex arrB (ixB10 + 1)
2✔
615
                    withC00 iA jB $ \ixC00 c00 -> do
2✔
616
                      unsafeLinearWrite marrC ixC00 (c00 + a00 * b00 + a01 * b10)
2✔
617
                      withC01 ixC00 $ \ixC01 c01 -> do
2✔
618
                        unsafeLinearWrite marrC ixC01 (c01 + a00 * b01 + a01 * b11)
2✔
619
                        withC10 ixC00 $ \ixC10 c10 ->
2✔
620
                          unsafeLinearWrite marrC ixC10 (c10 + a10 * b00 + a11 * b10)
2✔
621
                        withC11 ixC01 $ \ixC11 c11 ->
2✔
622
                          unsafeLinearWrite marrC ixC11 (c11 + a10 * b01 + a11 * b11)
2✔
623
                  loopColsB_UnRowBColA_UnRowA a00 a01 a10 a11 iA iB (jB + 2)
2✔
624
              | jB < nB = withB00B10 iB jB $ \_ b00 _ b10 ->
2✔
625
                  withC00 iA jB $ \ixC00 c00 -> do
2✔
626
                    unsafeLinearWrite marrC ixC00 (c00 + a00 * b00 + a01 * b10)
2✔
627
                    withC10 ixC00 $ \ixC10 c10 ->
2✔
628
                      unsafeLinearWrite marrC ixC10 (c10 + a10 * b00 + a11 * b10)
2✔
629
              | otherwise = pure ()
1✔
630

631
            loopColsB_UnRowBColA_RowA a00 a01 iA iB jB
2✔
632
              | jB < n2B = do
2✔
633
                  withB00B10 iB jB $ \ixB00 b00 ixB10 b10 -> do
2✔
634
                    let !b01 = unsafeLinearIndex arrB (ixB00 + 1)
2✔
635
                        !b11 = unsafeLinearIndex arrB (ixB10 + 1)
2✔
636
                    withC00 iA jB $ \ixC00 c00 -> do
2✔
637
                      unsafeLinearWrite marrC ixC00 (c00 + a00 * b00 + a01 * b10)
2✔
638
                      withC01 ixC00 $ \ixC01 c01 ->
2✔
639
                        unsafeLinearWrite marrC ixC01 (c01 + a00 * b01 + a01 * b11)
2✔
640
                  loopColsB_UnRowBColA_RowA a00 a01 iA iB (jB + 2)
2✔
641
              | jB < nB = withB00B10 iB jB $ \_ b00 _ b10 ->
1✔
642
                  withC00 iA jB $ \ixC00 c00 ->
2✔
643
                    unsafeLinearWrite marrC ixC00 (c00 + a00 * b00 + a01 * b10)
2✔
644
              | otherwise = pure ()
×
645

646
            loopColsB_RowBColA_UnRowA a00 a10 iA iB jB
2✔
647
              | jB < n2B = do
2✔
648
                  withB00 iB jB $ \ixB00 b00 -> do
2✔
649
                    let !b01 = unsafeLinearIndex arrB (ixB00 + 1)
2✔
650
                    withC00 iA jB $ \ixC00 c00 -> do
2✔
651
                      unsafeLinearWrite marrC ixC00 (c00 + a00 * b00)
2✔
652
                      withC01 ixC00 $ \ixC01 c01 -> do
2✔
653
                        unsafeLinearWrite marrC ixC01 (c01 + a00 * b01)
2✔
654
                        withC10 ixC00 $ \ixC10 c10 ->
2✔
655
                          unsafeLinearWrite marrC ixC10 (c10 + a10 * b00)
2✔
656
                        withC11 ixC01 $ \ixC11 c11 ->
2✔
657
                          unsafeLinearWrite marrC ixC11 (c11 + a10 * b01)
2✔
658
                  loopColsB_RowBColA_UnRowA a00 a10 iA iB (jB + 2)
2✔
659
              | jB < nB = withB00 iB jB $ \_ b00 ->
2✔
660
                  withC00 iA jB $ \ixC00 c00 -> do
2✔
661
                    unsafeLinearWrite marrC ixC00 (c00 + a00 * b00)
2✔
662
                    withC10 ixC00 $ \ixC10 c10 ->
2✔
663
                      unsafeLinearWrite marrC ixC10 (c10 + a10 * b00)
2✔
664
              | otherwise = pure ()
1✔
665

666
            loopColsB_RowBColA_RowA a00 iA iB jB
2✔
667
              | jB < n2B = do
2✔
668
                  withB00 iB jB $ \ixB00 b00 -> do
2✔
669
                    let !b01 = unsafeLinearIndex arrB (ixB00 + 1)
2✔
670
                    withC00 iA jB $ \ixC00 c00 -> do
2✔
671
                      unsafeLinearWrite marrC ixC00 (c00 + a00 * b00)
2✔
672
                      withC01 ixC00 $ \ixC01 c01 -> do
2✔
673
                        unsafeLinearWrite marrC ixC01 (c01 + a00 * b01)
2✔
674
                  loopColsB_RowBColA_RowA a00 iA iB (jB + 2)
2✔
675
              | jB < nB = withB00 iB jB $ \_ b00 ->
1✔
676
                  withC00 iA jB $ \ixC00 c00 ->
2✔
677
                    unsafeLinearWrite marrC ixC00 (c00 + a00 * b00)
2✔
678
              | otherwise = pure ()
×
679

680
            loopRowsB_UnRowA iA iB
2✔
681
              | iB < m2B = do
2✔
682
                  withA00A10 iA iB $ \ixA00 a00 ixA10 a10 -> do
2✔
683
                    let !a01 = unsafeLinearIndex arrA (ixA00 + 1)
2✔
684
                        !a11 = unsafeLinearIndex arrA (ixA10 + 1)
2✔
685
                    loopColsB_UnRowBColA_UnRowA a00 a01 a10 a11 iA iB 0
2✔
686
                  loopRowsB_UnRowA iA (iB + 2)
2✔
687
              | iB < mB =
2✔
688
                  withA00A10 iA iB $ \_ a00 _ a10 -> loopColsB_RowBColA_UnRowA a00 a10 iA iB 0
2✔
689
              | otherwise = pure ()
1✔
690

691
            loopRowsB_RowA iA iB
2✔
692
              | iB < m2B = do
2✔
693
                  withA00 iA iB $ \ixA00 a00 -> do
2✔
694
                    let !a01 = unsafeLinearIndex arrA (ixA00 + 1)
2✔
695
                    loopColsB_UnRowBColA_RowA a00 a01 iA iB 0
2✔
696
                  loopRowsB_RowA iA (iB + 2)
2✔
697
              | iB < mB = withA00 iA iB $ \_ a00 -> loopColsB_RowBColA_RowA a00 iA iB 0
2✔
698
              | otherwise = pure ()
1✔
699

700
            loopRowsA iA
2✔
701
              | iA < m2A = do
2✔
702
                  scheduleWork_ scheduler $ loopRowsB_UnRowA iA 0
2✔
703
                  loopRowsA (iA + 2)
2✔
704
              | iA < mA = scheduleWork_ scheduler $ loopRowsB_RowA iA 0
2✔
705
              | otherwise = pure ()
1✔
706
        loopRowsA 0
2✔
707

708
      unsafeFreeze comp marrC
2✔
709
  where
710
    comp = getComp arrA <> getComp arrB
2✔
711
    m2A = mA - mA `rem` 2
2✔
712
    m2B = mB - mB `rem` 2
2✔
713
    n2B = nB - nB `rem` 2
2✔
714
    Sz (mA :. nA) = size arrA
2✔
715
    Sz (mB :. nB) = size arrB
2✔
716
{-# INLINEABLE multiplyMatrices #-}
717

718
-- | Computes the matrix-matrix multiplication where second matrix is transposed (i.e. M
719
-- x N')
720
--
721
-- > m1 .><. transpose m2 == multiplyMatricesTransposed m1 m2
722
--
723
-- @since 0.5.6
724
multiplyMatricesTransposed
725
  :: (Numeric r e, Manifest r e, MonadThrow m)
726
  => Matrix r e
727
  -> Matrix r e
728
  -> m (Matrix D e)
729
multiplyMatricesTransposed arr1 arr2
×
730
  | n1 /= m2 = throwM $ SizeMismatchException (size arr1) (Sz2 m2 n2)
×
731
  | isEmpty arr1 || isEmpty arr2 = pure $ setComp comp empty
×
732
  | otherwise =
×
733
      pure $
×
734
        makeArray comp (SafeSz (m1 :. n2)) $ \(i :. j) ->
×
735
          unsafeDotProduct (unsafeLinearSlice (i * n1) n arr1) (unsafeLinearSlice (j * n1) n arr2)
×
736
  where
737
    comp = getComp arr1 <> getComp arr2
×
738
    n = SafeSz n1
×
739
    SafeSz (m1 :. n1) = size arr1
×
740
    SafeSz (n2 :. m2) = size arr2
×
741
{-# INLINE multiplyMatricesTransposed #-}
742

743
-- | Create an indentity matrix.
744
--
745
-- ==== __Example__
746
--
747
-- >>> import Data.Massiv.Array
748
-- >>> identityMatrix 5
749
-- Array DL Seq (Sz (5 :. 5))
750
--   [ [ 1, 0, 0, 0, 0 ]
751
--   , [ 0, 1, 0, 0, 0 ]
752
--   , [ 0, 0, 1, 0, 0 ]
753
--   , [ 0, 0, 0, 1, 0 ]
754
--   , [ 0, 0, 0, 0, 1 ]
755
--   ]
756
--
757
-- @since 0.3.6
758
identityMatrix :: Num e => Sz1 -> Matrix DL e
759
identityMatrix (Sz n) =
2✔
760
  makeLoadArrayS (Sz2 n n) 0 $ \w -> loopA_ 0 (< n) (+ 1) $ \i -> w (i :. i) 1
2✔
761
{-# INLINE identityMatrix #-}
762

763
-- | Create a lower triangular (L in LU decomposition) matrix of size @NxN@
764
--
765
-- ==== __Example__
766
--
767
-- >>> import Data.Massiv.Array
768
-- >>> lowerTriangular Seq 5 (\(i :. j) -> i + j)
769
-- Array DL Seq (Sz (5 :. 5))
770
--   [ [ 0, 0, 0, 0, 0 ]
771
--   , [ 1, 2, 0, 0, 0 ]
772
--   , [ 2, 3, 4, 0, 0 ]
773
--   , [ 3, 4, 5, 6, 0 ]
774
--   , [ 4, 5, 6, 7, 8 ]
775
--   ]
776
--
777
-- @since 0.5.2
778
lowerTriangular :: forall e. Num e => Comp -> Sz1 -> (Ix2 -> e) -> Matrix DL e
779
lowerTriangular comp (Sz1 n) f = DLArray comp (SafeSz (n :. n)) load
2✔
780
  where
781
    load :: Loader e
782
    load scheduler startAt uWrite uSet = do
2✔
783
      forM_ (0 ..: n) $ \i -> do
2✔
784
        let !k = startAt + i * n
2✔
785
        scheduleWork_ scheduler $ do
2✔
786
          forM_ (0 ... i) $ \j -> uWrite (k + j) (f (i :. j))
2✔
787
          uSet (k + i + 1) (Sz (n - i - 1)) 0
2✔
788
{-# INLINE lowerTriangular #-}
789

790
-- | Create an upper triangular (U in LU decomposition) matrix of size @NxN@
791
--
792
-- ==== __Example__
793
--
794
-- >>> import Data.Massiv.Array
795
-- >>> upperTriangular Par 5 (\(i :. j) -> i + j)
796
-- Array DL Par (Sz (5 :. 5))
797
--   [ [ 0, 1, 2, 3, 4 ]
798
--   , [ 0, 2, 3, 4, 5 ]
799
--   , [ 0, 0, 4, 5, 6 ]
800
--   , [ 0, 0, 0, 6, 7 ]
801
--   , [ 0, 0, 0, 0, 8 ]
802
--   ]
803
--
804
-- @since 0.5.2
805
upperTriangular :: forall e. Num e => Comp -> Sz1 -> (Ix2 -> e) -> Matrix DL e
806
upperTriangular comp (Sz1 n) f = DLArray comp (SafeSz (n :. n)) load
2✔
807
  where
808
    load :: Loader e
809
    load scheduler startAt uWrite uSet = do
2✔
810
      forM_ (0 ..: n) $ \i -> do
2✔
811
        let !k = startAt + i * n
2✔
812
        scheduleWork_ scheduler $ do
2✔
813
          uSet k (SafeSz i) 0
2✔
814
          forM_ (i ..: n) $ \j -> uWrite (k + j) (f (i :. j))
2✔
815
{-# INLINE upperTriangular #-}
816

817
-- | Negate each element of the array
818
--
819
-- @since 0.4.0
820
negateA :: (Index ix, Numeric r e) => Array r ix e -> Array r ix e
821
negateA = unsafeLiftArray negate
2✔
822
{-# INLINE negateA #-}
823

824
-- | Apply `abs` to each element of the array
825
--
826
-- @since 0.4.0
827
absA :: (Index ix, Numeric r e) => Array r ix e -> Array r ix e
828
absA = absPointwise
2✔
829
{-# INLINE absA #-}
830

831
-- | Apply `signum` to each element of the array
832
--
833
-- @since 0.4.0
834
signumA :: (Index ix, Numeric r e) => Array r ix e -> Array r ix e
835
signumA = unsafeLiftArray signum
2✔
836
{-# INLINE signumA #-}
837

838
-- | Divide each element of one array by another pointwise. Same as `!/!` but produces
839
-- monadic computation that allows for handling failure.
840
--
841
-- /__Throws Exception__/: `SizeMismatchException` when array sizes do not match.
842
--
843
-- @since 0.4.0
844
(./.)
845
  :: (Index ix, NumericFloat r e, MonadThrow m)
846
  => Array r ix e
847
  -> Array r ix e
848
  -> m (Array r ix e)
849
(./.) = applyExactSize2M divisionPointwise
2✔
850
{-# INLINE (./.) #-}
851

852
-- | Divide two arrays pointwise. Prefer to use monadic version of this function `./.`
853
-- whenever possible, because it is better to avoid partial functions.
854
--
855
-- [Partial] Mismatched array sizes will result in an impure exception being thrown.
856
--
857
-- ====__Example__
858
--
859
-- >>> let arr1 = fromIntegral <$> (Ix1 20 ..: 25) :: Array D Ix1 Float
860
-- >>> let arr2 = fromIntegral <$> (Ix1 100 ..: 105) :: Array D Ix1 Float
861
-- >>> arr1 !/! arr2
862
-- Array D Seq (Sz1 5)
863
--   [ 0.2, 0.20792079, 0.21568628, 0.22330096, 0.23076923 ]
864
--
865
-- @since 0.5.6
866
(!/!) :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e -> Array r ix e
867
(!/!) a1 a2 = throwEither (a1 ./. a2)
2✔
868
{-# INLINE (!/!) #-}
869

870
-- | Divide a scalar value by each element of the array.
871
--
872
-- > e /. arr == e *. recipA arr
873
--
874
-- ====__Example__
875
--
876
-- >>> let arr = fromIntegral <$> (Ix1 20 ..: 25) :: Array D Ix1 Float
877
-- >>> arr
878
-- Array D Seq (Sz1 5)
879
--   [ 20.0, 21.0, 22.0, 23.0, 24.0 ]
880
-- >>> 100 /. arr
881
-- Array D Seq (Sz1 5)
882
--   [ 5.0, 4.7619047, 4.5454545, 4.347826, 4.1666665 ]
883
--
884
-- @since 0.5.6
885
(/.) :: (Index ix, NumericFloat r e) => e -> Array r ix e -> Array r ix e
886
(/.) = scalarDivide
2✔
887
{-# INLINE (/.) #-}
888

889
-- | Divide each element of the array by a scalar value.
890
--
891
-- ====__Example__
892
--
893
-- >>> let arr = fromIntegral <$> (Ix1 20 ..: 25) :: Array D Ix1 Float
894
-- >>> arr
895
-- Array D Seq (Sz1 5)
896
--   [ 20.0, 21.0, 22.0, 23.0, 24.0 ]
897
-- >>> arr ./ 100
898
-- Array D Seq (Sz1 5)
899
--   [ 0.2, 0.21, 0.22, 0.23, 0.24 ]
900
--
901
-- @since 0.4.0
902
(./) :: (Index ix, NumericFloat r e) => Array r ix e -> e -> Array r ix e
903
(./) = divideScalar
2✔
904
{-# INLINE (./) #-}
905

906
(.^^)
907
  :: (Index ix, Numeric r e, Fractional e, Integral b)
908
  => Array r ix e
909
  -> b
910
  -> Array r ix e
911
(.^^) arr n = unsafeLiftArray (^^ n) arr
2✔
912
{-# INLINE (.^^) #-}
913

914
-- | Apply reciprocal to each element of the array.
915
--
916
-- > recipA arr == 1 /. arr
917
--
918
-- @since 0.4.0
919
recipA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
920
recipA = recipPointwise
2✔
921
{-# INLINE recipA #-}
922

923
-- | Apply exponent to each element of the array.
924
--
925
-- > expA arr == map exp arr
926
--
927
-- @since 0.4.0
928
expA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
929
expA = unsafeLiftArray exp
2✔
930
{-# INLINE expA #-}
931

932
-- | Apply square root to each element of the array.
933
--
934
-- > sqrtA arr == map sqrt arr
935
--
936
-- @since 0.4.0
937
sqrtA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
938
sqrtA = unsafeLiftArray sqrt
2✔
939
{-# INLINE sqrtA #-}
940

941
-- | Apply logarithm to each element of the array.
942
--
943
-- > logA arr == map log arr
944
--
945
-- @since 0.4.0
946
logA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
947
logA = unsafeLiftArray log
2✔
948
{-# INLINE logA #-}
949

950
-- | Apply logarithm to each element of the array where the base is in the same cell in
951
-- the second array.
952
--
953
-- > logBaseA arr1 arr2 == zipWith logBase arr1 arr2
954
--
955
-- [Partial] Throws an error when arrays do not have matching sizes
956
--
957
-- @since 0.4.0
958
logBaseA
959
  :: (Index ix, Source r1 e, Source r2 e, Floating e)
960
  => Array r1 ix e
961
  -> Array r2 ix e
962
  -> Array D ix e
963
logBaseA = liftArray2' logBase
2✔
964
{-# INLINE logBaseA #-}
965

966
-- TODO: siwtch to
967
-- (breaking) logBaseA :: Array r ix e -> e -> Array D ix e
968
-- logBasesM :: Array r ix e -> Array r ix e -> m (Array D ix e)
969

970
-- | Apply power to each element of the array where the power value is in the same cell
971
-- in the second array.
972
--
973
-- > arr1 .** arr2 == zipWith (**) arr1 arr2
974
--
975
-- [Partial] Throws an error when arrays do not have matching sizes
976
--
977
-- @since 0.4.0
978
(.**)
979
  :: (Index ix, Source r1 e, Source r2 e, Floating e)
980
  => Array r1 ix e
981
  -> Array r2 ix e
982
  -> Array D ix e
983
(.**) = liftArray2' (**)
2✔
984
{-# INLINE (.**) #-}
985

986
-- TODO:
987
-- !**! :: Array r1 ix e -> Array r2 ix e -> Array D ix e
988
-- .**. :: Array r1 ix e -> Array r2 ix e -> m (Array D ix e)
989
-- (breaking) .** :: Array r1 ix e -> e -> Array D ix e
990

991
-- | Apply sine function to each element of the array.
992
--
993
-- > sinA arr == map sin arr
994
--
995
-- @since 0.4.0
996
sinA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
997
sinA = unsafeLiftArray sin
2✔
998
{-# INLINE sinA #-}
999

1000
-- | Apply cosine function to each element of the array.
1001
--
1002
-- > cosA arr == map cos arr
1003
--
1004
-- @since 0.4.0
1005
cosA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1006
cosA = unsafeLiftArray cos
2✔
1007
{-# INLINE cosA #-}
1008

1009
-- | Apply tangent function to each element of the array.
1010
--
1011
-- > tanA arr == map tan arr
1012
--
1013
-- @since 0.4.0
1014
tanA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1015
tanA = unsafeLiftArray tan
2✔
1016
{-# INLINE tanA #-}
1017

1018
-- | Apply arcsine function to each element of the array.
1019
--
1020
-- > asinA arr == map asin arr
1021
--
1022
-- @since 0.4.0
1023
asinA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1024
asinA = unsafeLiftArray asin
2✔
1025
{-# INLINE asinA #-}
1026

1027
-- | Apply arctangent function to each element of the array.
1028
--
1029
-- > atanA arr == map atan arr
1030
--
1031
-- @since 0.4.0
1032
atanA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1033
atanA = unsafeLiftArray atan
2✔
1034
{-# INLINE atanA #-}
1035

1036
-- | Apply arccosine function to each element of the array.
1037
--
1038
-- > acosA arr == map acos arr
1039
--
1040
-- @since 0.4.0
1041
acosA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1042
acosA = unsafeLiftArray acos
2✔
1043
{-# INLINE acosA #-}
1044

1045
-- | Apply hyperbolic sine function to each element of the array.
1046
--
1047
-- > sinhA arr == map sinh arr
1048
--
1049
-- @since 0.4.0
1050
sinhA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1051
sinhA = unsafeLiftArray sinh
2✔
1052
{-# INLINE sinhA #-}
1053

1054
-- | Apply hyperbolic tangent function to each element of the array.
1055
--
1056
-- > tanhA arr == map tanh arr
1057
--
1058
-- @since 0.4.0
1059
tanhA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1060
tanhA = unsafeLiftArray tanh
2✔
1061
{-# INLINE tanhA #-}
1062

1063
-- | Apply hyperbolic cosine function to each element of the array.
1064
--
1065
-- > coshA arr == map cosh arr
1066
--
1067
-- @since 0.4.0
1068
coshA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1069
coshA = unsafeLiftArray cosh
2✔
1070
{-# INLINE coshA #-}
1071

1072
-- | Apply inverse hyperbolic sine function to each element of the array.
1073
--
1074
-- > asinhA arr == map asinh arr
1075
--
1076
-- @since 0.4.0
1077
asinhA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1078
asinhA = unsafeLiftArray asinh
2✔
1079
{-# INLINE asinhA #-}
1080

1081
-- | Apply inverse hyperbolic cosine function to each element of the array.
1082
--
1083
-- > acoshA arr == map acosh arr
1084
--
1085
-- @since 0.4.0
1086
acoshA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1087
acoshA = unsafeLiftArray acosh
2✔
1088
{-# INLINE acoshA #-}
1089

1090
-- | Apply inverse hyperbolic tangent function to each element of the array.
1091
--
1092
-- > atanhA arr == map atanh arr
1093
--
1094
-- @since 0.4.0
1095
atanhA :: (Index ix, NumericFloat r e) => Array r ix e -> Array r ix e
1096
atanhA = unsafeLiftArray atanh
2✔
1097
{-# INLINE atanhA #-}
1098

1099
-- | Perform a pointwise quotient where first array contains numerators and the second
1100
-- one denominators
1101
--
1102
-- > quotA arr1 arr2 == zipWith quot arr1 arr2
1103
--
1104
-- [Partial] Mismatched array sizes will result in an impure exception being thrown.
1105
--
1106
-- @since 0.1.0
1107
quotA
1108
  :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e)
1109
  => Array r1 ix e
1110
  -> Array r2 ix e
1111
  -> Array D ix e
1112
quotA = liftArray2' quot
×
1113
{-# INLINE quotA #-}
1114

1115
-- | Perform a pointwise remainder computation
1116
--
1117
-- > remA arr1 arr2 == zipWith rem arr1 arr2
1118
--
1119
-- [Partial] Mismatched array sizes will result in an impure exception being thrown.
1120
--
1121
-- @since 0.1.0
1122
remA
1123
  :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e)
1124
  => Array r1 ix e
1125
  -> Array r2 ix e
1126
  -> Array D ix e
1127
remA = liftArray2' rem
×
1128
{-# INLINE remA #-}
1129

1130
-- | Perform a pointwise integer division where first array contains numerators and the
1131
-- second one denominators
1132
--
1133
-- > divA arr1 arr2 == zipWith div arr1 arr2
1134
--
1135
-- [Partial] Mismatched array sizes will result in an impure exception being thrown.
1136
--
1137
-- @since 0.1.0
1138
divA
1139
  :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e)
1140
  => Array r1 ix e
1141
  -> Array r2 ix e
1142
  -> Array D ix e
1143
divA = liftArray2' div
×
1144
{-# INLINE divA #-}
1145

1146
-- TODO:
1147
--  * Array r ix e -> Array r ix e -> m (Array r ix e)
1148
--  * Array r ix e -> e -> Array r ix e
1149
--  * e -> Array r ix e -> Array r ix e
1150

1151
-- | Perform a pointwise modulo computation
1152
--
1153
-- > modA arr1 arr2 == zipWith mod arr1 arr2
1154
--
1155
-- [Partial] Mismatched array sizes will result in an impure exception being thrown.
1156
--
1157
-- @since 0.1.0
1158
modA
1159
  :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e)
1160
  => Array r1 ix e
1161
  -> Array r2 ix e
1162
  -> Array D ix e
1163
modA = liftArray2' mod
×
1164
{-# INLINE modA #-}
1165

1166
-- | Perform a pointwise quotient with remainder where first array contains numerators
1167
-- and the second one denominators
1168
--
1169
-- > quotRemA arr1 arr2 == zipWith quotRem arr1 arr2
1170
--
1171
-- [Partial] Mismatched array sizes will result in an impure exception being thrown.
1172
--
1173
-- @since 0.1.0
1174
quotRemA
1175
  :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e)
1176
  => Array r1 ix e
1177
  -> Array r2 ix e
1178
  -> (Array D ix e, Array D ix e)
1179
quotRemA arr1 = A.unzip . liftArray2' quotRem arr1
×
1180
{-# INLINE quotRemA #-}
1181

1182
-- | Perform a pointwise integer division with modulo where first array contains
1183
-- numerators and the second one denominators
1184
--
1185
-- > divModA arr1 arr2 == zipWith divMod arr1 arr2
1186
--
1187
-- [Partial] Mismatched array sizes will result in an impure exception being thrown.
1188
--
1189
-- @since 0.1.0
1190
divModA
1191
  :: (HasCallStack, Index ix, Source r1 e, Source r2 e, Integral e)
1192
  => Array r1 ix e
1193
  -> Array r2 ix e
1194
  -> (Array D ix e, Array D ix e)
1195
divModA arr1 = A.unzip . liftArray2' divMod arr1
×
1196
{-# INLINE divModA #-}
1197

1198
-- | Truncate each element of the array.
1199
--
1200
-- > truncateA arr == map truncate arr
1201
--
1202
-- @since 0.1.0
1203
truncateA :: (Index ix, Source r a, RealFrac a, Integral e) => Array r ix a -> Array D ix e
1204
truncateA = A.map truncate
×
1205
{-# INLINE truncateA #-}
1206

1207
-- | Round each element of the array.
1208
--
1209
-- > truncateA arr == map truncate arr
1210
--
1211
-- @since 0.1.0
1212
roundA :: (Index ix, Source r a, RealFrac a, Integral e) => Array r ix a -> Array D ix e
1213
roundA = A.map round
×
1214
{-# INLINE roundA #-}
1215

1216
-- | Ceiling of each element of the array.
1217
--
1218
-- > truncateA arr == map truncate arr
1219
--
1220
-- @since 0.1.0
1221
ceilingA :: (Index ix, Source r a, RealFrac a, Integral e) => Array r ix a -> Array D ix e
1222
ceilingA = A.map ceiling
×
1223
{-# INLINE ceilingA #-}
1224

1225
-- | Floor each element of the array.
1226
--
1227
-- > truncateA arr == map truncate arr
1228
--
1229
-- @since 0.1.0
1230
floorA :: (Index ix, Source r a, RealFrac a, Integral e) => Array r ix a -> Array D ix e
1231
floorA = A.map floor
×
1232
{-# INLINE floorA #-}
1233

1234
-- | Perform atan2 pointwise
1235
--
1236
-- > atan2A arr1 arr2 == zipWith atan2 arr1 arr2
1237
--
1238
-- /__Throws Exception__/: `SizeMismatchException` when array sizes do not match.
1239
--
1240
-- @since 0.1.0
1241
atan2A
1242
  :: (Index ix, Numeric r e, RealFloat e, MonadThrow m)
1243
  => Array r ix e
1244
  -> Array r ix e
1245
  -> m (Array r ix e)
1246
atan2A = liftNumArray2M atan2
2✔
1247
{-# INLINE atan2A #-}
1248

1249
-- | Same as `sumArraysM`, compute sum of arrays pointwise. All arrays must have the same
1250
-- size, otherwise it will result in an error.
1251
--
1252
-- @since 1.0.0
1253
sumArrays'
1254
  :: (HasCallStack, Foldable t, Load r ix e, Numeric r e) => t (Array r ix e) -> Array r ix e
UNCOV
1255
sumArrays' = throwEither . sumArraysM
×
1256
{-# INLINE sumArrays' #-}
1257

1258
-- | Compute sum of arrays pointwise. All arrays must have the same size.
1259
--
1260
-- ====__Examples__
1261
--
1262
-- >>> import Data.Massiv.Array as A
1263
-- >>> sumArraysM [] :: IO (Array P Ix3 Int)
1264
-- Array P Seq (Sz (0 :> 0 :. 0))
1265
--   [  ]
1266
-- >>> arr = A.makeArrayR P Seq (Sz3 4 5 6) $ \(i :> j :. k) -> i + j * k
1267
-- >>> arr
1268
-- Array P Seq (Sz (4 :> 5 :. 6))
1269
--   [ [ [ 0, 0, 0, 0, 0, 0 ]
1270
--     , [ 0, 1, 2, 3, 4, 5 ]
1271
--     , [ 0, 2, 4, 6, 8, 10 ]
1272
--     , [ 0, 3, 6, 9, 12, 15 ]
1273
--     , [ 0, 4, 8, 12, 16, 20 ]
1274
--     ]
1275
--   , [ [ 1, 1, 1, 1, 1, 1 ]
1276
--     , [ 1, 2, 3, 4, 5, 6 ]
1277
--     , [ 1, 3, 5, 7, 9, 11 ]
1278
--     , [ 1, 4, 7, 10, 13, 16 ]
1279
--     , [ 1, 5, 9, 13, 17, 21 ]
1280
--     ]
1281
--   , [ [ 2, 2, 2, 2, 2, 2 ]
1282
--     , [ 2, 3, 4, 5, 6, 7 ]
1283
--     , [ 2, 4, 6, 8, 10, 12 ]
1284
--     , [ 2, 5, 8, 11, 14, 17 ]
1285
--     , [ 2, 6, 10, 14, 18, 22 ]
1286
--     ]
1287
--   , [ [ 3, 3, 3, 3, 3, 3 ]
1288
--     , [ 3, 4, 5, 6, 7, 8 ]
1289
--     , [ 3, 5, 7, 9, 11, 13 ]
1290
--     , [ 3, 6, 9, 12, 15, 18 ]
1291
--     , [ 3, 7, 11, 15, 19, 23 ]
1292
--     ]
1293
--   ]
1294
-- >>> sumArraysM $ outerSlices arr
1295
-- Array P Seq (Sz (5 :. 6))
1296
--   [ [ 6, 6, 6, 6, 6, 6 ]
1297
--   , [ 6, 10, 14, 18, 22, 26 ]
1298
--   , [ 6, 14, 22, 30, 38, 46 ]
1299
--   , [ 6, 18, 30, 42, 54, 66 ]
1300
--   , [ 6, 22, 38, 54, 70, 86 ]
1301
--   ]
1302
-- >>> sumArraysM $ innerSlices arr
1303
-- Array D Seq (Sz (4 :. 5))
1304
--   [ [ 0, 15, 30, 45, 60 ]
1305
--   , [ 6, 21, 36, 51, 66 ]
1306
--   , [ 12, 27, 42, 57, 72 ]
1307
--   , [ 18, 33, 48, 63, 78 ]
1308
--   ]
1309
--
1310
-- @since 1.0.0
1311
sumArraysM
1312
  :: (Foldable t, Load r ix e, Numeric r e, MonadThrow m) => t (Array r ix e) -> m (Array r ix e)
1313
sumArraysM as =
×
1314
  case F.toList as of
×
1315
    [] -> pure empty
×
1316
    (x : xs) -> F.foldlM (.+.) x xs
×
1317
{-# INLINE sumArraysM #-}
1318

1319
-- OPTIMIZE: Allocate a single result array and write sums into it incrementally.
1320

1321
-- | Same as `productArraysM`. Compute product of arrays pointwise. All arrays must have
1322
-- the same size, otherwise it
1323
-- will result in an error.
1324
--
1325
-- @since 1.0.0
1326
productArrays'
1327
  :: (HasCallStack, Foldable t, Load r ix e, Numeric r e) => t (Array r ix e) -> Array r ix e
1328
productArrays' = throwEither . productArraysM
×
1329
{-# INLINE productArrays' #-}
1330

1331
-- | Compute product of arrays pointwise. All arrays must have the same size.
1332
--
1333
-- ====__Examples__
1334
--
1335
-- >>> import Data.Massiv.Array as A
1336
-- >>> productArraysM [] :: IO (Array P Ix3 Int)
1337
-- Array P Seq (Sz (0 :> 0 :. 0))
1338
--   [  ]
1339
-- >>> arr = A.makeArrayR P Seq (Sz3 4 5 6) $ \(i :> j :. k) -> i + j * k
1340
-- >>> arr
1341
-- Array P Seq (Sz (4 :> 5 :. 6))
1342
--   [ [ [ 0, 0, 0, 0, 0, 0 ]
1343
--     , [ 0, 1, 2, 3, 4, 5 ]
1344
--     , [ 0, 2, 4, 6, 8, 10 ]
1345
--     , [ 0, 3, 6, 9, 12, 15 ]
1346
--     , [ 0, 4, 8, 12, 16, 20 ]
1347
--     ]
1348
--   , [ [ 1, 1, 1, 1, 1, 1 ]
1349
--     , [ 1, 2, 3, 4, 5, 6 ]
1350
--     , [ 1, 3, 5, 7, 9, 11 ]
1351
--     , [ 1, 4, 7, 10, 13, 16 ]
1352
--     , [ 1, 5, 9, 13, 17, 21 ]
1353
--     ]
1354
--   , [ [ 2, 2, 2, 2, 2, 2 ]
1355
--     , [ 2, 3, 4, 5, 6, 7 ]
1356
--     , [ 2, 4, 6, 8, 10, 12 ]
1357
--     , [ 2, 5, 8, 11, 14, 17 ]
1358
--     , [ 2, 6, 10, 14, 18, 22 ]
1359
--     ]
1360
--   , [ [ 3, 3, 3, 3, 3, 3 ]
1361
--     , [ 3, 4, 5, 6, 7, 8 ]
1362
--     , [ 3, 5, 7, 9, 11, 13 ]
1363
--     , [ 3, 6, 9, 12, 15, 18 ]
1364
--     , [ 3, 7, 11, 15, 19, 23 ]
1365
--     ]
1366
--   ]
1367
-- >>> productArraysM $ outerSlices arr
1368
-- Array P Seq (Sz (5 :. 6))
1369
--   [ [ 0, 0, 0, 0, 0, 0 ]
1370
--   , [ 0, 24, 120, 360, 840, 1680 ]
1371
--   , [ 0, 120, 840, 3024, 7920, 17160 ]
1372
--   , [ 0, 360, 3024, 11880, 32760, 73440 ]
1373
--   , [ 0, 840, 7920, 32760, 93024, 212520 ]
1374
--   ]
1375
-- >>> productArraysM $ innerSlices arr
1376
-- Array D Seq (Sz (4 :. 5))
1377
--   [ [ 0, 0, 0, 0, 0 ]
1378
--   , [ 1, 720, 10395, 58240, 208845 ]
1379
--   , [ 64, 5040, 46080, 209440, 665280 ]
1380
--   , [ 729, 20160, 135135, 524880, 1514205 ]
1381
--   ]
1382
--
1383
-- @since 1.0.0
1384
productArraysM
1385
  :: (Foldable t, Load r ix e, Numeric r e, MonadThrow m) => t (Array r ix e) -> m (Array r ix e)
1386
productArraysM as =
×
1387
  case F.toList as of
×
1388
    [] -> pure empty
×
1389
    (x : xs) -> F.foldlM (.*.) x xs
×
1390
{-# INLINE productArraysM #-}
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc