MD5Stream.st
author penk
Wed, 19 Feb 2003 14:01:49 +0100
changeset 7041 1c0516e1f72d
parent 6864 0d5bd7218853
child 7042 dbb7898901e3
permissions -rw-r--r--
add testVektors

"
 COPYRIGHT (c) 1999 by eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"



"{ Package: 'stx:libbasic' }"

HashStream subclass:#MD5Stream
	instanceVariableNames:'hashContext'
	classVariableNames:'HashSize ContextSize'
	poolDictionaries:''
	category:'System-Crypt-Streams'
!

!MD5Stream primitiveDefinitions!
%{

/*
 * includes, defines, structure definitions
 * and typedefs come here.
 */

#include "md5.h"

%}
! !

!MD5Stream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1999 by eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


!

documentation
"
    Generate a MD5 hash value as defined in RFC 1321.
    This may be used as checksum
    or for generating cryptographic signatures.

    performance: roughly 
			27200 Kb/s on a 1.2Ghz Athlon
			12600 Kb/s on a 400Mhz PIII
			 9150 Kb/s on a 300Mhz Sparc.
    [author:]
	Stefan Vogel

    [see also:]
	SHA1Stream

    [class variables:]
	HashSize        size of returned hash value
	ContextSize     (implementation) size of hash context

    [instance variables:]
	hashContext     (implementation) 
			internal buffer for computation of the hash value
"
!

examples
"
  Test Vectors:
        'abc'

          #[90 1 50 98 3C D2 4F B0 D6 96 3F 7D 28 E1 7F 72]

        'abcdbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq'
          #[82 15 EF 7 96 A2 B CA AA E1 16 D3 87 6C 66 4A]

        A million repetitions of 'a'
          #[77 7 D6 AE 4E 2 7C 70 EE A2 A9 35 C2 29 6F 21]

                                                                [exBegin]
     (MD5Stream hashValueOf:'abc') printOn:Transcript base:16. Transcript cr.
                                                                [exEnd]

                                                                [exBegin]
     (MD5Stream hashValueOfStream:('abc' readStream)) printOn:Transcript base:16. Transcript cr.
                                                                [exEnd]

                                                                [exBegin]
    |hashStream|

    hashStream := MD5Stream new.
    hashStream nextPut:'abc'.
    hashStream hashValue printOn:Transcript base:16. Transcript cr.
    hashStream nextPut:'dbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq'.
    hashStream hashValue printOn:Transcript base:16. Transcript cr.
                                                                [exEnd]

                                                                [exBegin]
    |hashStream|

    hashStream := MD5Stream new.
    hashStream nextPut:'a' asByteArray.
    hashStream nextPut:'bc' asByteArray.
    hashStream hashValue printOn:Transcript base:16. Transcript cr.
    hashStream nextPut:'dbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq' asByteArray.
    hashStream hashValue printOn:Transcript base:16. Transcript cr.
                                                                [exEnd]

                                                                [exBegin]
    |hashStream|

    hashStream := MD5Stream new.
    1000000 timesRepeat:[ hashStream nextPut:$a ].
    hashStream hashValue printOn:Transcript base:16. Transcript cr.
                                                                [exEnd]

                                                                [exBegin]
    |hashStream|

    hashStream := MD5Stream new.
    hashStream nextPut:'a'.
    hashStream hashValue printOn:Transcript base:16. Transcript cr.
                                                                [exEnd]

                                                                [exBegin]
    |hashStream|

    hashStream := MD5Stream new.
    hashStream nextPut:$a.
    hashStream hashValue printOn:Transcript base:16. Transcript cr.
                                                                [exEnd]

                                                                [exBegin]
    |hashStream|

    hashStream := MD5Stream new.
    hashStream nextPut:'abc'.
    hashStream hashValue printOn:Transcript base:16. Transcript cr.
    hashStream reset.
    hashStream nextPut:'abc'.
    hashStream hashValue printOn:Transcript base:16. Transcript cr.
                                                                [exEnd]

  timing throughput:
                                                                [exBegin]
    |hashStream n t|

    hashStream := MD5Stream new.
    n := 1000000.
    t := Time millisecondsToRun:[
            n timesRepeat:[
                hashStream nextPutAll:'12345678901234567890123456789012345678901234567890'.
            ].
         ].
    t := (t / 1000) asFloat.
    Transcript show:t; show:' seconds for '; show:(50*n/1024) asFloat; showCR:' Kb'.
    Transcript show:(n*50/1024 / t); showCR:' Kb/s'
                                                                [exEnd]
"
!

testVectors
"
  Test Vectors:
        'abc'

          #[90 1 50 98 3C D2 4F B0 D6 96 3F 7D 28 E1 7F 72]

        'abcdbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq'
          #[82 15 EF 7 96 A2 B CA AA E1 16 D3 87 6C 66 4A]

        A million repetitions of 'a'
          #[77 7 D6 AE 4E 2 7C 70 EE A2 A9 35 C2 29 6F 21]
"
    |hashStream result stream|

    stream := WriteStream on:''.
    hashStream := MD5Stream new.
    hashStream nextPut:'abc'.
    result := hashStream hashValue.
    result printOn:stream base:16.
    stream contents = '#[90 1 50 98 3C D2 4F B0 D6 96 3F 7D 28 E1 7F 72]' ifFalse:[
        self error.
    ].
    stream reset.
    hashStream := MD5Stream new.
    hashStream nextPut:'abcdbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq'.
    result := hashStream hashValue.
    result printOn:stream base:16.
    stream contents = '#[82 15 EF 7 96 A2 B CA AA E1 16 D3 87 6C 66 4A]' ifFalse:[
        self error.
    ].
    stream reset.
    hashStream := MD5Stream new.
    1000000 timesRepeat:[ hashStream nextPut:$a ].
    result := hashStream hashValue.
    result printOn:stream base:16.
    stream contents = '#[77 7 D6 AE 4E 2 7C 70 EE A2 A9 35 C2 29 6F 21]' ifFalse:[
        self error.
    ].
    stream reset.
    result := MD5Stream hashValueOf:'abc'.
    result printOn:stream base:16.
    stream contents = '#[90 1 50 98 3C D2 4F B0 D6 96 3F 7D 28 E1 7F 72]' ifFalse:[
        self error.
    ].
