[GHC] #15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed`

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: 8.6.1 Component: Core | Version: 8.4.3 Libraries | Keywords: base, | Operating System: Unknown/Multiple Data.Fixed | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Hello; I'm creating this email to propose a change to `Data.Fixed`. Full credit for this idea goes to Bhavik Mehta (@b-mehta on GitHub), who implemented it in this [https://github.com/dmcclean/exact-pi/pull/8 PR] for `exact- pi`. In `Data.Fixed` there are several `E`-prefixed datatypes used to represent a certain number of digits of precision in fixed-precision arithmetic. For example, `E1` has 1 decimal place, `E12` has 12. Each of them, `E{0,1,2,3,6,9,12}` is hardcoded. If more precision types are to be provided, they have to be hardcoded as well, and all of these types resemble each other. I think there is room for improvement here. Instead of having {{{#!hs data E0 instance HasResolution E0 where resolution _ = 1 }}} and repeating it as many times as there are `E` datatypes, I propose to add the following type: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} import GHC.TypeLits (Nat, KnownNat, natVal) data E (n :: Nat) }}} and then do {{{#!hs instance KnownNat n => HasResolution (E n) where resolution _ = 10^natVal (undefined :: E n) }}} just once, replacing `data E0` with `type E0 = E 0` (and the same for the rest of them) to continue reexporting these types. `E` should also be exported. I've sent an email to the Core Libraries Committee regarding this issue. This is my first contribution to GHC, if I'm doing something incorrectly please tell me. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rockbmb): * owner: (none) => rockbmb * cc: AshleyYakeley (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rockbmb): * cc: AshleyYakeley (removed) * cc: Ashley, Yakeley (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rockbmb): * cc: Ashley, Yakeley (removed) * cc: "Ashley, Yakeley" (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rockbmb): I am trying to add "Ashley Yakeley" to the "Cc: " field, but the whitespace is preventing me from doing so. Can someone help me with this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rockbmb): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Bodigrim):
I've sent an email to the Core Libraries Committee regarding this issue.
Are you sure? I cannot find it in https://mail.haskell.org/pipermail/libraries/2018-September/thread.html -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Indeed, since this proposes to change the existing API in `Data.Fixed`, I would first send a mail to the libraries mailing list (which Bodigrim has linked to in comment:6) and solicit community feedback. If there is a consensus that this change should be adopted, we can proceed forward with the actual implementation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Bodigrim): AFAIU the proposed implementation (https://github.com/ghc/ghc/pull/196) is backward compatible and the only visible change is a new exported entity `Data.Fixed.E`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): That is still a breaking change, since it changes `E0`, `E1`, etc. from data types to type synonyms. Among other things, this will cause programs that declare instances against these types to stop compiling if they do not enable the `FlexibleInstances` extension. That change notwithstanding, I would also be interested to hear the community's feedback on the use of the `DataKinds` GHC extension in a prominent place in `base` like `Data.Fixed`. (`DataKinds` is already used in other places in `base`, but they're mostly sectioned off within the `GHC.*` namespace, where language extension experimentation is more readily tolerated.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rockbmb): I received this email from Microsoft not long after I sent an email to libraries@haskell.org: Delivery has failed to these recipients or groups: Haskell Libraries (libraries@haskell.org) Your message couldn't be delivered. Despite repeated attempts to contact the recipient's email system it didn't respond. Contact the recipient by some other means (by phone, for example) and ask them to tell their email admin that it appears that their email system isn't accepting connection requests from your email system. Give them the error details shown below. It's likely that the recipient's email admin is the only one who can fix this problem. I'll try again. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rockbmb): I just tried sending it again, it does not work. I received no confirmation of having sent the message, and I could not see it in September's threads. I've triple-checked my Mailman settings, I don't know what the issue is. I'll try to solve this so the mail gets sent. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Bodigrim):
Among other things, this will cause programs that declare instances against these types to stop compiling if they do not enable the FlexibleInstances extension.
As I noticed in a CLC mail thread(https://mail.haskell.org/pipermail/libraries/2018-September/028975.html), no code from Hackage derives such instances currently. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rockbmb): Since no code from Hackage derives instances against these types currently, does anyone disagree it is safe to assume no code (published on Hackage) will break from this change? Projects not uploaded to Hackage or that are closed-source and rely on GHC may have issues if they have instances defined for `E0/E1...`, but I do not think they will be too great. In these cases, would the addition of `FlexibleInstances` be problematic? I do not think so, but that is my opinion. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ashley Yakeley): 1. The time library uses Fixed, so I'm not sure the Hackage search was good? 2. As written, the proposed change eliminates non-base-10 Fixed. Are we sure we want to do that? 3. If we're considering breaking changes to Data.Fixed, the more urgent need (imo) is to generalise the representation type, which is currently hard-coded as Integer. Touching both points 2 and 3, [https://en.wikipedia.org/wiki/Q_(number_format) Q formats] are fixed- point with a given number of fractional lower bits. It would be useful to be able to represent these. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ashley Yakeley): I would also like to see Data.Fixed (and possibly also Data.Ratio and Data.Complex) put in a new core library. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

1. As written, the proposed change eliminates non-base-10 Fixed. Are we sure we want to do that?
2. If we're considering breaking changes to Data.Fixed, the more urgent need (imo) is to generalise the representation type, which is currently hard-coded as Integer.
Touching both points, [https://en.wikipedia.org/wiki/Q_(number_format) Q
#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rockbmb): Replying to [comment:14 Ashley Yakeley]: formats] are fixed-point with a given number of fractional lower bits. It would be useful to be able to represent these. I do not understand the point you make in 1., could you please elaborate? Regarding 2., I understand and agree. Would replacing a hardcoded `Integer` with `Integral a => ...` be sufficient? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ashley Yakeley): Never mind, it looks like my first point is not a concern, because you can still create other instances of HasResolution. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rockbmb): Replying to [comment:17 Ashley Yakeley]:
Never mind, it looks like my first point is not a concern, because you can still create other instances of HasResolution.
If that is the case, I do not mind addressing your second point in the PR I already made. Regarding Q formats, this sounds like a worthwhile addition, but it should probably be done in a separate PR, with a ticket here to match. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Bodigrim): Actually, we can generalise the current approach to any base: {{{#!hs data E (n :: Nat) instance KnownNat n => HasResolution (E n) where resolution = natVal . Compose type Milli = E 1000 }}} ------ With regards to the representation type: it does not make much sense to have `Int8` with resolution 1000. And there are only two integer types with arbitrary precision available in `base`. IMHO it is reasonable to stick to `Integer`, not least because it allows to avoid having any visible breaking change at all. ------
I would also like to see Data.Fixed (and possibly also Data.Ratio and Data.Complex) put in a new core library.
I believe it could be desired, if there is a demand for a more rapid development of these modules than for the rest of `base`, but as far as I see this is not the case. Otherwise I do not see any direct benefits of such breaking change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rockbmb): Replying to [comment:19 Bodigrim]:
Actually, we can generalise the current approach to any base: {{{#!hs data E (n :: Nat)
instance KnownNat n => HasResolution (E n) where resolution = natVal . Compose
type Milli = E 1000 }}}
How would the `Compose` help with numeric bases here? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Bodigrim): `Compose` itself makes no difference, of course. The instance from your PR is equivalent to `resolution = (10 ^) . natVal . Compose`. My suggestion is to put `resolution = natVal . Compose`, which makes us able to express desired accuracy both in decimal (`E 1000`) and binary (`E 1024`) digits, as well as in any other base. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ashley Yakeley): Alternatively, use Nat directly? {{{ newtype Fixed (n :: Nat) = MkFixed Integer }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ashley Yakeley): Regarding representation type, the performance of the time library, as well as ease of serialisation, might be improvable if `DiffTime` and `NominalDiffTime` (which wrap `Pico`) were represented with 128-bit integer type rather than `Integer`. See https://github.com/haskell/time/issues/80. That said, I'm not feeling a lot of pressure for this at the moment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ashley Yakeley): If I were starting over, with no compatibility concerns, I would certainly do this: {{{ newtype Fixed a (n :: Nat) = MkFixed a }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ashley Yakeley): `Nat` is just a wrapper for `Integer`, isn't it? As opposed to `data Nat = Z | S Nat`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Bodigrim): Replying to [comment:22 Ashley Yakeley]:
Alternatively, use Nat directly?
{{{ newtype Fixed (n :: Nat) = MkFixed Integer }}}
Yeah, looks nice. But one should scan Hackage again to make sure that no one derived `HasResolution` instances for his own types. Replying to [comment:25 Ashley Yakeley]:
`Nat` is just a wrapper for `Integer`, isn't it? As opposed to `data Nat = Z | S Nat`?
Yes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rockbmb): Replying to [comment:21 Bodigrim]:
`Compose` itself makes no difference, of course. The instance from your PR is equivalent to `resolution = (10 ^) . natVal . Compose`. My suggestion is to put `resolution = natVal . Compose`, which makes us able to express desired accuracy both in decimal (`E 1000`) and binary (`E 1024`) digits, as well as in any other base.
I understand now, I failed to notice that where I wrote `type Milli = E 3`, you wrote `type Milli = E 1000`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rockbmb): Replying to [comment:24 Ashley Yakeley]:
If I were starting over, with no compatibility concerns, I would certainly do this:
{{{ newtype Fixed a (n :: Nat) = MkFixed a }}}
In this case, isn't one of the two false: * One of the type parameters is unnecessary (I'd say `a`) * `HasResolution` is unnecessary ? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rockbmb): * cc: "Ashley, Yakeley" (removed) * cc: Ashley, Yakeley (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Bodigrim): I believe there are many shiny things which could be done, if we start from the scratch. Unfortunately, we don't. Also, my understanding is that no one has an appetite for visible breaking changes. Can we have it implemented as proposed in PR or as described in comment:19? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15622: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed` -------------------------------------+------------------------------------- Reporter: rockbmb | Owner: rockbmb Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.3 Resolution: | Keywords: base, | Data.Fixed Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rockbmb): I've pinged a maintainer on the GitHub's PR page, I would also like to either close or move forward with this, either as it currently is or with @Bodigrim's change. More elaborate changes can always come afterwards. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15622#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC