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
> performance, if needed.

There's

  http://hackage.haskell.org/package/safeint/

It's not implemented quite as efficiently as it theoretically could
be, but it might do more or less what you want.

Cheers,
  Andres

-- 
Andres Löh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 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 something along those lines.
>
>   -- ryan
>
>
> On Mon, Jul 30, 2012 at 1:43 PM, Евгений Пермяков wrote:
>
>> 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 preconditioning of variables, but this will kill
 any performance, if needed.

>>>
>>> In GHC.Prim -- primitives addIntC# and subIntC#:
>>>
>>>  addIntC# :: Int# -> Int# -> (#Int#, Int##)
 Add with carry. First member of result is (wrapped) sum; second member
 is 0 iff no overflow occured.

>>>
>>>  subIntC# :: Int# -> Int# -> (#Int#, Int##)
 Subtract with carry. First member of result is (wrapped) difference;
 second member is 0 iff no overflow occured.

>>>
>>> __**_
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org
>>> http://www.haskell.org/**mailman/listinfo/haskell-cafe
>>>
>> Still no way to detect overflow in *.
>>
>> Strangely enough, I found some relevant descriptions in *.pp in dev
>> branch, so I expect them in 7.6.1. They applies to native-size Word and Int
>> only.
>>
>>
>> __**_
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/**mailman/listinfo/haskell-cafe
>>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 something along those lines.

  -- ryan

On Mon, Jul 30, 2012 at 1:43 PM, Евгений Пермяков wrote:

> 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 preconditioning of variables, but this will kill
>>> any performance, if needed.
>>>
>>
>> In GHC.Prim -- primitives addIntC# and subIntC#:
>>
>>  addIntC# :: Int# -> Int# -> (#Int#, Int##)
>>> Add with carry. First member of result is (wrapped) sum; second member
>>> is 0 iff no overflow occured.
>>>
>>
>>  subIntC# :: Int# -> Int# -> (#Int#, Int##)
>>> Subtract with carry. First member of result is (wrapped) difference;
>>> second member is 0 iff no overflow occured.
>>>
>>
>> __**_
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/**mailman/listinfo/haskell-cafe
>>
> Still no way to detect overflow in *.
>
> Strangely enough, I found some relevant descriptions in *.pp in dev
> branch, so I expect them in 7.6.1. They applies to native-size Word and Int
> only.
>
>
> __**_
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 preconditioning of variables, but this 
will kill any performance, if needed.


In GHC.Prim — primitives addIntC# and subIntC#:


addIntC# :: Int# -> Int# -> (#Int#, Int##)
Add with carry. First member of result is (wrapped) sum; second 
member is 0 iff no overflow occured.



subIntC# :: Int# -> Int# -> (#Int#, Int##)
Subtract with carry. First member of result is (wrapped) difference; 
second member is 0 iff no overflow occured.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Still no way to detect overflow in *.

Strangely enough, I found some relevant descriptions in *.pp in dev 
branch, so I expect them in 7.6.1. They applies to native-size Word and 
Int only.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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  
kill any performance, if needed.


In GHC.Prim — primitives addIntC# and subIntC#:


addIntC# :: Int# -> Int# -> (#Int#, Int##)
Add with carry. First member of result is (wrapped) sum; second member  
is 0 iff no overflow occured.



subIntC# :: Int# -> Int# -> (#Int#, Int##)
Subtract with carry. First member of result is (wrapped) difference;  
second member is 0 iff no overflow occured.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe