
Hi, Is there some way to tell ghc, how to interpret numeric literals? I would like it to interpret 1 as 1 :: Integer not 1 as fromInteger (1 :: Integer) I have been playing with the following (rather ugly) code. {-# OPTIONS -XFunctionalDependencies -XMultiParamTypeClasses -XTypeSynonymInstances #-} module Test where import Prelude(Integer, Double) import qualified Prelude as P default(Integer, Double) type Z = Integer type R = Double class Plus a b c | a b -> c where (+) :: a -> b -> c instance Plus Z Z Z where j + k = j P.+ k instance Plus R R R where x + y = x P.+ y instance Plus R Z R where x + j = x P.+ P.fromInteger j instance Plus Z R R where j + x = P.fromInteger j P.+ x x = (1 :: Z) + (1.0 :: R) --y = 1 + 1.0 The commented line can't be compiled (because of ambiguous types, I think). - Lauri

On Fri, Mar 20, 2009 at 10:06 AM, Lauri Oksanen
Hi,
Is there some way to tell ghc, how to interpret numeric literals? I would like it to interpret 1 as 1 :: Integer not 1 as fromInteger (1 :: Integer)
Check out this section from the haskell language report: http://www.haskell.org/onlinereport/decls.html#default-decls
Only one default declaration is permitted per module, and its effect is limited to that module. If no default declaration is given in a >module then it assumed to be:
default (Integer, Double)
The empty default declaration, default (), turns off all defaults in a module.
Perhaps turning off all defaults will solve your problem? Regards, Roel

I think your best bet is -fno-implicit-prelude, and defining
fromInteger = id :: Integer->Integer.
On Fri, Mar 20, 2009 at 10:06 AM, Lauri Oksanen
Hi,
Is there some way to tell ghc, how to interpret numeric literals? I would like it to interpret 1 as 1 :: Integer not 1 as fromInteger (1 :: Integer)
I have been playing with the following (rather ugly) code.
{-# OPTIONS -XFunctionalDependencies -XMultiParamTypeClasses -XTypeSynonymInstances #-} module Test where import Prelude(Integer, Double) import qualified Prelude as P default(Integer, Double)
type Z = Integer type R = Double
class Plus a b c | a b -> c where (+) :: a -> b -> c
instance Plus Z Z Z where j + k = j P.+ k instance Plus R R R where x + y = x P.+ y
instance Plus R Z R where x + j = x P.+ P.fromInteger j instance Plus Z R R where j + x = P.fromInteger j P.+ x
x = (1 :: Z) + (1.0 :: R) --y = 1 + 1.0
The commented line can't be compiled (because of ambiguous types, I think).
- Lauri _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks for answers. Here is some working code if somebody plays later
with similar things.
{-# OPTIONS
-XNoImplicitPrelude
-XFunctionalDependencies
-XMultiParamTypeClasses
-XFlexibleInstances
#-}
module Test (
Integer
, Double
, fromInteger
, fromRational
, (+)
) where
import Prelude (Integer, Double)
import qualified Prelude as P
import qualified GHC.Real
fromInteger :: Integer -> Integer
fromInteger = P.id
fromRational :: P.Rational -> Double
fromRational (n GHC.Real.:% d) = let
n' = P.fromInteger n :: Double
d' = P.fromInteger d :: Double
in n' P./ d'
-- Prelude types ---------
instance Semigroup Integer where plus = (P.+)
instance Semigroup Double where plus = (P.+)
instance Subset Integer Double where embed = P.fromInteger
-- Class hierarchy ---------
class Plus a b c | a b -> c where
(+) :: a -> b -> c
class Semigroup a where
plus :: a -> a -> a
class Subset a b where
embed :: a -> b
instance (Semigroup a) => (Plus a a a) where (+) = plus
-- Coercion rules ---------
instance Plus Double Integer Double where
x + j = x + (embed j :: Double)
instance Plus Integer Double Double where
j + x = (embed j :: Double) + x
Ps. I'm very interested in hearing, if somebody has ideas, how to
generalize the coercion rules to something like
instance (Semigroup a) => (Subset b a) => (Plus a b a) where
x + j = x + (embed j)
- Lauri
On Fri, Mar 20, 2009 at 3:58 PM, Lennart Augustsson
I think your best bet is -fno-implicit-prelude, and defining fromInteger = id :: Integer->Integer.

That's a horrible definition of fromRational. Use
fromRational = P.fromRational.
On Fri, Mar 20, 2009 at 9:09 PM, Lauri Oksanen
Thanks for answers. Here is some working code if somebody plays later with similar things.
{-# OPTIONS -XNoImplicitPrelude -XFunctionalDependencies -XMultiParamTypeClasses -XFlexibleInstances #-} module Test ( Integer , Double , fromInteger , fromRational , (+) ) where import Prelude (Integer, Double) import qualified Prelude as P import qualified GHC.Real
fromInteger :: Integer -> Integer fromInteger = P.id
fromRational :: P.Rational -> Double fromRational (n GHC.Real.:% d) = let n' = P.fromInteger n :: Double d' = P.fromInteger d :: Double in n' P./ d'
-- Prelude types ---------
instance Semigroup Integer where plus = (P.+) instance Semigroup Double where plus = (P.+) instance Subset Integer Double where embed = P.fromInteger
-- Class hierarchy ---------
class Plus a b c | a b -> c where (+) :: a -> b -> c
class Semigroup a where plus :: a -> a -> a
class Subset a b where embed :: a -> b
instance (Semigroup a) => (Plus a a a) where (+) = plus
-- Coercion rules ---------
instance Plus Double Integer Double where x + j = x + (embed j :: Double) instance Plus Integer Double Double where j + x = (embed j :: Double) + x
Ps. I'm very interested in hearing, if somebody has ideas, how to generalize the coercion rules to something like
instance (Semigroup a) => (Subset b a) => (Plus a b a) where x + j = x + (embed j)
- Lauri
On Fri, Mar 20, 2009 at 3:58 PM, Lennart Augustsson
wrote: I think your best bet is -fno-implicit-prelude, and defining fromInteger = id :: Integer->Integer.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

True. Thanks.
- Lauri
On Sat, Mar 21, 2009 at 1:05 AM, Lennart Augustsson
That's a horrible definition of fromRational. Use fromRational = P.fromRational.
On Fri, Mar 20, 2009 at 9:09 PM, Lauri Oksanen
wrote: Thanks for answers. Here is some working code if somebody plays later with similar things.
{-# OPTIONS -XNoImplicitPrelude -XFunctionalDependencies -XMultiParamTypeClasses -XFlexibleInstances #-} module Test ( Integer , Double , fromInteger , fromRational , (+) ) where import Prelude (Integer, Double) import qualified Prelude as P import qualified GHC.Real
fromInteger :: Integer -> Integer fromInteger = P.id
fromRational :: P.Rational -> Double fromRational (n GHC.Real.:% d) = let n' = P.fromInteger n :: Double d' = P.fromInteger d :: Double in n' P./ d'
-- Prelude types ---------
instance Semigroup Integer where plus = (P.+) instance Semigroup Double where plus = (P.+) instance Subset Integer Double where embed = P.fromInteger
-- Class hierarchy ---------
class Plus a b c | a b -> c where (+) :: a -> b -> c
class Semigroup a where plus :: a -> a -> a
class Subset a b where embed :: a -> b
instance (Semigroup a) => (Plus a a a) where (+) = plus
-- Coercion rules ---------
instance Plus Double Integer Double where x + j = x + (embed j :: Double) instance Plus Integer Double Double where j + x = (embed j :: Double) + x
Ps. I'm very interested in hearing, if somebody has ideas, how to generalize the coercion rules to something like
instance (Semigroup a) => (Subset b a) => (Plus a b a) where x + j = x + (embed j)
- Lauri
On Fri, Mar 20, 2009 at 3:58 PM, Lennart Augustsson
wrote: I think your best bet is -fno-implicit-prelude, and defining fromInteger = id :: Integer->Integer.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Lauri Oksanen
-
Lennart Augustsson
-
Roel van Dijk