foundation-0.0.11: 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 Source #

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

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

Non Negative Number literals, convertible through the generic Natural type

Minimal complete definition

toNatural

Methods

toNatural :: a -> Natural Source #

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

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

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

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

Instances

Additive Double Source # 
Additive Float Source # 
Additive Int Source # 

Methods

azero :: Int Source #

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

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

Additive Int8 Source # 

Methods

azero :: Int8 Source #

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

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

Additive Int16 Source # 
Additive Int32 Source # 
Additive Int64 Source # 
Additive Integer Source # 
Additive Word Source # 

Methods

azero :: Word Source #

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

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

Additive Word8 Source # 
Additive Word16 Source # 
Additive Word32 Source # 
Additive Word64 Source # 
Additive Natural Source # 
Additive CSize Source # 
Additive Seconds Source # 
Additive NanoSeconds Source # 
Additive (CountOf ty) Source # 

Methods

azero :: CountOf ty Source #

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

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

Additive (Offset ty) Source # 

Methods

azero :: Offset ty Source #

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

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

class Subtractive a where Source #

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

Methods

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

Instances

Subtractive Char Source # 

Associated Types

type Difference Char :: * Source #

Methods

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

Subtractive Double Source # 

Associated Types

type Difference Double :: * Source #

Subtractive Float Source # 

Associated Types

type Difference Float :: * Source #

Subtractive Int Source # 

Associated Types

type Difference Int :: * Source #

Methods

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

Subtractive Int8 Source # 

Associated Types

type Difference Int8 :: * Source #

Methods

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

Subtractive Int16 Source # 

Associated Types

type Difference Int16 :: * Source #

Subtractive Int32 Source # 

Associated Types

type Difference Int32 :: * Source #

Subtractive Int64 Source # 

Associated Types

type Difference Int64 :: * Source #

Subtractive Integer Source # 

Associated Types

type Difference Integer :: * Source #

Subtractive Word Source # 

Associated Types

type Difference Word :: * Source #

Methods

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

Subtractive Word8 Source # 

Associated Types

type Difference Word8 :: * Source #

Subtractive Word16 Source # 

Associated Types

type Difference Word16 :: * Source #

Subtractive Word32 Source # 

Associated Types

type Difference Word32 :: * Source #

Subtractive Word64 Source # 

Associated Types

type Difference Word64 :: * Source #

Subtractive Natural Source # 

Associated Types

type Difference Natural :: * Source #

Subtractive (CountOf ty) Source # 

Associated Types

type Difference (CountOf ty) :: * Source #

Methods

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

Subtractive (Offset ty) Source # 

Associated Types

type Difference (Offset ty) :: * Source #

Methods

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

class Multiplicative a where Source #

Represent class of things that can be multiplied together

x * midentity = x
midentity * x = x

Minimal complete definition

midentity, (*)

Methods

midentity :: a Source #

Identity element over multiplication

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

Multiplication of 2 elements that result in another element

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

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 Source # 
Multiplicative Float Source # 
Multiplicative Int Source # 

Methods

midentity :: Int Source #

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

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

Multiplicative Int8 Source # 

Methods

midentity :: Int8 Source #

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

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

Multiplicative Int16 Source # 
Multiplicative Int32 Source # 
Multiplicative Int64 Source # 
Multiplicative Integer Source # 
Multiplicative Rational Source # 
Multiplicative Word Source # 

Methods

midentity :: Word Source #

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

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

Multiplicative Word8 Source # 
Multiplicative Word16 Source # 
Multiplicative Word32 Source # 
Multiplicative Word64 Source # 
Multiplicative Natural Source # 

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

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

mod :: a -> a -> a Source #

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

Instances

IDivisible Int Source # 

Methods

div :: Int -> Int -> Int Source #

mod :: Int -> Int -> Int Source #

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

IDivisible Int8 Source # 

Methods

div :: Int8 -> Int8 -> Int8 Source #

mod :: Int8 -> Int8 -> Int8 Source #

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

IDivisible Int16 Source # 
IDivisible Int32 Source # 
IDivisible Int64 Source # 
IDivisible Integer Source # 
IDivisible Word Source # 

Methods

div :: Word -> Word -> Word Source #

mod :: Word -> Word -> Word Source #

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

IDivisible Word8 Source # 
IDivisible Word16 Source # 
IDivisible Word32 Source # 
IDivisible Word64 Source # 
IDivisible Natural Source # 

class Multiplicative a => Divisible a where Source #

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

data Sign Source #

Sign of a signed number

Instances

Eq Sign Source # 

Methods

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

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

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

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