foundation-0.0.19: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation.Numerical

Description

Compared to the Haskell hierarchy of number classes this provide a more flexible approach that is closer to the mathematical foundation (group, field, etc)

This try to only provide one feature per class, at the expense of the number of classes.

Synopsis

Documentation

class (Enum a, Eq a, Ord a, Integral a) => IsIntegral a where #

Number literals, convertible through the generic Integer type.

all number are Enum'erable, meaning that you can move to next element

Minimal complete definition

toInteger

Methods

toInteger :: a -> Integer #

Instances

IsIntegral Int 

Methods

toInteger :: Int -> Integer #

IsIntegral Int8 

Methods

toInteger :: Int8 -> Integer #

IsIntegral Int16 

Methods

toInteger :: Int16 -> Integer #

IsIntegral Int32 

Methods

toInteger :: Int32 -> Integer #

IsIntegral Int64 

Methods

toInteger :: Int64 -> Integer #

IsIntegral Integer 

Methods

toInteger :: Integer -> Integer #

IsIntegral Natural 

Methods

toInteger :: Natural -> Integer #

IsIntegral Word 

Methods

toInteger :: Word -> Integer #

IsIntegral Word8 

Methods

toInteger :: Word8 -> Integer #

IsIntegral Word16 

Methods

toInteger :: Word16 -> Integer #

IsIntegral Word32 

Methods

toInteger :: Word32 -> Integer #

IsIntegral Word64 

Methods

toInteger :: Word64 -> Integer #

IsIntegral CChar 

Methods

toInteger :: CChar -> Integer #

IsIntegral CSChar 

Methods

toInteger :: CSChar -> Integer #

IsIntegral CUChar 

Methods

toInteger :: CUChar -> Integer #

IsIntegral CShort 

Methods

toInteger :: CShort -> Integer #

IsIntegral CUShort 

Methods

toInteger :: CUShort -> Integer #

IsIntegral CInt 

Methods

toInteger :: CInt -> Integer #

IsIntegral CUInt 

Methods

toInteger :: CUInt -> Integer #

IsIntegral CLong 

Methods

toInteger :: CLong -> Integer #

IsIntegral CULong 

Methods

toInteger :: CULong -> Integer #

IsIntegral CLLong 

Methods

toInteger :: CLLong -> Integer #

IsIntegral CULLong 

Methods

toInteger :: CULLong -> Integer #

IsIntegral CBool 

Methods

toInteger :: CBool -> Integer #

IsIntegral CPtrdiff 
IsIntegral CSize 

Methods

toInteger :: CSize -> Integer #

IsIntegral CWchar 

Methods

toInteger :: CWchar -> Integer #

IsIntegral CSigAtomic 
IsIntegral CIntPtr 

Methods

toInteger :: CIntPtr -> Integer #

IsIntegral CUIntPtr 
IsIntegral CIntMax 

Methods

toInteger :: CIntMax -> Integer #

IsIntegral CUIntMax 
IsIntegral Word256 

Methods

toInteger :: Word256 -> Integer #

IsIntegral Word128 

Methods

toInteger :: Word128 -> Integer #

IsIntegral (Offset ty) 

Methods

toInteger :: Offset ty -> Integer #

IsIntegral (CountOf ty) 

Methods

toInteger :: CountOf ty -> Integer #

class (Enum a, Eq a, Ord a, Integral a, IsIntegral a) => IsNatural a where #

Non Negative Number literals, convertible through the generic Natural type

Minimal complete definition

toNatural

Methods

toNatural :: a -> Natural #

class Signed a where Source #

types that have sign and can be made absolute

Minimal complete definition

abs, signum

Methods

abs :: a -> a Source #

signum :: a -> Sign Source #

class Additive a where #

Represent class of things that can be added together, contains a neutral element and is commutative.

x + azero = x
azero + x = x
x + y = y + x

Minimal complete definition

azero, (+)

Methods

azero :: a #

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

scale :: IsNatural n => n -> a -> a #

Instances

Additive Double 

Methods

azero :: Double #

(+) :: Double -> Double -> Double #

scale :: IsNatural n => n -> Double -> Double #

Additive Float 

Methods

azero :: Float #

(+) :: Float -> Float -> Float #

