Handling overflow and division by zero
Edward Kmett
ekmett at gmail.com
Sun Jun 28 22:30:14 UTC 2015
You should be able to reduce the bit-twiddling a great deal IIRC in the
word case.
SW a + SW b
| c <- a + b, c >= min a b = SW c
| otherwise = throw Overflow
There is a similar trick that escapes me at the moment for the signed case.
On Sun, Jun 28, 2015 at 6:15 PM, Nikita Karetnikov <nikita at karetnikov.org>
wrote:
> Haskell is often marketed as a safe (or safer) language, but there's
> an issue that makes it less safe as it could be. I'm talking about
> arithmetic overflows and division by zero. The safeint package tries
> to address this, but it only supports the Int type because (as I
> understand it) there are no useful primitives for other common types
> defined in Data.Int and Data.Word.
>
> I've tried adding Int64 support to safeint just to see how it would work
> without primops. Here's a snippet (I haven't tested this code well, so
> it may be wrong, sorry about that):
>
> shiftRUnsigned :: Word64 -> Int -> Word64
> shiftRUnsigned = shiftR
>
> --
> http://git.haskell.org/ghc.git/blob/HEAD:/compiler/codeGen/StgCmmPrim.hs#l930
> plusSI64 :: SafeInt64 -> SafeInt64 -> SafeInt64
> plusSI64 (SI64 a) (SI64 b) = if c == 0 then SI64 r else overflowError
> where
> r = a + b
> c = (fromIntegral $ (complement (a `xor` b)) .&. (a `xor` r))
> `shiftRUnsigned`
> ((finiteBitSize a) - 1)
>
> --
> http://git.haskell.org/ghc.git/blob/HEAD:/compiler/codeGen/StgCmmPrim.hs#l966
> minusSI64 :: SafeInt64 -> SafeInt64 -> SafeInt64
> minusSI64 (SI64 a) (SI64 b) = if c == 0 then SI64 r else overflowError
> where
> r = a - b
> c = (fromIntegral $ (a `xor` b) .&. (a `xor` r))
> `shiftRUnsigned`
> ((finiteBitSize a) - 1)
>
> -- https://stackoverflow.com/a/1815371
> timesSI64 :: SafeInt64 -> SafeInt64 -> SafeInt64
> timesSI64 (SI64 a) (SI64 b) =
> let x = a * b
> in if a /= 0 && x `div` a /= b
> then overflowError
> else SI64 x
>
> I may be wrong, but my understanding is that new primops could reduce
> overhead here. If so, would a patch adding them be accepted? Are
> there any caveats?
>
> In the safeint package, would it be reasonable to return an Either
> value instead of throwing an exception? Or would it be too much?
>
> I haven't created a wiki page or ticket because I don't know much, so
> I want to get some feedback before doing so. That would be my first
> patch to GHC (if ever), so maybe I'm not the best candidate, but I've
> been thinking about it for too long to ignore. :\
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20150628/49129f06/attachment.html>
More information about the ghc-devs
mailing list