Copyright | (c) The University of Glasgow 1994-2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | cvs-ghc@haskell.org |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
GHC.Num
Synopsis
- class Num a where
- subtract :: Num a => a -> a -> a
- module GHC.Integer
- module GHC.Natural
Documentation
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
is the additive identityfromInteger
0x + fromInteger 0
=x
negate
gives the additive inversex + negate x
=fromInteger 0
- Associativity of
(
*
) (x * y) * z
=x * (y * z)
is the multiplicative identityfromInteger
1x * fromInteger 1
=x
andfromInteger 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.
Methods
(+) :: a -> a -> a infixl 6 Source #
(-) :: a -> a -> a infixl 6 Source #
(*) :: a -> a -> a infixl 7 Source #
Unary negation.
Absolute value.
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
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
Instance details
Defined in GHC.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
Instance details
Defined in GHC.Int
Instance details
Defined in GHC.Int
Instance details
Defined in GHC.Int
Instance details
Defined in GHC.Num
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.Num
Instance details
Defined in GHC.Word
Instance details
Defined in GHC.Word
Instance details
Defined in GHC.Word
Instance details
Defined in GHC.Word
Instance details
Defined in Foreign.Ptr
Instance details
Defined in Foreign.Ptr
Instance details
Defined in Foreign.C.Types
Methods
(+) :: CUIntMax -> CUIntMax -> CUIntMax Source #
(-) :: CUIntMax -> CUIntMax -> CUIntMax Source #
(*) :: CUIntMax -> CUIntMax -> CUIntMax Source #
negate :: CUIntMax -> CUIntMax Source #
abs :: CUIntMax -> CUIntMax Source #
signum :: CUIntMax -> CUIntMax Source #
fromInteger :: Integer -> CUIntMax Source #
Instance details
Defined in Foreign.C.Types
Instance details
Defined in Foreign.C.Types
Methods
(+) :: CUIntPtr -> CUIntPtr -> CUIntPtr Source #
(-) :: CUIntPtr -> CUIntPtr -> CUIntPtr Source #
(*) :: CUIntPtr -> CUIntPtr -> CUIntPtr Source #
negate :: CUIntPtr -> CUIntPtr Source #
abs :: CUIntPtr -> CUIntPtr Source #
signum :: CUIntPtr -> CUIntPtr Source #
fromInteger :: Integer -> CUIntPtr Source #
Instance details
Defined in Foreign.C.Types
Instance details
Defined in Foreign.C.Types
Methods
(+) :: CSUSeconds -> CSUSeconds -> CSUSeconds Source #
(-) :: CSUSeconds -> CSUSeconds -> CSUSeconds Source #
(*) :: CSUSeconds -> CSUSeconds -> CSUSeconds Source #
negate :: CSUSeconds -> CSUSeconds Source #
abs :: CSUSeconds -> CSUSeconds Source #
signum :: CSUSeconds -> CSUSeconds Source #
fromInteger :: Integer -> CSUSeconds Source #
Instance details
Defined in Foreign.C.Types
Methods
(+) :: CUSeconds -> CUSeconds -> CUSeconds Source #
(-) :: CUSeconds -> CUSeconds -> CUSeconds Source #
(*) :: CUSeconds -> CUSeconds -> CUSeconds Source #
negate :: CUSeconds -> CUSeconds Source #
abs :: CUSeconds -> CUSeconds Source #
signum :: CUSeconds -> CUSeconds Source #
fromInteger :: Integer -> CUSeconds Source #
Instance details
Defined in Foreign.C.Types
Instance details
Defined in Foreign.C.Types
Instance details
Defined in Foreign.C.Types
Methods
(+) :: CSigAtomic -> CSigAtomic -> CSigAtomic Source #
(-) :: CSigAtomic -> CSigAtomic -> CSigAtomic Source #
(*) :: CSigAtomic -> CSigAtomic -> CSigAtomic Source #
negate :: CSigAtomic -> CSigAtomic Source #
abs :: CSigAtomic -> CSigAtomic Source #
signum :: CSigAtomic -> CSigAtomic Source #
fromInteger :: Integer -> CSigAtomic Source #
Instance details
Defined in Foreign.C.Types
Instance details
Defined in Foreign.C.Types
Instance details
Defined in Foreign.C.Types
Methods
(+) :: CPtrdiff -> CPtrdiff -> CPtrdiff Source #
(-) :: CPtrdiff -> CPtrdiff -> CPtrdiff Source #
(*) :: CPtrdiff -> CPtrdiff -> CPtrdiff Source #
negate :: CPtrdiff -> CPtrdiff Source #
abs :: CPtrdiff -> CPtrdiff Source #
signum :: CPtrdiff -> CPtrdiff Source #
fromInteger :: Integer -> CPtrdiff Source #
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
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 System.Posix.Types
Instance details
Defined in System.Posix.Types
Methods
(+) :: CSocklen -> CSocklen -> CSocklen Source #
(-) :: CSocklen -> CSocklen -> CSocklen Source #
(*) :: CSocklen -> CSocklen -> CSocklen Source #
negate :: CSocklen -> CSocklen Source #
abs :: CSocklen -> CSocklen Source #
signum :: CSocklen -> CSocklen Source #
fromInteger :: Integer -> CSocklen Source #
Instance details
Defined in System.Posix.Types
Methods
(+) :: CFsFilCnt -> CFsFilCnt -> CFsFilCnt Source #
(-) :: CFsFilCnt -> CFsFilCnt -> CFsFilCnt Source #
(*) :: CFsFilCnt -> CFsFilCnt -> CFsFilCnt Source #
negate :: CFsFilCnt -> CFsFilCnt Source #
abs :: CFsFilCnt -> CFsFilCnt Source #
signum :: CFsFilCnt -> CFsFilCnt Source #
fromInteger :: Integer -> CFsFilCnt Source #
Instance details
Defined in System.Posix.Types
Methods
(+) :: CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt Source #
(-) :: CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt Source #
(*) :: CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt Source #
negate :: CFsBlkCnt -> CFsBlkCnt Source #
abs :: CFsBlkCnt -> CFsBlkCnt Source #
signum :: CFsBlkCnt -> CFsBlkCnt Source #
fromInteger :: Integer -> CFsBlkCnt Source #
Instance details
Defined in System.Posix.Types
Methods
(+) :: CClockId -> CClockId -> CClockId Source #
(-) :: CClockId -> CClockId -> CClockId Source #
(*) :: CClockId -> CClockId -> CClockId Source #
negate :: CClockId -> CClockId Source #
abs :: CClockId -> CClockId Source #
signum :: CClockId -> CClockId Source #
fromInteger :: Integer -> CClockId Source #
Instance details
Defined in System.Posix.Types
Instance details
Defined in System.Posix.Types
Methods
(+) :: CBlkSize -> CBlkSize -> CBlkSize Source #
(-) :: CBlkSize -> CBlkSize -> CBlkSize Source #
(*) :: CBlkSize -> CBlkSize -> CBlkSize Source #
negate :: CBlkSize -> CBlkSize Source #
abs :: CBlkSize -> CBlkSize Source #
signum :: CBlkSize -> CBlkSize Source #
fromInteger :: Integer -> CBlkSize 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
Instance details
Defined in GHC.Real
Instance details
Defined in Data.Ord
Instance details
Defined in Data.Semigroup.Internal
Methods
(+) :: Product a -> Product a -> Product a Source #
(-) :: Product a -> Product a -> Product a Source #
(*) :: Product a -> Product a -> Product a Source #
negate :: Product a -> Product a Source #
abs :: Product a -> Product a Source #
signum :: Product a -> Product a Source #
fromInteger :: Integer -> Product a Source #
Instance details
Defined in Data.Semigroup.Internal
Instance details
Defined in Data.Functor.Identity
Methods
(+) :: Identity a -> Identity a -> Identity a Source #
(-) :: Identity a -> Identity a -> Identity a Source #
(*) :: Identity a -> Identity a -> Identity a Source #
negate :: Identity a -> Identity a Source #
abs :: Identity a -> Identity a Source #
signum :: Identity a -> Identity a Source #
fromInteger :: Integer -> Identity a Source #
Instance details
Defined in Data.Semigroup
Instance details
Defined in Data.Semigroup
Instance details
Defined in Data.Complex
Methods
(+) :: Complex a -> Complex a -> Complex a Source #
(-) :: Complex a -> Complex a -> Complex a Source #
(*) :: Complex a -> Complex a -> Complex a Source #
negate :: Complex a -> Complex a Source #
abs :: Complex a -> Complex a Source #
signum :: Complex a -> Complex a Source #
fromInteger :: Integer -> Complex a Source #
Instance details
Defined in Data.Functor.Contravariant
Instance details
Defined in Data.Fixed
Instance details
Defined in Data.Semigroup.Internal
Instance details
Defined in Data.Monoid
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 #
module GHC.Integer
module GHC.Natural