Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- class C a
- zero :: C a => a
- (+), (-) :: C a => a -> a -> a
- (+), (-) :: C a => a -> a -> a
- negate :: C a => a -> a
- subtract :: C a => a -> a -> a
- sum :: C a => [a] -> a
- sum1 :: C a => [a] -> a
- sumNestedAssociative :: C a => [a] -> a
- sumNestedCommutative :: C a => [a] -> a
- elementAdd :: C x => (v -> x) -> T (v, v) x
- elementSub :: C x => (v -> x) -> T (v, v) x
- elementNeg :: C x => (v -> x) -> T v x
- (<*>.+) :: C x => T (v, v) (x -> a) -> (v -> x) -> T (v, v) a
- (<*>.-) :: C x => T (v, v) (x -> a) -> (v -> x) -> T (v, v) a
- (<*>.-$) :: C x => T v (x -> a) -> (v -> x) -> T v a
- propAssociative :: (Eq a, C a) => a -> a -> a -> Bool
- propCommutative :: (Eq a, C a) => a -> a -> Bool
- propIdentity :: (Eq a, C a) => a -> Bool
- propInverse :: (Eq a, C a) => a -> Bool
Class
Additive a encapsulates the notion of a commutative group, specified by the following laws:
a + b === b + a (a + b) + c === a + (b + c) zero + a === a a + negate a === 0
Typical examples include integers, dollars, and vectors.
Instances
C Double Source # | |
C Float Source # | |
C Int Source # | |
C Int8 Source # | |
C Int16 Source # | |
C Int32 Source # | |
C Int64 Source # | |
C Integer Source # | |
C Word Source # | |
C Word8 Source # | |
C Word16 Source # | |
C Word32 Source # | |
C Word64 Source # | |
C T Source # | |
C T Source # | |
C T Source # | |
C T Source # | |
C v => C [v] Source # | The |
Integral a => C (Ratio a) Source # | |
RealFloat a => C (Complex a) Source # | |
(Ord a, C a) => C (T a) Source # | |
C a => C (T a) Source # | |
Num a => C (T a) Source # | |
(Eq a, C a) => C (T a) Source # | |
C a => C (T a) Source # | |
(Eq a, C a) => C (T a) Source # | |
C a => C (T a) Source # | |
C a => C (T a) Source # | |
C a => C (T a) Source # | |
C a => C (T a) Source # | |
C a => C (T a) Source # | |
C a => C (T a) Source # | |
(C a, C a) => C (T a) Source # | |
(C a, C a, C a) => C (T a) Source # | genPartialFractionInt /\ \x -> genPartialFractionInt /\ \y -> add x y genPartialFractionInt /\ \x -> genPartialFractionInt /\ \y -> sub x y genPartialFractionPoly /\ \x -> genPartialFractionPoly /\ \y -> add x y genPartialFractionPoly /\ \x -> genPartialFractionPoly /\ \y -> sub x y |
C a => C (T a) Source # | genIntMatrix /\ \a -> genSameMatrix a /\ \b -> Laws.commutative (+) a b genIntMatrix /\ \a -> genSameMatrix a /\ \b -> genSameMatrix b /\ \c -> Laws.associative (+) a b c |
C a => C (T a) Source # | |
C a => C (T a) Source # | |
C a => C (T a) Source # | |
C a => C (T a) Source # | |
C v => C (b -> v) Source # | |
(C v0, C v1) => C (v0, v1) Source # | |
(Ord i, Eq v, C v) => C (Map i v) Source # | |
(Ord a, C b) => C (T a b) Source # | |
C v => C (T a v) Source # | |
(C u, C a) => C (T u a) Source # | |
(Ord i, C a) => C (T i a) Source # | |
C v => C (T a v) Source # | |
(C v0, C v1, C v2) => C (v0, v1, v2) Source # | |
subtract :: C a => a -> a -> a Source #
subtract
is (-)
with swapped operand order.
This is the operand order which will be needed in most cases
of partial application.
Complex functions
sum :: C a => [a] -> a Source #
Sum up all elements of a list. An empty list yields zero.
This function is inappropriate for number types like Peano.
Maybe we should make sum
a method of Additive.
This would also make lengthLeft
and lengthRight
superfluous.
sum1 :: C a => [a] -> a Source #
Sum up all elements of a non-empty list. This avoids including a zero which is useful for types where no universal zero is available. ToDo: Should have NonEmpty type.
\(QC.NonEmpty ns) -> A.sum ns == (A.sum1 ns :: Integer)
sumNestedAssociative :: C a => [a] -> a Source #
Sum the operands in an order, such that the dependencies are minimized. Does this have a measurably effect on speed?
Requires associativity.
\ns -> A.sum ns == (A.sumNestedAssociative ns :: Integer)
sumNestedCommutative :: C a => [a] -> a Source #
Make sure that the last entries in the list are equally often part of an addition. Maybe this can reduce rounding errors. The list that sum2 computes is a breadth-first-flattened binary tree.
Requires associativity and commutativity.
\ns -> A.sum ns == (A.sumNestedCommutative ns :: Integer)
Instance definition helpers
elementAdd :: C x => (v -> x) -> T (v, v) x Source #
Instead of baking the add operation into the element function,
we could use higher rank types
and pass a generic uncurry (+)
to the run function.
We do not do so in order to stay Haskell 98
at least for parts of NumericPrelude.
elementSub :: C x => (v -> x) -> T (v, v) x Source #
elementNeg :: C x => (v -> x) -> T v x Source #
(<*>.+) :: C x => T (v, v) (x -> a) -> (v -> x) -> T (v, v) a infixl 4 Source #
addPair :: (Additive.C a, Additive.C b) => (a,b) -> (a,b) -> (a,b) addPair = Elem.run2 $ Elem.with (,) <*>.+ fst <*>.+ snd