concat-examples-0.3.0.0: Some examples of compiling to categories
Safe HaskellSafe-Inferred
LanguageHaskell2010

ConCat.Free.LinearRow

Description

Linear maps as "row-major" functor compositions

Documentation

type (:-*) a b s = b (a s) infixr 1 Source #

($*) :: forall s a b. (Zip a, Foldable a, Functor b, Num s) => (a :-* b) s -> a s -> b s infixr 9 Source #

lapplyL :: forall s a b. (Zip a, Foldable a, Functor b, Num s) => (a :-* b) s -> a s -> b s Source #

zeroL :: (Zeroable a, Zeroable b, Num s) => (a :-* b) s Source #

scaleL :: (Diagonal a, Num s) => s -> (a :-* a) s Source #

idL :: (Diagonal a, Num s) => (a :-* a) s Source #

compL :: (Zip a, Zip b, Zeroable a, Foldable b, Functor c, Num s) => (b :-* c) s -> (a :-* b) s -> (a :-* c) s Source #

exlL :: (Zeroable a, Diagonal a, Zeroable b, Num s) => ((a :*: b) :-* a) s Source #

exrL :: (Zeroable b, Diagonal b, Zeroable a, Num s) => ((a :*: b) :-* b) s Source #

crossL :: (Zeroable a, Zeroable b, Zeroable c, Zeroable d, Num s, Zip c, Zip d) => (a :-* c) s -> (b :-* d) s -> ((a :*: b) :-* (c :*: d)) s Source #

forkL :: (a :-* c) s -> (a :-* d) s -> (a :-* (c :*: d)) s Source #

dupL :: (Diagonal a, Num s) => (a :-* (a :*: a)) s Source #

itL :: (a :-* U1) s Source #

inlL :: (Zeroable a, Diagonal a, Zeroable b, Num s) => (a :-* (a :*: b)) s Source #

inrL :: (Zeroable a, Zeroable b, Diagonal b, Num s) => (b :-* (a :*: b)) s Source #

joinL :: Zip c => (a :-* c) s -> (b :-* c) s -> ((a :*: b) :-* c) s Source #

jamL :: (Diagonal a, Zip a, Num s) => ((a :*: a) :-* a) s Source #

newtype L s a b Source #

Constructors

L ((V s a :-* V s b) s) 

Instances

Instances details
(Num s, Diagonal (V s a), Coercible (Rep (L s a a)) (Rep (L s a b))) => CoerceCat (L s :: Type -> Type -> Type) (a :: Type) (b :: Type) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

coerceC :: L s a b Source #

(r ~ Rep a, V s r ~ V s a, Ok (L s) a) => RepCat (L s :: Type -> Type -> Type) (a :: Type) (r :: Type) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

reprC :: L s a r Source #

abstC :: L s r a Source #

