rings-0.1.3: Ring-like objects.

Safe HaskellSafe
LanguageHaskell2010

Data.Semimodule

Contents

Synopsis

Left modules

class (Semiring l, (Additive - Monoid) a) => LeftSemimodule l a where Source #

Left semimodule over a commutative semiring.

All instances must satisfy the following identities:

lscale s (x + y) = lscale s x + lscale s y
lscale (s1 + s2) x = lscale s1 x + lscale s2 x
lscale (s1 * s2) = lscale s1 . lscale s2
lscale zero = zero

When the ring of coefficients s is unital we must additionally have: lscale one = id

See the properties module for a detailed specification of the laws.

Methods

lscale :: l -> a -> a Source #

Left-multiply by a scalar.

Instances
Semiring a => LeftSemimodule a a Source # 
Instance details

Defined in Data.Semimodule

Methods

lscale :: a -> a -> a Source #

Ring a => LeftSemimodule a (Complex a) Source # 
Instance details

Defined in Data.Semimodule

Methods

lscale :: a -> Complex a -> Complex a Source #

Semiring a => LeftSemimodule a (Ratio a) Source # 
Instance details

Defined in Data.Semimodule

Methods

lscale :: a -> Ratio a -> Ratio a Source #

Semiring a => LeftSemimodule a (V4 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: a -> V4 a -> V4 a Source #

Semiring a => LeftSemimodule a (V3 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: a -> V3 a -> V3 a Source #

Semiring a => LeftSemimodule a (V2 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: a -> V2 a -> V2 a Source #

Semiring a => LeftSemimodule a (V1 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: a -> V1 a -> V1 a Source #

(LeftSemimodule l a, LeftSemimodule l b) => LeftSemimodule l (a, b) Source # 
Instance details

Defined in Data.Semimodule

Methods

lscale :: l -> (a, b) -> (a, b) Source #

LeftSemimodule l a => LeftSemimodule l (Op a e) Source # 
Instance details

Defined in Data.Semimodule

Methods

lscale :: l -> Op a e -> Op a e Source #

LeftSemimodule l a => LeftSemimodule l (e -> a) Source # 
Instance details

Defined in Data.Semimodule

Methods

lscale :: l -> (e -> a) -> e -> a Source #

Semiring a => LeftSemimodule a (Cov a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

lscale :: a -> Cov a b -> Cov a b Source #

Semiring a => LeftSemimodule a (Vec a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

lscale :: a -> Vec a b -> Vec a b Source #

(LeftSemimodule l a, LeftSemimodule l b, LeftSemimodule l c) => LeftSemimodule l (a, b, c) Source # 
Instance details

Defined in Data.Semimodule

Methods

lscale :: l -> (a, b, c) -> (a, b, c) Source #

Semiring a => LeftSemimodule a (Lin a b c) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

lscale :: a -> Lin a b c -> Lin a b c Source #

Semiring a => LeftSemimodule (M44 a) (M44 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M44 a -> M44 a -> M44 a Source #

Semiring a => LeftSemimodule (M44 a) (M43 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M44 a -> M43 a -> M43 a Source #

Semiring a => LeftSemimodule (M44 a) (M42 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M44 a -> M42 a -> M42 a Source #

Semiring a => LeftSemimodule (M44 a) (M41 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M44 a -> M41 a -> M41 a Source #

Semiring a => LeftSemimodule (M33 a) (M34 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M33 a -> M34 a -> M34 a Source #

Semiring a => LeftSemimodule (M33 a) (M33 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M33 a -> M33 a -> M33 a Source #

Semiring a => LeftSemimodule (M33 a) (M32 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M33 a -> M32 a -> M32 a Source #

Semiring a => LeftSemimodule (M33 a) (M31 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M33 a -> M31 a -> M31 a Source #

Semiring a => LeftSemimodule (M22 a) (M24 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M22 a -> M24 a -> M24 a Source #

Semiring a => LeftSemimodule (M22 a) (M23 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M22 a -> M23 a -> M23 a Source #

Semiring a => LeftSemimodule (M22 a) (M22 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M22 a -> M22 a -> M22 a Source #

Semiring a => LeftSemimodule (M22 a) (M21 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M22 a -> M21 a -> M21 a Source #

Semiring a => LeftSemimodule (M11 a) (M14 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M11 a -> M14 a -> M14 a Source #

Semiring a => LeftSemimodule (M11 a) (M13 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M11 a -> M13 a -> M13 a Source #

Semiring a => LeftSemimodule (M11 a) (M12 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M11 a -> M12 a -> M12 a Source #

Semiring a => LeftSemimodule (M11 a) (M11 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

lscale :: M11 a -> M11 a -> M11 a Source #

Counital a b => LeftSemimodule (End a b) (Cov a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

lscale :: End a b -> Cov a b -> Cov a b Source #

Semiring a => LeftSemimodule (End a b) (Vec a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

lscale :: End a b -> Vec a b -> Vec a b Source #

Counital a b => LeftSemimodule (Lin a b b) (Lin a b c) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

lscale :: Lin a b b -> Lin a b c -> Lin a b c Source #

(*.) :: LeftSemimodule l a => l -> a -> a infixr 7 Source #

Left-multiply a module element by a scalar.

(/.) :: Semifield a => Functor f => a -> f a -> f a infixr 7 Source #

Right-divide a vector by a scalar (on the left).

(\.) :: Semifield a => Functor f => a -> f a -> f a infixr 7 Source #

Left-divide a vector by a scalar.

lerp :: LeftModule r a => r -> a -> a -> a Source #

Linearly interpolate between two vectors.

>>> u = V3 (1 :% 1) (2 :% 1) (3 :% 1) :: V3 Rational
>>> v = V3 (2 :% 1) (4 :% 1) (6 :% 1) :: V3 Rational
>>> r = 1 :% 2 :: Rational
>>> lerp r u v
V3 (6 % 4) (12 % 4) (18 % 4)

lscaleDef :: Semiring a => Functor f => a -> f a -> f a infixr 7 Source #

Default definition of lscale for a free module.

negateDef :: LeftModule Integer a => a -> a Source #

Default definition of << for a commutative group.

Right modules

class (Semiring r, (Additive - Monoid) a) => RightSemimodule r a where Source #

Right semimodule over a commutative semiring.

The laws for right semimodules are analagous to those of left semimodules.

See the properties module for a detailed specification.

Methods

rscale :: r -> a -> a Source #

Right-multiply by a scalar.

Instances
Semiring a => RightSemimodule a a Source # 
Instance details

Defined in Data.Semimodule

Methods

rscale :: a -> a -> a Source #

Semiring a => RightSemimodule a (Ratio a) Source # 
Instance details

Defined in Data.Semimodule

Methods

rscale :: a -> Ratio a -> Ratio a Source #

Semiring a => RightSemimodule a (V4 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: a -> V4 a -> V4 a Source #

Semiring a => RightSemimodule a (V3 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: a -> V3 a -> V3 a Source #

Semiring a => RightSemimodule a (V2 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: a -> V2 a -> V2 a Source #

Semiring a => RightSemimodule a (V1 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: a -> V1 a -> V1 a Source #

(RightSemimodule r a, RightSemimodule r b) => RightSemimodule r (a, b) Source # 
Instance details

Defined in Data.Semimodule

Methods

rscale :: r -> (a, b) -> (a, b) Source #

RightSemimodule r a => RightSemimodule r (Op a e) Source # 
Instance details

Defined in Data.Semimodule

Methods

rscale :: r -> Op a e -> Op a e Source #

RightSemimodule r a => RightSemimodule r (e -> a) Source # 
Instance details

Defined in Data.Semimodule

Methods

rscale :: r -> (e -> a) -> e -> a Source #

Semiring a => RightSemimodule a (Cov a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

rscale :: a -> Cov a b -> Cov a b Source #

Semiring a => RightSemimodule a (Vec a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

rscale :: a -> Vec a b -> Vec a b Source #

(RightSemimodule r a, RightSemimodule r b, RightSemimodule r c) => RightSemimodule r (a, b, c) Source # 
Instance details

Defined in Data.Semimodule

Methods

rscale :: r -> (a, b, c) -> (a, b, c) Source #

Semiring a => RightSemimodule a (Lin a b m) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

rscale :: a -> Lin a b m -> Lin a b m Source #

Semiring a => RightSemimodule (M44 a) (M44 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M44 a -> M44 a -> M44 a Source #

Semiring a => RightSemimodule (M44 a) (M34 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M44 a -> M34 a -> M34 a Source #

Semiring a => RightSemimodule (M44 a) (M24 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M44 a -> M24 a -> M24 a Source #

Semiring a => RightSemimodule (M44 a) (M14 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M44 a -> M14 a -> M14 a Source #

Semiring a => RightSemimodule (M33 a) (M43 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M33 a -> M43 a -> M43 a Source #

Semiring a => RightSemimodule (M33 a) (M33 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M33 a -> M33 a -> M33 a Source #

Semiring a => RightSemimodule (M33 a) (M23 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M33 a -> M23 a -> M23 a Source #

Semiring a => RightSemimodule (M33 a) (M13 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M33 a -> M13 a -> M13 a Source #

Semiring a => RightSemimodule (M22 a) (M42 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M22 a -> M42 a -> M42 a Source #

Semiring a => RightSemimodule (M22 a) (M32 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M22 a -> M32 a -> M32 a Source #

Semiring a => RightSemimodule (M22 a) (M22 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M22 a -> M22 a -> M22 a Source #

Semiring a => RightSemimodule (M22 a) (M12 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M22 a -> M12 a -> M12 a Source #

Semiring a => RightSemimodule (M11 a) (M41 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M11 a -> M41 a -> M41 a Source #

Semiring a => RightSemimodule (M11 a) (M31 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M11 a -> M31 a -> M31 a Source #

Semiring a => RightSemimodule (M11 a) (M21 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M11 a -> M21 a -> M21 a Source #

Semiring a => RightSemimodule (M11 a) (M11 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

rscale :: M11 a -> M11 a -> M11 a Source #

Counital a b => RightSemimodule (End a b) (Cov a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

rscale :: End a b -> Cov a b -> Cov a b Source #

Semiring a => RightSemimodule (End a b) (Vec a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

rscale :: End a b -> Vec a b -> Vec a b Source #

Counital a c => RightSemimodule (Lin a c c) (Lin a b c) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

rscale :: Lin a c c -> Lin a b c -> Lin a b c Source #

(.*) :: RightSemimodule r a => a -> r -> a infixl 7 Source #

Right-multiply a module element by a scalar.

(./) :: Semifield a => Functor f => f a -> a -> f a infixl 7 Source #

Right-divide a vector by a scalar.

(.\) :: Semifield a => Functor f => f a -> a -> f a infixl 7 Source #

Left-divide a vector by a scalar (on the right).

rscaleDef :: Semiring a => Functor f => a -> f a -> f a infixl 7 Source #

Default definition of rscale for a free module.

Bimodules

type Bimodule l r a = (LeftModule l a, RightModule r a, Bisemimodule l r a) Source #

type FreeModule a f = (Free f, (Additive - Group) (f a), Bimodule a a (f a)) Source #

type FreeSemimodule a f = (Free f, Bisemimodule a a (f a)) Source #

class (LeftSemimodule l a, RightSemimodule r a) => Bisemimodule l r a where Source #

Bisemimodule over a commutative semiring.

lscale l . rscale r = rscale r . lscale l

Minimal complete definition

Nothing

Methods

discale :: l -> r -> a -> a Source #

Left and right-multiply by two scalars.

Instances
Semiring a => Bisemimodule a a a Source # 
Instance details

Defined in Data.Semimodule

Methods

discale :: a -> a -> a -> a Source #

Semiring a => Bisemimodule a a (Ratio a) Source # 
Instance details

Defined in Data.Semimodule

Methods

discale :: a -> a -> Ratio a -> Ratio a Source #

Semiring a => Bisemimodule a a (V4 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: a -> a -> V4 a -> V4 a Source #

Semiring a => Bisemimodule a a (V3 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: a -> a -> V3 a -> V3 a Source #

Semiring a => Bisemimodule a a (V2 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: a -> a -> V2 a -> V2 a Source #

Semiring a => Bisemimodule a a (V1 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: a -> a -> V1 a -> V1 a Source #

(Bisemimodule r r a, Bisemimodule r r b) => Bisemimodule r r (a, b) Source # 
Instance details

Defined in Data.Semimodule

Methods

discale :: r -> r -> (a, b) -> (a, b) Source #

Bisemimodule r r a => Bisemimodule r r (Op a e) Source # 
Instance details

Defined in Data.Semimodule

Methods

discale :: r -> r -> Op a e -> Op a e Source #

Bisemimodule r r a => Bisemimodule r r (e -> a) Source # 
Instance details

Defined in Data.Semimodule

Methods

discale :: r -> r -> (e -> a) -> e -> a Source #

Bisemimodule a a a => Bisemimodule a a (Cov a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

discale :: a -> a -> Cov a b -> Cov a b Source #

Bisemimodule a a a => Bisemimodule a a (Vec a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

discale :: a -> a -> Vec a b -> Vec a b Source #

(Bisemimodule r r a, Bisemimodule r r b, Bisemimodule r r c) => Bisemimodule r r (a, b, c) Source # 
Instance details

Defined in Data.Semimodule

Methods

discale :: r -> r -> (a, b, c) -> (a, b, c) Source #

Bisemimodule a a a => Bisemimodule a a (Lin a b c) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

discale :: a -> a -> Lin a b c -> Lin a b c Source #

Semiring a => Bisemimodule (M44 a) (M33 a) (M43 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M44 a -> M33 a -> M43 a -> M43 a Source #

Semiring a => Bisemimodule (M44 a) (M22 a) (M42 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M44 a -> M22 a -> M42 a -> M42 a Source #

Semiring a => Bisemimodule (M44 a) (M11 a) (M41 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M44 a -> M11 a -> M41 a -> M41 a Source #

Semiring a => Bisemimodule (M33 a) (M44 a) (M34 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M33 a -> M44 a -> M34 a -> M34 a Source #

Semiring a => Bisemimodule (M33 a) (M22 a) (M32 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M33 a -> M22 a -> M32 a -> M32 a Source #

Semiring a => Bisemimodule (M33 a) (M11 a) (M31 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M33 a -> M11 a -> M31 a -> M31 a Source #

Semiring a => Bisemimodule (M22 a) (M44 a) (M24 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M22 a -> M44 a -> M24 a -> M24 a Source #

Semiring a => Bisemimodule (M22 a) (M33 a) (M23 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M22 a -> M33 a -> M23 a -> M23 a Source #

Semiring a => Bisemimodule (M22 a) (M11 a) (M21 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M22 a -> M11 a -> M21 a -> M21 a Source #

Semiring a => Bisemimodule (M11 a) (M44 a) (M14 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M11 a -> M44 a -> M14 a -> M14 a Source #

Semiring a => Bisemimodule (M11 a) (M33 a) (M13 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M11 a -> M33 a -> M13 a -> M13 a Source #

Semiring a => Bisemimodule (M11 a) (M22 a) (M12 a) Source # 
Instance details

Defined in Data.Semimodule.Finite

Methods

discale :: M11 a -> M22 a -> M12 a -> M12 a Source #

Counital a b => Bisemimodule (End a b) (End a b) (Cov a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

discale :: End a b -> End a b -> Cov a b -> Cov a b Source #

Semiring a => Bisemimodule (End a b) (End a b) (Vec a b) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

discale :: End a b -> End a b -> Vec a b -> Vec a b Source #

(Counital a b, Counital a c) => Bisemimodule (Lin a b b) (Lin a c c) (Lin a b c) Source # 
Instance details

Defined in Data.Semimodule.Free

Methods

discale :: Lin a b b -> Lin a c c -> Lin a b c -> Lin a b c Source #

Algebras

type FreeAlgebra a f = (FreeSemimodule a f, Algebra a (Rep f)) Source #

An algebra over a free module f.

Note that this is distinct from a free algebra.

class Semiring a => Algebra a b where Source #

An algebra over a semiring.

Note that the algebra needn't be associative.

Methods

joined :: (b -> b -> a) -> b -> a Source #

joined = runLin diagonal . uncurry
Instances
Semiring a => Algebra a IntSet Source # 
Instance details

Defined in Data.Semimodule

Methods

joined :: (IntSet -> IntSet -> a) -> IntSet -> a Source #

Semiring a => Algebra a () Source # 
Instance details

Defined in Data.Semimodule

Methods

joined :: (() -> () -> a) -> () -> a Source #

Semiring r => Algebra r E4 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

joined :: (E4 -> E4 -> r) -> E4 -> r Source #

Semiring r => Algebra r E3 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

joined :: (E3 -> E3 -> r) -> E3 -> r Source #

Semiring r => Algebra r E2 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

joined :: (E2 -> E2 -> r) -> E2 -> r Source #

Semiring r => Algebra r E1 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

joined :: (E1 -> E1 -> r) -> E1 -> r Source #

(Semiring a, Ord b) => Algebra a (Set b) Source # 
Instance details

Defined in Data.Semimodule

Methods

joined :: (Set b -> Set b -> a) -> Set b -> a Source #

Semiring a => Algebra a (Seq b) Source # 
Instance details

Defined in Data.Semimodule

Methods

joined :: (Seq b -> Seq b -> a) -> Seq b -> a Source #

Semiring a => Algebra a [b] Source #

Tensor algebra on b.

>>> joined (<>) [1..3 :: Int]
[1,2,3,1,2,3,1,2,3,1,2,3]
>>> joined (\f g -> fold (f ++ g)) [1..3] :: Int
24
Instance details

Defined in Data.Semimodule

Methods

joined :: ([b] -> [b] -> a) -> [b] -> a Source #

(Algebra a b1, Algebra a b2) => Algebra a (b1, b2) Source # 
Instance details

Defined in Data.Semimodule

Methods

joined :: ((b1, b2) -> (b1, b2) -> a) -> (b1, b2) -> a Source #

(Algebra a b1, Algebra a b2, Algebra a b3) => Algebra a (b1, b2, b3) Source # 
Instance details

Defined in Data.Semimodule

Methods

joined :: ((b1, b2, b3) -> (b1, b2, b3) -> a) -> (b1, b2, b3) -> a Source #

Unital algebras

type FreeUnital a f = (FreeAlgebra a f, Unital a (Rep f)) Source #

A unital algebra over a free semimodule f.

class Algebra a b => Unital a b where Source #

A unital algebra over a semiring.

Methods

unital :: a -> b -> a Source #

unital = runLin initial . const
Instances
Semiring a => Unital a IntSet Source # 
Instance details

Defined in Data.Semimodule

Methods

unital :: a -> IntSet -> a Source #

Semiring a => Unital a () Source # 
Instance details

Defined in Data.Semimodule

Methods

unital :: a -> () -> a Source #

Semiring r => Unital r E4 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

unital :: r -> E4 -> r Source #

Semiring r => Unital r E3 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

unital :: r -> E3 -> r Source #

Semiring r => Unital r E2 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

unital :: r -> E2 -> r Source #

Semiring r => Unital r E1 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

unital :: r -> E1 -> r Source #

(Semiring a, Ord b) => Unital a (Set b) Source # 
Instance details

Defined in Data.Semimodule

Methods

unital :: a -> Set b -> a Source #

Semiring a => Unital a (Seq b) Source # 
Instance details

Defined in Data.Semimodule

Methods

unital :: a -> Seq b -> a Source #

Semiring a => Unital a [b] Source # 
Instance details

Defined in Data.Semimodule

Methods

unital :: a -> [b] -> a Source #

(Unital a b1, Unital a b2) => Unital a (b1, b2) Source # 
Instance details

Defined in Data.Semimodule

Methods

unital :: a -> (b1, b2) -> a Source #

(Unital a b1, Unital a b2, Unital a b3) => Unital a (b1, b2, b3) Source # 
Instance details

Defined in Data.Semimodule

Methods

unital :: a -> (b1, b2, b3) -> a Source #

Coalgebras

type FreeCoalgebra a f = (FreeSemimodule a f, Coalgebra a (Rep f)) Source #

A coalgebra over a free semimodule f.

class Semiring a => Coalgebra a c where Source #

A coalgebra over a semiring.

Methods

cojoined :: (c -> a) -> c -> c -> a Source #

cojoined = curry . runLin codiagonal
Instances
Semiring a => Coalgebra a IntSet Source #

The free commutative band coalgebra over Int

Instance details

Defined in Data.Semimodule

Methods

cojoined :: (IntSet -> a) -> IntSet -> IntSet -> a Source #

Semiring a => Coalgebra a () Source # 
Instance details

Defined in Data.Semimodule

Methods

cojoined :: (() -> a) -> () -> () -> a Source #

Semiring r => Coalgebra r E4 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

cojoined :: (E4 -> r) -> E4 -> E4 -> r Source #

Semiring r => Coalgebra r E3 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

cojoined :: (E3 -> r) -> E3 -> E3 -> r Source #

Semiring r => Coalgebra r E2 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

cojoined :: (E2 -> r) -> E2 -> E2 -> r Source #

Semiring r => Coalgebra r E1 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

cojoined :: (E1 -> r) -> E1 -> E1 -> r Source #

(Semiring a, Ord c) => Coalgebra a (Set c) Source #

The free commutative band coalgebra

Instance details

Defined in Data.Semimodule

Methods

cojoined :: (Set c -> a) -> Set c -> Set c -> a Source #

Semiring a => Coalgebra a (Seq c) Source # 
Instance details

Defined in Data.Semimodule

Methods

cojoined :: (Seq c -> a) -> Seq c -> Seq c -> a Source #

Semiring a => Coalgebra a [c] Source #

The tensor coalgebra on c.

Instance details

Defined in Data.Semimodule

Methods

cojoined :: ([c] -> a) -> [c] -> [c] -> a Source #

Algebra a b => Coalgebra a (b -> a) Source # 
Instance details

Defined in Data.Semimodule

Methods

cojoined :: ((b -> a) -> a) -> (b -> a) -> (b -> a) -> a Source #

(Coalgebra a c1, Coalgebra a c2) => Coalgebra a (c1, c2) Source # 
Instance details

Defined in Data.Semimodule

Methods

cojoined :: ((c1, c2) -> a) -> (c1, c2) -> (c1, c2) -> a Source #

(Coalgebra a c1, Coalgebra a c2, Coalgebra a c3) => Coalgebra a (c1, c2, c3) Source # 
Instance details

Defined in Data.Semimodule

Methods

cojoined :: ((c1, c2, c3) -> a) -> (c1, c2, c3) -> (c1, c2, c3) -> a Source #

Unital coalgebras

type FreeCounital a f = (FreeCoalgebra a f, Counital a (Rep f)) Source #

A counital coalgebra over a free semimodule f.

class Coalgebra a c => Counital a c where Source #

A counital coalgebra over a semiring.

Methods

counital :: (c -> a) -> a Source #

Instances
Semiring a => Counital a IntSet Source # 
Instance details

Defined in Data.Semimodule

Methods

counital :: (IntSet -> a) -> a Source #

Semiring a => Counital a () Source # 
Instance details

Defined in Data.Semimodule

Methods

counital :: (() -> a) -> a Source #

Semiring r => Counital r E4 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

counital :: (E4 -> r) -> r Source #

Semiring r => Counital r E3 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

counital :: (E3 -> r) -> r Source #

Semiring r => Counital r E2 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

counital :: (E2 -> r) -> r Source #

Semiring r => Counital r E1 Source # 
Instance details

Defined in Data.Semimodule.Basis

Methods

counital :: (E1 -> r) -> r Source #

(Semiring a, Ord c) => Counital a (Set c) Source # 
Instance details

Defined in Data.Semimodule

Methods

counital :: (Set c -> a) -> a Source #

Semiring a => Counital a (Seq c) Source # 
Instance details

Defined in Data.Semimodule

Methods

counital :: (Seq c -> a) -> a Source #

Semiring a => Counital a [c] Source # 
Instance details

Defined in Data.Semimodule

Methods

counital :: ([c] -> a) -> a Source #

Unital a b => Counital a (b -> a) Source # 
Instance details

Defined in Data.Semimodule

Methods

counital :: ((b -> a) -> a) -> a Source #

(Counital a c1, Counital a c2) => Counital a (c1, c2) Source # 
Instance details

Defined in Data.Semimodule

Methods

counital :: ((c1, c2) -> a) -> a Source #

(Counital a c1, Counital a c2, Counital a c3) => Counital a (c1, c2, c3) Source # 
Instance details

Defined in Data.Semimodule

Methods

counital :: ((c1, c2, c3) -> a) -> a Source #

Bialgebras

type FreeBialgebra a f = (FreeAlgebra a f, FreeCoalgebra a f, Bialgebra a (Rep f)) Source #

A bialgebra over a free semimodule f.

class (Unital a b, Counital a b) => Bialgebra a b Source #

A bialgebra over a semiring.

Instances
Semiring a => Bialgebra a () Source # 
Instance details

Defined in Data.Semimodule

Semiring r => Bialgebra r E4 Source # 
Instance details

Defined in Data.Semimodule.Basis

Semiring r => Bialgebra r E3 Source # 
Instance details

Defined in Data.Semimodule.Basis

Semiring r => Bialgebra r E2 Source # 
Instance details

Defined in Data.Semimodule.Basis

Semiring r => Bialgebra r E1 Source # 
Instance details

Defined in Data.Semimodule.Basis

Semiring a => Bialgebra a (Seq b) Source # 
Instance details

Defined in Data.Semimodule

Semiring a => Bialgebra a [b] Source # 
Instance details

Defined in Data.Semimodule

(Bialgebra a b1, Bialgebra a b2) => Bialgebra a (b1, b2) Source # 
Instance details

Defined in Data.Semimodule

(Bialgebra a b1, Bialgebra a b2, Bialgebra a b3) => Bialgebra a (b1, b2, b3) Source # 
Instance details

Defined in Data.Semimodule