scale :: IsNatural n => n -> Float -> Float #

Additive Int 

Methods

azero :: Int #

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

scale :: IsNatural n => n -> Int -> Int #

Additive Int8 

Methods

azero :: Int8 #

(+) :: Int8 -> Int8 -> Int8 #

scale :: IsNatural n => n -> Int8 -> Int8 #

Additive Int16 

Methods

azero :: Int16 #

(+) :: Int16 -> Int16 -> Int16 #

scale :: IsNatural n => n -> Int16 -> Int16 #

Additive Int32 

Methods

azero :: Int32 #

(+) :: Int32 -> Int32 -> Int32 #

scale :: IsNatural n => n -> Int32 -> Int32 #

Additive Int64 

Methods

azero :: Int64 #

(+) :: Int64 -> Int64 -> Int64 #

scale :: IsNatural n => n -> Int64 -> Int64 #

Additive Integer 

Methods

azero :: Integer #

(+) :: Integer -> Integer -> Integer #

scale :: IsNatural n => n -> Integer -> Integer #

Additive Natural 

Methods

azero :: Natural #

(+) :: Natural -> Natural -> Natural #

scale :: IsNatural n => n -> Natural -> Natural #

Additive Word 

Methods

azero :: Word #

(+) :: Word -> Word -> Word #

scale :: IsNatural n => n -> Word -> Word #

Additive Word8 

Methods

azero :: Word8 #

(+) :: Word8 -> Word8 -> Word8 #

scale :: IsNatural n => n -> Word8 -> Word8 #

Additive Word16 

Methods

azero :: Word16 #

(+) :: Word16 -> Word16 -> Word16 #

scale :: IsNatural n => n -> Word16 -> Word16 #

Additive Word32 

Methods

azero :: Word32 #

(+) :: Word32 -> Word32 -> Word32 #

scale :: IsNatural n => n -> Word32 -> Word32 #

Additive Word64 

Methods

azero :: Word64 #

(+) :: Word64 -> Word64 -> Word64 #

scale :: IsNatural n => n -> Word64 -> Word64 #

Additive COff 

Methods

azero :: COff #

(+) :: COff -> COff -> COff #

scale :: IsNatural n => n -> COff -> COff #

Additive CChar 

Methods

azero :: CChar #

(+) :: CChar -> CChar -> CChar #

scale :: IsNatural n => n -> CChar -> CChar #

Additive CSChar 

Methods

azero :: CSChar #

(+) :: CSChar -> CSChar -> CSChar #

scale :: IsNatural n => n -> CSChar -> CSChar #

Additive CUChar 

Methods

azero :: CUChar #

(+) :: CUChar -> CUChar -> CUChar #

scale :: IsNatural n => n -> CUChar -> CUChar #

Additive CShort 

Methods

azero :: CShort #

(+) :: CShort -> CShort -> CShort #

scale :: IsNatural n => n -> CShort -> CShort #

Additive CUShort 

Methods

azero :: CUShort #

(+) :: CUShort -> CUShort -> CUShort #

scale :: IsNatural n => n -> CUShort -> CUShort #

Additive CInt 

Methods

azero :: CInt #

(+) :: CInt -> CInt -> CInt #

scale :: IsNatural n => n -> CInt -> CInt #

Additive CUInt 

Methods

azero :: CUInt #

(+) :: CUInt -> CUInt -> CUInt #

scale :: IsNatural n => n -> CUInt -> CUInt #

Additive CLong 

Methods

azero :: CLong #

(+) :: CLong -> CLong -> CLong #

scale :: IsNatural n => n -> CLong -> CLong #

Additive CULong 

Methods

azero :: CULong #

(+) :: CULong -> CULong -> CULong #

scale :: IsNatural n => n -> CULong -> CULong #

Additive CLLong 

Methods

azero :: CLLong #

(+) :: CLLong -> CLLong -> CLLong #

scale :: IsNatural n => n -> CLLong -> CLLong #

Additive CULLong 

Methods

azero :: CULLong #

(+) :: CULLong -> CULLong -> CULLong #

scale :: IsNatural n => n -> CULLong -> CULLong #

Additive CFloat 

Methods

azero :: CFloat #

