[Haskell] Strictness question

2005-06-07 Thread Gary Morris
Hello everyone,

I've been playing with implementing the Kocher attacks on RSA in
Haskell.  For the simplest version, I decided to implement the
exponentiation in the same module.  However, my initial tests suggest
that the times don't have any correlation with the operations being
performed.  I'm wondering, however, if this is because some of the
computation is being delayed until later in the program (when I'm not
timing) - if that makes any sense.  My code is:

{-
For a given n, base, val, expt and i, this function computes val ^ 2 and then,
 if the ith bit of expt is 1, multiplies by base, and returns the result.
 (All these computations are done mod n.)
-}
 exptmod' :: Integer - Integer - Integer - Int - Integer - Integer
 exptmod' n base expt i val | testBit expt i = (val ^ 2) * base `mod` n
| otherwise  = val ^ 2 `mod` n
  
{-
 This function uses exptmod' to compute base ^ expt mod n.  Because it folds
 from the right, it checks bits from keySize down to 0, even though the list
 comprehension goes the other direction.
-}
 exptmod :: Integer - Integer - Integer - Int - Integer
 exptmod base expt n keySize = foldr (exptmod' n base expt) 1 [0..keySize]

to compute the exponentiation and mods.  Later, I time it using:

 time :: IO a - IO (a, Integer)
 time act = do time1 - accuticks
   res - act
   time2 - accuticks
   return (res, time2 - time1)

 check :: Integer - IO Integer
 check m = do (_,t) - time (ioexptmod m privkey modulus keySize)
  return t

 ioexptmod :: Integer - Integer - Integer - Int - IO Integer
 ioexptmod base expt n keySize = return $! exptmod base expt n keySize

where accuticks is an interface to the rdtsc op on Windows and to
clock_gettime(CLOCK_REALTIME,...) on Linux.  My hope was that the use
of $! would force it to compute the exponentiation while I was timing
-- and the average times are around 30K clock cycles, suggesting that
it's doing the work, but I was wondering if it was possible that I was
missing something.

Thanks,

 /g

-- 
I'll see you down in Arizona Bay
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Strictness question

2005-06-07 Thread Ben Lippmeier

Gary Morris wrote:


ioexptmod :: Integer - Integer - Integer - Int - IO Integer
ioexptmod base expt n keySize = return $! exptmod base expt n keySize



My hope was that the use
of $! would force it to compute the exponentiation while I was timing



-- and the average times are around 30K clock cycles, suggesting that
it's doing the work, but I was wondering if it was possible that I was
missing something.


An expression like (f $! x) is only ever going to force x to whnf (weak 
head normal form).


To gloss over details: it'll reduce x far enough so it knows that it's 
an Integer, but it won't nessesarally compute that integers value.


If you want to ensure that something is actually computed in a lazy 
language, you need to do something with the result that *absolutely* 
needs a completely constructed object.. Printing to screen is a prime 
candidate, the system can't print something unless it's evaluated it.


Those 30K clocks suggest it's doing _some_ work. I wouldn't start making 
bets on what that work actually consists of though..


BTW: Haskell would have to be my absolutely last choice for 
experimenting with timing attacks against RSA.. Let's just say that I 
admire your courage! :)


Ben.







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


Re: [Haskell] Strictness question

2005-06-07 Thread Marcin 'Qrczak' Kowalczyk
Ben Lippmeier [EMAIL PROTECTED] writes:

 To gloss over details: it'll reduce x far enough so it knows that it's
 an Integer, but it won't nessesarally compute that integers value.

No, Integers don't contain any lazy components.
It statically knows that it's an integer.

-- 
   __( Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] Re: [Haskell] Strictness question

2005-06-07 Thread Ben Lippmeier


 To gloss over details: it'll reduce x far enough so it knows that
 it's an Integer, but it won't nessesarally compute that integers
 value.

 No, Integers don't contain any lazy components.
 It statically knows that it's an integer.

I meant that it would reduce to the outermost constructor but 
nessesarally evaluate the rest of the object.


Ok, I actually looked up the implementation of Integer in GHC.

 -- | Arbitrary-precision integers.
 data Integer   
   = S# Int# -- small integers
 #ifndef ILX
   | J# Int# ByteArray#  -- large integers
 #else
   | J# Void BigInteger  -- .NET big ints

You were right and I was wrong, Integers contain no lazy components. 
Perhaps that just highlights the folly of guessing how much actually 
gets evaluated in a lazy language.. :)


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


RE: stupid strictness question

2002-12-05 Thread Simon Marlow
 Now, we define:
 
  data SMaybe a = SNothing | SJust !a  deriving Show
 
 Now, we run:
 
 *Strict Just (undefined::Int)
 Just *** Exception: Prelude.undefined
 *Strict Just $! (undefined::Int)
 *** Exception: Prelude.undefined
 *Strict SJust $! (undefined::Int)
 *** Exception: Prelude.undefined
 *Strict SJust (undefined::Int)
 SJust *** Exception: Prelude.undefined

 I can't figure out why this last one is different from the 
 one before it, or the one before that.

