vector-space and standard API for vectors

Hello everyone! It's well known that Num & Co type classes are not adequate for vectors (I don't mean arrays). I have an idea how to address this problem. Conal Elliott wrote very nice set of type classes for vectors. (Definition below). I used them for some time and quite pleased. Code is concise and readable.
class AdditiveGroup v where zeroV :: v (^+^) :: v -> v -> v negateV :: v -> v
class AdditiveGroup v => VectorSpace v where type Scalar v :: * (*^) :: Scalar v -> v -> v
class VectorSpace v => InnerSpace v where (<.>) :: v -> v -> Scalar v
There are few problems though. Fisrt one is inlining. Functions are not inlined so if client code uses uses stream fusion it breaks. Second is dependecies. Vector-space doesn't have big chain of dependencies. People may be reluctant to use vector-spaces just for API for small packages. My proposal is to split type classes above into separate package which provide only type classes, doesn't have any dependencies. Second point is to lean more on performance side in performance vs elegance. Add INLINE pragmas everywhere (unfortunate feature of stream fusion), move ^-^ to AdditiveGroup with default implementation. I'd like to know opinion of haskellers on this and specifically opinion of Conal Eliott as author and maintainer (I CC'ed him)

On 10/22/10 8:46 AM, Alexey Khudyakov wrote:
Hello everyone!
It's well known that Num & Co type classes are not adequate for vectors (I don't mean arrays). I have an idea how to address this problem.
Conal Elliott wrote very nice set of type classes for vectors. (Definition below). I used them for some time and quite pleased. Code is concise and readable.
class AdditiveGroup v where zeroV :: v (^+^) :: v -> v -> v negateV :: v -> v [...] I'd like to know opinion of haskellers on this and specifically opinion of Conal Eliott as author and maintainer (I CC'ed him)
Just my standard complaint: lack of support for semirings, modules, and other simple/general structures. How come everyone's in such a hurry to run off towards Euclidean spaces et al.? I'd rather see, class Additive v where -- or AdditiveMonoid, if preferred zeroV :: v (^+^) :: v -> v -> v class Additive v => AdditiveGroup v where negateV :: v -> v type family Scalar :: * -> * class Additive v => LeftModule v where (*^) :: Scalar v -> v -> v class Additive v => RightModule v where (^*) :: v -> Scalar v -> v ... Though I don't know how much that'd affect the niceness properties you mentioned. -- Live well, ~wren

On 23.10.2010 05:11, wren ng thornton wrote:
On 10/22/10 8:46 AM, Alexey Khudyakov wrote:
Hello everyone!
It's well known that Num & Co type classes are not adequate for vectors (I don't mean arrays). I have an idea how to address this problem.
Conal Elliott wrote very nice set of type classes for vectors. (Definition below). I used them for some time and quite pleased. Code is concise and readable.
class AdditiveGroup v where zeroV :: v (^+^) :: v -> v -> v negateV :: v -> v [...] I'd like to know opinion of haskellers on this and specifically opinion of Conal Eliott as author and maintainer (I CC'ed him)
Just my standard complaint: lack of support for semirings, modules, and other simple/general structures. How come everyone's in such a hurry to run off towards Euclidean spaces et al.?
They give familiar warm fuzzy feeling. It's same as monads and applicative functors (-:
I'd rather see,
class Additive v where -- or AdditiveMonoid, if preferred zeroV :: v (^+^) :: v -> v -> v
class Additive v => AdditiveGroup v where negateV :: v -> v
Seems good for me. One more instance declaration to write and no changes in usage. However when written this way it becomes obvious that `zeroV' == `mempty' and ^+^ = mappend. Is Additive really needed then?
type family Scalar :: * -> *
class Additive v => LeftModule v where (*^) :: Scalar v -> v -> v
class Additive v => RightModule v where (^*) :: v -> Scalar v -> v
Could you give some example of data type for which (*^) ≠ flip (^*)? I couldn't imagine one.
...
Though I don't know how much that'd affect the niceness properties you mentioned.

On Saturday 23 October 2010 22:53:32, Alexey Khudyakov wrote:
type family Scalar :: * -> *
class Additive v => LeftModule v where (*^) :: Scalar v -> v -> v
class Additive v => RightModule v where (^*) :: v -> Scalar v -> v
Could you give some example of data type for which (*^) ≠ flip (^*)? I couldn't imagine one.
Take any noncommutative ring R (quaternions for example) and consider the space R^n as a) a left R-module and b) a right R-module.