(+) :: CFloat -> CFloat -> CFloat #

scale :: IsNatural n => n -> CFloat -> CFloat #

Additive CDouble 

Methods

azero :: CDouble #

(+) :: CDouble -> CDouble -> CDouble #

scale :: IsNatural n => n -> CDouble -> CDouble #

Additive CPtrdiff 
Additive CSize 

Methods

azero :: CSize #

(+) :: CSize -> CSize -> CSize #

scale :: IsNatural n => n -> CSize -> CSize #

Additive CWchar 

Methods

azero :: CWchar #

(+) :: CWchar -> CWchar -> CWchar #

scale :: IsNatural n => n -> CWchar -> CWchar #

Additive CSigAtomic 
Additive CClock 

Methods

azero :: CClock #

(+) :: CClock -> CClock -> CClock #

scale :: IsNatural n => n -> CClock -> CClock #

Additive CTime 

Methods

azero :: CTime #

(+) :: CTime -> CTime -> CTime #

scale :: IsNatural n => n -> CTime -> CTime #

Additive CUSeconds 
Additive CSUSeconds 
Additive CIntPtr 

Methods

azero :: CIntPtr #

(+) :: CIntPtr -> CIntPtr -> CIntPtr #

scale :: IsNatural n => n -> CIntPtr -> CIntPtr #

Additive CUIntPtr 
Additive CIntMax 

Methods

azero :: CIntMax #

(+) :: CIntMax -> CIntMax -> CIntMax #

scale :: IsNatural n => n -> CIntMax -> CIntMax #

Additive CUIntMax 
Additive Word256 

Methods

azero :: Word256 #

(+) :: Word256 -> Word256 -> Word256 #

scale :: IsNatural n => n -> Word256 -> Word256 #

Additive Word128 

Methods

azero :: Word128 #

(+) :: Word128 -> Word128 -> Word128 #

scale :: IsNatural n => n -> Word128 -> Word128 #

Additive Seconds # 

Methods

azero :: Seconds #

(+) :: Seconds -> Seconds -> Seconds #

scale :: IsNatural n => n -> Seconds -> Seconds #

Additive NanoSeconds # 
Additive (Offset ty) 

Methods

azero :: Offset ty #

(+) :: Offset ty -> Offset ty -> Offset ty #

scale :: IsNatural n => n -> Offset ty -> Offset ty #

Additive (CountOf ty) 

Methods

azero :: CountOf ty #

(+) :: CountOf ty -> CountOf ty -> CountOf ty #

scale :: IsNatural n => n -> CountOf ty -> CountOf ty #

(KnownNat n, NatWithinBound Word64 n) => Additive (Zn64 n) 

Methods

azero :: Zn64 n #

(+) :: Zn64 n -> Zn64 n -> Zn64 n #

scale :: IsNatural n => n -> Zn64 n -> Zn64 n #

KnownNat n => Additive (Zn n) 

Methods

azero :: Zn n #

(+) :: Zn n -> Zn n -> Zn n #

scale :: IsNatural n => n -> Zn n -> Zn n #

class Subtractive a where #

Represent class of things that can be subtracted.

Note that the result is not necessary of the same type as the operand depending on the actual type.

For example:

(-) :: Int -> Int -> Int
(-) :: DateTime -> DateTime -> Seconds
(-) :: Ptr a -> Ptr a -> PtrDiff
(-) :: Natural -> Natural -> Maybe Natural

Minimal complete definition

(-)

Associated Types

type Difference a :: * #

Methods

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

Instances

Subtractive Char 

Associated Types

type Difference Char :: * #

Methods

(-) :: Char -> Char -> Difference Char #

Subtractive Double 

Associated Types

type Difference Double :: * #

Subtractive Float 

Associated Types

type Difference Float :: * #

Methods

(-) :: Float -> Float -> Difference Float #

Subtractive Int 

Associated Types

type Difference Int :: * #

Methods

(-) :: Int -> Int -> Difference Int #

Subtractive Int8 

Associated Types

type Difference Int8 :: * #

Methods

(-) :: Int8 -> Int8 -> Difference Int8 #

Subtractive Int16 

Associated Types

type Difference Int16 :: * #

Methods

(-) :: Int16 -> Int16 -> Difference Int16 #

