base-4.21.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 Source #

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 #

Instance details

Defined in GHC.Internal.Foreign.C.Types

Num Int16 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Num Int32 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Num Int64 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Num Int8 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Instance details

Defined in GHC.Internal.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 GHC.Internal.System.Posix.Types

Instance details

Defined in GHC.Internal.System.Posix.Types

Instance details

Defined in GHC.Internal.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 GHC.Internal.System.Posix.Types

Instance details

Defined in GHC.Internal.System.Posix.Types

Instance details

Defined in GHC.Internal.System.Posix.Types

Instance details

Defined in GHC.Internal.System.Posix.Types

Instance details

Defined in GHC.Internal.System.Posix.Types

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

Num Word32 Source #

Since: base-2.1

Num Word64 Source #

Since: base-2.1

Num Word8 Source #

Since: base-2.1

Num Integer Source #

Since: base-2.1

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

Num Int Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.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 Word Source #

Since: base-2.1

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

Since: base-4.9.0.0

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

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 #

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) 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 Applicative s, 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 #

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.

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

Deprecated: Use integerQuotRem# instead

integerAbs :: Integer -> Integer #

integerAdd :: Integer -> Integer -> Integer #

integerAnd :: Integer -> Integer -> Integer #

integerBit :: Word -> Integer #

integerBit# :: Word# -> Integer #

integerCheck :: Integer -> Bool #

integerCheck# :: Integer -> Bool# #

integerCompare :: Integer -> Integer -> Ordering #

integerComplement :: Integer -> Integer #

integerDecodeDouble# :: Double# -> (# Integer, Int# #) #

integerDiv :: Integer -> Integer -> Integer #

integerDivMod :: Integer -> Integer -> (Integer, Integer) #

integerDivMod# :: Integer -> Integer -> (# Integer, Integer #) #

integerEncodeDouble :: Integer -> Int -> Double #

integerEncodeDouble# :: Integer -> Int# -> Double# #

integerEncodeFloat# :: Integer -> Int# -> Float# #

integerEq :: Integer -> Integer -> Bool #

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

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

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

integerFromBigNat# :: BigNat# -> Integer #

integerFromBigNatNeg# :: BigNat# -> Integer #

integerFromBigNatSign# :: Int# -> BigNat# -> Integer #

integerFromByteArray :: Word# -> ByteArray# -> Word# -> Bool# -> Integer #

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

integerFromInt :: Int -> Integer #

integerFromInt# :: Int# -> Integer #

integerFromInt64# :: Int64# -> Integer #

integerFromNatural :: Natural -> Integer #

integerFromWord :: Word -> Integer #

integerFromWord# :: Word# -> Integer #

integerFromWord64# :: Word64# -> Integer #

integerFromWordList :: Bool -> [Word] -> Integer #

integerFromWordNeg# :: Word# -> Integer #

integerFromWordSign# :: Int# -> Word# -> Integer #

integerGcd :: Integer -> Integer -> Integer #

integerGcde :: Integer -> Integer -> (Integer, Integer, Integer) #

integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #) #

integerGe :: Integer -> Integer -> Bool #

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

integerGt :: Integer -> Integer -> Bool #

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

integerIsNegative :: Integer -> Bool #

integerIsNegative# :: Integer -> Bool# #

integerIsOne :: Integer -> Bool #

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

integerIsZero :: Integer -> Bool #

integerLcm :: Integer -> Integer -> Integer #

integerLe :: Integer -> Integer -> Bool #

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

integerLog2 :: Integer -> Word #

integerLog2# :: Integer -> Word# #

integerLogBase :: Integer -> Integer -> Word #

integerLogBase# :: Integer -> Integer -> Word# #

integerLogBaseWord :: Word -> Integer -> Word #

integerLogBaseWord# :: Word# -> Integer -> Word# #

integerLt :: Integer -> Integer -> Bool #

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

integerMod :: Integer -> Integer -> Integer #

integerMul :: Integer -> Integer -> Integer #

integerNe :: Integer -> Integer -> Bool #

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

integerNegate :: Integer -> Integer #

integerOne :: Integer #

integerOr :: Integer -> Integer -> Integer #

integerPopCount# :: Integer -> Int# #

integerPowMod# :: Integer -> Integer -> Natural -> (# Natural | () #) #

integerQuot :: Integer -> Integer -> Integer #

integerQuotRem :: Integer -> Integer -> (Integer, Integer) #

integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #) #

integerRecipMod# :: Integer -> Natural -> (# Natural | () #) #

integerRem :: Integer -> Integer -> Integer #

integerShiftL :: Integer -> Word -> Integer #

integerShiftL# :: Integer -> Word# -> Integer #

integerShiftR :: Integer -> Word -> Integer #

integerShiftR# :: Integer -> Word# -> Integer #

integerSignum :: Integer -> Integer #

integerSignum# :: Integer -> Int# #

integerSizeInBase# :: Word# -> Integer -> Word# #

integerSqr :: Integer -> Integer #

integerSub :: Integer -> Integer -> Integer #

integerTestBit :: Integer -> Word -> Bool #

integerTestBit# :: Integer -> Word# -> Bool# #

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

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

integerToBigNatClamp# :: Integer -> BigNat# #

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

integerToInt :: Integer -> Int #

integerToInt# :: Integer -> Int# #

integerToInt64# :: Integer -> Int64# #

