{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples #-}{-# OPTIONS_HADDOCK not-home #-}------------------------------------------------------------------------------- |-- Module : GHC.Internal.Num-- Copyright : (c) The University of Glasgow 1994-2002-- License : see libraries/base/LICENSE---- Maintainer : ghc-devs@haskell.org-- Stability : internal-- Portability : non-portable (GHC Extensions)---- The 'Num' class and the 'Integer' type.-------------------------------------------------------------------------------moduleGHC.Internal.Num (Num (..),subtract ,quotRemInteger ,moduleGHC.Num.Integer ,moduleGHC.Num.Natural -- reexported for backward compatibility,moduleGHC.Internal.Natural ,moduleGHC.Internal.Integer )where
#include "MachDeps.h"
importqualifiedGHC.Internal.Natural importqualifiedGHC.Internal.Integer importGHC.Internal.Base importGHC.Num.Integer importGHC.Num.Natural infixl7* infixl6+ ,- default()-- Double isn't available yet,-- and we shouldn't be using defaults anyway-- | Basic numeric class.---- The Haskell Report defines no laws for 'Num'. However, @('+')@ and @('*')@ are-- customarily expected to define a ring and have the following properties:---- [__Associativity of @('+')@__]: @(x + y) + z@ = @x + (y + z)@-- [__Commutativity of @('+')@__]: @x + y@ = @y + x@-- [__@'fromInteger' 0@ is the additive identity__]: @x + fromInteger 0@ = @x@-- [__'negate' gives the additive inverse__]: @x + negate x@ = @fromInteger 0@-- [__Associativity of @('*')@__]: @(x * y) * z@ = @x * (y * z)@-- [__@'fromInteger' 1@ is the multiplicative identity__]:-- @x * fromInteger 1@ = @x@ and @fromInteger 1 * x@ = @x@-- [__Distributivity of @('*')@ with respect to @('+')@__]:-- @a * (b + c)@ = @(a * b) + (a * c)@ and @(b + c) * a@ = @(b * a) + (c * a)@-- [__Coherence with 'toInteger'__]: if the type also implements 'GHC.Real.Integral', then-- 'fromInteger' is a left inverse for 'GHC.Internal.Real.toInteger', i.e. @fromInteger (toInteger i) == i@---- Note that it /isn't/ customarily expected that a type instance of both 'Num'-- and 'Ord' implement an ordered ring. Indeed, in @base@ only 'Integer' and-- 'Data.Ratio.Rational' do.classNum a where{-# MINIMAL(+),(*),abs ,signum ,fromInteger ,(negate |(-))#-}(+) ,(-),(*) ::a ->a ->a -- | Unary negation.negate ::a ->a -- | Absolute value.abs ::a ->a -- | Sign of a number.-- The functions 'abs' and 'signum' should satisfy the law:---- > abs x * signum x == x---- For real numbers, the 'signum' is either @-1@ (negative), @0@ (zero)-- or @1@ (positive).signum ::a ->a -- | Conversion from an 'Integer'.-- An integer literal represents the application of the function-- 'fromInteger' to the appropriate value of type 'Integer',-- so such literals have type @('Num' a) => a@.fromInteger ::Integer ->a {-# INLINE(-)#-}{-# INLINEnegate #-}a
x - 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 a
x =a
0a -> a -> a
forall a. Num a => a -> a -> a
- a
x -- | the same as @'flip' ('-')@.---- Because @-@ is treated specially in the Haskell grammar,-- @(-@ /e/@)@ is not a section, but an application of prefix negation.-- However, @('subtract'@ /exp/@)@ is equivalent to the disallowed section.{-# INLINEsubtract #-}subtract ::(Num a )=>a ->a ->a subtract :: forall a. Num a => a -> a -> a
subtract a
x a
y =a
y a -> a -> a
forall a. Num a => a -> a -> a
- a
x -- | @since base-2.01instanceNum Int whereI# Int#
x + :: Int -> Int -> Int
+ I# Int#
y =Int# -> Int
I# (Int#
x Int# -> Int# -> Int#
+# Int#
y )I# Int#
x - :: Int -> Int -> Int
- I# Int#
y =Int# -> Int
I# (Int#
x Int# -> Int# -> Int#
-# Int#
y )negate :: Int -> Int
negate (I# Int#
x )=Int# -> Int
I# (Int# -> Int#
negateInt# Int#
x )I# Int#
x * :: Int -> Int -> Int
* I# Int#
y =Int# -> Int
I# (Int#
x Int# -> Int# -> Int#
*# Int#
y )abs :: Int -> Int
abs Int
n =ifInt
n Int -> Int -> Bool
`geInt` Int
0thenInt
n elseInt -> Int
forall a. Num a => a -> a
negate Int
n signum :: Int -> Int
signum Int
n |Int
n Int -> Int -> Bool
`ltInt` Int
0=Int -> Int
forall a. Num a => a -> a
negate Int
1|Int
n Int -> Int -> Bool
`eqInt` Int
0=Int
0|Bool
otherwise =Int
1fromInteger :: Integer -> Int
fromInteger Integer
i =Int# -> Int
I# (Integer -> Int#
integerToInt# Integer
i )-- | @since base-2.01instanceNum Word where(W# Word#
x# )+ :: Word -> Word -> Word
+ (W# Word#
y# )=Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`plusWord#` Word#
y# )(W# Word#
x# )- :: Word -> Word -> Word
- (W# Word#
y# )=Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`minusWord#` Word#
y# )(W# Word#
x# )* :: Word -> Word -> Word
* (W# Word#
y# )=Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`timesWord#` Word#
y# )negate :: Word -> Word
negate (W# Word#
x# )=Word# -> Word
W# (Int# -> Word#
int2Word# (Int# -> Int#
negateInt# (Word# -> Int#
word2Int# Word#
x# )))abs :: Word -> Word
abs Word
x =Word
x signum :: Word -> Word
signum Word
0=Word
0signum Word
_=Word
1fromInteger :: Integer -> Word
fromInteger Integer
i =Word# -> Word
W# (Integer -> Word#
integerToWord# Integer
i )-- | @since base-2.01instanceNum Integer where+ :: Integer -> Integer -> Integer
(+) =Integer -> Integer -> Integer
integerAdd (-)=Integer -> Integer -> Integer
integerSub * :: Integer -> Integer -> Integer
(*) =Integer -> Integer -> Integer
integerMul negate :: Integer -> Integer
negate =Integer -> Integer
integerNegate fromInteger :: Integer -> Integer
fromInteger Integer
i =Integer
i abs :: Integer -> Integer
abs =Integer -> Integer
integerAbs signum :: Integer -> Integer
signum =Integer -> Integer
integerSignum -- | Note that `Natural`'s 'Num' instance isn't a ring: no element but 0 has an-- additive inverse. It is a semiring though.---- @since base-4.8.0.0instanceNum Natural where+ :: Natural -> Natural -> Natural
(+) =Natural -> Natural -> Natural
naturalAdd (-)=Natural -> Natural -> Natural
naturalSubThrow * :: Natural -> Natural -> Natural
(*) =Natural -> Natural -> Natural
naturalMul negate :: Natural -> Natural
negate =Natural -> Natural
naturalNegate fromInteger :: Integer -> Natural
fromInteger Integer
i =Integer -> Natural
integerToNaturalThrow Integer
i abs :: Natural -> Natural
abs =Natural -> Natural
forall a. a -> a
id signum :: Natural -> Natural
signum =Natural -> Natural
naturalSignum {-# DEPRECATEDquotRemInteger"Use integerQuotRem# instead"#-}quotRemInteger ::Integer ->Integer ->(#Integer ,Integer #)quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
quotRemInteger =Integer -> Integer -> (# Integer, Integer #)
integerQuotRem# 

AltStyle によって変換されたページ (->オリジナル) /