rings-0.0.3: Ring-like objects.

Safe HaskellSafe
LanguageHaskell2010

Data.Semimodule

Synopsis

Documentation

type Free f = (Representable f, Eq (Rep f)) Source #

type Basis b f = (Free f, Rep f ~ b) Source #

type Module r a = (Ring r, Group a, Semimodule r a) Source #

class (Semiring r, Semigroup a) => Semimodule r a where Source #

Semimodule over a commutative semiring.

All instances must satisfy the following identities:

 r *. (x <> y) == r *. x <> r *. y
 (r + s) *. x == r *. x <> s *. x
 (r * s) *. x == r *. (s *. x)

When the ring of coefficients r is unital we must additionally have:

 one *. x == x

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

Minimal complete definition

Nothing

Methods

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

Left-multiply by a scalar.

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

Right-multiply by a scalar.

Instances
Group a => Semimodule Integer a Source # 
Instance details

Defined in Data.Semimodule

Methods

(*.) :: Integer -> a -> a Source #

(.*) :: a -> Integer -> a Source #

Monoid a => Semimodule Natural a Source # 
Instance details

Defined in Data.Semimodule

Methods

(*.) :: Natural -> a -> a Source #

(.*) :: a -> Natural -> a Source #

Semigroup a => Semimodule () a Source # 
Instance details

Defined in Data.Semimodule

Methods

(*.) :: () -> a -> a Source #

(.*) :: a -> () -> a Source #

Semiring r => Semimodule r () Source # 
Instance details

Defined in Data.Semimodule

Methods

(*.) :: r -> () -> () Source #

(.*) :: () -> r -> () Source #

Semiring Bool => Semimodule Bool (Additive Bool) Source # 
Instance details

Defined in Data.Semimodule

Semiring Double => Semimodule Double (Additive Double) Source # 
Instance details

Defined in Data.Semimodule

Semiring Float => Semimodule Float (Additive Float) Source # 
Instance details

Defined in Data.Semimodule

Semiring Int => Semimodule Int (Additive Int) Source # 
Instance details

Defined in Data.Semimodule

Semiring Int8 => Semimodule Int8 (Additive Int8) Source # 
Instance details

Defined in Data.Semimodule

Semiring Int16 => Semimodule Int16 (Additive Int16) Source # 
Instance details

Defined in Data.Semimodule

Semiring Int32 => Semimodule Int32 (Additive Int32) Source # 
Instance details

Defined in Data.Semimodule

Semiring Int64 => Semimodule Int64 (Additive Int64) Source # 
Instance details

Defined in Data.Semimodule

Semiring Word => Semimodule Word (Additive Word) Source # 
Instance details

Defined in Data.Semimodule

Semiring Word8 => Semimodule Word8 (Additive Word8) Source # 
Instance details

Defined in Data.Semimodule

Semiring Word16 => Semimodule Word16 (Additive Word16) Source # 
Instance details

Defined in Data.Semimodule

Semiring Word32 => Semimodule Word32 (Additive Word32) Source # 
Instance details

Defined in Data.Semimodule

Semiring Word64 => Semimodule Word64 (Additive Word64) Source # 
Instance details

Defined in Data.Semimodule

(Ring a, Semimodule r a) => Semimodule r (Additive (Complex a)) Source # 
Instance details

Defined in Data.Semimodule

Methods

(*.) :: r -> Additive (Complex a) -> Additive (Complex a) Source #

(.*) :: Additive (Complex a) -> r -> Additive (Complex a) Source #

(Semiring a, Semimodule r a) => Semimodule r (Additive (Ratio a)) Source # 
Instance details

Defined in Data.Semimodule

Methods

(*.) :: r -> Additive (Ratio a) -> Additive (Ratio a) Source #

(.*) :: Additive (Ratio a) -> r -> Additive (Ratio a) Source #

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

Defined in Data.Semimodule.Vector

Methods

(*.) :: a -> V4 a -> V4 a Source #

(.*) :: V4 a -> a -> V4 a Source #

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

Defined in Data.Semimodule.Vector

Methods

(*.) :: a -> V3 a -> V3 a Source #

(.*) :: V3 a -> a -> V3 a Source #

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

Defined in Data.Semimodule.Vector

Methods

(*.) :: a -> V2 a -> V2 a Source #

(.*) :: V2 a -> a -> V2 a Source #

Semiring a => Semimodule a (Quaternion a) Source # 
Instance details

Defined in Data.Algebra.Quaternion

Methods

(*.) :: a -> Quaternion a -> Quaternion a Source #

(.*) :: Quaternion a -> a -> Quaternion a Source #

Semiring Uni => Semimodule Uni (Additive Uni) Source # 
Instance details

Defined in Data.Semimodule

Semiring Deci => Semimodule Deci (Additive Deci) Source # 
Instance details

Defined in Data.Semimodule

Semiring Centi => Semimodule Centi (Additive Centi) Source # 
Instance details

Defined in Data.Semimodule

Semiring Milli => Semimodule Milli (Additive Milli) Source # 
Instance details

Defined in Data.Semimodule

Semiring Micro => Semimodule Micro (Additive Micro) Source # 
Instance details

Defined in Data.Semimodule

Semiring Nano => Semimodule Nano (Additive Nano) Source # 
Instance details

Defined in Data.Semimodule

Semiring Pico => Semimodule Pico (Additive Pico) Source # 
Instance details

Defined in Data.Semimodule

Semiring CFloat => Semimodule CFloat (Additive CFloat) Source # 
Instance details

Defined in Data.Semimodule

Semiring CDouble => Semimodule CDouble (Additive CDouble) Source # 
Instance details

Defined in Data.Semimodule

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

Defined in Data.Semimodule

Methods

(*.) :: r -> (a, b) -> (a, b) Source #

(.*) :: (a, b) -> r -> (a, b) Source #

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

Defined in Data.Semimodule

Methods

(*.) :: r -> (e -> a) -> e -> a Source #

(.*) :: (e -> a) -> r -> e -> a Source #

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

Defined in Data.Semimodule

Methods

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

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

multl :: Semiring a => Functor f => a -> f a -> f a Source #

Default definition of '(*.)' for a free module.

multr :: Semiring a => Functor f => f a -> a -> f a Source #

Default definition of '(.*)' for a free module.

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

Default definition of << for a commutative group.

lerp :: Module 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)

(.*.) :: Free f => Foldable f => Semiring a => f a -> f a -> a infix 6 Source #

Dot product.

>>> V3 1 2 3 .*. V3 1 2 3
14

quadrance :: Free f => Foldable f => Semiring a => f a -> a Source #

Squared l2 norm of a vector.

qd :: Free f => Foldable f => Module a (f a) => f a -> f a -> a Source #

Squared l2 norm of the difference between two vectors.

dirac :: Eq i => Semiring a => i -> i -> a Source #

Dirac delta function.

idx :: Free f => Semiring a => Rep f -> f a Source #

Create a unit vector at an index.

>>> idx I21 :: V2 Int
V2 1 0
>>> idx I42 :: V4 Int
V4 0 1 0 0