add Storable a => Storable (Ratio a) and Storable a => Storable (Complex a) to base

Getting those two into base for 7.10 would be quite nice. I think this will mostly impact folks who maintain numerical computing libraries, such as myself, and even then, I think this would be a change well worth having! discussion period 1 week (because I'd like to get it OK'd with plenty of time before the merge window for 7.10 finally closes)

On Mon, 3 Nov 2014, Carter Schonwald wrote:
Getting those two into base for 7.10 would be quite nice. I think this will mostly impact folks who maintain numerical computing libraries, such as myself, and even then, I think this would be a change well worth having!
Storable (Complex a) would be nice, but how can Storable (Ratio a) work reliably? (Storable a) means that values of type 'a' are represented by a fixed number of bytes. That is, for (Storable a => Ratio a) you would have a ratio of fixed size integers. Silent overflow in integers is already nasty, but in Ratios the effect of overflows is even worse.

On Mon, Nov 3, 2014 at 6:54 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Mon, 3 Nov 2014, Carter Schonwald wrote:
Getting those two into base for 7.10 would be quite nice.
I think this will mostly impact folks who maintain numerical computing libraries, such as myself, and even then, I think this would be a change well worth having!
Storable (Complex a) would be nice, but how can Storable (Ratio a) work reliably? (Storable a) means that values of type 'a' are represented by a fixed number of bytes. That is, for (Storable a => Ratio a) you would have a ratio of fixed size integers. Silent overflow in integers is already nasty, but in Ratios the effect of overflows is even worse.
I may be missing something, but wouldn't the `Storable` constraint ensure that only integral types with a fixed size can be stored? Said another way, `Ratio a` is isomorphic to a strict pair of `a`, and the latter can clearly be serialized without any loss of precision. Why would `Ratio a` be any different? Michael

On Mon, 3 Nov 2014, Michael Snoyman wrote:
I may be missing something, but wouldn't the `Storable` constraint ensure that only integral types with a fixed size can be stored? Said another way, `Ratio a` is isomorphic to a strict pair of `a`, and the latter can clearly be serialized without any loss of precision. Why would `Ratio a` be any different?
You can serialize it without problems, but the arithmetic of Ratios with fixed size integers is pretty, say, non-standard. :-) E.g. Prelude Data.Ratio> 1%29 + 1%31 :: Rational 60 % 899 Prelude Data.Ratio> 1%29 + 1%31 :: Int8 12 % (-25)

On Mon, Nov 3, 2014 at 7:13 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Mon, 3 Nov 2014, Michael Snoyman wrote:
I may be missing something, but wouldn't the `Storable` constraint ensure
that only integral types with a fixed size can be stored? Said another way, `Ratio a` is isomorphic to a strict pair of `a`, and the latter can clearly be serialized without any loss of precision. Why would `Ratio a` be any different?
You can serialize it without problems, but the arithmetic of Ratios with fixed size integers is pretty, say, non-standard. :-)
E.g.
Prelude Data.Ratio> 1%29 + 1%31 :: Rational 60 % 899
Prelude Data.Ratio> 1%29 + 1%31 :: Int8 12 % (-25)
In other words, you don't disagree with the `Storable` instance itself being valid, it's just that it encourages bad practice? Michael

+1 from me. Storable (Ratio a) probably won't see much use, but it should exist nonetheless to prevent it having to be orphaned. On Mon, Nov 3, 2014 at 11:07 AM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
Getting those two into base for 7.10 would be quite nice.
I think this will mostly impact folks who maintain numerical computing libraries, such as myself, and even then, I think this would be a change well worth having!
discussion period 1 week (because I'd like to get it OK'd with plenty of time before the merge window for 7.10 finally closes)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Mon, 3 Nov 2014, Henning Thielemann wrote:
On Mon, 3 Nov 2014, Edward Kmett wrote:
+1 from me. Storable (Ratio a) probably won't see much use, but it should exist nonetheless to prevent it having to be orphaned.
Omitting the Ratio instance it has the advantage that people are warned.
We could also block such an instance: https://ghc.haskell.org/trac/ghc/ticket/7775 https://ghc.haskell.org/trac/ghc/ticket/9334

To be honest I don't think omitting an instance because you don't believe the type should be used at all is a useful strategy. If we want to have a discussion on the merit of allowing Ratio a to be overloaded at all I think that is a worthy discussion. Perhaps Ratio a should go away and just become Rational, but I think that is a very separate proposal. Mind you it is one that I'd support. -Edward On Mon, Nov 3, 2014 at 12:00 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Mon, 3 Nov 2014, Edward Kmett wrote:
+1 from me. Storable (Ratio a) probably won't see much use, but it should
exist nonetheless to prevent it having to be orphaned.
Omitting the Ratio instance it has the advantage that people are warned.

