Cryptography-Digest Digest #627, Volume #12       Thu, 7 Sep 00 03:13:01 EDT

Contents:
  Re: Carnivore article in October CACM _Inside_Risks (wtshaw)
  Re: Carnivore article in October CACM _Inside_Risks (Crypto Neophyte)
  ExCSS Source Code ([EMAIL PROTECTED])
  Re: Diffie-Hellman C-sample? ("Paul Pires")
  Re: could you please tell me how this calculation has been obtained ? (Michael Brown)
  Re: could you please tell me how this calculation has been obtained ? (jungle)
  Free Upgrade PGP Personal Privacy 6.5.8 - how? (Jacques Therrien)
  Re: Carnivore article in October CACM _Inside_Risks ("Douglas A. Gwyn")
  Re: on a ligher note... (David A Molnar)
  Re: Losing AES Candidates Could Be a Good Bet? ("Douglas A. Gwyn")
  Re: Ciphertext Randomness/Statistical Tests ("Douglas A. Gwyn")
  Re: Losing AES Candidates Could Be a Good Bet? (John Savard)
  Re: RSA Patent Dead Today (John Savard)
  Re: 4x4 s-boxes (Mack)

----------------------------------------------------------------------------

From: [EMAIL PROTECTED] (wtshaw)
Crossposted-To: comp.security.misc,alt.security,talk.politics.crypto
Subject: Re: Carnivore article in October CACM _Inside_Risks
Date: Wed, 06 Sep 2000 20:55:37 -0600

In article <[EMAIL PROTECTED]>, Steve Smith <[EMAIL PROTECTED]> wrote:

> Roger Schlafly wrote:
> 
> > Why wouldn't the ISPs just unplug Carnivore, reboot, and
> > tell the FBI that they'll plug it back in when it works?
> 
> Because anybody who did so would immediately be thrown in jail for
> violating a court order.
> 
Power outages are not subject to court order. Incompatible engineered
devices are themselves against the law if knowingly installed to sabotage
any computer network.
-- 
A Pangram(corrected, needed a G): 
Vexed xenophobes fear crypto's jazzy, quaint workings.

------------------------------

From: Crypto Neophyte <[EMAIL PROTECTED]>
Subject: Re: Carnivore article in October CACM _Inside_Risks
Crossposted-To: comp.security.misc,alt.security,talk.politics.crypto
Date: Wed, 6 Sep 2000 22:27:36 -0500

On Wed, 6 Sep 2000 21:55:37 -0500, wtshaw wrote
(in message <[EMAIL PROTECTED]>):

>  Incompatible engineered devices are themselves against the law if knowingly 
> installed to sabotage any computer network.

As a child of the 60's and the Hoover era, since when has something being 
against the law stopped the FBI.
HKRIS


------------------------------

From: [EMAIL PROTECTED]
Subject: ExCSS Source Code
Date: Thu, 07 Sep 2000 03:23:00 GMT

This is source code describing the algorithm to decode the Content
Scrambling System. It's written in Standard ML and is purely functional
and machine-independent.


structure ExCSS :>
  sig
    type bytevector = Word8.word Vector.vector

    (* keys are 6 bytes *)
    type key = bytevector

    (* an example player key *)
    val playerkey : key

    (* takes encrypted disk key and player key,
       returns decrypted disk key *)
    val titlekey1 : key * key -> key

    (* takes encrypted title key and disk key,
       returns decrypted title key *)
    val titlekey2 : key * key -> key

    (* takes an encrypted title key and encrytped disk key,
       returns a decrypted title key *)
    val detitlekey : key * key -> key

    (* takes a 2048-byte sector and decryption key,
       returns decrypted sector *)
    val descramble : bytevector * key -> bytevector

  end =
