MD5Stream.st
author Claus Gittinger <cg@exept.de>
Sat, 10 Oct 2009 22:47:02 +0200
changeset 12204 e95118ee583f
parent 10783 d98a226dee25
child 12256 5d87f49ba760
permissions -rw-r--r--
changed: #documentation

"
 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 
                        80000 Kb/s on a 2Ghz Duo
                        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
"
                                                                [exBegin]
    Test Vectors (from FIPS PUB 180-1); results are:

    '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]
                                                                [exEnd]


                                                                [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]
"
! !

!MD5Stream class methodsFor:'initialization'!

initialize
    |ctxSize|

%{
    ctxSize = __mkSmallInteger(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 class methodsFor:'testing'!

testVector

    ^ #( 
            ('abc'
              #[16r90 16r01 16r50 16r98 16r3C 16rD2 16r4F 16rB0 16rD6 16r96 16r3F 16r7D 16r28 16rE1 16r7F 16r72])

            ('abcdbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq'
             #[16r82 16r15 16rEF 16r07 16r96 16rA2 16r0B 16rCA 16rAA 16rE1 16r16 16rD3 16r87 16r6C 16r66 16r4A])
        ) copyWith: 
        (Array with:(String new:1000000 withAll:$a)
               with:#[16r77 16r07 16rD6 16rAE 16r4E 16r02 16r7C 16r70 16rEE 16rA2 16rA9 16r35 16rC2 16r29 16r6F 16r21])


    "
      self test
    "
! !

!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"
!

nextPutBytes:count from:anObject startingAt:start
    "update the hash value with count bytes from an object starting at index start.
     The object must have non-pointer indexed instvars 
     (i.e. be a ByteArray, String, Float- or DoubleArray),
     or an externalBytes object (with known size)"

%{
    int len, offs;
    int objSize, nInstVars, nInstBytes;
    char *extPtr;

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

        len = __intVal(count);
        offs = __intVal(start) - 1;

        if (__isExternalBytesLike(anObject)) {
            OBJ sz;

            nInstBytes = 0;
            extPtr = (char *)__externalBytesAddress(anObject);
            sz = __externalBytesSize(anObject);
            if (__isSmallInteger(sz)) {
                objSize = __intVal(sz);
            } else {
                objSize = 0; /* unknown */
            }
        } else {
            OBJ oClass;

            oClass = __Class(anObject);
            switch (__intVal(__ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
                case BYTEARRAY:
                case WORDARRAY:
                case LONGARRAY:
                case SWORDARRAY:
                case SLONGARRAY:
                case FLOATARRAY:
                case DOUBLEARRAY:
                    break;
                default:
                    goto bad;
            }
            nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
            nInstBytes = OHDR_SIZE + __OBJS2BYTES__(nInstVars);
            objSize = __Size(anObject) - nInstBytes;
            extPtr = (char *)__byteArrayVal(anObject);
        }
        if ((offs >= 0) && (len >= 0) && (objSize >= (len + offs))) {
            MD5Update(ctx, extPtr+offs, len);
            RETURN (count);
        }
    }
bad: ;
%}.

    ^ self primitiveFailed
! !

!MD5Stream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/MD5Stream.st,v 1.8 2009-10-10 20:47:02 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/MD5Stream.st,v 1.8 2009-10-10 20:47:02 cg Exp $'
! !

MD5Stream initialize!