safe-decimal-0.2.0.0: Safe and very efficient arithmetic operations on fixed decimal point numbers

Safe HaskellSafe
LanguageHaskell2010

Numeric.Decimal.BoundedArithmetic

Contents

Synopsis

Arith Monad

data Arith a Source #

Monad for performing safe computation

Constructors

Arith !a 
ArithError !SomeException 
Instances
Monad Arith Source # 
Instance details

Defined in Numeric.Decimal.BoundedArithmetic

Methods

(>>=) :: Arith a -> (a -> Arith b) -> Arith b #

(>>) :: Arith a -> Arith b -> Arith b #

return :: a -> Arith a #

fail :: String -> Arith a #

Functor Arith Source # 
Instance details

Defined in Numeric.Decimal.BoundedArithmetic

Methods

fmap :: (a -> b) -> Arith a -> Arith b #

(<$) :: a -> Arith b -> Arith a #

Applicative Arith Source # 
Instance details

Defined in Numeric.Decimal.BoundedArithmetic

Methods

pure :: a -> Arith a #

(<*>) :: Arith (a -> b) -> Arith a -> Arith b #

liftA2 :: (a -> b -> c) -> Arith a -> Arith b -> Arith c #

(*>) :: Arith a -> Arith b -> Arith b #

(<*) :: Arith a -> Arith b -> Arith a #

MonadThrow Arith Source # 
Instance details

Defined in Numeric.Decimal.BoundedArithmetic

Methods

throwM :: Exception e => e -> Arith a #

KnownNat s => Fractional (Arith (Decimal r s Word64)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Fractional (Arith (Decimal r s Word32)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Fractional (Arith (Decimal r s Word16)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Fractional (Arith (Decimal r s Word8)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Fractional (Arith (Decimal r s Word)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

(/) :: Arith (Decimal r s Word) -> Arith (Decimal r s Word) -> Arith (Decimal r s Word) #

recip :: Arith (Decimal r s Word) -> Arith (Decimal r s Word) #

fromRational :: Rational -> Arith (Decimal r s Word) #

KnownNat s => Fractional (Arith (Decimal r s Int64)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Fractional (Arith (Decimal r s Int32)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Fractional (Arith (Decimal r s Int16)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Fractional (Arith (Decimal r s Int8)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

(/) :: Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) #

recip :: Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) #

fromRational :: Rational -> Arith (Decimal r s Int8) #

KnownNat s => Fractional (Arith (Decimal r s Int)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

(/) :: Arith (Decimal r s Int) -> Arith (Decimal r s Int) -> Arith (Decimal r s Int) #

recip :: Arith (Decimal r s Int) -> Arith (Decimal r s Int) #

fromRational :: Rational -> Arith (Decimal r s Int) #

KnownNat s => Fractional (Arith (Decimal r s Integer)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Num (Arith (Decimal r s Word64)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Num (Arith (Decimal r s Word32)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Num (Arith (Decimal r s Word16)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Num (Arith (Decimal r s Word8)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Num (Arith (Decimal r s Word)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

(+) :: Arith (Decimal r s Word) -> Arith (Decimal r s Word) -> Arith (Decimal r s Word) #

(-) :: Arith (Decimal r s Word) -> Arith (Decimal r s Word) -> Arith (Decimal r s Word) #

(*) :: Arith (Decimal r s Word) -> Arith (Decimal r s Word) -> Arith (Decimal r s Word) #

negate :: Arith (Decimal r s Word) -> Arith (Decimal r s Word) #

abs :: Arith (Decimal r s Word) -> Arith (Decimal r s Word) #

signum :: Arith (Decimal r s Word) -> Arith (Decimal r s Word) #

fromInteger :: Integer -> Arith (Decimal r s Word) #

KnownNat s => Num (Arith (Decimal r s Int64)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Num (Arith (Decimal r s Int32)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Num (Arith (Decimal r s Int16)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

KnownNat s => Num (Arith (Decimal r s Int8)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

(+) :: Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) #

(-) :: Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) #

(*) :: Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) #

negate :: Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) #

abs :: Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) #

signum :: Arith (Decimal r s Int8) -> Arith (Decimal r s Int8) #

fromInteger :: Integer -> Arith (Decimal r s Int8) #

KnownNat s => Num (Arith (Decimal r s Int)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

(+) :: Arith (Decimal r s Int) -> Arith (Decimal r s Int) -> Arith (Decimal r s Int) #

(-) :: Arith (Decimal r s Int) -> Arith (Decimal r s Int) -> Arith (Decimal r s Int) #

(*) :: Arith (Decimal r s Int) -> Arith (Decimal r s Int) -> Arith (Decimal r s Int) #

negate :: Arith (Decimal r s Int) -> Arith (Decimal r s Int) #

abs :: Arith (Decimal r s Int) -> Arith (Decimal r s Int) #

signum :: Arith (Decimal r s Int) -> Arith (Decimal r s Int) #

fromInteger :: Integer -> Arith (Decimal r s Int) #

KnownNat s => Num (Arith (Decimal r s Integer)) Source # 
Instance details

Defined in Numeric.Decimal.Internal

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

Defined in Numeric.Decimal.BoundedArithmetic

Methods

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

show :: Arith a -> String #

showList :: [Arith a] -> ShowS #

arithM :: MonadThrow m => Arith a -> m a Source #

Convert Arith computation to any MonadThrow

>>> import Numeric.Decimal
>>> :set -XDataKinds
>>> arithM (1.1 * 123 :: Arith (Decimal RoundDown 3 Int))
135.300
>>> arithM (1.1 - 123 :: Arith (Decimal RoundDown 3 Word))
*** Exception: arithmetic underflow
>>> 1.1 - 123 :: Arith (Decimal RoundDown 3 Word)
ArithError arithmetic underflow

Since: 0.2.0

arithMaybe :: Arith a -> Maybe a Source #

A version of arithM restricted to Maybe

Since: 0.2.0

arithEither :: Arith a -> Either SomeException a Source #

A version of arithM restricted to Either

Since: 0.2.0

Bounded

plusBounded :: (MonadThrow m, Ord a, Num a, Bounded a) => a -> a -> m a Source #

Add two bounded numbers while checking for Overflow/Underflow

Since: 0.1.0

minusBounded :: (MonadThrow m, Ord a, Num a, Bounded a) => a -> a -> m a Source #

Subtract two bounded numbers while checking for Overflow/Underflow

Since: 0.1.0

timesBounded :: (MonadThrow m, Integral a, Bounded a) => a -> a -> m a Source #

Multiply two numbers while checking for Overflow

Since: 0.1.0

absBounded :: (MonadThrow m, Num p, Ord p) => p -> m p Source #

Compute absolute value, while checking for Overflow

Since: 0.2.0

fromIntegerBounded :: forall m a. (MonadThrow m, Integral a, Bounded a) => Integer -> m a Source #

Convert from an unbounded Integer to a Bounded Integral, while checking for bounds and raising Overflow/Underflow

Since: 0.1.0

divBounded :: (MonadThrow m, Integral a, Bounded a) => a -> a -> m a Source #

Divide two numbers while checking for Overflow and DivideByZero

Since: 0.1.0

quotBounded :: (MonadThrow m, Integral a, Bounded a) => a -> a -> m a Source #

Find quotient of two numbers while checking for Overflow and DivideByZero

Since: 0.1.0

quotRemBounded :: (MonadThrow m, Integral a, Bounded a) => a -> a -> m (a, a) Source #

Find quotient an remainder of two numbers while checking for Overflow and DivideByZero

Since: 0.1.0