Safe Haskell | None |
---|---|
Language | Haskell2010 |
Safe numeric operations.
We take a fairly conservative approach here - this module is an extension not a replacement for Prelude. Our suffix naming conventions are as follows:
@
orW
-- wrap - same as Prelude, but confirms explicitly to the reader that you thought about the issue%
orE
-- explicit error (
)Either
ArithException
:
orS
-- saturate atminBound
ormaxBound
!
orX
-- runtime exception. This is suitable only for trusted inputs, since otherwise you allow the attacker to crash your code arbitrarily.
Currently we provide replacements for:
conversion functions
fromIntegral
andfromInteger
; instead usedivision functions
div
,mod
,divMod
,quot
,rem
,quotRem
; instead use
When using this module, you might also like to ban the unsafe functions from your codebase, e.g. via hlint:
- functions: - {name: [fromIntegral, fromInteger, +, '-', '*', ^], within: [], message: "Use safe versions from Safe.Numeric"} - {name: [div, mod, divMod, quot, rem, quotRem], within: [], message: "Use safe versions from Safe.Numeric"}
Synopsis
- class NumExpand b a where
- ex :: b -> a
- class NumConvert b a where
- type Word29_ = Word
- type Int29_ = Int
- (+@) :: Num a => a -> a -> a
- (+%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a
- (+:) :: (Integral a, Bounded a) => a -> a -> a
- (+!) :: (Integral a, Bounded a) => Partial => a -> a -> a
- (-@) :: Num a => a -> a -> a
- (-%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a
- (-:) :: (Integral a, Bounded a) => a -> a -> a
- (-!) :: (Integral a, Bounded a) => Partial => a -> a -> a
- (*@) :: Num a => a -> a -> a
- (*%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a
- (*:) :: (Integral a, Bounded a) => a -> a -> a
- (*!) :: (Integral a, Bounded a) => Partial => a -> a -> a
- (^@) :: Integral a => a -> a -> a
- (^%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a
- (^:) :: (Integral a, Bounded a) => a -> a -> a
- (^!) :: (Integral a, Bounded a) => Partial => a -> a -> a
- type DivResult a = Either Ordering a
- divE :: Integral a => a -> a -> DivResult a
- divX :: Integral a => a -> a -> a
- modE :: Integral a => a -> a -> DivResult a
- modX :: Integral a => a -> a -> a
- divModE :: Integral a => a -> a -> DivResult (a, a)
- divModX :: Integral a => a -> a -> (a, a)
- quotE :: Integral a => a -> a -> DivResult a
- quotX :: Integral a => a -> a -> a
- remE :: Integral a => a -> a -> DivResult a
- remX :: Integral a => a -> a -> a
- quotRemE :: Integral a => a -> a -> DivResult (a, a)
- quotRemX :: Integral a => a -> a -> (a, a)
Conversions
class NumExpand b a where Source #
Nothing
Safely expand type b
into type a
, with no runtime bounds checking.
a.k.a. "fromIntegral
hurts my fingers and my eyes"
The value is statically guaranteed to remain the same relative to 0 in both directions, i.e. not overflow or underflow, without any runtime checks.
Instances
class NumConvert b a where Source #
Convert from a type into a smaller type
Nothing
Wrap around if the input is out-of-bounds.
ctE :: b -> Either ArithException a Source #
Explicit error if the input is out-of-bounds.
ctX :: Partial => b -> a Source #
Runtime (async) exception if the input is out-of-bounds.
Instances
Summary of instances
Fr\To W8 W16 W29_ W32 W64 W128 W256 I8 I16 I29_ I32 I64 I128 I256 Itgr W8 X X X X X X X X X X X X X X W16 X X X X X X X X X X X X W29_ X X W32 X X X X X X X X W64 X X X X X X W128 X X X X W256 X X I8 X X X X X X X X I16 X X X X X X X I29_ X X I32 X X X X X I64 X X X X I128 X X X I256 X X Itgr X
In the above table, X means NumExpand
, empty means NumConvert
.
Safe, free NumExpand
from W29_
and I29_
to other bounded types are not
guaranteed since there is no specified upper bound on the sizes of the former.
Generally, we cannot have NumExpand a b
and NumExpand b a
unless b = a
.
Arithmetic
(+@) :: Num a => a -> a -> a infixl 6 Source #
Add with wrap-around.
Same as +
but indicates to the reader that you explicitly thought
about this issue and decided that wrap-around is the correct behaviour.
(+%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a infixl 6 Source #
Add with explicit error on overflow or underflow.
(+!) :: (Integral a, Bounded a) => Partial => a -> a -> a infixl 6 Source #
Add with runtime (async) exception on overflow or underflow.
(-@) :: Num a => a -> a -> a infixl 6 Source #
Subtract with wrap-around.
Same as -
but indicates to the reader that you explicitly thought
about this issue and decided that wrap-around is the correct behaviour.
(-%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a infixl 6 Source #
Subtract with explicit error on overflow or underflow.
(-!) :: (Integral a, Bounded a) => Partial => a -> a -> a infixl 6 Source #
Subtract with runtime (async) exception on overflow or underflow.
(*@) :: Num a => a -> a -> a infixl 7 Source #
Multiply with wrap-around.
Same as *
but indicates to the reader that you explicitly thought
about this issue and decided that wrap-around is the correct behaviour.
(*%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a infixl 7 Source #
Multiply with explicit error on overflow or underflow.
(*!) :: (Integral a, Bounded a) => Partial => a -> a -> a infixl 7 Source #
Multiply with runtime (async) exception on overflow or underflow.
(^@) :: Integral a => a -> a -> a infixr 8 Source #
Power with wrap-around.
Same as ^
but indicates to the reader that you explicitly thought
about this issue and decided that wrap-around is the correct behaviour.
(^%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a infixr 8 Source #
Power with explicit error on overflow or underflow.
(^!) :: (Integral a, Bounded a) => Partial => a -> a -> a infixr 8 Source #
Power with runtime (async) exception on overflow or underflow.
Division
type DivResult a = Either Ordering a Source #
Type alias for a division-operation result with explicit error.
The Left
case means division by zero, and its parameter represents the
sign of the nominator operand.
divE :: Integral a => a -> a -> DivResult a Source #
Division (truncated towards -Inf) with explicit error on division-by-zero.
divX :: Integral a => a -> a -> a Source #
Division (truncated towards -Inf) with runtime (async) exception on division-by-zero.
Same as div
but indicates to the reader that you explicitly thought
about this issue and decided that runtime exception is the correct behaviour.
modE :: Integral a => a -> a -> DivResult a Source #
Modulus (truncated towards -Inf) with explicit error on division-by-zero.
modX :: Integral a => a -> a -> a Source #
Modulus (truncated towards -Inf) with runtime (async) exception on division-by-zero.
Same as mod
but indicates to the reader that you explicitly thought
about this issue and decided that runtime exception is the correct behaviour.
divModE :: Integral a => a -> a -> DivResult (a, a) Source #
Division-and-modulus (truncated towards -Inf) with explicit error on division-by-zero.
divModX :: Integral a => a -> a -> (a, a) Source #
Division-and-modulus (truncated towards -Inf) with runtime (async) exception on division-by-zero.
Same as divMod
but indicates to the reader that you explicitly thought
about this issue and decided that runtime exception is the correct behaviour.
quotE :: Integral a => a -> a -> DivResult a Source #
Division (truncated towards 0) with explicit error on division-by-zero.
quotX :: Integral a => a -> a -> a Source #
Division (truncated towards 0) with runtime (async) exception on division-by-zero.
Same as quot
but indicates to the reader that you explicitly thought
about this issue and decided that runtime exception is the correct behaviour.
remE :: Integral a => a -> a -> DivResult a Source #
Modulus (truncated towards 0) with explicit error on division-by-zero.
remX :: Integral a => a -> a -> a Source #
Modulus (truncated towards 0) with runtime (async) exception on division-by-zero.
Same as rem
but indicates to the reader that you explicitly thought
about this issue and decided that runtime exception is the correct behaviour.