numeric-prelude-0.4.4: An experimental alternative hierarchy of numeric type classes
Copyright(c) Henning Thielemann 2007-2012
Maintainernumericprelude@henning-thielemann.de
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Number.Peano

Description

Lazy Peano numbers represent natural numbers inclusive infinity. Since they are lazily evaluated, they are optimally for use as number type of genericLength et.al.

Synopsis

Documentation

data T Source #

Constructors

Zero 
Succ T 

Instances

Instances details
Bounded T Source # 
Instance details

Defined in Number.Peano

Methods

minBound :: T #

maxBound :: T #

Enum T Source # 
Instance details

Defined in Number.Peano

Methods

succ :: T -> T #

pred :: T -> T #

toEnum :: Int -> T #

fromEnum :: T -> Int #

enumFrom :: T -> [T] #

enumFromThen :: T -> T -> [T] #

enumFromTo :: T -> T -> [T] #

enumFromThenTo :: T -> T -> T -> [T] #

Eq T Source # 
Instance details

Defined in Number.Peano

Methods

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

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

Integral T Source # 
Instance details

Defined in Number.Peano

Methods

quot :: T -> T -> T #

rem :: T -> T -> T #

div :: T -> T -> T #

mod :: T -> T -> T #

quotRem :: T -> T -> (T, T) #

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

toInteger :: T -> Integer #

Num T Source # 
Instance details

Defined in Number.Peano

Methods

(+) :: T -> T -> T #

(-) :: T -> T -> T #

(*) :: T -> T -> T #

negate :: T -> T #

abs :: T -> T #

signum :: T -> T #

fromInteger :: Integer -> T #

Ord T Source # 
Instance details

Defined in Number.Peano

Methods

compare :: T -> T -> Ordering #

(<) :: T -> T -> Bool #

(<=) :: T -> T -> Bool #

(>) :: T -> T -> Bool #

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

max :: T -> T -> T #

min :: T -> T -> T #

Read T Source # 
Instance details

Defined in Number.Peano

Real T Source # 
Instance details

Defined in Number.Peano

Methods

toRational :: T -> Rational #

Show T Source # 
Instance details

Defined in Number.Peano

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

Ix T Source # 
Instance details

Defined in Number.Peano

Methods

range :: (T, T) -> [T] #

index :: (T, T) -> T -> Int #

unsafeIndex :: (T, T) -> T -> Int #

inRange :: (T, T) -> T -> Bool #

rangeSize :: (T, T) -> Int #

unsafeRangeSize :: (T, T) -> Int #

C T Source # 
Instance details

Defined in Number.Peano

Methods

compare :: T -> T -> Ordering Source #

C T Source # 
Instance details

Defined in Number.Peano

Methods

zero :: T Source #

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

(-) :: T -> T -> T Source #

negate :: T -> T Source #

C T Source # 
Instance details

Defined in Number.Peano

Methods

isZero :: T -> Bool Source #

C T Source # 
Instance details

Defined in Number.Peano

Methods

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

one :: T Source #

fromInteger :: Integer -> T Source #

(^) :: T -> Integer -> T Source #

C T Source # 
Instance details

Defined in Number.Peano

Methods

idt :: T Source #

(<*>) :: T -> T -> T Source #

cumulate :: [T] -> T Source #

C T Source # 
Instance details

Defined in Number.Peano

Methods

split :: T -> T -> (T, (Bool, T)) Source #

C T Source # 
Instance details

Defined in Number.Peano

Methods

div :: T -> T -> T Source #

mod :: T -> T -> T Source #

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

C T Source # 
Instance details

Defined in Number.Peano

C T Source # 
Instance details

Defined in Number.Peano

Methods

extendedGCD :: T -> T -> (T, (T, T)) Source #

gcd :: T -> T -> T Source #

lcm :: T -> T -> T Source #

C T Source # 
Instance details

Defined in Number.Peano

Methods

abs :: T -> T Source #

signum :: T -> T Source #

C T Source # 
Instance details

Defined in Number.Peano

C T Source # 
Instance details

Defined in Number.Peano

Methods

quot :: T -> T -> T Source #

rem :: T -> T -> T Source #

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

C T Source # 
Instance details

Defined in Number.Peano

Methods

toInteger :: T -> Integer Source #

err :: String -> String -> a Source #

add :: T -> T -> T Source #

sub :: T -> T -> T Source #

subNeg :: T -> T -> (Bool, T) Source #

mul :: T -> T -> T Source #

fromPosEnum :: (C a, Enum a) => a -> T Source #

toPosEnum :: (C a, Enum a) => T -> a Source #

ifLazy :: Bool -> T -> T -> T Source #

If all values are completely defined, then it holds

if b then x else y == ifLazy b x y

However if b is undefined, then it is at least known that the result is larger than min x y.

argMinFull :: (T, a) -> (T, a) -> (T, a) Source #

cf. To how to find the shortest list in a list of lists efficiently, this means, also in the presence of infinite lists. http://www.haskell.org/pipermail/haskell-cafe/2006-October/018753.html

argMin :: (T, a) -> (T, a) -> a Source #

On equality the first operand is returned.

argMinimum :: [(T, a)] -> a Source #

argMaxFull :: (T, a) -> (T, a) -> (T, a) Source #

argMax :: (T, a) -> (T, a) -> a Source #

On equality the first operand is returned.

argMaximum :: [(T, a)] -> a Source #

isAscendingFiniteList :: [T] -> Bool Source #

x0 <= x1 && x1 <= x2 ... for possibly infinite numbers in finite lists.

toListMaybe :: a -> T -> [Maybe a] Source #

glue :: T -> T -> (T, (Bool, T)) Source #

In glue x y == (z,(b,r)) z represents min x y, r represents max x y - min x y, and x<=y == b.

Cf. Numeric.NonNegative.Chunky

data Valuable a Source #

Constructors

Valuable 

Fields

Instances

Instances details
Eq a => Eq (Valuable a) Source # 
Instance details

Defined in Number.Peano

Methods

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

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

Ord a => Ord (Valuable a) Source # 
Instance details

Defined in Number.Peano

Methods

compare :: Valuable a -> Valuable a -> Ordering #

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

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

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

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

max :: Valuable a -> Valuable a -> Valuable a #

min :: Valuable a -> Valuable a -> Valuable a #

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

Defined in Number.Peano

Methods

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

show :: Valuable a -> String #

showList :: [Valuable a] -> ShowS #

(&&~) :: Valuable Bool -> Valuable Bool -> Valuable Bool infixr 3 Source #

Compute (&&) with minimal costs.