Subtractive Int32 

Associated Types

type Difference Int32 :: * #

Methods

(-) :: Int32 -> Int32 -> Difference Int32 #

Subtractive Int64 

Associated Types

type Difference Int64 :: * #

Methods

(-) :: Int64 -> Int64 -> Difference Int64 #

Subtractive Integer 

Associated Types

type Difference Integer :: * #

Subtractive Natural 

Associated Types

type Difference Natural :: * #

Subtractive Word 

Associated Types

type Difference Word :: * #

Methods

(-) :: Word -> Word -> Difference Word #

Subtractive Word8 

Associated Types

type Difference Word8 :: * #

Methods

(-) :: Word8 -> Word8 -> Difference Word8 #

Subtractive Word16 

Associated Types

type Difference Word16 :: * #

Subtractive Word32 

Associated Types

type Difference Word32 :: * #

Subtractive Word64 

Associated Types

type Difference Word64 :: * #

Subtractive COff 

Associated Types

type Difference COff :: * #

Methods

(-) :: COff -> COff -> Difference COff #

Subtractive CChar 

Associated Types

type Difference CChar :: * #

Methods

(-) :: CChar -> CChar -> Difference CChar #

Subtractive CSChar 

Associated Types

type Difference CSChar :: * #

Subtractive CUChar 

Associated Types

type Difference CUChar :: * #

Subtractive CShort 

Associated Types

type Difference CShort :: * #

Subtractive CUShort 

Associated Types

type Difference CUShort :: * #

Subtractive CInt 

Associated Types

type Difference CInt :: * #

Methods

(-) :: CInt -> CInt -> Difference CInt #

Subtractive CUInt 

Associated Types

type Difference CUInt :: * #

Methods

(-) :: CUInt -> CUInt -> Difference CUInt #

Subtractive CLong 

Associated Types

type Difference CLong :: * #

Methods

(-) :: CLong -> CLong -> Difference CLong #

Subtractive CULong 

Associated Types

type Difference CULong :: * #

Subtractive CLLong 

Associated Types

type Difference CLLong :: * #

Subtractive CULLong 

Associated Types

type Difference CULLong :: * #

Subtractive CBool 

Associated Types

type Difference CBool :: * #

Methods

(-) :: CBool -> CBool -> Difference CBool #

Subtractive CFloat 

Associated Types

type Difference CFloat :: * #

Subtractive CDouble 

Associated Types

type Difference CDouble :: * #

Subtractive CPtrdiff 

Associated Types

type Difference CPtrdiff :: * #

Subtractive CSize 

Associated Types

type Difference CSize :: * #

Methods

(-) :: CSize -> CSize -> Difference CSize #

Subtractive CWchar 

Associated Types

type Difference CWchar :: * #

Subtractive CSigAtomic 

Associated Types

type Difference CSigAtomic :: * #

Subtractive CClock 

Associated Types

type Difference CClock :: * #

Subtractive CTime 

Associated Types

type Difference CTime :: * #

Methods

(-) :: CTime -> CTime -> Difference CTime #

Subtractive CUSeconds 

Associated Types

type Difference CUSeconds :: * #

Subtractive CSUSeconds 

Associated Types

type Difference CSUSeconds :: * #

Subtractive CIntPtr 

Associated Types

type Difference CIntPtr :: * #

Subtractive CUIntPtr 

Associated Types

type Difference CUIntPtr :: * #

Subtractive CIntMax 

Associated Types

type Difference CIntMax :: * #

Subtractive CUIntMax 

Associated Types

type Difference CUIntMax :: * #

Subtractive Word256 

Associated Types

type Difference Word256 :: * #

Subtractive Word128 

Associated Types

type Difference Word128 :: * #

Subtractive (Offset ty) 

Associated Types

type Difference (Offset ty) :: * #

Methods

(-) :: Offset ty -> Offset ty -> Difference (Offset ty) #

Subtractive (CountOf ty) 

Associated Types

type Difference (CountOf ty) :: * #

Methods

(-) :: CountOf ty -> CountOf ty -> Difference (CountOf ty) #

(KnownNat n, NatWithinBound Word64 n) => Subtractive (Zn64 n) 

Associated Types

