[GHC] #12708: RFC: Representation polymorphic Num
GHC
ghc-devs at haskell.org
Fri Oct 14 22:11:30 UTC 2016
#12708: RFC: Representation polymorphic Num
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner:
Type: feature | Status: new
request |
Priority: normal | Milestone:
Component: Core | Version: 8.0.1
Libraries |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I can create a GHC proposal for this but I need a sanity check first
{{{#!hs
import Prelude hiding (Num (..))
import qualified Prelude as P
import GHC.Prim
import GHC.Types
class Num (a :: Type k) where
(+) :: a -> a -> a
(-) :: a -> a -> a
(*) :: a -> a -> a
negate :: a -> a
abs :: a -> a
signum :: a -> a
fromInteger :: Integer -> a
instance Num Int# where
(+) :: Int# -> Int# -> Int#
(+) = (+#)
(-) :: Int# -> Int# -> Int#
(-) = (-#)
(*) :: Int# -> Int# -> Int#
(*) = (*#)
negate :: Int# -> Int#
negate = negateInt#
...
fromInteger :: Integer -> Int#
fromInteger (fromInteger -> I# int) = int
instance Num Double# where
(+) :: Double# -> Double# -> Double#
(+) = (+##)
(-) :: Double# -> Double# -> Double#
(-) = (-##)
(*) :: Double# -> Double# -> Double#
(*) = (*##)
negate :: Double# -> Double#
negate = negateDouble#
...
fromInteger :: Integer -> Double#
fromInteger (fromInteger -> D# dbl) = dbl
}}}
Note how the `fromInteger` views aren't qualified? That's because we can
branch on the kind and all of a sudden, all instances of old `Num` are
instances of our `Num`
{{{#!hs
instance P.Num a => Num (a :: Type) where
(+) = (P.+)
(-) = (P.-)
(*) = (P.*)
negate = P.negate
abs = P.abs
signum = P.signum
fromInteger = P.fromInteger
}}}
----
Same with `Show` etc. etc.
{{{#!hs
class Show (a :: TYPE k) where
show :: (a :: TYPE k) -> String
instance P.Show a => Show (a :: Type) where
show :: (a :: Type) -> String
show = P.show
instance Show Int# where
show :: Int# -> String
show int = show (I# int)
instance Show Double# where
show :: Double# -> String
show dbl = show (D# dbl)
}}}
----
What effects would this have? They are even printed the same by default
{{{#!hs
>>> :kind Prelude.Num
Prelude.Num :: * -> Constraint
>>> :kind Main.Num
Main.Num :: * -> Constraint
>>> :set -fprint-explicit-runtime-reps
>>> :kind Main.Num
Main.Num :: TYPE k -> Constraint
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12708>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list