struct

  exception Unimplemented and Impossible
  open Vector

  (* functional vector modify *)
  fun modify (v : 'a vector,
              i : int,
              a : 'a) : 'a vector =
    mapi (fn (ii, aa) => if ii = i then a else aa) (v, 0, NONE)

  structure W8 = Word8
  structure W32 = Word32

  type bytevector = W8.word Vector.vector

  val w32 = W32.fromInt o W8.toInt
  val w8  = W8.fromInt o W32.toIntX

  type key = W8.word vector

  val playerkey : bytevector =
    fromList [0wx51, 0wx67, 0wx67, 0wxC5, 0wxE0, 0wx00]

local  val table1 = Vector.fromList [
0x33,0x73,0x3b,0x26,0x63,0x23,0x6b,0x76,0x3e,0x7e,0x36,0x2b,0x6e,0x2e,0x66,0x
7b,
0xd3,0x93,0xdb,0x06,0x43,0x03,0x4b,0x96,0xde,0x9e,0xd6,0x0b,0x4e,0x0e,0x46,0x
9b,
0x57,0x17,0x5f,0x82,0xc7,0x87,0xcf,0x12,0x5a,0x1a,0x52,0x8f,0xca,0x8a,0xc2,0x
1f,
0xd9,0x99,0xd1,0x00,0x49,0x09,0x41,0x90,0xd8,0x98,0xd0,0x01,0x48,0x08,0x40,0x
91,
0x3d,0x7d,0x35,0x24,0x6d,0x2d,0x65,0x74,0x3c,0x7c,0x34,0x25,0x6c,0x2c,0x64,0x
75,
0xdd,0x9d,0xd5,0x04,0x4d,0x0d,0x45,0x94,0xdc,0x9c,0xd4,0x05,0x4c,0x0c,0x44,0x
95,
0x59,0x19,0x51,0x80,0xc9,0x89,0xc1,0x10,0x58,0x18,0x50,0x81,0xc8,0x88,0xc0,0x
11,
0xd7,0x97,0xdf,0x02,0x47,0x07,0x4f,0x92,0xda,0x9a,0xd2,0x0f,0x4a,0x0a,0x42,0x
9f,
0x53,0x13,0x5b,0x86,0xc3,0x83,0xcb,0x16,0x5e,0x1e,0x56,0x8b,0xce,0x8e,0xc6,0x
1b,
0xb3,0xf3,0xbb,0xa6,0xe3,0xa3,0xeb,0xf6,0xbe,0xfe,0xb6,0xab,0xee,0xae,0xe6,0x
fb,
0x37,0x77,0x3f,0x22,0x67,0x27,0x6f,0x72,0x3a,0x7a,0x32,0x2f,0x6a,0x2a,0x62,0x
7f,
0xb9,0xf9,0xb1,0xa0,0xe9,0xa9,0xe1,0xf0,0xb8,0xf8,0xb0,0xa1,0xe8,0xa8,0xe0,0x
f1,
0x5d,0x1d,0x55,0x84,0xcd,0x8d,0xc5,0x14,0x5c,0x1c,0x54,0x85,0xcc,0x8c,0xc4,0x
15,
0xbd,0xfd,0xb5,0xa4,0xed,0xad,0xe5,0xf4,0xbc,0xfc,0xb4,0xa5,0xec,0xac,0xe4,0x
f5,
0x39,0x79,0x31,0x20,0x69,0x29,0x61,0x70,0x38,0x78,0x30,0x21,0x68,0x28,0x60,0x
71,
0xb7,0xf7,0xbf,0xa2,0xe7,0xa7,0xef,0xf2,0xba,0xfa,0xb2,0xaf,0xea,0xaa,0xe2,0x
ff]

  val table2 = Vector.fromList [
0x00,0x01,0x02,0x03,0x04,0x05,0x06,0x07,0x09,0x08,0x0b,0x0a,0x0d,0x0c,0x0f,0x
0e,
0x12,0x13,0x10,0x11,0x16,0x17,0x14,0x15,0x1b,0x1a,0x19,0x18,0x1f,0x1e,0x1d,0x
1c,
0x24,0x25,0x26,0x27,0x20,0x21,0x22,0x23,0x2d,0x2c,0x2f,0x2e,0x29,0x28,0x2b,0x
2a,
0x36,0x37,0x34,0x35,0x32,0x33,0x30,0x31,0x3f,0x3e,0x3d,0x3c,0x3b,0x3a,0x39,0x
38,
0x49,0x48,0x4b,0x4a,0x4d,0x4c,0x4f,0x4e,0x40,0x41,0x42,0x43,0x44,0x45,0x46,0x
47,
0x5b,0x5a,0x59,0x58,0x5f,0x5e,0x5d,0x5c,0x52,0x53,0x50,0x51,0x56,0x57,0x54,0x
55,
0x6d,0x6c,0x6f,0x6e,0x69,0x68,0x6b,0x6a,0x64,0x65,0x66,0x67,0x60,0x61,0x62,0x
63,
0x7f,0x7e,0x7d,0x7c,0x7b,0x7a,0x79,0x78,0x76,0x77,0x74,0x75,0x72,0x73,0x70,0x
71,
0x92,0x93,0x90,0x91,0x96,0x97,0x94,0x95,0x9b,0x9a,0x99,0x98,0x9f,0x9e,0x9d,0x
9c,
0x80,0x81,0x82,0x83,0x84,0x85,0x86,0x87,0x89,0x88,0x8b,0x8a,0x8d,0x8c,0x8f,0x
8e,
0xb6,0xb7,0xb4,0xb5,0xb2,0xb3,0xb0,0xb1,0xbf,0xbe,0xbd,0xbc,0xbb,0xba,0xb9,0x
b8,
0xa4,0xa5,0xa6,0xa7,0xa0,0xa1,0xa2,0xa3,0xad,0xac,0xaf,0xae,0xa9,0xa8,0xab,0x
aa,
0xdb,0xda,0xd9,0xd8,0xdf,0xde,0xdd,0xdc,0xd2,0xd3,0xd0,0xd1,0xd6,0xd7,0xd4,0x
d5,
0xc9,0xc8,0xcb,0xca,0xcd,0xcc,0xcf,0xce,0xc0,0xc1,0xc2,0xc3,0xc4,0xc5,0xc6,0x
c7,
0xff,0xfe,0xfd,0xfc,0xfb,0xfa,0xf9,0xf8,0xf6,0xf7,0xf4,0xf5,0xf2,0xf3,0xf0,0x
f1,
0xed,0xec,0xef,0xee,0xe9,0xe8,0xeb,0xea,0xe4,0xe5,0xe6,0xe7,0xe0,0xe1,0xe2,0x
e3]

in

  fun tab0 0  = 5
    | tab0 1  = 0
    | tab0 2  = 1
    | tab0 3  = 2
    | tab0 4  = 3
    | tab0 5  = 4
    | tab0 6  = 0
    | tab0 7  = 1
    | tab0 8  = 2
    | tab0 9  = 3
    | tab0 10 = 4
    | tab0 _  = raise Impossible

  fun tab3 0 = 0wx00 : W32.word
    | tab3 1 = 0wx24
    | tab3 2 = 0wx49
    | tab3 3 = 0wx6d
    | tab3 4 = 0wx92
    | tab3 5 = 0wxb6
    | tab3 6 = 0wxdb
    | tab3 7 = 0wxff
    | tab3 n = tab3 (n mod 8)

  (* substitutions above *)
  fun tab1 n = W32.fromInt (Vector.sub (table1, n))
  fun tab2 n = W32.fromInt (Vector.sub (table2, n))

  (* reverse bits *)
  fun tab4 n =
    let
      fun set i = W32.<<(0w1, Word.fromInt i)
      fun b i = (if W32.andb(n, set i) > 0w0 then
                   set (7 - i) else 0w0)
    in
      b 0 + b 1 + b 2 + b 3 + b 4 + b 5 + b 6 + b 7
    end

  (* reverse bits, then not *)
  fun tab5 n =
    W32.xorb(tab4 n, 0wxFF)

  val tab1w = tab1 o W32.toIntX
  val tab2w = tab2 o W32.toIntX
  val tab3w = tab3 o W32.toIntX

end

(* this functional takes a table as its
   first parameter. It is used to generate
   titlekey1 and titlekey2 *)
fun decode table (enc    : key,
                  pk     : key) : key =
  let

    fun im x = w32 (sub (pk, x))
    val t1 = im 0 + 0w256
    val t2 = im 1
    val t3 = im 5 * (0w256*0w256*0w256) +
             im 4 * (0w256*0w256) +
             im 3 * (0w256) +
             im 2
    val t4 = im 2 mod 0w8

    val t3 = (t3 + 0w4) * 0w2 - t4

    fun l1 (_, 5, k) = Vector.fromList (rev k)
      | l1 ((t1, t2, t3, t5), n, k) =
      let
        val t4 = W32.xorb (tab3w t1, tab2w t2)
        val t2 = t1 div 0w2
        val t1 = W32.xorb(W32.<< (W32.andb(t1, 0w1), 0w8), t4)
        val t4 = tab4 t4
        val t6 =
          (W32.xorb(W32.xorb(W32.xorb (t3 div 0w8, t3) div 0w2, t3) div
0w256,
                    t3) div 0w32) mod 0w256
        val t3 = W32.orb(t3 * 0w256, t6)
        val t6 = table t6
        val t5 = t5 + t6 + t4
        val res = t5 mod 0w256
        val t5 = t5 div 0w256
      in
        l1 ((t1, t2, t3, t5), n + 1, res :: k)
      end

    val k = l1 ((t1, t2, t3, 0w0), 0, nil)

    fun l2 (~1, key) = key : W8.word vector
      | l2 (n, key) =
      l2 (n - 1,
          modify (key, tab0 (n + 1),
                  W8.fromInt
                  (W32.toInt
                   (W32.xorb (sub (k, tab0 (n + 1)),
                              W32.xorb (tab1 (W8.toInt (sub (key,
                                                             tab0 (n +
1)))),
                                        w32 (sub (key, tab0 n))))))))
  in
    (l2 (9, enc))
  end

val titlekey1 = decode tab4
val titlekey2 = decode tab5

fun detitlekey (tkey : key, dkey : key) : key =
  titlekey2 (tkey,
             titlekey1 (playerkey,
                        dkey))

fun descramble (sector  : W8.word vector,
                dec_key : key) =
  let
    fun sec x = w32 (sub (sector, x))
    fun key x = w32 (sub (dec_key, x))

    val t1 = W32.orb(0wx100,W32.xorb(key 0, sec 0x54))
    val t2 = W32.xorb(key 1, sec 0x55)

    val t3 = W32.xorb
      (key 5 * (0w256*0w256*0w256) +
       key 4 * (0w256*0w256) +
       key 3 * (0w256) +
       key 2,
       sec 0x59 * (0w256*0w256*0w256) +
       sec 0x58 * (0w256*0w256) +
       sec 0x57 * (0w256) +
       sec 0x56)

    val t4 = t3 mod 0w8

    val t3 = (t3 + 0w4) * 0w2 - t4

    fun foldme (_, b, ((t1, t2, t3, t5), l)) =
      let
        val t4 = W32.xorb(tab2w t2, tab3w t1)
        val t2 = t1 div 0w2
        val t1 = W32.xorb(W32.andb(t1, 0w1) * 0w256, t4)
        val t4 = tab5 t4
        val t6 =
          (W32.xorb(W32.xorb(W32.xorb (t3 div 0w8, t3) div 0w2, t3) div
0w256,
                    t3) div 0w32) mod 0w256
        val t3 = W32.orb(t3 * 0w256, t6)

        val t6 = tab4 t6

        val t5 = t4 + t5 + t6

      in
        ( (t1, t2, t3, t5 div 0w256),
         W8.xorb(w8 (tab1 (W8.toInt b)),
                 w8 t5) :: l )
      end

  in

    Vector.concat [Vector.extract (sector, 0, SOME 0x80),
                   Vector.fromList (rev (#2
                                         (Vector.foldli foldme
                                          ((t1, t2, t3, 0w0), nil)
                                          (sector, 0x80, NONE))))]

  end

end


Sent via Deja.com http://www.deja.com/
Before you buy.

------------------------------

From: "Paul Pires" <[EMAIL PROTECTED]>
Subject: Re: Diffie-Hellman C-sample?
Date: Wed, 6 Sep 2000 21:02:47 -0700


<[EMAIL PROTECTED]> wrote in message news:8p6v0b$6ij$[EMAIL PROTECTED]...
> In article <05Ct5.8796$[EMAIL PROTECTED]>,
>   "Verd" <[EMAIL PROTECTED]> wrote:
> > Dear all,
> >
> > Right now I'm looking for some materials on Diffie-Hellman
> implementation on
> > C language.
> >  Could anyone of you recommend me some samples, or materials?
> > It's not easy to implement that algorithm if there is enough time,
> but I
> > have
> > only 48 hours or so.
> > I hope your helps.
> > Thanks
> >
> > With best wishes...
> > Gogh..
> >
> > P.S.: I hope this is the correct n/g to ask such a question, if it
> turns
> > out the other way round, pls let me know ;)
>
> What exactly do you want?  I can wip up some C code that uses MPI if
> you like ... Perhaps during the weekend.  If you need it in 2 days send
> 300$ my way :) hehehehe...

