numhask-0.8.1.0: A numeric class hierarchy.
Safe HaskellNone
LanguageHaskell2010

NumHask

Description

Numeric classes.

Synopsis

Usage

>>> :set -XRebindableSyntax
>>> import NumHask.Prelude
>>> 1+1
2

Overview

numhask is largely a set of classes that can replace the Num class and it's descendents. Principles that have guided design include:

  • balanced class density. The numeric heirarchy begins with addition and multiplication, choosing not to build from a Magma base. Whilst not being as principled as other approaches, this circumvents the instance explosion problems of Haskell whilst maintaining clarity of class purpose.
  • operator-first. In most cases, a class exists to define useful operators. The exceptions are Distributive, Ring and Field, which are collections of operators representing major teleological fault lines.
  • lawful. Most classes have laws associated with them that serve to relate class operators together in a meaningful way.
  • low-impact. The library attempts to fit in with the rest of the Haskell ecosystem. It provides instances for common numbers: Int, Integer, Double, Float and the Word classes. It avoids name (or idea) clashes with other popular libraries and adopts conventions in the current prelude where they make sense.
  • proof-of-concept. The library may be below industrial-strength depending on a definition of this term. At the same time, correspondence around improving the library is most welcome.

The class heirarchy looks somewhat like this:

If the base started with magma, and the library tolerated clashing with Semigroup and Monoid in base, it would look like:

These first two levels, contained in Group are moral super-classes.

Prelude Mappings

Num is a very old part of haskell, and is virtually unchanged since it's specification in haskell98.

A deconstruction of Num and mapping to numhask.

-- | Basic numeric class.
class  Num a  where
   {-# MINIMAL (+), (*), abs, signum, fromInteger, (negate | (-)) #-}

   (+), (-), (*)       :: a -> a -> a
   -- | Unary negation.
   negate              :: a -> a

(+) is an operator of the Additive class

(-) & negate are functions in the Subtractive class, and

(*) is an operator of the Multiplicative class.

zero and one are also introduced to the numeric heirarchy.

   -- | Absolute value.
   abs                 :: a -> a
   -- | 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).
   signum              :: a -> a

abs is a function in the Signed class. The concept of an absolute value can also include situations where the domain and codomain are different, and norm as a function in the Norm class is supplied for these cases.

sign replaces signum, because signum is simply a naming crime. basis can also be seen as a generalisation of sign.

   -- | 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@.
   fromInteger         :: Integer -> a

FromInteger becomes its own class and FromIntegral is introduced to polymorphise the covariant.

Mappings from other areas of prelude include:\

Integral becomes Integral and a polymorphic ToIntegral is introduced.

Fractional is roughly synonymous to Field together with a polymorphic FromRatio.

RealFrac becomes the polymorphic QuotientField

Floating is split into ExpField and TrigField

RealFloat is not attempted. Life is too short.

Extensions

RebindableSyntax is recommended for use with numhask.

As a replacement for the numerical classes, numhask clashes significantly with an unqualified import of the Prelude. Either numhask modules should be qualified, or prelude turned off with the NoImplicitPrelude extension, or with RebindableSyntax, which implies NoImplicitPrelude.

defaulting

Without RebindableSyntax, numeric literals default as follows:

>>> :set -XNoRebindableSyntax
>>> :t 1
1 :: Num a => a
>>> :t 1.0
1.0 :: Fractional a => a

With RebindableSyntax (which also switches NoImplicitPrelude on) literal numbers change to the numhask types, FromInteger and FromRational:

>>> :set -XRebindableSyntax
>>> :t 1
1 :: FromInteger a => a
>>> :t 1.0
1.0 :: FromRational a => a
>>> 1
1
>>> 1.0
1.0

RebindableSyntax is a tradeoff, however, and usage comes attached with other non-numeric changes that NumHask.Prelude attempts to counteract.

See haskell2010 Section 4.3.4 for the nuts and bolts to defaulting.

The effect of ExtendedDefaultRules in ghci or switched on as an extension also need to be understood. It can lead to unusual interactions with numerics and strange error messages at times because it adds () and [] to the start of the type defaulting list.

Exports

class Additive a => Subtractive a where Source #

or Subtraction

\a -> a - a == zero
\a -> negate a == zero - a
\a -> negate a + a == zero
\a -> a + negate a == zero
>>> negate 1
-1
>>> 1 - 2
-1

Minimal complete definition

negate

Methods

negate :: a -> a Source #

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

Instances

Instances details
Subtractive Bool Source # 
Instance details

Defined in NumHask.Algebra.Additive

Methods

negate :: Bool -> Bool Source #

(-) :: Bool -> Bool -> Bool Source #

Subtractive Double Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive Float Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive Int Source # 
Instance details

Defined in NumHask.Algebra.Additive

Methods

negate :: Int -> Int Source #

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

Subtractive Int8 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Methods

negate :: Int8 -> Int8 Source #

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

Subtractive Int16 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive Int32 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive Int64 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive Integer Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive Natural Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive Word Source # 
Instance details

Defined in NumHask.Algebra.Additive

Methods

negate :: Word -> Word Source #

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

