ghc-internal-9.1001.0: Basic libraries
Copyright(c) The University of Glasgow 1994-2002
Licensesee libraries/base/LICENSE
Maintainerghc-devs@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC Extensions)
Safe HaskellTrustworthy
LanguageHaskell2010

GHC.Internal.Num

Description

The Num class and the Integer type.

Synopsis

Documentation

class Num a where Source #

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 Integral, then fromInteger is a left inverse for 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 Rational do.

Minimal complete definition

(+), (*), abs, signum, fromInteger, (negate | (-))

Methods

(+) :: a -> a -> a infixl 6 Source #

(-) :: a -> a -> a infixl 6 Source #

(*) :: a -> a -> a infixl 7 Source #

negate :: a -> a Source #

Unary negation.

abs :: a -> a Source #

Absolute value.

signum :: a -> a Source #

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).

fromInteger :: Integer -> a Source #

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.

Instances

Instances details
Num CBool Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CClock Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CDouble Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CFloat Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CLLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CPtrdiff Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSigAtomic Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSize Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CTime Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CULLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CULong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CWchar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num IntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Num WordPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Num Int16 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Num Int32 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Num Int64 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Num Int8 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Num CBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CBlkSize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CCc Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CClockId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CDev Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CFsBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CFsFilCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CGid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CIno Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CKey Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CMode Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CNfds Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CNlink Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num COff Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CPid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CRLim Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CSocklen Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CSpeed Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CSsize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CTcflag Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CUid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num Fd Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: Fd -> Fd -> Fd Source #

(-) :: Fd -> Fd -> Fd Source #

(*) :: Fd -> Fd -> Fd Source #

negate :: Fd -> Fd Source #

abs :: Fd -> Fd Source #

signum :: Fd -> Fd Source #

fromInteger :: Integer -> Fd Source #

Num Word16 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Num Word32 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Num Word64 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Num Word8 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Num Integer Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Num

Num Natural Source #

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.0

Instance details

Defined in GHC.Internal.Num

Num Double Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:

>>> (0.1 + 0.1) + 0.4 == 0.1 + (0.1 + 0.4)
False
>>> (0.1 + 0.2) * 0.3 == 0.1 * 0.3 + 0.2 * 0.3
False
>>> (0.1 * 0.1) * 0.3 == 0.1 * (0.1 * 0.3)
False
Instance details

Defined in GHC.Internal.Float

Num Float Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:

>>> (0.1 + 0.1 :: Float) + 0.5 == 0.1 + (0.1 + 0.5)
False
>>> (0.1 + 0.2 :: Float) * 0.9 == 0.1 * 0.9 + 0.2 * 0.9
False
>>> (0.1 * 0.1 :: Float) * 0.9 == 0.1 * (0.1 * 0.9)
False
Instance details

Defined in GHC.Internal.Float

Num Int Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Num

Num Word Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Num

