Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type Natural = Integer
- timesDefault :: (Additive a1, Additive a2, Integral a1) => a1 -> a2 -> a2
- class Additive a where
- class Show a => TestEqual a where
- law_refl :: TestEqual a => a -> Property
- laws_testEqual :: forall a. Arbitrary a => TestEqual a => Property
- nameLaw :: Testable prop => String -> prop -> Property
- law_assoc :: forall a. TestEqual a => String -> (a -> a -> a) -> a -> a -> a -> Property
- law_left_id :: forall a. TestEqual a => String -> (a -> a -> a) -> a -> a -> Property
- law_right_id :: forall a. TestEqual a => String -> (a -> a -> a) -> a -> a -> Property
- laws_monoid :: forall a. (Arbitrary a, TestEqual a) => String -> (a -> a -> a) -> a -> Property
- law_commutative :: TestEqual a => String -> (a -> a -> a) -> a -> a -> Property
- laws_comm_monoid :: forall a. (Arbitrary a, TestEqual a) => String -> (a -> a -> a) -> a -> Property
- law_times :: (TestEqual a, Additive a) => Positive Integer -> a -> Property
- laws_additive :: forall a. Arbitrary a => (Additive a, TestEqual a) => Property
- law_exp_pos :: (TestEqual a, Multiplicative a) => a -> Property
- laws_multiplicative :: forall a. Arbitrary a => (Multiplicative a, TestEqual a) => Property
- law_fromInteger :: forall a. (TestEqual a, Ring a) => Integer -> Property
- laws_ring :: forall a. Arbitrary a => (Ring a, TestEqual a) => Property
- sum :: (Foldable t, Additive a) => t a -> a
- class Additive r => DecidableZero r where
- law_decidable_zero :: forall a. (DecidableZero a, TestEqual a) => Property
- class Additive a => AbelianAdditive a
- laws_abelian_additive :: forall a. (Arbitrary a, AbelianAdditive a, TestEqual a) => Property
- multDefault :: Group a => Natural -> a -> a
- class Additive a => Group a where
- law_negate_minus :: (TestEqual a, Group a) => a -> a -> Property
- law_mult :: (TestEqual a, Group a) => Integer -> a -> Property
- laws_group :: forall a. Arbitrary a => (Group a, TestEqual a) => Property
- laws_abelian_group :: forall a. Arbitrary a => (Group a, TestEqual a) => Property
- (*<) :: (Functor f, Multiplicative a) => a -> f a -> f a
- class Scalable s a where
- (*^) :: s -> a -> a
- class Scalable' a where
- type SemiModule s a = (AbelianAdditive a, SemiRing s, Scalable s a)
- type Module s a = (SemiModule s a, Group s, Group a)
- law_module_zero :: forall s a. (Module s a, TestEqual a) => s -> Property
- law_module_one :: forall s a. (Module s a, TestEqual a) => a -> Property
- law_module_sum :: forall s a. (Module s a, TestEqual a) => s -> a -> a -> Property
- law_module_sum_left :: forall s a. (Module s a, TestEqual a) => s -> s -> a -> Property
- law_module_mul :: forall s a. (Module s a, TestEqual a) => s -> s -> a -> Property
- laws_module :: forall s a. Arbitrary a => (Module s a, TestEqual a, Arbitrary s, Show s) => Property
- class Multiplicative a where
- positiveExponentDefault :: Multiplicative a => a -> Natural -> a
- product :: (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
- class (Ring a, DecidableZero a) => EuclideanDomain a where
- gcd :: EuclideanDomain a => a -> a -> a
- lcm :: EuclideanDomain a => a -> a -> a
- class (Ord a, Ring a, Enum a, EuclideanDomain a) => Integral a where
- ifThenElse :: Bool -> t -> t -> t
- class Division a => Roots a where
- type Algebraic a = (Roots a, Field a)
- class Algebraic a => Transcendental a where
- (^?) :: Transcendental a => a -> a -> a
- class Algebraic a => AlgebraicallyClosed a where
- imaginaryUnit :: a
- rootOfUnity :: Integer -> Integer -> a
- newtype Sum a = Sum {
- fromSum :: a
- newtype Product a = Product {
- fromProduct :: a
- newtype App f x = App (f x)
Documentation
class Additive a where Source #
Additive monoid
Instances
class Show a => TestEqual a where Source #
Instances
TestEqual Double Source # | |
TestEqual Int Source # | |
(Ord x, Show x, Arbitrary x, TestEqual a, Additive a) => TestEqual (Map x a) Source # | |
(Show s, Additive s, TestEqual s) => TestEqual (M s a b) Source # | |
TestEqual (f b a) => TestEqual (Op f a b) Source # | |
(TestEqual s, Arbitrary s, Arbitrary1 a, Arbitrary1 b, Show (a (b s)), VectorR b, VectorR a) => TestEqual (Mat s a b) Source # | |
laws_monoid :: forall a. (Arbitrary a, TestEqual a) => String -> (a -> a -> a) -> a -> Property Source #
laws_comm_monoid :: forall a. (Arbitrary a, TestEqual a) => String -> (a -> a -> a) -> a -> Property Source #
law_exp_pos :: (TestEqual a, Multiplicative a) => a -> Property Source #
laws_multiplicative :: forall a. Arbitrary a => (Multiplicative a, TestEqual a) => Property Source #
class Additive r => DecidableZero r where Source #
Instances
DecidableZero CInt Source # | |
DecidableZero Word16 Source # | |
DecidableZero Word32 Source # | |
DecidableZero Word8 Source # | |
DecidableZero Integer Source # | |
DecidableZero Double Source # | |
DecidableZero Float Source # | |
DecidableZero Int Source # | |
DecidableZero x => DecidableZero (Complex x) Source # | |
(Integral x, DecidableZero x) => DecidableZero (Ratio x) Source # | |
(Ord k, DecidableZero v, AbelianAdditive v) => DecidableZero (Map k v) Source # | |
(AbelianAdditive c, Eq c, DecidableZero c, Ord e) => DecidableZero (LinComb e c) Source # | |
law_decidable_zero :: forall a. (DecidableZero a, TestEqual a) => Property Source #
class Additive a => AbelianAdditive a Source #
Instances
laws_abelian_additive :: forall a. (Arbitrary a, AbelianAdditive a, TestEqual a) => Property Source #
multDefault :: Group a => Natural -> a -> a Source #
class Additive a => Group a where Source #
Instances
Group CInt Source # | |
Group Int16 Source # | |
Group Int32 Source # | |
Group Int8 Source # | |
Group Word16 Source # | |
Group Word32 Source # | |
Group Word8 Source # | |
Group Integer Source # | |
Group Double Source # | |
Group Float Source # | |
Group Int Source # | |
Group a => Group (Complex a) Source # | |
Integral a => Group (Ratio a) Source # | |
Division a => Group (Log a) Source # | |
EuclideanDomain a => Group (Ratio a) Source # | |
(Ord k, Group v, AbelianAdditive v) => Group (Map k v) Source # | |
(Applicative f, Group a) => Group (App f a) Source # | |
(Ord x, AbelianAdditive c, Group c, DecidableZero c) => Group (Affine x c) Source # | |
(AbelianAdditive c, Group c, DecidableZero c, Ord e) => Group (LinComb e c) Source # | |
Group a => Group (Pointwise x a) Source # | |
Group v => Group (k -> v) Source # | |
Group s => Group (M s a b) Source # | |
(Applicative f, Group a) => Group (Euclid f a) Source # | |
Group (f b a) => Group (Op f a b) Source # | |
(Applicative f, Applicative g, Group a) => Group (Mat a f g) 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.
Instances
class Scalable' a where Source #
"Most natural" scaling. Also disambiguates the scalar type, but using a fundep.
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 = (*^)
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
Instances
Multiplicative Property Source # | |
Multiplicative CInt Source # | |
Multiplicative Int16 Source # | |
Multiplicative Int32 Source # | |
Multiplicative Int8 Source # | |
Multiplicative Word16 Source # | |
Multiplicative Word32 Source # | |
Multiplicative Word8 Source # | |
Multiplicative Integer Source # | |
Multiplicative Bool Source # | |
Multiplicative Double Source # | |
Multiplicative Float Source # | |
Multiplicative Int Source # | |
Ring a => Multiplicative (Complex a) Source # | |
Integral a => Multiplicative (Ratio a) Source # | |
Additive a => Multiplicative (Exp a) Source # | |
EuclideanDomain a => Multiplicative (Ratio a) Source # | |
(Category cat, Obj cat a) => Multiplicative (Endo cat a) Source # | |
(Applicative f, Multiplicative a) => Multiplicative (App f a) Source # | |
Multiplicative a => Multiplicative (Pointwise x a) Source # | |
positiveExponentDefault :: Multiplicative a => a -> Natural -> a Source #
product :: (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 #
Nothing
fromInteger :: Integer -> a Source #
Instances
class Multiplicative a => Division a where Source #
Instances
Division Double Source # | |
Division Float Source # | |
Field a => Division (Complex a) Source # | |
Integral a => Division (Ratio a) Source # | |
Group a => Division (Exp a) Source # | |
EuclideanDomain a => Division (Ratio a) Source # | Since: 2.0.1 |
(Dagger cat, Obj cat a) => Division (Endo cat a) Source # | |
(Applicative f, Division s) => Division (App f s) Source # | |
Division a => Division (Pointwise x a) Source # | |
class (Ring a, Division a) => Field a where Source #
Nothing
fromRational :: Rational -> a Source #
Instances
Field Double Source # | |
Defined in Algebra.Classes fromRational :: Rational -> Double Source # | |
Field Float Source # | |
Defined in Algebra.Classes fromRational :: Rational -> Float Source # | |
Field a => Field (Complex a) Source # | |
Defined in Algebra.Classes fromRational :: Rational -> Complex a Source # | |
Integral a => Field (Ratio a) Source # | |
Defined in Algebra.Classes fromRational :: Rational -> Ratio a Source # | |
EuclideanDomain a => Field (Ratio a) Source # | |
Defined in Algebra.Morphism.Ratio fromRational :: Rational -> Ratio a Source # | |
(Applicative f, Field s) => Field (App f s) Source # | |
Defined in Algebra.Classes fromRational :: Rational -> App f s Source # | |
Field a => Field (Pointwise x a) Source # | |
Defined in Algebra.Morphism.Pointwise fromRational :: Rational -> Pointwise x a Source # |
class (Ring a, DecidableZero a) => EuclideanDomain a where Source #
stdAssociate :: a -> a Source #
normalize :: a -> (a, a) Source #
quot :: a -> a -> a infixl 7 Source #
Instances
gcd :: EuclideanDomain a => a -> a -> a Source #
lcm :: EuclideanDomain a => a -> a -> a Source #
is the smallest positive integer that both lcm
x yx
and y
divide.
class (Ord a, Ring a, Enum a, EuclideanDomain a) => Integral a where Source #
div :: a -> a -> a infixl 7 Source #
mod :: a -> a -> a infixl 7 Source #
ifThenElse :: Bool -> t -> t -> t Source #
class Algebraic a => Transcendental a where Source #
Class providing transcendental functions
(**) :: a -> a -> a infixr 8 Source #
logBase :: a -> a -> a Source #
computes log1p
x
, but provides more precise
results for small (absolute) values of log
(1 + x)x
if possible.
Since: 4.9.0.0
computes expm1
x
, but provides more precise
results for small (absolute) values of exp
x - 1x
if possible.
Since: 4.9.0.0
Instances
(^?) :: Transcendental a => a -> a -> a infixr 8 Source #
class Algebraic a => AlgebraicallyClosed a where Source #
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
(RealFloat a, Transcendental a) => AlgebraicallyClosed (Complex a) Source # | |
Defined in Algebra.Classes imaginaryUnit :: Complex a Source # |
Product | |
|
Instances
Multiplicative a => Monoid (Product a) Source # | |
Multiplicative a => Semigroup (Product a) Source # | |
Generic (Product a) Source # | |
Show a => Show (Product a) Source # | |
Eq a => Eq (Product a) Source # | |
Ord a => Ord (Product a) Source # | |
Defined in Algebra.Classes | |
type Rep (Product a) Source # | |
Defined in Algebra.Classes |
App (f x) |