{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoStarIsType #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module LAoP.Matrix.Type
(
Matrix (..),
Countable,
CountableDimensions,
CountableN,
CountableDimensionsN,
FromListsN,
Liftable,
Trivial,
TrivialP,
Zero,
One,
empty,
one,
junc,
split,
I.FromNat,
I.Count,
I.Normalize,
I.FromLists,
fromLists,
toLists,
toList,
matrixBuilder,
row,
col,
zeros,
ones,
bang,
point,
constant,
fmapM,
bimapM,
unitM,
multM,
selectM,
returnM,
bindM,
columns,
rows,
tr,
cond,
abideJS,
abideSJ,
zipWithM,
(===),
p1,
p2,
(|||),
i1,
i2,
(-|-),
(><),
kp1,
kp2,
khatri,
identity,
comp,
fromF,
fromF',
toRel,
pretty,
prettyPrint
)
where
import Data.Void
import Data.Proxy
import Data.Kind
import GHC.TypeLits
import Control.DeepSeq
import LAoP.Utils
import qualified Control.Category as C
import qualified LAoP.Matrix.Internal as I
newtype Matrix e (cols :: Type) (rows :: Type) = M (I.Matrix e (I.Normalize cols) (I.Normalize rows))
deriving (Int -> Matrix e cols rows -> ShowS
[Matrix e cols rows] -> ShowS
Matrix e cols rows -> String
(Int -> Matrix e cols rows -> ShowS)
-> (Matrix e cols rows -> String)
-> ([Matrix e cols rows] -> ShowS)
-> Show (Matrix e cols rows)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall e cols rows. Show e => Int -> Matrix e cols rows -> ShowS
forall e cols rows. Show e => [Matrix e cols rows] -> ShowS
forall e cols rows. Show e => Matrix e cols rows -> String
showList :: [Matrix e cols rows] -> ShowS
$cshowList :: forall e cols rows. Show e => [Matrix e cols rows] -> ShowS
show :: Matrix e cols rows -> String
$cshow :: forall e cols rows. Show e => Matrix e cols rows -> String
showsPrec :: Int -> Matrix e cols rows -> ShowS
$cshowsPrec :: forall e cols rows. Show e => Int -> Matrix e cols rows -> ShowS
Show, Integer -> Matrix e cols rows
Matrix e cols rows -> Matrix e cols rows
Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
(Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows)
-> (Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows)
-> (Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows)
-> (Matrix e cols rows -> Matrix e cols rows)
-> (Matrix e cols rows -> Matrix e cols rows)
-> (Matrix e cols rows -> Matrix e cols rows)
-> (Integer -> Matrix e cols rows)
-> Num (Matrix e cols rows)
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall e cols rows. Num e => Integer -> Matrix e cols rows
forall e cols rows.
Num e =>
Matrix e cols rows -> Matrix e cols rows
forall e cols rows.
Num e =>
Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
fromInteger :: Integer -> Matrix e cols rows
$cfromInteger :: forall e cols rows. Num e => Integer -> Matrix e cols rows
signum :: Matrix e cols rows -> Matrix e cols rows
$csignum :: forall e cols rows.
Num e =>
Matrix e cols rows -> Matrix e cols rows
abs :: Matrix e cols rows -> Matrix e cols rows
$cabs :: forall e cols rows.
Num e =>
Matrix e cols rows -> Matrix e cols rows
negate :: Matrix e cols rows -> Matrix e cols rows
$cnegate :: forall e cols rows.
Num e =>
Matrix e cols rows -> Matrix e cols rows
* :: Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
$c* :: forall e cols rows.
Num e =>
Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
- :: Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
$c- :: forall e cols rows.
Num e =>
Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
+ :: Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
$c+ :: forall e cols rows.
Num e =>
Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
Num, Matrix e cols rows -> Matrix e cols rows -> Bool
(Matrix e cols rows -> Matrix e cols rows -> Bool)
-> (Matrix e cols rows -> Matrix e cols rows -> Bool)
-> Eq (Matrix e cols rows)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall e cols rows.
Eq e =>
Matrix e cols rows -> Matrix e cols rows -> Bool
/= :: Matrix e cols rows -> Matrix e cols rows -> Bool
$c/= :: forall e cols rows.
Eq e =>
Matrix e cols rows -> Matrix e cols rows -> Bool
== :: Matrix e cols rows -> Matrix e cols rows -> Bool
$c== :: forall e cols rows.
Eq e =>
Matrix e cols rows -> Matrix e cols rows -> Bool
Eq, Eq (Matrix e cols rows)
Eq (Matrix e cols rows) =>
(Matrix e cols rows -> Matrix e cols rows -> Ordering)
-> (Matrix e cols rows -> Matrix e cols rows -> Bool)
-> (Matrix e cols rows -> Matrix e cols rows -> Bool)
-> (Matrix e cols rows -> Matrix e cols rows -> Bool)
-> (Matrix e cols rows -> Matrix e cols rows -> Bool)
-> (Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows)
-> (Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows)
-> Ord (Matrix e cols rows)
Matrix e cols rows -> Matrix e cols rows -> Bool
Matrix e cols rows -> Matrix e cols rows -> Ordering
Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall e cols rows. Ord e => Eq (Matrix e cols rows)
forall e cols rows.
Ord e =>
Matrix e cols rows -> Matrix e cols rows -> Bool
forall e cols rows.
Ord e =>
Matrix e cols rows -> Matrix e cols rows -> Ordering
forall e cols rows.
Ord e =>
Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
min :: Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
$cmin :: forall e cols rows.
Ord e =>
Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
max :: Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
$cmax :: forall e cols rows.
Ord e =>
Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
>= :: Matrix e cols rows -> Matrix e cols rows -> Bool
$c>= :: forall e cols rows.
Ord e =>
Matrix e cols rows -> Matrix e cols rows -> Bool
> :: Matrix e cols rows -> Matrix e cols rows -> Bool
$c> :: forall e cols rows.
Ord e =>
Matrix e cols rows -> Matrix e cols rows -> Bool
<= :: Matrix e cols rows -> Matrix e cols rows -> Bool
$c<= :: forall e cols rows.
Ord e =>
Matrix e cols rows -> Matrix e cols rows -> Bool
< :: Matrix e cols rows -> Matrix e cols rows -> Bool
$c< :: forall e cols rows.
Ord e =>
Matrix e cols rows -> Matrix e cols rows -> Bool
compare :: Matrix e cols rows -> Matrix e cols rows -> Ordering
$ccompare :: forall e cols rows.
Ord e =>
Matrix e cols rows -> Matrix e cols rows -> Ordering
$cp1Ord :: forall e cols rows. Ord e => Eq (Matrix e cols rows)
Ord, Matrix e cols rows -> ()
(Matrix e cols rows -> ()) -> NFData (Matrix e cols rows)
forall a. (a -> ()) -> NFData a
forall e cols rows. NFData e => Matrix e cols rows -> ()
rnf :: Matrix e cols rows -> ()
$crnf :: forall e cols rows. NFData e => Matrix e cols rows -> ()
NFData) via (I.Matrix e (I.Normalize cols) (I.Normalize rows))
type Countable a = KnownNat (I.Count a)
type CountableDimensions a b = (Countable a, Countable b)
type CountableN a = KnownNat (I.Count (I.Normalize a))
type CountableDimensionsN a b = (CountableN a, CountableN b)
type FromListsN e a b = I.FromLists e (I.Normalize a) (I.Normalize b)
type Liftable e a b = (Bounded a, Bounded b, Enum a, Enum b, Eq b, Num e, Ord e)
type Trivial a = I.Normalize (I.Normalize a) ~ I.Normalize (I.Normalize (I.Normalize a))
type Trivial2 a = I.Normalize a ~ I.Normalize (I.Normalize a)
type Trivial3 a = I.FromNat (I.Count (I.Normalize (I.Normalize a))) ~ I.Normalize (I.Normalize a)
type TrivialP a b = I.Normalize (a, b) ~ I.Normalize (I.Normalize a, I.Normalize b)
instance (Num e) => C.Category (Matrix e) where
id :: Matrix e a a
id = Matrix e a a
forall a. HasCallStack => a
undefined
. :: Matrix e b c -> Matrix e a b -> Matrix e a c
(.) = Matrix e b c -> Matrix e a b -> Matrix e a c
forall e cr rows cols.
Num e =>
Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
comp
bimapM ::
( Liftable e a b,
Liftable e c d,
CountableDimensionsN a c,
CountableDimensionsN b d,
FromListsN e d c,
FromListsN e b a
) => (a -> b) -> (c -> d) -> Matrix e a c -> Matrix e b d
bimapM :: (a -> b) -> (c -> d) -> Matrix e a c -> Matrix e b d
bimapM f :: a -> b
f g :: c -> d
g m :: Matrix e a c
m = (c -> d) -> Matrix e c d
forall e a b.
(Liftable e a b, CountableDimensionsN a b, FromListsN e b a) =>
(a -> b) -> Matrix e a b
fromF' c -> d
g Matrix e c d -> Matrix e a c -> Matrix e a d
forall e cr rows cols.
Num e =>
Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
`comp` Matrix e a c
m Matrix e a d -> Matrix e b a -> Matrix e b d
forall e cr rows cols.
Num e =>
Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
`comp` Matrix e a b -> Matrix e b a
forall e cols rows. Matrix e cols rows -> Matrix e rows cols
tr ((a -> b) -> Matrix e a b
forall e a b.
(Liftable e a b, CountableDimensionsN a b, FromListsN e b a) =>
(a -> b) -> Matrix e a b
fromF' a -> b
f)
type Zero = Void
type One = ()
empty :: Matrix e Zero Zero
empty :: Matrix e Zero Zero
empty = Matrix e (Normalize Zero) (Normalize Zero) -> Matrix e Zero Zero
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M Matrix e (Normalize Zero) (Normalize Zero)
forall e. Matrix e Zero Zero
I.Empty
one :: e -> Matrix e One One
one :: e -> Matrix e () ()
one = Matrix e () () -> Matrix e () ()
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e () () -> Matrix e () ())
-> (e -> Matrix e () ()) -> e -> Matrix e () ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Matrix e () ()
forall e. e -> Matrix e () ()
I.One
junc ::
Matrix e a rows ->
Matrix e b rows ->
Matrix e (Either a b) rows
junc :: Matrix e a rows -> Matrix e b rows -> Matrix e (Either a b) rows
junc (M a :: Matrix e (Normalize a) (Normalize rows)
a) (M b :: Matrix e (Normalize b) (Normalize rows)
b) = Matrix e (Normalize (Either a b)) (Normalize rows)
-> Matrix e (Either a b) rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize a) (Normalize rows)
-> Matrix e (Normalize b) (Normalize rows)
-> Matrix e (Either (Normalize a) (Normalize b)) (Normalize rows)
forall e a rows b.
Matrix e a rows -> Matrix e b rows -> Matrix e (Either a b) rows
I.Junc Matrix e (Normalize a) (Normalize rows)
a Matrix e (Normalize b) (Normalize rows)
b)
infixl 3 |||
(|||) ::
Matrix e a rows ->
Matrix e b rows ->
Matrix e (Either a b) rows
||| :: Matrix e a rows -> Matrix e b rows -> Matrix e (Either a b) rows
(|||) = Matrix e a rows -> Matrix e b rows -> Matrix e (Either a b) rows
forall e a rows b.
Matrix e a rows -> Matrix e b rows -> Matrix e (Either a b) rows
junc
split ::
Matrix e cols a ->
Matrix e cols b ->
Matrix e cols (Either a b)
split :: Matrix e cols a -> Matrix e cols b -> Matrix e cols (Either a b)
split (M a :: Matrix e (Normalize cols) (Normalize a)
a) (M b :: Matrix e (Normalize cols) (Normalize b)
b) = Matrix e (Normalize cols) (Normalize (Either a b))
-> Matrix e cols (Either a b)
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cols) (Normalize a)
-> Matrix e (Normalize cols) (Normalize b)
-> Matrix e (Normalize cols) (Either (Normalize a) (Normalize b))
forall e cols a b.
Matrix e cols a -> Matrix e cols b -> Matrix e cols (Either a b)
I.Split Matrix e (Normalize cols) (Normalize a)
a Matrix e (Normalize cols) (Normalize b)
b)
infixl 2 ===
(===) ::
Matrix e cols a ->
Matrix e cols b ->
Matrix e cols (Either a b)
=== :: Matrix e cols a -> Matrix e cols b -> Matrix e cols (Either a b)
(===) = Matrix e cols a -> Matrix e cols b -> Matrix e cols (Either a b)
forall e cols a b.
Matrix e cols a -> Matrix e cols b -> Matrix e cols (Either a b)
split
fmapM ::
( Liftable e a b,
CountableDimensionsN a b,
FromListsN e b a
)
=>
(a -> b) -> Matrix e c a -> Matrix e c b
fmapM :: (a -> b) -> Matrix e c a -> Matrix e c b
fmapM f :: a -> b
f m :: Matrix e c a
m = (a -> b) -> Matrix e a b
forall e a b.
(Liftable e a b, CountableDimensionsN a b, FromListsN e b a) =>
(a -> b) -> Matrix e a b
fromF' a -> b
f Matrix e a b -> Matrix e c a -> Matrix e c b
forall e cr rows cols.
Num e =>
Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
`comp` Matrix e c a
m
unitM :: (Num e) => Matrix e () ()
unitM :: Matrix e () ()
unitM = e -> Matrix e () ()
forall e. e -> Matrix e () ()
one 1
multM ::
( CountableDimensionsN a b,
CountableN (a, b),
Num e,
FromListsN e (a, b) a,
FromListsN e (a, b) b,
TrivialP a b
) => Matrix e c a -> Matrix e c b -> Matrix e c (a, b)
multM :: Matrix e c a -> Matrix e c b -> Matrix e c (a, b)
multM = Matrix e c a -> Matrix e c b -> Matrix e c (a, b)
forall e cols a b.
(Num e, CountableDimensionsN a b, CountableN (a, b),
FromListsN e (a, b) a, FromListsN e (a, b) b, TrivialP a b) =>
Matrix e cols a -> Matrix e cols b -> Matrix e cols (a, b)
khatri
returnM ::
forall e a .
( Num e,
Enum e,
Enum a,
FromListsN e () a,
Countable a
) => a -> Matrix e One a
returnM :: a -> Matrix e () a
returnM a :: a
a = [e] -> Matrix e () a
forall e rows. FromListsN e () rows => [e] -> Matrix e () rows
col [e]
l
where
i :: Int
i = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Proxy (Count a) -> Integer
forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Integer
natVal (Proxy (Count a)
forall k (t :: k). Proxy t
Proxy :: Proxy (I.Count a))
x :: Int
x = a -> Int
forall a. Enum a => a -> Int
fromEnum a
a
l :: [e]
l = Int -> [e] -> [e]
forall a. Int -> [a] -> [a]
take Int
x [0,0..] [e] -> [e] -> [e]
forall a. [a] -> [a] -> [a]
++ [1] [e] -> [e] -> [e]
forall a. [a] -> [a] -> [a]
++ Int -> [e] -> [e]
forall a. Int -> [a] -> [a]
take (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) [0,0..]
bindM :: (Num e) => Matrix e a b -> Matrix e b c -> Matrix e a c
bindM :: Matrix e a b -> Matrix e b c -> Matrix e a c
bindM = (Matrix e b c -> Matrix e a b -> Matrix e a c)
-> Matrix e a b -> Matrix e b c -> Matrix e a c
forall a b c. (a -> b -> c) -> b -> a -> c
flip Matrix e b c -> Matrix e a b -> Matrix e a c
forall e cr rows cols.
Num e =>
Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
comp
fromLists :: (FromListsN e cols rows) => [[e]] -> Matrix e cols rows
fromLists :: [[e]] -> Matrix e cols rows
fromLists = Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows)
-> ([[e]] -> Matrix e (Normalize cols) (Normalize rows))
-> [[e]]
-> Matrix e cols rows
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[e]] -> Matrix e (Normalize cols) (Normalize rows)
forall e cols rows.
FromLists e cols rows =>
[[e]] -> Matrix e cols rows
I.fromLists
matrixBuilder ::
(FromListsN e cols rows, CountableDimensionsN cols rows )
=> ((Int, Int) -> e) -> Matrix e cols rows
matrixBuilder :: ((Int, Int) -> e) -> Matrix e cols rows
matrixBuilder = Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows)
-> (((Int, Int) -> e)
-> Matrix e (Normalize cols) (Normalize rows))
-> ((Int, Int) -> e)
-> Matrix e cols rows
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Int) -> e) -> Matrix e (Normalize cols) (Normalize rows)
forall e cols rows.
(FromLists e cols rows, CountableDimensions cols rows) =>
((Int, Int) -> e) -> Matrix e cols rows
I.matrixBuilder
col :: (FromListsN e () rows) => [e] -> Matrix e One rows
col :: [e] -> Matrix e () rows
col = Matrix e () (Normalize rows) -> Matrix e () rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e () (Normalize rows) -> Matrix e () rows)
-> ([e] -> Matrix e () (Normalize rows)) -> [e] -> Matrix e () rows
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [e] -> Matrix e () (Normalize rows)
forall e rows. FromLists e () rows => [e] -> Matrix e () rows
I.col
row :: (FromListsN e cols ()) => [e] -> Matrix e cols One
row :: [e] -> Matrix e cols ()
row = Matrix e (Normalize cols) () -> Matrix e cols ()
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cols) () -> Matrix e cols ())
-> ([e] -> Matrix e (Normalize cols) ()) -> [e] -> Matrix e cols ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [e] -> Matrix e (Normalize cols) ()
forall e cols. FromLists e cols () => [e] -> Matrix e cols ()
I.row
fromF ::
( Liftable e a b,
CountableDimensionsN cols rows,
FromListsN e rows cols
) =>
(a -> b) -> Matrix e cols rows
fromF :: (a -> b) -> Matrix e cols rows
fromF = Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows)
-> ((a -> b) -> Matrix e (Normalize cols) (Normalize rows))
-> (a -> b)
-> Matrix e cols rows
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> Matrix e (Normalize cols) (Normalize rows)
forall a b cols rows e.
(Liftable e a b, CountableDimensions cols rows,
FromLists e rows cols) =>
(a -> b) -> Matrix e cols rows
I.fromF
fromF' ::
( Liftable e a b,
CountableDimensionsN a b,
FromListsN e b a
) =>
(a -> b) -> Matrix e a b
fromF' :: (a -> b) -> Matrix e a b
fromF' = Matrix e (Normalize a) (Normalize b) -> Matrix e a b
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize a) (Normalize b) -> Matrix e a b)
-> ((a -> b) -> Matrix e (Normalize a) (Normalize b))
-> (a -> b)
-> Matrix e a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> Matrix e (Normalize a) (Normalize b)
forall a b e.
(Liftable e a b, CountableDimensionsN a b, FromListsN e b a) =>
(a -> b) -> Matrix e (Normalize a) (Normalize b)
I.fromF'
toRel ::
( Liftable (Natural 0 1) a b,
CountableDimensionsN a b,
FromListsN (Natural 0 1) b a
) => (a -> b -> Bool) -> Matrix (Natural 0 1) a b
toRel :: (a -> b -> Bool) -> Matrix (Natural 0 1) a b
toRel = Matrix (Natural 0 1) (Normalize a) (Normalize b)
-> Matrix (Natural 0 1) a b
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix (Natural 0 1) (Normalize a) (Normalize b)
-> Matrix (Natural 0 1) a b)
-> ((a -> b -> Bool)
-> Matrix (Natural 0 1) (Normalize a) (Normalize b))
-> (a -> b -> Bool)
-> Matrix (Natural 0 1) a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b -> Bool)
-> Matrix (Natural 0 1) (Normalize a) (Normalize b)
forall a b.
(Bounded a, Bounded b, Enum a, Enum b, Eq b,
CountableDimensionsN a b, FromListsN (Natural 0 1) b a) =>
(a -> b -> Bool) -> Relation (Normalize a) (Normalize b)
I.toRel
toLists :: Matrix e cols rows -> [[e]]
toLists :: Matrix e cols rows -> [[e]]
toLists (M m :: Matrix e (Normalize cols) (Normalize rows)
m) = Matrix e (Normalize cols) (Normalize rows) -> [[e]]
forall e cols rows. Matrix e cols rows -> [[e]]
I.toLists Matrix e (Normalize cols) (Normalize rows)
m
toList :: Matrix e cols rows -> [e]
toList :: Matrix e cols rows -> [e]
toList (M m :: Matrix e (Normalize cols) (Normalize rows)
m) = Matrix e (Normalize cols) (Normalize rows) -> [e]
forall e cols rows. Matrix e cols rows -> [e]
I.toList Matrix e (Normalize cols) (Normalize rows)
m
zeros ::
(Num e, FromListsN e cols rows, CountableDimensionsN cols rows)
=> Matrix e cols rows
zeros :: Matrix e cols rows
zeros = Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M Matrix e (Normalize cols) (Normalize rows)
forall e cols rows.
(Num e, FromLists e cols rows, CountableDimensions cols rows) =>
Matrix e cols rows
I.zeros
ones ::
(Num e, FromListsN e cols rows, CountableDimensionsN cols rows)
=> Matrix e cols rows
ones :: Matrix e cols rows
ones = Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M Matrix e (Normalize cols) (Normalize rows)
forall e cols rows.
(Num e, FromLists e cols rows, CountableDimensions cols rows) =>
Matrix e cols rows
I.ones
constant ::
(Num e, FromListsN e cols rows, CountableDimensionsN cols rows)
=> e -> Matrix e cols rows
constant :: e -> Matrix e cols rows
constant = Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows)
-> (e -> Matrix e (Normalize cols) (Normalize rows))
-> e
-> Matrix e cols rows
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Matrix e (Normalize cols) (Normalize rows)
forall e cols rows.
(Num e, FromLists e cols rows, CountableDimensions cols rows) =>
e -> Matrix e cols rows
I.constant
bang ::
forall e cols.
(Num e, Enum e, FromListsN e cols (), CountableN cols) =>
Matrix e cols One
bang :: Matrix e cols ()
bang = Matrix e (Normalize cols) (Normalize ()) -> Matrix e cols ()
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M Matrix e (Normalize cols) (Normalize ())
forall e cols.
(Num e, Enum e, FromLists e cols (), Countable cols) =>
Matrix e cols ()
I.bang
point ::
( Bounded a,
Enum a,
Eq a,
Num e,
Ord e,
CountableN a,
FromListsN e a One
) => a -> Matrix e One a
point :: a -> Matrix e () a
point = (() -> a) -> Matrix e () a
forall e a b.
(Liftable e a b, CountableDimensionsN a b, FromListsN e b a) =>
(a -> b) -> Matrix e a b
fromF' ((() -> a) -> Matrix e () a)
-> (a -> () -> a) -> a -> Matrix e () a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> () -> a
forall a b. a -> b -> a
const
identity ::
(Num e, FromListsN e a a, CountableN a) =>
Matrix e a a
identity :: Matrix e a a
identity = Matrix e (Normalize a) (Normalize a) -> Matrix e a a
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M Matrix e (Normalize a) (Normalize a)
forall e cols.
(Num e, FromLists e cols cols, Countable cols) =>
Matrix e cols cols
I.identity
{-# NOINLINE identity #-}
comp :: (Num e) => Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
comp :: Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
comp (M a :: Matrix e (Normalize cr) (Normalize rows)
a) (M b :: Matrix e (Normalize cols) (Normalize cr)
b) = Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cr) (Normalize rows)
-> Matrix e (Normalize cols) (Normalize cr)
-> Matrix e (Normalize cols) (Normalize rows)
forall e cr rows cols.
Num e =>
Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
I.comp Matrix e (Normalize cr) (Normalize rows)
a Matrix e (Normalize cols) (Normalize cr)
b)
{-# NOINLINE comp #-}
{-# RULES
"comp/identity1" forall m. comp m identity = m ;
"comp/identity2" forall m. comp identity m = m
#-}
p1 ::
( Num e,
CountableDimensionsN n m,
FromListsN e n m,
FromListsN e m m
) =>
Matrix e (Either m n) m
p1 :: Matrix e (Either m n) m
p1 = Matrix e (Normalize (Either m n)) (Normalize m)
-> Matrix e (Either m n) m
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M Matrix e (Normalize (Either m n)) (Normalize m)
forall e m n.
(Num e, CountableDimensions n m, FromLists e n m,
FromLists e m m) =>
Matrix e (Either m n) m
I.p1
p2 ::
( Num e,
CountableDimensionsN n m,
FromListsN e m n,
FromListsN e n n
) =>
Matrix e (Either m n) n
p2 :: Matrix e (Either m n) n
p2 = Matrix e (Normalize (Either m n)) (Normalize n)
-> Matrix e (Either m n) n
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M Matrix e (Normalize (Either m n)) (Normalize n)
forall e m n.
(Num e, CountableDimensions n m, FromLists e m n,
FromLists e n n) =>
Matrix e (Either m n) n
I.p2
i1 ::
( Num e,
CountableDimensionsN n m,
FromListsN e n m,
FromListsN e m m
) =>
Matrix e m (Either m n)
i1 :: Matrix e m (Either m n)
i1 = Matrix e (Either m n) m -> Matrix e m (Either m n)
forall e cols rows. Matrix e cols rows -> Matrix e rows cols
tr Matrix e (Either m n) m
forall e n m.
(Num e, CountableDimensionsN n m, FromListsN e n m,
FromListsN e m m) =>
Matrix e (Either m n) m
p1
i2 ::
( Num e,
CountableDimensionsN n m,
FromListsN e m n,
FromListsN e n n
) =>
Matrix e n (Either m n)
i2 :: Matrix e n (Either m n)
i2 = Matrix e (Either m n) n -> Matrix e n (Either m n)
forall e cols rows. Matrix e cols rows -> Matrix e rows cols
tr Matrix e (Either m n) n
forall e n m.
(Num e, CountableDimensionsN n m, FromListsN e m n,
FromListsN e n n) =>
Matrix e (Either m n) n
p2
rows :: (CountableN rows) => Matrix e cols rows -> Int
rows :: Matrix e cols rows -> Int
rows (M m :: Matrix e (Normalize cols) (Normalize rows)
m) = Matrix e (Normalize cols) (Normalize rows) -> Int
forall e cols rows. Countable rows => Matrix e cols rows -> Int
I.rows Matrix e (Normalize cols) (Normalize rows)
m
columns :: (CountableN cols) => Matrix e cols rows -> Int
columns :: Matrix e cols rows -> Int
columns (M m :: Matrix e (Normalize cols) (Normalize rows)
m) = Matrix e (Normalize cols) (Normalize rows) -> Int
forall e cols rows. Countable cols => Matrix e cols rows -> Int
I.columns Matrix e (Normalize cols) (Normalize rows)
m
infixl 5 -|-
(-|-) ::
( Num e,
CountableDimensionsN j k,
FromListsN e k k,
FromListsN e j k,
FromListsN e k j,
FromListsN e j j
) =>
Matrix e n k ->
Matrix e m j ->
Matrix e (Either n m) (Either k j)
-|- :: Matrix e n k -> Matrix e m j -> Matrix e (Either n m) (Either k j)
(-|-) (M a :: Matrix e (Normalize n) (Normalize k)
a) (M b :: Matrix e (Normalize m) (Normalize j)
b) = Matrix e (Normalize (Either n m)) (Normalize (Either k j))
-> Matrix e (Either n m) (Either k j)
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize n) (Normalize k)
-> Matrix e (Normalize m) (Normalize j)
-> Matrix
e
(Either (Normalize n) (Normalize m))
(Either (Normalize k) (Normalize j))
forall e n k m j.
(Num e, CountableDimensions j k, FromLists e k k, FromLists e j k,
FromLists e k j, FromLists e j j) =>
Matrix e n k -> Matrix e m j -> Matrix e (Either n m) (Either k j)
(I.-|-) Matrix e (Normalize n) (Normalize k)
a Matrix e (Normalize m) (Normalize j)
b)
kp1 ::
forall e m k .
( Num e,
CountableDimensionsN m k,
CountableN (m, k),
FromListsN e (m, k) m,
TrivialP m k
) => Matrix e (m, k) m
kp1 :: Matrix e (m, k) m
kp1 = Matrix e (Normalize (m, k)) (Normalize m) -> Matrix e (m, k) m
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M ((Num e, CountableDimensions (Normalize k) (Normalize m),
FromLists e (Normalize (Normalize m, Normalize k)) (Normalize m),
CountableN (Normalize m, Normalize k)) =>
Matrix e (Normalize (Normalize m, Normalize k)) (Normalize m)
forall e m k.
(Num e, CountableDimensions k m, FromLists e (Normalize (m, k)) m,
CountableN (m, k)) =>
Matrix e (Normalize (m, k)) m
I.kp1 @e @(I.Normalize m) @(I.Normalize k))
kp2 ::
forall e m k.
( Num e,
CountableDimensionsN k m,
CountableN (m, k),
FromListsN e (m, k) k,
TrivialP m k
) => Matrix e (m, k) k
kp2 :: Matrix e (m, k) k
kp2 = Matrix e (Normalize (m, k)) (Normalize k) -> Matrix e (m, k) k
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M ((Num e, CountableDimensions (Normalize k) (Normalize m),
FromLists e (Normalize (Normalize m, Normalize k)) (Normalize k),
CountableN (Normalize m, Normalize k)) =>
Matrix e (Normalize (Normalize m, Normalize k)) (Normalize k)
forall e m k.
(Num e, CountableDimensions k m, FromLists e (Normalize (m, k)) k,
CountableN (m, k)) =>
Matrix e (Normalize (m, k)) k
I.kp2 @e @(I.Normalize m) @(I.Normalize k))
khatri ::
forall e cols a b.
( Num e,
CountableDimensionsN a b,
CountableN (a, b),
FromListsN e (a, b) a,
FromListsN e (a, b) b,
TrivialP a b
) => Matrix e cols a -> Matrix e cols b -> Matrix e cols (a, b)
khatri :: Matrix e cols a -> Matrix e cols b -> Matrix e cols (a, b)
khatri a :: Matrix e cols a
a b :: Matrix e cols b
b =
let kp1' :: Matrix e (a, b) a
kp1' = (Num e, CountableDimensionsN a b, CountableN (a, b),
FromListsN e (a, b) a, TrivialP a b) =>
Matrix e (a, b) a
forall e m k.
(Num e, CountableDimensionsN m k, CountableN (m, k),
FromListsN e (m, k) m, TrivialP m k) =>
Matrix e (m, k) m
kp1 @e @a @b
kp2' :: Matrix e (a, b) b
kp2' = (Num e, CountableDimensionsN b a, CountableN (a, b),
FromListsN e (a, b) b, TrivialP a b) =>
Matrix e (a, b) b
forall e m k.
(Num e, CountableDimensionsN k m, CountableN (m, k),
FromListsN e (m, k) k, TrivialP m k) =>
Matrix e (m, k) k
kp2 @e @a @b
in Matrix e a (a, b) -> Matrix e cols a -> Matrix e cols (a, b)
forall e cr rows cols.
Num e =>
Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
comp (Matrix e (a, b) a -> Matrix e a (a, b)
forall e cols rows. Matrix e cols rows -> Matrix e rows cols
tr Matrix e (a, b) a
kp1') Matrix e cols a
a Matrix e cols (a, b)
-> Matrix e cols (a, b) -> Matrix e cols (a, b)
forall a. Num a => a -> a -> a
* Matrix e b (a, b) -> Matrix e cols b -> Matrix e cols (a, b)
forall e cr rows cols.
Num e =>
Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
comp (Matrix e (a, b) b -> Matrix e b (a, b)
forall e cols rows. Matrix e cols rows -> Matrix e rows cols
tr Matrix e (a, b) b
kp2') Matrix e cols b
b
infixl 4 ><
(><) ::
forall e m p n q.
( Num e,
CountableDimensionsN m n,
CountableDimensionsN p q,
CountableDimensionsN (m, n) (p, q),
FromListsN e (m, n) m,
FromListsN e (m, n) n,
FromListsN e (p, q) p,
FromListsN e (p, q) q,
TrivialP m n,
TrivialP p q
) => Matrix e m p -> Matrix e n q -> Matrix e (m, n) (p, q)
>< :: Matrix e m p -> Matrix e n q -> Matrix e (m, n) (p, q)
(><) a :: Matrix e m p
a b :: Matrix e n q
b =
let kp1' :: Matrix e (m, n) m
kp1' = (Num e, CountableDimensionsN m n, CountableN (m, n),
FromListsN e (m, n) m, TrivialP m n) =>
Matrix e (m, n) m
forall e m k.
(Num e, CountableDimensionsN m k, CountableN (m, k),
FromListsN e (m, k) m, TrivialP m k) =>
Matrix e (m, k) m
kp1 @e @m @n
kp2' :: Matrix e (m, n) n
kp2' = (Num e, CountableDimensionsN n m, CountableN (m, n),
FromListsN e (m, n) n, TrivialP m n) =>
Matrix e (m, n) n
forall e m k.
(Num e, CountableDimensionsN k m, CountableN (m, k),
FromListsN e (m, k) k, TrivialP m k) =>
Matrix e (m, k) k
kp2 @e @m @n
in Matrix e (m, n) p -> Matrix e (m, n) q -> Matrix e (m, n) (p, q)
forall e cols a b.
(Num e, CountableDimensionsN a b, CountableN (a, b),
FromListsN e (a, b) a, FromListsN e (a, b) b, TrivialP a b) =>
Matrix e cols a -> Matrix e cols b -> Matrix e cols (a, b)
khatri (Matrix e m p -> Matrix e (m, n) m -> Matrix e (m, n) p
forall e cr rows cols.
Num e =>
Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
comp Matrix e m p
a Matrix e (m, n) m
kp1') (Matrix e n q -> Matrix e (m, n) n -> Matrix e (m, n) q
forall e cr rows cols.
Num e =>
Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows
comp Matrix e n q
b Matrix e (m, n) n
kp2')
abideJS :: Matrix e cols rows -> Matrix e cols rows
abideJS :: Matrix e cols rows -> Matrix e cols rows
abideJS (M m :: Matrix e (Normalize cols) (Normalize rows)
m) = Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cols) (Normalize rows)
-> Matrix e (Normalize cols) (Normalize rows)
forall e cols rows. Matrix e cols rows -> Matrix e cols rows
I.abideJS Matrix e (Normalize cols) (Normalize rows)
m)
abideSJ :: Matrix e cols rows -> Matrix e cols rows
abideSJ :: Matrix e cols rows -> Matrix e cols rows
abideSJ (M m :: Matrix e (Normalize cols) (Normalize rows)
m) = Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cols) (Normalize rows)
-> Matrix e (Normalize cols) (Normalize rows)
forall e cols rows. Matrix e cols rows -> Matrix e cols rows
I.abideSJ Matrix e (Normalize cols) (Normalize rows)
m)
tr :: Matrix e cols rows -> Matrix e rows cols
tr :: Matrix e cols rows -> Matrix e rows cols
tr (M m :: Matrix e (Normalize cols) (Normalize rows)
m) = Matrix e (Normalize rows) (Normalize cols) -> Matrix e rows cols
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cols) (Normalize rows)
-> Matrix e (Normalize rows) (Normalize cols)
forall e cols rows. Matrix e cols rows -> Matrix e rows cols
I.tr Matrix e (Normalize cols) (Normalize rows)
m)
selectM ::
( Num e,
FromListsN e b b,
CountableN b
) => Matrix e cols (Either a b) -> Matrix e a b -> Matrix e cols b
selectM :: Matrix e cols (Either a b) -> Matrix e a b -> Matrix e cols b
selectM (M m :: Matrix e (Normalize cols) (Normalize (Either a b))
m) (M y :: Matrix e (Normalize a) (Normalize b)
y) = Matrix e (Normalize cols) (Normalize b) -> Matrix e cols b
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M (Matrix e (Normalize cols) (Either (Normalize a) (Normalize b))
-> Matrix e (Normalize a) (Normalize b)
-> Matrix e (Normalize cols) (Normalize b)
forall e b cols a.
(Num e, FromLists e b b, Countable b) =>
Matrix e cols (Either a b) -> Matrix e a b -> Matrix e cols b
I.select Matrix e (Normalize cols) (Either (Normalize a) (Normalize b))
Matrix e (Normalize cols) (Normalize (Either a b))
m Matrix e (Normalize a) (Normalize b)
y)
cond ::
( Trivial a,
Trivial2 a,
Trivial3 a,
CountableN a,
FromListsN e () a,
FromListsN e a (),
FromListsN e a a,
Liftable e a Bool
)
=>
(a -> Bool) -> Matrix e a b -> Matrix e a b -> Matrix e a b
cond :: (a -> Bool) -> Matrix e a b -> Matrix e a b -> Matrix e a b
cond p :: a -> Bool
p (M a :: Matrix e (Normalize a) (Normalize b)
a) (M b :: Matrix e (Normalize a) (Normalize b)
b) = Matrix e (Normalize a) (Normalize b) -> Matrix e a b
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M ((a -> Bool)
-> Matrix e (Normalize (Normalize a)) (Normalize b)
-> Matrix e (Normalize (Normalize a)) (Normalize b)
-> Matrix e (Normalize (Normalize a)) (Normalize b)
forall cols e a rows.
(Trivial cols, Countable cols, FromLists e () cols,
FromLists e cols (), FromLists e cols cols, Bounded a, Enum a,
Num e, Ord e) =>
(a -> Bool)
-> Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows
I.cond a -> Bool
p Matrix e (Normalize a) (Normalize b)
Matrix e (Normalize (Normalize a)) (Normalize b)
a Matrix e (Normalize a) (Normalize b)
Matrix e (Normalize (Normalize a)) (Normalize b)
b)
pretty :: (CountableDimensionsN cols rows, Show e) => Matrix e cols rows -> String
pretty :: Matrix e cols rows -> String
pretty (M m :: Matrix e (Normalize cols) (Normalize rows)
m) = Matrix e (Normalize cols) (Normalize rows) -> String
forall cols rows e.
(CountableDimensions cols rows, Show e) =>
Matrix e cols rows -> String
I.pretty Matrix e (Normalize cols) (Normalize rows)
m
prettyPrint :: (CountableDimensionsN cols rows, Show e) => Matrix e cols rows -> IO ()
prettyPrint :: Matrix e cols rows -> IO ()
prettyPrint (M m :: Matrix e (Normalize cols) (Normalize rows)
m) = Matrix e (Normalize cols) (Normalize rows) -> IO ()
forall cols rows e.
(CountableDimensions cols rows, Show e) =>
Matrix e cols rows -> IO ()
I.prettyPrint Matrix e (Normalize cols) (Normalize rows)
m
zipWithM :: (e -> f -> g) -> Matrix e a b -> Matrix f a b -> Matrix g a b
zipWithM :: (e -> f -> g) -> Matrix e a b -> Matrix f a b -> Matrix g a b
zipWithM f :: e -> f -> g
f (M a :: Matrix e (Normalize a) (Normalize b)
a) (M b :: Matrix f (Normalize a) (Normalize b)
b) = Matrix g (Normalize a) (Normalize b) -> Matrix g a b
forall e cols rows.
Matrix e (Normalize cols) (Normalize rows) -> Matrix e cols rows
M ((e -> f -> g)
-> Matrix e (Normalize a) (Normalize b)
-> Matrix f (Normalize a) (Normalize b)
-> Matrix g (Normalize a) (Normalize b)
forall e f g cols rows.
(e -> f -> g)
-> Matrix e cols rows -> Matrix f cols rows -> Matrix g cols rows
I.zipWithM e -> f -> g
f Matrix e (Normalize a) (Normalize b)
a Matrix f (Normalize a) (Normalize b)
b)