On 10/23/10 4:53 PM, Alexey Khudyakov wrote:
On 23.10.2010 05:11, wren ng thornton wrote:
I'd rather see,
class Additive v where -- or AdditiveMonoid, if preferred zeroV :: v (^+^) :: v -> v -> v
class Additive v => AdditiveGroup v where negateV :: v -> v
Seems good for me. One more instance declaration to write and no changes in usage.
However when written this way it becomes obvious that `zeroV' == `mempty' and ^+^ = mappend. Is Additive really needed then?
It depends on the usage, since we don't have a nice way of having multiple Monoid instances in scope with different identifiers for their respective mzero/mappend. For example, in Edward Kmett's monoids[1] library he reuses Monoid for additive monoids and adds a new Multiplicative class for multiplicative monoids; that way you can use operators for a semiring without needing newtype wrappers everywhere in order to distinguish the two structures on the same type. When dealing with modules and vector spaces we have three or four different monoids in play: the additive and multiplicative monoids of the underlying semiring/ring/field, and the additive and multiplicative monoids of the module/vectorspace. Lacking the aforementioned feature, that means there are good reasons to have duplicate classes (i.e., they're all monoids) so long as they are documented as capturing different notions (e.g., distinguishing "scalar" and "vectorial" uses). I don't care much about the name of the class, I'd just like support for monoids, semirings,... when they lack a group, ring,... structure. [1] http://hackage.haskell.org/package/monoids
type family Scalar :: * -> *
class Additive v => LeftModule v where (*^) :: Scalar v -> v -> v
class Additive v => RightModule v where (^*) :: v -> Scalar v -> v
Could you give some example of data type for which (*^) ≠ flip (^*)? I couldn't imagine one.
Choose any underlying semiring/ring/field with non-commutative multiplication. For a simple one, consider collections of paths over a graph. Addition is choice, so union in the collection. Multiplication is concatenation, mapping over the collection. While xs+ys == ys+xs because union is commutative, xs*ys /= ys*xs because (*ys) adds ys to the end of the paths whereas (ys*) adds ys to the beginning of the path. As Daniel Fischer mentions, quaternions are another common example. -- Live well, ~wren

On 24.10.2010 03:38, wren ng thornton wrote:
On 10/23/10 4:53 PM, Alexey Khudyakov wrote:
On 23.10.2010 05:11, wren ng thornton wrote:
I'd rather see,
class Additive v where -- or AdditiveMonoid, if preferred zeroV :: v (^+^) :: v -> v -> v
class Additive v => AdditiveGroup v where negateV :: v -> v
Seems good for me. One more instance declaration to write and no changes in usage.
However when written this way it becomes obvious that `zeroV' == `mempty' and ^+^ = mappend. Is Additive really needed then?
It depends on the usage, since we don't have a nice way of having multiple Monoid instances in scope with different identifiers for their respective mzero/mappend. For example, in Edward Kmett's monoids[1] library he reuses Monoid for additive monoids and adds a new Multiplicative class for multiplicative monoids; that way you can use operators for a semiring without needing newtype wrappers everywhere in order to distinguish the two structures on the same type.
When dealing with modules and vector spaces we have three or four different monoids in play: the additive and multiplicative monoids of the underlying semiring/ring/field, and the additive and multiplicative monoids of the module/vectorspace. Lacking the aforementioned feature, that means there are good reasons to have duplicate classes (i.e., they're all monoids) so long as they are documented as capturing different notions (e.g., distinguishing "scalar" and "vectorial" uses).
I don't care much about the name of the class, I'd just like support for monoids, semirings,... when they lack a group, ring,... structure.
Then what about following type class hierarchy? I think it supports those structures. Only restriction is that it forces one to have both left and right modules. It's possible to split them but I think it will be to painful for vector spaces over R and C. class AdditiveMonoid v where (^+^) :: v → v → v zeroV :: v class AdditiveMonoid ⇒ AdditiveGroup v where negateV :: v → v -- For performance sake (^-^) :: v → v → v v ^-^ u = v ^+^ negateV u class Module v where type Scalar v :: * (*^) :: Scalar v → v → v (^*) :: v → Scalar v → v (^*) = flip (*^) class (AdditiveGroup v, Module v) ⇒ VectorSpace v class VectorSpace v ⇒ InnerSpace v where (<.>) :: v → v → Scalar v

On 10/26/10 8:51 AM, Alexey Khudyakov wrote:
On 24.10.2010 03:38, wren ng thornton wrote:
I don't care much about the name of the class, I'd just like support for monoids, semirings,... when they lack a group, ring,... structure.
Then what about following type class hierarchy? I think it supports those structures. Only restriction is that it forces one to have both left and right modules. It's possible to split them but I think it will be to painful for vector spaces over R and C.
class Module v where type Scalar v :: * (*^) :: Scalar v → v → v (^*) :: v → Scalar v → v (^*) = flip (*^)
Is there any good reason for forcing them together? Why not, use the hierarchy I proposed earlier? If you want to reduce the clutter in type signatures for real and complex vector spaces then just add to my previous -- Or just call it "Module" if preferred. class (LeftModule v, RightModule v) => AssociativeModule v where -- Law: (^*) == flip (*^) This way, when (not if) people want nonassociative modules the classes are already there. The additional overhead in defining an associative module is only three lines when using default implementation; two lines otherwise: type instance Scalar Foo = Bar instance AssociativeModule Foo where instance RightModule Foo where (^*) = flip (^*) instance LeftModule Foo where (*^) = ... vs instance Module Foo where type Scalar Foo = Bar (*^) = ... And once it's defined, the usage is the same: just require AssociativeModule and you'll pull in both (*^) and (^*). We already know that there are noncommutative modules/vectorspaces of interest (e.g., modules over quaternions and modules over graph paths), why not support them from the beginning? It seems like you're going out of your way to exclude things that would be trivial to include. This is exactly why this is my standard complaint against the various proposals out there for new numeric hierarchies. People who are used to only using R^n think the proposals are just fine, but none of the proposals capture the structures I work with daily. Which means the new proposals are no better than the Prelude for me. -- Live well, ~wren

On Wed, Oct 27, 2010 at 2:53 AM, wren ng thornton
On 10/26/10 8:51 AM, Alexey Khudyakov wrote:
On 24.10.2010 03:38, wren ng thornton wrote:
I don't care much about the name of the class, I'd just like support for monoids, semirings,... when they lack a group, ring,... structure.
Then what about following type class hierarchy? I think it supports those structures. Only restriction is that it forces one to have both left and right modules. It's possible to split them but I think it will be to painful for vector spaces over R and C.
class Module v where type Scalar v :: * (*^) :: Scalar v → v → v (^*) :: v → Scalar v → v (^*) = flip (*^)
Is there any good reason for forcing them together? Why not, use the hierarchy I proposed earlier? If you want to reduce the clutter in type signatures for real and complex vector spaces then just add to my previous
-- Or just call it "Module" if preferred. class (LeftModule v, RightModule v) => AssociativeModule v where -- Law: (^*) == flip (*^)
This way, when (not if) people want nonassociative modules the classes are already there. The additional overhead in defining an associative module is only three lines when using default implementation; two lines otherwise:
type instance Scalar Foo = Bar instance AssociativeModule Foo where instance RightModule Foo where (^*) = flip (^*) instance LeftModule Foo where (*^) = ... vs
instance Module Foo where type Scalar Foo = Bar (*^) = ...
And once it's defined, the usage is the same: just require AssociativeModule and you'll pull in both (*^) and (^*).
Main reason is that it complicate creation of instances for types for which multiplication is associative and commutative more complicated. Programmer must write three instances instead of one and they must satisfy some law. It leads to code which more difficult to understand and contain more bug (mostly dumb). This is tradeoff between usability and generality. Modules are much less frequent and much less known than vector space. I for example didn't known about their existence before. I think difficulties should be pushed on the people who define instances for non associative modules. One possibility is to add separate type classes for left and right modules and require that is type is has both Module and LeftModule instances (*^^) == (*^) class Module v where (^*) :: v -> Scalar v -> v (*^) :: Scalar v -> v -> v Of course code that is written to work with left/right modules wont work with associative modules.
We already know that there are noncommutative modules/vectorspaces of interest (e.g., modules over quaternions and modules over graph paths), why not support them from the beginning? It seems like you're going out of your way to exclude things that would be trivial to include. This is exactly why this is my standard complaint against the various proposals out there for new numeric hierarchies. People who are used to only using R^n think the proposals are just fine, but none of the proposals capture the structures I work with daily. Which means the new proposals are no better than the Prelude for me.
I have to admit that I with R^n and therefore mostly care about this use case. I think good set of type classes should be small enough (IMHO five or so). It should not require to write unnecessary code in common cases. Probably this is case when rule "one size doesn't fit all" applies.

On 10/31/10 6:36 PM, Alexey Khudyakov wrote:
On Wed, Oct 27, 2010 at 2:53 AM, wren ng thornton wrote:
Is there any good reason for forcing them together? Why not, use the hierarchy I proposed earlier? [...]
Main reason is that it complicate creation of instances for types for which multiplication is associative and commutative more complicated. Programmer must write three instances instead of one and they must satisfy some law. It leads to code which more difficult to understand and contain more bug (mostly dumb).
Regardless of the class API instances must obey the law (or else have buggy results), so the law is uninteresting. We implicitly use such laws all the time, but usually we do so without having a class constraint to make our assumptions explicit. Isn't making assumptions explicit part of the reason for using a strongly typed language? And as I mentioned previously, the burden of implementation is 2 or 3 *lines* of code. Talking about the number of class instances people must write is obfuscating the fact that it's trivial to add two lines of code. And this is code that gets written once, in a library.
This is tradeoff between usability and generality.
Your proposal, like so many I've seen before, is unusable because it lacks the necessary generality. The complexity of my proposal is insignificant: it requires only 2~3 lines of code, and an acknowledgment that there are structures other than vectorspaces.
Modules are much less frequent and much less known than vector space.
Modules are more frequent than vector spaces, by definition, because every vector space is a module. Since you're not requiring Fractional(Scalar v), there isn't even any difference between them in the class API. Your claim is like saying that we shouldn't have support for Applicative because Monads are more common. Again, there are more applicative functors than monads, the only cognitive overhead of having the Applicative class is acknowledging that there are structures other than monads, and adding Applicative enables a helpful style of programming which there is no reason to exclude.
One possibility is to add separate type classes for left and right modules and require that is type is has both Module and LeftModule instances (*^^) == (*^)
class Module v where (^*) :: v -> Scalar v -> v (*^) :: Scalar v -> v -> v
Of course code that is written to work with left/right modules wont work with associative modules.
Which my proposal fixes by making associative modules a subclass of both left- and right-modules. -- Live well, ~wren

We already know that there are noncommutative modules/vectorspaces of interest (e.g., modules over quaternions and modules over graph paths), why not support them from the beginning? It seems like you're going out of your way to exclude things that would be trivial to include. This is exactly why this is my standard complaint against the various proposals out there for new numeric hierarchies. People who are used to only using R^n think the proposals are just fine, but none of the proposals capture the structures I work with daily. Which means the new proposals are no better than the Prelude for me.
Could you tell what data structures do you use? It's difficult to think about them without concrete examples.

On 11/5/10 7:54 AM, Alexey Khudyakov wrote:
We already know that there are noncommutative modules/vectorspaces of interest (e.g., modules over quaternions and modules over graph paths), why not support them from the beginning? It seems like you're going out of your way to exclude things that would be trivial to include. This is exactly why this is my standard complaint against the various proposals out there for new numeric hierarchies. People who are used to only using R^n think the proposals are just fine, but none of the proposals capture the structures I work with daily. Which means the new proposals are no better than the Prelude for me.
Could you tell what data structures do you use? It's difficult to think about them without concrete examples.
Data structures? That varies a lot depending on the task: Data.Map, Data.Set, Data.IntMap, Data.IntSet, Data.Trie, Data.ByteString... A lot of my concrete examples of semirings and modules come from natural language processing tasks. One example I already mentioned is the semiring of a collection of paths over a graph (so something like Data.Set (Data.Seq Arc)). Path collections show up, for example, when dealing with Markov chains and HMMs where the goal is to maximize or sum the weights over all paths. To make it clearer, a Markov chain is a probabilistic version of a finite state automaton, so you have some set of nodes, and the arcs for transitioning from one node to another have probabilistic weights on them. An HMM is an extension of a Markov chain into a probabilistic version of a Moore machine, so in addition to the probabilistic transitions from state to state, we also have for each state a probability distribution over emitted symbols. An interesting problem for HMMs is this: given some observed sequence of emitted symbols, reconstruct the most likely path of states which would cause the symbol sequence to be emitted. A nearly identical problem is: given some observed sequence of symbols, determine the total probability of all state sequences which could have generated it. In addition to the perspective of HMMs as probabilistic Moore machines, there are two other perspectives which are helpful. One is the graphical model perspective where we have something that looks a bit like this (in fixed-width font): Q0 -> Q1 -> Q2 -> ... -> Qn | | | v v v S1 S2 Sn Each Sk and Qk are random variables. The random variables Qk represent being in some particular state q at time k, and the choice of which state is drawn from a probability distribution based on the state Q(k-1). The random variables Sk represent emitting some particular symbol s at time k, and the choice of which symbol is drawn from a distribution based on the state Qk. The third perspective, which is the most helpful one for solving our two problems, is if we take this graphical model and unfold it into a trellis graph (ignoring the Sk variables for now). Each node in the trellis represents an assignment of particular values to each of the random variables. So if Q1 could take on values qA, qB, and qC then we'd have three nodes for each of Q1=qA, Q1=qB, and Q1=qC. The arcs in the trellis are weighted with the probability of transitioning from one node to the next; so an arc Q1=q1 -> Q2=q2 has weight Pr(Q2=q2 | Q1=q1). A path through the trellis represents a variable assignment, which is to say a sequence of states in the Markov chain; and the weight of the path is the probability of the Markov chain taking that path. There is a general algorithm for solving the two problems I mentioned, and ultimately they're the same algorithm except with different semirings. Note that a collection of paths between two points on a graph forms a semiring[1] where sum is the union of path collections and product is the extension of paths[2], so the answers we want can be gotten by semiring homomorphisms from the collection of paths to some other domain. To get the probability of all state sequences which could give rise to a given symbol sequence we can use the probability semiring[3] ---which we can simplify to the metric space [0..1] with (+) and (*), since the algorithm ensures that all events are disjoint. This version is called the "forward algorithm". To get the probability the most likely state sequence we can use the semiring [0..1] with max and (+), which is called the "Viterbi algorithm". In practice we tend to use the log version of these semirings in order to prevent underflow. There's also a variant of the Viterbi algorithm which stores backpointers to the most likely previous state, which makes it easier to recover the most likely state sequence instead of just the (log)probability of the sequence. The Viterbi algorithm with back pointers is also a semiring: Maybe(Prob, Maybe State) with Nothing as zero, Just(1,Nothing) as one, argmax as sum: mx<+>my = do { (px,_) <- mx ; (py,_) <- my ; if px > py then mx else my }, and product: mx<*>my = do { (px,x) <- mx ; (py,y) <- my ; Just (px*py, y `mplus` x)}. The collection-of-paths semiring is noncommutative since extending the end of a path is different than extending the beginning. The Viterbi with backpointers semiring is noncommutative since we'll get different backpointers depending on the order of arguments to the product. If we extend our probabilities to use quantum probability theory then all of these probabilistic semirings become noncommutative because of order effects on quantum probabilities. These HMM problems can also be thought of from the perspective of a grammar, where HMMs happen to be restricted to produce linear derivation "trees". Looking at other grammars like probabilistic CFGs allows us to extend the idea of generating sequences to the idea of generating trees. The forward-backward algorithm for sequences (of which the forward algorithm is half) generalizes to the inside-outside algorithm for trees. Ultimately, chart parsing algorithms like CKY are doing something very similar to the Viterbi algorithm in order to determine the most likely parse tree which would give rise to some observed sentence. So all these semirings have tree-based analogues as well. This use of semirings is just like the use of monoids in finger trees[4], except that we generalize the idea from a monoid on one tree into a semiring on a packed forest of trees. Naturally there are many such semirings which are noncommutative since adding a left-child to a tree is different than adding a right-child. [1] Or actually a 2-semiring, much as a groupoid (2-group) is a generalization of groups and a category (2-monoid) is a generalization of a monoid. [2] Note that the collection of paths semiring also has something like a module structure. The "scalars" are single arcs in the underlying graph. I only say that it's something like a module/vector space, because whether the family of arcs supports its own semiring/ring/field operations depends on the specific graph in question. If we assume certain closure properties on the family of arcs, similar to the transitive closure properties of composition in categories, then it is indeed a module. However, we do not have those closure properties for the specific example in question. [3] That is the event space E with operations <+> and <*> with the empty event as zero and the certainty event as one. Colloquially <+> is the union of events and <*> is the intersection. For x,y in E their probabilities are defined by Pr(x<+>y) = Pr(x) + Pr(y) - Pr(x,y) and Pr(x<*>y) = Pr(x,y) where Pr(x,y) = Pr(x)*Pr(y) iff x and y are independent. [4] http://apfelmus.nfshost.com/articles/monoid-fingertree.html -- Live well, ~wren

Just out of curiosity, why do you (and many others I've seen with similar
proposals) talk about additive monoids? are they somehow fundamentally
different from multiplicative monoids? Or is it just a matter of notation?
When I was playing with building an algebraic hierarchy, I picked a
"neutral" operator for my monoids (I actually started at magma, but it's the
same thing) and then introduced the addition and multiplication distinction
at semirings, as it seemed pointless to distinguish them until you have a
notion of a distributive law between the two.
On Fri, Oct 22, 2010 at 9:11 PM, wren ng thornton
On 10/22/10 8:46 AM, Alexey Khudyakov wrote:
Hello everyone!
It's well known that Num & Co type classes are not adequate for vectors (I don't mean arrays). I have an idea how to address this problem.
Conal Elliott wrote very nice set of type classes for vectors. (Definition below). I used them for some time and quite pleased. Code is concise and readable.
class AdditiveGroup v where zeroV :: v (^+^) :: v -> v -> v negateV :: v -> v [...]
I'd like to know opinion of haskellers on this and specifically opinion of Conal Eliott as author and maintainer (I CC'ed him)
Just my standard complaint: lack of support for semirings, modules, and other simple/general structures. How come everyone's in such a hurry to run off towards Euclidean spaces et al.?
I'd rather see,
class Additive v where -- or AdditiveMonoid, if preferred
zeroV :: v (^+^) :: v -> v -> v
class Additive v => AdditiveGroup v where negateV :: v -> v
type family Scalar :: * -> *
class Additive v => LeftModule v where (*^) :: Scalar v -> v -> v
class Additive v => RightModule v where (^*) :: v -> Scalar v -> v
...
Though I don't know how much that'd affect the niceness properties you mentioned.
-- Live well, ~wren
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 24.10.2010 01:19, Daniel Peebles wrote:
Just out of curiosity, why do you (and many others I've seen with similar proposals) talk about additive monoids? are they somehow fundamentally different from multiplicative monoids? Or is it just a matter of notation? When I was playing with building an algebraic hierarchy, I picked a "neutral" operator for my monoids (I actually started at magma, but it's the same thing) and then introduced the addition and multiplication distinction at semirings, as it seemed pointless to distinguish them until you have a notion of a distributive law between the two.
I'm not sure that I understood your question completely. But I think it happens naturally. Authors of such proposals just don't think about monoids and abstract algebra. They think about R^n. It appears quite frequently (well it depends on domain) and Num&Co is useless. Proposals are born out of that frustration. Probably people who do care about distinction between additive and multiplicative monoids don't face that problem or it's