integerToMutableByteArray :: Integer -> MutableByteArray# RealWorld -> Word# -> Bool# -> IO Word #

integerToMutableByteArray# :: Integer -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #) #

integerToNatural :: Integer -> Natural #

integerToNaturalClamp :: Integer -> Natural #

integerToNaturalThrow :: Integer -> Natural #

integerToWord :: Integer -> Word #

integerToWord# :: Integer -> Word# #

integerToWord64# :: Integer -> Word64# #

integerXor :: Integer -> Integer -> Integer #

integerZero :: Integer #

data Integer #

Constructors

Instances

Instances details
PrintfArg Integer Source #

Since: base-2.1

Instance details

Defined in Text.Printf

Bits Integer Source #

Since: base-2.1

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

Ix Integer Source #

Since: base-2.1

Num Integer Source #

Since: base-2.1

Read Integer Source #

Since: base-2.1

Integral Integer Source #

Since: base-2.0.1

Real Integer Source #

Since: base-2.0.1

Instance details

Defined in GHC.Internal.Real

Show Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Instance details

Defined in GHC.Num.Integer

Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Integer -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Integer -> Code m Integer Source #

naturalAdd :: Natural -> Natural -> Natural #

naturalAnd :: Natural -> Natural -> Natural #

naturalAndNot :: Natural -> Natural -> Natural #

naturalBit :: Word -> Natural #

naturalBit# :: Word# -> Natural #

naturalCheck :: Natural -> Bool #

naturalCheck# :: Natural -> Bool# #

naturalClearBit :: Natural -> Word -> Natural #

naturalClearBit# :: Natural -> Word# -> Natural #

naturalCompare :: Natural -> Natural -> Ordering #

naturalComplementBit :: Natural -> Word -> Natural #

naturalComplementBit# :: Natural -> Word# -> Natural #

naturalEncodeDouble# :: Natural -> Int# -> Double# #

naturalEncodeFloat# :: Natural -> Int# -> Float# #

naturalEq :: Natural -> Natural -> Bool #

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

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

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

naturalFromBigNat# :: BigNat# -> Natural #

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

naturalFromWord :: Word -> Natural #

naturalFromWord# :: Word# -> Natural #

naturalFromWord2# :: Word# -> Word# -> Natural #

naturalFromWordList :: [Word] -> Natural #

naturalGcd :: Natural -> Natural -> Natural #

naturalGe :: Natural -> Natural -> Bool #

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

naturalGt :: Natural -> Natural -> Bool #

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

naturalIsOne :: Natural -> Bool #

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

naturalIsZero :: Natural -> Bool #

naturalLcm :: Natural -> Natural -> Natural #

naturalLe :: Natural -> Natural -> Bool #

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

naturalLog2 :: Natural -> Word #

naturalLog2# :: Natural -> Word# #

naturalLogBase :: Natural -> Natural -> Word #

naturalLogBase# :: Natural -> Natural -> Word# #

naturalLogBaseWord :: Word -> Natural -> Word #

naturalLogBaseWord# :: Word# -> Natural -> Word# #

naturalLt :: Natural -> Natural -> Bool #

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

naturalMul :: Natural -> Natural -> Natural #

naturalNe :: Natural -> Natural -> Bool #

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

naturalNegate :: Natural -> Natural #

naturalOne :: Natural #

naturalOr :: Natural -> Natural -> Natural #

naturalPopCount :: Natural -> Word #

naturalPopCount# :: Natural -> Word# #

naturalPowMod :: Natural -> Natural -> Natural -> Natural #

naturalQuot :: Natural -> Natural -> Natural #

naturalQuotRem :: Natural -> Natural -> (Natural, Natural) #

naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #) #

naturalRem :: Natural -> Natural -> Natural #

naturalSetBit :: Natural -> Word -> Natural #

naturalSetBit# :: Natural -> Word# -> Natural #

naturalShiftL :: Natural -> Word -> Natural #

naturalShiftL# :: Natural -> Word# -> Natural #

naturalShiftR :: Natural -> Word -> Natural #

naturalShiftR# :: Natural -> Word# -> Natural #

naturalSignum :: Natural -> Natural #

naturalSizeInBase# :: Word# -> Natural -> Word# #

naturalSqr :: Natural -> Natural #

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

naturalSubThrow :: Natural -> Natural -> Natural #

naturalSubUnsafe :: Natural -> Natural -> Natural #

naturalTestBit :: Natural -> Word -> Bool #

naturalTestBit# :: Natural -> Word# -> Bool# #

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

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

naturalToBigNat# :: Natural -> BigNat# #

naturalToMutableByteArray# :: Natural -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #) #

naturalToWord :: Natural -> Word #

naturalToWord# :: Natural -> Word# #

naturalToWordClamp :: Natural -> Word #

naturalToWordClamp# :: Natural -> Word# #

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

naturalXor :: Natural -> Natural -> Natural #

naturalZero :: Natural #

data Natural #

Constructors

Instances

Instances details
PrintfArg Natural Source #

Since: base-4.8.0.0

Instance details

Defined in Text.Printf

Bits Natural Source #

Since: base-4.8.0

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

Ix Natural Source #

Since: base-4.8.0.0

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

Read Natural Source #

Since: base-4.8.0.0

Integral Natural Source #

Since: base-4.8.0.0

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

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

Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Natural -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Natural -> Code m Natural 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

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