Num a => Num (Identity a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Num a => Num (Down a) Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

(+) :: Down a -> Down a -> Down a Source #

(-) :: Down a -> Down a -> Down a Source #

(*) :: Down a -> Down a -> Down a Source #

negate :: Down a -> Down a Source #

abs :: Down a -> Down a Source #

signum :: Down a -> Down a Source #

fromInteger :: Integer -> Down a Source #

Num a => Num (Product a) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Num a => Num (Sum a) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(+) :: Sum a -> Sum a -> Sum a Source #

(-) :: Sum a -> Sum a -> Sum a Source #

(*) :: Sum a -> Sum a -> Sum a Source #

negate :: Sum a -> Sum a Source #

abs :: Sum a -> Sum a Source #

signum :: Sum a -> Sum a Source #

fromInteger :: Integer -> Sum a Source #

Integral a => Num (Ratio a) Source #

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

(+) :: Ratio a -> Ratio a -> Ratio a Source #

(-) :: Ratio a -> Ratio a -> Ratio a Source #

(*) :: Ratio a -> Ratio a -> Ratio a Source #

negate :: Ratio a -> Ratio a Source #

abs :: Ratio a -> Ratio a Source #

signum :: Ratio a -> Ratio a Source #

fromInteger :: Integer -> Ratio a Source #

Num a => Num (Const a b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

(+) :: Const a b -> Const a b -> Const a b Source #

(-) :: Const a b -> Const a b -> Const a b Source #

(*) :: Const a b -> Const a b -> Const a b Source #

negate :: Const a b -> Const a b Source #

abs :: Const a b -> Const a b Source #

signum :: Const a b -> Const a b Source #

fromInteger :: Integer -> Const a b Source #

(Applicative f, Num a) => Num (Ap f a) Source #

Note that even if the underlying Num and Applicative instances are lawful, for most Applicatives, this instance will not be lawful. If you use this instance with the list Applicative, the following customary laws will not hold:

Commutativity:

>>> Ap [10,20] + Ap [1,2]
Ap {getAp = [11,12,21,22]}
>>> Ap [1,2] + Ap [10,20]
Ap {getAp = [11,21,12,22]}

Additive inverse:

>>> Ap [] + negate (Ap [])
Ap {getAp = []}
>>> fromInteger 0 :: Ap [] Int
Ap {getAp = [0]}

Distributivity:

>>> Ap [1,2] * (3 + 4)
Ap {getAp = [7,14]}
>>> (Ap [1,2] * 3) + (Ap [1,2] * 4)
Ap {getAp = [7,11,10,14]}

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(+) :: Ap f a -> Ap f a -> Ap f a Source #

(-) :: Ap f a -> Ap f a -> Ap f a Source #

(*) :: Ap f a -> Ap f a -> Ap f a Source #

negate :: Ap f a -> Ap f a Source #

abs :: Ap f a -> Ap f a Source #

signum :: Ap f a -> Ap f a Source #

fromInteger :: Integer -> Ap f a Source #

Num (f a) => Num (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(+) :: Alt f a -> Alt f a -> Alt f a Source #

(-) :: Alt f a -> Alt f a -> Alt f a Source #

(*) :: Alt f a -> Alt f a -> Alt f a Source #

negate :: Alt f a -> Alt f a Source #

abs :: Alt f a -> Alt f a Source #

signum :: Alt f a -> Alt f a Source #

fromInteger :: Integer -> Alt f a Source #

subtract :: Num a => a -> a -> a Source #

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.

quotRemInteger :: Integer -> Integer -> (# Integer, Integer #) Source #

Deprecated: Use integerQuotRem# instead

data Natural Source #

Natural number

Invariant: numbers <= 0xffffffffffffffff use the NS constructor

Instances

Instances details
Bits Natural Source #

@since base-4.8.0

Instance details

Defined in GHC.Internal.Bits

Data Natural Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Natural -> c Natural Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Natural Source #

toConstr :: Natural -> Constr Source #

dataTypeOf :: Natural -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Natural) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Natural) Source #

gmapT :: (forall b. Data b => b -> b) -> Natural -> Natural Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Natural -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Natural -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Natural -> m Natural Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural Source #

Enum Natural Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Enum

Ix Natural Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Ix

Num Natural Source #

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.0

Instance details

Defined in GHC.Internal.Num

Read Natural Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Read

Integral Natural Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Real

Real Natural Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Real

Show Natural Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Show

Eq Natural 
Instance details

Defined in GHC.Num.Natural

Ord Natural 
Instance details

Defined in GHC.Num.Natural

TestCoercion SNat Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeNats

Methods

testCoercion :: forall (a :: Nat) (b :: Nat). SNat a -> SNat b -> Maybe (Coercion a b) Source #

TestEquality SNat Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeNats

Methods

testEquality :: forall (a :: Nat) (b :: Nat). SNat a -> SNat b -> Maybe (a :~: b) Source #

type Compare (a :: Natural) (b :: Natural) Source # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

type Compare (a :: Natural) (b :: Natural) = CmpNat a b

data Integer Source #

Arbitrary precision integers. In contrast with fixed-size integral types such as Int, the Integer type represents the entire infinite range of integers.

Integers are stored in a kind of sign-magnitude form, hence do not expect two's complement form when using bit operations.

If the value is small (i.e., fits into an Int), the IS constructor is used. Otherwise IP and IN constructors are used to store a BigNat representing the positive or the negative value magnitude, respectively.

Invariant: IP and IN are used iff the value does not fit in IS.

Instances

Instances details
Bits Integer Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Bits

Data Integer Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Integer -> c Integer Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Integer Source #

toConstr :: Integer -> Constr Source #

dataTypeOf :: Integer -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Integer) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Integer) Source #

gmapT :: (forall b. Data b => b -> b) -> Integer -> Integer Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Integer -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Integer -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

Enum Integer Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Enum

Ix Integer Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Ix

Num Integer Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Num

Read Integer Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Integral Integer Source #

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Real Integer Source #

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Show Integer Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Eq Integer 
Instance details

Defined in GHC.Num.Integer

Ord Integer 
Instance details

Defined in GHC.Num.Integer