base-4.14.2.0: Basic libraries
Copyright(c) The University of Glasgow 1994-2002
Licensesee libraries/base/LICENSE
Maintainercvs-ghc@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC Extensions)
Safe HaskellTrustworthy
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)

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

Note that due to the presence of NaN, not all elements of Double have an additive inverse.

>>> 0/0 + (negate 0/0 :: Double)
NaN

Also note that due to the presence of -0, Double 's Num instance doesn't have an additive identity

>>> 0 + (-0 :: Double)
0.0

Since: base-2.1

Num Float #

Note that due to the presence of NaN, not all elements of Float have an additive inverse.

>>> 0/0 + (negate 0/0 :: Float)
NaN

Also note that due to the presence of -0, Float 's Num instance doesn't have an additive identity

>>> 0 + (-0 :: Float)
0.0

Since: base-2.1

Instance details

Defined in GHC.Float

Num Int #

Since: base-2.1

Instance details

Defined in GHC.Num

Methods

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

(-) :: Int -> Int -> Int Source #

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

negate :: Int -> Int Source #

abs :: Int -> Int Source #

signum :: Int -> Int Source #

fromInteger :: Integer -> Int Source #

Num Int8 #

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int16 #

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int32 #

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int64 #

Since: base-2.1

Instance details

Defined in GHC.Int

Num Integer #

Since: base-2.1

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

Num Word #

Since: base-2.1

Instance details

Defined in GHC.Num

Num Word8 #

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word16 #

Since: base-2.1

Num Word32 #

Since: base-2.1

Num Word64 #

Since: base-2.1

Instance details

Defined in Foreign.C.Types

Instance details

Defined in Foreign.C.Types

Instance details

Defined in Foreign.C.Types

Instance details

Defined in Foreign.C.Types

Instance details

Defined in Foreign.C.Types

Instance details

Defined in Foreign.C.Types

Instance details

Defined in Foreign.C.Types

Num Fd #
Instance details

Defined in 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 #

Instance details

Defined in System.Posix.Types

Instance details

Defined in System.Posix.Types

Methods

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

(-) :: CId -> CId -> CId Source #

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

negate :: CId -> CId Source #

abs :: CId -> CId Source #

signum :: CId -> CId Source #

fromInteger :: Integer -> CId Source #

Instance details

Defined in System.Posix.Types

Methods

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

(-) :: CCc -> CCc -> CCc Source #

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

negate :: CCc -> CCc Source #

abs :: CCc -> CCc Source #

signum :: CCc -> CCc Source #

fromInteger :: Integer -> CCc Source #

Instance details

Defined in System.Posix.Types

Instance details

Defined in System.Posix.Types

Instance details

Defined in System.Posix.Types

Instance details

Defined in System.Posix.Types

Instance details

Defined in System.Posix.Types

Instance details

Defined in System.Posix.Types

Integral a => Num (Ratio a) #

Since: base-2.0.1

Instance details

Defined in GHC.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 (Down a) #

Since: base-4.11.0.0

Instance details

Defined in 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 Data.Semigroup.Internal

Num a => Num (Sum a) #

Since: base-4.7.0.0

Instance details

Defined in 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 #

Num a => Num (Identity a) #

Since: base-4.9.0.0

Num a => Num (Max a) #

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

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 #

RealFloat a => Num (Complex a) #

Since: base-2.1

Instance details

Defined in Data.Complex

Num a => Num (Op a b) #
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 #

HasResolution a => Num (Fixed a) #

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 (f a) => Num (Alt f a) #

Since: base-4.8.0.0

Instance details

Defined in 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 #

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

Since: base-4.12.0.0

Instance details

Defined in 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 a => Num (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in 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 #

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.

module GHC.Integer

module GHC.Natural

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