This one is a GHCi (not GHC) bug.  You may have seen this message while
loading the source containing the strict constructor definition:

WARNING: ignoring polymorphic case in interpreted mode.
   Possibly due to strict polymorphic/functional constructor args.
   Your program may leak space unexpectedly.

which means that GHCi essentially ignored the strictness flag on the
polymorphic field of the SJust constructor.  To work around the bug, you
can compile that module with GHC.

The good news is that this bug will be fixed in the next major release.

Cheers,
Simon
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



stupid strictness question

2002-12-04 Thread Hal Daume III
i know i know, this has been asked a million times, but i was searching
through the archives with no success, so i figured i'd bug you guys.

according to the report:

  A declaration of the form 

data cx = T u1 ... uk = ... | K s1 ... sn | ... 

  where each si is either of the form ! ti or ti, replaces every 
  occurance of K in an expression by 

(\x1 ... xn - ( ((K op1 x1) op2 x2) ... ) opn xn) 

  where opi is the lazy apply function $ if si is of the form ti, 
  and opi is the strict apply function $! (see Section 6.2) if si 
  is of the form !ti. Pattern matching on K is not affected by
  strictness flags. 

so.  we define:

 data L = L  Int deriving Show
 data S = S !Int deriving Show

and, as expected, we get:

*Strict L undefined
L *** Exception: Prelude.undefined
*Strict L $! undefined
*** Exception: Prelude.undefined
*Strict S undefined
*** Exception: Prelude.undefined

Now, we define:

 data SMaybe a = SNothing | SJust !a  deriving Show

Now, we run:

*Strict Just (undefined::Int)
Just *** Exception: Prelude.undefined
*Strict Just $! (undefined::Int)
*** Exception: Prelude.undefined
*Strict SJust $! (undefined::Int)
*** Exception: Prelude.undefined
*Strict SJust (undefined::Int)
SJust *** Exception: Prelude.undefined

I can't figure out why this last one is different from the one before it,
or the one before that.  Interestingly, Hugs disagrees (the previous was
with ghc 5.04.1):

Strict Just (undefined::Int)
Just 
Program error: {undefined}
Strict Just $! (undefined::Int)
Program error: {undefined}
Strict SJust $! (undefined::Int)
Program error: {undefined}
Strict SJust (undefined::Int)
Program error: {undefined}

Which is what I expected.  Can someone clarify here?

 - Hal

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



strictness question

2001-03-02 Thread S. Doaitse Swierstra

I ran into a difference between GHC and Hugs. The following code:

f  (P p) ~(P q)   = P (\ k - \inp - let (((pv, (qv, r)), m), st) = 
p (q k) inp
   in  (((pv qv  , r ), m), st))

runs fine with Hugs but blows up with GHC, whereas:

f  (P p) ~(P q)   = P (\ k - \inp - let ~(~(~(pv, ~(qv, r)), m), 
st) = p (q k) inp
   in  (((pv qv  , r ), m), st))

runs fine with GHC too.

 From the Haskell manual I understand that pattern matching in "let"'s 
should be done lazily, so the addition of a collection of ~'s should 
not make a difference. Am I right with  this interpretation?

A possible source of this problem may be origination from the smarter 
GHC optimiser, but in that case the optimiser is not doing its work 
well.

Doaitse Swierstra




-- 
__
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
   P.O.Box 80.089, 3508 TB UTRECHT,   the Netherlands
   Mail:  mailto:[EMAIL PROTECTED]
   WWW:   http://www.cs.uu.nl/
   PGP Public Key: http://www.cs.uu.nl/people/doaitse/
   tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: strictness question

2001-03-02 Thread Marcin 'Qrczak' Kowalczyk

Thu, 1 Mar 2001 12:25:33 +0100, S. Doaitse Swierstra [EMAIL PROTECTED] pisze:

 From the Haskell manual I understand that pattern matching in "let"'s 
 should be done lazily, so the addition of a collection of ~'s should 
 not make a difference.

Toplevel ~ in let doesn't change anything. But nested ~'s do make
a difference. When a variable of a pattern is evaluated, the whole
pattern is matched. When you protect a subpattern by ~ deferring its
matching and a variable from the subpattern is evaluated, again the
whole subpattern is matched, unless its subsubpatterns are protected
with their own ~'s etc.

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTPCZA
QRCZAK


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: strictness question

2001-03-02 Thread S. Doaitse Swierstra

Thanks for the prompt reply. Hugs apparently is more lazy and 
performs all the matching lazily, and that really makes a difference 
in my case.

  Doaitse

