numeric-prelude-0.1.1: An experimental alternative hierarchy of numeric type classesSource codeContentsIndex
Number.Peano
Portabilityportable
Stabilityprovisional
Maintainernumericprelude@henning-thielemann.de
Description
Lazy Peano numbers represent natural numbers inclusive infinity. Since they are lazily evaluated, they are optimally for use as number type of Data.List.genericLength et.al.
Synopsis
data T
= Zero
| Succ T
infinity :: T
err :: String -> String -> a
add :: T -> T -> T
sub :: T -> T -> T
subNeg :: T -> T -> (Bool, T)
mul :: T -> T -> T
fromPosEnum :: (C a, Enum a) => a -> T
toPosEnum :: (C a, Enum a) => T -> a
argMinFull :: (T, a) -> (T, a) -> (T, a)
argMin :: (T, a) -> (T, a) -> a
argMinimum :: [(T, a)] -> a
argMaxFull :: (T, a) -> (T, a) -> (T, a)
argMax :: (T, a) -> (T, a) -> a
argMaximum :: [(T, a)] -> a
isAscendingFiniteList :: [T] -> Bool
isAscendingFiniteNumbers :: [T] -> Bool
toListMaybe :: a -> T -> [Maybe a]
glue :: T -> T -> (T, T, Bool)
isAscending :: [T] -> Bool
data Valuable a = Valuable {
costs :: T
value :: a
}
increaseCosts :: T -> Valuable a -> Valuable a
(&&~) :: Valuable Bool -> Valuable Bool -> Valuable Bool
andW :: [Valuable Bool] -> Valuable Bool
leW :: T -> T -> Valuable Bool
isAscendingW :: [T] -> Valuable Bool
legacyInstance :: a
Documentation
data T Source
Constructors
Zero
Succ T
show/hide Instances
infinity :: TSource
err :: String -> String -> aSource
add :: T -> T -> TSource
sub :: T -> T -> TSource
subNeg :: T -> T -> (Bool, T)Source
mul :: T -> T -> TSource
fromPosEnum :: (C a, Enum a) => a -> TSource
toPosEnum :: (C a, Enum a) => T -> aSource
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) -> aSource
On equality the first operand is returned.
argMinimum :: [(T, a)] -> aSource
argMaxFull :: (T, a) -> (T, a) -> (T, a)Source
argMax :: (T, a) -> (T, a) -> aSource
On equality the first operand is returned.
argMaximum :: [(T, a)] -> aSource
isAscendingFiniteList :: [T] -> BoolSource
x0 <= x1 && x1 <= x2 ... for possibly infinite numbers in finite lists.
isAscendingFiniteNumbers :: [T] -> BoolSource
toListMaybe :: a -> T -> [Maybe a]Source
glue :: T -> T -> (T, T, Bool)Source

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

Cf. Numeric.NonNegative.Chunky

isAscending :: [T] -> BoolSource
data Valuable a Source
Constructors
Valuable
costs :: T
value :: a
show/hide Instances
Eq a => Eq (Valuable a)
Ord a => Ord (Valuable a)
Show a => Show (Valuable a)
increaseCosts :: T -> Valuable a -> Valuable aSource
(&&~) :: Valuable Bool -> Valuable Bool -> Valuable BoolSource
Compute '(&&)' with minimal costs.
andW :: [Valuable Bool] -> Valuable BoolSource
leW :: T -> T -> Valuable BoolSource
isAscendingW :: [T] -> Valuable BoolSource
legacyInstance :: aSource
Produced by Haddock version 2.4.2