[NumericPrelude] Bug in Numeric Prelude or GHC?

Grigory Sarnitskiy sargrigory at ya.ru
Mon Jun 20 15:07:08 BST 2011


> Up to GHC-6.12 you needed to put
> {-# LANGUAGE NoImplicitPrelude #-}
> on top  of your module.
>
> From GHC-7.0 on you need
> {-# LANGUAGE RebindableSyntax #-}
>
> It tells GHC to use our custom 'negate' function, instead of the one from
> Prelude.


It still doesn't work. Here is the sample Main.hs that exhibits the behavior described:

{-# LANGUAGE RebindableSyntax #-}

module Main where

import NumericPrelude
import Algebra.Additive

data (Ord a) => Expression a =
      Var String
    | Const  a
    | Sum    [Expression a]
    | ITimes Integer (Expression a)
    deriving (Eq, Ord, Show)

instance (C a, Ord a) => C (Expression a) where
   zero     = Const zero
   negate x = ITimes (-1) x
   x + y    = Sum [x, y]

infixr 8 ***
(***) :: (C a, Ord a) => Integer -> Expression a -> Expression a
i *** f = ITimes i f

a = Var "a"

in ghci :

*Main> -a :: Expression Float

<interactive>:1:1:
    No instance for (GHC.Num.Num (Expression Float))
      arising from a use of syntactic negation
    Possible fix:
      add an instance declaration for (GHC.Num.Num (Expression Float))
    In the expression: - a :: Expression Float
    In an equation for `it': it = - a :: Expression Float



More information about the Numeric-Prelude mailing list