{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving, GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DataKinds #-}
module OAlg.Entity.Matrix.Definition
(
Matrix(..), rows, cols, mtxxs
, mtxRowCol, mtxColRow
, mtxMap
, mtxGroupRow, mtxGroupDim
, mtxJoin, mtxJoinDim
, matrix, matrixTtl, matrixBlc
, diagonal, diagonal'
, coMatrix, coMatrixInv, mtxFromOpOp
, isoCoMatrixDst
, XStandardOrientationMatrix(..)
, xMatrix, xMatrixTtl
, xodZ, xodZZ
) where
import Control.Monad
import Data.Typeable
import Data.Foldable
import Data.List (map,repeat,zip,span)
import OAlg.Prelude
import OAlg.Category.Path as P
import OAlg.Data.Singleton
import OAlg.Data.Canonical
import OAlg.Data.Constructable
import OAlg.Structure.Exception
import OAlg.Structure.Oriented
import OAlg.Structure.Multiplicative
import OAlg.Structure.Fibred
import OAlg.Structure.Additive
import OAlg.Structure.Vectorial
import OAlg.Structure.Distributive
import OAlg.Structure.Algebraic
import OAlg.Structure.Exponential
import OAlg.Structure.Number
import OAlg.Entity.Product
import OAlg.Entity.Sequence hiding (span)
import OAlg.Hom.Oriented
import OAlg.Hom.Multiplicative
import OAlg.Hom.Fibred
import OAlg.Hom.Additive
import OAlg.Hom.Distributive
import OAlg.Hom.Definition
import OAlg.Entity.Matrix.Dim
import OAlg.Entity.Matrix.Entries
data Matrix x = Matrix (Dim' x) (Dim' x) (Entries N N x)
rows :: Matrix x -> Dim' x
rows :: forall x. Matrix x -> Dim' x
rows (Matrix Dim' x
r Dim' x
_ Entries N N x
_) = Dim' x
r
cols :: Matrix x -> Dim' x
cols :: forall x. Matrix x -> Dim' x
cols (Matrix Dim' x
_ Dim' x
c Entries N N x
_) = Dim' x
c
mtxxs :: Matrix x -> Entries N N x
mtxxs :: forall x. Matrix x -> Entries N N x
mtxxs (Matrix Dim' x
_ Dim' x
_ Entries N N x
xs) = Entries N N x
xs
deriving instance Oriented x => Show (Matrix x)
deriving instance Oriented x => Eq (Matrix x)
deriving instance (Oriented x, Ord x, OrdPoint x) => Ord (Matrix x)
instance (Additive x, FibredOriented x) => Validable (Matrix x) where
valid :: Matrix x -> Statement
valid m :: Matrix x
m@(Matrix Dim x (Point x)
rw Dim x (Point x)
cl (Entries (PSequence [(x, (N, N))]
xijs))) = String -> Label
Label (forall a. Show a => a -> String
show forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall a. Typeable a => a -> TypeRep
typeOf Matrix x
m) Label -> Statement -> Statement
:<=>:
[Statement] -> Statement
And [ String -> Label
Label String
"1" Label -> Statement -> Statement
:<=>: String -> Label
Label String
"rw" Label -> Statement -> Statement
:<=>: forall a. Validable a => a -> Statement
valid Dim x (Point x)
rw
, String -> Label
Label String
"1" Label -> Statement -> Statement
:<=>: String -> Label
Label String
"cl" Label -> Statement -> Statement
:<=>:forall a. Validable a => a -> Statement
valid Dim x (Point x)
cl
, case [(x, (N, N))]
xijs of
[] -> Statement
SValid
((x, (N, N))
xij:[(x, (N, N))]
xijs) -> forall {a} {s :: * -> *} {i} {s :: * -> *} {i}.
(Additive a, Oriented a, Sequence s i (Point a),
Sequence s i (Point a), Show i, Show i, Validable i,
Validable i) =>
s (Point a)
-> s (Point a) -> (a, (i, i)) -> [(a, (i, i))] -> Statement
vld Dim x (Point x)
rw Dim x (Point x)
cl (x, (N, N))
xij [(x, (N, N))]
xijs
] where
vld :: s (Point a)
-> s (Point a) -> (a, (i, i)) -> [(a, (i, i))] -> Statement
vld s (Point a)
rw s (Point a)
cl (a, (i, i))
xij [] = forall {q} {s :: * -> *} {i} {s :: * -> *} {i}.
(Additive q, Oriented q, Sequence s i (Point q),
Sequence s i (Point q), Show i, Show i, Validable i,
Validable i) =>
s (Point q) -> s (Point q) -> (q, (i, i)) -> Statement
vldEntries s (Point a)
rw s (Point a)
cl (a, (i, i))
xij
vld s (Point a)
rw s (Point a)
cl (a, (i, i))
xij ((a, (i, i))
xlk:[(a, (i, i))]
xijs) = [Statement] -> Statement
And [ forall {q} {s :: * -> *} {i} {s :: * -> *} {i}.
(Additive q, Oriented q, Sequence s i (Point q),
Sequence s i (Point q), Show i, Show i, Validable i,
Validable i) =>
s (Point q) -> s (Point q) -> (q, (i, i)) -> Statement
vldEntries s (Point a)
rw s (Point a)
cl (a, (i, i))
xij
, String -> Label
Label String
"2" Label -> Statement -> Statement
:<=>: let ij :: (i, i)
ij = forall a b. (a, b) -> b
snd (a, (i, i))
xij
lk :: (i, i)
lk = forall a b. (a, b) -> b
snd (a, (i, i))
xlk
in ((i, i)
ij forall a. Ord a => a -> a -> Bool
< (i, i)
lk) Bool -> Message -> Statement
:?>[Parameter] -> Message
Params [String
"(ij,kl)"String -> String -> Parameter
:=forall a. Show a => a -> String
show ((i, i)
ij,(i, i)
lk)]
, s (Point a)
-> s (Point a) -> (a, (i, i)) -> [(a, (i, i))] -> Statement
vld s (Point a)
rw s (Point a)
cl (a, (i, i))
xlk [(a, (i, i))]
xijs
]
vldEntries :: s (Point q) -> s (Point q) -> (q, (i, i)) -> Statement
vldEntries s (Point q)
rw s (Point q)
cl xij :: (q, (i, i))
xij@(q
x,(i
i,i
j))
= [Statement] -> Statement
And [ String -> Label
Label String
"2" Label -> Statement -> Statement
:<=>: forall a. Validable a => a -> Statement
valid (q, (i, i))
xij
, String -> Label
Label String
"3.1" Label -> Statement -> Statement
:<=>: (forall b. Boolean b => b -> b
not (forall a. Additive a => a -> Bool
isZero q
x)) Bool -> Message -> Statement
:?> [Parameter] -> Message
Params [String
"xij"String -> String -> Parameter
:=forall a. Show a => a -> String
show (q, (i, i))
xij]
, String -> Label
Label String
"3.2" Label -> Statement -> Statement
:<=>: (forall q. Oriented q => q -> Orientation (Point q)
orientation q
x forall a. Eq a => a -> a -> Bool
== (s (Point q)
cl forall (s :: * -> *) i x. Sequence s i x => s x -> i -> x
? i
j) forall p. p -> p -> Orientation p
:> (s (Point q)
rw forall (s :: * -> *) i x. Sequence s i x => s x -> i -> x
? i
i))
Bool -> Message -> Statement
:?> [Parameter] -> Message
Params [String
"xij"String -> String -> Parameter
:=forall a. Show a => a -> String
show (q, (i, i))
xij]
]
instance (Additive x, FibredOriented x) => Entity (Matrix x)
mtxColRow :: Matrix x -> Col N (Row N x)
mtxColRow :: forall x. Matrix x -> Col N (Row N x)
mtxColRow (Matrix Dim' x
_ Dim' x
_ Entries N N x
xs) = forall i j x. Eq i => Entries i j x -> Col i (Row j x)
etscr Entries N N x
xs
mtxRowCol :: Matrix x -> Row N (Col N x)
mtxRowCol :: forall x. Matrix x -> Row N (Col N x)
mtxRowCol (Matrix Dim' x
_ Dim' x
_ Entries N N x
xs) = forall i j x. (Ord i, Ord j) => Entries i j x -> Row j (Col i x)
etsrc Entries N N x
xs
instance (Additive x, FibredOriented x) => Oriented (Matrix x) where
type Point (Matrix x) = Dim' x
orientation :: Matrix x -> Orientation (Point (Matrix x))
orientation (Matrix Dim x (Point x)
rw Dim x (Point x)
cl Entries N N x
_) = Dim x (Point x)
cl forall p. p -> p -> Orientation p
:> Dim x (Point x)
rw
instance (Additive x, FibredOriented x) => Fibred (Matrix x) where
type Root (Matrix x) = Orientation (Dim' x)
instance (Additive x, FibredOriented x) => FibredOriented (Matrix x)
instance (Additive x, FibredOriented x) => Additive (Matrix x) where
zero :: Root (Matrix x) -> Matrix x
zero (Dim x (Point x)
cl:>Dim x (Point x)
rw) = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim x (Point x)
rw Dim x (Point x)
cl forall i j x. Entries i j x
etsEmpty
Matrix Dim x (Point x)
rw Dim x (Point x)
cl Entries N N x
xs + :: Matrix x -> Matrix x -> Matrix x
+ Matrix Dim x (Point x)
rw' Dim x (Point x)
cl' Entries N N x
ys
| Dim x (Point x)
rw forall a. Eq a => a -> a -> Bool
== Dim x (Point x)
rw' forall b. Boolean b => b -> b -> b
&& Dim x (Point x)
cl forall a. Eq a => a -> a -> Bool
== Dim x (Point x)
cl' = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim x (Point x)
rw Dim x (Point x)
cl (forall x i j.
(Additive x, Ord i, Ord j) =>
Entries i j x -> Entries i j x -> Entries i j x
etsAdd Entries N N x
xs Entries N N x
ys)
| Bool
otherwise = forall a e. Exception e => e -> a
throw forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ ArithmeticException
NotAddable
ntimes :: N -> Matrix x -> Matrix x
ntimes N
n (Matrix Dim x (Point x)
rw Dim x (Point x)
cl Entries N N x
xs)
= forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim x (Point x)
rw Dim x (Point x)
cl (forall x i j. Additive x => Entries i j x -> Entries i j x
etsElimZeros forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Additive a => N -> a -> a
ntimes N
n) Entries N N x
xs)
instance (Abelian x, FibredOriented x) => Abelian (Matrix x) where
negate :: Matrix x -> Matrix x
negate (Matrix Dim' x
rw Dim' x
cl Entries N N x
xs) = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim' x
rw Dim' x
cl (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Abelian a => a -> a
negate Entries N N x
xs)
ztimes :: Z -> Matrix x -> Matrix x
ztimes Z
z (Matrix Dim' x
rw Dim' x
cl Entries N N x
xs)
= forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim' x
rw Dim' x
cl (forall x i j. Additive x => Entries i j x -> Entries i j x
etsElimZeros forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Abelian a => Z -> a -> a
ztimes Z
z) Entries N N x
xs)
instance (Vectorial x, FibredOriented x) => Vectorial (Matrix x) where
type Scalar (Matrix x) = Scalar x
Scalar (Matrix x)
r ! :: Scalar (Matrix x) -> Matrix x -> Matrix x
! Matrix Dim' x
rw Dim' x
cl Entries N N x
xs = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim' x
rw Dim' x
cl forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall x i j. Additive x => Entries i j x -> Entries i j x
etsElimZeros forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Scalar (Matrix x)
rforall v. Vectorial v => Scalar v -> v -> v
!) Entries N N x
xs
instance Distributive x => Multiplicative (Matrix x) where
one :: Point (Matrix x) -> Matrix x
one Point (Matrix x)
d = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Point (Matrix x)
d Point (Matrix x)
d Entries N N x
ones where
ones :: Entries N N x
ones = forall x i j. Additive x => Entries i j x -> Entries i j x
etsElimZeros forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall i j x. PSequence (i, j) x -> Entries i j x
Entries forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall i x. [(x, i)] -> PSequence i x
PSequence forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\(Point x
p,N
i) -> (forall c. Multiplicative c => Point c -> c
one Point x
p,(N
i,N
i))) forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall p x. (p ~ Point x) => Dim x p -> [(p, N)]
dimxs Point (Matrix x)
d
Matrix Dim x (Point x)
i Dim x (Point x)
k Entries N N x
xs * :: Matrix x -> Matrix x -> Matrix x
* Matrix Dim x (Point x)
k' Dim x (Point x)
j Entries N N x
ys
| Dim x (Point x)
k forall a. Eq a => a -> a -> Bool
== Dim x (Point x)
k' = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim x (Point x)
i Dim x (Point x)
j (forall i j x. Col i (Row j x) -> Entries i j x
crets forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall x k i j.
(Distributive x, Ord k) =>
Col i (Row k x) -> Row j (Col k x) -> Col i (Row j x)
etsMlt (forall i j x. Eq i => Entries i j x -> Col i (Row j x)
etscr Entries N N x
xs) (forall i j x. (Ord i, Ord j) => Entries i j x -> Row j (Col i x)
etsrc Entries N N x
ys))
| Bool
otherwise = forall a e. Exception e => e -> a
throw ArithmeticException
NotMultiplicable
npower :: Matrix x -> N -> Matrix x
npower Matrix x
m N
1 = Matrix x
m
npower Matrix x
m N
_ | forall b. Boolean b => b -> b
not (forall q. Oriented q => q -> Bool
isEndo Matrix x
m) = forall a e. Exception e => e -> a
throw ArithmeticException
NotExponential
npower Matrix x
m N
0 = forall c. Multiplicative c => Point c -> c
one (forall x. Matrix x -> Dim' x
rows Matrix x
m)
npower (Matrix Dim x (Point x)
r Dim x (Point x)
_ Entries N N x
xs) N
n = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim x (Point x)
r Dim x (Point x)
r (forall i j x. Col i (Row j x) -> Entries i j x
crets Col N (Row N x)
xs') where
xs' :: Col N (Row N x)
xs' = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl forall x k i j.
(Distributive x, Ord k) =>
Col i (Row k x) -> Row j (Col k x) -> Col i (Row j x)
etsMlt (forall i j x. Eq i => Entries i j x -> Col i (Row j x)
etscr Entries N N x
xs) forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall a. N -> [a] -> [a]
takeN (forall a. Enum a => a -> a
pred N
n) forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall a. a -> [a]
repeat forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ (forall i j x. (Ord i, Ord j) => Entries i j x -> Row j (Col i x)
etsrc Entries N N x
xs)
instance Distributive x => Distributive (Matrix x)
instance Algebraic x => Algebraic (Matrix x)
instance (Distributive x, TransposableDistributive x) => Transposable (Matrix x) where
transpose :: Matrix x -> Matrix x
transpose (Matrix Dim' x
r Dim' x
c Entries N N x
xs) = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim' x
c Dim' x
r (forall x. Transposable x => x -> x
transpose Entries N N x
xs)
instance (Distributive x, TransposableDistributive x) => TransposableOriented (Matrix x)
instance (Distributive x, TransposableDistributive x)
=> TransposableMultiplicative (Matrix x)
instance (Distributive x, TransposableDistributive x) => TransposableDistributive (Matrix x)
matrix :: (Additive x, p ~ Point x)
=> Dim x p -> Dim x p -> [(x,N,N)] -> Matrix x
matrix :: forall x p.
(Additive x, p ~ Point x) =>
Dim x p -> Dim x p -> [(x, N, N)] -> Matrix x
matrix Dim x p
rw Dim x p
cl [(x, N, N)]
xijs = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim x p
rw Dim x p
cl Entries N N x
xijs' where
xijs' :: Entries N N x
xijs' = forall x i j. Additive x => Entries i j x -> Entries i j x
etsElimZeros forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall i j x. PSequence (i, j) x -> Entries i j x
Entries forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall i x. Ord i => (x -> x -> x) -> [(x, i)] -> PSequence i x
psequence forall a. Additive a => a -> a -> a
(+) forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\(x
x,N
i,N
j) -> (x
x,(N
i,N
j))) [(x, N, N)]
xijs
matrixTtl :: (Additive x, FibredOriented x, Total x) => N -> N -> [(x,N,N)] -> Matrix x
matrixTtl :: forall x.
(Additive x, FibredOriented x, Total x) =>
N -> N -> [(x, N, N)] -> Matrix x
matrixTtl N
rws N
cls = forall x p.
(Additive x, p ~ Point x) =>
Dim x p -> Dim x p -> [(x, N, N)] -> Matrix x
matrix Dim x (Point x)
rw Dim x (Point x)
cl where
rw :: Dim x (Point x)
rw = forall p x. (Entity p, p ~ Point x) => p -> Dim x p
dim forall s. Singleton s => s
unit forall f. Exponential f => f -> Exponent f -> f
^ N
rws
cl :: Dim x (Point x)
cl = forall p x. (Entity p, p ~ Point x) => p -> Dim x p
dim forall s. Singleton s => s
unit forall f. Exponential f => f -> Exponent f -> f
^ N
cls
matrixBlc :: (Additive x, FibredOriented x)
=> [Dim' x] -> [Dim' x] -> [(Matrix x,N,N)] -> Matrix (Matrix x)
matrixBlc :: forall x.
(Additive x, FibredOriented x) =>
[Dim' x] -> [Dim' x] -> [(Matrix x, N, N)] -> Matrix (Matrix x)
matrixBlc [Dim x (Point x)]
rws [Dim x (Point x)]
cls = forall x p.
(Additive x, p ~ Point x) =>
Dim x p -> Dim x p -> [(x, N, N)] -> Matrix x
matrix Dim (Matrix x) (Dim x (Point x))
rw Dim (Matrix x) (Dim x (Point x))
cl where
rw :: Dim (Matrix x) (Dim x (Point x))
rw = forall p x. (Entity p, p ~ Point x) => [p] -> Dim x p
productDim [Dim x (Point x)]
rws
cl :: Dim (Matrix x) (Dim x (Point x))
cl = forall p x. (Entity p, p ~ Point x) => [p] -> Dim x p
productDim [Dim x (Point x)]
cls
diagonal' :: Additive x => N -> Dim' x -> Dim' x -> [x] -> Matrix x
diagonal' :: forall x. Additive x => N -> Dim' x -> Dim' x -> [x] -> Matrix x
diagonal' N
r Dim' x
n Dim' x
m [x]
xs = forall x p.
(Additive x, p ~ Point x) =>
Dim x p -> Dim x p -> [(x, N, N)] -> Matrix x
matrix Dim' x
n Dim' x
m [(x, N, N)]
xs' where
xs' :: [(x, N, N)]
xs' = forall a b. (a -> b) -> [a] -> [b]
map (\(x
x,N
i) -> (x
x,N
i,N
i)) ([x]
xs forall a b. [a] -> [b] -> [(a, b)]
`zip` [N
r..])
diagonal :: Additive x => Dim' x -> Dim' x -> [x] -> Matrix x
diagonal :: forall x. Additive x => Dim' x -> Dim' x -> [x] -> Matrix x
diagonal = forall x. Additive x => N -> Dim' x -> Dim' x -> [x] -> Matrix x
diagonal' N
0
mtxJoinDim :: Oriented x => Dim' (Matrix x) -> Dim' x
mtxJoinDim :: forall x. Oriented x => Dim' (Matrix x) -> Dim' x
mtxJoinDim (Dim CSequence (Point (Matrix x))
dm) = forall x. CSequence (Point x) -> Dim x (Point x)
Dim
forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall x. Constructable x => Form x -> x
make
forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall y x r.
Singleton (Point y) =>
(x -> ProductForm r y) -> ProductForm r x -> ProductForm r y
prfMapTotal forall x. U (ProductSymbol x) -> ProductForm N (U x)
f
forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall y x r.
Singleton (Point y) =>
(x -> ProductForm r y) -> ProductForm r x -> ProductForm r y
prfMapTotal forall x. U (Dim' x) -> ProductForm N (U (ProductSymbol (Point x)))
g
forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall x. Exposable x => x -> Form x
form CSequence (Point (Matrix x))
dm
where f :: U (ProductSymbol x) -> ProductForm N (U x)
f :: forall x. U (ProductSymbol x) -> ProductForm N (U x)
f (U ProductSymbol x
xs) = forall x. Exposable x => x -> Form x
form ProductSymbol x
xs
g :: U (Dim' x) -> ProductForm N (U (ProductSymbol (Point x)))
g :: forall x. U (Dim' x) -> ProductForm N (U (ProductSymbol (Point x)))
g (U (Dim CSequence (Point x)
xs)) = forall r a. a -> ProductForm r a
P forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall x. x -> U x
U CSequence (Point x)
xs
mtxJoin :: Oriented x => Matrix (Matrix x) -> Matrix x
mtxJoin :: forall x. Oriented x => Matrix (Matrix x) -> Matrix x
mtxJoin (Matrix Dim' (Matrix x)
rw Dim' (Matrix x)
cl Entries N N (Matrix x)
ets) = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim x (Point x)
rw' Dim x (Point x)
cl' Entries N N x
ets' where
rw' :: Dim x (Point x)
rw' = forall x. Oriented x => Dim' (Matrix x) -> Dim' x
mtxJoinDim Dim' (Matrix x)
rw
cl' :: Dim x (Point x)
cl' = forall x. Oriented x => Dim' (Matrix x) -> Dim' x
mtxJoinDim Dim' (Matrix x)
cl
ets' :: Entries N N x
ets' = forall i j x.
(i ~ N, j ~ N) =>
ProductSymbol i
-> ProductSymbol j -> Entries i j (Entries i j x) -> Entries i j x
etsJoin ProductSymbol N
di ProductSymbol N
dj forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall x. Matrix x -> Entries N N x
mtxxs Entries N N (Matrix x)
ets
di :: ProductSymbol N
di = forall y x.
Entity y =>
(x -> y) -> ProductSymbol x -> ProductSymbol y
psyMap forall x. LengthN x => x -> N
lengthN forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall x p. Dim x p -> ProductSymbol p
fromDim Dim' (Matrix x)
rw
dj :: ProductSymbol N
dj = forall y x.
Entity y =>
(x -> y) -> ProductSymbol x -> ProductSymbol y
psyMap forall x. LengthN x => x -> N
lengthN forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall x p. Dim x p -> ProductSymbol p
fromDim Dim' (Matrix x)
cl
mtxGroupDim :: Distributive x => Dim' x -> Dim' (Matrix x)
mtxGroupDim :: forall x. Distributive x => Dim' x -> Dim' (Matrix x)
mtxGroupDim Dim x (Point x)
d = forall p x. (Entity p, p ~ Point x) => [p] -> Dim x p
productDim forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\(Point x
p,N
n) -> forall p x. (Entity p, p ~ Point x) => p -> Dim x p
dim Point x
p forall f. Exponential f => f -> Exponent f -> f
^ N
n) forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall r a. Word r a -> [(a, r)]
fromWord forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall p x. (Entity p, p ~ Point x) => Dim x p -> Word N p
dimwrd Dim x (Point x)
d
mtxGroupRow :: Distributive x => Matrix x -> Matrix (Matrix x)
mtxGroupRow :: forall x. Distributive x => Matrix x -> Matrix (Matrix x)
mtxGroupRow (Matrix Dim x (Point x)
r Dim x (Point x)
c Entries N N x
xs) = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim' (Matrix x)
r' Dim (Matrix x) (Dim x (Point x))
c' Entries N N (Matrix x)
xs' where
r' :: Dim' (Matrix x)
r' = forall x. Distributive x => Dim' x -> Dim' (Matrix x)
mtxGroupDim Dim x (Point x)
r
c' :: Dim (Matrix x) (Dim x (Point x))
c' = forall p x. (Entity p, p ~ Point x) => p -> Dim x p
dim Dim x (Point x)
c
wrd :: [(Point x, N)]
wrd = forall r a. Word r a -> [(a, r)]
fromWord (forall p x. (Entity p, p ~ Point x) => Dim x p -> Word N p
dimwrd Dim x (Point x)
r)
xs' :: Entries N N (Matrix x)
xs' = forall i j x. PSequence (i, j) x -> Entries i j x
Entries forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall i x. [(x, i)] -> PSequence i x
PSequence forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall x.
Oriented x =>
Dim' x
-> N
-> [((Point x, N), N)]
-> [(Row N x, N)]
-> [(Matrix x, (N, N))]
split Dim x (Point x)
c N
0 ([(Point x, N)]
wrd forall a b. [a] -> [b] -> [(a, b)]
`zip` [N
0..]) (forall i x. Col i x -> [(x, i)]
colxs forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall i j x. Eq i => Entries i j x -> Col i (Row j x)
etscr Entries N N x
xs)
split :: Oriented x
=> Dim' x -> N -> [((Point x,N),N)] -> [(Row N x,N)]
-> [(Matrix x,(N,N))]
split :: forall x.
Oriented x =>
Dim' x
-> N
-> [((Point x, N), N)]
-> [(Row N x, N)]
-> [(Matrix x, (N, N))]
split Dim x (Point x)
_ N
_ [((Point x, N), N)]
_ [] = []
split Dim x (Point x)
c N
i [] [(Row N x, N)]
rws = forall a. HasCallStack => String -> a
error forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall a. Show a => a -> String
show (Dim x (Point x)
c,N
i,[(Row N x, N)]
rws)
split Dim x (Point x)
c N
i (((Point x
d,N
l),N
i''):[((Point x, N), N)]
ds') rws :: [(Row N x, N)]
rws@((Row N x
_,N
i'):[(Row N x, N)]
_)
| N
i forall a. Ord a => a -> a -> Bool
<= N
i' forall b. Boolean b => b -> b -> b
&& N
i' forall a. Ord a => a -> a -> Bool
< N
il = (forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim x (Point x)
d' Dim x (Point x)
c (forall i j x. Col i (Row j x) -> Entries i j x
crets Col N (Row N x)
xs),(N
i'',N
0)) forall a. a -> [a] -> [a]
: forall x.
Oriented x =>
Dim' x
-> N
-> [((Point x, N), N)]
-> [(Row N x, N)]
-> [(Matrix x, (N, N))]
split Dim x (Point x)
c N
il [((Point x, N), N)]
ds' [(Row N x, N)]
rws'
| Bool
otherwise = forall x.
Oriented x =>
Dim' x
-> N
-> [((Point x, N), N)]
-> [(Row N x, N)]
-> [(Matrix x, (N, N))]
split Dim x (Point x)
c N
il [((Point x, N), N)]
ds' [(Row N x, N)]
rws
where il :: N
il = N
iforall a. Additive a => a -> a -> a
+N
l
d' :: Dim x (Point x)
d' = forall p x. (Entity p, p ~ Point x) => p -> Dim x p
dim Point x
d forall f. Exponential f => f -> Exponent f -> f
^ N
l
([(Row N x, N)]
xs',[(Row N x, N)]
rws') = forall a. (a -> Bool) -> [a] -> ([a], [a])
span ((forall a. Ord a => a -> a -> Bool
<N
il) forall (c :: * -> * -> *) y z x.
Category c =>
c y z -> c x y -> c x z
. forall a b. (a, b) -> b
snd) [(Row N x, N)]
rws
xs :: Col N (Row N x)
xs = forall i x. PSequence i x -> Col i x
Col forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall i x. [(x, i)] -> PSequence i x
PSequence forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\(Row N x
rw,N
i') -> (Row N x
rw,N
i'N -> N -> N
>-N
i)) [(Row N x, N)]
xs'
mtxMapStruct :: Hom Dst h => Struct Dst y -> h x y -> Matrix x -> Matrix y
mtxMapStruct :: forall (h :: * -> * -> *) y x.
Hom Dst h =>
Struct Dst y -> h x y -> Matrix x -> Matrix y
mtxMapStruct Struct Dst y
Struct h x y
h (Matrix Dim' x
rw Dim' x
cl Entries N N x
xs) = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim y (Point y)
rw' Dim y (Point y)
cl' Entries N N y
ys where
rw' :: Dim y (Point y)
rw' = forall q y p x.
(Entity q, q ~ Point y) =>
(p -> q) -> Dim x p -> Dim y q
dimMap (forall (h :: * -> * -> *) a b.
HomOriented h =>
h a b -> Point a -> Point b
pmap h x y
h) Dim' x
rw
cl' :: Dim y (Point y)
cl' = forall q y p x.
(Entity q, q ~ Point y) =>
(p -> q) -> Dim x p -> Dim y q
dimMap (forall (h :: * -> * -> *) a b.
HomOriented h =>
h a b -> Point a -> Point b
pmap h x y
h) Dim' x
cl
ys :: Entries N N y
ys = forall x i j. Additive x => Entries i j x -> Entries i j x
etsElimZeros forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
amap h x y
h) Entries N N x
xs
mtxMap :: Hom Dst h => h x y -> Matrix x -> Matrix y
mtxMap :: forall (h :: * -> * -> *) x y.
Hom Dst h =>
h x y -> Matrix x -> Matrix y
mtxMap h x y
h = forall (h :: * -> * -> *) y x.
Hom Dst h =>
Struct Dst y -> h x y -> Matrix x -> Matrix y
mtxMapStruct (forall s t x. Transformable s t => Struct s x -> Struct t x
tau forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall (m :: * -> * -> *) x y.
Morphism m =>
m x y -> Struct (ObjectClass m) y
range h x y
h) h x y
h
instance HomDistributive h => Applicative1 h Matrix where
amap1 :: forall a b. h a b -> Matrix a -> Matrix b
amap1 = forall (h :: * -> * -> *) x y.
Hom Dst h =>
h x y -> Matrix x -> Matrix y
mtxMap
type instance Dual (Matrix x) = Matrix (Op x)
coMatrix :: Entity (Point x) => Matrix x -> Dual (Matrix x)
coMatrix :: forall x. Entity (Point x) => Matrix x -> Dual (Matrix x)
coMatrix (Matrix Dim' x
rw Dim' x
cl Entries N N x
xs) = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim (Op x) (Point (Op x))
cl' Dim (Op x) (Point (Op x))
rw' Dual (Entries N N x)
xs' where
cl' :: Dim (Op x) (Point (Op x))
cl' = forall q y p x.
(Entity q, q ~ Point y) =>
(p -> q) -> Dim x p -> Dim y q
dimMap forall x. x -> x
id Dim' x
cl
rw' :: Dim (Op x) (Point (Op x))
rw' = forall q y p x.
(Entity q, q ~ Point y) =>
(p -> q) -> Dim x p -> Dim y q
dimMap forall x. x -> x
id Dim' x
rw
xs' :: Dual (Entries N N x)
xs' = forall i j x.
(Ord i, Ord j) =>
Entries i j x -> Dual (Entries i j x)
coEntries Entries N N x
xs
mtxFromOpOp :: Entity (Point x) => Matrix (Op (Op x)) -> Matrix x
mtxFromOpOp :: forall x. Entity (Point x) => Matrix (Op (Op x)) -> Matrix x
mtxFromOpOp (Matrix Dim' (Op (Op x))
rw Dim' (Op (Op x))
cl Entries N N (Op (Op x))
xs) = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim x (Point x)
rw' Dim x (Point x)
cl' Entries N N x
xs' where
rw' :: Dim x (Point x)
rw' = forall q y p x.
(Entity q, q ~ Point y) =>
(p -> q) -> Dim x p -> Dim y q
dimMap forall x. x -> x
id Dim' (Op (Op x))
rw
cl' :: Dim x (Point x)
cl' = forall q y p x.
(Entity q, q ~ Point y) =>
(p -> q) -> Dim x p -> Dim y q
dimMap forall x. x -> x
id Dim' (Op (Op x))
cl
xs' :: Entries N N x
xs' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall x. Op (Op x) -> x
fromOpOp Entries N N (Op (Op x))
xs
coMatrixInv :: Entity (Point x) => Dual (Matrix x) -> Matrix x
coMatrixInv :: forall x. Entity (Point x) => Dual (Matrix x) -> Matrix x
coMatrixInv (Matrix Dim' (Op x)
rw Dim' (Op x)
cl Entries N N (Op x)
xs) = forall x. Dim' x -> Dim' x -> Entries N N x -> Matrix x
Matrix Dim x (Point x)
cl' Dim x (Point x)
rw' Entries N N x
xs' where
cl' :: Dim x (Point x)
cl' = forall q y p x.
(Entity q, q ~ Point y) =>
(p -> q) -> Dim x p -> Dim y q
dimMap forall x. x -> x
id Dim' (Op x)
cl
rw' :: Dim x (Point x)
rw' = forall q y p x.
(Entity q, q ~ Point y) =>
(p -> q) -> Dim x p -> Dim y q
dimMap forall x. x -> x
id Dim' (Op x)
rw
xs' :: Entries N N x
xs' = forall i j x.
(Ord i, Ord j) =>
Dual (Entries i j x) -> Entries i j x
coEntriesInv Entries N N (Op x)
xs
instance EntityPoint x => Dualisable (Matrix x) where
toDual :: Matrix x -> Dual (Matrix x)
toDual = forall x. Entity (Point x) => Matrix x -> Dual (Matrix x)
coMatrix
fromDual :: Dual (Matrix x) -> Matrix x
fromDual = forall x. Entity (Point x) => Dual (Matrix x) -> Matrix x
coMatrixInv
instance ForgetfulDst s => Applicative (OpMap Matrix s) where
amap :: forall a b. OpMap Matrix s a b -> a -> b
amap h :: OpMap Matrix s a b
h@OpMap Matrix s a b
ToOp1 = forall x. Struct Dst x -> Op (Matrix x) -> Matrix (Op x)
coMatrixDst (forall s t x. Transformable s t => Struct s x -> Struct t x
tau (forall (f :: * -> *) s x.
OpMap f s (Op (f x)) (f (Op x)) -> Struct s x
toOp1Struct OpMap Matrix s a b
h)) where
coMatrixDst :: Struct Dst x -> Op (Matrix x) -> Matrix (Op x)
coMatrixDst :: forall x. Struct Dst x -> Op (Matrix x) -> Matrix (Op x)
coMatrixDst Struct Dst x
Struct = forall x. Entity (Point x) => Matrix x -> Dual (Matrix x)
coMatrix forall (c :: * -> * -> *) y z x.
Category c =>
c y z -> c x y -> c x z
. forall x. Op x -> x
fromOp
amap h :: OpMap Matrix s a b
h@OpMap Matrix s a b
FromOp1 = forall x. Struct Dst x -> Matrix (Op x) -> Op (Matrix x)
coMatrixDst (forall s t x. Transformable s t => Struct s x -> Struct t x
tau (forall (f :: * -> *) s x.
OpMap f s (f (Op x)) (Op (f x)) -> Struct s x
fromOp1Struct OpMap Matrix s a b
h)) where
coMatrixDst :: Struct Dst x -> Matrix (Op x) -> Op (Matrix x)
coMatrixDst :: forall x. Struct Dst x -> Matrix (Op x) -> Op (Matrix x)
coMatrixDst Struct Dst x
Struct = forall x. x -> Op x
Op forall (c :: * -> * -> *) y z x.
Category c =>
c y z -> c x y -> c x z
. forall x. Entity (Point x) => Dual (Matrix x) -> Matrix x
coMatrixInv
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomOriented (OpMap Matrix s) where
pmap :: forall a b. OpMap Matrix s a b -> Point a -> Point b
pmap h :: OpMap Matrix s a b
h@OpMap Matrix s a b
ToOp1 = forall x.
Struct Dst x -> Point (Op (Matrix x)) -> Point (Matrix (Op x))
coDimDst (forall s t x. Transformable s t => Struct s x -> Struct t x
tau (forall (f :: * -> *) s x.
OpMap f s (Op (f x)) (f (Op x)) -> Struct s x
toOp1Struct OpMap Matrix s a b
h)) where
coDimDst :: Struct Dst x -> Point (Op (Matrix x)) -> Point (Matrix (Op x))
coDimDst :: forall x.
Struct Dst x -> Point (Op (Matrix x)) -> Point (Matrix (Op x))
coDimDst Struct Dst x
Struct = forall q y p x.
(Entity q, q ~ Point y) =>
(p -> q) -> Dim x p -> Dim y q
dimMap forall x. x -> x
id
pmap h :: OpMap Matrix s a b
h@OpMap Matrix s a b
FromOp1 = forall x.
Struct Dst x -> Point (Matrix (Op x)) -> Point (Op (Matrix x))
coDimDst (forall s t x. Transformable s t => Struct s x -> Struct t x
tau (forall (f :: * -> *) s x.
OpMap f s (f (Op x)) (Op (f x)) -> Struct s x
fromOp1Struct OpMap Matrix s a b
h)) where
coDimDst :: Struct Dst x -> Point (Matrix (Op x)) -> Point (Op (Matrix x))
coDimDst :: forall x.
Struct Dst x -> Point (Matrix (Op x)) -> Point (Op (Matrix x))
coDimDst Struct Dst x
Struct = forall q y p x.
(Entity q, q ~ Point y) =>
(p -> q) -> Dim x p -> Dim y q
dimMap forall x. x -> x
id
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomMultiplicative (OpMap Matrix s)
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomFibred (OpMap Matrix s)
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomFibredOriented (OpMap Matrix s)
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomAdditive (OpMap Matrix s)
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomDistributive (OpMap Matrix s)
instance ForgetfulDst s => Applicative (IsoOpMap Matrix s) where
amap :: forall a b. IsoOpMap Matrix s a b -> a -> b
amap = forall x y. Exposable x => (Form x -> y) -> x -> y
restrict forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
amap
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomOriented (IsoOpMap Matrix s) where pmap :: forall a b. IsoOpMap Matrix s a b -> Point a -> Point b
pmap = forall x y. Exposable x => (Form x -> y) -> x -> y
restrict forall (h :: * -> * -> *) a b.
HomOriented h =>
h a b -> Point a -> Point b
pmap
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomMultiplicative (IsoOpMap Matrix s)
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomFibred (IsoOpMap Matrix s)
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomFibredOriented (IsoOpMap Matrix s)
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomAdditive (IsoOpMap Matrix s)
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> HomDistributive (IsoOpMap Matrix s)
instance ForgetfulDst s => Functorial (IsoOpMap Matrix s)
instance (TransformableOp s, ForgetfulDst s, ForgetfulTyp s, Typeable s)
=> FunctorialHomOriented (IsoOpMap Matrix s)
isoCoMatrixDst :: Distributive x => IsoOpMap Matrix Dst (Op (Matrix x)) (Matrix (Op x))
isoCoMatrixDst :: forall x.
Distributive x =>
IsoOpMap Matrix Dst (Op (Matrix x)) (Matrix (Op x))
isoCoMatrixDst = forall x. Constructable x => Form x -> x
make (forall s (f :: * -> *) y.
(Structure s (Op (f y)), Structure s (f (Op y)), Structure s y) =>
OpMap f s (Op (f y)) (f (Op y))
ToOp1 forall (m :: * -> * -> *) y z x. m y z -> Path m x y -> Path m x z
:. forall (m :: * -> * -> *) x. Struct (ObjectClass m) x -> Path m x x
IdPath forall s x. Structure s x => Struct s x
Struct)
xMatrix :: Additive x
=> Q -> XOrtOrientation x -> X (Orientation (Point (Matrix x)))
-> XOrtOrientation (Matrix x)
xMatrix :: forall x.
Additive x =>
Q
-> XOrtOrientation x
-> X (Orientation (Point (Matrix x)))
-> XOrtOrientation (Matrix x)
xMatrix Q
qMax XOrtOrientation x
xx X (Orientation (Point (Matrix x)))
xoDim = forall q.
X (Orientation (Point q))
-> (Orientation (Point q) -> X q) -> XOrtOrientation q
XOrtOrientation X (Orientation (Point (Matrix x)))
xoDim Orientation (Dim x (Point x)) -> X (Matrix x)
xMtx where
xn :: N -> X N
xn N
0 = forall x. X x
XEmpty
xn N
n = N -> N -> X N
xNB N
0 (forall a. Enum a => a -> a
pred N
n)
xMtx :: Orientation (Dim x (Point x)) -> X (Matrix x)
xMtx (Dim x (Point x)
cl:>Dim x (Point x)
rw) = do
N
n <- N -> N -> X N
xNB N
0 N
xMax
[(x, N, N)]
xs <- N -> (Dim x (Point x), N) -> (Dim x (Point x), N) -> X [(x, N, N)]
xets N
n (Dim x (Point x)
rw,N
lrw) (Dim x (Point x)
cl,N
lcl)
forall (m :: * -> *) a. Monad m => a -> m a
return forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall x p.
(Additive x, p ~ Point x) =>
Dim x p -> Dim x p -> [(x, N, N)] -> Matrix x
matrix Dim x (Point x)
rw Dim x (Point x)
cl [(x, N, N)]
xs
where lcl :: N
lcl = forall x. LengthN x => x -> N
lengthN Dim x (Point x)
cl
lrw :: N
lrw = forall x. LengthN x => x -> N
lengthN Dim x (Point x)
rw
xMax :: N
xMax = forall a b. Projectible a b => b -> a
prj forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall a b. (a, b) -> a
fst forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall r. Number r => r -> (Z, r)
zFloorFraction forall (h :: * -> * -> *) a b. Applicative h => h a b -> a -> b
$ forall a b. Embeddable a b => a -> b
inj (N
lclforall c. Multiplicative c => c -> c -> c
*N
lrw) forall c. Multiplicative c => c -> c -> c
* Q
qMax
xets :: N -> (Dim x (Point x), N) -> (Dim x (Point x), N) -> X [(x, N, N)]
xets N
0 (Dim x (Point x), N)
_ (Dim x (Point x), N)
_ = forall (m :: * -> *) a. Monad m => a -> m a
return []
xets N
n (Dim x (Point x)
rw,N
lrw) (Dim x (Point x)
cl,N
lcl) = do
[(x, N, N)]
xs <- N -> (Dim x (Point x), N) -> (Dim x (Point x), N) -> X [(x, N, N)]
xets (forall a. Enum a => a -> a
pred N
n) (Dim x (Point x)
rw,N
lrw) (Dim x (Point x)
cl,N
lcl)
N
i <- N -> X N
xn N
lrw
N
j <- N -> X N
xn N
lcl
x
x <- forall q. XOrtOrientation q -> Orientation (Point q) -> X q
xoArrow XOrtOrientation x
xx (Dim x (Point x)
cl forall (s :: * -> *) i x. Sequence s i x => s x -> i -> x
? N
j forall p. p -> p -> Orientation p
:> Dim x (Point x)
rw forall (s :: * -> *) i x. Sequence s i x => s x -> i -> x
? N
i)
forall (m :: * -> *) a. Monad m => a -> m a
return ((x
x,N
i,N
j)forall a. a -> [a] -> [a]
:[(x, N, N)]
xs)
xMatrixTtl :: (Distributive x, Total x)
=> N -> Q -> X x -> XOrtOrientation (Matrix x)
xMatrixTtl :: forall x.
(Distributive x, Total x) =>
N -> Q -> X x -> XOrtOrientation (Matrix x)
xMatrixTtl N
dimMax Q
qMax X x
xx = forall x.
Additive x =>
Q
-> XOrtOrientation x
-> X (Orientation (Point (Matrix x)))
-> XOrtOrientation (Matrix x)
xMatrix Q
qMax (forall q. Total q => X q -> XOrtOrientation q
xoTtl X x
xx) X (Orientation (Dim x (Point x)))
xoDim where
d :: Dim x (Point x)
d = forall p x. (Entity p, p ~ Point x) => p -> Dim x p
dim forall s. Singleton s => s
unit
xoDim :: X (Orientation (Dim x (Point x)))
xoDim = do
N
n <- N -> N -> X N
xNB N
0 N
dimMax
N
m <- N -> N -> X N
xNB N
0 N
dimMax
forall (m :: * -> *) a. Monad m => a -> m a
return (Dim x (Point x)
dforall f. Exponential f => f -> Exponent f -> f
^N
n forall p. p -> p -> Orientation p
:> Dim x (Point x)
dforall f. Exponential f => f -> Exponent f -> f
^N
m)
xodZ :: XOrtOrientation (Matrix Z)
xodZ :: XOrtOrientation (Matrix Z)
xodZ = forall x.
(Distributive x, Total x) =>
N -> Q -> X x -> XOrtOrientation (Matrix x)
xMatrixTtl N
5 Q
0.9 (Z -> Z -> X Z
xZB (-Z
100) Z
100)
xodZZ :: XOrtOrientation (Matrix (Matrix Z))
xodZZ :: XOrtOrientation (Matrix (Matrix Z))
xodZZ = forall x.
Additive x =>
Q
-> XOrtOrientation x
-> X (Orientation (Point (Matrix x)))
-> XOrtOrientation (Matrix x)
xMatrix Q
0.7 XOrtOrientation (Matrix Z)
xodZ X (Orientation (Dim (Matrix Z) (Dim Z ())))
xoDim where
dMax :: N
dMax = N
10
xd :: X (Point (Matrix Z))
xd = forall q. Oriented q => XOrtOrientation q -> X (Point q)
xoPoint XOrtOrientation (Matrix Z)
xodZ
xoDim :: X (Orientation (Dim (Matrix Z) (Dim Z ())))
xoDim = do
[Dim Z ()]
n <- forall x. N -> N -> X x -> X [x]
xTakeB N
0 N
dMax X (Dim Z ())
xd
[Dim Z ()]
m <- forall x. N -> N -> X x -> X [x]
xTakeB N
0 N
dMax X (Dim Z ())
xd
forall (m :: * -> *) a. Monad m => a -> m a
return (forall p x. (Entity p, p ~ Point x) => [p] -> Dim x p
productDim [Dim Z ()]
n forall p. p -> p -> Orientation p
:> forall p x. (Entity p, p ~ Point x) => [p] -> Dim x p
productDim [Dim Z ()]
m)
class XStandardOrientationMatrix x where
xStandardOrientationMatrix :: X (Orientation (Dim' x))
instance XStandardPoint (Matrix Z)
instance XStandardOrientationMatrix Z where
xStandardOrientationMatrix :: X (Orientation (Dim' Z))
xStandardOrientationMatrix = do
Dim Z ()
n <- forall x. XStandard x => X x
xStandard
Dim Z ()
m <- forall x. XStandard x => X x
xStandard
forall (m :: * -> *) a. Monad m => a -> m a
return (Dim Z ()
nforall p. p -> p -> Orientation p
:>Dim Z ()
m)
instance ( Additive x, FibredOriented x
, XStandardOrtOrientation x, XStandardOrientationMatrix x
)
=> XStandardOrtOrientation (Matrix x) where
xStandardOrtOrientation :: XOrtOrientation (Matrix x)
xStandardOrtOrientation = forall x.
Additive x =>
Q
-> XOrtOrientation x
-> X (Orientation (Point (Matrix x)))
-> XOrtOrientation (Matrix x)
xMatrix Q
0.8 forall q. XStandardOrtOrientation q => XOrtOrientation q
xStandardOrtOrientation forall x. XStandardOrientationMatrix x => X (Orientation (Dim' x))
xStandardOrientationMatrix
instance XStandardOrtSite From (Matrix Z) where
xStandardOrtSite :: XOrtSite 'From (Matrix Z)
xStandardOrtSite = forall q. Oriented q => XOrtOrientation q -> XOrtSite 'From q
xoFrom forall q. XStandardOrtOrientation q => XOrtOrientation q
xStandardOrtOrientation
instance XStandardOrtSiteFrom (Matrix Z)
instance XStandardOrtSite To (Matrix Z) where
xStandardOrtSite :: XOrtSite 'To (Matrix Z)
xStandardOrtSite = forall q. Oriented q => XOrtOrientation q -> XOrtSite 'To q
xoTo forall q. XStandardOrtOrientation q => XOrtOrientation q
xStandardOrtOrientation