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

David Feuer david.feuer at gmail.com
Mon Sep 17 18:44:07 UTC 2018


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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20180917/56d95052/attachment.html>


More information about the Libraries mailing list