Charge more....Much more...

Paul

>
> Tom
>
>
> Sent via Deja.com http://www.deja.com/
> Before you buy.





------------------------------

From: Michael Brown <[EMAIL PROTECTED]>
Crossposted-To: alt.security.pgp
Subject: Re: could you please tell me how this calculation has been obtained ?
Date: Thu, 07 Sep 2000 16:37:05 +1200

I'd guess it'd be based somehow on the number of public keys on
keyservers. That's how I would do it.
jungle wrote:
> 
> hi mike,
> 
> in the recent [ 25 aug ] ap article by peter svensson, he is writing,
> wallach said, that pgp is used by 7 million people ...
> 
> could you please tell me how this calculation has been obtained ?
> how accurate this number is ?
> 
> --
> thanks, richard

------------------------------

From: jungle <[EMAIL PROTECTED]>
Crossposted-To: alt.security.pgp
Subject: Re: could you please tell me how this calculation has been obtained ?
Date: Thu, 07 Sep 2000 01:24:41 -0400

thanks for your contribution ...
I originally directed this e-mail to :

TO [EMAIL PROTECTED] 
CC [EMAIL PROTECTED]

of NAI, and copy it to 2 forums ...

I'm waiting for NAI [ official ] management response ...

Michael Brown wrote:
> 
> I'd guess it'd be based somehow on the number of public keys on
> keyservers. That's how I would do it.
> jungle wrote:
> >
> > hi mike,
> >
> > in the recent [ 25 aug ] ap article by peter svensson, he is writing,
> > wallach said, that pgp is used by 7 million people ...
> >
> > could you please tell me how this calculation has been obtained ?
> > how accurate this number is ?
> >
> > --
> > thanks, richard



