base-4.20.0.0: Core data structures and operations
Copyright(c) The University of Glasgow 1994-2002
Licensesee libraries/base/LICENSE
Maintainerghc-devs@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC Extensions)
Safe HaskellNone
LanguageHaskell2010

GHC.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 Unique

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Unique

Methods

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

(-) :: Unique -> Unique -> Unique Source #

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

negate :: Unique -> Unique Source #

abs :: Unique -> Unique Source #

signum :: Unique -> Unique Source #

fromInteger :: Integer -> Unique Source #

Num CBool 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CClock 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CDouble 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CFloat 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CInt 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CIntMax 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CIntPtr 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CLLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CPtrdiff 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSUSeconds 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CShort 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSigAtomic 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSize 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CTime 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUInt 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUIntMax 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUIntPtr 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CULLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CULong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUSeconds 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUShort 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CWchar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Num WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Num Int16

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Num Int32

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Num Int64

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Num Int8

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Num CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CNlink 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num Fd 
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

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Num Word32

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Num Word64

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Num Word8

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Num Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Num

Num Natural

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 Int

@since base-2.01

Instance details

Defined in GHC.Internal.Num

Num Word

@since base-2.01

Instance details

Defined in GHC.Internal.Num

RealFloat a => Num (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Num a => Num (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

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

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

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

negate :: Max a -> Max a Source #

abs :: Max a -> Max a Source #

signum :: Max a -> Max a Source #

fromInteger :: Integer -> Max a Source #

Num a => Num (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

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

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

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

negate :: Min a -> Min a Source #

abs :: Min a -> Min a Source #

signum :: Min a -> Min a Source #

fromInteger :: Integer -> Min a Source #

Num a => Num (Identity a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Num a => Num (Down a)

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

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Num a => Num (Sum a)

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

@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 #

HasResolution a => Num (Fixed a) Source #

Multiplication is not associative or distributive:

>>> (0.2 * 0.6 :: Deci) * 0.9 == 0.2 * (0.6 * 0.9)
False
>>> (0.1 + 0.1 :: Deci) * 0.5 == 0.1 * 0.5 + 0.1 * 0.5
False

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

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

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

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

negate :: Fixed a -> Fixed a Source #

abs :: Fixed a -> Fixed a Source #

signum :: Fixed a -> Fixed a Source #

fromInteger :: Integer -> Fixed a Source #

Num a => Num (Op a b) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

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

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

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

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

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

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

fromInteger :: Integer -> Op a b Source #

Num a => Num (Const a b)

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

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)

@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 #

Num (f (g a)) => Num (Compose f g a) Source #

Since: base-4.19.0.0

Instance details

Defined in Data.Functor.Compose

Methods

(+) :: Compose f g a -> Compose f g a -> Compose f g a Source #

(-) :: Compose f g a -> Compose f g a -> Compose f g a Source #

(*) :: Compose f g a -> Compose f g a -> Compose f g a Source #

negate :: Compose f g a -> Compose f g a Source #

abs :: Compose f g a -> Compose f g a Source #

signum :: Compose f g a -> Compose f g a Source #

fromInteger :: Integer -> Compose f g 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.

data Integer #

Constructors

IS Int# 
IP ByteArray# 
IN ByteArray# 

Instances

Instances details
PrintfArg Integer Source #

Since: base-2.1

Instance details

Defined in Text.Printf

Bits Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Bits

Data Integer

@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

@since base-2.01

Instance details

Defined in GHC.Internal.Enum

Ix Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Ix

Num Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Num

Read Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Integral Integer

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Real Integer

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Show Integer

@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

integerCheck# :: Integer -> Bool# #

integerEq# :: Integer -> Integer -> Bool# #

integerFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Integer #) #

integerFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> State# s -> (# State# s, Integer #) #

integerGe# :: Integer -> Integer -> Bool# #

integerGt# :: Integer -> Integer -> Bool# #

integerIsPowerOf2# :: Integer -> (# (# #) | Word# #) #

integerLe# :: Integer -> Integer -> Bool# #

integerLt# :: Integer -> Integer -> Bool# #

integerNe# :: Integer -> Integer -> Bool# #

integerToAddr :: Integer -> Addr# -> Bool# -> IO Word #

integerToAddr# :: Integer -> Addr# -> Bool# -> State# s -> (# State# s, Word# #) #

integerToBigNatSign# :: Integer -> (# Int#, BigNat# #) #

data Natural #

Constructors

NS Word# 
NB ByteArray# 

Instances

Instances details
PrintfArg Natural Source #

Since: base-4.8.0.0

Instance details

Defined in Text.Printf

Bits Natural

@since base-4.8.0

Instance details

Defined in GHC.Internal.Bits

Data Natural

@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

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Enum

Ix Natural

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Ix

Num Natural

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

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Read

Integral Natural

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Real

Real Natural

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Real

Show Natural

@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

KnownNat n => HasResolution (n :: Nat) Source #

For example, Fixed 1000 will give you a Fixed with a resolution of 1000.

Instance details

Defined in Data.Fixed

Methods

resolution :: p n -> Integer Source #

TestCoercion SNat

@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

@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) 
Instance details

Defined in GHC.Internal.Data.Type.Ord

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

naturalCheck# :: Natural -> Bool# #

naturalEq# :: Natural -> Natural -> Bool# #

naturalFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Natural #) #

naturalFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> State# s -> (# State# s, Natural #) #

naturalGe# :: Natural -> Natural -> Bool# #

naturalGt# :: Natural -> Natural -> Bool# #

naturalIsPowerOf2# :: Natural -> (# (# #) | Word# #) #

naturalLe# :: Natural -> Natural -> Bool# #

naturalLt# :: Natural -> Natural -> Bool# #

naturalNe# :: Natural -> Natural -> Bool# #

naturalSub :: Natural -> Natural -> (# (# #) | Natural #) #

naturalToAddr :: Natural -> Addr# -> Bool# -> IO Word #

naturalToAddr# :: Natural -> Addr# -> Bool# -> State# s -> (# State# s, Word# #) #

naturalToBigNat# :: Natural -> BigNat# #

naturalToWordMaybe# :: Natural -> (# (# #) | Word# #) #