safe-decimal-0.2.1.0: Safe and very efficient arithmetic operations on fixed decimal point numbers
Safe HaskellNone
LanguageHaskell2010

Numeric.Decimal

Synopsis

Arithmetic

newtype Decimal r (s :: Nat) p Source #

Decimal number with custom precision (p) and type level scaling (s) parameter (i.e. number of digits after the decimal point). As well as the rounding (r) strategy to use.

Constructors

Decimal p 

Instances

Instances details
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

Functor (Decimal r s) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

fmap :: (a -> b) -> Decimal r s a -> Decimal r s b #

(<$) :: a -> Decimal r s b -> Decimal r s a #

Applicative (Decimal r s) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

pure :: a -> Decimal r s a #

(<*>) :: Decimal r s (a -> b) -> Decimal r s a -> Decimal r s b #

liftA2 :: (a -> b -> c) -> Decimal r s a -> Decimal r s b -> Decimal r s c #

(*>) :: Decimal r s a -> Decimal r s b -> Decimal r s b #

(<*) :: Decimal r s a -> Decimal r s b -> Decimal r s a #

Bounded p => Bounded (Decimal r s p) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

minBound :: Decimal r s p #

maxBound :: Decimal r s p #

Eq p => Eq (Decimal r s p) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

(==) :: Decimal r s p -> Decimal r s p -> Bool #

(/=) :: Decimal r s p -> Decimal r s p -> Bool #

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

Defined in Numeric.Decimal.Internal

Ord p => Ord (Decimal r s p) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

compare :: Decimal r s p -> Decimal r s p -> Ordering #

(<) :: Decimal r s p -> Decimal r s p -> Bool #

(<=) :: Decimal r s p -> Decimal r s p -> Bool #

(>) :: Decimal r s p -> Decimal r s p -> Bool #

(>=) :: Decimal r s p -> Decimal r s p -> Bool #

max :: Decimal r s p -> Decimal r s p -> Decimal r s p #

min :: Decimal r s p -> Decimal r s p -> Decimal r s p #

(Integral p, KnownNat s) => Show (Decimal r s p) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

showsPrec :: Int -> Decimal r s p -> ShowS #

show :: Decimal r s p -> String #

showList :: [Decimal r s p] -> ShowS #

Generic (Decimal r s p) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Associated Types

type Rep (Decimal r s p) :: Type -> Type #

Methods

from :: Decimal r s p -> Rep (Decimal r s p) x #

to :: Rep (Decimal r s p) x -> Decimal r s p #

NFData p => NFData (Decimal r s p) Source # 
Instance details

Defined in Numeric.Decimal.Internal

Methods

rnf :: Decimal r s p -> () #

type Rep (Decimal r s p) Source # 
Instance details

Defined in Numeric.Decimal.Internal