On 23/10/2010 5:19 PM, Daniel Peebles wrote:
Just out of curiosity, why do you (and many others I've seen with similar proposals) talk about additive monoids? are they somehow fundamentally different from multiplicative monoids?
People usually use additive notation for commutative monoids, and multiplicative notation for generic monoids. It's a convention, nothing else. Otherwise, of course they are isomorphic.
When I was playing with building an algebraic hierarchy, I picked a "neutral" operator for my monoids (I actually started at magma, but it's the same thing) and then introduced the addition and multiplication distinction at semirings, as it seemed pointless to distinguish them until you have a notion of a distributive law between the two.
How you do this really depends on what features you have for naming/renaming, how notions of inheritance/subtyping work, etc. Having multiple names for structures which are, in fact, isomorphic, turns out to be really convenient when you want to combine the structures without duplicating declarations. Let me stress that again: 'really convenient'. Not required, manditory, or anything else like that. Of course, all we really require is any Turing complete language. So if 'require' is the main criterion, we should all still be programming in assembler. There really is a reason we're having this discussion on the Haskell-cafe mailing list... Jacques

On 10/23/10 5:19 PM, Daniel Peebles wrote:
Just out of curiosity, why do you (and many others I've seen with similar proposals) talk about additive monoids? are they somehow fundamentally different from multiplicative monoids? Or is it just a matter of notation? When I was playing with building an algebraic hierarchy, I picked a "neutral" operator for my monoids (I actually started at magma, but it's the same thing) and then introduced the addition and multiplication distinction at semirings, as it seemed pointless to distinguish them until you have a notion of a distributive law between the two.
Mathematically speaking, of course you're right about the distinction only mattering once you get to semirings et al. But problems arise re the type class system and how to use it. For example, in many contexts we just want a monoid and we don't care what kind it is (e.g., fun with fingertrees). For these, it's fine to use a neutral monoid with newtype wrappers to capture the multiple monoidal structures on certain types. But in many other contexts we want to have multiple monoids in scope at once (e.g., when dealing with semirings,...). For these, the newtype approach is a nightmare of illegibility, so we should have (at least) two classes ((+),0) and ((*),1). The question then becomes: which of these is the "primary" situation? If neutral monoids are (as H98 and H2010 assume), then one of the two classes for semirings could be the same as the neutral class (as in Ed's monads). But then, how should we decide whether the additive or multiplicative structure is more "neutral"? And why should there be this syntactic imbalance when, mathematically, there isn't? I'd argue that neither usage is "primary", and therefore the best solution is actually to have three classes (neutral, additive, and multiplicative) with two functors (additive->neutral, multiplicative->neutral) to connect them[1]. In addition to removing the need to argue for primacy, it also removes the need to remember which monoid is considered the "neutral" one, as well as removing the syntactic imbalance between them. Both multiplicative and additive monoids would be on the base type, whereas the two neutral monoids would be newtypes. [1] the Exp/Log isomorphism between additive and multiplicative are not considered here, as there are good arguments both for using newtypes and for not using them. -- Live well, ~wren

On 10/23/10 7:52 PM, wren ng thornton wrote:
I'd argue that neither usage is "primary", and therefore the best solution is actually to have three classes (neutral, additive, and multiplicative) with two functors (additive->neutral, multiplicative->neutral) to connect them[1].[...]
[1] the Exp/Log isomorphism between additive and multiplicative are not considered here, as there are good arguments both for using newtypes and for not using them.
Of course, I mean "functor" in the category theoretic sense (monoid homomorphisms, in this case). Not in the type class sense, per se (though all newtypes are/can be Functors). -- Live well, ~wren

On Oct 24, 2010, at 8:52 AM, wren ng thornton wrote:
But then, how should we decide whether the additive or multiplicative structure is more "neutral"?
On Oct 24, 2010, at 7:08 AM, Jacques Carette wrote:
People usually use additive notation for commutative monoids, and multiplicative notation for generic monoids. It's a convention, nothing else.
I recently used class Monoid m where one :: m (*) :: m -> m -> m class CommutativeMonoid m where zero :: m (+) :: m -> m -> m class (Monoid s, CommutativeMonoid s) => Semiring s (The `Semiring` class only serves as a contract for additional laws.) Considering the convention Jaques mentions and my wish for splitting the two monoids underlying a semiring into separate classes, it seemed natural to use multiplicative notation for the "neutral" case. Sebastian

hi, I am trying to run and understand a lifting program from [1]. The program lifts points to moving points that vary their position over time. I made some effort to run the progrm but I do not know how to overide the +,-,*,sqr, and sqrt from the Num class. Below is my current attempt. I do not wish to change or imporve the code, rather I wish to understand it as it stands and find out what needs to be added to get the outputs shown below i.e. distance between points p1 and p2 --> 1.55 and the distance between moving points mp1 and mp2 for time 2 ----> 5.83. data Point = Point Float Float data Line = Line Point Point data Polygon = Polygon [Point] type Time = Float -- Functor Changing, which adds time parameter t to its input value. -- For example, Changing Float indicates a changing floating number (i.e. a function of time). type Changing v = Time -> v -- The abstract lifting functions class Lifts a where lift0 :: a -> f a lift1 :: (a -> b) -> f a -> f b lift2 :: (a -> b -> c) -> f a -> f b -> f c -- Not too sure about this, instance Lifts Changing Float where lift0 a = \t -> a lift1 op a = \t -> op (a t) lift2 op a b = \t -> op (a t) op (b t) class Number a where (+), (-), (*) :: a -> a -> a sqr, sqrt :: a -> a sqr a = a * a -- The class point which support vector plus and minus as well as -- distance operation is defined as follow class Number s => Points p s where x, y :: p s -> s x (Point x1 y1) = x1 y (Point x1 y1) = y1 (+), (-) :: p s -> p s -> p s (+) a b = Point (x a + x b) (y a + y b) (-) a b = Point (x a - x b) (y a - y b) dist :: p s -> p s -> s dist a b = sqrt(sqr((x a)-(x b))+sqr((y a)-(y b))) -- The lifting the operations for numbers shoukd provide a distance -- function which can be used for both static and moving points: instance Number v => Number (Changing v) where (+) = lift2 (+) (-) = lift2 (-) (*) = lift2 (*) sqrt = lift1 (sqrt) -- Running the code -- If p1 and p2 are two 2D static points, -- their distance d is calculated as follows: p1, p2 :: Point Float p1 = Point 3.4 5.5 p2 = Point 4.5 4.5 -- distance between p1 and p2 --> 1.55 d = dist p1 p2 -- For 2D moving points mp1 and mp2, their distance md, -- which is a function of time, is calculated as follows: mp1, mp2 :: Point (Changing Float) mp1 = Point (\t -> 4.0 + 0.5 * t)(\t -> 4.0 - 0.5 * t) mp2 = Point (\t -> 0.0 + 1.0 * t)(\t -> 0.0 - 1.0 * t) -- distance between mp1 and mp2 md = dist mp1 mp2 -- distance md for time 2 ----> 5.83 md 2 [1] A Mathematical Tool to Extend 2D Spatial Operations to Higher Dimensions: by Farid Karimipour1,2, Mahmoud R. Delavar1, and Andrew U. Frank2 http://books.google.ie/books?id=JUGpGN_jwf0C&pg=PA153&lpg=PA153&dq=Karimipour+%22A+Mathematical+Tool+to+Extend+2D+Spatial+Operations+to+Higher+Dimensions%22&source=bl&ots=fu-lSkPMr3&sig=ztkcRV3Cv6hn9T6iwQCJ9sB75IM&hl=en&ei=QS7ETJHPGoiA5Ab0zZW6Aw&sa=X&oi=book_result&ct=result&resnum=4&ved=0CCMQ6AEwAw#v=onepage&q=Karimipour%20%22A%20Mathematical%20Tool%20to%20Extend%202D%20Spatial%20Operations%20to%20Higher%20Dimensions%22&f=false This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

wren ng thornton schrieb:
On 10/22/10 8:46 AM, Alexey Khudyakov wrote:
Hello everyone!
It's well known that Num & Co type classes are not adequate for vectors (I don't mean arrays). I have an idea how to address this problem.
Conal Elliott wrote very nice set of type classes for vectors. (Definition below). I used them for some time and quite pleased. Code is concise and readable.
class AdditiveGroup v where zeroV :: v (^+^) :: v -> v -> v negateV :: v -> v [...] I'd like to know opinion of haskellers on this and specifically opinion of Conal Eliott as author and maintainer (I CC'ed him)
Looks like you are about to re-implement numeric-prelude. :-)
Just my standard complaint: lack of support for semirings, modules, and other simple/general structures. How come everyone's in such a hurry to run off towards Euclidean spaces et al.?
I'd rather see,
class Additive v where -- or AdditiveMonoid, if preferred zeroV :: v (^+^) :: v -> v -> v
class Additive v => AdditiveGroup v where negateV :: v -> v
type family Scalar :: * -> *
Vector (Complex a) is a vector with respect to both 'a' and 'Complex a'.

