{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE UndecidableInstances #-}
module Numeric.LAPACK.Matrix.Array (
Matrix(Array),
ArrayMatrix,
Array,
Full,
General,
Tall,
Wide,
Square,
shape,
reshape,
mapShape,
toVector,
fromVector,
lift0,
lift1,
lift2,
lift3,
lift4,
unlift1,
unlift2,
unliftRow,
unliftColumn,
Plain.Homogeneous, zero, negate, scaleReal, scale, scaleRealReal, (.*#),
Plain.ShapeOrder, forceOrder, Plain.shapeOrder, adaptOrder,
Plain.Additive, add, sub, (#+#), (#-#),
Plain.Complex,
Plain.SquareShape,
Multiply.MultiplyVector,
Multiply.MultiplySquare,
Multiply.Power,
Multiply.Multiply,
Divide.Determinant,
Divide.Solve,
Divide.Inverse,
) where
import qualified Numeric.LAPACK.Matrix.Plain.Divide as Divide
import qualified Numeric.LAPACK.Matrix.Plain.Multiply as Multiply
import qualified Numeric.LAPACK.Matrix.Plain.Class as Plain
import qualified Numeric.LAPACK.Matrix.Type as Type
import qualified Numeric.LAPACK.Matrix.Shape.Private as MatrixShape
import qualified Numeric.LAPACK.Matrix.Shape.Box as Box
import qualified Numeric.LAPACK.Matrix.Basic as Basic
import Numeric.LAPACK.Matrix.Plain.Format (FormatArray, formatArray)
import Numeric.LAPACK.Matrix.Type (Matrix)
import Numeric.LAPACK.Vector (Vector)
import Numeric.LAPACK.Scalar (RealOf)
import qualified Numeric.Netlib.Class as Class
import qualified Control.DeepSeq as DeepSeq
import qualified Data.Array.Comfort.Storable.Unchecked as Array
import qualified Data.Array.Comfort.Storable as CheckedArray
import qualified Data.Array.Comfort.Shape as Shape
import Prelude hiding (negate)
data Array shape
newtype instance Matrix (Array shape) a = Array (Array.Array shape a)
deriving (Int -> Matrix (Array shape) a -> ShowS
[Matrix (Array shape) a] -> ShowS
Matrix (Array shape) a -> String
(Int -> Matrix (Array shape) a -> ShowS)
-> (Matrix (Array shape) a -> String)
-> ([Matrix (Array shape) a] -> ShowS)
-> Show (Matrix (Array shape) a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall shape a.
(C shape, Storable a, Show shape, Show a) =>
Int -> Matrix (Array shape) a -> ShowS
forall shape a.
(C shape, Storable a, Show shape, Show a) =>
[Matrix (Array shape) a] -> ShowS
forall shape a.
(C shape, Storable a, Show shape, Show a) =>
Matrix (Array shape) a -> String
showList :: [Matrix (Array shape) a] -> ShowS
$cshowList :: forall shape a.
(C shape, Storable a, Show shape, Show a) =>
[Matrix (Array shape) a] -> ShowS
show :: Matrix (Array shape) a -> String
$cshow :: forall shape a.
(C shape, Storable a, Show shape, Show a) =>
Matrix (Array shape) a -> String
showsPrec :: Int -> Matrix (Array shape) a -> ShowS
$cshowsPrec :: forall shape a.
(C shape, Storable a, Show shape, Show a) =>
Int -> Matrix (Array shape) a -> ShowS
Show)
type ArrayMatrix shape = Matrix (Array shape)
type Full vert horiz height width =
ArrayMatrix (MatrixShape.Full vert horiz height width)
type General height width = ArrayMatrix (MatrixShape.General height width)
type Tall height width = ArrayMatrix (MatrixShape.Tall height width)
type Wide height width = ArrayMatrix (MatrixShape.Wide height width)
type Square sh = ArrayMatrix (MatrixShape.Square sh)
instance (DeepSeq.NFData shape) => Type.NFData (Array shape) where
rnf :: Matrix (Array shape) a -> ()
rnf (Array arr) = Array shape a -> ()
forall a. NFData a => a -> ()
DeepSeq.rnf Array shape a
arr
instance (Box.Box sh) => Type.Box (Array sh) where
type HeightOf (Array sh) = Box.HeightOf sh
type WidthOf (Array sh) = Box.WidthOf sh
height :: Matrix (Array sh) a -> HeightOf (Array sh)
height (Array arr) = sh -> HeightOf sh
forall shape. Box shape => shape -> HeightOf shape
Box.height (sh -> HeightOf sh) -> sh -> HeightOf sh
forall a b. (a -> b) -> a -> b
$ Array sh a -> sh
forall sh a. Array sh a -> sh
Array.shape Array sh a
arr
width :: Matrix (Array sh) a -> WidthOf (Array sh)
width (Array arr) = sh -> WidthOf sh
forall shape. Box shape => shape -> WidthOf shape
Box.width (sh -> WidthOf sh) -> sh -> WidthOf sh
forall a b. (a -> b) -> a -> b
$ Array sh a -> sh
forall sh a. Array sh a -> sh
Array.shape Array sh a
arr
shape :: ArrayMatrix sh a -> sh
shape :: ArrayMatrix sh a -> sh
shape (Array a) = Array sh a -> sh
forall sh a. Array sh a -> sh
Array.shape Array sh a
a
reshape ::
(Shape.C sh0, Shape.C sh1) =>
sh1 -> ArrayMatrix sh0 a -> ArrayMatrix sh1 a
reshape :: sh1 -> ArrayMatrix sh0 a -> ArrayMatrix sh1 a
reshape = (Array sh0 a -> Array sh1 a)
-> ArrayMatrix sh0 a -> ArrayMatrix sh1 a
forall shA a shB b.
(Array shA a -> Array shB b)
-> ArrayMatrix shA a -> ArrayMatrix shB b
lift1 ((Array sh0 a -> Array sh1 a)
-> ArrayMatrix sh0 a -> ArrayMatrix sh1 a)
-> (sh1 -> Array sh0 a -> Array sh1 a)
-> sh1
-> ArrayMatrix sh0 a
-> ArrayMatrix sh1 a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. sh1 -> Array sh0 a -> Array sh1 a
forall sh0 sh1 a.
(C sh0, C sh1) =>
sh1 -> Array sh0 a -> Array sh1 a
CheckedArray.reshape
mapShape ::
(Shape.C sh0, Shape.C sh1) =>
(sh0 -> sh1) -> ArrayMatrix sh0 a -> ArrayMatrix sh1 a
mapShape :: (sh0 -> sh1) -> ArrayMatrix sh0 a -> ArrayMatrix sh1 a
mapShape = (Array sh0 a -> Array sh1 a)
-> ArrayMatrix sh0 a -> ArrayMatrix sh1 a
forall shA a shB b.
(Array shA a -> Array shB b)
-> ArrayMatrix shA a -> ArrayMatrix shB b
lift1 ((Array sh0 a -> Array sh1 a)
-> ArrayMatrix sh0 a -> ArrayMatrix sh1 a)
-> ((sh0 -> sh1) -> Array sh0 a -> Array sh1 a)
-> (sh0 -> sh1)
-> ArrayMatrix sh0 a
-> ArrayMatrix sh1 a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (sh0 -> sh1) -> Array sh0 a -> Array sh1 a
forall sh0 sh1 a.
(C sh0, C sh1) =>
(sh0 -> sh1) -> Array sh0 a -> Array sh1 a
CheckedArray.mapShape
toVector :: ArrayMatrix sh a -> Array.Array sh a
toVector :: ArrayMatrix sh a -> Array sh a
toVector (Array a) = Array sh a
a
fromVector ::
(Plain.Admissible sh, Class.Floating a) =>
Array.Array sh a -> ArrayMatrix sh a
fromVector :: Array sh a -> ArrayMatrix sh a
fromVector Array sh a
arr =
Array sh a -> ArrayMatrix sh a
forall shape a. Array shape a -> Matrix (Array shape) a
Array (Array sh a -> ArrayMatrix sh a) -> Array sh a -> ArrayMatrix sh a
forall a b. (a -> b) -> a -> b
$
case Array sh a -> Maybe String
forall shape a.
(Admissible shape, Floating a) =>
Array shape a -> Maybe String
Plain.check Array sh a
arr of
Maybe String
Nothing -> Array sh a
arr
Just String
msg -> String -> Array sh a
forall a. HasCallStack => String -> a
error (String -> Array sh a) -> String -> Array sh a
forall a b. (a -> b) -> a -> b
$ String
"Matrix.Array.fromVector: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg
lift0 :: Array.Array shA a -> ArrayMatrix shA a
lift0 :: Array shA a -> ArrayMatrix shA a
lift0 = Array shA a -> ArrayMatrix shA a
forall shape a. Array shape a -> Matrix (Array shape) a
Array
lift1 ::
(Array.Array shA a -> Array.Array shB b) ->
ArrayMatrix shA a -> ArrayMatrix shB b
lift1 :: (Array shA a -> Array shB b)
-> ArrayMatrix shA a -> ArrayMatrix shB b
lift1 Array shA a -> Array shB b
f (Array a) = Array shB b -> ArrayMatrix shB b
forall shape a. Array shape a -> Matrix (Array shape) a
Array (Array shB b -> ArrayMatrix shB b)
-> Array shB b -> ArrayMatrix shB b
forall a b. (a -> b) -> a -> b
$ Array shA a -> Array shB b
f Array shA a
a
lift2 ::
(Array.Array shA a -> Array.Array shB b -> Array.Array shC c) ->
ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c
lift2 :: (Array shA a -> Array shB b -> Array shC c)
-> ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c
lift2 Array shA a -> Array shB b -> Array shC c
f (Array a) (Array b) = Array shC c -> ArrayMatrix shC c
forall shape a. Array shape a -> Matrix (Array shape) a
Array (Array shC c -> ArrayMatrix shC c)
-> Array shC c -> ArrayMatrix shC c
forall a b. (a -> b) -> a -> b
$ Array shA a -> Array shB b -> Array shC c
f Array shA a
a Array shB b
b
lift3 ::
(Array.Array shA a -> Array.Array shB b ->
Array.Array shC c -> Array.Array shD d) ->
ArrayMatrix shA a -> ArrayMatrix shB b ->
ArrayMatrix shC c -> ArrayMatrix shD d
lift3 :: (Array shA a -> Array shB b -> Array shC c -> Array shD d)
-> ArrayMatrix shA a
-> ArrayMatrix shB b
-> ArrayMatrix shC c
-> ArrayMatrix shD d
lift3 Array shA a -> Array shB b -> Array shC c -> Array shD d
f (Array a) (Array b) (Array c) = Array shD d -> ArrayMatrix shD d
forall shape a. Array shape a -> Matrix (Array shape) a
Array (Array shD d -> ArrayMatrix shD d)
-> Array shD d -> ArrayMatrix shD d
forall a b. (a -> b) -> a -> b
$ Array shA a -> Array shB b -> Array shC c -> Array shD d
f Array shA a
a Array shB b
b Array shC c
c
lift4 ::
(Array.Array shA a -> Array.Array shB b ->
Array.Array shC c -> Array.Array shD d ->
Array.Array shE e) ->
ArrayMatrix shA a -> ArrayMatrix shB b ->
ArrayMatrix shC c -> ArrayMatrix shD d ->
ArrayMatrix shE e
lift4 :: (Array shA a
-> Array shB b -> Array shC c -> Array shD d -> Array shE e)
-> ArrayMatrix shA a
-> ArrayMatrix shB b
-> ArrayMatrix shC c
-> ArrayMatrix shD d
-> ArrayMatrix shE e
lift4 Array shA a
-> Array shB b -> Array shC c -> Array shD d -> Array shE e
f (Array a) (Array b) (Array c) (Array d) = Array shE e -> ArrayMatrix shE e
forall shape a. Array shape a -> Matrix (Array shape) a
Array (Array shE e -> ArrayMatrix shE e)
-> Array shE e -> ArrayMatrix shE e
forall a b. (a -> b) -> a -> b
$ Array shA a
-> Array shB b -> Array shC c -> Array shD d -> Array shE e
f Array shA a
a Array shB b
b Array shC c
c Array shD d
d
unlift1 ::
(ArrayMatrix shA a -> ArrayMatrix shB b) ->
Array.Array shA a -> Array.Array shB b
unlift1 :: (ArrayMatrix shA a -> ArrayMatrix shB b)
-> Array shA a -> Array shB b
unlift1 ArrayMatrix shA a -> ArrayMatrix shB b
f Array shA a
a = ArrayMatrix shB b -> Array shB b
forall sh a. ArrayMatrix sh a -> Array sh a
toVector (ArrayMatrix shB b -> Array shB b)
-> ArrayMatrix shB b -> Array shB b
forall a b. (a -> b) -> a -> b
$ ArrayMatrix shA a -> ArrayMatrix shB b
f (ArrayMatrix shA a -> ArrayMatrix shB b)
-> ArrayMatrix shA a -> ArrayMatrix shB b
forall a b. (a -> b) -> a -> b
$ Array shA a -> ArrayMatrix shA a
forall shape a. Array shape a -> Matrix (Array shape) a
Array Array shA a
a
unlift2 ::
(ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c) ->
Array.Array shA a -> Array.Array shB b -> Array.Array shC c
unlift2 :: (ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c)
-> Array shA a -> Array shB b -> Array shC c
unlift2 ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c
f Array shA a
a Array shB b
b = ArrayMatrix shC c -> Array shC c
forall sh a. ArrayMatrix sh a -> Array sh a
toVector (ArrayMatrix shC c -> Array shC c)
-> ArrayMatrix shC c -> Array shC c
forall a b. (a -> b) -> a -> b
$ ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c
f (Array shA a -> ArrayMatrix shA a
forall shape a. Array shape a -> Matrix (Array shape) a
Array Array shA a
a) (Array shB b -> ArrayMatrix shB b
forall shape a. Array shape a -> Matrix (Array shape) a
Array Array shB b
b)
unliftRow ::
MatrixShape.Order ->
(General () height0 a -> General () height1 b) ->
Vector height0 a -> Vector height1 b
unliftRow :: Order
-> (General () height0 a -> General () height1 b)
-> Vector height0 a
-> Vector height1 b
unliftRow Order
order = Order
-> (General () height0 a -> General () height1 b)
-> Vector height0 a
-> Vector height1 b
forall height0 a height1 b.
Order
-> (General () height0 a -> General () height1 b)
-> Vector height0 a
-> Vector height1 b
Basic.unliftRow Order
order ((General () height0 a -> General () height1 b)
-> Vector height0 a -> Vector height1 b)
-> ((General () height0 a -> General () height1 b)
-> General () height0 a -> General () height1 b)
-> (General () height0 a -> General () height1 b)
-> Vector height0 a
-> Vector height1 b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (General () height0 a -> General () height1 b)
-> General () height0 a -> General () height1 b
forall shA a shB b.
(ArrayMatrix shA a -> ArrayMatrix shB b)
-> Array shA a -> Array shB b
unlift1
unliftColumn ::
MatrixShape.Order ->
(General height0 () a -> General height1 () b) ->
Vector height0 a -> Vector height1 b
unliftColumn :: Order
-> (General height0 () a -> General height1 () b)
-> Vector height0 a
-> Vector height1 b
unliftColumn Order
order = Order
-> (General height0 () a -> General height1 () b)
-> Vector height0 a
-> Vector height1 b
forall height0 a height1 b.
Order
-> (General height0 () a -> General height1 () b)
-> Vector height0 a
-> Vector height1 b
Basic.unliftColumn Order
order ((General height0 () a -> General height1 () b)
-> Vector height0 a -> Vector height1 b)
-> ((General height0 () a -> General height1 () b)
-> General height0 () a -> General height1 () b)
-> (General height0 () a -> General height1 () b)
-> Vector height0 a
-> Vector height1 b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (General height0 () a -> General height1 () b)
-> General height0 () a -> General height1 () b
forall shA a shB b.
(ArrayMatrix shA a -> ArrayMatrix shB b)
-> Array shA a -> Array shB b
unlift1
instance (FormatArray sh) => Type.FormatMatrix (Array sh) where
formatMatrix :: String -> Matrix (Array sh) a -> out
formatMatrix String
fmt (Array a) = String -> Array sh a -> out
forall sh a out.
(FormatArray sh, Floating a, Output out) =>
String -> Array sh a -> out
formatArray String
fmt Array sh a
a
instance (Multiply.MultiplySame sh) => Type.MultiplySame (Array sh) where
multiplySame :: Matrix (Array sh) a -> Matrix (Array sh) a -> Matrix (Array sh) a
multiplySame = (Array sh a -> Array sh a -> Array sh a)
-> Matrix (Array sh) a
-> Matrix (Array sh) a
-> Matrix (Array sh) a
forall shA a shB b shC c.
(Array shA a -> Array shB b -> Array shC c)
-> ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c
lift2 Array sh a -> Array sh a -> Array sh a
forall shape a.
(MultiplySame shape, Floating a) =>
Array shape a -> Array shape a -> Array shape a
Multiply.same
instance
(Plain.SquareShape sh, Box.WidthOf sh ~ width, Shape.Static width) =>
Type.StaticIdentity (Array sh) where
staticIdentity :: Matrix (Array sh) a
staticIdentity =
Array sh a -> Matrix (Array sh) a
forall shape a. Array shape a -> Matrix (Array shape) a
lift0 (Array sh a -> Matrix (Array sh) a)
-> Array sh a -> Matrix (Array sh) a
forall a b. (a -> b) -> a -> b
$ Order -> width -> Array sh a
forall shape sh a.
(SquareShape shape, HeightOf shape ~ sh, Floating a) =>
Order -> sh -> Array shape a
Plain.identityOrder Order
MatrixShape.RowMajor width
forall sh. Static sh => sh
Shape.static
zero ::
(Plain.Homogeneous shape, Class.Floating a) => shape -> ArrayMatrix shape a
zero :: shape -> ArrayMatrix shape a
zero = Array shape a -> ArrayMatrix shape a
forall shape a. Array shape a -> Matrix (Array shape) a
lift0 (Array shape a -> ArrayMatrix shape a)
-> (shape -> Array shape a) -> shape -> ArrayMatrix shape a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. shape -> Array shape a
forall shape a.
(Homogeneous shape, Floating a) =>
shape -> Array shape a
Plain.zero
negate ::
(Plain.Homogeneous shape, Class.Floating a) =>
ArrayMatrix shape a -> ArrayMatrix shape a
negate :: ArrayMatrix shape a -> ArrayMatrix shape a
negate = (Array shape a -> Array shape a)
-> ArrayMatrix shape a -> ArrayMatrix shape a
forall shA a shB b.
(Array shA a -> Array shB b)
-> ArrayMatrix shA a -> ArrayMatrix shB b
lift1 Array shape a -> Array shape a
forall shape a.
(Homogeneous shape, Floating a) =>
Array shape a -> Array shape a
Plain.negate
scaleReal ::
(Plain.Homogeneous shape, Class.Floating a) =>
RealOf a -> ArrayMatrix shape a -> ArrayMatrix shape a
scaleReal :: RealOf a -> ArrayMatrix shape a -> ArrayMatrix shape a
scaleReal = (Array shape a -> Array shape a)
-> ArrayMatrix shape a -> ArrayMatrix shape a
forall shA a shB b.
(Array shA a -> Array shB b)
-> ArrayMatrix shA a -> ArrayMatrix shB b
lift1 ((Array shape a -> Array shape a)
-> ArrayMatrix shape a -> ArrayMatrix shape a)
-> (RealOf a -> Array shape a -> Array shape a)
-> RealOf a
-> ArrayMatrix shape a
-> ArrayMatrix shape a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RealOf a -> Array shape a -> Array shape a
forall shape a.
(Homogeneous shape, Floating a) =>
RealOf a -> Array shape a -> Array shape a
Plain.scaleReal
newtype ScaleReal f a = ScaleReal {ScaleReal f a -> a -> f a -> f a
getScaleReal :: a -> f a -> f a}
scaleRealReal ::
(Plain.Homogeneous shape, Class.Real a) =>
a -> ArrayMatrix shape a -> ArrayMatrix shape a
scaleRealReal :: a -> ArrayMatrix shape a -> ArrayMatrix shape a
scaleRealReal =
ScaleReal (Matrix (Array shape)) a
-> a -> ArrayMatrix shape a -> ArrayMatrix shape a
forall (f :: * -> *) a. ScaleReal f a -> a -> f a -> f a
getScaleReal (ScaleReal (Matrix (Array shape)) a
-> a -> ArrayMatrix shape a -> ArrayMatrix shape a)
-> ScaleReal (Matrix (Array shape)) a
-> a
-> ArrayMatrix shape a
-> ArrayMatrix shape a
forall a b. (a -> b) -> a -> b
$ ScaleReal (Matrix (Array shape)) Float
-> ScaleReal (Matrix (Array shape)) Double
-> ScaleReal (Matrix (Array shape)) a
forall a (f :: * -> *). Real a => f Float -> f Double -> f a
Class.switchReal ((Float -> Matrix (Array shape) Float -> Matrix (Array shape) Float)
-> ScaleReal (Matrix (Array shape)) Float
forall (f :: * -> *) a. (a -> f a -> f a) -> ScaleReal f a
ScaleReal Float -> Matrix (Array shape) Float -> Matrix (Array shape) Float
forall shape a.
(Homogeneous shape, Floating a) =>
RealOf a -> ArrayMatrix shape a -> ArrayMatrix shape a
scaleReal) ((Double
-> Matrix (Array shape) Double -> Matrix (Array shape) Double)
-> ScaleReal (Matrix (Array shape)) Double
forall (f :: * -> *) a. (a -> f a -> f a) -> ScaleReal f a
ScaleReal Double
-> Matrix (Array shape) Double -> Matrix (Array shape) Double
forall shape a.
(Homogeneous shape, Floating a) =>
RealOf a -> ArrayMatrix shape a -> ArrayMatrix shape a
scaleReal)
scale, (.*#) ::
(Multiply.Scale shape, Class.Floating a) =>
a -> ArrayMatrix shape a -> ArrayMatrix shape a
scale :: a -> ArrayMatrix shape a -> ArrayMatrix shape a
scale = (Array shape a -> Array shape a)
-> ArrayMatrix shape a -> ArrayMatrix shape a
forall shA a shB b.
(Array shA a -> Array shB b)
-> ArrayMatrix shA a -> ArrayMatrix shB b
lift1 ((Array shape a -> Array shape a)
-> ArrayMatrix shape a -> ArrayMatrix shape a)
-> (a -> Array shape a -> Array shape a)
-> a
-> ArrayMatrix shape a
-> ArrayMatrix shape a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Array shape a -> Array shape a
forall shape a.
(Scale shape, Floating a) =>
a -> Array shape a -> Array shape a
Multiply.scale
.*# :: a -> ArrayMatrix shape a -> ArrayMatrix shape a
(.*#) = a -> ArrayMatrix shape a -> ArrayMatrix shape a
forall shape a.
(Scale shape, Floating a) =>
a -> ArrayMatrix shape a -> ArrayMatrix shape a
scale
infixl 7 .*#
forceOrder ::
(Plain.ShapeOrder shape, Class.Floating a) =>
MatrixShape.Order -> ArrayMatrix shape a -> ArrayMatrix shape a
forceOrder :: Order -> ArrayMatrix shape a -> ArrayMatrix shape a
forceOrder = (Array shape a -> Array shape a)
-> ArrayMatrix shape a -> ArrayMatrix shape a
forall shA a shB b.
(Array shA a -> Array shB b)
-> ArrayMatrix shA a -> ArrayMatrix shB b
lift1 ((Array shape a -> Array shape a)
-> ArrayMatrix shape a -> ArrayMatrix shape a)
-> (Order -> Array shape a -> Array shape a)
-> Order
-> ArrayMatrix shape a
-> ArrayMatrix shape a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Order -> Array shape a -> Array shape a
forall shape a.
(ShapeOrder shape, Floating a) =>
Order -> Array shape a -> Array shape a
Plain.forceOrder
adaptOrder ::
(Plain.ShapeOrder shape, Class.Floating a) =>
ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
adaptOrder :: ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
adaptOrder = (Array shape a -> Array shape a -> Array shape a)
-> ArrayMatrix shape a
-> ArrayMatrix shape a
-> ArrayMatrix shape a
forall shA a shB b shC c.
(Array shA a -> Array shB b -> Array shC c)
-> ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c
lift2 Array shape a -> Array shape a -> Array shape a
forall shape a.
(ShapeOrder shape, Floating a) =>
Array shape a -> Array shape a -> Array shape a
Plain.adaptOrder
infixl 6 #+#, #-#, `add`, `sub`
add, sub, (#+#), (#-#) ::
(Plain.Additive shape, Class.Floating a) =>
ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
add :: ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
add = (Array shape a -> Array shape a -> Array shape a)
-> ArrayMatrix shape a
-> ArrayMatrix shape a
-> ArrayMatrix shape a
forall shA a shB b shC c.
(Array shA a -> Array shB b -> Array shC c)
-> ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c
lift2 Array shape a -> Array shape a -> Array shape a
forall shape a.
(Additive shape, Floating a) =>
Array shape a -> Array shape a -> Array shape a
Plain.add
sub :: ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
sub = (Array shape a -> Array shape a -> Array shape a)
-> ArrayMatrix shape a
-> ArrayMatrix shape a
-> ArrayMatrix shape a
forall shA a shB b shC c.
(Array shA a -> Array shB b -> Array shC c)
-> ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c
lift2 Array shape a -> Array shape a -> Array shape a
forall shape a.
(Additive shape, Floating a) =>
Array shape a -> Array shape a -> Array shape a
Plain.sub
#+# :: ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
(#+#) = ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
forall shape a.
(Additive shape, Floating a) =>
ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
add
#-# :: ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
(#-#) = ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
forall shape a.
(Additive shape, Floating a) =>
ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
sub