{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples #-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.Num (module GHC.Num, module GHC.Integer, module GHC.Natural) where
#include "MachDeps.h"
import GHC.Base
import GHC.Integer
import GHC.Natural
infixl 7  *
infixl 6  +, -
default ()              
                        
class  Num a  where
    {-# MINIMAL (+), (*), abs, signum, fromInteger, (negate | (-)) #-}
    (+), (-), (*)       :: a -> a -> a
    
    negate              :: a -> a
    
    abs                 :: a -> a
    
    
    
    
    
    
    
    signum              :: a -> a
    
    
    
    
    fromInteger         :: Integer -> a
    {-# INLINE (-) #-}
    {-# INLINE negate #-}
    x :: a
x - y :: a
y               = a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a -> a
forall a. Num a => a -> a
negate a
y
    negate x :: a
x            = 0 a -> a -> a
forall a. Num a => a -> a -> a
- a
x
{-# INLINE subtract #-}
subtract :: (Num a) => a -> a -> a
subtract :: a -> a -> a
subtract x :: a
x y :: a
y = a
y a -> a -> a
forall a. Num a => a -> a -> a
- a
x
instance  Num Int  where
    I# x :: Int#
x + :: Int -> Int -> Int
+ I# y :: Int#
y = Int# -> Int
I# (Int#
x Int# -> Int# -> Int#
+# Int#
y)
    I# x :: Int#
x - :: Int -> Int -> Int
- I# y :: Int#
y = Int# -> Int
I# (Int#
x Int# -> Int# -> Int#
-# Int#
y)
    negate :: Int -> Int
negate (I# x :: Int#
x) = Int# -> Int
I# (Int# -> Int#
negateInt# Int#
x)
    I# x :: Int#
x * :: Int -> Int -> Int
* I# y :: Int#
y = Int# -> Int
I# (Int#
x Int# -> Int# -> Int#
*# Int#
y)
    abs :: Int -> Int
abs n :: Int
n  = if Int
n Int -> Int -> Bool
`geInt` 0 then Int
n else Int -> Int
forall a. Num a => a -> a
negate Int
n
    signum :: Int -> Int
signum n :: Int
n | Int
n Int -> Int -> Bool
`ltInt` 0 = Int -> Int
forall a. Num a => a -> a
negate 1
             | Int
n Int -> Int -> Bool
`eqInt` 0 = 0
             | Bool
otherwise   = 1
    {-# INLINE fromInteger #-}   
    fromInteger :: Integer -> Int
fromInteger i :: Integer
i = Int# -> Int
I# (Integer -> Int#
integerToInt Integer
i)
instance Num Word where
    (W# x# :: Word#
x#) + :: Word -> Word -> Word
+ (W# y# :: Word#
y#)      = Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`plusWord#` Word#
y#)
    (W# x# :: Word#
x#) - :: Word -> Word -> Word
- (W# y# :: Word#
y#)      = Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`minusWord#` Word#
y#)
    (W# x# :: Word#
x#) * :: Word -> Word -> Word
* (W# y# :: Word#
y#)      = Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`timesWord#` Word#
y#)
    negate :: Word -> Word
negate (W# x# :: Word#
x#)         = Word# -> Word
W# (Int# -> Word#
int2Word# (Int# -> Int#
negateInt# (Word# -> Int#
word2Int# Word#
x#)))
    abs :: Word -> Word
abs x :: Word
x                  = Word
x
    signum :: Word -> Word
signum 0               = 0
    signum _               = 1
    fromInteger :: Integer -> Word
fromInteger i :: Integer
i          = Word# -> Word
W# (Integer -> Word#
integerToWord Integer
i)
instance  Num Integer  where
    + :: Integer -> Integer -> Integer
(+) = Integer -> Integer -> Integer
plusInteger
    (-) = Integer -> Integer -> Integer
minusInteger
    * :: Integer -> Integer -> Integer
(*) = Integer -> Integer -> Integer
timesInteger
    negate :: Integer -> Integer
negate         = Integer -> Integer
negateInteger
    fromInteger :: Integer -> Integer
fromInteger x :: Integer
x  =  Integer
x
    abs :: Integer -> Integer
abs = Integer -> Integer
absInteger
    signum :: Integer -> Integer
signum = Integer -> Integer
signumInteger
instance  Num Natural  where
    + :: Natural -> Natural -> Natural
(+) = Natural -> Natural -> Natural
plusNatural
    (-) = Natural -> Natural -> Natural
minusNatural
    * :: Natural -> Natural -> Natural
(*) = Natural -> Natural -> Natural
timesNatural
    negate :: Natural -> Natural
negate      = Natural -> Natural
negateNatural
    fromInteger :: Integer -> Natural
fromInteger = Integer -> Natural
naturalFromInteger
    abs :: Natural -> Natural
abs = Natural -> Natural
forall a. a -> a
id
    signum :: Natural -> Natural
signum = Natural -> Natural
signumNatural