numeric-prelude-0.4.3.1: An experimental alternative hierarchy of numeric type classes

Copyright(c) Dylan Thurston Henning Thielemann 2004-2005
Maintainernumericprelude@henning-thielemann.de
Stabilityprovisional
Portabilityrequires multi-parameter type classes
Safe HaskellNone
LanguageHaskell98

Algebra.Module

Contents

Description

Abstraction of modules

Synopsis

Documentation

class (C a, C v) => C a v where Source #

A Module over a ring satisfies:

  a *> (b + c) === a *> b + a *> c
  (a * b) *> c === a *> (b *> c)
  (a + b) *> c === a *> c + b *> c

Minimal complete definition

(*>)

Methods

(*>) :: a -> v -> v infixr 7 Source #

scale a vector by a scalar

Instances
C Double Double Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: Double -> Double -> Double Source #

C Float Float Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: Float -> Float -> Float Source #

C Int Int Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: Int -> Int -> Int Source #

C Int8 Int8 Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: Int8 -> Int8 -> Int8 Source #

C Int16 Int16 Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: Int16 -> Int16 -> Int16 Source #

C Int32 Int32 Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: Int32 -> Int32 -> Int32 Source #

C Int64 Int64 Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: Int64 -> Int64 -> Int64 Source #

C Integer Integer Source # 
Instance details

Defined in Algebra.Module

C T T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

(*>) :: T -> T -> T Source #

C a => C Integer (T a) Source # 
Instance details

Defined in Algebra.Module

Methods

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

(C a b, RealFloat b) => C a (Complex b) Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: a -> Complex b -> Complex b Source #

C a v => C a [v] Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: a -> [v] -> [v] Source #

C a b => C a (T b) Source # 
Instance details

Defined in MathObj.PowerSeries

Methods

(*>) :: a -> T b -> T b Source #

C a b => C a (T b) Source # 
Instance details

Defined in MathObj.Polynomial

Methods

(*>) :: a -> T b -> T b Source #

(C a v, C v) => C a (T v) Source # 
Instance details

Defined in MathObj.PowerSum

Methods

(*>) :: a -> T v -> T v Source #

C a b => C a (T b) Source # 
Instance details

Defined in MathObj.Matrix

Methods

(*>) :: a -> T b -> T b Source #

C a b => C a (T b) Source #

The '(*>)' method can't replace scale because it requires the Algebra.Module constraint

Instance details

Defined in Number.Complex

Methods

(*>) :: a -> T b -> T b Source #

C a b => C a (T b) Source #

The '(*>)' method can't replace scale because it requires the Algebra.Module constraint

Instance details

Defined in Number.Quaternion

Methods

(*>) :: a -> T b -> T b Source #

C a b => C a (T b) Source # 
Instance details

Defined in MathObj.LaurentPolynomial

Methods

(*>) :: a -> T b -> T b Source #

C a v => C a (c -> v) Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: a -> (c -> v) -> c -> v Source #

(C a b0, C a b1) => C a (b0, b1) Source # 
Instance details

Defined in Algebra.Module

Methods

(*>) :: a -> (b0, b1) -> (b0, b1) Source #

(C u, C a b) => C a (T u b) Source # 
Instance details

Defined in Number.DimensionTerm

Methods

(*>) :: a -> T u b -> T u b Source #

(Ord i, Eq a, Eq v, C a v) => C a (Map i v) Source # 
Instance details

Defined in MathObj.DiscreteMap

Methods

(*>) :: a -> Map i v -> Map i v Source #

(Ord i, C a v) => C a (T i v) Source # 
Instance details

Defined in Number.Physical

Methods

(*>) :: a -> T i v -> T i v Source #

C a v => C a (T b v) Source # 
Instance details

Defined in Number.SI

Methods

(*>) :: a -> T b v -> T b v Source #

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

Defined in Algebra.Module

Methods

(*>) :: a -> (b0, b1, b2) -> (b0, b1, b2) Source #

C a => C (T a) (T a) Source # 
Instance details

Defined in Algebra.Module

Methods

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

C a v => C (T a) (T v) Source # 
Instance details

Defined in MathObj.Wrapper.NumericPrelude

Methods

(*>) :: T a -> T v -> T v Source #

(<*>.*>) :: C a x => T (a, v) (x -> c) -> (v -> x) -> T (a, v) c Source #

Instances for atomic types

Instances for composed types

Related functions

linearComb :: C a v => [a] -> [v] -> v Source #

Compute the linear combination of a list of vectors.

ToDo: Should it use zipWith ?

integerMultiply :: (C a, C v) => a -> v -> v Source #

This function can be used to define any C as a module over Integer.

Better move to Algebra.Additive?

Properties

propCascade :: (Eq v, C a v) => v -> a -> a -> Bool Source #

propRightDistributive :: (Eq v, C a v) => a -> v -> v -> Bool Source #

propLeftDistributive :: (Eq v, C a v) => v -> a -> a -> Bool Source #