------------------------------

From: Jacques Therrien <[EMAIL PROTECTED]>
Crossposted-To: alt.security.pgp,comp.security.pgp.discuss
Subject: Free Upgrade PGP Personal Privacy 6.5.8 - how?
Date: Thu, 07 Sep 2000 05:24:51 GMT

WAS:  PGP 6.5.8 test: That's NOT enough !!!

In article <8oklam$7oc$[EMAIL PROTECTED]>, Philip Stromer 
<[EMAIL PROTECTED]> wrote:

> In article <8oe9gi$n89$[EMAIL PROTECTED]>,
> [EMAIL PROTECTED] wrote:
> 
> > Aye, for once we agree.  PGP have handled this problem extremely
> > poorly from both a technical and PR perspective.
> >
> > I can't see a "pretty" way forward...
> 
> I spoke to some PGP "spin doctor" yesterday and he said if I have PGP
> Personal Privacy 6.5.3, I'm safe since it doesn't even have a back door
> for any corporate types.  Is this accurate, or baloney?
  ------ snip ------

Philip,

This is "baloney".  While PGP Personal Privacy 6.5.3 (which I also use) 
cannot "create" ADKs [as PGP versions used by corporate clients do -- 
these are not backdoors], it has exactly the same problems as 
PGPfreeware 6.5.3 as far as the ADK weakness is concerned.  It will 
encrypt to a second public key specified by a bogus ADK which is not in 
the signed portion of the key.