On 30 October 2010 11:07, Henning Thielemann
Looks like you are about to re-implement numeric-prelude. :-)
Ah, but Numeric-Prelude is huge though[*]. DavidA complains in the recent Cafe thread "Decoupling type classes (e.g. Applicative)?" that the Num hierarchy can't be replaced due to inertia. My own feeling is it can't be replaced because no-one can define an acceptable middle ground between the two extremes: miminal - Haskell currently (for discussion, we'll elide some of the "problems" such as the Show superclass constriant). huge - numeric-prelude or a "mathematics" system such as Aldor. [*] This is not a criticism - just an observation.

On Sat, Oct 30, 2010 at 2:07 PM, Henning Thielemann
wren ng thornton schrieb:
On 10/22/10 8:46 AM, Alexey Khudyakov wrote:
Hello everyone!
It's well known that Num & Co type classes are not adequate for vectors (I don't mean arrays). I have an idea how to address this problem.
Conal Elliott wrote very nice set of type classes for vectors. (Definition below). I used them for some time and quite pleased. Code is concise and readable.
> class AdditiveGroup v where > zeroV :: v > (^+^) :: v -> v -> v > negateV :: v -> v [...] I'd like to know opinion of haskellers on this and specifically opinion of Conal Eliott as author and maintainer (I CC'ed him)
Looks like you are about to re-implement numeric-prelude. :-)
Only limited subset. Very limited. Everything is too big to be implemented
Vector (Complex a) is a vector with respect to both 'a' and 'Complex a'.
It is but it's difficult to encode this. Type class below allows to have multiple scalars. But then type checker cannot infer type of 2 in expression `2 *^ vector' and so type signature must be added which is hardly usable class Module v s where (*^) :: s -> v -> v I think one is forced to convert real number to complex or use some operations specific to data type.

