algebra-4.1: Constructive abstract algebra

Safe HaskellNone

Numeric.Map

Synopsis

Documentation

newtype Map r b a Source

linear maps from elements of a free module to another free module over r

 f $# x + y = (f $# x) + (f $# y)
 f $# (r .* x) = r .* (f $# x)

Map r b a represents a linear mapping from a free module with basis a over r to a free module with basis b over r.

Note well the reversed direction of the arrow, due to the contravariance of change of basis!

This way enables we can employ arbitrary pure functions as linear maps by lifting them using arr, or build them by using the monad instance for Map r b. As a consequence Map is an instance of, well, almost everything.

Constructors

Map ((a -> r) -> b -> r) 

Instances

MonadReader b (Map r b) 
RightModule r s => RightModule r (Map s b m) 
LeftModule r s => LeftModule r (Map s b m) 
Arrow (Map r) 
Monoidal r => ArrowZero (Map r) 
Monoidal r => ArrowPlus (Map r) 
ArrowChoice (Map r) 
ArrowApply (Map r) 
Category (Map r) 
Semigroupoid (Map r) 
Monad (Map r b) 
Functor (Map r b) 
Monoidal r => MonadPlus (Map r b) 
Applicative (Map r b) 
Monoidal r => Alternative (Map r b) 
Monoidal r => Plus (Map r b) 
Additive r => Alt (Map r b) 
Apply (Map r b) 
Bind (Map r b) 
Abelian s => Abelian (Map s b a) 
Additive r => Additive (Map r b a) 
Monoidal s => Monoidal (Map s b a) 
Coalgebra r m => Semiring (Map r b m) 
Coalgebra r m => Multiplicative (Map r b m) 
Group s => Group (Map s b a) 
CounitalCoalgebra r m => Unital (Map r b m) 
(Rig r, CounitalCoalgebra r m) => Rig (Map r b m) 
(Ring r, CounitalCoalgebra r m) => Ring (Map r a m) 
(Commutative m, Coalgebra r m) => Commutative (Map r b m) 
Coalgebra r m => RightModule (Map r b m) (Map r b m) 
Coalgebra r m => LeftModule (Map r b m) (Map r b m) 

($@) :: Map r b a -> b -> Covector r aSource

extract a linear functional from a linear map

multMap :: Coalgebra r c => Map r (c, c) cSource

comultMap :: Algebra r a => Map r a (a, a)Source

(inefficiently) combine a linear combination of basis vectors to make a map. arrMap :: (Monoidal r, Semiring r) => (b -> [(r, a)]) -> Map r b a arrMap f = Map $ k b -> sum [ r * k a | (r, a) <- f b ]

convolveMap :: (Algebra r a, Coalgebra r c) => Map r a c -> Map r a c -> Map r a cSource

convolution given an associative algebra and coassociative coalgebra