It too needs the Hot Fix, or get the upgrade to 6.5.8.
______________

NAI announced present owners could get a free upgrade to PGP Personal 
Privacy 6.5.8, however we would have to get it from McAfee.  Well, what 
I expected from previous experience happened.

I submitted my request to <[EMAIL PROTECTED]>, and McAfee replied 
that I can get a free download [PGPfreeware] from "www.pgpi.org" -- the 
usual nonsense!!!

I have repeated the request, explaining to them the difference between 
the two (to the people I bought it from!!?!&?%) -- with a copy to NAI. I 
have not as yet received a reply to my second request.

*** Has any one been able to get the free copy we are owed to upgrade to 
PGP Personal Privacy 6.5.8?  If so please tell us how?  Details please.

*** Are others trying to or about to try to get the free upgrade?  We 
should perhaps all get together on this, and try to solve this problem 
once and for all.

I am really fed up with the bureaucratic run-around and confusion inside 
NAI and McAfee on this.  NAI should solve the problem with McAfee before 
telling us to get it from there, and provide us with the name of someone 
in McAfee who understands the problem and their telephone number (email 
address, fax number, or whatever).

It is not up to the paying customers to solve their internal problems  - 
and they obviously do have serious ones.  The onus to provide upgrades 
(especially for correcting serious errors like this one) lies normally 
with the developer (NAI), rather than a reseller (McAfee).  The 
developer should at least verify that the upgrade is indeed available.

