"Natural" polymorphism for n*(n+1)/2

Some nominally rational functions, e.g n*(n+1)/2, yield integer values for integer arguments. I seek either a way to wrap such a function so it has type Num a => a->a or a convincing argument that it can't be done. Doug

On Wed, 16 Dec 2020, M Douglas McIlroy wrote:
Some nominally rational functions, e.g n*(n+1)/2, yield integer values for integer arguments. I seek either a way to wrap such a function so it has type Num a => a->a or a convincing argument that it can't be done.
Num will be difficult, but with Integral class you could use 'div'.

I very much doubt that Num a is sufficient. That's not even enough to check whether a number is even. You can certainly perform the calculation with `Integral a`, but you'll have to apply some external reasoning to see that the result is correct. On Wed, Dec 16, 2020, 4:45 PM M Douglas McIlroy < m.douglas.mcilroy@dartmouth.edu> wrote:
Some nominally rational functions, e.g n*(n+1)/2, yield integer values for integer arguments. I seek either a way to wrap such a function so it has type Num a => a->a or a convincing argument that it can't be done.
Doug _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Num + Enum would be enough though, since n*(n+1)/2 = sum [1..n], n*(n+1)*(n+2)/6 = sum (map (\m -> sum [1..m]) [1..n]) etc. Not quite effective, of course.
On 16 Dec 2020, at 22:57, David Feuer
wrote: I very much doubt that Num a is sufficient. That's not even enough to check whether a number is even. You can certainly perform the calculation with `Integral a`, but you'll have to apply some external reasoning to see that the result is correct.
On Wed, Dec 16, 2020, 4:45 PM M Douglas McIlroy
wrote: Some nominally rational functions, e.g n*(n+1)/2, yield integer values for integer arguments. I seek either a way to wrap such a function so it has type Num a => a->a or a convincing argument that it can't be done. Doug _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Num alone is enough: sum [1..n] = sum (map fromInteger [1..n]) On 12/16/20 11:07 PM, MigMit wrote:
Num + Enum would be enough though, since n*(n+1)/2 = sum [1..n], n*(n+1)*(n+2)/6 = sum (map (\m -> sum [1..m]) [1..n]) etc. Not quite effective, of course.
On 16 Dec 2020, at 22:57, David Feuer
wrote: I very much doubt that Num a is sufficient. That's not even enough to check whether a number is even. You can certainly perform the calculation with `Integral a`, but you'll have to apply some external reasoning to see that the result is correct.
On Wed, Dec 16, 2020, 4:45 PM M Douglas McIlroy
wrote: Some nominally rational functions, e.g n*(n+1)/2, yield integer values for integer arguments. I seek either a way to wrap such a function so it has type Num a => a->a or a convincing argument that it can't be done. Doug _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

A small optimization, maybe: fromInteger ((n * (n+1)) `div` 2)?
On 16 Dec 2020, at 23:13, Jaro Reinders
wrote: Num alone is enough: sum [1..n] = sum (map fromInteger [1..n])
On 12/16/20 11:07 PM, MigMit wrote:
Num + Enum would be enough though, since n*(n+1)/2 = sum [1..n], n*(n+1)*(n+2)/6 = sum (map (\m -> sum [1..m]) [1..n]) etc. Not quite effective, of course.
On 16 Dec 2020, at 22:57, David Feuer
wrote: I very much doubt that Num a is sufficient. That's not even enough to check whether a number is even. You can certainly perform the calculation with `Integral a`, but you'll have to apply some external reasoning to see that the result is correct.
On Wed, Dec 16, 2020, 4:45 PM M Douglas McIlroy
wrote: Some nominally rational functions, e.g n*(n+1)/2, yield integer values for integer arguments. I seek either a way to wrap such a function so it has type Num a => a->a or a convincing argument that it can't be done. Doug _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

