gasp-1.4.0.0: A framework of algebraic classes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Algebra.Classes

Synopsis

Documentation

timesDefault :: (Additive a1, Additive a2, Integral a1) => a1 -> a2 -> a2 Source #

class Additive a where Source #

Additive monoid

Minimal complete definition

(+), zero

Methods

(+) :: a -> a -> a infixl 6 Source #

zero :: a Source #

times :: Natural -> a -> a Source #

Instances

Instances details
Additive CInt Source # 
Instance details

Defined in Algebra.Classes

Additive Int16 Source # 
Instance details

Defined in Algebra.Classes

Additive Int32 Source # 
Instance details

Defined in Algebra.Classes

Additive Int8 Source # 
Instance details

Defined in Algebra.Classes

Additive Word16 Source # 
Instance details

Defined in Algebra.Classes

Additive Word32 Source # 
Instance details

Defined in Algebra.Classes

Additive Word8 Source # 
Instance details

Defined in Algebra.Classes

Additive Integer Source # 
Instance details

Defined in Algebra.Classes

Additive Bool Source # 
Instance details

Defined in Algebra.Classes

Additive Double Source # 
Instance details

Defined in Algebra.Classes

Additive Float Source # 
Instance details

Defined in Algebra.Classes

Additive Int Source # 
Instance details

Defined in Algebra.Classes

Methods

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

zero :: Int Source #

times :: Natural -> Int -> Int Source #

Additive a => Additive (Complex a) Source # 
Instance details

Defined in Algebra.Classes