At 8:11 AM -0800 3/2/01, Simon Peyton-Jones wrote:
Strange.  You don't supply a complete program, so it's hard to
test. 

Nevertheless, the Haskell Report (Sect 3.12) specifies that
a let adds a single twiddle.  Thus

   let (x, (y,z)) = e in b

means

   let x = case e of (x,(y,z)) - x
y = case e of (x,(y,z)) - y
z = case e of (x,(y,z)) - z
   in b

And that is what GHC implements.  You get something different if you
add twiddles inside:

   let (x, ~(y,z)) = e in b

means
   let x = case e of (x,_) - x
y = case e of (_,(y,_)) - y
   etc

Adding more twiddles means less eager matching.  I don't know whether
Hugs implements this.

Simon

| -Original Message-
| From: S. Doaitse Swierstra [mailto:[EMAIL PROTECTED]]
| Sent: 01 March 2001 11:26
| To: [EMAIL PROTECTED]
| Subject: strictness question
|
|
| I ran into a difference between GHC and Hugs. The following code:
|
| f  (P p) ~(P q)   = P (\ k - \inp - let (((pv, (qv, r)), m), st) =
| p (q k) inp
|in  (((pv qv  , r ), m), st))
|
| runs fine with Hugs but blows up with GHC, whereas:
|
| f  (P p) ~(P q)   = P (\ k - \inp - let ~(~(~(pv, ~(qv, r)), m),
| st) = p (q k) inp
|in  (((pv qv  , r ), m), st))
|
| runs fine with GHC too.
|
|  From the Haskell manual I understand that pattern matching
| in "let"'s
| should be done lazily, so the addition of a collection of ~'s should
| not make a difference. Am I right with  this interpretation?
|
| A possible source of this problem may be origination from the smarter
| GHC optimiser, but in that case the optimiser is not doing its work
| well.
|
| Doaitse Swierstra
|
|
|
|
| --
| __
| 
| S. Doaitse Swierstra, Department of Computer Science, Utrecht
| University
|P.O.Box 80.089, 3508 TB UTRECHT,   the
| Netherlands
|Mail:  mailto:[EMAIL PROTECTED]
|WWW:   http://www.cs.uu.nl/
|PGP Public Key:
http://www.cs.uu.nl/people/doaitse/
tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

-- 
__
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
   P.O.Box 80.089, 3508 TB UTRECHT,   the Netherlands
   Mail:  mailto:[EMAIL PROTECTED]
   WWW:   http://www.cs.uu.nl/
   PGP Public Key: http://www.cs.uu.nl/people/doaitse/
   tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: strictness question

2001-03-02 Thread Simon Peyton-Jones

Strange.  You don't supply a complete program, so it's hard to
test.  

Nevertheless, the Haskell Report (Sect 3.12) specifies that 
a let adds a single twiddle.  Thus

let (x, (y,z)) = e in b

means

let x = case e of (x,(y,z)) - x
 y = case e of (x,(y,z)) - y
 z = case e of (x,(y,z)) - z
in b

And that is what GHC implements.  You get something different if you 
add twiddles inside:

let (x, ~(y,z)) = e in b

means
let x = case e of (x,_) - x
 y = case e of (_,(y,_)) - y
etc

Adding more twiddles means less eager matching.  I don't know whether
Hugs implements this.

Simon

| -Original Message-
| From: S. Doaitse Swierstra [mailto:[EMAIL PROTECTED]]
| Sent: 01 March 2001 11:26
| To: [EMAIL PROTECTED]
| Subject: strictness question
| 
| 
| I ran into a difference between GHC and Hugs. The following code:
| 
| f  (P p) ~(P q)   = P (\ k - \inp - let (((pv, (qv, r)), m), st) = 
| p (q k) inp
|in  (((pv qv  , r ), m), st))
| 
| runs fine with Hugs but blows up with GHC, whereas:
| 
| f  (P p) ~(P q)   = P (\ k - \inp - let ~(~(~(pv, ~(qv, r)), m), 
| st) = p (q k) inp
|in  (((pv qv  , r ), m), st))
| 
| runs fine with GHC too.
| 
|  From the Haskell manual I understand that pattern matching 
| in "let"'s 
| should be done lazily, so the addition of a collection of ~'s should 
| not make a difference. Am I right with  this interpretation?
| 
| A possible source of this problem may be origination from the smarter 
| GHC optimiser, but in that case the optimiser is not doing its work 
| well.
| 
| Doaitse Swierstra
| 
| 
| 
| 
| -- 
| __
| 
| S. Doaitse Swierstra, Department of Computer Science, Utrecht 
| University
|P.O.Box 80.089, 3508 TB UTRECHT,   the 
| Netherlands
|Mail:  mailto:[EMAIL PROTECTED]
|WWW:   http://www.cs.uu.nl/
|PGP Public Key: 
http://www.cs.uu.nl/people/doaitse/
   tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell