Re: [Haskell-cafe] Detecting numeric overflows

2012-07-31 Thread Andres Löh
Hi. On Mon, Jul 30, 2012 at 8:47 AM, Евгений Пермяков wrote: > Can someone tell me if there are any primitives, that used to detect machine > type overflows, in ghc haskell ? I perfectly understand, that I can build > something based on preconditioning of variables, but this will kill any > perfo

Re: [Haskell-cafe] Detecting numeric overflows

2012-07-31 Thread Ryan Ingram
Actually, looking at the docs, I'm not sure if case expressions work on unboxed ints; you may need addCarry (I# x) (I# y) = case addIntC# x y of (# s, c #) -> (I# s, c /=# 0#) which is somewhat simpler anyways. -- ryan On Tue, Jul 31, 2012 at 1:56 AM, Ryan Ingram wrote: > Sure, but it's eas

Re: [Haskell-cafe] Detecting numeric overflows

2012-07-31 Thread Ryan Ingram
Sure, but it's easy to roll your own from those primitives: {-# LANGUAGE MagicHash, UnboxedTuples #-} import GHC.Exts addCarry :: Int -> Int -> (Int, Bool) addCarry (I# x) (I# y) = case addIntC# x y of (# s, c #) -> case c of 0# -> (I# s, False) _ -> (I# s, True) or someth

Re: [Haskell-cafe] Detecting numeric overflows

2012-07-30 Thread Евгений Пермяков
On 07/31/2012 12:04 AM, Artyom Kazak wrote: Евгений Пермяков писал в своём письме Mon, 30 Jul 2012 09:47:48 +0300: Can someone tell me if there are any primitives, that used to detect machine type overflows, in ghc haskell ? I perfectly understand, that I can build something based on precond

Re: [Haskell-cafe] Detecting numeric overflows

2012-07-30 Thread Artyom Kazak
Евгений Пермяков писал в своём письме Mon, 30 Jul 2012 09:47:48 +0300: Can someone tell me if there are any primitives, that used to detect machine type overflows, in ghc haskell ? I perfectly understand, that I can build something based on preconditioning of variables, but this will kil

[Haskell-cafe] Detecting numeric overflows

2012-07-29 Thread Евгений Пермяков
Can someone tell me if there are any primitives, that used to detect machine type overflows, in ghc haskell ? I perfectly understand, that I can build something based on preconditioning of variables, but this will kill any performance, if needed. ___