type Rep (Decimal r s p) = D1 ('MetaData "Decimal" "Numeric.Decimal.Internal" "safe-decimal-0.2.1.0-5KDIsr4t4an9249ciT0WRE" 'True) (C1 ('MetaCons "Decimal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 p)))

class Integral p => Round r p where Source #

Rounding strategy to be used with decimal numbers.

Since: 0.1.0

Methods

roundDecimal :: KnownNat k => Decimal r (n + k) p -> Decimal r n p Source #

Reduce the scale of a number by k decimal places using rounding strategy r

Since: 0.1.0

Instances

Instances details
Round RoundToZero Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Int -> Decimal RoundToZero n Int Source #

Round RoundToZero Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Int8 -> Decimal RoundToZero n Int8 Source #

Round RoundToZero Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Int16 -> Decimal RoundToZero n Int16 Source #

Round RoundToZero Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Int32 -> Decimal RoundToZero n Int32 Source #

Round RoundToZero Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Int64 -> Decimal RoundToZero n Int64 Source #

Round RoundToZero Integer Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Integer -> Decimal RoundToZero n Integer Source #

Round RoundToZero Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Word -> Decimal RoundToZero n Word Source #

Round RoundToZero Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Word8 -> Decimal RoundToZero n Word8 Source #

Round RoundToZero Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Word16 -> Decimal RoundToZero n Word16 Source #

Round RoundToZero Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Word32 -> Decimal RoundToZero n Word32 Source #

Round RoundToZero Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Word64 -> Decimal RoundToZero n Word64 Source #

Round RoundDown Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Int -> Decimal RoundDown n Int Source #

Round RoundDown Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Int8 -> Decimal RoundDown n Int8 Source #

Round RoundDown Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Int16 -> Decimal RoundDown n Int16 Source #

Round RoundDown Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Int32 -> Decimal RoundDown n Int32 Source #

Round RoundDown Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Int64 -> Decimal RoundDown n Int64 Source #

Round RoundDown Integer Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Integer -> Decimal RoundDown n Integer Source #

Round RoundDown Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Word -> Decimal RoundDown n Word Source #

Round RoundDown Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Word8 -> Decimal RoundDown n Word8 Source #

Round RoundDown Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Word16 -> Decimal RoundDown n Word16 Source #

Round RoundDown Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Word32 -> Decimal RoundDown n Word32 Source #

Round RoundDown Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Word64 -> Decimal RoundDown n Word64 Source #

Round RoundHalfFromZero Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfFromZero (n + k) Int -> Decimal RoundHalfFromZero n Int Source #

Round RoundHalfFromZero Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfFromZero (n + k) Int8 -> Decimal RoundHalfFromZero n Int8 Source #

Round RoundHalfFromZero Int16 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Int32 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Int64 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Integer Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfFromZero (n + k) Word -> Decimal RoundHalfFromZero n Word Source #

Round RoundHalfFromZero Word8 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Word16 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Word32 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Word64 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfToZero Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Int -> Decimal RoundHalfToZero n Int Source #

Round RoundHalfToZero Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Int8 -> Decimal RoundHalfToZero n Int8 Source #

Round RoundHalfToZero Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Int16 -> Decimal RoundHalfToZero n Int16 Source #

Round RoundHalfToZero Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Int32 -> Decimal RoundHalfToZero n Int32 Source #

Round RoundHalfToZero Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Int64 -> Decimal RoundHalfToZero n Int64 Source #

Round RoundHalfToZero Integer Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfToZero Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Word -> Decimal RoundHalfToZero n Word Source #

Round RoundHalfToZero Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Word8 -> Decimal RoundHalfToZero n Word8 Source #

Round RoundHalfToZero Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Word16 -> Decimal RoundHalfToZero n Word16 Source #

Round RoundHalfToZero Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Word32 -> Decimal RoundHalfToZero n Word32 Source #

Round RoundHalfToZero Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Word64 -> Decimal RoundHalfToZero n Word64 Source #

Round RoundHalfEven Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Int -> Decimal RoundHalfEven n Int Source #

Round RoundHalfEven Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Int8 -> Decimal RoundHalfEven n Int8 Source #

Round RoundHalfEven Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Int16 -> Decimal RoundHalfEven n Int16 Source #

Round RoundHalfEven Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Int32 -> Decimal RoundHalfEven n Int32 Source #

Round RoundHalfEven Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Int64 -> Decimal RoundHalfEven n Int64 Source #

Round RoundHalfEven Integer Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Integer -> Decimal RoundHalfEven n Integer Source #

Round RoundHalfEven Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Word -> Decimal RoundHalfEven n Word Source #

Round RoundHalfEven Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Word8 -> Decimal RoundHalfEven n Word8 Source #

Round RoundHalfEven Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Word16 -> Decimal RoundHalfEven n Word16 Source #

Round RoundHalfEven Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Word32 -> Decimal RoundHalfEven n Word32 Source #

Round RoundHalfEven Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Word64 -> Decimal RoundHalfEven n Word64 Source #

Round RoundHalfDown Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Int -> Decimal RoundHalfDown n Int Source #

Round RoundHalfDown Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Int8 -> Decimal RoundHalfDown n Int8 Source #

Round RoundHalfDown Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Int16 -> Decimal RoundHalfDown n Int16 Source #

Round RoundHalfDown Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Int32 -> Decimal RoundHalfDown n Int32 Source #

Round RoundHalfDown Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Int64 -> Decimal RoundHalfDown n Int64 Source #

Round RoundHalfDown Integer Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Integer -> Decimal RoundHalfDown n Integer Source #

Round RoundHalfDown Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Word -> Decimal RoundHalfDown n Word Source #

Round RoundHalfDown Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Word8 -> Decimal RoundHalfDown n Word8 Source #

Round RoundHalfDown Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Word16 -> Decimal RoundHalfDown n Word16 Source #

Round RoundHalfDown Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Word32 -> Decimal RoundHalfDown n Word32 Source #

Round RoundHalfDown Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Word64 -> Decimal RoundHalfDown n Word64 Source #

Round RoundHalfUp Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Int -> Decimal RoundHalfUp n Int Source #

Round RoundHalfUp Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Int8 -> Decimal RoundHalfUp n Int8 Source #

Round RoundHalfUp Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Int16 -> Decimal RoundHalfUp n Int16 Source #

Round RoundHalfUp Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Int32 -> Decimal RoundHalfUp n Int32 Source #

Round RoundHalfUp Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Int64 -> Decimal RoundHalfUp n Int64 Source #

Round RoundHalfUp Integer Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Integer -> Decimal RoundHalfUp n Integer Source #

Round RoundHalfUp Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Word -> Decimal RoundHalfUp n Word Source #

Round RoundHalfUp Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Word8 -> Decimal RoundHalfUp n Word8 Source #

Round RoundHalfUp Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Word16 -> Decimal RoundHalfUp n Word16 Source #

Round RoundHalfUp Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Word32 -> Decimal RoundHalfUp n Word32 Source #

Round RoundHalfUp Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Word64 -> Decimal RoundHalfUp n Word64 Source #

wrapDecimal :: Integral p => p -> Decimal r s p Source #

Wrap an Integral as a Decimal. No scaling will be done.

>>> import Numeric.Decimal
>>> wrapDecimal 1234 :: Decimal RoundHalfUp 4 Int
0.1234
>>> wrapDecimal 1234 :: Decimal RoundHalfUp 2 Int
12.34

Since: 0.1.0

unwrapDecimal :: Decimal r s p -> p Source #

Get out the underlying representation for the decimal number. No scaling will be done.

>>> import Numeric.Decimal
>>> unwrapDecimal (wrapDecimal 1234 :: Decimal RoundHalfUp 4 Int)
1234

Since: 0.1.0

splitDecimal :: (Integral p, KnownNat s) => Decimal r s p -> (p, p) Source #

Split the number at the decimal point, i.e. whole number and the fraction

>>> import Numeric.Decimal
>>> splitDecimal <$> (12.34 :: Arith (Decimal RoundHalfUp 2 Int))
Arith (12,34)

Since: 0.1.0

decimalNumerator :: Integral p => Decimal r s p -> Integer Source #

Get the numerator. Same as toInteger . unwrapDecimal

>>> import Numeric.Decimal
>>> :set -XDataKinds -XTypeApplications
>>> decimalNumerator <$> arithD @RoundHalfEven @3 @Int 123.45
Arith 123450

Since: 0.2.0

decimalDenominator :: KnownNat s => Decimal r s p -> Integer Source #

Get the decimal denominator. Always will be a multiple of 10. Does not evaluate the argument.

>>> import Numeric.Decimal
>>> :set -XDataKinds -XTypeApplications
>>> decimalDenominator <$> arithD @RoundHalfEven @3 @Int 123.45
Arith 1000

Since: 0.2.0

getScale :: forall r s p. KnownNat s => Decimal r s p -> Integer Source #

Get the scale of a Decimal. Argument is not evaluated.

>>> import Numeric.Decimal
>>> d <- arithM (36 :: Arith (Decimal RoundHalfUp 5 Int))
>>> d
36.00000
>>> getScale d
5

Since: 0.1.0

scaleUp :: forall k r n. KnownNat k => Decimal r n Integer -> Decimal r (n + k) Integer Source #

Increase the precision of a Decimal, use roundDecimal if inverse is desired.

>>> import Numeric.Decimal
>>> d2 <- arithM (1.65 :: Arith (Decimal RoundHalfUp 2 Integer))
>>> d2
1.65
>>> scaleUp d2 :: Decimal RoundHalfUp 50 Integer
1.65000000000000000000000000000000000000000000000000

Since: 0.2.0

scaleUpBounded :: forall k r n p m. (MonadThrow m, Integral p, Bounded p, KnownNat k) => Decimal r n p -> m (Decimal r (n + k) p) Source #

Increase the precision of a Decimal backed by a bounded type, use roundDecimal if inverse is desired.

>>> import Numeric.Decimal
>>> d2 <- arithM (1.65 :: Arith (Decimal RoundHalfUp 2 Int16))
>>> scaleUpBounded d2 :: IO (Decimal RoundHalfUp 3 Int16)
1.650
>>> scaleUpBounded d2 :: IO (Decimal RoundHalfUp 4 Int16)
1.6500
>>> scaleUpBounded d2 :: IO (Decimal RoundHalfUp 5 Int16)
*** Exception: arithmetic overflow

Since: 0.1.1

castRounding :: forall r' r s p. Decimal r s p -> Decimal r' s p Source #

Change the rounding strategy of a Decimal

>>> import Numeric.Decimal
>>> :set -XDataKinds -XTypeApplications
>>> d <- arithMD @RoundHalfUp @3 @Int 123.45
>>> roundDecimal d :: Decimal RoundHalfUp 1 Int
123.5
>>> :t castRounding @RoundDown d
castRounding @RoundDown d :: Decimal RoundDown 3 Int
>>> roundDecimal (castRounding d) :: Decimal RoundDown 1 Int
123.4

Since: 0.2.0

parseDecimalBounded :: forall r s p. (KnownNat s, Bounded p, Integral p) => Bool -> String -> Either String (Decimal r s p) Source #

Decimal Arithmetic

Integer

absDecimal :: KnownNat s => Decimal r s Integer -> Decimal r s Integer Source #

Compute absolute value of a decimal

Since: 0.2.0

signumDecimal :: KnownNat s => Decimal r s Integer -> Decimal r s Integer Source #

Compute signum of a decimal, always one of 1, 0 or -1

Since: 0.2.0

plusDecimal :: Decimal r s Integer -> Decimal r s Integer -> Decimal r s Integer Source #

Add two decimal numbers backed by Integer.

Since: 0.1.0

minusDecimal :: Decimal r s Integer -> Decimal r s Integer -> Decimal r s Integer Source #

Subtract two decimal numbers backed by Integer.

Since: 0.1.0

timesDecimal :: Decimal r s1 Integer -> Decimal r s2 Integer -> Decimal r (s1 + s2) Integer Source #

Multiply two bounded decimal numbers, adjusting their scale at the type level as well.

Since: 0.1.0

timesDecimalWithoutLoss :: forall r s m. (KnownNat s, MonadThrow m) => Decimal r s Integer -> Decimal r s Integer -> m (Decimal r s Integer) Source #

Multiply two decimal numbers that have the same scale, while throwing PrecisionLoss whenever multiplication cannot be done without rounding.

Since: 0.2.0

timesDecimalWithRounding :: (KnownNat s, Round r Integer) => Decimal r s Integer -> Decimal r s Integer -> Decimal r s Integer Source #

Multiply two decimal numbers backed by Integer, while rounding the result according to the rounding strategy.

Since: 0.2.0

divideDecimalWithoutLoss :: forall r s m. (KnownNat s, MonadThrow m) => Decimal r s Integer -> Decimal r s Integer -> m (Decimal r s Integer) Source #

Divide two decimal numbers that have the same scale, while throwing PrecisionLoss whenever division cannot be done without rounding.

Since: 0.2.0

fromIntegerDecimal :: forall r s. KnownNat s => Integer -> Decimal r s Integer Source #

Convert an Integer while performing the necessary scaling

>>> import Numeric.Decimal
>>> fromIntegerDecimal 1234 :: Decimal RoundHalfUp 4 Integer
1234.0000

Since: 0.2.0

fromRationalDecimalWithoutLoss :: forall m r s. (MonadThrow m, KnownNat s) => Rational -> m (Decimal r s Integer) Source #

Convert from Rational to a Decimal backed by Integer. PrecisionLoss will be thrown if conversion cannot be achieved without any loss of data. In case that rounding is acceptable use fromRationalDecimalBoundedWithRounding

Since: 0.2.0

toRationalDecimal :: (KnownNat s, Integral p) => Decimal r s p -> Rational Source #

Convert a decimal to a Rational

Since: 0.2.0

Bounded Integral

absDecimalBounded :: (KnownNat s, MonadThrow m, Integral p, Bounded p) => Decimal r s p -> m (Decimal r s p) Source #

Compute absolute value of a bounded decimal. Protects against overflows for negative minBound.

>>> abs (minBound :: Int8)
-128
>>> import Numeric.Decimal
>>> d <- arithM (fromRational (-1.28) :: Arith (Decimal RoundHalfUp 2 Int8))
>>> d
-1.28
>>> absDecimalBounded d :: Either SomeException (Decimal RoundHalfUp 2 Int8)
Left arithmetic overflow

Note - Watch out for order of negation

>>> -1.28 :: Arith (Decimal RoundHalfUp 2 Int8)
ArithError arithmetic overflow
>>> negate (1.28 :: Arith (Decimal RoundHalfUp 2 Int8))
ArithError arithmetic overflow
>>> :set -XNegativeLiterals
>>> -1.28 :: Arith (Decimal RoundHalfUp 2 Int8)
Arith -1.28

Since: 0.2.0

signumDecimalBounded :: (KnownNat s, MonadThrow m, Integral p, Bounded p) => Decimal r s p -> m (Decimal r s p) Source #

Compute signum of a decimal, always one of 1, 0 or -1

plusDecimalBounded :: (MonadThrow m, Eq p, Ord p, Num p, Bounded p) => Decimal r s p -> Decimal r s p -> m (Decimal r s p) Source #

Add two decimal numbers.

Since: 0.1.0

minusDecimalBounded :: (MonadThrow m, Eq p, Ord p, Num p, Bounded p) => Decimal r s p -> Decimal r s p -> m (Decimal r s p) Source #

Subtract two decimal numbers.

Since: 0.1.0

timesDecimalBounded :: (MonadThrow m, Integral p, Bounded p) => Decimal r s1 p -> Decimal r s2 p -> m (Decimal r (s1 + s2) p) Source #

Multiply two bounded decimal numbers, adjusting their scale at the type level as well.

Since: 0.1.0

timesDecimalBoundedWithoutLoss :: forall r s p m. (Integral p, Bounded p, KnownNat s, MonadThrow m) => Decimal r s p -> Decimal r s p -> m (Decimal r s p) Source #

Multiply two decimal numbers that have the same scale, while throwing PrecisionLoss whenever multiplication cannot be done without rounding. Also checks for bounds and can throw Overflow/Underflow.

Since: 0.2.0

timesDecimalBoundedWithRounding :: (MonadThrow m, KnownNat s, Round r Integer, Integral p, Bounded p) => Decimal r s p -> Decimal r s p -> m (Decimal r s p) Source #

Multiply two decimal numbers, while rounding the result according to the rounding strategy.

Since: 0.2.0

divideDecimalBoundedWithoutLoss :: forall r s p m. (Integral p, Bounded p, KnownNat s, MonadThrow m) => Decimal r s p -> Decimal r s p -> m (Decimal r s p) Source #

Divide two decimal numbers that have the same scale, while throwing PrecisionLoss whenever division cannot be done without rounding.

Since: 0.2.0

fromIntegralDecimalBounded :: (Integral p, Bounded p, KnownNat s, MonadThrow m) => p -> m (Decimal r s p) Source #

Convert a bounded integeral into a decimal, while performing the necessary scaling

>>> import Numeric.Decimal
>>> fromIntegralDecimalBounded 1234 :: IO (Decimal RoundHalfUp 4 Int)
1234.0000
>>> fromIntegralDecimalBounded 1234 :: IO (Decimal RoundHalfUp 4 Int16)
*** Exception: arithmetic overflow

Since: 0.2.0

integralDecimalToDecimalBounded :: (Integral p', Integral p, Bounded p, KnownNat s, MonadThrow m) => Decimal r s p' -> m (Decimal r s p) Source #

Convert a decimal backed by an integral to another decimal backed by a bounded integeral, while checking for Overflow/Underflow

>>> import Numeric.Decimal
>>> fromIntegralDecimalBounded 1234 :: IO (Decimal RoundHalfUp 4 Int)
1234.0000
>>> fromIntegralDecimalBounded 1234 :: IO (Decimal RoundHalfUp 4 Int16)
*** Exception: arithmetic overflow

Since: 0.2.0

quotRemDecimalBounded :: forall m r s p. (MonadThrow m, Integral p, Bounded p) => Decimal r s p -> Integer -> m (Decimal r s p, Decimal r s p) Source #

fromIntegerDecimalBounded :: forall m r s p. (MonadThrow m, Integral p, Bounded p) => Decimal r s Integer -> m (Decimal r s p) Source #

fromIntegerDecimalBoundedIntegral :: forall m r s p. (MonadThrow m, Integral p, Bounded p, KnownNat s) => Integer -> m (Decimal r s p) Source #

Convert an Integer to a Decimal backed by a bounded integral while doing proper scaling and checking the bounds.

Since: 0.2.0

fromRationalDecimalBoundedWithoutLoss :: (MonadThrow m, KnownNat s, Integral p, Bounded p) => Rational -> m (Decimal r s p) Source #

Convert a Rational to a bounded Decimal, but only if there is no precision loss or Overflow/Undeflow.

Since: 0.2.0

bindM2Decimal :: Monad m => (p1 -> p2 -> m p) -> m (Decimal r1 s1 p1) -> m (Decimal r2 s2 p2) -> m (Decimal r s p) Source #

bindM2 :: Monad m => (a -> b -> m c) -> m a -> m b -> m c Source #

Evaluation failure

class Monad m => MonadThrow (m :: Type -> Type) where #

A class for monads in which exceptions may be thrown.

Instances should obey the following law:

throwM e >> x = throwM e

In other words, throwing an exception short-circuits the rest of the monadic computation.

Methods

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

Throw an exception. Note that this throws when this action is run in the monad m, not when it is applied. It is a generalization of Control.Exception's throwIO.

Should satisfy the law:

throwM e >> f = throwM e

Instances

Instances details
MonadThrow [] 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> [a] #

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

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

MonadThrow IO 
Instance details

Defined in Control.Monad.Catch

Methods

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

MonadThrow Q 
Instance details

Defined in Control.Monad.Catch

Methods

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

MonadThrow STM 
Instance details

Defined in Control.Monad.Catch

Methods

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

MonadThrow Arith Source # 
Instance details

Defined in Numeric.Decimal.BoundedArithmetic

Methods

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

e ~ SomeException => MonadThrow (Either e) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> Either e a #

MonadThrow (ST s) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ST s a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> MaybeT m a #

MonadThrow m => MonadThrow (ListT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ListT m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ExceptT e m a #

MonadThrow m => MonadThrow (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IdentityT m a #

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ErrorT e m a #

MonadThrow m => MonadThrow (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ReaderT r m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a #

MonadThrow m => MonadThrow (ContT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ContT r m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a #

data SomeException #

The SomeException type is the root of the exception type hierarchy. When an exception of type e is thrown, behind the scenes it is encapsulated in a SomeException.

Instances

Instances details
Show SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Exception SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

arithD :: forall r s p. Arith (Decimal r s p) -> Arith (Decimal r s p) Source #

A way to type restrict a polymorphic computation.

arithD provide an easy way to use TypeApplications to supply a type of Decimal:

>>> import Numeric.Decimal
>>> :set -XTypeApplications
>>> arithM $ arithD @RoundDown @3 @Word (1.1 + 123)
124.100
>>> arithM $ arithD @RoundDown @3 @Word (1.1 - 123)
*** Exception: arithmetic underflow

Since: 0.2.0

arithMD :: forall r s p m. MonadThrow m => Arith (Decimal r s p) -> m (Decimal r s p) Source #

A way to type restrict a polymorphic computation.

arithD provide an easy way to use TypeApplications to supply a type of Decimal:

>>> import Numeric.Decimal
>>> :set -XDataKinds -XTypeApplications
>>> arithMD @RoundDown @3 @Word (1.1 + 123)
124.100
>>> arithMD @RoundDown @3 @Word (1.1 - 123)
*** Exception: arithmetic underflow

Since: 0.2.0

arithMaybeD :: forall r s p. Arith (Decimal r s p) -> Maybe (Decimal r s p) Source #

A version of arithD that converts to Maybe

>>> import Numeric.Decimal
>>> :set -XTypeApplications
>>> arithMaybeD @RoundDown @3 @Word (1.1 + 123)
Just 124.100
>>> arithMaybeD @RoundDown @3 @Word (1.1 - 123)
Nothing

Since: 0.2.0

arithEitherD :: forall r s p. Arith (Decimal r s p) -> Either SomeException (Decimal r s p) Source #

A version of arithD that converts to Either

Since: 0.2.0

arithRoundD :: forall s' r s p k. (Round r p, KnownNat k, s ~ (s' + k)) => Arith (Decimal r s p) -> Arith (Decimal r s' p) Source #

A way to type restrict a polymorphic computation.

>>> import Numeric.Decimal
>>> arithRoundD @1 @RoundDown @2 @Word (123.05 + 1.1)
Arith 124.1

Since: 0.2.0

Rounding

Round half up

data RoundHalfUp Source #

Round half up rounding strategy:

>>> :set -XDataKinds
>>> roundDecimal <$> (3.740 :: Arith (Decimal RoundHalfUp 3 Int)) :: Arith (Decimal RoundHalfUp 1 Int)
Arith 3.7

Or with a bit more concise approach using arithRoundD and TypeApplications:

>>> :set -XTypeApplications
>>> arithRoundD @1 @RoundHalfUp @3 @Int 3.740
Arith 3.7
>>> arithRoundD @1 @RoundHalfUp @3 @Int 3.749
Arith 3.7
>>> arithRoundD @1 @RoundHalfUp @3 @Int 3.750
Arith 3.8
>>> arithRoundD @1 @RoundHalfUp @3 @Int 3.751
Arith 3.8
>>> arithRoundD @1 @RoundHalfUp @3 @Int 3.760
Arith 3.8
>>> arithRoundD @1 @RoundHalfUp @3 @Int (-3.740)
Arith -3.7
>>> arithRoundD @1 @RoundHalfUp @3 @Int (-3.749)
Arith -3.7
>>> arithRoundD @1 @RoundHalfUp @3 @Int (-3.750)
Arith -3.7
>>> arithRoundD @1 @RoundHalfUp @3 @Int (-3.751)
Arith -3.8
>>> arithRoundD @1 @RoundHalfUp @3 @Int (-3.760)
Arith -3.8

Since: 0.1.0

Instances

Instances details
Round RoundHalfUp Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Int -> Decimal RoundHalfUp n Int Source #

Round RoundHalfUp Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Int8 -> Decimal RoundHalfUp n Int8 Source #

Round RoundHalfUp Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Int16 -> Decimal RoundHalfUp n Int16 Source #

Round RoundHalfUp Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Int32 -> Decimal RoundHalfUp n Int32 Source #

Round RoundHalfUp Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Int64 -> Decimal RoundHalfUp n Int64 Source #

Round RoundHalfUp Integer Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Integer -> Decimal RoundHalfUp n Integer Source #

Round RoundHalfUp Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Word -> Decimal RoundHalfUp n Word Source #

Round RoundHalfUp Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Word8 -> Decimal RoundHalfUp n Word8 Source #

Round RoundHalfUp Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Word16 -> Decimal RoundHalfUp n Word16 Source #

Round RoundHalfUp Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Word32 -> Decimal RoundHalfUp n Word32 Source #

Round RoundHalfUp Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfUp (n + k) Word64 -> Decimal RoundHalfUp n Word64 Source #

roundHalfUp :: forall r n k p. (Integral p, KnownNat k) => Decimal r (n + k) p -> Decimal r n p Source #

Round half down

data RoundHalfDown Source #

Round half down rounding strategy:

>>> :set -XDataKinds
>>> :set -XTypeApplications
>>> arithRoundD @1 @RoundHalfDown @3 @Int 3.740
Arith 3.7
>>> arithRoundD @1 @RoundHalfDown @3 @Int 3.749
Arith 3.7
>>> arithRoundD @1 @RoundHalfDown @3 @Int 3.750
Arith 3.7
>>> arithRoundD @1 @RoundHalfDown @3 @Int 3.751
Arith 3.8
>>> arithRoundD @1 @RoundHalfDown @3 @Int 3.760
Arith 3.8
>>> arithRoundD @1 @RoundHalfDown @3 @Int (-3.740)
Arith -3.7
>>> arithRoundD @1 @RoundHalfDown @3 @Int (-3.749)
Arith -3.7
>>> arithRoundD @1 @RoundHalfDown @3 @Int (-3.750)
Arith -3.8
>>> arithRoundD @1 @RoundHalfDown @3 @Int (-3.751)
Arith -3.8
>>> arithRoundD @1 @RoundHalfDown @3 @Int (-3.760)
Arith -3.8

Since: 0.2.0

Instances

Instances details
Round RoundHalfDown Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Int -> Decimal RoundHalfDown n Int Source #

Round RoundHalfDown Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Int8 -> Decimal RoundHalfDown n Int8 Source #

Round RoundHalfDown Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Int16 -> Decimal RoundHalfDown n Int16 Source #

Round RoundHalfDown Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Int32 -> Decimal RoundHalfDown n Int32 Source #

Round RoundHalfDown Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Int64 -> Decimal RoundHalfDown n Int64 Source #

Round RoundHalfDown Integer Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Integer -> Decimal RoundHalfDown n Integer Source #

Round RoundHalfDown Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Word -> Decimal RoundHalfDown n Word Source #

Round RoundHalfDown Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Word8 -> Decimal RoundHalfDown n Word8 Source #

Round RoundHalfDown Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Word16 -> Decimal RoundHalfDown n Word16 Source #

Round RoundHalfDown Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Word32 -> Decimal RoundHalfDown n Word32 Source #

Round RoundHalfDown Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfDown (n + k) Word64 -> Decimal RoundHalfDown n Word64 Source #

roundHalfDown :: forall r n k p. (Integral p, KnownNat k) => Decimal r (n + k) p -> Decimal r n p Source #

Round half even

data RoundHalfEven Source #

Round half even rounding strategy. If the fractional part of x is 0.5, then y is the even integer nearest to x. This is the default rounding strategy in Haskell implemented by round.

>>> :set -XDataKinds
>>> :set -XTypeApplications
>>> arithRoundD @1 @RoundHalfEven @3 @Int 3.650
Arith 3.6
>>> arithRoundD @1 @RoundHalfEven @3 @Int 3.740
Arith 3.7
>>> arithRoundD @1 @RoundHalfEven @3 @Int 3.749
Arith 3.7
>>> arithRoundD @1 @RoundHalfEven @3 @Int 3.750
Arith 3.8
>>> arithRoundD @1 @RoundHalfEven @3 @Int 3.751
Arith 3.8
>>> arithRoundD @1 @RoundHalfEven @3 @Int 3.760
Arith 3.8
>>> arithRoundD @1 @RoundHalfEven @3 @Int (-3.650)
Arith -3.6
>>> arithRoundD @1 @RoundHalfEven @3 @Int (-3.740)
Arith -3.7
>>> arithRoundD @1 @RoundHalfEven @3 @Int (-3.749)
Arith -3.7
>>> arithRoundD @1 @RoundHalfEven @3 @Int (-3.750)
Arith -3.8
>>> arithRoundD @1 @RoundHalfEven @3 @Int (-3.751)
Arith -3.8
>>> arithRoundD @1 @RoundHalfEven @3 @Int (-3.760)
Arith -3.8

Since: 0.2.0

Instances

Instances details
Round RoundHalfEven Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Int -> Decimal RoundHalfEven n Int Source #

Round RoundHalfEven Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Int8 -> Decimal RoundHalfEven n Int8 Source #

Round RoundHalfEven Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Int16 -> Decimal RoundHalfEven n Int16 Source #

Round RoundHalfEven Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Int32 -> Decimal RoundHalfEven n Int32 Source #

Round RoundHalfEven Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Int64 -> Decimal RoundHalfEven n Int64 Source #

Round RoundHalfEven Integer Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Integer -> Decimal RoundHalfEven n Integer Source #

Round RoundHalfEven Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Word -> Decimal RoundHalfEven n Word Source #

Round RoundHalfEven Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Word8 -> Decimal RoundHalfEven n Word8 Source #

Round RoundHalfEven Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Word16 -> Decimal RoundHalfEven n Word16 Source #

Round RoundHalfEven Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Word32 -> Decimal RoundHalfEven n Word32 Source #

Round RoundHalfEven Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfEven (n + k) Word64 -> Decimal RoundHalfEven n Word64 Source #

roundHalfEven :: forall r n k p. (Integral p, KnownNat k) => Decimal r (n + k) p -> Decimal r n p Source #

Round half to zero

data RoundHalfToZero Source #

Round half towards zero rounding strategy. If the fraction of x is exactly 0.5, then y = x − 0.5 if x is positive, and y = x + 0.5 if x is negative.

>>> :set -XDataKinds
>>> :set -XTypeApplications
>>> arithRoundD @1 @RoundHalfToZero @3 @Int 3.650
Arith 3.6
>>> arithRoundD @1 @RoundHalfToZero @3 @Int 3.740
Arith 3.7
>>> arithRoundD @1 @RoundHalfToZero @4 @Int 3.7501
Arith 3.8
>>> arithRoundD @1 @RoundHalfToZero @3 @Int (-3.650)
Arith -3.6
>>> arithRoundD @1 @RoundHalfToZero @3 @Int (-3.740)
Arith -3.7
>>> arithRoundD @1 @RoundHalfToZero @4 @Int (-3.7501)
Arith -3.8
>>> arithRoundD @1 @RoundHalfToZero @3 @Int (-3.760)
Arith -3.8

Instances

Instances details
Round RoundHalfToZero Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Int -> Decimal RoundHalfToZero n Int Source #

Round RoundHalfToZero Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Int8 -> Decimal RoundHalfToZero n Int8 Source #

Round RoundHalfToZero Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Int16 -> Decimal RoundHalfToZero n Int16 Source #

Round RoundHalfToZero Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Int32 -> Decimal RoundHalfToZero n Int32 Source #

Round RoundHalfToZero Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Int64 -> Decimal RoundHalfToZero n Int64 Source #

Round RoundHalfToZero Integer Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfToZero Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Word -> Decimal RoundHalfToZero n Word Source #

Round RoundHalfToZero Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Word8 -> Decimal RoundHalfToZero n Word8 Source #

Round RoundHalfToZero Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Word16 -> Decimal RoundHalfToZero n Word16 Source #

Round RoundHalfToZero Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Word32 -> Decimal RoundHalfToZero n Word32 Source #

Round RoundHalfToZero Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfToZero (n + k) Word64 -> Decimal RoundHalfToZero n Word64 Source #

roundHalfToZero :: forall r n k p. (Integral p, KnownNat k) => Decimal r (n + k) p -> Decimal r n p Source #

Round half from zero

data RoundHalfFromZero Source #

Round half away from zero rounding strategy. If the fraction of x is exactly 0.5, then y = x + 0.5 if x is positive, and y = x − 0.5 if x is negative.

>>> :set -XDataKinds
>>> :set -XTypeApplications
>>> arithRoundD @1 @RoundHalfFromZero @3 @Int 3.650
Arith 3.7
>>> arithRoundD @1 @RoundHalfFromZero @3 @Int 3.740
Arith 3.7
>>> arithRoundD @1 @RoundHalfFromZero @3 @Int 3.751
Arith 3.8
>>> arithRoundD @1 @RoundHalfFromZero @3 @Int (-3.650)
Arith -3.7
>>> arithRoundD @1 @RoundHalfFromZero @3 @Int (-3.740)
Arith -3.7
>>> arithRoundD @1 @RoundHalfFromZero @3 @Int (-3.751)
Arith -3.8
>>> arithRoundD @1 @RoundHalfFromZero @3 @Int (-3.760)
Arith -3.8

Instances

Instances details
Round RoundHalfFromZero Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfFromZero (n + k) Int -> Decimal RoundHalfFromZero n Int Source #

Round RoundHalfFromZero Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfFromZero (n + k) Int8 -> Decimal RoundHalfFromZero n Int8 Source #

Round RoundHalfFromZero Int16 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Int32 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Int64 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Integer Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundHalfFromZero (n + k) Word -> Decimal RoundHalfFromZero n Word Source #

Round RoundHalfFromZero Word8 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Word16 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Word32 Source # 
Instance details

Defined in Numeric.Decimal

Round RoundHalfFromZero Word64 Source # 
Instance details

Defined in Numeric.Decimal

roundHalfFromZero :: forall r n k p. (Integral p, KnownNat k) => Decimal r (n + k) p -> Decimal r n p Source #

Round down

data RoundDown Source #

Round down rounding startegy. This the strategy that is implemented by floor. Round towards minus infinity:

>>> :set -XDataKinds
>>> :set -XTypeApplications
>>> arithRoundD @1 @RoundDown @2 @Int 3.65
Arith 3.6
>>> arithRoundD @1 @RoundDown @2 @Int 3.75
Arith 3.7
>>> arithRoundD @1 @RoundDown @2 @Int 3.89
Arith 3.8
>>> arithRoundD @1 @RoundDown @2 @Int (-3.65)
Arith -3.7

Since: 0.2.0

Instances

Instances details
Round RoundDown Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Int -> Decimal RoundDown n Int Source #

Round RoundDown Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Int8 -> Decimal RoundDown n Int8 Source #

Round RoundDown Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Int16 -> Decimal RoundDown n Int16 Source #

Round RoundDown Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Int32 -> Decimal RoundDown n Int32 Source #

Round RoundDown Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Int64 -> Decimal RoundDown n Int64 Source #

Round RoundDown Integer Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Integer -> Decimal RoundDown n Integer Source #

Round RoundDown Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Word -> Decimal RoundDown n Word Source #

Round RoundDown Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Word8 -> Decimal RoundDown n Word8 Source #

Round RoundDown Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Word16 -> Decimal RoundDown n Word16 Source #

Round RoundDown Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Word32 -> Decimal RoundDown n Word32 Source #

Round RoundDown Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundDown (n + k) Word64 -> Decimal RoundDown n Word64 Source #

type Floor = RoundDown Source #

Synonym for round down

Since: 0.2.0

roundDown :: forall r n k p. (Integral p, KnownNat k) => Decimal r (n + k) p -> Decimal r n p Source #

Round towards zero

data RoundToZero Source #

Round towards zero strategy. Similar to Haskell's truncate. Drop the fractional digits, regardless of the sign.

>>> :set -XDataKinds
>>> :set -XTypeApplications
>>> arithRoundD @1 @RoundToZero @2 @Int 3.65
Arith 3.6
>>> arithRoundD @1 @RoundToZero @2 @Int 3.75
Arith 3.7
>>> arithRoundD @1 @RoundToZero @2 @Int 3.89
Arith 3.8
>>> arithRoundD @1 @RoundToZero @2 @Int (-3.65)
Arith -3.6

Since: 0.2.0

Instances

Instances details
Round RoundToZero Int Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Int -> Decimal RoundToZero n Int Source #

Round RoundToZero Int8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Int8 -> Decimal RoundToZero n Int8 Source #

Round RoundToZero Int16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Int16 -> Decimal RoundToZero n Int16 Source #

Round RoundToZero Int32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Int32 -> Decimal RoundToZero n Int32 Source #

Round RoundToZero Int64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Int64 -> Decimal RoundToZero n Int64 Source #

Round RoundToZero Integer Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Integer -> Decimal RoundToZero n Integer Source #

Round RoundToZero Word Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Word -> Decimal RoundToZero n Word Source #

Round RoundToZero Word8 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Word8 -> Decimal RoundToZero n Word8 Source #

Round RoundToZero Word16 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Word16 -> Decimal RoundToZero n Word16 Source #

Round RoundToZero Word32 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Word32 -> Decimal RoundToZero n Word32 Source #

Round RoundToZero Word64 Source # 
Instance details

Defined in Numeric.Decimal

Methods

roundDecimal :: forall (k :: Nat) (n :: Nat). KnownNat k => Decimal RoundToZero (n + k) Word64 -> Decimal RoundToZero n Word64 Source #

type Truncate = RoundToZero Source #

Synonym for RoundToZero

Since: 0.1.0

roundToZero :: forall r n k p. (Integral p, KnownNat k) => Decimal r (n + k) p -> Decimal r n p Source #

Operations

decimalList :: Integral p => [p] -> [Decimal r s p] Source #

O(1) - Conversion of a list.

Note: It doesn't do any scaling, eg:

>>> :set -XDataKinds
>>> import Numeric.Decimal
>>> decimalList [1,20,300] :: [Decimal RoundHalfUp 2 Int]
[0.01,0.20,3.00]

If scaling is what you need use fromIntegral instead:

>>> sequenceA [1, 20, 300] :: Arith [Decimal RoundHalfUp 2 Int]
Arith [1.00,20.00,300.00]

Since: 0.1.0

sumDecimalBounded :: (MonadThrow m, Foldable f, Eq p, Ord p, Num p, Bounded p) => f (Decimal r s p) -> m (Decimal r s p) Source #

Sum a list of decimal numbers

>>> :set -XDataKinds
>>> sequenceA [1.1, 20.02, 300.003] >>= sumDecimalBounded :: Arith (Decimal RoundHalfUp 3 Int)
Arith 321.123

Since: 0.2.0

productDecimalBoundedWithRounding :: (MonadThrow m, Foldable f, KnownNat s, Round r Integer, Integral p, Bounded p) => f (Decimal r s p) -> m (Decimal r s p) Source #

Multiply all decimal numbers in the list while doing rounding.

>>> :set -XDataKinds
>>> product [1.1, 20.02, 300.003] :: Double
6606.666066000001
>>> xs <- arithM (mapM fromRational [1.1, 20.02, 300.003] :: Arith [Decimal RoundHalfUp 4 Int])
>>> xs
[1.1000,20.0200,300.0030]
>>> productDecimalBoundedWithRounding xs
6606.6661

Since: 0.2.0

Conversion

Fixed

type family FixedScale e :: Nat Source #

Instances

Instances details
type FixedScale E0 Source # 
Instance details

Defined in Numeric.Decimal

type FixedScale E0 = 0
type FixedScale E1 Source # 
Instance details

Defined in Numeric.Decimal

type FixedScale E1 = 1
type FixedScale E2 Source # 
Instance details

Defined in Numeric.Decimal

type FixedScale E2 = 2
type FixedScale E3 Source # 
Instance details

Defined in Numeric.Decimal

type FixedScale E3 = 3
type FixedScale E6 Source # 
Instance details

Defined in Numeric.Decimal

type FixedScale E6 = 6
type FixedScale E9 Source # 
Instance details

Defined in Numeric.Decimal

type FixedScale E9 = 9
type FixedScale E12 Source # 
Instance details

Defined in Numeric.Decimal

type FixedScale E12 = 12

toFixedDecimal :: (s ~ FixedScale e, Integral p) => Decimal r s p -> Fixed e Source #

Convert a Decimal to a Fixed with the exactly same precision.

>>> toFixedDecimal <$> (3.65 :: Arith (Decimal RoundDown 2 Int)) :: Arith (Fixed E2)
Arith 3.65
>>> toFixedDecimal $ fromFixedDecimal (123.45 :: Fixed E2) :: Fixed E2
123.45

Since: 0.2.0

fromFixedDecimal :: s ~ FixedScale e => Fixed e -> Decimal r s Integer Source #

Convert a Fixed to a Decimal with the exactly same precision

>>> fromFixedDecimal (123.45 :: Fixed E2)
123.45

Since: 0.2.0

fromFixedDecimalBounded :: (s ~ FixedScale e, MonadThrow m, Integral p, Bounded p) => Fixed e -> m (Decimal r s p) Source #

Convert a Fixed to a decimal backed by a bounded integral with the exactly same precision

>>> fromFixedDecimalBounded (123.458 :: Fixed E3) :: Arith (Decimal RoundToZero 3 Int)
Arith 123.458
>>> fromFixedDecimalBounded (123.458 :: Fixed E3) :: Arith (Decimal RoundToZero 3 Int8)
ArithError arithmetic overflow
>>> fromFixedDecimalBounded (-123.458 :: Fixed E3) :: Arith (Decimal RoundToZero 3 Word)
ArithError arithmetic underflow

Since: 0.2.0

Scientific

toScientificDecimal :: (Integral p, KnownNat s) => Decimal r s p -> Scientific Source #

Convert a Decimal to Scientific

Since: 0.1.0

fromScientificDecimal :: forall m r s. (MonadThrow m, KnownNat s) => Scientific -> m (Decimal r s Integer) Source #

Convert Scientific to Decimal without loss of precision. Will return Left Underflow if Scientific has too many decimal places, more than Decimal scaling is capable to handle.

Since: 0.1.0

fromScientificDecimalBounded :: forall m r s p. (MonadThrow m, Integral p, Bounded p, KnownNat s) => Scientific -> m (Decimal r s p) Source #

Convert from Scientific to bounded Decimal while checking for Overflow/Underflow

Since: 0.1.0