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

Safe HaskellNone
LanguageHaskell98

Number.Positional.Check

Contents

Description

Interface to Number.Positional which dynamically checks for equal bases.

Synopsis

Documentation

data T Source #

The value Cons b e m represents the number b^e * (m!!0 / 1 + m!!1 / b + m!!2 / b^2 + ...). The interpretation of exponent is chosen such that floor (logBase b (Cons b e m)) == e. That is, it is good for multiplication and logarithms. (Because of the necessity to normalize the multiplication result, the alternative interpretation wouldn't be more complicated.) However for base conversions, roots, conversion to fixed point and working with the fractional part the interpretation b^e * (m!!0 / b + m!!1 / b^2 + m!!2 / b^3 + ...) would fit better. The digits in the mantissa range from 1-base to base-1. The representation is not unique and cannot be made unique in finite time. This way we avoid infinite carry ripples.

Constructors

Cons 

Fields

Instances

Eq T Source # 

Methods

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

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

Fractional T Source # 

Methods

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

recip :: T -> T #

fromRational :: Rational -> T #

Num T Source # 

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 # 

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 #

Show T Source # 

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

C T Source # 

Methods

zero :: T Source #

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

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

negate :: T -> T Source #

C T Source # 

Methods

isZero :: T -> Bool Source #

C T Source # 

Methods

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

one :: T Source #

fromInteger :: Integer -> T Source #

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

C T Source # 

Methods

abs :: T -> T Source #

signum :: T -> T Source #

C T Source # 

Methods

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

recip :: T -> T Source #

fromRational' :: Rational -> T Source #

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

C T Source # 

Methods

sqrt :: T -> T Source #

root :: Integer -> T -> T Source #

(^/) :: T -> Rational -> T Source #

C T Source # 

Methods

pi :: T Source #

exp :: T -> T Source #

log :: T -> T Source #

logBase :: T -> T -> T Source #

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

sin :: T -> T Source #

cos :: T -> T Source #

tan :: T -> T Source #

asin :: T -> T Source #

acos :: T -> T Source #

atan :: T -> T Source #

sinh :: T -> T Source #

cosh :: T -> T Source #

tanh :: T -> T Source #

asinh :: T -> T Source #

acosh :: T -> T Source #

atanh :: T -> T Source #

C T Source # 

Methods

splitFraction :: C b => T -> (b, T) Source #

fraction :: T -> T Source #

ceiling :: C b => T -> b Source #

floor :: C b => T -> b Source #

truncate :: C b => T -> b Source #

round :: C b => T -> b Source #

C T Source # 
C T Source # 

Methods

atan2 :: T -> T -> T Source #

Power T Source # 

Methods

power :: Rational -> T T -> T T Source #

basic helpers

compress :: T -> T Source #

Shift digits towards zero by partial application of carries. E.g. 1.8 is converted to 2.(-2) If the digits are in the range (1-base, base-1) the resulting digits are in the range ((1-base)2-2, (base-1)2+2). The result is still not unique, but may be useful for further processing.

carry :: T -> T Source #

perfect carry resolution, works only on finite numbers

conversions

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

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

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