gasp-1.4.0.0: A framework of algebraic classes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Algebra.Category.BlockMatrix

Documentation

data M s a b where Source #

Constructors

Zero :: M s a b 
Diag :: s -> M s a a 
(:▵) :: M s a b -> M s a c -> M s a (b c) 
(:▿) :: M s b a -> M s c a -> M s (b c) a 
EmptyL :: M s Zero a 
EmptyR :: M s a Zero 

Instances

Instances details
Ring s => Category (M s :: Type -> Type -> Type) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Associated Types

type Obj (M s) :: k -> Constraint Source #

Methods

(.) :: forall (a :: k) (b :: k) (c :: k). (Obj (M s) a, Obj (M s) b, Obj (M s) c) => M s b c -> M s a b -> M s a c Source #

id :: forall (a :: k). Obj (M s) a => M s a a Source #

Ring s => Braided ((⊕) :: Type -> Type -> Type) (Zero :: Type) (M s :: Type -> Type -> Type) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

swap :: forall (a :: k) (b :: k). (Obj (M s) a, Obj (M s) b) => M s (a b) (b a) Source #

swap_ :: forall (a :: k) (b :: k). (Obj (M s) a, Obj (M s) b) => M s (a b) (b a) Source #

Ring s => Cartesian ((⊕) :: Type -> Type -> Type) (Zero :: Type) (M s :: Type -> Type -> Type) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

exl :: forall (a :: k) (b :: k). O2 (M s) a b => M s (a b) a Source #

exr :: forall (a :: k) (b :: k). O2 (M s) a b => M s (a b) b Source #

dis :: forall (a :: k). Obj (M s) a => M s a Zero Source #

dup :: forall (a :: k). Obj (M s) a => M s a (a a) Source #

(▵) :: forall (a :: k) (b :: k) (c :: k). (Obj (M s) a, Obj (M s) b, Obj (M s) c) => M s a b -> M s a c -> M s a (b c) Source #

Ring s => CoCartesian ((⊕) :: Type -> Type -> Type) (Zero :: Type) (M s :: Type -> Type -> Type) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

inl :: forall (a :: k) (b :: k). O2 (M s) a b => M s a (a b) Source #

inr :: forall (a :: k) (b :: k). O2 (M s) a b => M s b (a b) Source #

new :: forall (a :: k). Obj (M s) a => M s Zero a Source #

jam :: forall (a :: k). Obj (M s) a => M s (a a) a Source #

(▿) :: forall (a :: k) (b :: k) (c :: k). (Obj (M s) a, Obj (M s) b, Obj (M s) c) => M s b a -> M s c a -> M s (b c) a Source #

Ring s => Monoidal ((⊕) :: Type -> Type -> Type) (Zero :: Type) (M s :: Type -> Type -> Type) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

(⊗) :: forall (a :: k) (b :: k) (c :: k) (d :: k). (Obj (M s) a, Obj (M s) b, Obj (M s) c, Obj (M s) d) => M s a b -> M s c d -> M s (a c) (b d) Source #

assoc :: forall (a :: k) (b :: k) (c :: k). (Obj (M s) a, Obj (M s) b, Obj (M s) c) => M s ((a b) c) (a (b c)) Source #

assoc_ :: forall (a :: k) (b :: k) (c :: k). (Obj (M s) a, Obj (M s) b, Obj (M s) c) => M s (a (b c)) ((a b) c) Source #

unitorR :: forall (a :: k). (Obj (M s) a, Obj (M s) Zero) => M s a (a Zero) Source #

unitorR_ :: forall (a :: k). (Obj (M s) a, Obj (M s) Zero) => M s (a Zero) a Source #

unitorL :: forall (a :: k). (Obj (M s) a, Obj (M s) Zero) => M s a (Zero a) Source #

unitorL_ :: forall (a :: k). (Obj (M s) a, Obj (M s) Zero) => M s (Zero a) a Source #

Ring s => Symmetric ((⊕) :: Type -> Type -> Type) (Zero :: Type) (M s :: Type -> Type -> Type) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Ring s => Scalable s (M s a b) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

(*^) :: s -> M s a b -> M s a b Source #

Show s => Show (M s a b) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

showsPrec :: Int -> M s a b -> ShowS #

show :: M s a b -> String #

showList :: [M s a b] -> ShowS #

Additive s => Additive (M s a b) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

(+) :: M s a b -> M s a b -> M s a b Source #

zero :: M s a b Source #

times :: Natural -> M s a b -> M s a b Source #

Group s => Group (M s a b) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

(-) :: M s a b -> M s a b -> M s a b Source #

subtract :: M s a b -> M s a b -> M s a b Source #

negate :: M s a b -> M s a b Source #

mult :: Integer -> M s a b -> M s a b Source #

(Show s, Additive s, TestEqual s) => TestEqual (M s a b) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

(=.=) :: M s a b -> M s a b -> Property Source #

type Obj (M s :: Type -> Type -> Type) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

type Obj (M s :: Type -> Type -> Type) = Trivial :: Type -> Constraint

testZero :: (Additive s, TestEqual s) => M s a b -> Property Source #

findSplit :: M s a (b c) -> (M s a b, M s a c) Source #

findSplit' :: M s (b c) a -> (M s b a, M s c a) Source #

transpose :: M s a b -> M s b a Source #