Subtractive Word8 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive Word16 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive Word32 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive Word64 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Subtractive a => Subtractive (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

negate :: Complex a -> Complex a Source #

(-) :: Complex a -> Complex a -> Complex a Source #

(Ord a, Signed a, Integral a, Ring a) => Subtractive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

negate :: Ratio a -> Ratio a Source #

(-) :: Ratio a -> Ratio a -> Ratio a Source #

Subtractive b => Subtractive (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Additive

Methods

negate :: (a -> b) -> a -> b Source #

(-) :: (a -> b) -> (a -> b) -> a -> b Source #

class Additive a where Source #

or Addition

For practical reasons, we begin the class tree with Additive. Starting with Associative and Unital, or using Semigroup and Monoid from base tends to confuse the interface once you start having to disinguish between (say) monoidal addition and monoidal multiplication.

\a -> zero + a == a
\a -> a + zero == a
\a b c -> (a + b) + c == a + (b + c)
\a b -> a + b == b + a

By convention, (+) is regarded as commutative, but this is not universal, and the introduction of another symbol which means non-commutative addition seems a bit dogmatic.

>>> zero + 1
1
>>> 1 + 1
2

Methods

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

zero :: a Source #

Instances

Instances details
Additive Bool Source # 
Instance details

Defined in NumHask.Algebra.Additive

Methods

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

zero :: Bool Source #

Additive Double Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive Float Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive Int Source # 
Instance details

Defined in NumHask.Algebra.Additive

Methods

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

zero :: Int Source #

Additive Int8 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Methods

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

zero :: Int8 Source #

Additive Int16 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive Int32 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive Int64 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive Integer Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive Natural Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive Word Source # 
Instance details

Defined in NumHask.Algebra.Additive

Methods

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

zero :: Word Source #

Additive Word8 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive Word16 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive Word32 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive Word64 Source # 
Instance details

Defined in NumHask.Algebra.Additive

Additive a => Additive (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

(+) :: Complex a -> Complex a -> Complex a Source #

zero :: Complex a Source #

(Ord a, Signed a, Integral a, Ring a) => Additive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

(+) :: Ratio a -> Ratio a -> Ratio a Source #

zero :: Ratio a Source #

Additive b => Additive (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Additive

Methods

(+) :: (a -> b) -> (a -> b) -> a -> b Source #

zero :: a -> b Source #

sum :: (Additive a, Foldable f) => f a -> a Source #

Compute the sum of a Foldable.

class Multiplicative a => Divisive a where Source #

or Division

Though unusual, the term Divisive usefully fits in with the grammer of other classes and avoids name clashes that occur with some popular libraries.

\(a :: Double) -> a / a ~= one || a == zero
\(a :: Double) -> recip a ~= one / a || a == zero
\(a :: Double) -> recip a * a ~= one || a == zero
\(a :: Double) -> a * recip a ~= one || a == zero
>>> recip 2.0
0.5
>>> 1 / 2
0.5

Minimal complete definition

recip

Methods

recip :: a -> a Source #

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

Instances

Instances details
Divisive Double Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Divisive Float Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

(Subtractive a, Divisive a) => Divisive (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

recip :: Complex a -> Complex a Source #

(/) :: Complex a -> Complex a -> Complex a Source #

(Ord a, Signed a, Integral a, Ring a) => Divisive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

recip :: Ratio a -> Ratio a Source #

(/) :: Ratio a -> Ratio a -> Ratio a Source #

Divisive b => Divisive (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

recip :: (a -> b) -> a -> b Source #

(/) :: (a -> b) -> (a -> b) -> a -> b Source #

class Multiplicative a where Source #

or Multiplication

For practical reasons, we begin the class tree with Additive and Multiplicative. Starting with Associative and Unital, or using Semigroup and Monoid from base tends to confuse the interface once you start having to disinguish between (say) monoidal addition and monoidal multiplication.

\a -> one * a == a
\a -> a * one == a
\a b c -> (a * b) * c == a * (b * c)

By convention, (*) is regarded as not necessarily commutative, but this is not universal, and the introduction of another symbol which means commutative multiplication seems a bit dogmatic.

>>> one * 2
2
>>> 2 * 3
6

Methods

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

one :: a Source #

Instances

Instances details
Multiplicative Bool Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

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

one :: Bool Source #

Multiplicative Double Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Multiplicative Float Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

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

one :: Float Source #

Multiplicative Int Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

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

one :: Int Source #

Multiplicative Int8 Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

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

one :: Int8 Source #

Multiplicative Int16 Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

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

one :: Int16 Source #

Multiplicative Int32 Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

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

one :: Int32 Source #

Multiplicative Int64 Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

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

one :: Int64 Source #

Multiplicative Integer Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Multiplicative Natural Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Multiplicative Word Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

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

one :: Word Source #

Multiplicative Word8 Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

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

one :: Word8 Source #

Multiplicative Word16 Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Multiplicative Word32 Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Multiplicative Word64 Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

(Subtractive a, Multiplicative a) => Multiplicative (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

(*) :: Complex a -> Complex a -> Complex a Source #

one :: Complex a Source #

(Ord a, Signed a, Integral a, Ring a, Multiplicative a) => Multiplicative (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

(*) :: Ratio a -> Ratio a -> Ratio a Source #

one :: Ratio a Source #

Multiplicative b => Multiplicative (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Multiplicative

Methods

(*) :: (a -> b) -> (a -> b) -> a -> b Source #

one :: a -> b Source #

product :: (Multiplicative a, Foldable f) => f a -> a Source #

Compute the product of a Foldable.

class Distributive a => InvolutiveRing a where Source #

Involutive Ring

adj (a + b) ==> adj a + adj b
adj (a * b) ==> adj a * adj b
adj one ==> one
adj (adj a) ==> a

Note: elements for which adj a == a are called "self-adjoint".

Minimal complete definition

Nothing

Methods

adj :: a -> a Source #

Instances

Instances details
InvolutiveRing Double Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Double -> Double Source #

InvolutiveRing Float Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Float -> Float Source #

InvolutiveRing Int Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Int -> Int Source #

InvolutiveRing Int8 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Int8 -> Int8 Source #

InvolutiveRing Int16 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Int16 -> Int16 Source #

InvolutiveRing Int32 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Int32 -> Int32 Source #

InvolutiveRing Int64 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Int64 -> Int64 Source #

InvolutiveRing Integer Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Integer -> Integer Source #

InvolutiveRing Natural Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Natural -> Natural Source #

InvolutiveRing Word Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Word -> Word Source #

InvolutiveRing Word8 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Word8 -> Word8 Source #

InvolutiveRing Word16 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Word16 -> Word16 Source #

InvolutiveRing Word32 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Word32 -> Word32 Source #

InvolutiveRing Word64 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: Word64 -> Word64 Source #

(Distributive a, Subtractive a) => InvolutiveRing (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

adj :: Complex a -> Complex a Source #

InvolutiveRing b => InvolutiveRing (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

adj :: (a -> b) -> a -> b Source #

class (StarSemiring a, Idempotent a) => KleeneAlgebra a Source #

A Kleene Algebra is a Star Semiring with idempotent addition.

a * x + x = a ==> star a * x + x = x
x * a + x = a ==> x * star a + x = x

Instances

Instances details
KleeneAlgebra b => KleeneAlgebra (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Ring

class Distributive a => StarSemiring a where Source #

A StarSemiring is a semiring with an additional unary operator (star) satisfying:

\a -> star a = one + a * star a

Minimal complete definition

Nothing

Methods

star :: a -> a Source #

plus :: a -> a Source #

Instances

Instances details
StarSemiring b => StarSemiring (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Ring

Methods

star :: (a -> b) -> a -> b Source #

plus :: (a -> b) -> a -> b Source #

class (Distributive a, Subtractive a) => Ring a Source #

A Ring is an abelian group under addition (Unital, Associative, Commutative, Invertible) and monoidal under multiplication (Unital, Associative), and where multiplication distributes over addition.

\a -> zero + a == a
\a -> a + zero == a
\a b c -> (a + b) + c == a + (b + c)
\a b -> a + b == b + a
\a -> a - a == zero
\a -> negate a == zero - a
\a -> negate a + a == zero
\a -> a + negate a == zero
\a -> one * a == a
\a -> a * one == a
\a b c -> (a * b) * c == a * (b * c)
\a b c -> a * (b + c) == a * b + a * c
\a b c -> (a + b) * c == a * c + b * c
\a -> zero * a == zero
\a -> a * zero == zero

Instances

Instances details
(Distributive a, Subtractive a) => Ring a Source # 
Instance details

Defined in NumHask.Algebra.Ring

class (Additive a, Multiplicative a) => Distributive a Source #

Distributive

\a b c -> a * (b + c) == a * b + a * c
\a b c -> (a + b) * c == a * c + b * c
\a -> zero * a == zero
\a -> a * zero == zero

The sneaking in of the Absorption laws here glosses over the possibility that the multiplicative zero element does not have to correspond with the additive unital zero.

Instances

Instances details
Distributive Bool Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Double Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Float Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Int Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Int8 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Int16 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Int32 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Int64 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Integer Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Natural Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Word Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Word8 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Word16 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Word32 Source # 
Instance details

Defined in NumHask.Algebra.Ring

Distributive Word64 Source # 
Instance details

Defined in NumHask.Algebra.Ring

(Distributive a, Subtractive a) => Distributive (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

(Ord a, Signed a, Integral a, Ring a) => Distributive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Distributive b => Distributive (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Ring

two :: (Multiplicative a, Additive a) => a Source #

Defining two requires adding the multiplicative unital to itself. In other words, the concept of two is a Ring one.

>>> two
2

class Field a => TrigField a where Source #

Trigonometric Field

Minimal complete definition

pi, sin, cos, asin, acos, atan, atan2, sinh, cosh, asinh, acosh, atanh

Methods

pi :: a Source #

sin :: a -> a Source #

cos :: a -> a Source #

tan :: a -> a Source #

asin :: a -> a Source #

acos :: a -> a Source #

atan :: a -> a Source #

atan2 :: a -> a -> a Source #

sinh :: a -> a Source #

cosh :: a -> a Source #

tanh :: a -> a Source #

asinh :: a -> a Source #

acosh :: a -> a Source #

atanh :: a -> a Source #

Instances

Instances details
TrigField Double Source # 
Instance details

Defined in NumHask.Algebra.Field

TrigField Float Source # 
Instance details

Defined in NumHask.Algebra.Field

TrigField b => TrigField (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Field

Methods

pi :: a -> b Source #

sin :: (a -> b) -> a -> b Source #

cos :: (a -> b) -> a -> b Source #

tan :: (a -> b) -> a -> b Source #

asin :: (a -> b) -> a -> b Source #

acos :: (a -> b) -> a -> b Source #

atan :: (a -> b) -> a -> b Source #

atan2 :: (a -> b) -> (a -> b) -> a -> b Source #

sinh :: (a -> b) -> a -> b Source #

cosh :: (a -> b) -> a -> b Source #

tanh :: (a -> b) -> a -> b Source #

asinh :: (a -> b) -> a -> b Source #

acosh :: (a -> b) -> a -> b Source #

atanh :: (a -> b) -> a -> b Source #

class (Subtractive a, Field a) => LowerBoundedField a where Source #

Negative infinity.

Minimal complete definition

Nothing

Methods

negInfinity :: a Source #

Instances

Instances details
LowerBoundedField Double Source # 
Instance details

Defined in NumHask.Algebra.Field

LowerBoundedField Float Source # 
Instance details

Defined in NumHask.Algebra.Field

LowerBoundedField a => LowerBoundedField (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

(Ord a, Signed a, Integral a, Field a) => LowerBoundedField (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

LowerBoundedField b => LowerBoundedField (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Field

Methods

negInfinity :: a -> b Source #

class Field a => UpperBoundedField a where Source #

A bounded field introduces the concepts of infinity and NaN.

one / zero + infinity == infinity
infinity + a == infinity
zero / zero != nan

Note the tricky law that, although nan is assigned to zero/zero, they are never-the-less not equal. A committee decided this.

Minimal complete definition

Nothing

Methods

infinity :: a Source #

nan :: a Source #

Instances

Instances details
UpperBoundedField Double Source # 
Instance details

Defined in NumHask.Algebra.Field

UpperBoundedField Float Source # 
Instance details

Defined in NumHask.Algebra.Field

(UpperBoundedField a, Subtractive a) => UpperBoundedField (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

(Ord a, Signed a, Integral a, Ring a, Distributive a) => UpperBoundedField (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

UpperBoundedField b => UpperBoundedField (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Field

Methods

infinity :: a -> b Source #

nan :: a -> b Source #

class (Field a, Multiplicative b, Additive b) => QuotientField a b where Source #

Conversion from a Field to a Ring

See Field of fractions

a - one < floor a <= a <= ceiling a < a + one
round a == floor (a + half)

Minimal complete definition

properFraction

Methods

properFraction :: a -> (b, a) Source #

round :: a -> b Source #

default round :: (Ord a, Ord b, Subtractive b, Integral b) => a -> b Source #

ceiling :: a -> b Source #

default ceiling :: Ord a => a -> b Source #

floor :: a -> b Source #

default floor :: (Ord a, Subtractive b) => a -> b Source #

truncate :: a -> b Source #

default truncate :: Ord a => a -> b Source #

Instances

Instances details
QuotientField Double Int Source # 
Instance details

Defined in NumHask.Algebra.Field

QuotientField Double Integer Source # 
Instance details

Defined in NumHask.Algebra.Field

QuotientField Float Int Source # 
Instance details

Defined in NumHask.Algebra.Field

QuotientField Float Integer Source # 
Instance details

Defined in NumHask.Algebra.Field

(Ord a, Signed a, Integral a, Ring a, Ord b, Signed b, Integral b, Ring b, Field a, FromIntegral b a) => QuotientField (Ratio a) b Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

properFraction :: Ratio a -> (b, Ratio a) Source #

round :: Ratio a -> b Source #

ceiling :: Ratio a -> b Source #

floor :: Ratio a -> b Source #

truncate :: Ratio a -> b Source #

QuotientField b c => QuotientField (a -> b) (a -> c) Source # 
Instance details

Defined in NumHask.Algebra.Field

Methods

properFraction :: (a -> b) -> (a -> c, a -> b) Source #

round :: (a -> b) -> a -> c Source #

ceiling :: (a -> b) -> a -> c Source #

floor :: (a -> b) -> a -> c Source #

truncate :: (a -> b) -> a -> c Source #

class Field a => ExpField a where Source #

A hyperbolic field class

sqrt . (**2) == id
log . exp == id
for +ive b, a != 0,1: a ** logBase a b ≈ b

Minimal complete definition

exp, log

Methods

exp :: a -> a Source #

log :: a -> a Source #

logBase :: a -> a -> a Source #

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

sqrt :: a -> a Source #

Instances

Instances details
ExpField Double Source # 
Instance details

Defined in NumHask.Algebra.Field

ExpField Float Source # 
Instance details

Defined in NumHask.Algebra.Field

(Ord a, TrigField a, ExpField a) => ExpField (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

ExpField b => ExpField (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Field

Methods

exp :: (a -> b) -> a -> b Source #

log :: (a -> b) -> a -> b Source #

logBase :: (a -> b) -> (a -> b) -> a -> b Source #

(**) :: (a -> b) -> (a -> b) -> a -> b Source #

sqrt :: (a -> b) -> a -> b Source #

class (Distributive a, Subtractive a, Divisive a) => Field a Source #

A Field is a set on which addition, subtraction, multiplication, and division are defined. It is also assumed that multiplication is distributive over addition.

A summary of the rules inherited from super-classes of Field. Floating point computation is a terrible, messy business and, in practice, only rough approximation can be achieve for association and distribution.

zero + a == a
a + zero == a
((a + b) + c) (a + (b + c))
a + b == b + a
a - a == zero
negate a == zero - a
negate a + a == zero
a + negate a == zero
one * a == a
a * one == a
((a * b) * c) == (a * (b * c))
(a * (b + c)) == (a * b + a * c)
((a + b) * c) == (a * c + b * c)
a * zero == zero
zero * a == zero
a / a == one || a == zero
recip a == one / a || a == zero
recip a * a == one || a == zero
a * recip a == one || a == zero

Instances

Instances details
Field Double Source # 
Instance details

Defined in NumHask.Algebra.Field

Field Float Source # 
Instance details

Defined in NumHask.Algebra.Field

Field a => Field (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

(Ord a, Signed a, Integral a, Ring a) => Field (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Field b => Field (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Field

half :: Field a => a Source #

A half is a Field because it requires addition, multiplication and division.

class MeetSemiLattice a => BoundedMeetSemiLattice a where Source #

A meet-semilattice with an identity element top for /\.

Identity: x /\ top == x

Methods

top :: a Source #

Instances

Instances details
BoundedMeetSemiLattice Bool Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Bool Source #

BoundedMeetSemiLattice Double Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Double Source #

BoundedMeetSemiLattice Float Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Float Source #

BoundedMeetSemiLattice Int Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Int Source #

BoundedMeetSemiLattice Int8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Int8 Source #

BoundedMeetSemiLattice Int16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Int16 Source #

BoundedMeetSemiLattice Int32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Int32 Source #

BoundedMeetSemiLattice Int64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Int64 Source #

BoundedMeetSemiLattice Word Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Word Source #

BoundedMeetSemiLattice Word8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Word8 Source #

BoundedMeetSemiLattice Word16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Word16 Source #

BoundedMeetSemiLattice Word32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Word32 Source #

BoundedMeetSemiLattice Word64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Word64 Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

top :: Complex a Source #

(Eq (a -> b), BoundedMeetSemiLattice b) => BoundedMeetSemiLattice (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: a -> b Source #

class JoinSemiLattice a => BoundedJoinSemiLattice a where Source #

A join-semilattice with an identity element bottom for \/.

Identity: x \/ bottom == x

Methods

bottom :: a Source #

Instances

Instances details
BoundedJoinSemiLattice Bool Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Bool Source #

BoundedJoinSemiLattice Double Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Double Source #

BoundedJoinSemiLattice Float Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Float Source #

BoundedJoinSemiLattice Int Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Int Source #

BoundedJoinSemiLattice Int8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Int8 Source #

BoundedJoinSemiLattice Int16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Int16 Source #

BoundedJoinSemiLattice Int32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Int32 Source #

BoundedJoinSemiLattice Int64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Int64 Source #

BoundedJoinSemiLattice Natural Source # 
Instance details

Defined in NumHask.Algebra.Lattice

BoundedJoinSemiLattice Word Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Word Source #

BoundedJoinSemiLattice Word8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Word8 Source #

BoundedJoinSemiLattice Word16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Word16 Source #

BoundedJoinSemiLattice Word32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Word32 Source #

BoundedJoinSemiLattice Word64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Word64 Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

bottom :: Complex a Source #

(Eq (a -> b), BoundedJoinSemiLattice b) => BoundedJoinSemiLattice (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: a -> b Source #

class Eq a => MeetSemiLattice a where Source #

A algebraic structure with element meets: See Semilattice

Associativity: x /\ (y /\ z) == (x /\ y) /\ z
Commutativity: x /\ y == y /\ x
Idempotency:   x /\ x == x

Methods

(/\) :: a -> a -> a infixr 6 Source #

Instances

Instances details
MeetSemiLattice Bool Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Bool -> Bool -> Bool Source #

MeetSemiLattice Double Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Float Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Int Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Int -> Int -> Int Source #

MeetSemiLattice Int8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Int8 -> Int8 -> Int8 Source #

MeetSemiLattice Int16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Int16 -> Int16 -> Int16 Source #

MeetSemiLattice Int32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Int32 -> Int32 -> Int32 Source #

MeetSemiLattice Int64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Int64 -> Int64 -> Int64 Source #

MeetSemiLattice Integer Source # 
Instance details

Defined in NumHask.Algebra.Lattice

MeetSemiLattice Natural Source # 
Instance details

Defined in NumHask.Algebra.Lattice

MeetSemiLattice Word Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Word -> Word -> Word Source #

MeetSemiLattice Word8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Word8 -> Word8 -> Word8 Source #

MeetSemiLattice Word16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Word16 -> Word16 -> Word16 Source #

MeetSemiLattice Word32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Word32 -> Word32 -> Word32 Source #

MeetSemiLattice Word64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: Word64 -> Word64 -> Word64 Source #

MeetSemiLattice a => MeetSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

(/\) :: Complex a -> Complex a -> Complex a Source #

(Ord a, Signed a) => MeetSemiLattice (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

(/\) :: Ratio a -> Ratio a -> Ratio a Source #

(Eq (a -> b), MeetSemiLattice b) => MeetSemiLattice (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(/\) :: (a -> b) -> (a -> b) -> a -> b Source #

class Eq a => JoinSemiLattice a where Source #

A algebraic structure with element joins: See Semilattice

Associativity: x \/ (y \/ z) == (x \/ y) \/ z
Commutativity: x \/ y == y \/ x
Idempotency:   x \/ x == x

Methods

(\/) :: a -> a -> a infixr 5 Source #

Instances

Instances details
JoinSemiLattice Bool Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Bool -> Bool -> Bool Source #

JoinSemiLattice Double Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Float Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Int Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Int -> Int -> Int Source #

JoinSemiLattice Int8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Int8 -> Int8 -> Int8 Source #

JoinSemiLattice Int16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Int16 -> Int16 -> Int16 Source #

JoinSemiLattice Int32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Int32 -> Int32 -> Int32 Source #

JoinSemiLattice Int64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Int64 -> Int64 -> Int64 Source #

JoinSemiLattice Integer Source # 
Instance details

Defined in NumHask.Algebra.Lattice

JoinSemiLattice Natural Source # 
Instance details

Defined in NumHask.Algebra.Lattice

JoinSemiLattice Word Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Word -> Word -> Word Source #

JoinSemiLattice Word8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Word8 -> Word8 -> Word8 Source #

JoinSemiLattice Word16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Word16 -> Word16 -> Word16 Source #

JoinSemiLattice Word32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Word32 -> Word32 -> Word32 Source #

JoinSemiLattice Word64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: Word64 -> Word64 -> Word64 Source #

JoinSemiLattice a => JoinSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

(\/) :: Complex a -> Complex a -> Complex a Source #

(Ord a, Signed a) => JoinSemiLattice (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

(\/) :: Ratio a -> Ratio a -> Ratio a Source #

(Eq (a -> b), JoinSemiLattice b) => JoinSemiLattice (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

(\/) :: (a -> b) -> (a -> b) -> a -> b Source #

joinLeq :: JoinSemiLattice a => a -> a -> Bool Source #

The partial ordering induced by the join-semilattice structure

meetLeq :: MeetSemiLattice a => a -> a -> Bool Source #

The partial ordering induced by the meet-semilattice structure

class (Distributive a, MultiplicativeAction m a) => Module m a Source #

A Module

a .* one == a
(a + b) .* c == (a .* c) + (b .* c)
c *. (a + b) == (c *. a) + (c *. b)
a .* zero == zero
a .* b == b *. a

class Divisive a => DivisiveAction m a | m -> a where Source #

Divisive Action

Methods

(./) :: a -> m -> m infixl 7 Source #

(/.) :: m -> a -> m infixl 7 Source #

class Multiplicative a => MultiplicativeAction m a | m -> a where Source #

Multiplicative Action

Methods

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

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

class Subtractive a => SubtractiveAction m a | m -> a where Source #

Subtractive Action

Methods

(.-) :: a -> m -> m infixl 6 Source #

(-.) :: m -> a -> m infixl 6 Source #

class Additive a => AdditiveAction m a | m -> a where Source #

Additive Action

Methods

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

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

class (Eq a, Additive a, Subtractive a, MeetSemiLattice a) => Epsilon a where Source #

A small number, especially useful for approximate equality.

Minimal complete definition

Nothing

Methods

epsilon :: a Source #

nearZero :: a -> Bool Source #

aboutEqual :: a -> a -> Bool Source #

Instances

Instances details
Epsilon Double Source #

1e-14

Instance details

Defined in NumHask.Algebra.Metric

Epsilon Float Source #

1e-6

Instance details

Defined in NumHask.Algebra.Metric

Epsilon Int Source #

0

Instance details

Defined in NumHask.Algebra.Metric

Epsilon Int8 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Epsilon Int16 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Epsilon Int32 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Epsilon Int64 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Epsilon Integer Source # 
Instance details

Defined in NumHask.Algebra.Metric

Epsilon Word Source # 
Instance details

Defined in NumHask.Algebra.Metric

Epsilon Word8 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Epsilon Word16 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Epsilon Word32 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Epsilon Word64 Source # 
Instance details

Defined in NumHask.Algebra.Metric

(Ord a, Signed a, Subtractive a, Epsilon a) => Epsilon (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

(Ord a, Signed a, Integral a, Ring a, MeetSemiLattice a) => Epsilon (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

data Polar mag dir Source #

Something that has a magnitude and a direction.

Constructors

Polar 

Fields

Instances

Instances details
(Eq mag, Eq dir) => Eq (Polar mag dir) Source # 
Instance details

Defined in NumHask.Algebra.Metric

Methods

(==) :: Polar mag dir -> Polar mag dir -> Bool #

(/=) :: Polar mag dir -> Polar mag dir -> Bool #

(Show mag, Show dir) => Show (Polar mag dir) Source # 
Instance details

Defined in NumHask.Algebra.Metric

Methods

showsPrec :: Int -> Polar mag dir -> ShowS #

show :: Polar mag dir -> String #

showList :: [Polar mag dir] -> ShowS #

Generic (Polar mag dir) Source # 
Instance details

Defined in NumHask.Algebra.Metric

Associated Types

type Rep (Polar mag dir) :: Type -> Type #

Methods

from :: Polar mag dir -> Rep (Polar mag dir) x #

to :: Rep (Polar mag dir) x -> Polar mag dir #

type Rep (Polar mag dir) Source # 
Instance details

Defined in NumHask.Algebra.Metric

type Rep (Polar mag dir) = D1 ('MetaData "Polar" "NumHask.Algebra.Metric" "numhask-0.8.1.0-6vtGETGPv6z5KBqA0pprnK" 'False) (C1 ('MetaCons "Polar" 'PrefixI 'True) (S1 ('MetaSel ('Just "magnitude") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 mag) :*: S1 ('MetaSel ('Just "direction") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 dir)))

class (Additive coord, Multiplicative coord, Additive dir, Multiplicative dir) => Direction coord dir | coord -> dir where Source #

Convert between a "co-ordinated" or "higher-kinded" number and representations of an angle. Typically thought of as polar co-ordinate conversion.

See Polar coordinate system

ray . angle == basis
norm (ray x) == one

Methods

angle :: coord -> dir Source #

ray :: dir -> coord Source #

Instances

Instances details
TrigField a => Direction (Complex a) a Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

angle :: Complex a -> a Source #

ray :: a -> Complex a Source #

class (Additive a, Multiplicative b, Additive b) => Norm a b | a -> b where Source #

Norm is a slight generalisation of Signed. The class has the same shape but allows the codomain to be different to the domain.

norm a >= zero
norm zero == zero
a == norm a .* basis a
norm (basis a) == one

Methods

norm :: a -> b Source #

or length, or ||v||

basis :: a -> a Source #

or direction, or v-hat

Instances

Instances details
Norm Double Double Source # 
Instance details

Defined in NumHask.Algebra.Metric

Norm Float Float Source # 
Instance details

Defined in NumHask.Algebra.Metric

Norm Int Int Source # 
Instance details

Defined in NumHask.Algebra.Metric

Methods

norm :: Int -> Int Source #

basis :: Int -> Int Source #

Norm Int8 Int8 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Methods

norm :: Int8 -> Int8 Source #

basis :: Int8 -> Int8 Source #

Norm Int16 Int16 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Norm Int32 Int32 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Norm Int64 Int64 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Norm Integer Integer Source # 
Instance details

Defined in NumHask.Algebra.Metric

Norm Natural Natural Source # 
Instance details

Defined in NumHask.Algebra.Metric

Norm Word Word Source # 
Instance details

Defined in NumHask.Algebra.Metric

Methods

norm :: Word -> Word Source #

basis :: Word -> Word Source #

Norm Word8 Word8 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Norm Word16 Word16 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Norm Word32 Word32 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Norm Word64 Word64 Source # 
Instance details

Defined in NumHask.Algebra.Metric

ExpField a => Norm (Complex a) a Source #

A euclidean-style norm is strong convention for Complex.

Instance details

Defined in NumHask.Data.Complex

Methods

norm :: Complex a -> a Source #

basis :: Complex a -> Complex a Source #

(Ord a, Signed a, Integral a, Ring a) => Norm (Ratio a) (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

norm :: Ratio a -> Ratio a Source #

basis :: Ratio a -> Ratio a Source #

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

signum from base is not an operator name in numhask and is replaced by sign. Compare with Norm where there is a change in codomain.

abs a * sign a == a

abs zero == zero, so any value for sign zero is ok. We choose lawful neutral:

sign zero == zero

Methods

sign :: a -> a Source #

abs :: a -> a Source #

Instances

Instances details
Signed Double Source # 
Instance details

Defined in NumHask.Algebra.Metric

Signed Float Source # 
Instance details

Defined in NumHask.Algebra.Metric

Signed Int Source # 
Instance details

Defined in NumHask.Algebra.Metric

Methods

sign :: Int -> Int Source #

abs :: Int -> Int Source #

Signed Int8 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Methods

sign :: Int8 -> Int8 Source #

abs :: Int8 -> Int8 Source #

Signed Int16 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Signed Int32 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Signed Int64 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Signed Integer Source # 
Instance details

Defined in NumHask.Algebra.Metric

Signed Natural Source # 
Instance details

Defined in NumHask.Algebra.Metric

Signed Word Source # 
Instance details

Defined in NumHask.Algebra.Metric

Methods

sign :: Word -> Word Source #

abs :: Word -> Word Source #

Signed Word8 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Signed Word16 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Signed Word32 Source # 
Instance details

Defined in NumHask.Algebra.Metric

Signed Word64 Source # 
Instance details

Defined in NumHask.Algebra.Metric

(Ord a, Signed a, Integral a, Ring a) => Signed (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

sign :: Ratio a -> Ratio a Source #

abs :: Ratio a -> Ratio a Source #

distance :: (Norm a b, Subtractive a) => a -> a -> b Source #

Distance, which combines the Subtractive notion of difference, with Norm.

distance a b >= zero
distance a a == zero
distance a b .* basis (a - b) == a - b

polar :: (Norm coord mag, Direction coord dir) => coord -> Polar mag dir Source #

Convert from a number to a Polar.

coord :: (MultiplicativeAction coord mag, Direction coord dir) => Polar mag dir -> coord Source #

Convert from a Polar to a (coordinated aka higher-kinded) number.

(~=) :: Epsilon a => a -> a -> Bool infixl 4 Source #

About equal.

class (Associative a, Unital a, Invertible a, Commutative a) => AbelianGroup a Source #

An Abelian Group is an Associative, Unital, Invertible and Commutative Magma . In other words, it is a Commutative Group

Instances

Instances details
(Associative a, Unital a, Invertible a, Commutative a) => AbelianGroup a Source # 
Instance details

Defined in NumHask.Algebra.Group

class Magma a => Idempotent a Source #

An Idempotent Magma is a magma where every element is Idempotent.

a ⊕ a = a

Instances

Instances details
Idempotent b => Idempotent (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Group

class Magma a => Absorbing a where Source #

An Absorbing is a Magma with an Absorbing Element

a ⊕ absorb = absorb

Methods

absorb :: a Source #

Instances

Instances details
Absorbing b => Absorbing (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Group

Methods

absorb :: a -> b Source #

class (Associative a, Unital a, Invertible a) => Group a Source #

A Group is a Associative, Unital and Invertible Magma.

Instances

Instances details
(Associative a, Unital a, Invertible a) => Group a Source # 
Instance details

Defined in NumHask.Algebra.Group

class Magma a => Invertible a where Source #

An Invertible Magma

∀ a,b ∈ T: inv a ⊕ (a ⊕ b) = b = (b ⊕ a) ⊕ inv a

Methods

inv :: a -> a Source #

Instances

Instances details
Invertible b => Invertible (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Group

Methods

inv :: (a -> b) -> a -> b Source #

class Magma a => Commutative a Source #

A Commutative Magma is a Magma where the binary operation is commutative.

a ⊕ b = b ⊕ a

Instances

Instances details
Commutative b => Commutative (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Group

class Magma a => Associative a Source #

An Associative Magma

(a ⊕ b) ⊕ c = a ⊕ (b ⊕ c)

Instances

Instances details
Associative b => Associative (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Group

class Magma a => Unital a where Source #

A Unital Magma is a magma with an identity element (the unit).

unit ⊕ a = a
a ⊕ unit = a

Methods

unit :: a Source #

Instances

Instances details
Unital b => Unital (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Group

Methods

unit :: a -> b Source #

class Magma a where Source #

A Magma is a tuple (T,magma) consisting of

  • a type a, and
  • a function (magma) :: T -> T -> T

The mathematical laws for a magma are:

  • magma is defined for all possible pairs of type T, and
  • magma is closed in the set of all possible values of type T

or, more tersly,

∀ a, b ∈ T: a ⊕ b ∈ T

These laws are true by construction in haskell: the type signature of and the above mathematical laws are synonyms.

Methods

(⊕) :: a -> a -> a infix 3 Source #

Instances

Instances details
Magma b => Magma (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Group

Methods

(⊕) :: (a -> b) -> (a -> b) -> a -> b Source #

data Complex a Source #

Complex numbers have real and imaginary parts.

The Foldable and Traversable instances traverse the real part first.

Constructors

!a :+ !a infix 6

forms a complex number from its real and imaginary rectangular components.

Instances

Instances details
Functor Complex Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

fmap :: (a -> b) -> Complex a -> Complex b #

(<$) :: a -> Complex b -> Complex a #

Foldable Complex Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

fold :: Monoid m => Complex m -> m #

foldMap :: Monoid m => (a -> m) -> Complex a -> m #

foldMap' :: Monoid m => (a -> m) -> Complex a -> m #

foldr :: (a -> b -> b) -> b -> Complex a -> b #

foldr' :: (a -> b -> b) -> b -> Complex a -> b #

foldl :: (b -> a -> b) -> b -> Complex a -> b #

foldl' :: (b -> a -> b) -> b -> Complex a -> b #

foldr1 :: (a -> a -> a) -> Complex a -> a #

foldl1 :: (a -> a -> a) -> Complex a -> a #

toList :: Complex a -> [a] #

null :: Complex a -> Bool #

length :: Complex a -> Int #

elem :: Eq a => a -> Complex a -> Bool #

maximum :: Ord a => Complex a -> a #

minimum :: Ord a => Complex a -> a #

sum :: Num a => Complex a -> a #

product :: Num a => Complex a -> a #

Traversable Complex Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

traverse :: Applicative f => (a -> f b) -> Complex a -> f (Complex b) #

sequenceA :: Applicative f => Complex (f a) -> f (Complex a) #

mapM :: Monad m => (a -> m b) -> Complex a -> m (Complex b) #

sequence :: Monad m => Complex (m a) -> m (Complex a) #

Eq a => Eq (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

(==) :: Complex a -> Complex a -> Bool #

(/=) :: Complex a -> Complex a -> Bool #

Data a => Data (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Complex a -> c (Complex a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Complex a) #

toConstr :: Complex a -> Constr #

dataTypeOf :: Complex a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Complex a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Complex a)) #

gmapT :: (forall b. Data b => b -> b) -> Complex a -> Complex a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Complex a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Complex a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Complex a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Complex a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) #

Read a => Read (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Show a => Show (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

showsPrec :: Int -> Complex a -> ShowS #

show :: Complex a -> String #

showList :: [Complex a] -> ShowS #

Generic (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Associated Types

type Rep (Complex a) :: Type -> Type #

Methods

from :: Complex a -> Rep (Complex a) x #

to :: Rep (Complex a) x -> Complex a #

Subtractive a => Subtractive (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

negate :: Complex a -> Complex a Source #

(-) :: Complex a -> Complex a -> Complex a Source #

Additive a => Additive (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

(+) :: Complex a -> Complex a -> Complex a Source #

zero :: Complex a Source #

(Subtractive a, Divisive a) => Divisive (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

recip :: Complex a -> Complex a Source #

(/) :: Complex a -> Complex a -> Complex a Source #

(Subtractive a, Multiplicative a) => Multiplicative (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

(*) :: Complex a -> Complex a -> Complex a Source #

one :: Complex a Source #

(Distributive a, Subtractive a) => InvolutiveRing (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

adj :: Complex a -> Complex a Source #

(Distributive a, Subtractive a) => Distributive (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

LowerBoundedField a => LowerBoundedField (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

(UpperBoundedField a, Subtractive a) => UpperBoundedField (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

(Ord a, TrigField a, ExpField a) => ExpField (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Field a => Field (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

top :: Complex a Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

bottom :: Complex a Source #

MeetSemiLattice a => MeetSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

(/\) :: Complex a -> Complex a -> Complex a Source #

JoinSemiLattice a => JoinSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

(\/) :: Complex a -> Complex a -> Complex a Source #

(Ord a, Signed a, Subtractive a, Epsilon a) => Epsilon (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Generic1 Complex Source # 
Instance details

Defined in NumHask.Data.Complex

Associated Types

type Rep1 Complex :: k -> Type #

Methods

from1 :: forall (a :: k). Complex a -> Rep1 Complex a #

to1 :: forall (a :: k). Rep1 Complex a -> Complex a #

(Additive a, FromIntegral a b) => FromIntegral (Complex a) b Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

fromIntegral :: b -> Complex a Source #

TrigField a => Direction (Complex a) a Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

angle :: Complex a -> a Source #

ray :: a -> Complex a Source #

ExpField a => Norm (Complex a) a Source #

A euclidean-style norm is strong convention for Complex.

Instance details

Defined in NumHask.Data.Complex

Methods

norm :: Complex a -> a Source #

basis :: Complex a -> Complex a Source #

type Rep (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

type Rep (Complex a) = D1 ('MetaData "Complex" "NumHask.Data.Complex" "numhask-0.8.1.0-6vtGETGPv6z5KBqA0pprnK" 'False) (C1 ('MetaCons ":+" ('InfixI 'NotAssociative 6) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))
type Rep1 Complex Source # 
Instance details

Defined in NumHask.Data.Complex

type Rep1 Complex = D1 ('MetaData "Complex" "NumHask.Data.Complex" "numhask-0.8.1.0-6vtGETGPv6z5KBqA0pprnK" 'False) (C1 ('MetaCons ":+" ('InfixI 'NotAssociative 6) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))

realPart :: Complex a -> a Source #

Extracts the real part of a complex number.

imagPart :: Complex a -> a Source #

Extracts the imaginary part of a complex number.

class FromInteger a where Source #

fromInteger is special in two ways:

  • numeric integral literals (like "42") are interpreted specifically as "fromInteger (42 :: GHC.Num.Integer)". The prelude version is used as default (or whatever fromInteger is in scope if RebindableSyntax is set).
  • The default rules in haskell2010 specify that constraints on fromInteger need to be in a form C v, where v is a Num or a subclass of Num.

So a type synonym of `type FromInteger a = FromIntegral a Integer` doesn't work well with type defaulting; hence the need for a separate class.

Methods

fromInteger :: Integer -> a Source #

Instances

Instances details
FromInteger Double Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Float Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Int8 Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Int16 Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Int32 Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Int64 Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Natural Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Word Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Word8 Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Word16 Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Word32 Source # 
Instance details

Defined in NumHask.Data.Integral

FromInteger Word64 Source # 
Instance details

Defined in NumHask.Data.Integral

class FromIntegral a b where Source #

Polymorphic version of fromInteger

fromIntegral a == a

Minimal complete definition

fromIntegral

Methods

fromIntegral :: b -> a Source #

default fromIntegral :: a ~ b => b -> a Source #

Instances

Instances details
FromIntegral Double Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Double Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Float Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Float Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int Int Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

fromIntegral :: Int -> Int Source #

FromIntegral Int Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int8 Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int8 Int8 Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int8 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int16 Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int16 Int16 Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int16 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int32 Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int32 Int32 Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int32 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int64 Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int64 Int64 Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Int64 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Integer Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Integer Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Natural Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Natural Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Natural Natural Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word Word Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word8 Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word8 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word8 Word8 Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word16 Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word16 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word16 Word16 Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word32 Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word32 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word32 Word32 Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word64 Int Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word64 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

FromIntegral Word64 Word64 Source # 
Instance details

Defined in NumHask.Data.Integral

(Additive a, FromIntegral a b) => FromIntegral (Complex a) b Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

fromIntegral :: b -> Complex a Source #

(FromIntegral a b, Multiplicative a) => FromIntegral (Ratio a) b Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

fromIntegral :: b -> Ratio a Source #

FromIntegral a b => FromIntegral (c -> a) b Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

fromIntegral :: b -> c -> a Source #

class ToIntegral a b where Source #

toIntegral is kept separate from Integral to help with compatability issues.

toIntegral a == a

Minimal complete definition

toIntegral

Methods

toIntegral :: a -> b Source #

default toIntegral :: a ~ b => a -> b Source #

Instances

Instances details
ToIntegral Int Int Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

toIntegral :: Int -> Int Source #

ToIntegral Int Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Int8 Int Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

toIntegral :: Int8 -> Int Source #

ToIntegral Int8 Int8 Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

toIntegral :: Int8 -> Int8 Source #

ToIntegral Int8 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Int16 Int Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

toIntegral :: Int16 -> Int Source #

ToIntegral Int16 Int16 Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Int16 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Int32 Int Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

toIntegral :: Int32 -> Int Source #

ToIntegral Int32 Int32 Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Int32 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Int64 Int Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

toIntegral :: Int64 -> Int Source #

ToIntegral Int64 Int64 Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Int64 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Integer Int Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Integer Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Natural Int Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Natural Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Natural Natural Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word Int Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

toIntegral :: Word -> Int Source #

ToIntegral Word Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word Word Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

toIntegral :: Word -> Word Source #

ToIntegral Word8 Int Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

toIntegral :: Word8 -> Int Source #

ToIntegral Word8 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word8 Word8 Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word16 Int Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word16 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word16 Word16 Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word32 Int Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word32 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word32 Word32 Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word64 Int Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word64 Integer Source # 
Instance details

Defined in NumHask.Data.Integral

ToIntegral Word64 Word64 Source # 
Instance details

Defined in NumHask.Data.Integral

class Distributive a => Integral a where Source #

An Integral is anything that satisfies the law:

b == zero || b * (a `div` b) + (a `mod` b) == a

Minimal complete definition

divMod, quotRem

Methods

div :: a -> a -> a infixl 7 Source #

mod :: a -> a -> a infixl 7 Source #

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

quot :: a -> a -> a Source #

rem :: a -> a -> a Source #

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

Instances

Instances details
Integral Int Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

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

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

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

quot :: Int -> Int -> Int Source #

rem :: Int -> Int -> Int Source #

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

Integral Int8 Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

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

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

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

quot :: Int8 -> Int8 -> Int8 Source #

rem :: Int8 -> Int8 -> Int8 Source #

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

Integral Int16 Source # 
Instance details

Defined in NumHask.Data.Integral

Integral Int32 Source # 
Instance details

Defined in NumHask.Data.Integral

Integral Int64 Source # 
Instance details

Defined in NumHask.Data.Integral

Integral Integer Source # 
Instance details

Defined in NumHask.Data.Integral

Integral Natural Source # 
Instance details

Defined in NumHask.Data.Integral

Integral Word Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

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

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

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

quot :: Word -> Word -> Word Source #

rem :: Word -> Word -> Word Source #

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

Integral Word8 Source # 
Instance details

Defined in NumHask.Data.Integral

Integral Word16 Source # 
Instance details

Defined in NumHask.Data.Integral

Integral Word32 Source # 
Instance details

Defined in NumHask.Data.Integral

Integral Word64 Source # 
Instance details

Defined in NumHask.Data.Integral

Integral b => Integral (a -> b) Source # 
Instance details

Defined in NumHask.Data.Integral

Methods

div :: (a -> b) -> (a -> b) -> a -> b Source #

mod :: (a -> b) -> (a -> b) -> a -> b Source #

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

quot :: (a -> b) -> (a -> b) -> a -> b Source #

rem :: (a -> b) -> (a -> b) -> a -> b Source #

quotRem :: (a -> b) -> (a -> b) -> (a -> b, a -> b) Source #

even :: (Eq a, Integral a) => a -> Bool Source #

>>> even 2
True

odd :: (Eq a, Integral a) => a -> Bool Source #

>>> odd 3
True

(^^) :: (Ord b, Divisive a, Subtractive b, Integral b) => a -> b -> a infixr 8 Source #

raise a number to an Integral power

(^) :: Divisive a => a -> Int -> a infixr 8 Source #

raise a number to an Int power

Note: This differs from (^) found in prelude which is a partial function (it errors on negative integrals). This monomorphic version is provided to help reduce ambiguous type noise in common usages of this sign.

type Rational = Ratio Integer #

Arbitrary-precision rational numbers, represented as a ratio of two Integer values. A rational number may be constructed using the % operator.

class FromRational a where Source #

fromRational is special in two ways:

  • numeric decimal literals (like "53.66") are interpreted as exactly "fromRational (53.66 :: GHC.Real.Ratio Integer)". The prelude version, GHC.Real.fromRational is used as default (or whatever is in scope if RebindableSyntax is set).
  • The default rules in haskell2010 specify that contraints on fromRational need to be in a form C v, where v is a Num or a subclass of Num.

So a type synonym of `type FromRational a = FromRatio a Integer` doesn't work well with type defaulting; hence the need for a separate class.

Methods

fromRational :: Rational -> a Source #

Instances

Instances details
FromRational Double Source # 
Instance details

Defined in NumHask.Data.Rational

FromRational Float Source # 
Instance details

Defined in NumHask.Data.Rational

FromRational (Ratio Integer) Source # 
Instance details

Defined in NumHask.Data.Rational

class FromRatio a b where Source #

Fractional in base splits into fromRatio and Field

>>> fromRatio (5 :% 2 :: Ratio Integer) :: Double
2.5

Minimal complete definition

Nothing

Methods

fromRatio :: Ratio b -> a Source #

default fromRatio :: Ratio b ~ a => Ratio b -> a Source #

Instances

Instances details
FromRatio Double Integer Source # 
Instance details

Defined in NumHask.Data.Rational

FromRatio Float Integer Source # 
Instance details

Defined in NumHask.Data.Rational

FromRatio Rational Integer Source # 
Instance details

Defined in NumHask.Data.Rational

class ToRatio a b where Source #

toRatio is equivalent to Real in base, but is polymorphic in the Integral type.

toRatio (3.1415927 :: Float) :: Ratio Integer

13176795 :% 4194304

Minimal complete definition

Nothing

Methods

toRatio :: a -> Ratio b Source #

default toRatio :: (Ratio c ~ a, FromIntegral b c, ToRatio (Ratio b) b) => a -> Ratio b Source #

Instances

Instances details
ToRatio Double Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Float Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int8 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int16 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int32 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int64 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Integer Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Natural Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Rational Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word8 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word16 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word32 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word64 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio (Ratio Integer) Integer Source # 
Instance details

Defined in NumHask.Data.Rational

data Ratio a Source #

A rational number

Constructors

!a :% !a 

Instances

Instances details
(Eq a, Additive a) => Eq (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

(==) :: Ratio a -> Ratio a -> Bool #

(/=) :: Ratio a -> Ratio a -> Bool #

(Ord a, Multiplicative a, Additive a) => Ord (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

compare :: Ratio a -> Ratio a -> Ordering #

(<) :: Ratio a -> Ratio a -> Bool #

(<=) :: Ratio a -> Ratio a -> Bool #

(>) :: Ratio a -> Ratio a -> Bool #

(>=) :: Ratio a -> Ratio a -> Bool #

max :: Ratio a -> Ratio a -> Ratio a #

min :: Ratio a -> Ratio a -> Ratio a #

Show a => Show (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

showsPrec :: Int -> Ratio a -> ShowS #

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

(Ord a, Signed a, Integral a, Ring a) => Subtractive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

negate :: Ratio a -> Ratio a Source #

(-) :: Ratio a -> Ratio a -> Ratio a Source #

(Ord a, Signed a, Integral a, Ring a) => Additive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

(+) :: Ratio a -> Ratio a -> Ratio a Source #

zero :: Ratio a Source #

(Ord a, Signed a, Integral a, Ring a) => Divisive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

recip :: Ratio a -> Ratio a Source #

(/) :: Ratio a -> Ratio a -> Ratio a Source #

(Ord a, Signed a, Integral a, Ring a, Multiplicative a) => Multiplicative (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

(*) :: Ratio a -> Ratio a -> Ratio a Source #

one :: Ratio a Source #

(Ord a, Signed a, Integral a, Ring a) => Distributive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

(Ord a, Signed a, Integral a, Field a) => LowerBoundedField (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

(Ord a, Signed a, Integral a, Ring a, Distributive a) => UpperBoundedField (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

(Ord a, Signed a, Integral a, Ring a) => Field (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

(Ord a, Signed a) => MeetSemiLattice (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

(/\) :: Ratio a -> Ratio a -> Ratio a Source #

(Ord a, Signed a) => JoinSemiLattice (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

(\/) :: Ratio a -> Ratio a -> Ratio a Source #

(Ord a, Signed a, Integral a, Ring a, MeetSemiLattice a) => Epsilon (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

(Ord a, Signed a, Integral a, Ring a) => Signed (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

sign :: Ratio a -> Ratio a Source #

abs :: Ratio a -> Ratio a Source #

FromRational (Ratio Integer) Source # 
Instance details

Defined in NumHask.Data.Rational

(FromIntegral a b, Multiplicative a) => FromIntegral (Ratio a) b Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

fromIntegral :: b -> Ratio a Source #

(Ord a, Signed a, Integral a, Ring a, Ord b, Signed b, Integral b, Ring b, Field a, FromIntegral b a) => QuotientField (Ratio a) b Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

properFraction :: Ratio a -> (b, Ratio a) Source #

round :: Ratio a -> b Source #

ceiling :: Ratio a -> b Source #

floor :: Ratio a -> b Source #

truncate :: Ratio a -> b Source #

ToRatio (Ratio Integer) Integer Source # 
Instance details

Defined in NumHask.Data.Rational

(Ord a, Signed a, Integral a, Ring a) => Norm (Ratio a) (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

norm :: Ratio a -> Ratio a Source #

basis :: Ratio a -> Ratio a Source #

reduce :: (Eq a, Subtractive a, Signed a, Integral a) => a -> a -> Ratio a Source #

reduce normalises a ratio by dividing both numerator and denominator by their greatest common divisor.

gcd :: (Eq a, Signed a, Integral a) => a -> a -> a Source #

gcd x y is the non-negative factor of both x and y of which every common factor of x and y is also a factor; for example gcd 4 2 = 2, gcd (-4) 6 = 2, gcd 0 4 = 4. gcd 0 0 = 0. (That is, the common divisor that is "greatest" in the divisibility preordering.)

Note: Since for signed fixed-width integer types, abs minBound < 0, the result may be negative if one of the arguments is minBound (and necessarily is if the other is 0 or minBound) for such types.

throw :: forall (r :: RuntimeRep) (a :: TYPE r) e. Exception e => e -> a #

Throw an exception. Exceptions may be thrown from purely functional code, but may only be caught within the IO monad.