If they had the good sense of issuing registration numbers for retail 
commercial software (as other developers do, including shareware 
authors), we would not have this type of problem.

As every shareware author does, they could just post the upgrade on the 
Web, and only those with a valid registration number would be able to 
use those downloads without paying.

Or simply ask people for their registration number when they try to 
download.  Problem solved.


Cheers,

Jacques

------------------------------

From: "Douglas A. Gwyn" <[EMAIL PROTECTED]>
Subject: Re: Carnivore article in October CACM _Inside_Risks
Date: Thu, 07 Sep 2000 01:57:34 -0400

Mok-Kong Shen wrote:
> "Douglas A. Gwyn" wrote:
> > What isn't so obvious is how we
> > let the FBI get away with maintaining that they have some
> > sort of right to be able to wire-tap.
> As far as I know, in Germany a goverment agency may, with
> the consent of a judge, leagally do wiretapping or install
> a (secret) microphone. If the same applies to US, ...

You seem to have missed the point; I didn't say, "right to
wiretap", I said "right to be able to wiretap".  I don't
dispute the former (when approved by a judge for probable
cause), but I do dispute the latter.  Should we require
builders to install listening devices in every house in
order to facilitate bugging, or auto manufacturers to plant
tracking devices in every car they make so that they can be
switched on by law enforcement if the need arises?  Who is
supposed to be in charge, the people or their government?

------------------------------

From: David A Molnar <[EMAIL PROTECTED]>
Subject: Re: on a ligher note...
Date: 7 Sep 2000 05:38:34 GMT

[EMAIL PROTECTED] wrote:
>> Because computers more obviously refuse to do what their
>> programmers tell them to do.

> Actually, after reading the auction, my question was answered by the
> fact that the machine in question is named Mario, after a somewhat
> famous hockey player from the area. ;)

oh. and I thought it was the plumber. 

ObCrypto : what crypto-related reading material last kept you up all
night?

-David

------------------------------

From: "Douglas A. Gwyn" <[EMAIL PROTECTED]>
Subject: Re: Losing AES Candidates Could Be a Good Bet?
Date: Thu, 07 Sep 2000 02:13:14 -0400

"SCOTT19U.ZIP_GUY" wrote:
> Becasue they most likely would have never gotten in front of the
> public unless the NSA precieved them as weak.

So, how many of the original AES submissions were suppressed
by the NSA, anyway?  And one wonders by what mechanism, since
NIST was running the show.

------------------------------

From: "Douglas A. Gwyn" <[EMAIL PROTECTED]>
Subject: Re: Ciphertext Randomness/Statistical Tests
Date: Thu, 07 Sep 2000 02:15:14 -0400

Tim Tyler wrote:
> This is saying that strength implies randomeness - not that randomness
> implies strength, as you appear to be suggesting.

However, the opposite is closer to the truth.

------------------------------

From: [EMAIL PROTECTED] (John Savard)
Subject: Re: Losing AES Candidates Could Be a Good Bet?
Date: Thu, 07 Sep 2000 06:13:44 GMT

On Wed, 6 Sep 2000 14:12:26 -0700, "David C. Barber" <[EMAIL PROTECTED]>
wrote, in part:

>The winning candidate will continue to be subjected to analysis and attack
>for years to come, while the also-rans will likely quickly drop off the
>radar screens of most people.

>Call it: Security Through Lack of Interest.  :^)

This principle, if not the specific idea, has been suggested by Terry
Ritter. Of course, that depends on whether the attacks might not work
on other ciphers too. Also, depending on the final choice, one or more
of the also-rans might still be to the taste of some people. I think
that SAFER+, despite not being a finalist, will be used for a while:
and both Twofish and MARS will see considerable service regardless of
which of the five finalists wins.

