HashStream.st
author Claus Gittinger <cg@exept.de>
Wed, 04 Jan 2012 19:55:36 +0100
changeset 13889 f335cf6d5783
parent 13366 0e1bdf4f4156
child 13900 0dc22ed6d46f
permissions -rw-r--r--
added: #hashSize

"
 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' }"

Stream subclass:#HashStream
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'System-Crypt-Hashing'
!

!HashStream 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
"
    Abstract class. Subclasses generate hash values used as checksums
    or for generating cryptographic signatures.

    [author:]
        Stefan Vogel

    [see also:]
        SHA1Stream MD5Stream
"
! !

!HashStream class methodsFor:'instance creation'!

new
    "have to re-allow new - it was disabled in Stream"
    ^ self basicNew initialize


!

random
    "create a random number generator using myself"

    ^ HashRandom with:self

    "
     SHA1Stream random next
    "

    "Modified: / 12.11.1999 / 17:21:17 / stefan"
! !

!HashStream class methodsFor:'compatibility - squeak'!

hashMessage:aStringOrByteArrayOrStream
    "SQUEAK compatibility 
        - but this is a bad choice - squeak uses #digestMessage: at the instance side"

    ^ self hashValueOf:aStringOrByteArrayOrStream
! !

!HashStream class methodsFor:'queries'!

canStream
    "simple hash functions (squeak-ported) cannot stream.
     Use hashFunction: there"

    ^ true
!

hashSize
    self subclassResponsibility

    "Created: / 04-01-2012 / 19:22:32 / cg"
! !

!HashStream class methodsFor:'self tests'!

test
    "test against testVector"

    self testVector do:[:pair |
        |data expectedHash expectedHashBytes hashStream|

        data := pair first.
        expectedHash := pair second.
        expectedHash isString ifTrue:[
            expectedHashBytes := ByteArray fromHexString:expectedHash
        ] ifFalse:[
            expectedHashBytes := expectedHash
        ].

        "/ non-stream interface must be implemented by all
        self assert:(self hashValueOf:data) = expectedHashBytes message:'Test failed'.
        self canStream ifTrue:[
            hashStream := self new.
            hashStream nextPut:data.
            self assert:hashStream hashValue = expectedHashBytes message:'Test failed'
        ].
    ].

    "
        MD5Stream test.
        SHA1Stream test.
        RipeMD160Stream test.
    "
!

testVector
    "define a testvector to test the implementation"

    ^ self subclassResponsibility
! !

!HashStream class methodsFor:'utilities'!

digestMessage:aStringOrByteArrayOrStream
    ^ self hashValueOf:aStringOrByteArrayOrStream
!

hashValueOf:aStringOrByteArrayOrStream
    |hashStream|

    hashStream := self new.
    aStringOrByteArrayOrStream readStream copyToEndInto:hashStream.

    ^ hashStream hashValue

    "
     MD5Stream hashValueOf:'BlaBlaBla'
     MD5Stream hashValueOf:('makefile' asFilename readStream)
     MD5Stream hashValueOf:('BlaBlaBla' readStream)
    "
!

hashValueOfFile:aFilename
    |hash|

    aFilename asFilename readingFileDo:[:readStream|
        readStream binary.
        hash := self hashValueOf:readStream.
    ].
    ^ hash

    "
     MD5Stream hashValueOfFile:'makefile'
    "
! !

!HashStream methodsFor:'accessing'!

contents
    "return the entire contents of the stream
     - this is our hashValue."

    ^ self hashValue

    "Created: / 17.3.1999 / 15:10:03 / stefan"
! !

!HashStream methodsFor:'not implemented'!

next
    ^ self shouldNotImplement

    "Created: / 17.3.1999 / 15:11:03 / stefan"
! !

!HashStream methodsFor:'operations'!

digestMessage:bytes
    "answer the digest of bytes"

    self reset.
    self nextPutAll:bytes.

    ^ self contents.

    "
        SHA1Stream new 
                digestMessage:'123456789abcdefg';
                digestMessage:'123456789abcdefg'

        (SHA1Stream new hmac key:'123456') 
                digestMessage:'123456789abcdefg';
                digestMessage:'123456789abcdefg'

        (SHA1Stream new hmac key:'123456') 
                nextPutAll:'123456789abcdefg';
                contents
    "
!

hmac
    "answer a hmac stream with myself"

    ^ HmacStream on:self

    "
        (SHA1Stream new hmac key:'exampleKey') digestMessage:'message to generate MAC of'
    "
!

reset
    "initialize to a clean state"

    ^ self subclassResponsibility
! !

!HashStream methodsFor:'queries'!

blockSize
    "the class knows about the basic block size"

    ^ self class blockSize

    "Created: / 18.3.1999 / 10:17:02 / stefan"
!

hashSize
    "the class knows about the basic hash size"

    ^ self class hashSize

    "Created: / 18.3.1999 / 10:17:12 / stefan"
    "Modified: / 15.10.1999 / 11:53:20 / stefan"
!

hashValue
    "retunr the value of the computeted hash"

    ^ self subclassResponsibility
!

isReadable
    "return true, if reading is supported by the recevier.
     Always return false here"

    ^ false

    "Modified: / 17.3.1999 / 15:06:09 / stefan"
!

isWritable
    "return true, if writing is supported by the recevier.
     Always return true here"

    ^ true

    "Created: / 17.3.1999 / 15:05:49 / stefan"
! !

!HashStream methodsFor:'testing'!

atEnd
    "return true if the end of the stream has been reached;
    this is never reached"

    ^ false

    "Created: / 17.3.1999 / 15:08:55 / stefan"
! !

!HashStream methodsFor:'writing'!

nextPut:anObject
    "add the hash of anObject to the computed hash so far.
     anObject can be a Character, SmallInteger, or Character-, Byte-
     Integer-Array"

    ^ self subclassResponsibility
!

nextPutAll:aCollection
    "Hash streams handle Strings and ByteArrays in nextPut:"

    aCollection isByteCollection ifTrue:[
        self nextPut:aCollection.
    ] ifFalse:[
        super nextPutAll:aCollection
    ].

    "Created: / 14.10.1999 / 11:22:50 / stefan"
!

nextPutBytes:count from:anObject startingAt:start
    "write count bytes from an object starting at index start.
     Return the number of bytes written.
     The object must have non-pointer indexed instvars 
     (i.e. be a ByteArray, String, Float- or DoubleArray).     
     Use with care - non object oriented i/o.
     This is provided for compatibility with externalStream;
     to support binary storage.

     Redefined, because HashStream encodes integers as 4 bytes.
     You should implement this method in subclasses"

    |idx|

    "self subclassResponsibility"

    idx := start.
    1 to:count do:[:i |
        self nextPut:(anObject byteAt:idx) asCharacter.
        idx := idx + 1
    ].
    ^ count
! !

!HashStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/HashStream.st,v 1.15 2012-01-04 18:55:36 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/HashStream.st,v 1.15 2012-01-04 18:55:36 cg Exp $'
! !