"
self testVectors
"
! !

!MD5Stream class methodsFor:'initialization'!

initialize
    |ctxSize|

%{
    ctxSize = __MKSMALLINT(sizeof(MD5_CTX));
%}.
    ContextSize := ctxSize.
    HashSize := 16.

    "
	self initialize
    "



! !

!MD5Stream class methodsFor:'queries'!

blockSize
    "return the block size used internally by the compression function"

    ^ 64

    "Created: / 18.3.1999 / 08:36:44 / stefan"
!

hashSize
    "return the size of the hashvalue returned by instances of this class"

    ^ HashSize

    "Created: / 18.3.1999 / 08:02:16 / stefan"
! !

!MD5Stream methodsFor:'initialization'!

initialize

    hashContext := ByteArray new:ContextSize.
    self reset.

    "Modified: / 18.3.1999 / 08:03:42 / stefan"
! !

!MD5Stream methodsFor:'positioning'!

reset
   "reset the stream in order to compute a new hash value"

%{
   if (__isNonNilObject(__INST(hashContext)) &&
       __qClass(__INST(hashContext)) == @global(ByteArray) &&
       __byteArraySize(__INST(hashContext)) == sizeof(MD5_CTX)
   ) {
	MD5_CTX *ctx = 
	    (MD5_CTX *)__ByteArrayInstPtr(__INST(hashContext))->ba_element;

	MD5Init(ctx);
	RETURN(self);
   }
%}.
   ^ self primitiveFailed



! !

!MD5Stream methodsFor:'queries'!

hashValue
    "Get the value hashed so far.
     The context is kept, so that more objects may be hashed after
     retrieving a hash value"


    |digest|

    digest := ByteArray new:HashSize.

%{
    if (__isNonNilObject(__INST(hashContext)) &&
	__qClass(__INST(hashContext)) == @global(ByteArray) &&
	__byteArraySize(__INST(hashContext)) == sizeof(MD5_CTX) &&
	__isNonNilObject(digest) &&
	__qClass(digest) == @global(ByteArray) &&
	__byteArraySize(digest) == 16
    ) {
	MD5_CTX *ctx = 
	    (MD5_CTX *)__ByteArrayInstPtr(__INST(hashContext))->ba_element;
	MD5_CTX copyContext;

	memcpy(&copyContext, ctx, sizeof(copyContext));
	MD5Final(__ByteArrayInstPtr(digest)->ba_element, &copyContext);
	RETURN(digest);
    }
%}.

    ^ self primitiveFailed     
! !

!MD5Stream methodsFor:'writing'!

nextPut:anObject
  "update our hash value for anObject.
   anObject may be a String, a Character, a Smallinteger or an Array of primitive
   types like ByteArray.
  "

  |ret|

%{
   if (__isNonNilObject(__INST(hashContext)) &&
       __qClass(__INST(hashContext)) == @global(ByteArray) &&
       __byteArraySize(__INST(hashContext)) == sizeof(MD5_CTX)
   ) {
	MD5_CTX *ctx = 
	    (MD5_CTX *)__ByteArrayInstPtr(__INST(hashContext))->ba_element;

	if (__isNonNilObject(anObject)) {
	    OBJ cls =__qClass(anObject);
	    INT mask = (INT)(__ClassInstPtr(cls)->c_flags) & __MASKSMALLINT(ARRAYMASK);

	    if (cls == @global(String) || cls == @global(Symbol)) {
		/* String: omit leading '\0' */

		MD5Update(ctx, __StringInstPtr(anObject)->s_element, __stringSize(anObject));
	    } else if (mask != __MASKSMALLINT(POINTERARRAY) &&
		mask != __MASKSMALLINT(WKPOINTERARRAY) &&
		mask != __MASKSMALLINT(0)
	    ) {
		/* Byte|Integer|.... Array */

		register int n;
		char *pFirst;

		n /* nInstVars */  = __intVal(__ClassInstPtr(cls)->c_ninstvars);
		n /* nInstBytes */ = OHDR_SIZE + __OBJS2BYTES__(n /* nInstVars */);
		pFirst = (char *)(__InstPtr(anObject)) + n /* nInstBytes */;
		n /* nbytes */     = __qSize(anObject) - n /* nInstBytes */;
		MD5Update(ctx, pFirst, n);
	    } else if (cls == @global(Character)) {
		/* Character */
        
		INT val = __intVal(_characterVal(anObject));
		if (val > 255) {
		    /* Two byte character */
		    short s = val;
		    MD5Update(ctx, &s, 2);
		} else {
		    char c = val;
		    MD5Update(ctx, &c, 1);
		}
	    } else {
		ret = false;
	    }
	} else {
	    if (anObject == nil) {
		ret = false;
	    } else {
		/* SmallInteger */
                
		INT i = __intVal(anObject);
		MD5Update(ctx, &i, sizeof(INT));
	    }
	}
    }
%}.

    ret notNil ifTrue:[
	^ self primitiveFailed
    ].
                

    "Created: 22.10.1996 / 21:53:24 / stefan"
! !

!MD5Stream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/MD5Stream.st,v 1.2 2003-02-19 13:01:49 penk Exp $'
! !

MD5Stream initialize!