type Difference (Zn64 n) :: * #

Methods

(-) :: Zn64 n -> Zn64 n -> Difference (Zn64 n) #

KnownNat n => Subtractive (Zn n) 

Associated Types

type Difference (Zn n) :: * #

Methods

(-) :: Zn n -> Zn n -> Difference (Zn n) #

class Multiplicative a where #

Represent class of things that can be multiplied together

x * midentity = x
midentity * x = x

Minimal complete definition

midentity, (*)

Methods

midentity :: a #

Identity element over multiplication

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

Multiplication of 2 elements that result in another element

(^) :: (IsNatural n, IDivisible n) => a -> n -> a infixr 8 #

Raise to power, repeated multiplication e.g. > a ^ 2 = a * a > a ^ 10 = (a ^ 5) * (a ^ 5) .. (^) :: (IsNatural n) => a -> n -> a

Instances

Multiplicative Double 

Methods

midentity :: Double #

(*) :: Double -> Double -> Double #

(^) :: (IsNatural n, IDivisible n) => Double -> n -> Double #

Multiplicative Float 

Methods

midentity :: Float #

(*) :: Float -> Float -> Float #

(^) :: (IsNatural n, IDivisible n) => Float -> n -> Float #

Multiplicative Int 

Methods

midentity :: Int #

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

(^) :: (IsNatural n, IDivisible n) => Int -> n -> Int #

Multiplicative Int8 

Methods

midentity :: Int8 #

(*) :: Int8 -> Int8 -> Int8 #

(^) :: (IsNatural n, IDivisible n) => Int8 -> n -> Int8 #

Multiplicative Int16 

Methods

midentity :: Int16 #

(*) :: Int16 -> Int16 -> Int16 #

(^) :: (IsNatural n, IDivisible n) => Int16 -> n -> Int16 #

Multiplicative Int32 

Methods

midentity :: Int32 #

(*) :: Int32 -> Int32 -> Int32 #

(^) :: (IsNatural n, IDivisible n) => Int32 -> n -> Int32 #

Multiplicative Int64 

Methods

midentity :: Int64 #

(*) :: Int64 -> Int64 -> Int64 #

(^) :: (IsNatural n, IDivisible n) => Int64 -> n -> Int64 #

Multiplicative Integer 
Multiplicative Natural 
Multiplicative Rational 
Multiplicative Word 

Methods

midentity :: Word #

(*) :: Word -> Word -> Word #

(^) :: (IsNatural n, IDivisible n) => Word -> n -> Word #

Multiplicative Word8 

Methods

midentity :: Word8 #

(*) :: Word8 -> Word8 -> Word8 #

(^) :: (IsNatural n, IDivisible n) => Word8 -> n -> Word8 #

Multiplicative Word16 

Methods

midentity :: Word16 #

(*) :: Word16 -> Word16 -> Word16 #

(^) :: (IsNatural n, IDivisible n) => Word16 -> n -> Word16 #

Multiplicative Word32 

Methods

midentity :: Word32 #

(*) :: Word32 -> Word32 -> Word32 #

(^) :: (IsNatural n, IDivisible n) => Word32 -> n -> Word32 #

Multiplicative Word64 

Methods

midentity :: Word64 #

(*) :: Word64 -> Word64 -> Word64 #

(^) :: (IsNatural n, IDivisible n) => Word64 -> n -> Word64 #

Multiplicative COff 

Methods

midentity :: COff #

(*) :: COff -> COff -> COff #

(^) :: (IsNatural n, IDivisible n) => COff -> n -> COff #

Multiplicative CChar 

Methods

midentity :: CChar #

(*) :: CChar -> CChar -> CChar #

(^) :: (IsNatural n, IDivisible n) => CChar -> n -> CChar #

Multiplicative CSChar 

Methods

midentity :: CSChar #

(*) :: CSChar -> CSChar -> CSChar #

(^) :: (IsNatural n, IDivisible n) => CSChar -> n -> CSChar #

Multiplicative CUChar 

Methods

midentity :: CUChar #

(*) :: CUChar -> CUChar -> CUChar #

(^) :: (IsNatural n, IDivisible n) => CUChar -> n -> CUChar #

Multiplicative CShort 

Methods

midentity :: CShort #

