foundation-0.0.22: 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 (Integral a, Eq a, Ord 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

Methods

toInteger :: a -> Integer #

Instances
IsIntegral Int 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Int -> Integer #

IsIntegral Int8 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Int8 -> Integer #

IsIntegral Int16 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Int16 -> Integer #

IsIntegral Int32 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Int32 -> Integer #

IsIntegral Int64 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Int64 -> Integer #

IsIntegral Integer 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Integer -> Integer #

IsIntegral Natural 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Natural -> Integer #

IsIntegral Word 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Word -> Integer #

IsIntegral Word8 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Word8 -> Integer #

IsIntegral Word16 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Word16 -> Integer #

IsIntegral Word32 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Word32 -> Integer #

IsIntegral Word64 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: Word64 -> Integer #

IsIntegral CChar 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CChar -> Integer #

IsIntegral CSChar 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CSChar -> Integer #

IsIntegral CUChar 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CUChar -> Integer #

IsIntegral CShort 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CShort -> Integer #

IsIntegral CUShort 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CUShort -> Integer #

IsIntegral CInt 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CInt -> Integer #

IsIntegral CUInt 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CUInt -> Integer #

IsIntegral CLong 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CLong -> Integer #

IsIntegral CULong 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CULong -> Integer #

IsIntegral CLLong 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CLLong -> Integer #

IsIntegral CULLong 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CULLong -> Integer #

IsIntegral CBool 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CBool -> Integer #

IsIntegral CPtrdiff 
Instance details

Defined in Basement.Numerical.Number

IsIntegral CSize 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CSize -> Integer #

IsIntegral CWchar 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CWchar -> Integer #

IsIntegral CSigAtomic 
Instance details

Defined in Basement.Numerical.Number

IsIntegral CIntPtr 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CIntPtr -> Integer #

IsIntegral CUIntPtr 
Instance details

Defined in Basement.Numerical.Number

IsIntegral CIntMax 
Instance details

Defined in Basement.Numerical.Number

Methods

toInteger :: CIntMax -> Integer #

IsIntegral CUIntMax 
Instance details

Defined in Basement.Numerical.Number

IsIntegral Word256 
Instance details

Defined in Basement.Types.Word256

Methods

toInteger :: Word256 -> Integer #

IsIntegral Word128 
Instance details

Defined in Basement.Types.Word128

Methods

toInteger :: Word128 -> Integer #

IsIntegral (Offset ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

toInteger :: Offset ty -> Integer #

IsIntegral (CountOf ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

toInteger :: CountOf ty -> Integer #

(KnownNat n, NatWithinBound Word64 n) => IsIntegral (Zn64 n) 
Instance details

Defined in Basement.Bounded

Methods

toInteger :: Zn64 n -> Integer #

KnownNat n => IsIntegral (Zn n) 
Instance details

Defined in Basement.Bounded

Methods

toInteger :: Zn n -> Integer #

class IsIntegral a => IsNatural a where #

Non Negative Number literals, convertible through the generic Natural type

Methods

toNatural :: a -> Natural #

Instances
IsNatural Natural 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: Natural -> Natural #

IsNatural Word 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: Word -> Natural #

IsNatural Word8 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: Word8 -> Natural #

IsNatural Word16 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: Word16 -> Natural #

IsNatural Word32 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: Word32 -> Natural #

IsNatural Word64 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: Word64 -> Natural #

IsNatural CUChar 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: CUChar -> Natural #

IsNatural CUShort 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: CUShort -> Natural #

IsNatural CUInt 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: CUInt -> Natural #

IsNatural CULong 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: CULong -> Natural #

IsNatural CULLong 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: CULLong -> Natural #

IsNatural CSize 
Instance details

Defined in Basement.Numerical.Number

Methods

toNatural :: CSize -> Natural #

IsNatural CUIntPtr 
Instance details

Defined in Basement.Numerical.Number

IsNatural CUIntMax 
Instance details

Defined in Basement.Numerical.Number

IsNatural Word256 
Instance details

Defined in Basement.Types.Word256

Methods

toNatural :: Word256 -> Natural #

IsNatural Word128 
Instance details

Defined in Basement.Types.Word128

Methods

toNatural :: Word128 -> Natural #

IsNatural (Offset ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

toNatural :: Offset ty -> Natural #

IsNatural (CountOf ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

toNatural :: CountOf ty -> Natural #

(KnownNat n, NatWithinBound Word64 n) => IsNatural (Zn64 n) 
Instance details

Defined in Basement.Bounded

Methods

toNatural :: Zn64 n -> Natural #

KnownNat n => IsNatural (Zn n) 
Instance details

Defined in Basement.Bounded

Methods

toNatural :: Zn n -> Natural #

class Signed a where Source #

types that have sign and can be made absolute

Methods

abs :: a -> a Source #

signum :: a -> Sign Source #

Instances
Signed Double Source # 
Instance details

Defined in Foundation.Numerical

Signed Float Source # 
Instance details

Defined in Foundation.Numerical

Signed Int Source # 
Instance details

Defined in Foundation.Numerical

Methods

abs :: Int -> Int Source #

signum :: Int -> Sign Source #

Signed Int8 Source # 
Instance details

Defined in Foundation.Numerical

Methods

abs :: Int8 -> Int8 Source #

signum :: Int8 -> Sign Source #

Signed Int16 Source # 
Instance details

Defined in Foundation.Numerical

Signed Int32 Source # 
Instance details

Defined in Foundation.Numerical

Signed Int64 Source # 
Instance details

Defined in Foundation.Numerical

Signed Integer Source # 
Instance details

Defined in Foundation.Numerical

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

Defined in Basement.Numerical.Additive

Methods

azero :: Double #

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

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

Additive Float 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Float #

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

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

Additive Int 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Int #

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

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

Additive Int8 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Int8 #

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

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

Additive Int16 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Int16 #

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

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

Additive Int32 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Int32 #

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

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

Additive Int64 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Int64 #

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

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

Additive Integer 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Integer #

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

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

Additive Natural 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Natural #

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

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

Additive Word 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Word #

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

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

Additive Word8 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Word8 #

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

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

Additive Word16 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Word16 #

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

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

Additive Word32 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Word32 #

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

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

Additive Word64 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Word64 #

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

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

Additive COff 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: COff #

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

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

Additive CChar 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CChar #

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

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

Additive CSChar 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CSChar #

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

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

Additive CUChar 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CUChar #

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

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

Additive CShort 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CShort #

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

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

Additive CUShort 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CUShort #

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

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

Additive CInt 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CInt #

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

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

Additive CUInt 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CUInt #

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

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

Additive CLong 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CLong #

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

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

Additive CULong 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CULong #

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

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

Additive CLLong 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CLLong #

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

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

Additive CULLong 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CULLong #

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

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

Additive CFloat 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CFloat #

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

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

Additive CDouble 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CDouble #

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

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

Additive CPtrdiff 
Instance details

Defined in Basement.Numerical.Additive

Additive CSize 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CSize #

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

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

Additive CWchar 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CWchar #

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

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

Additive CSigAtomic 
Instance details

Defined in Basement.Numerical.Additive

Additive CClock 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CClock #

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

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

Additive CTime 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CTime #

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

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

Additive CUSeconds 
Instance details

Defined in Basement.Numerical.Additive

Additive CSUSeconds 
Instance details

Defined in Basement.Numerical.Additive

Additive CIntPtr 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CIntPtr #

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

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

Additive CUIntPtr 
Instance details

Defined in Basement.Numerical.Additive

Additive CIntMax 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: CIntMax #

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

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

Additive CUIntMax 
Instance details

Defined in Basement.Numerical.Additive

Additive Word256 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Word256 #

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

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

Additive Word128 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Word128 #

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

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

Additive Seconds Source # 
Instance details

Defined in Foundation.Time.Types

Methods

azero :: Seconds #

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

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

Additive NanoSeconds Source # 
Instance details

Defined in Foundation.Time.Types

SizeValid n => Additive (Bits n) 
Instance details

Defined in Basement.Bits

Methods

azero :: Bits n #

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

scale :: IsNatural n0 => n0 -> Bits n -> Bits n #

Additive (Offset ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

azero :: Offset ty #

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

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

Additive (CountOf ty) 
Instance details

Defined in Basement.Types.OffsetSize

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

Defined in Basement.Numerical.Additive

Methods

azero :: Zn64 n #

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

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

KnownNat n => Additive (Zn n) 
Instance details

Defined in Basement.Numerical.Additive

Methods

azero :: Zn n #

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

scale :: IsNatural n0 => n0 -> 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

Associated Types

type Difference a :: Type #

Methods

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

Instances
Subtractive Char 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Char :: Type #

Methods

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

Subtractive Double 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Double :: Type #

Subtractive Float 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Float :: Type #

Methods

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

Subtractive Int 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int :: Type #

Methods

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

Subtractive Int8 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int8 :: Type #

Methods

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

Subtractive Int16 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int16 :: Type #

Methods

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

Subtractive Int32 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int32 :: Type #

Methods

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

Subtractive Int64 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int64 :: Type #

Methods

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

Subtractive Integer 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Integer :: Type #

Subtractive Natural 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Natural :: Type #

Subtractive Word 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word :: Type #

Methods

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

Subtractive Word8 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word8 :: Type #

Methods

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

Subtractive Word16 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word16 :: Type #

Subtractive Word32 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word32 :: Type #

Subtractive Word64 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word64 :: Type #

Subtractive COff 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference COff :: Type #

Methods

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

Subtractive CChar 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CChar :: Type #

Methods

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

Subtractive CSChar 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CSChar :: Type #

Subtractive CUChar 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CUChar :: Type #

Subtractive CShort 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CShort :: Type #

Subtractive CUShort 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CUShort :: Type #

Subtractive CInt 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CInt :: Type #

Methods

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

Subtractive CUInt 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CUInt :: Type #

Methods

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

Subtractive CLong 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CLong :: Type #

Methods

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

Subtractive CULong 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CULong :: Type #

Subtractive CLLong 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CLLong :: Type #

Subtractive CULLong 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CULLong :: Type #

Subtractive CBool 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CBool :: Type #

Methods

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

Subtractive CFloat 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CFloat :: Type #

Subtractive CDouble 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CDouble :: Type #

Subtractive CPtrdiff 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CPtrdiff :: Type #

Subtractive CSize 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CSize :: Type #

Methods

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

Subtractive CWchar 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CWchar :: Type #

Subtractive CSigAtomic 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CSigAtomic :: Type #

Subtractive CClock 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CClock :: Type #

Subtractive CTime 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CTime :: Type #

Methods

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

Subtractive CUSeconds 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CUSeconds :: Type #

Subtractive CSUSeconds 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CSUSeconds :: Type #

Subtractive CIntPtr 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CIntPtr :: Type #

Subtractive CUIntPtr 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CUIntPtr :: Type #

Subtractive CIntMax 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CIntMax :: Type #

Subtractive CUIntMax 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CUIntMax :: Type #

Subtractive Word256 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word256 :: Type #

Subtractive Word128 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word128 :: Type #

SizeValid n => Subtractive (Bits n) 
Instance details

Defined in Basement.Bits

Associated Types

type Difference (Bits n) :: Type #

Methods

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

Subtractive (Offset ty) 
Instance details

Defined in Basement.Types.OffsetSize

Associated Types

type Difference (Offset ty) :: Type #

Methods

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

Subtractive (CountOf ty) 
Instance details

Defined in Basement.Types.OffsetSize

Associated Types

type Difference (CountOf ty) :: Type #

Methods

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

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

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference (Zn64 n) :: Type #

Methods

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

KnownNat n => Subtractive (Zn n) 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference (Zn n) :: Type #

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, Enum 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 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Double #

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

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

Multiplicative Float 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Float #

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

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

Multiplicative Int 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Int #

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

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

Multiplicative Int8 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Int8 #

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

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

Multiplicative Int16 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Int16 #

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

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

Multiplicative Int32 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Int32 #

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

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

Multiplicative Int64 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Int64 #

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

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

Multiplicative Integer 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Natural 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Rational 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Word #

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

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

Multiplicative Word8 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Word8 #

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

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

Multiplicative Word16 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Word16 #

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

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

Multiplicative Word32 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Word32 #

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

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

Multiplicative Word64 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: Word64 #

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

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

Multiplicative COff 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: COff #

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

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

Multiplicative CChar 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CChar #

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

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

Multiplicative CSChar 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CSChar #

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

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

Multiplicative CUChar 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CUChar #

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

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

Multiplicative CShort 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CShort #

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

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

Multiplicative CUShort 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CInt 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CInt #

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

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

Multiplicative CUInt 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CUInt #

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

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

Multiplicative CLong 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CLong #

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

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

Multiplicative CULong 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CULong #

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

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

Multiplicative CLLong 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CLLong #

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

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

Multiplicative CULLong 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CFloat 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CFloat #

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

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

Multiplicative CDouble 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CPtrdiff 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CSize 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CSize #

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

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

Multiplicative CWchar 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CWchar #

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

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

Multiplicative CSigAtomic 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CClock 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CClock #

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

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

Multiplicative CTime 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

midentity :: CTime #

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

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

Multiplicative CUSeconds 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CSUSeconds 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CIntPtr 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CUIntPtr 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CIntMax 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CUIntMax 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word256 
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word128 
Instance details

Defined in Basement.Numerical.Multiplicative

SizeValid n => Multiplicative (Bits n) 
Instance details

Defined in Basement.Bits

Methods

midentity :: Bits n #

(*) :: Bits n -> Bits n -> Bits n #

(^) :: (IsNatural n0, Enum n0, IDivisible n0) => Bits n -> n0 -> Bits n #

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

Defined in Basement.Numerical.Multiplicative

Methods

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

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

IDivisible Int8 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

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

IDivisible Int16 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: Int16 -> Int16 -> Int16 #

mod :: Int16 -> Int16 -> Int16 #

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

IDivisible Int32 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: Int32 -> Int32 -> Int32 #

mod :: Int32 -> Int32 -> Int32 #

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

IDivisible Int64 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: Int64 -> Int64 -> Int64 #

mod :: Int64 -> Int64 -> Int64 #

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

IDivisible Integer 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Natural 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

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

IDivisible Word8 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: Word8 -> Word8 -> Word8 #

mod :: Word8 -> Word8 -> Word8 #

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

IDivisible Word16 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: Word16 -> Word16 -> Word16 #

mod :: Word16 -> Word16 -> Word16 #

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

IDivisible Word32 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: Word32 -> Word32 -> Word32 #

mod :: Word32 -> Word32 -> Word32 #

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

IDivisible Word64 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: Word64 -> Word64 -> Word64 #

mod :: Word64 -> Word64 -> Word64 #

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

IDivisible CChar 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CChar -> CChar -> CChar #

mod :: CChar -> CChar -> CChar #

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

IDivisible CSChar 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CSChar -> CSChar -> CSChar #

mod :: CSChar -> CSChar -> CSChar #

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

IDivisible CUChar 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CUChar -> CUChar -> CUChar #

mod :: CUChar -> CUChar -> CUChar #

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

IDivisible CShort 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CShort -> CShort -> CShort #

mod :: CShort -> CShort -> CShort #

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

IDivisible CUShort 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CInt 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CInt -> CInt -> CInt #

mod :: CInt -> CInt -> CInt #

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

IDivisible CUInt 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CUInt -> CUInt -> CUInt #

mod :: CUInt -> CUInt -> CUInt #

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

IDivisible CLong 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CLong -> CLong -> CLong #

mod :: CLong -> CLong -> CLong #

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

IDivisible CULong 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CULong -> CULong -> CULong #

mod :: CULong -> CULong -> CULong #

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

IDivisible CLLong 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CLLong -> CLLong -> CLLong #

mod :: CLLong -> CLLong -> CLLong #

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

IDivisible CULLong 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CPtrdiff 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CSize 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CSize -> CSize -> CSize #

mod :: CSize -> CSize -> CSize #

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

IDivisible CWchar 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

div :: CWchar -> CWchar -> CWchar #

mod :: CWchar -> CWchar -> CWchar #

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

IDivisible CSigAtomic 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CIntPtr 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CUIntPtr 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CIntMax 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CUIntMax 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word256 
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word128 
Instance details

Defined in Basement.Numerical.Multiplicative

SizeValid n => IDivisible (Bits n) 
Instance details

Defined in Basement.Bits

Methods

div :: Bits n -> Bits n -> Bits n #

mod :: Bits n -> Bits n -> Bits n #

divMod :: Bits n -> Bits n -> (Bits n, Bits n) #

class Multiplicative a => Divisible a where #

Support for division between same types

This is likely to change to represent specific mathematic divisions

Methods

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

Instances
Divisible Double 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

(/) :: Double -> Double -> Double #

Divisible Float 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

(/) :: Float -> Float -> Float #

Divisible Rational 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

(/) :: Rational -> Rational -> Rational #

Divisible CFloat 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

(/) :: CFloat -> CFloat -> CFloat #

Divisible CDouble 
Instance details

Defined in Basement.Numerical.Multiplicative

Methods

(/) :: CDouble -> CDouble -> CDouble #

data Sign Source #

Sign of a signed number

Instances
Eq Sign Source # 
Instance details

Defined in Foundation.Numerical

Methods

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

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

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

class IntegralRounding a where Source #

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