That has n :: Integer, not n :: a, right? @Douglas: What about the ring of polynomials over the integers, i.e. Z[X]? We can certainly define a Num instance for that if we set 'signum _ = 1' and 'abs = id'. 'fromInteger' then injects constant polynomials. However, if 'n' is X + 1, then n*(n+1) is X^2 + 3X + 2; what's that divided by 2? Not well-defined, since we were talking about polynomials over the integers. If your function is to have type Num a => a -> a, it will need to handle this case, but I don't see a way in which it can. - Tom P.S. Unless, of course, you allow extra typeclasses; other posters have already suggested (inefficient) versions for Ord and Enum. -------- Original Message -------- On 16 Dec 2020, 23:13, Jaro Reinders < jaro.reinders@gmail.com> wrote: Num alone is enough: sum [1..n] = sum (map fromInteger [1..n]) On 12/16/20 11:07 PM, MigMit wrote:
Num + Enum would be enough though, since n*(n+1)/2 = sum [1..n], n*(n+1)*(n+2)/6 = sum (map (\m -> sum [1..m]) [1..n]) etc. Not quite effective, of course.
On 16 Dec 2020, at 22:57, David Feuer
wrote:
I very much doubt that Num a is sufficient. That's not even enough to check whether a number is even. You can certainly perform the calculation with `Integral a`, but you'll have to apply some external reasoning to see that the result is correct.
On Wed, Dec 16, 2020, 4:45 PM M Douglas McIlroy
wrote:
Some nominally rational functions, e.g n*(n+1)/2,
yield integer values for integer arguments. I seek
either a way to wrap such a function so it has type
Num a => a->a or a convincing argument that it can't
be done.
Doug
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Wed, 16 Dec 2020, Tom Smeding wrote:
@Douglas: What about the ring of polynomials over the integers, i.e. Z[X]? We can certainly define a Num instance for that if we set 'signum _ = 1' and 'abs = id'. 'fromInteger' then injects constant polynomials.
I also thought about polynomials, but Num is a Ring plus 'signum' and 'abs'. Are your definitions ob 'signum' and 'abs' sound? Are there other sound definitions that may allow the n*(n+1)/2 magic?

I'm not sure what "sound" means if the documentation[1] for Num states that the only reasonable expectation is that of a ring. However, if we are to have laws for signum and abs, then I would expect that 'abs n = n * signum n'. My definitions satisfy that law. Furthermore for polynomials, I don't think there is a useful definition of 'abs' where 'abs n' has a higher degree than 'n' itself. Assuming that 'abs' does not increase the degree, I don't think there are any other _useful_ definitions of abs and signum than the ones I gave: multiplication in Z[X] will never decrease the degree, so the degree of 'n * signum n' is at least that of 'n', and therefore the degree of 'abs n' is the same as that of 'n'; therefore 'signum n' is a constant polynomial (without X'es). With that restriction the only reasonable choice I see is 'signum = const 1'. But even if you take 'abs' and 'signum' to be absolutely wild functions, to be able to write n*(n+1)/2 you need to define your division operator. There is certainly not one in base that will work for 'Int -> Int' as well as 'Float -> Float' as well as 'Poly Integer -> Poly Integer'. And in particular not abs nor signum. :) - Tom [1]: https://hackage.haskell.org/package/base-4.14.1.0/docs/Prelude.html#t:Num -------- Original Message -------- On 16 Dec 2020, 23:26, Henning Thielemann < lemming@henning-thielemann.de> wrote: On Wed, 16 Dec 2020, Tom Smeding wrote:
@Douglas:
What about the ring of polynomials over the integers, i.e. Z[X]? We can certainly define a Num instance for that
if we set 'signum _ = 1' and 'abs = id'. 'fromInteger' then injects constant polynomials.
I also thought about polynomials, but Num is a Ring plus 'signum' and 'abs'. Are your definitions ob 'signum' and 'abs' sound? Are there other sound definitions that may allow the n*(n+1)/2 magic?

