[Haskell-cafe] Num instances for 2-dimensional types

Henning Thielemann lemming at henning-thielemann.de
Mon Oct 5 17:58:28 EDT 2009


On Mon, 5 Oct 2009, Soenke Hahn wrote:

> On Monday 05 October 2009 10:14:02 pm Henning Thielemann wrote:
>>
>> I use NumericPrelude that has more fine grained type classes. E.g. (+)
>> is in Additive and (*) is in Ring.
>>
>> http://hackage.haskell.org/package/numeric-prelude
>>
>
> That is pretty cool, thanks. How do your import statements look like, when you
> use numeric-prelude? Mine look a bit ugly:
>
> import Prelude hiding ((+), (-), negate)
> import Algebra.Additive ((+), (-), negate)

{-# LANGUAGE NoImplicitPrelude #-}

or

import Prelude ()

and

import qualified Algebra.Additive as Additive   (e.g. for Additive.C)
import NumericPrelude
import PreludeBase

The first form is necessary if you use number literals, what is the case 
for you I think.


More information about the Haskell-Cafe mailing list