Fwd: Generalize `E{0,1,2,3,6,9,12}` from `Data.Fixed`

andrew.lelechenko at gmail.com andrew.lelechenko at gmail.com
Mon Sep 17 12:39:58 UTC 2018


(Alexandre asked me to forward the email below on his behalf, because he is experiencing technical difficulties with this mail list. — Andrew)

Greetings CLC;

I'm writing 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 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

```
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:

```
{-# LANGUAGE DataKinds      #-}
{-# LANGUAGE KindSignatures #-}

import GHC.TypeLits (Nat, KnownNat, natVal)

data E (n :: Nat)
```

and then do

```
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 have created a Trac feature request ticket with the same contents as this email, and made a PR to GHC’s repository on GitHub.
 
To finalize, there are a few topics I’d like to raise regarding this change.

1. Does the community find this change beneficial in general?
2. Does the community approve of using DataKinds in a mundane section of the base package?
3. Does everyone accept a small breaking change of E0, E1, etc. from a data type to a type synonym? Or should we go the conservative way and just add E without refactoring E0, E1, etc.?

Regards,

Alexandre

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20180917/2da206ed/attachment.html>


More information about the Libraries mailing list