On Wed, 16 Dec 2020, Tom Smeding wrote:
I'm not sure what "sound" means if the documentation[1] for Num states that the only reasonable expectation is that of a ring.
However, if we are to have laws for signum and abs, then I would expect that 'abs n = n * signum n'. My definitions satisfy that law.
What about abs x = x/2 and signum _ = 2? Would satisfy your law and solve the problem of the original poster.

You say 'abs x = x/2', but what's that (/)? For example, what is 'abs' supposed to give when called on (the representation of) the polynomial X^2 + 3X + 2? Interesting also to think about what the meaning of 'n*(n+1)/2' on polynomials should even be. What is the sum of the numbers (polynomials?) from 1 to X + 1? - Tom -------- Original Message -------- On 16 Dec 2020, 23:48, Henning Thielemann < lemming@henning-thielemann.de> wrote: On Wed, 16 Dec 2020, Tom Smeding wrote:
I'm not sure what "sound" means if the documentation[1] for Num states that the only reasonable expectation is
that of a ring.
However, if we are to have laws for signum and abs, then I would expect that 'abs n = n * signum n'. My
definitions satisfy that law.
What about abs x = x/2 and signum _ = 2? Would satisfy your law and solve the problem of the original poster.

On Wed, 16 Dec 2020, Tom Smeding wrote:
You say 'abs x = x/2', but what's that (/)? For example, what is 'abs' supposed to give when called on (the representation of) the polynomial X^2 + 3X + 2?
I meant it this way: instance (Fractional a) => Num (Polynomial a) where abs = fmap (/2)

Good point, that would allow the original, desired function to be written 'f :: Num a => a -> a; f n = abs (n * (n + 1))'. However, that doesn't do the right thing when 'a' is Int or Float. Any candidate 'f' would need to be written, all auxiliary functions inlined, in terms of the operations of Num. Since there is no way to do that when a ~ Int (since the Num Int instance doesn't have backdoors like this), it won't work. My polynomial example really only gives a conceptual idea why it _shouldn't_ work. Assuming I'm not missing something; it's late here. - Tom -------- Original Message -------- On 17 Dec 2020, 00:13, Henning Thielemann < lemming@henning-thielemann.de> wrote: On Wed, 16 Dec 2020, Tom Smeding wrote:
You say 'abs x = x/2', but what's that (/)? For example, what is 'abs'
supposed to give when called on (the representation of) the polynomial
X^2 + 3X + 2?
I meant it this way: instance (Fractional a) => Num (Polynomial a) where abs = fmap (/2)

here's why it cannot be done: data TwoByTwoMatrix = TTM Integer Integer Integer Integer instance Num TwoByTwoMatrix where fromInteger i = TTM i 0 0 i (TTM a b c d) + (TTM e f g h) = TTM (a+e) (b+f) (c+g) (d+h) negate m = (fromInteger (-1)) * m (TTM a b c d) * (TTM e f g h) = TTM (b*g+a*e) (a*f+b*h) (d*g+c*e) (c*f+d*h) It should follow that the above is a (non-abelian) ring, as required (all definitions follow the standard matrix addition/multiplication/addition convensions). n = (TTM 0 1 0 0) then: n * (n + 1) = n. Since n has odd entries, it cannot be divided by 2 (more precisely: we cannot find an m s.t. n * 2 = m). Best, Sebastiaan On Wed, Dec 16, 2020 at 6:14 PM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Wed, 16 Dec 2020, Tom Smeding wrote:
You say 'abs x = x/2', but what's that (/)? For example, what is 'abs' supposed to give when called on (the representation of) the polynomial X^2 + 3X + 2?
I meant it this way:
instance (Fractional a) => Num (Polynomial a) where abs = fmap (/2) _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (7)
-
David Feuer
-
Henning Thielemann
-
Jaro Reinders
-
M Douglas McIlroy
-
MigMit
-
Sebastiaan Joosten
-
Tom Smeding