Data.Fixed Missing E4, E5, etc

Edward Kmett ekmett at gmail.com
Thu Aug 4 08:01:29 UTC 2016


Despite appearances the above code doesn't need overlapping instances, as
the KnownNat n constraint forces (n :: Nat), while the existing instances
are all in *.

On Thu, Aug 4, 2016 at 4:00 AM, Edward Kmett <ekmett at gmail.com> wrote:

> This could be done in a backwards compatible way by making the
> HasResolution class polykinded.
>
> {-# LANGUAGE PolyKinds, ScopedTypeVariables, DataKinds #-}
> import Data.Proxy
>
> instance KnownNat n => HasResolution n where
>   resolution _ = natVal (Proxy :: Proxy n)
>
> Then we could just keep the existing Exx for backwards compatibility or
> for folks who want portable code, and folks who want the fancier API can
> have it. Not only that but with `reflection` they could safely generate
> precision types dynamically at runtime if it was an unknown. Not a bad
> return on investment for 3 lines of code!
>
> -Edward
>
>
> On Thu, Aug 4, 2016 at 3:38 AM, Erik Hesselink <hesselink at gmail.com>
> wrote:
>
>> If Data.Fixed in base is changed, might it make more sense to switch
>> to type level naturals and KnownNat as a class? It implements exactly
>> the same functionality but in a more readable and general way.
>>
>> Erik
>>
>> On 3 August 2016 at 19:46, Andrew Martin <andrew.thaddeus at gmail.com>
>> wrote:
>> > Thanks for your response. I'm actually already doing you recommended in
>> my
>> > library. It does work, but I still think it would be better to have
>> this in
>> > base.
>> >
>> > -Andrew Martin
>> >
>> > On Wed, Aug 3, 2016 at 11:46 AM, Merijn Verstraaten <
>> merijn at inconsistent.nl>
>> > wrote:
>> >>
>> >> Hi Andrew,
>> >>
>> >> Data.Fixed actually already provides all the tools you need to support
>> any
>> >> arbitrary precision. As such, I don't see the need to add obscure
>> precisions
>> >> to the library in addition to the existing common ones. Using
>> Data.Fixed
>> >> with a 4 digit precision like you want can be achieved in 3 lines of
>> code in
>> >> you geolite library. Simply define:
>> >>
>> >> data MyPrecision
>> >> instance HasResolution MyPrecision where
>> >>     resolution _ = 4
>> >>
>> >> and use "Fixed MyPrecision" as type in your library. As you can see in
>> the
>> >> haddocks, the Num, Real, RealFrac, etc. instances work for any
>> arbitrary
>> >> instance of HasResolution.
>> >>
>> >> Cheers,
>> >> Merijn
>> >>
>> >> > On 3 Aug 2016, at 13:57, Andrew Martin <andrew.thaddeus at gmail.com>
>> >> > wrote:
>> >> >
>> >> > I've been working on a library for parsing geolite's GeoIP csv file
>> >> >
>> >> > (
>> http://hackage.haskell.org/package/geolite-csv-0.2/docs/Geolite-Types.html
>> ).
>> >> > In this file, the latitude and longitude are always given to four
>> >> > decimal points of precision. It seems like the Fixed data type (from
>> >> > Data.Fixed in base) is the best choice for representing this.
>> >> >
>> >> > However, the precision levels provided are:
>> >> >
>> >> > - E0
>> >> > - E1
>> >> > - E2
>> >> > - E3
>> >> > - E6
>> >> > - E9
>> >> > - E12
>> >> >
>> >> > I would like to propose adding all of the missing ones into
>> Data.Fixed
>> >> > as well. Even though needed a four-decimal-point-precision number is
>> >> > uncommon, it's not unheard of. Admittedly, the precision offered by
>> E11
>> >> > seems unlikely to ever be needed, but I think it would be nice for
>> >> > completeness. I would be happy to PR this if others agree that it's a
>> >> > good idea.
>> >> >
>> >> > -Andrew Martin
>> >> >
>> >> > _______________________________________________
>> >> > Libraries mailing list
>> >> > Libraries at haskell.org
>> >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>> >>
>> >
>> >
>> >
>> > --
>> > -Andrew Thaddeus Martin
>> >
>> > _______________________________________________
>> > Libraries mailing list
>> > Libraries at haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>> >
>> _______________________________________________
>> 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/20160804/303981df/attachment.html>


More information about the Libraries mailing list