non-negative-0.1.1.2: Non-negative numbers

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

Numeric.NonNegative.Wrapper

Description

A type for non-negative numbers. It performs a run-time check at construction time (i.e. at run-time) and is a member of the non-negative number type class C.

Synopsis

Documentation

data T a Source #

Instances

(Ord a, Num a, Bounded a) => Bounded (T a) Source # 

Methods

minBound :: T a #

maxBound :: T a #

(Ord a, Num a, Enum a) => Enum (T a) Source # 

Methods

succ :: T a -> T a #

pred :: T a -> T a #

toEnum :: Int -> T a #

fromEnum :: T a -> Int #

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

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

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

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

Eq a => Eq (T a) Source # 

Methods

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

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

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

Methods

pi :: T a #

exp :: T a -> T a #

log :: T a -> T a #

sqrt :: T a -> T a #

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

logBase :: T a -> T a -> T a #

sin :: T a -> T a #

cos :: T a -> T a #

tan :: T a -> T a #

asin :: T a -> T a #

acos :: T a -> T a #

atan :: T a -> T a #

sinh :: T a -> T a #

cosh :: T a -> T a #

tanh :: T a -> T a #

asinh :: T a -> T a #

acosh :: T a -> T a #

atanh :: T a -> T a #

log1p :: T a -> T a #

expm1 :: T a -> T a #

log1pexp :: T a -> T a #

log1mexp :: T a -> T a #

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

Methods

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

recip :: T a -> T a #

fromRational :: Rational -> T a #

Integral a => Integral (T a) Source # 

Methods

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

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

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

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

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

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

toInteger :: T a -> Integer #

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

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 #

Ord a => Ord (T a) Source # 

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 #

Real a => Real (T a) Source # 

Methods

toRational :: T a -> Rational #

RealFrac a => RealFrac (T a) Source # 

Methods

properFraction :: Integral b => T a -> (b, T a) #

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

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

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

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

Show a => Show (T a) Source # 

Methods

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

show :: T a -> String #

showList :: [T a] -> ShowS #

Num a => Monoid (T a) Source # 

Methods

mempty :: T a #

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

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

(Num a, Arbitrary a) => Arbitrary (T a) Source # 

Methods

arbitrary :: Gen (T a) #

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

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

Methods

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

fromNumber :: (Ord a, Num a) => a -> T a Source #

Convert a number to a non-negative number. If a negative number is given, an error is raised.

fromNumberMsg Source #

Arguments

:: (Ord a, Num a) 
=> String

name of the calling function to be used in the error message

-> a 
-> T a 

fromNumberClip :: (Ord a, Num a) => a -> T a Source #

Convert a number to a non-negative number. A negative number will be replaced by zero. Use this function with care since it may hide bugs.

fromNumberUnsafe :: a -> T a Source #

Wrap a number into a non-negative number without doing checks. This routine exists entirely for efficiency reasons and must be used only in cases where you are absolutely sure, that the input number is non-negative.

toNumber :: T a -> a Source #

type Int = T Int Source #

type Ratio a = T (Ratio a) Source #