On Mon, 3 Nov 2014, Edward Kmett wrote:
To be honest I don't think omitting an instance because you don't believe the type should be used at all is a useful strategy.
Explicitly forbidding Storable (Ratio a) has the advantage that we can explain the reasons in the documentation of the blocking instance. In contrast, a missing instance just looks like someone has forgotten it. It would be simple to turn a blocked instance into a useful one in future, once one is found. It is also easier to do so if no orphan instances of Storable (Ratio a) lie around.

Haskell as a language and GHC as an implementation both lack a mechanism for 'explicitly forbidding the construction of an instance'. While I can accept an argument that Ratio Int and the like are 'a bad abstraction', they do exist in the language we have today, and the ability to store/load one of these things if you have one strikes me as a thing unrelated to its existence of a bad abstraction. The badness of the abstraction, however, is not helped nor harmed by the existence of a Storable instance. If you want to lobby to destroy the polymorphism of Ratio, and limit it to Rational, I'd be all for that. It is a much bigger and much more controversial debate, runs into standards issues, etc., but its one worth considering,. That said, I don't think crippling the thing we have because you don't think it should exist is the right way to go about it, though. -Edward On Mon, Nov 3, 2014 at 3:18 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Mon, 3 Nov 2014, Edward Kmett wrote:
To be honest I don't think omitting an instance because you don't believe
the type should be used at all is a useful strategy.
Explicitly forbidding Storable (Ratio a) has the advantage that we can explain the reasons in the documentation of the blocking instance. In contrast, a missing instance just looks like someone has forgotten it. It would be simple to turn a blocked instance into a useful one in future, once one is found. It is also easier to do so if no orphan instances of Storable (Ratio a) lie around.

On Mon, 3 Nov 2014, Edward Kmett wrote:
Haskell as a language and GHC as an implementation both lack a mechanism for 'explicitly forbidding the construction of an instance'.
In the links I sent, it is described how to achieve that with current available technology: https://ghc.haskell.org/trac/ghc/ticket/9334#comment:9
The badness of the abstraction, however, is not helped nor harmed by the existence of a Storable instance.
My point was, that Storable means "fixed size type", and thus it selects the inappropriate types from the Integral ones. As I said, there could be other big integer types where Ratio works, but they won't be Storable.

For Storable (Ratio a), when peeking a (Ratio a) value, should the instance reduce it to lowest terms or not? If not, then you can construct an unreduced (Ratio a) value, which AFAIK isn't otherwise possible with the Ratio API. If so, then you need an (Integral a) constraint as well as (Storable a). Furthermore, peeking a value and poking it back may change the bytes stored at the Ptr, which is unusual behavior for a Storable instance. Neither behavior seems generally useful to all programs, so I'm -1 on adding any instance for Storable (Ratio a). +1 for Storable (Complex a) though. Regards, Reid Barton On Mon, Nov 3, 2014 at 11:07 AM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
Getting those two into base for 7.10 would be quite nice.
I think this will mostly impact folks who maintain numerical computing libraries, such as myself, and even then, I think this would be a change well worth having!
discussion period 1 week (because I'd like to get it OK'd with plenty of time before the merge window for 7.10 finally closes)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I think any such instance would have to enforce the invariants of the type
and load via (%), which does mean it'd need the Integral constraint.
Loading and storing with Storable can already change some of the bits in
all sorts of types.
Nothing says that every bit configuration with a given size is a legal
inhabitant of the type we store. Consider Storable Float and Storable
Double: We silently change between quiet and signaling NaNs.
We've actually run into this in the wild at work, because a naive test we
wrote was to round trip Ermine code by loading and serializing it and
comparing the result bitwise, but loading and storing Floats/Doubles
changed them.
Similarly if you had a padded struct nothing says we'd peek the bits in the
gaps between fields.
So Storable (Ratio a) changing some bits if you round trip in and out isn't
unusual at all and in that light, I'm generally in favor of having it for
completeness.
That said I'd also support a longer term and much broader discussion about
if we want Ratio a to exist at all.
It doesn't support any of the usecases one would classically want out of a
ring of fractions, and basically exists solely as a dangerous
representation that blows up easily, and as a source of pain for users.
-Edward
On Mon, Nov 3, 2014 at 12:27 PM, Reid Barton
For Storable (Ratio a), when peeking a (Ratio a) value, should the instance reduce it to lowest terms or not?
If not, then you can construct an unreduced (Ratio a) value, which AFAIK isn't otherwise possible with the Ratio API.
If so, then you need an (Integral a) constraint as well as (Storable a). Furthermore, peeking a value and poking it back may change the bytes stored at the Ptr, which is unusual behavior for a Storable instance.
Neither behavior seems generally useful to all programs, so I'm -1 on adding any instance for Storable (Ratio a).
+1 for Storable (Complex a) though.
Regards, Reid Barton
On Mon, Nov 3, 2014 at 11:07 AM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
Getting those two into base for 7.10 would be quite nice.
I think this will mostly impact folks who maintain numerical computing libraries, such as myself, and even then, I think this would be a change well worth having!
discussion period 1 week (because I'd like to get it OK'd with plenty of time before the merge window for 7.10 finally closes)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Mon, Nov 03, 2014 at 11:07:25AM -0500, Carter Schonwald wrote:
discussion period 1 week (because I'd like to get it OK'd with plenty of time before the merge window for 7.10 finally closes)
I think an imminent release is, if anything, generally a reason for a /longer/ discussion period, to reduce the chances of making a mistake in haste. If a mistake makes it into a release, it's a lot harder to correct. Thanks Ian

