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

Henning Thielemann lemming at henning-thielemann.de
Mon Sep 17 18:37:15 UTC 2018


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.


More information about the Libraries mailing list