
If you add NoImplicitPrelude, I think you should also be able to do:
import Prelude hiding (Num)
import qualified Prelude (Num)
instance Num a => Plus a a where
type PlusResult a a = a
a + b = a Prelude.+ b
On Tue, Mar 12, 2013 at 2:24 PM, MigMit
On Mar 13, 2013, at 12:54 AM, "Richard A. O'Keefe"
wrote: The interesting challenge here is that we should have
Date + Period -> Date Date - Period -> Date Period + Date -> Date Period - Date -> ILLEGAL Period + Period -> Deriod Period - Period -> Period Date + Date -> ILLEGAL Date - Date -> Date
and _also_ (remember we are trying to beat C++ here) Int +/- Int -> Int.
Well, an obvious suggestion would be to use MultiParamTypeClasses and TypeFamilies:
{- LANGUAGE MultiParamTypeClasses, TypeFamilies -} module Date where import Prelude hiding (Num, (+)) data Date = Date data Period = Period class Plus a b where type PlusResult a b (+) :: a -> b -> PlusResult a b instance Plus Date Period where type PlusResult Date Period = Date Date + Period = Date instance Plus Period Date where type PlusResult Period Date = Date Period + Date = Date instance Plus Period Period where type PlusResult Period Period = Period Period + Period = Period
But I suppose you've been thinking about Haskell98. That, I'm afraid, doesn't seem possible. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe