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

Andrew Lelechenko andrew.lelechenko at gmail.com
Wed Sep 19 19:30:29 UTC 2018


I am fine with the change proposed by Alexandre and I am also OK with DataKinds. Frankly speaking, I cannot think of any practical reason why we should be shy to use this extension.

With regards to the amount of breakage, introduced by the change, I grepped the whole Hackage for 

instance.*\b(E0|Uni|E1|Deci|E2|Centi|E3|Milli|E6|Micro|E9|Nano|E12|Pico)\b

There are matching lines in `thyme-0.3.5.5`, but it appears to be instances for Data.Thyme.Internal.Micro.Micro and not for Data.Fixed.Micro. 
It also matched `units-2.4.1`, `units-defs-2.0.1`, `unittyped-0.1`, `zm-0.3.2`, but again these are Deci/Centi/Milli/Micro/Nano/Pico defined locally. The only relevant match is in xlsx-0.7.2/test/CommonTests.hs:

instance Monad m => Serial m (Fixed E12) where ...

but it is an instance for Fixed E12 and not for E12 itself. And this module enables FlexibleInstances already.

That said, it seems to me that the breaking change, switching E0/E1/… from data type to type synonym, would not actually affect anyone. 

— 
Best regards,
Andrew

> On 17 Sep 2018, at 19:44, David Feuer <david.feuer at gmail.com> wrote:
> 
> Indeed, it's reasonable to mix and match Peano naturals with TypeLits. But that's easily done in a library that exposes a Haskell 98 interface over a TypeLits-based implementation. I don't think everyone should have to pay the potential efficiency price of Peano naturals for the sake of standards purity.
> 
> On Mon, Sep 17, 2018, 2:37 PM Henning Thielemann <lemming at henning-thielemann.de> wrote:
> 
> On Mon, 17 Sep 2018, andrew.lelechenko at gmail.com wrote:
> 
> > 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)
> > ```
> 
> I'd prefer a Haskell 98 solution and simply use type level Peano numbers 
> and define E0, E3 etc. as type synonyms. If this is not sufficiently 
> compatible we could setup a new module._______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries



More information about the Libraries mailing list