Strongly +1 to Ian's suggestion about not making decisions in haste.
I guess I'm +1 to both instances. I do agree with Henning that types like
`Ratio Int16` are generally ill-advised, but that doesn't mean we should
cripple Ratio. Rather it makes me question whether `Ratio a` itself makes
sense, and perhaps we should monomorphize it to Integers. But that's a
very different proposal.
On Mon Nov 03 2014 at 9:43:55 AM Ian Lynagh
On Mon, Nov 03, 2014 at 11:07:25AM -0500, Carter Schonwald wrote:
discussion period 1 week (because I'd like to get it OK'd with plenty of time before the merge window for 7.10 finally closes)
I think an imminent release is, if anything, generally a reason for a /longer/ discussion period, to reduce the chances of making a mistake in haste. If a mistake makes it into a release, it's a lot harder to correct.
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Mon, Nov 3, 2014 at 12:57 PM, John Lato
Rather it makes me question whether `Ratio a` itself makes sense, and perhaps we should monomorphize it to Integers.
I've been questioning that for a while, to be honest. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

I dont care about Ratio a personally, but ed mentioned it when I asked for
feedback about complex a
I'm totally ok with narrowing the proposal to just Complex a IF that would
remove any objections
On Mon, Nov 3, 2014 at 1:04 PM, Brandon Allbery
On Mon, Nov 3, 2014 at 12:57 PM, John Lato
wrote: Rather it makes me question whether `Ratio a` itself makes sense, and perhaps we should monomorphize it to Integers.
I've been questioning that for a while, to be honest.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Mon, 3 Nov 2014, Brandon Allbery wrote:
On Mon, Nov 3, 2014 at 12:57 PM, John Lato
wrote: Rather it makes me question whether `Ratio a` itself makes sense, and perhaps we should monomorphize it to Integers. I've been questioning that for a while, to be honest.
There could be other big integer types. In principle, Ratio also works for polynomials, but not in the way it is defined in 'base'.

Presumably also Gaussian integers, also not the way it's defined in base. On Mon, Nov 3, 2014 at 1:15 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Mon, 3 Nov 2014, Brandon Allbery wrote:
On Mon, Nov 3, 2014 at 12:57 PM, John Lato
wrote: Rather it makes me question whether `Ratio a` itself makes sense, and perhaps we should monomorphize it to Integers.
I've been questioning that for a while, to be honest.
There could be other big integer types. In principle, Ratio also works for polynomials, but not in the way it is defined in 'base'.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Sadly using Complex for Gaussian integers isn't possible with abs/signum in
Num and that isn't changing any time soon.
On Mon, Nov 3, 2014 at 1:55 PM, David Feuer
Presumably also Gaussian integers, also not the way it's defined in base.
On Mon, Nov 3, 2014 at 1:15 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Mon, 3 Nov 2014, Brandon Allbery wrote:
On Mon, Nov 3, 2014 at 12:57 PM, John Lato
wrote: Rather it makes me question whether `Ratio a` itself makes sense, and perhaps we should monomorphize it to Integers.
I've been questioning that for a while, to be honest.
There could be other big integer types. In principle, Ratio also works for polynomials, but not in the way it is defined in 'base'.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 2014-11-03 at 18:57:27 +0100, John Lato wrote:
Rather it makes me question whether `Ratio a` itself makes sense, and perhaps we should monomorphize it to Integers. But that's a very different proposal.
IMHO, 'Ratio Natural' would be an example for something useful besides 'Ratio Integer'

On 2014-11-03 at 17:07:25 +0100, Carter Schonwald wrote:
Getting those two into base for 7.10 would be quite nice.
I think this will mostly impact folks who maintain numerical computing libraries, such as myself, and even then, I think this would be a change well worth having!
discussion period 1 week (because I'd like to get it OK'd with plenty of time before the merge window for 7.10 finally closes)
I'm +1 for the `Storable (Complex a)` instance; I am, however, +0.1 for `Storable (Ratio a)` (I'm not for it as it doesn't seem too useful (and hence used) for bounded types such as fixed-width integer, otoh I'm not totally against an instance it as it'd help avoid the temptation of orphan instances as pointed out in the discussion so far)
participants (10)
-
Brandon Allbery
-
Carter Schonwald
-
David Feuer
-
Edward Kmett
-
Henning Thielemann
-
Herbert Valerio Riedel
-
Ian Lynagh
-
John Lato
-
Michael Snoyman
-
Reid Barton