Vector (Complex a) is a vector with respect to both 'a' and 'Complex a'.
Even worse, () is a vector w.r.t. *every* scalar type. On Sat, Oct 30, 2010 at 3:07 AM, Henning Thielemann < schlepptop@henning-thielemann.de> wrote:
wren ng thornton schrieb:
On 10/22/10 8:46 AM, Alexey Khudyakov wrote:
Hello everyone!
It's well known that Num & Co type classes are not adequate for vectors (I don't mean arrays). I have an idea how to address this problem.
Conal Elliott wrote very nice set of type classes for vectors. (Definition below). I used them for some time and quite pleased. Code is concise and readable.
class AdditiveGroup v where zeroV :: v (^+^) :: v -> v -> v negateV :: v -> v [...] I'd like to know opinion of haskellers on this and specifically opinion of Conal Eliott as author and maintainer (I CC'ed him)
Looks like you are about to re-implement numeric-prelude. :-)
Just my standard complaint: lack of support for semirings, modules, and other simple/general structures. How come everyone's in such a hurry to run off towards Euclidean spaces et al.?
I'd rather see,
class Additive v where -- or AdditiveMonoid, if preferred zeroV :: v (^+^) :: v -> v -> v
class Additive v => AdditiveGroup v where negateV :: v -> v
type family Scalar :: * -> *
Vector (Complex a) is a vector with respect to both 'a' and 'Complex a'.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 02/11/2010 8:16 PM, Conal Elliott wrote:
Vector (Complex a) is a vector with respect to both 'a' and 'Complex a'.
Even worse, () is a vector w.r.t. *every* scalar type.
Why is this bad? () is the canonical 0-dimensional vector space. 0-dimensional vector spaces are very useful because they allow quite a number of linear algebra algorithms to be stated ``inductively'' with no funny special cases. Jacques

On Thursday 04 November 2010 15:33:09, Jacques Carette wrote:
On 02/11/2010 8:16 PM, Conal Elliott wrote:
Vector (Complex a) is a vector with respect to both 'a' and 'Complex a'.
Even worse, () is a vector w.r.t. *every* scalar type.
Why is this bad?
It's bad for making a type class with a "Scalar" type family (or FunDeps). instance VectorSpace () where type Scalar () = ???
() is the canonical 0-dimensional vector space. 0-dimensional vector spaces are very useful because they allow quite a number of linear algebra algorithms to be stated ``inductively'' with no funny special cases.
Jacques
participants (11)
-
Alexey Khudyakov
-
Conal Elliott
-
Daniel Fischer
-
Daniel Peebles
-
Gregory Collins
-
Henning Thielemann
-
Jacques Carette
-
Patrick Browne
-
Sebastian Fischer
-
Stephen Tetley
-
wren ng thornton