John Savard
http://home.ecn.ab.ca/~jsavard/crypto.htm

------------------------------

From: [EMAIL PROTECTED] (John Savard)
Subject: Re: RSA Patent Dead Today
Date: Thu, 07 Sep 2000 06:18:27 GMT

On 06 Sep 2000 16:04:50 +0100, Shellac
<[EMAIL PROTECTED]> wrote, in part:

>FWIW, I reckon they did this to spoil parties arranged for the 20th
>;-)

*My* guess is that, because even the second edition of Bruce
Schneier's super-popular book, Applied Cryptography, was published
before the changes in the patent law that extended their patent a few
weeks till the 20th of September, they didn't want to get into the
messy business of enforcing their patent against thousands of
unwitting violators.

John Savard
http://home.ecn.ab.ca/~jsavard/crypto.htm

------------------------------

From: [EMAIL PROTECTED] (Mack)
Date: 07 Sep 2000 07:08:25 GMT
Subject: Re: 4x4 s-boxes

>
>[EMAIL PROTECTED] wrote:
>> [EMAIL PROTECTED] (Mack) wrote:
>> > Tim Tyler wrote:
>> > >Douglas A. Gwyn <[EMAIL PROTECTED]> wrote:
>> > >: Terry Ritter wrote:
>> > >
>> > >:> While the FT originally defined "bent," most modern treatments use
>> > >:> the FWT.
>> > >
>> > >: ?  What does the definition of bent function look like in terms
>> > >: of Walsh transforms?
>> > >
>> > >Bent function <-> "All entries in the WT have the same magnitude".
>> > >
>> > >: Is it as simple as the FT version?
>> > >
>> > >It's extremely simple.
>> > >
>> > >:> As far as I know, in modern open cryptography, these concepts
>> > >:> [maximal nonlinearity and uniform Fourier weights] are the same.
>> > >
>> > >: They can't be the same, because the latter defines a bent function
>> > >: but you guys are claiming that bent functions aren't maximally
>> > >: nonlinear.
>> > >
>> > >Only Tom's claiming that AFAICS.  Everyone else appears to be
>> > >disagreeing.
>[snip]
>
>> Mack:
>> > My specific claim was that Bent functions only exist on equations
>> > of 2*n variables, are not balanced, and are maximally non-linear.
>> > Hence cannot produce bijective s-boxes.
>> 
>> You guys are all wrong.  In the original paper were "bent" was defined
>> there was no mention of non-balanced functions.
>
>I assume you're referring to
>
>[15] O. S. Rothaus,
>     "On 'bent" functions,"
>     Journal of Combinatorial Theory, Ser. A 20 (1976), pp. 300-305
>
>? I don't have a copy of that, but presumably if it doesn't mention
>non-balanced functions, then it isn't saying anything about whether bent
>functions are balanced or not.
>

Tom has found his error and admitted it.  That paper does
count the zeros of a function.  ie. weight and hence its
balanced-ness.

>> In fact "bent" doesn't refer to maximal non-linear functions at all.
>> 
>> Read up the papers, specially "Perfect Nonlinear Sboxes", Kaisa Nyberg,
>> Eurocrypt '91 P379.  The term "bent" is defined in section 2.
>
>- From that paper:
>
># In [12] Meier and Staffelbach discuss perfect nonlinear Boolean functions,
># which are defined to be at maximum distance from linear structures. These
># functions are the same as the previously known bent functions [15].
>
>That seems to be perfectly consistent with what Mack and Tim Tyler have
>been saying, and *not* consistent with '"bent" doesn't refer to maximal
>non-linear functions at all'.

For the record toms error appears to have been calculating the
maximum of the walsh transform instead of all walsh transforms being
equal.

>
>- -- 
>David Hopwood <[EMAIL PROTECTED]>
>


Mack
Remove njunk123 from name to reply by e-mail

------------------------------


** FOR YOUR REFERENCE **

The service address, to which questions about the list itself and requests
to be added to or deleted from it should be directed, is:

    Internet: [EMAIL PROTECTED]

You can send mail to the entire list (and sci.crypt) via:

    Internet: [EMAIL PROTECTED]

End of Cryptography-Digest Digest
******************************

Reply via email to