(*) :: CShort -> CShort -> CShort #

(^) :: (IsNatural n, IDivisible n) => CShort -> n -> CShort #

Multiplicative CUShort 
Multiplicative CInt 

Methods

midentity :: CInt #

(*) :: CInt -> CInt -> CInt #

(^) :: (IsNatural n, IDivisible n) => CInt -> n -> CInt #

Multiplicative CUInt 

Methods

midentity :: CUInt #

(*) :: CUInt -> CUInt -> CUInt #

(^) :: (IsNatural n, IDivisible n) => CUInt -> n -> CUInt #

Multiplicative CLong 

Methods

midentity :: CLong #

(*) :: CLong -> CLong -> CLong #

(^) :: (IsNatural n, IDivisible n) => CLong -> n -> CLong #

Multiplicative CULong 

Methods

midentity :: CULong #

(*) :: CULong -> CULong -> CULong #

(^) :: (IsNatural n, IDivisible n) => CULong -> n -> CULong #

Multiplicative CLLong 

Methods

midentity :: CLLong #

(*) :: CLLong -> CLLong -> CLLong #

(^) :: (IsNatural n, IDivisible n) => CLLong -> n -> CLLong #

Multiplicative CULLong 
Multiplicative CFloat 

Methods

midentity :: CFloat #

(*) :: CFloat -> CFloat -> CFloat #

(^) :: (IsNatural n, IDivisible n) => CFloat -> n -> CFloat #

Multiplicative CDouble 
Multiplicative CPtrdiff 
Multiplicative CSize 

Methods

midentity :: CSize #

(*) :: CSize -> CSize -> CSize #

(^) :: (IsNatural n, IDivisible n) => CSize -> n -> CSize #

Multiplicative CWchar 

Methods

midentity :: CWchar #

(*) :: CWchar -> CWchar -> CWchar #

(^) :: (IsNatural n, IDivisible n) => CWchar -> n -> CWchar #

Multiplicative CSigAtomic 
Multiplicative CClock 

Methods

midentity :: CClock #

(*) :: CClock -> CClock -> CClock #

(^) :: (IsNatural n, IDivisible n) => CClock -> n -> CClock #

Multiplicative CTime 

Methods

midentity :: CTime #

(*) :: CTime -> CTime -> CTime #

(^) :: (IsNatural n, IDivisible n) => CTime -> n -> CTime #

Multiplicative CUSeconds 
Multiplicative CSUSeconds 
Multiplicative CIntPtr 
Multiplicative CUIntPtr 
Multiplicative CIntMax 
Multiplicative CUIntMax 
Multiplicative Word256 
Multiplicative Word128 

class (Additive a, Multiplicative a) => IDivisible a where #

Represent types that supports an euclidian division

(x ‘div‘ y) * y + (x ‘mod‘ y) == x

Minimal complete definition

div, mod | divMod

Methods

div :: a -> a -> a #

mod :: a -> a -> a #

divMod :: a -> a -> (a, a) #

Instances

IDivisible Int 

Methods

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

divMod :: Int -> Int -> (Int, Int) #

IDivisible Int8 

Methods

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

IDivisible Int16 

Methods

div :: Int16 -> Int16 -> Int16 #

mod :: Int16 -> Int16 -> Int16 #

divMod :: Int16 -> Int16 -> (Int16, Int16) #

IDivisible Int32 

Methods

div :: Int32 -> Int32 -> Int32 #

mod :: Int32 -> Int32 -> Int32 #

divMod :: Int32 -> Int32 -> (Int32, Int32) #

IDivisible Int64 

Methods

div :: Int64 -> Int64 -> Int64 #

mod :: Int64 -> Int64 -> Int64 #

divMod :: Int64 -> Int64 -> (Int64, Int64) #

IDivisible Integer 
IDivisible Natural 
IDivisible Word 

Methods

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

divMod :: Word -> Word -> (Word, Word) #

IDivisible Word8 

Methods

div :: Word8 -> Word8 -> Word8 #

mod :: Word8 -> Word8 -> Word8 #

divMod :: Word8 -> Word8 -> (Word8, Word8) #

IDivisible Word16 

Methods

div :: Word16 -> Word16 -> Word16 #

