numeric-prelude-0.4.3.2: An experimental alternative hierarchy of numeric type classes

Copyright(c) Henning Thielemann 2007-2010
Maintainerhaskell@henning-thielemann.de
Stabilitystable
PortabilityHaskell 98
Safe HaskellNone
LanguageHaskell98

Number.NonNegativeChunky

Description

A lazy number type, which is a generalization of lazy Peano numbers. Comparisons can be made lazy and thus computations are possible which are impossible with strict number types, e.g. you can compute let y = min (1+y) 2 in y. You can even work with infinite values. However, depending on the granularity, the memory consumption is higher than that for strict number types. This number type is of interest for the merge operation of event lists, which allows for co-recursive merges.

Synopsis

Documentation

data T a Source #

A chunky non-negative number is a list of non-negative numbers. It represents the sum of the list elements. It is possible to represent a finite number with infinitely many chunks by using an infinite number of zeros.

Note the following problems:

Addition is commutative only for finite representations. E.g. let y = min (1+y) 2 in y is defined, let y = min (y+1) 2 in y is not.

The type is equivalent to Chunky.

Instances
C a => Eq (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

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

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

(C a, Fractional a) => Fractional (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

(/) :: T a -> T a -> T a #

recip :: T a -> T a #

fromRational :: Rational -> T a #

(C a, Num a) => Num (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

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

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

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

negate :: T a -> T a #

abs :: T a -> T a #

signum :: T a -> T a #

fromInteger :: Integer -> T a #

C a => Ord (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

compare :: T a -> T a -> Ordering #

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

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

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

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

max :: T a -> T a -> T a #

min :: T a -> T a -> T a #

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

Defined in Number.NonNegativeChunky

Methods

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

show :: T a -> String #

showList :: [T a] -> ShowS #

C a => Semigroup (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

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

sconcat :: NonEmpty (T a) -> T a #

stimes :: Integral b => b -> T a -> T a #

C a => Monoid (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

mempty :: T a #

mappend :: T a -> T a -> T a #

mconcat :: [T a] -> T a #

(C a, Arbitrary a) => Arbitrary (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

arbitrary :: Gen (T a) #

shrink :: T a -> [T a] #

C a => C (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

zero :: T a Source #

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

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

negate :: T a -> T a Source #

C a => C (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

isZero :: T a -> Bool Source #

(C a, C a) => C (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

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

C a => C (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

idt :: T a Source #

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

cumulate :: [T a] -> T a Source #

C a => C (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

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

(Ord a, C a, C a) => C (T a) Source #

divMod is implemented in terms of divModStrict. If it is needed we could also provide a function that accesses the divisor first in a lazy way and then uses a strict divisor for subsequent rounds of the subtraction loop. This way we can handle the cases "dividend smaller than divisor" and "dividend greater than divisor" in a lazy and efficient way. However changing the way of operation within one number is also not nice.

Instance details

Defined in Number.NonNegativeChunky

Methods

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

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

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

(C a, C a, C a) => C (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

abs :: T a -> T a Source #

signum :: T a -> T a Source #

(C a, C a) => C (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

toRational :: T a -> Rational Source #

(C a, C a) => C (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

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

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

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

(C a, C a) => C (T a) Source # 
Instance details

Defined in Number.NonNegativeChunky

Methods

toInteger :: T a -> Integer Source #

fromChunks :: C a => [a] -> T a Source #

toChunks :: C a => T a -> [a] Source #

fromNumber :: C a => a -> T a Source #

toNumber :: C a => T a -> a Source #

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

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

minMaxDiff :: C a => T a -> T a -> (T a, (Bool, T a)) Source #

normalize :: C a => T a -> T a Source #

Remove zero chunks.

isNull :: C a => T a -> Bool Source #

isPositive :: C a => T a -> Bool Source #

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

divModLazy accesses the divisor in a lazy way. However this is only relevant if the dividend is smaller than the divisor. For large dividends the divisor will be accessed multiple times but since it is already fully evaluated it could also be strict.

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

This function has a strict divisor and maintains the chunk structure of the dividend at a smaller scale.