| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Algebra.Classes
Synopsis
- type Natural = Integer
- newtype Sum a = Sum {
- fromSum :: a
- newtype Product a = Product {
- fromProduct :: a
- newtype Exponential a = Exponential {
- fromExponential :: a
- class Additive a where
- add :: (Foldable t, Additive a) => t a -> a
- class Additive r => DecidableZero r where
- class Additive a => AbelianAdditive a
- class Additive a => Group a where
- class (AbelianAdditive a, PreRing scalar) => Module scalar a where
- (*^) :: scalar -> a -> a
- class Multiplicative a where
- multiply :: (Multiplicative a, Foldable f) => f a -> a
- type SemiRing a = (Multiplicative a, AbelianAdditive a)
- type PreRing a = (SemiRing a, Group a)
- fromIntegerDefault :: PreRing a => Integer -> a
- class (Module a a, PreRing a) => Ring a where
- fromInteger :: Integer -> a
- class Multiplicative a => Division a where
- class (Ring a, Division a) => Field a where
- fromRational :: Rational -> a
- type VectorSpace scalar a = (Field scalar, Module scalar a)
- class Ring a => EuclideanDomain a where
- class (Real a, Enum a, EuclideanDomain a) => Integral a where
- data Ratio a = !a :% !a
- type MyRational = Ratio Integer
- gcd :: Integral a => a -> a -> a
- ifThenElse :: Bool -> t -> t -> t
- data InitialAdditive
Documentation
Constructors
| Product | |
Fields
| |
Instances
| Multiplicative a => Semigroup (Product a) Source # | |
| Multiplicative a => Monoid (Product a) Source # | |
newtype Exponential a Source #
Constructors
| Exponential | |
Fields
| |
Instances
| Group a => Division (Exponential a) Source # | |
Defined in Algebra.Classes Methods recip :: Exponential a -> Exponential a Source # (/) :: Exponential a -> Exponential a -> Exponential a Source # | |
| Additive a => Multiplicative (Exponential a) Source # | |
Defined in Algebra.Classes Methods (*) :: Exponential a -> Exponential a -> Exponential a Source # one :: Exponential a Source # (^) :: Exponential a -> Natural -> Exponential a Source # | |
class Additive a where Source #
Additive monoid
Instances
| Additive Double Source # | |
| Additive Float Source # | |
| Additive Int Source # | |
| Additive Integer Source # | |
| Additive Word8 Source # | |
| Additive Word16 Source # | |
| Additive Word32 Source # | |
| Additive CInt Source # | |
| Additive InitialAdditive Source # | |
Defined in Algebra.Classes Methods (+) :: InitialAdditive -> InitialAdditive -> InitialAdditive Source # zero :: InitialAdditive Source # times :: Natural -> InitialAdditive -> InitialAdditive Source # | |
| Integral a => Additive (Ratio a) Source # | |
| (Ord k, Additive v) => Additive (Map k v) Source # | |
| (Applicative f, Additive a) => Additive (Euclid f a) Source # | |
| (Applicative f, Applicative g, Additive a) => Additive (Mat a f g) Source # | |
class Additive r => DecidableZero r where Source #
Instances
class Additive a => AbelianAdditive a Source #
Instances
| AbelianAdditive Double Source # | |
Defined in Algebra.Classes | |
| AbelianAdditive Float Source # | |
Defined in Algebra.Classes | |
| AbelianAdditive Int Source # | |
Defined in Algebra.Classes | |
| AbelianAdditive Integer Source # | |
Defined in Algebra.Classes | |
| AbelianAdditive CInt Source # | |
Defined in Algebra.Classes | |
| Integral a => AbelianAdditive (Ratio a) Source # | |
Defined in Algebra.Classes | |
| (Ord k, AbelianAdditive v) => AbelianAdditive (Map k v) Source # | |
Defined in Algebra.Classes | |
| (Applicative f, AbelianAdditive a) => AbelianAdditive (Euclid f a) Source # | |
Defined in Algebra.Linear | |
| (Applicative f, Applicative g, AbelianAdditive a) => AbelianAdditive (Mat a f g) Source # | |
Defined in Algebra.Linear | |
class Additive a => Group a where Source #
Instances
| Group Double Source # | |
| Group Float Source # | |
| Group Int Source # | |
| Group Integer Source # | |
| Group Word8 Source # | |
| Group Word16 Source # | |
| Group Word32 Source # | |
| Group CInt Source # | |
| Integral a => Group (Ratio a) Source # | |
| (Ord k, Group v) => Group (Map k v) Source # | |
| (Applicative f, Group a) => Group (Euclid f a) Source # | |
| (Applicative f, Applicative g, Group a) => Group (Mat a f g) Source # | |
class (AbelianAdditive a, PreRing scalar) => Module scalar a where Source #
Module
Instances
| Module Double Double Source # | |
| Module Float Float Source # | |
| Module Int Int Source # | |
| Module Integer Integer Source # | |
| Module Rational Double Source # | |
| Module CInt CInt Source # | |
| (Ord k, Module v v) => Module v (Map k v) Source # | |
| (Applicative f, Module s a) => Module s (Euclid f a) Source # | |
| (Applicative f, Applicative g, Module s a) => Module s (Mat a f g) Source # | |
| Integral a => Module (Ratio a) (Ratio a) Source # | |
class Multiplicative a where Source #
Multiplicative monoid
Instances
| Multiplicative Double Source # | |
| Multiplicative Float Source # | |
| Multiplicative Int Source # | |
| Multiplicative Integer Source # | |
| Multiplicative Word8 Source # | |
| Multiplicative Word16 Source # | |
| Multiplicative Word32 Source # | |
| Multiplicative CInt Source # | |
| Integral a => Multiplicative (Ratio a) Source # | |
| Additive a => Multiplicative (Exponential a) Source # | |
Defined in Algebra.Classes Methods (*) :: Exponential a -> Exponential a -> Exponential a Source # one :: Exponential a Source # (^) :: Exponential a -> Natural -> Exponential a Source # | |
| (Ring s, Applicative v, Traversable v) => Multiplicative (OrthoMat v s) Source # | |
multiply :: (Multiplicative a, Foldable f) => f a -> a Source #
type SemiRing a = (Multiplicative a, AbelianAdditive a) Source #
fromIntegerDefault :: PreRing a => Integer -> a Source #
class (Module a a, PreRing a) => Ring a where Source #
Minimal complete definition
Nothing
Methods
fromInteger :: Integer -> a Source #
Instances
| Ring Double Source # | |
Defined in Algebra.Classes Methods fromInteger :: Integer -> Double Source # | |
| Ring Float Source # | |
Defined in Algebra.Classes Methods fromInteger :: Integer -> Float Source # | |
| Ring Int Source # | |
Defined in Algebra.Classes Methods fromInteger :: Integer -> Int Source # | |
| Ring Integer Source # | |
Defined in Algebra.Classes Methods fromInteger :: Integer -> Integer Source # | |
| Ring CInt Source # | |
Defined in Algebra.Classes Methods fromInteger :: Integer -> CInt Source # | |
| Integral a => Ring (Ratio a) Source # | |
Defined in Algebra.Classes Methods fromInteger :: Integer -> Ratio a Source # | |
class Multiplicative a => Division a where Source #
Instances
| Division Double Source # | |
| Division Float Source # | |
| Integral a => Division (Ratio a) Source # | |
| Group a => Division (Exponential a) Source # | |
Defined in Algebra.Classes Methods recip :: Exponential a -> Exponential a Source # (/) :: Exponential a -> Exponential a -> Exponential a Source # | |
| (Ring s, Applicative v, Traversable v) => Division (OrthoMat v s) Source # | |
class (Ring a, Division a) => Field a where Source #
Minimal complete definition
Nothing
Methods
fromRational :: Rational -> a Source #
Instances
| Field Double Source # | |
Defined in Algebra.Classes Methods fromRational :: Rational -> Double Source # | |
| Field Float Source # | |
Defined in Algebra.Classes Methods fromRational :: Rational -> Float Source # | |
| Integral a => Field (Ratio a) Source # | |
Defined in Algebra.Classes Methods fromRational :: Rational -> Ratio a Source # | |
type VectorSpace scalar a = (Field scalar, Module scalar a) Source #
class Ring a => EuclideanDomain a where Source #
Methods
stdAssociate :: a -> a Source #
normalize :: a -> (a, a) Source #
div :: a -> a -> a infixl 7 Source #
Instances
| EuclideanDomain Int Source # | |
| EuclideanDomain Integer Source # | |
Defined in Algebra.Classes | |
| EuclideanDomain CInt Source # | |
class (Real a, Enum a, EuclideanDomain a) => Integral a where Source #
Minimal complete definition
Constructors
| !a :% !a |
type MyRational = Ratio Integer Source #
ifThenElse :: Bool -> t -> t -> t Source #
data InitialAdditive Source #
Constructors
| InitialAdditive :+ InitialAdditive | |
| Zero |
Instances
| Show InitialAdditive Source # | |
Defined in Algebra.Classes Methods showsPrec :: Int -> InitialAdditive -> ShowS # show :: InitialAdditive -> String # showList :: [InitialAdditive] -> ShowS # | |
| Additive InitialAdditive Source # | |
Defined in Algebra.Classes Methods (+) :: InitialAdditive -> InitialAdditive -> InitialAdditive Source # zero :: InitialAdditive Source # times :: Natural -> InitialAdditive -> InitialAdditive Source # | |