mod :: Word16 -> Word16 -> Word16 #

divMod :: Word16 -> Word16 -> (Word16, Word16) #

IDivisible Word32 

Methods

div :: Word32 -> Word32 -> Word32 #

mod :: Word32 -> Word32 -> Word32 #

divMod :: Word32 -> Word32 -> (Word32, Word32) #

IDivisible Word64 

Methods

div :: Word64 -> Word64 -> Word64 #

mod :: Word64 -> Word64 -> Word64 #

divMod :: Word64 -> Word64 -> (Word64, Word64) #

IDivisible CChar 

Methods

div :: CChar -> CChar -> CChar #

mod :: CChar -> CChar -> CChar #

divMod :: CChar -> CChar -> (CChar, CChar) #

IDivisible CSChar 

Methods

div :: CSChar -> CSChar -> CSChar #

mod :: CSChar -> CSChar -> CSChar #

divMod :: CSChar -> CSChar -> (CSChar, CSChar) #

IDivisible CUChar 

Methods

div :: CUChar -> CUChar -> CUChar #

mod :: CUChar -> CUChar -> CUChar #

divMod :: CUChar -> CUChar -> (CUChar, CUChar) #

IDivisible CShort 

Methods

div :: CShort -> CShort -> CShort #

mod :: CShort -> CShort -> CShort #

divMod :: CShort -> CShort -> (CShort, CShort) #

IDivisible CUShort 
IDivisible CInt 

Methods

div :: CInt -> CInt -> CInt #

mod :: CInt -> CInt -> CInt #

divMod :: CInt -> CInt -> (CInt, CInt) #

IDivisible CUInt 

Methods

div :: CUInt -> CUInt -> CUInt #

mod :: CUInt -> CUInt -> CUInt #

divMod :: CUInt -> CUInt -> (CUInt, CUInt) #

IDivisible CLong 

Methods

div :: CLong -> CLong -> CLong #

mod :: CLong -> CLong -> CLong #

divMod :: CLong -> CLong -> (CLong, CLong) #

IDivisible CULong 

Methods

div :: CULong -> CULong -> CULong #

mod :: CULong -> CULong -> CULong #

divMod :: CULong -> CULong -> (CULong, CULong) #

IDivisible CLLong 

Methods

div :: CLLong -> CLLong -> CLLong #

mod :: CLLong -> CLLong -> CLLong #

divMod :: CLLong -> CLLong -> (CLLong, CLLong) #

IDivisible CULLong 
IDivisible CPtrdiff 
IDivisible CSize 

Methods

div :: CSize -> CSize -> CSize #

mod :: CSize -> CSize -> CSize #

divMod :: CSize -> CSize -> (CSize, CSize) #

IDivisible CWchar 

Methods

div :: CWchar -> CWchar -> CWchar #

mod :: CWchar -> CWchar -> CWchar #

divMod :: CWchar -> CWchar -> (CWchar, CWchar) #

IDivisible CSigAtomic 
IDivisible CIntPtr 
IDivisible CUIntPtr 
IDivisible CIntMax 
IDivisible CUIntMax 
IDivisible Word256 
IDivisible Word128 

class Multiplicative a => Divisible a where #

Support for division between same types

This is likely to change to represent specific mathematic divisions

Minimal complete definition

(/)

Methods

(/) :: a -> a -> a infixl 7 #

Instances

data Sign Source #

Sign of a signed number

Instances

Eq Sign Source # 

Methods

(==) :: Sign -> Sign -> Bool #

(/=) :: Sign -> Sign -> Bool #

recip :: Divisible a => a -> a #

class IntegralRounding a where Source #

Minimal complete definition

roundUp, roundDown, roundTruncate, roundNearest

Methods

roundUp :: Integral n => a -> n Source #

Round up, to the next integral.

Also known as ceiling

roundDown :: Integral n => a -> n Source #

Round down, to the previous integral

Also known as floor

roundTruncate :: Integral n => a -> n Source #

Truncate to the closest integral to the fractional number closer to 0.

This is equivalent to roundUp for negative Number and roundDown for positive Number

roundNearest :: Integral n => a -> n Source #

Round to the nearest integral

roundNearest 3.6

4 > roundNearest 3.4 3