(OkCAR (L s a b), IfCat (:>) (Rep (L s a b))) => IfCat (:>) (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

ifC :: IfT (:>) (L s a b) Source #

HasV s (Rep (L s a b)) => HasV s (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Associated Types

type V s (L s a b) :: Type -> Type Source #

Methods

toV :: L s a b -> V s (L s a b) s Source #

unV :: V s (L s a b) s -> L s a b Source #

BraidedPCat (L s) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

swapP :: Ok2 (L s) a b => L s (Prod (L s) a b) (Prod (L s) b a) Source #

Category (L s) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Associated Types

type Ok (L s) :: Type -> Constraint Source #

Methods

id :: Ok (L s) a => L s a a Source #

(.) :: forall b c a. Ok3 (L s) a b c => L s b c -> L s a b -> L s a c Source #

CoproductPCat (L s) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

inlP :: Ok2 (L s) a b => L s a (CoprodP (L s) a b) Source #

inrP :: Ok2 (L s) a b => L s b (CoprodP (L s) a b) Source #

jamP :: Ok (L s) a => L s (CoprodP (L s) a a) a Source #

MonoidalPCat (L s) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

(***) :: Ok4 (L s) a b c d => L s a c -> L s b d -> L s (Prod (L s) a b) (Prod (L s) c d) Source #

first :: forall a a' b. Ok3 (L s) a b a' => L s a a' -> L s (Prod (L s) a b) (Prod (L s) a' b) Source #

second :: Ok3 (L s) a b b' => L s b b' -> L s (Prod (L s) a b) (Prod (L s) a b') Source #

OkAdd (L s) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

okAdd :: Ok' (L s) a |- Sat Additive a Source #

ProductCat (L s) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

exl :: Ok2 (L s) a b => L s (Prod (L s) a b) a Source #

exr :: Ok2 (L s) a b => L s (Prod (L s) a b) b Source #

dup :: Ok (L s) a => L s a (Prod (L s) a a) Source #

(Foldable (V s a), Foldable (V s b), Show s) => Show (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

showsPrec :: Int -> L s a b -> ShowS Source #

show :: L s a b -> String Source #

showList :: [L s a b] -> ShowS Source #

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

Defined in ConCat.Free.LinearRow

Methods

zero :: L s a b Source #

(^+^) :: L s a b -> L s a b -> L s a b Source #

HasRep (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Associated Types

type Rep (L s a b) Source #

Methods

repr :: L s a b -> Rep (L s a b) Source #

abst :: Rep (L s a b) -> L s a b Source #

OkCAR (L s a b) => GenBuses (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

genBuses' :: Template u v -> [Source] -> BusesM (Buses (L s a b)) Source #

ty :: Ty Source #

unflattenB' :: State [Source] (Buses (L s a b)) Source #

Newtype (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Associated Types

type O (L s a b) Source #

Methods

pack :: O (L s a b) -> L s a b Source #

unpack :: L s a b -> O (L s a b) Source #

(Foldable (V s a), Foldable (V s b), Pretty s) => Pretty (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

pPrintPrec :: PrettyLevel -> Rational -> L s a b -> Doc Source #

pPrint :: L s a b -> Doc Source #

pPrintList :: PrettyLevel -> [L s a b] -> Doc Source #

type V s (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

type V s (L s a b) = V s (Rep (L s a b))
type Ok (L s) Source # 
Instance details

Defined in ConCat.Free.LinearRow

type Ok (L s) = OkLM s
type Rep (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

type Rep (L s a b) = (V s a :-* V s b) s
type Iv (L s a b) Source # 
Instance details

Defined in ConCat.Interval

type Iv (L s a b) = Iv (O (L s a b))
type O (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

type O (L s a b) = (V s a :-* V s b) s

type LR = L R Source #

flatten :: (Foldable (V s a), Foldable (V s b)) => L s a b -> [[s]] Source #

type OkLF f = (Foldable f, Zeroable f, Zip f, Diagonal f) Source #

type OkLM' s a = (Num s, HasV s a, OkLF (V s a)) Source #

class (Num s, Additive a, HasV s a, OkLF (V s a)) => OkLM s a Source #

Instances

Instances details
(Num s, Additive a, HasV s a, OkLF (V s a)) => OkLM s a Source # 
Instance details

Defined in ConCat.Free.LinearRow

OpCon (:*) (Sat (OkLM s) :: Type -> Type) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

inOp :: forall (a :: k) (b :: k). (Sat (OkLM s) a && Sat (OkLM s) b) |- Sat (OkLM s) (a :* b) Source #

zeroLM :: (Num s, Zeroable (V s a), Zeroable (V s b)) => L s a b Source #

addLM :: Ok2 (L s) a b => Binop (L s a b) Source #

lapply :: (Num s, Ok2 (L s) a b) => L s a b -> a -> b Source #

type HasL s a = (HasV s a, Diagonal (V s a), Num s) Source #

type HasLin s a b = (HasV s a, HasV s b, Diagonal (V s a), Representable (V s b), Num s) Source #

linear :: forall s a b. HasLin s a b => (a -> b) -> L s a b Source #

linearF :: forall s f g. (Diagonal f, Representable g, Num s) => (f s -> g s) -> (f :-* g) s Source #

scalarMul :: OkLM s a => s -> L s a a Source #

negateLM :: OkLM s a => L s a a Source #

lmap :: forall s a b. (a -> b) -> L s a b Source #