Integral a => Additive (Ratio a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(+) :: Ratio a -> Ratio a -> Ratio a Source #

zero :: Ratio a Source #

times :: Natural -> Ratio a -> Ratio a Source #

Multiplicative a => Additive (Log a) Source # 
Instance details

Defined in Algebra.Morphism.Exponential

Methods

(+) :: Log a -> Log a -> Log a Source #

zero :: Log a Source #

times :: Natural -> Log a -> Log a Source #

EuclideanDomain a => Additive (Ratio a) Source #

Since: 2.0.1

Instance details

Defined in Algebra.Morphism.Ratio

Methods

(+) :: Ratio a -> Ratio a -> Ratio a Source #

zero :: Ratio a Source #

times :: Natural -> Ratio a -> Ratio a Source #

(Ord k, AbelianAdditive v) => Additive (Map k v) Source # 
Instance details

Defined in Algebra.Classes

Methods

(+) :: Map k v -> Map k v -> Map k v Source #

zero :: Map k v Source #

times :: Natural -> Map k v -> Map k v Source #

(Applicative f, Additive a) => Additive (App f a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(+) :: App f a -> App f a -> App f a Source #

zero :: App f a Source #

times :: Natural -> App f a -> App f a Source #

(Ord x, AbelianAdditive c, DecidableZero c) => Additive (Affine x c) Source # 
Instance details

Defined in Algebra.Morphism.Affine

Methods

(+) :: Affine x c -> Affine x c -> Affine x c Source #

zero :: Affine x c Source #

times :: Natural -> Affine x c -> Affine x c Source #

(AbelianAdditive c, DecidableZero c, Ord e) => Additive (LinComb e c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

(+) :: LinComb e c -> LinComb e c -> LinComb e c Source #

zero :: LinComb e c Source #

times :: Natural -> LinComb e c -> LinComb e c Source #

Additive a => Additive (Pointwise x a) Source # 
Instance details

Defined in Algebra.Morphism.Pointwise

Methods

(+) :: Pointwise x a -> Pointwise x a -> Pointwise x a Source #

zero :: Pointwise x a Source #

times :: Natural -> Pointwise x a -> Pointwise x a Source #

Additive v => Additive (k -> v) Source # 
Instance details

Defined in Algebra.Classes

Methods

(+) :: (k -> v) -> (k -> v) -> k -> v Source #

zero :: k -> v Source #

times :: Natural -> (k -> v) -> k -> v Source #

Additive s => Additive (M s a b) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

(+) :: M s a b -> M s a b -> M s a b Source #

zero :: M s a b Source #

times :: Natural -> M s a b -> M s a b Source #

Additive s => Additive (Rel s a b) Source # 
Instance details

Defined in Algebra.Category.Relation

Methods

(+) :: Rel s a b -> Rel s a b -> Rel s a b Source #

zero :: Rel s a b Source #

times :: Natural -> Rel s a b -> Rel s a b Source #

(Applicative f, Additive a) => Additive (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Methods

(+) :: Euclid f a -> Euclid f a -> Euclid f a Source #

zero :: Euclid f a Source #

times :: Natural -> Euclid f a -> Euclid f a Source #

Additive (f b a) => Additive (Op f a b) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

(+) :: Op f a b -> Op f a b -> Op f a b Source #

zero :: Op f a b Source #

times :: Natural -> Op f a b -> Op f a b Source #

(Applicative f, Applicative g, Additive a) => Additive (Mat a f g) Source # 
Instance details

Defined in Algebra.Linear

Methods

(+) :: Mat a f g -> Mat a f g -> Mat a f g Source #

zero :: Mat a f g Source #

times :: Natural -> Mat a f g -> Mat a f g Source #

class Show a => TestEqual a where Source #

Methods

(=.=) :: a -> a -> Property infix 0 Source #

Instances

Instances details
TestEqual Double Source # 
Instance details

Defined in Algebra.Classes

TestEqual Int Source # 
Instance details

Defined in Algebra.Classes

Methods

(=.=) :: Int -> Int -> Property Source #

(Ord x, Show x, Arbitrary x, TestEqual a, Additive a) => TestEqual (Map x a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(=.=) :: Map x a -> Map x a -> Property Source #

(Show s, Additive s, TestEqual s) => TestEqual (M s a b) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

(=.=) :: M s a b -> M s a b -> Property Source #

TestEqual (f b a) => TestEqual (Op f a b) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

(=.=) :: Op f a b -> Op f a b -> Property Source #

(TestEqual s, Arbitrary s, Arbitrary1 a, Arbitrary1 b, Show (a (b s)), VectorR b, VectorR a) => TestEqual (Mat s a b) Source # 
Instance details

Defined in Algebra.Linear

Methods

(=.=) :: Mat s a b -> Mat s a b -> Property Source #

nameLaw :: Testable prop => String -> prop -> Property Source #

law_assoc :: forall a. TestEqual a => String -> (a -> a -> a) -> a -> a -> a -> Property Source #

law_left_id :: forall a. TestEqual a => String -> (a -> a -> a) -> a -> a -> Property Source #

law_right_id :: forall a. TestEqual a => String -> (a -> a -> a) -> a -> a -> Property Source #

laws_monoid :: forall a. (Arbitrary a, TestEqual a) => String -> (a -> a -> a) -> a -> Property Source #

law_commutative :: TestEqual a => String -> (a -> a -> a) -> a -> a -> Property Source #

laws_comm_monoid :: forall a. (Arbitrary a, TestEqual a) => String -> (a -> a -> a) -> a -> Property Source #

laws_ring :: forall a. Arbitrary a => (Ring a, TestEqual a) => Property Source #

sum :: (Foldable t, Additive a) => t a -> a Source #

class Additive r => DecidableZero r where Source #

Methods

isZero :: r -> Bool Source #

Instances

Instances details
DecidableZero CInt Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: CInt -> Bool Source #

DecidableZero Word16 Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: Word16 -> Bool Source #

DecidableZero Word32 Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: Word32 -> Bool Source #

DecidableZero Word8 Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: Word8 -> Bool Source #

DecidableZero Integer Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: Integer -> Bool Source #

DecidableZero Double Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: Double -> Bool Source #

DecidableZero Float Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: Float -> Bool Source #

DecidableZero Int Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: Int -> Bool Source #

DecidableZero x => DecidableZero (Complex x) Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: Complex x -> Bool Source #

(Integral x, DecidableZero x) => DecidableZero (Ratio x) Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: Ratio x -> Bool Source #

(Ord k, DecidableZero v, AbelianAdditive v) => DecidableZero (Map k v) Source # 
Instance details

Defined in Algebra.Classes

Methods

isZero :: Map k v -> Bool Source #

(AbelianAdditive c, Eq c, DecidableZero c, Ord e) => DecidableZero (LinComb e c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

isZero :: LinComb e c -> Bool Source #

class Additive a => AbelianAdditive a Source #

Instances

Instances details
AbelianAdditive CInt Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Int16 Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Int32 Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Int8 Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Word16 Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Word32 Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Word8 Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Integer Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Bool Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Double Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Float Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive Int Source # 
Instance details

Defined in Algebra.Classes

AbelianAdditive a => AbelianAdditive (Complex a) Source # 
Instance details

Defined in Algebra.Classes

Integral a => AbelianAdditive (Ratio a) Source # 
Instance details

Defined in Algebra.Classes

EuclideanDomain a => AbelianAdditive (Ratio a) Source # 
Instance details

Defined in Algebra.Morphism.Ratio

(Ord k, AbelianAdditive v) => AbelianAdditive (Map k v) Source # 
Instance details

Defined in Algebra.Classes

(Applicative f, AbelianAdditive a) => AbelianAdditive (App f a) Source # 
Instance details

Defined in Algebra.Classes

(Ord x, AbelianAdditive c, DecidableZero c) => AbelianAdditive (Affine x c) Source # 
Instance details

Defined in Algebra.Morphism.Affine

(AbelianAdditive c, DecidableZero c, Ord x) => AbelianAdditive (LinComb x c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Additive a => AbelianAdditive (Pointwise x a) Source # 
Instance details

Defined in Algebra.Morphism.Pointwise

AbelianAdditive v => AbelianAdditive (k -> v) Source # 
Instance details

Defined in Algebra.Classes

(Applicative f, Applicative g, AbelianAdditive a) => AbelianAdditive (Mat a f g) Source # 
Instance details

Defined in Algebra.Linear

multDefault :: Group a => Natural -> a -> a Source #

class Additive a => Group a where Source #

Minimal complete definition

(negate | (-) | subtract)

Methods

(-) :: a -> a -> a infixl 6 Source #

subtract :: a -> a -> a Source #

negate :: a -> a Source #

mult :: Integer -> a -> a Source #

Instances

Instances details
Group CInt Source # 
Instance details

Defined in Algebra.Classes

Group Int16 Source # 
Instance details

Defined in Algebra.Classes

Group Int32 Source # 
Instance details

Defined in Algebra.Classes

Group Int8 Source # 
Instance details

Defined in Algebra.Classes

Group Word16 Source # 
Instance details

Defined in Algebra.Classes

Group Word32 Source # 
Instance details

Defined in Algebra.Classes

Group Word8 Source # 
Instance details

Defined in Algebra.Classes

Group Integer Source # 
Instance details

Defined in Algebra.Classes

Group Double Source # 
Instance details

Defined in Algebra.Classes

Group Float Source # 
Instance details

Defined in Algebra.Classes

Group Int Source # 
Instance details

Defined in Algebra.Classes

Methods

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

subtract :: Int -> Int -> Int Source #

negate :: Int -> Int Source #

mult :: Integer -> Int -> Int Source #

Group a => Group (Complex a) Source # 
Instance details

Defined in Algebra.Classes

Integral a => Group (Ratio a) Source # 
Instance details

Defined in Algebra.Classes

Methods

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

subtract :: Ratio a -> Ratio a -> Ratio a Source #

negate :: Ratio a -> Ratio a Source #

mult :: Integer -> Ratio a -> Ratio a Source #

Division a => Group (Log a) Source # 
Instance details

Defined in Algebra.Morphism.Exponential

Methods

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

subtract :: Log a -> Log a -> Log a Source #

negate :: Log a -> Log a Source #

mult :: Integer -> Log a -> Log a Source #

EuclideanDomain a => Group (Ratio a) Source # 
Instance details

Defined in Algebra.Morphism.Ratio

Methods

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

subtract :: Ratio a -> Ratio a -> Ratio a Source #

negate :: Ratio a -> Ratio a Source #

mult :: Integer -> Ratio a -> Ratio a Source #

(Ord k, Group v, AbelianAdditive v) => Group (Map k v) Source # 
Instance details

Defined in Algebra.Classes

Methods

(-) :: Map k v -> Map k v -> Map k v Source #

subtract :: Map k v -> Map k v -> Map k v Source #

negate :: Map k v -> Map k v Source #

mult :: Integer -> Map k v -> Map k v Source #

(Applicative f, Group a) => Group (App f a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(-) :: App f a -> App f a -> App f a Source #

subtract :: App f a -> App f a -> App f a Source #

negate :: App f a -> App f a Source #

mult :: Integer -> App f a -> App f a Source #

(Ord x, AbelianAdditive c, Group c, DecidableZero c) => Group (Affine x c) Source # 
Instance details

Defined in Algebra.Morphism.Affine

Methods

(-) :: Affine x c -> Affine x c -> Affine x c Source #

subtract :: Affine x c -> Affine x c -> Affine x c Source #

negate :: Affine x c -> Affine x c Source #

mult :: Integer -> Affine x c -> Affine x c Source #

(AbelianAdditive c, Group c, DecidableZero c, Ord e) => Group (LinComb e c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

(-) :: LinComb e c -> LinComb e c -> LinComb e c Source #

subtract :: LinComb e c -> LinComb e c -> LinComb e c Source #

negate :: LinComb e c -> LinComb e c Source #

mult :: Integer -> LinComb e c -> LinComb e c Source #

Group a => Group (Pointwise x a) Source # 
Instance details

Defined in Algebra.Morphism.Pointwise

Methods

(-) :: Pointwise x a -> Pointwise x a -> Pointwise x a Source #

subtract :: Pointwise x a -> Pointwise x a -> Pointwise x a Source #

negate :: Pointwise x a -> Pointwise x a Source #

mult :: Integer -> Pointwise x a -> Pointwise x a Source #

Group v => Group (k -> v) Source # 
Instance details

Defined in Algebra.Classes

Methods

(-) :: (k -> v) -> (k -> v) -> k -> v Source #

subtract :: (k -> v) -> (k -> v) -> k -> v Source #

negate :: (k -> v) -> k -> v Source #

mult :: Integer -> (k -> v) -> k -> v Source #

Group s => Group (M s a b) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

(-) :: M s a b -> M s a b -> M s a b Source #

subtract :: M s a b -> M s a b -> M s a b Source #

negate :: M s a b -> M s a b Source #

mult :: Integer -> M s a b -> M s a b Source #

(Applicative f, Group a) => Group (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Methods

(-) :: Euclid f a -> Euclid f a -> Euclid f a Source #

subtract :: Euclid f a -> Euclid f a -> Euclid f a Source #

negate :: Euclid f a -> Euclid f a Source #

mult :: Integer -> Euclid f a -> Euclid f a Source #

Group (f b a) => Group (Op f a b) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

(-) :: Op f a b -> Op f a b -> Op f a b Source #

subtract :: Op f a b -> Op f a b -> Op f a b Source #

negate :: Op f a b -> Op f a b Source #

mult :: Integer -> Op f a b -> Op f a b Source #

(Applicative f, Applicative g, Group a) => Group (Mat a f g) Source # 
Instance details

Defined in Algebra.Linear

Methods

(-) :: Mat a f g -> Mat a f g -> Mat a f g Source #

subtract :: Mat a f g -> Mat a f g -> Mat a f g Source #

negate :: Mat a f g -> Mat a f g Source #

mult :: Integer -> Mat a f g -> Mat a f g Source #

laws_group :: forall a. Arbitrary a => (Group a, TestEqual a) => Property Source #

(*<) :: (Functor f, Multiplicative a) => a -> f a -> f a infixr 7 Source #

Functorial scaling. Compared to (*^) this operator disambiguates the scalar type, by using the functor structure and using the multiplicative instance for scalars.

class Scalable s a where Source #

Any instance must preserve the following invariants: 1. if Multiplicative a and Scalable a a, then (*) = (*^) for a. 2. Scalable must define a partial order relation, in particular, instances of the form (Scalable s a) => Scalable s (T ... a ...) are acceptable, and should be declared overlappable.

Methods

(*^) :: s -> a -> a infixr 7 Source #

Instances

Instances details
Scalable CInt CInt Source # 
Instance details

Defined in Algebra.Classes

Methods

(*^) :: CInt -> CInt -> CInt Source #

Scalable Int16 Int16 Source # 
Instance details

Defined in Algebra.Classes

Methods

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

Scalable Int32 Int32 Source # 
Instance details

Defined in Algebra.Classes

Methods

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

Scalable Int8 Int8 Source # 
Instance details

Defined in Algebra.Classes

Methods

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

Scalable Rational Double Source # 
Instance details

Defined in Algebra.Classes

Methods

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

Scalable Word16 Word16 Source # 
Instance details

Defined in Algebra.Classes

Methods

(*^) :: Word16 -> Word16 -> Word16 Source #

Scalable Word32 Word32 Source # 
Instance details

Defined in Algebra.Classes

Methods

(*^) :: Word32 -> Word32 -> Word32 Source #

Scalable Word8 Word8 Source # 
Instance details

Defined in Algebra.Classes

Methods

(*^) :: Word8 -> Word8 -> Word8 Source #

Scalable Integer Integer Source # 
Instance details

Defined in Algebra.Classes

Scalable Double Double Source # 
Instance details

Defined in Algebra.Classes

Methods

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

Scalable Float Float Source # 
Instance details

Defined in Algebra.Classes

Methods

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

Scalable Int Int Source # 
Instance details

Defined in Algebra.Classes

Methods

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

Multiplicative a => Scalable Integer (Log a) Source # 
Instance details

Defined in Algebra.Morphism.Exponential

Methods

(*^) :: Integer -> Log a -> Log a Source #

Scalable s a => Scalable s (Complex a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(*^) :: s -> Complex a -> Complex a Source #

Multiplicative c => Scalable c (Affine x c) Source # 
Instance details

Defined in Algebra.Morphism.Affine

Methods

(*^) :: c -> Affine x c -> Affine x c Source #

Scalable s a => Scalable s (Map k a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(*^) :: s -> Map k a -> Map k a Source #

Scalable s a => Scalable s (LinComb k a) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

(*^) :: s -> LinComb k a -> LinComb k a Source #

Scalable s a => Scalable s (k -> a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(*^) :: s -> (k -> a) -> k -> a Source #

Ring s => Scalable s (M s a b) Source # 
Instance details

Defined in Algebra.Category.BlockMatrix

Methods

(*^) :: s -> M s a b -> M s a b Source #

(Functor f, Scalable s a) => Scalable s (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Methods

(*^) :: s -> Euclid f a -> Euclid f a Source #

(Functor f, Functor g, Scalable s a) => Scalable s (Mat a f g) Source # 
Instance details

Defined in Algebra.Linear

Methods

(*^) :: s -> Mat a f g -> Mat a f g Source #

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

Defined in Algebra.Classes

Methods

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

Integral a => Scalable (Ratio a) (Ratio a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(*^) :: Ratio a -> Ratio a -> Ratio a Source #

EuclideanDomain a => Scalable (Ratio a) (Ratio a) Source # 
Instance details

Defined in Algebra.Morphism.Ratio

Methods

(*^) :: Ratio a -> Ratio a -> Ratio a Source #

(Applicative f, Scalable s a) => Scalable (App f s) (App f a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(*^) :: App f s -> App f a -> App f a Source #

Multiplicative a => Scalable (Pointwise x a) (Pointwise x a) Source # 
Instance details

Defined in Algebra.Morphism.Pointwise

Methods

(*^) :: Pointwise x a -> Pointwise x a -> Pointwise x a Source #

class Scalable' a where Source #

"Most natural" scaling. Also disambiguates the scalar type, but using a fundep.

Associated Types

type Scalar a Source #

Methods

(!*^) :: Scalar a -> a -> a Source #

type SemiModule s a = (AbelianAdditive a, SemiRing s, Scalable s a) Source #

A prefix variant of (*^), useful when using type applications. scale :: forall s a. Scalable s a => s -> a -> a scale = (*^)

type Module s a = (SemiModule s a, Group s, Group a) Source #

law_module_zero :: forall s a. (Module s a, TestEqual a) => s -> Property Source #

law_module_one :: forall s a. (Module s a, TestEqual a) => a -> Property Source #

law_module_sum :: forall s a. (Module s a, TestEqual a) => s -> a -> a -> Property Source #

law_module_sum_left :: forall s a. (Module s a, TestEqual a) => s -> s -> a -> Property Source #

law_module_mul :: forall s a. (Module s a, TestEqual a) => s -> s -> a -> Property Source #

laws_module :: forall s a. Arbitrary a => (Module s a, TestEqual a, Arbitrary s, Show s) => Property Source #

class Multiplicative a where Source #

Multiplicative monoid

Minimal complete definition

(*), one

Methods

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

one :: a Source #

(^+) :: a -> Natural -> a infixr 8 Source #

Instances

Instances details
Multiplicative Property Source # 
Instance details

Defined in Algebra.Classes

Multiplicative CInt Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Int16 Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Int32 Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Int8 Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Word16 Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Word32 Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Word8 Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Integer Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Bool Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Double Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Float Source # 
Instance details

Defined in Algebra.Classes

Multiplicative Int Source # 
Instance details

Defined in Algebra.Classes

Methods

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

one :: Int Source #

(^+) :: Int -> Natural -> Int Source #

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

Defined in Algebra.Classes

Integral a => Multiplicative (Ratio a) Source # 
Instance details

Defined in Algebra.Classes

Methods

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

one :: Ratio a Source #

(^+) :: Ratio a -> Natural -> Ratio a Source #

Additive a => Multiplicative (Exp a) Source # 
Instance details

Defined in Algebra.Morphism.Exponential

Methods

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

one :: Exp a Source #

(^+) :: Exp a -> Natural -> Exp a Source #

EuclideanDomain a => Multiplicative (Ratio a) Source # 
Instance details

Defined in Algebra.Morphism.Ratio

Methods

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

one :: Ratio a Source #

(^+) :: Ratio a -> Natural -> Ratio a Source #

(Category cat, Obj cat a) => Multiplicative (Endo cat a) Source # 
Instance details

Defined in Algebra.Category.Endo

Methods

(*) :: Endo cat a -> Endo cat a -> Endo cat a Source #

one :: Endo cat a Source #

(^+) :: Endo cat a -> Natural -> Endo cat a Source #

(Applicative f, Multiplicative a) => Multiplicative (App f a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(*) :: App f a -> App f a -> App f a Source #

one :: App f a Source #

(^+) :: App f a -> Natural -> App f a Source #

Multiplicative a => Multiplicative (Pointwise x a) Source # 
Instance details

Defined in Algebra.Morphism.Pointwise

Methods

(*) :: Pointwise x a -> Pointwise x a -> Pointwise x a Source #

one :: Pointwise x a Source #

(^+) :: Pointwise x a -> Natural -> Pointwise x a Source #

product :: (Multiplicative a, Foldable f) => f a -> a Source #

type PreRing a = (SemiRing a, Group a) Source #

class (Module a a, PreRing a) => Ring a where Source #

Minimal complete definition

Nothing

Methods

fromInteger :: Integer -> a Source #

Instances

Instances details
Ring CInt Source # 
Instance details

Defined in Algebra.Classes

Ring Int16 Source # 
Instance details

Defined in Algebra.Classes

Ring Int32 Source # 
Instance details

Defined in Algebra.Classes

Ring Int8 Source # 
Instance details

Defined in Algebra.Classes

Ring Word16 Source # 
Instance details

Defined in Algebra.Classes

Ring Word32 Source # 
Instance details

Defined in Algebra.Classes

Ring Word8 Source # 
Instance details

Defined in Algebra.Classes

Ring Integer Source # 
Instance details

Defined in Algebra.Classes

Ring Double Source # 
Instance details

Defined in Algebra.Classes

Ring Float Source # 
Instance details

Defined in Algebra.Classes

Ring Int Source # 
Instance details

Defined in Algebra.Classes

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

Defined in Algebra.Classes

Integral a => Ring (Ratio a) Source # 
Instance details

Defined in Algebra.Classes

EuclideanDomain a => Ring (Ratio a) Source # 
Instance details

Defined in Algebra.Morphism.Ratio

(Applicative f, Ring a) => Ring (App f a) Source # 
Instance details

Defined in Algebra.Classes

Methods

fromInteger :: Integer -> App f a Source #

Ring a => Ring (Pointwise x a) Source # 
Instance details

Defined in Algebra.Morphism.Pointwise

class Multiplicative a => Division a where Source #

Minimal complete definition

(recip | (/))

Methods

recip :: a -> a Source #

(/) :: a -> a -> a infixl 7 Source #

(^) :: a -> Integer -> a infixr 8 Source #

Instances

Instances details
Division Double Source # 
Instance details

Defined in Algebra.Classes

Division Float Source # 
Instance details

Defined in Algebra.Classes

Field a => Division (Complex a) Source # 
Instance details

Defined in Algebra.Classes

Methods

recip :: Complex a -> Complex a Source #

(/) :: Complex a -> Complex a -> Complex a Source #

(^) :: Complex a -> Integer -> Complex a Source #

Integral a => Division (Ratio a) Source # 
Instance details

Defined in Algebra.Classes

Methods

recip :: Ratio a -> Ratio a Source #

(/) :: Ratio a -> Ratio a -> Ratio a Source #

(^) :: Ratio a -> Integer -> Ratio a Source #

Group a => Division (Exp a) Source # 
Instance details

Defined in Algebra.Morphism.Exponential

Methods

recip :: Exp a -> Exp a Source #

(/) :: Exp a -> Exp a -> Exp a Source #

(^) :: Exp a -> Integer -> Exp a Source #

EuclideanDomain a => Division (Ratio a) Source #

Since: 2.0.1

Instance details

Defined in Algebra.Morphism.Ratio

Methods

recip :: Ratio a -> Ratio a Source #

(/) :: Ratio a -> Ratio a -> Ratio a Source #

(^) :: Ratio a -> Integer -> Ratio a Source #

(Dagger cat, Obj cat a) => Division (Endo cat a) Source # 
Instance details

Defined in Algebra.Category.Endo

Methods

recip :: Endo cat a -> Endo cat a Source #

(/) :: Endo cat a -> Endo cat a -> Endo cat a Source #

(^) :: Endo cat a -> Integer -> Endo cat a Source #

(Applicative f, Division s) => Division (App f s) Source # 
Instance details

Defined in Algebra.Classes

Methods

recip :: App f s -> App f s Source #

(/) :: App f s -> App f s -> App f s Source #

(^) :: App f s -> Integer -> App f s Source #

Division a => Division (Pointwise x a) Source # 
Instance details

Defined in Algebra.Morphism.Pointwise

Methods

recip :: Pointwise x a -> Pointwise x a Source #

(/) :: Pointwise x a -> Pointwise x a -> Pointwise x a Source #

(^) :: Pointwise x a -> Integer -> Pointwise x a Source #

class (Ring a, Division a) => Field a where Source #

Minimal complete definition

Nothing

Methods

fromRational :: Rational -> a Source #

Instances

Instances details
Field Double Source # 
Instance details

Defined in Algebra.Classes

Field Float Source # 
Instance details

Defined in Algebra.Classes

Field a => Field (Complex a) Source # 
Instance details

Defined in Algebra.Classes

Integral a => Field (Ratio a) Source # 
Instance details

Defined in Algebra.Classes

EuclideanDomain a => Field (Ratio a) Source # 
Instance details

Defined in Algebra.Morphism.Ratio

(Applicative f, Field s) => Field (App f s) Source # 
Instance details

Defined in Algebra.Classes

Methods

fromRational :: Rational -> App f s Source #

Field a => Field (Pointwise x a) Source # 
Instance details

Defined in Algebra.Morphism.Pointwise

class (Ring a, DecidableZero a) => EuclideanDomain a where Source #

Minimal complete definition

(stdUnit | normalize), (quotRem | quot, rem)

Methods

stdAssociate :: a -> a Source #

stdUnit :: a -> a Source #

normalize :: a -> (a, a) Source #

quot :: a -> a -> a infixl 7 Source #

rem :: a -> a -> a infixl 7 Source #

quotRem :: a -> a -> (a, a) Source #

gcd :: EuclideanDomain a => a -> a -> a Source #

lcm :: EuclideanDomain a => a -> a -> a Source #

lcm x y is the smallest positive integer that both x and y divide.

class (Ord a, Ring a, Enum a, EuclideanDomain a) => Integral a where Source #

Minimal complete definition

toInteger

Methods

div :: a -> a -> a infixl 7 Source #

mod :: a -> a -> a infixl 7 Source #

divMod :: a -> a -> (a, a) Source #

toInteger :: a -> Integer Source #

Instances

Instances details
Integral Integer Source # 
Instance details

Defined in Algebra.Classes

Integral Int Source # 
Instance details

Defined in Algebra.Classes

Methods

div :: Int -> Int -> Int Source #

mod :: Int -> Int -> Int Source #

divMod :: Int -> Int -> (Int, Int) Source #

toInteger :: Int -> Integer Source #

ifThenElse :: Bool -> t -> t -> t Source #

class Division a => Roots a where Source #

Minimal complete definition

root | (^/)

Methods

sqrt :: a -> a Source #

root :: Integer -> a -> a Source #

(^/) :: a -> Rational -> a infixr 8 Source #

Instances

Instances details
Roots Double Source # 
Instance details

Defined in Algebra.Classes

Roots Float Source # 
Instance details

Defined in Algebra.Classes

(RealFloat a, Ord a, Algebraic a) => Roots (Complex a) Source # 
Instance details

Defined in Algebra.Classes

Field a => Roots (Exp a) Source # 
Instance details

Defined in Algebra.Morphism.Exponential

Methods

sqrt :: Exp a -> Exp a Source #

root :: Integer -> Exp a -> Exp a Source #

(^/) :: Exp a -> Rational -> Exp a Source #

(Applicative f, Roots s) => Roots (App f s) Source # 
Instance details

Defined in Algebra.Classes

Methods

sqrt :: App f s -> App f s Source #

root :: Integer -> App f s -> App f s Source #

(^/) :: App f s -> Rational -> App f s Source #

Roots a => Roots (Pointwise x a) Source # 
Instance details

Defined in Algebra.Morphism.Pointwise

Methods

sqrt :: Pointwise x a -> Pointwise x a Source #

root :: Integer -> Pointwise x a -> Pointwise x a Source #

(^/) :: Pointwise x a -> Rational -> Pointwise x a Source #

type Algebraic a = (Roots a, Field a) Source #

class Algebraic a => Transcendental a where Source #

Class providing transcendental functions

Minimal complete definition

pi, exp, log, sin, cos, asin, acos, atan, sinh, cosh, asinh, acosh, atanh

Methods

pi :: a Source #

exp :: a -> a Source #

log :: a -> a Source #

(**) :: a -> a -> a infixr 8 Source #

logBase :: a -> a -> a Source #

sin :: a -> a Source #

cos :: a -> a Source #

tan :: a -> a Source #

asin :: a -> a Source #

acos :: a -> a Source #

atan :: a -> a Source #

sinh :: a -> a Source #

cosh :: a -> a Source #

tanh :: a -> a Source #

asinh :: a -> a Source #

acosh :: a -> a Source #

atanh :: a -> a Source #

log1p :: a -> a Source #

log1p x computes log (1 + x), but provides more precise results for small (absolute) values of x if possible.

Since: 4.9.0.0

expm1 :: a -> a Source #

expm1 x computes exp x - 1, but provides more precise results for small (absolute) values of x if possible.

Since: 4.9.0.0

log1pexp :: a -> a Source #

log1pexp x computes log (1 + exp x), but provides more precise results if possible.

Examples:

  • if x is a large negative number, log (1 + exp x) will be imprecise for the reasons given in log1p.
  • if exp x is close to -1, log (1 + exp x) will be imprecise for the reasons given in expm1.

Since: 4.9.0.0

log1mexp :: a -> a Source #

log1mexp x computes log (1 - exp x), but provides more precise results if possible.

Examples:

  • if x is a large negative number, log (1 - exp x) will be imprecise for the reasons given in log1p.
  • if exp x is close to 1, log (1 - exp x) will be imprecise for the reasons given in expm1.

Since: 4.9.0.0

Instances

Instances details
Transcendental Double Source # 
Instance details

Defined in Algebra.Classes

Transcendental Float Source # 
Instance details

Defined in Algebra.Classes

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

Defined in Algebra.Classes

(Applicative f, Transcendental s) => Transcendental (App f s) Source # 
Instance details

Defined in Algebra.Classes

Methods

pi :: App f s Source #

exp :: App f s -> App f s Source #

log :: App f s -> App f s Source #

(**) :: App f s -> App f s -> App f s Source #

logBase :: App f s -> App f s -> App f s Source #

sin :: App f s -> App f s Source #

cos :: App f s -> App f s Source #

tan :: App f s -> App f s Source #

asin :: App f s -> App f s Source #

acos :: App f s -> App f s Source #

atan :: App f s -> App f s Source #

sinh :: App f s -> App f s Source #

cosh :: App f s -> App f s Source #

tanh :: App f s -> App f s Source #

asinh :: App f s -> App f s Source #

acosh :: App f s -> App f s Source #

atanh :: App f s -> App f s Source #

log1p :: App f s -> App f s Source #

expm1 :: App f s -> App f s Source #

log1pexp :: App f s -> App f s Source #

log1mexp :: App f s -> App f s Source #

Transcendental a => Transcendental (Pointwise x a) Source # 
Instance details

Defined in Algebra.Morphism.Pointwise

(^?) :: Transcendental a => a -> a -> a infixr 8 Source #

class Algebraic a => AlgebraicallyClosed a where Source #

Minimal complete definition

rootOfUnity

Methods

imaginaryUnit :: a Source #

rootOfUnity :: Integer -> Integer -> a Source #

rootOfUnity n give the nth roots of unity. The 2nd argument specifies which one is demanded

Instances

Instances details
(RealFloat a, Transcendental a) => AlgebraicallyClosed (Complex a) Source # 
Instance details

Defined in Algebra.Classes

newtype Sum a Source #

Constructors

Sum 

Fields

Instances

Instances details
Additive a => Monoid (Sum a) Source # 
Instance details

Defined in Algebra.Classes

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Additive a => Semigroup (Sum a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Generic (Sum a) Source # 
Instance details

Defined in Algebra.Classes

Associated Types

type Rep (Sum a) :: Type -> Type #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Show a => Show (Sum a) Source # 
Instance details

Defined in Algebra.Classes

Methods

showsPrec :: Int -> Sum a -> ShowS #

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Binary a => Binary (Sum a) Source # 
Instance details

Defined in Algebra.Classes

Methods

put :: Sum a -> Put #

get :: Get (Sum a) #

putList :: [Sum a] -> Put #

Eq a => Eq (Sum a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(==) :: Sum a -> Sum a -> Bool #

(/=) :: Sum a -> Sum a -> Bool #

Ord a => Ord (Sum a) Source # 
Instance details

Defined in Algebra.Classes

Methods

compare :: Sum a -> Sum a -> Ordering #

(<) :: Sum a -> Sum a -> Bool #

(<=) :: Sum a -> Sum a -> Bool #

(>) :: Sum a -> Sum a -> Bool #

(>=) :: Sum a -> Sum a -> Bool #

max :: Sum a -> Sum a -> Sum a #

min :: Sum a -> Sum a -> Sum a #

type Rep (Sum a) Source # 
Instance details

Defined in Algebra.Classes

type Rep (Sum a) = D1 ('MetaData "Sum" "Algebra.Classes" "gasp-1.4.0.0-4Z31dYmTpJbCzuuYkBBWRm" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Product a Source #

Constructors

Product 

Fields

Instances

Instances details
Multiplicative a => Monoid (Product a) Source # 
Instance details

Defined in Algebra.Classes

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Multiplicative a => Semigroup (Product a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Generic (Product a) Source # 
Instance details

Defined in Algebra.Classes

Associated Types

type Rep (Product a) :: Type -> Type #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Show a => Show (Product a) Source # 
Instance details

Defined in Algebra.Classes

Methods

showsPrec :: Int -> Product a -> ShowS #

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Eq a => Eq (Product a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(==) :: Product a -> Product a -> Bool #

(/=) :: Product a -> Product a -> Bool #

Ord a => Ord (Product a) Source # 
Instance details

Defined in Algebra.Classes

Methods

compare :: Product a -> Product a -> Ordering #

(<) :: Product a -> Product a -> Bool #

(<=) :: Product a -> Product a -> Bool #

(>) :: Product a -> Product a -> Bool #

(>=) :: Product a -> Product a -> Bool #

max :: Product a -> Product a -> Product a #

min :: Product a -> Product a -> Product a #

type Rep (Product a) Source # 
Instance details

Defined in Algebra.Classes

type Rep (Product a) = D1 ('MetaData "Product" "Algebra.Classes" "gasp-1.4.0.0-4Z31dYmTpJbCzuuYkBBWRm" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype App f x Source #

Constructors

App (f x) 

Instances

Instances details
Applicative f => Applicative (App f) Source # 
Instance details

Defined in Algebra.Classes

Methods

pure :: a -> App f a #

(<*>) :: App f (a -> b) -> App f a -> App f b #

liftA2 :: (a -> b -> c) -> App f a -> App f b -> App f c #

(*>) :: App f a -> App f b -> App f b #

(<*) :: App f a -> App f b -> App f a #

Functor f => Functor (App f) Source # 
Instance details

Defined in Algebra.Classes

Methods

fmap :: (a -> b) -> App f a -> App f b #

(<$) :: a -> App f b -> App f a #

(Applicative f, AbelianAdditive a) => AbelianAdditive (App f a) Source # 
Instance details

Defined in Algebra.Classes

(Applicative f, Additive a) => Additive (App f a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(+) :: App f a -> App f a -> App f a Source #

zero :: App f a Source #

times :: Natural -> App f a -> App f a Source #

(Applicative f, Division s) => Division (App f s) Source # 
Instance details

Defined in Algebra.Classes

Methods

recip :: App f s -> App f s Source #

(/) :: App f s -> App f s -> App f s Source #

(^) :: App f s -> Integer -> App f s Source #

(Applicative f, Field s) => Field (App f s) Source # 
Instance details

Defined in Algebra.Classes

Methods

fromRational :: Rational -> App f s Source #

(Applicative f, Group a) => Group (App f a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(-) :: App f a -> App f a -> App f a Source #

subtract :: App f a -> App f a -> App f a Source #

negate :: App f a -> App f a Source #

mult :: Integer -> App f a -> App f a Source #

(Applicative f, Multiplicative a) => Multiplicative (App f a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(*) :: App f a -> App f a -> App f a Source #

one :: App f a Source #

(^+) :: App f a -> Natural -> App f a Source #

(Applicative f, Ring a) => Ring (App f a) Source # 
Instance details

Defined in Algebra.Classes

Methods

fromInteger :: Integer -> App f a Source #

(Applicative f, Roots s) => Roots (App f s) Source # 
Instance details

Defined in Algebra.Classes

Methods

sqrt :: App f s -> App f s Source #

root :: Integer -> App f s -> App f s Source #

(^/) :: App f s -> Rational -> App f s Source #

(Applicative f, Transcendental s) => Transcendental (App f s) Source # 
Instance details

Defined in Algebra.Classes

Methods

pi :: App f s Source #

exp :: App f s -> App f s Source #

log :: App f s -> App f s Source #

(**) :: App f s -> App f s -> App f s Source #

logBase :: App f s -> App f s -> App f s Source #

sin :: App f s -> App f s Source #

cos :: App f s -> App f s Source #

tan :: App f s -> App f s Source #

asin :: App f s -> App f s Source #

acos :: App f s -> App f s Source #

atan :: App f s -> App f s Source #

sinh :: App f s -> App f s Source #

cosh :: App f s -> App f s Source #

tanh :: App f s -> App f s Source #

asinh :: App f s -> App f s Source #

acosh :: App f s -> App f s Source #

atanh :: App f s -> App f s Source #

log1p :: App f s -> App f s Source #

expm1 :: App f s -> App f s Source #

log1pexp :: App f s -> App f s Source #

log1mexp :: App f s -> App f s Source #

(Applicative f, Scalable s a) => Scalable (App f s) (App f a) Source # 
Instance details

Defined in Algebra.Classes

Methods

(*^) :: App f s -> App f a -> App f a Source #