\begin{code}
module GHC.Num (module GHC.Num, module GHC.Integer) where
import GHC.Base
import GHC.Integer
infixl 7  *
infixl 6  +, 
default ()              
                        
\end{code}
%*********************************************************
%*                                                      *
\subsection{Standard numeric class}
%*                                                      *
%*********************************************************
\begin{code}
class  Num a  where
    (+), (), (*)       :: a -> a -> a
    
    negate              :: a -> a
    
    abs                 :: a -> a
    
    
    
    
    
    
    
    signum              :: a -> a
    
    
    
    
    fromInteger         :: Integer -> a
    
    
    x  y               = x + negate y
    negate x            = 0  x
subtract :: (Num a) => a -> a -> a
subtract x y = y  x
\end{code}
%*********************************************************
%*                                                      *
\subsection{Instances for @Int@}
%*                                                      *
%*********************************************************
\begin{code}
instance  Num Int  where
    I# x + I# y = I# (x +# y)
    I# x  I# y = I# (x -# y)
    negate (I# x) = I# (negateInt# x)
    I# x * I# y = I# (x *# y)
    abs n  = if n `geInt` 0 then n else negate n
    signum n | n `ltInt` 0 = negate 1
             | n `eqInt` 0 = 0
             | otherwise   = 1
    	 
    fromInteger i = I# (integerToInt i)
\end{code}
%*********************************************************
%*                                                      *
\subsection{Instances for @Word@}
%*                                                      *
%*********************************************************
\begin{code}
instance Num Word where
    (W# x#) + (W# y#)      = W# (x# `plusWord#` y#)
    (W# x#)  (W# y#)      = W# (x# `minusWord#` y#)
    (W# x#) * (W# y#)      = W# (x# `timesWord#` y#)
    negate (W# x#)         = W# (int2Word# (negateInt# (word2Int# x#)))
    abs x                  = x
    signum 0               = 0
    signum _               = 1
    fromInteger i          = W# (integerToWord i)
\end{code}
%*********************************************************
%*                                                      *
\subsection{The @Integer@ instances for @Num@}
%*                                                      *
%*********************************************************
\begin{code}
instance  Num Integer  where
    (+) = plusInteger
    () = minusInteger
    (*) = timesInteger
    negate         = negateInteger
    fromInteger x  =  x
    abs = absInteger
    signum = signumInteger
\end{code}