RegressionTests__CryptTests.st
author Claus Gittinger <cg@exept.de>
Mon, 02 Dec 2013 20:10:04 +0100
changeset 1036 c42c54df984e
parent 1035 2be1f5b478ca
child 1038 5443ea4b780e
permissions -rw-r--r--
class: RegressionTests::CryptTests changed: #test11_rsaKey

"{ Package: 'exept:regression' }"

"{ NameSpace: RegressionTests }"

TestCase subclass:#CryptTests
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'tests-Regression'
!

!CryptTests class methodsFor:'documentation'!

documentation
"
    documentation to be added.

    [author:]
        exept

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!CryptTests methodsFor:'initialize / release'!

setUp
    "common setup - invoked before testing."

    super setUp
!

tearDown
    "common cleanup - invoked after testing."

    super tearDown
! !

!CryptTests methodsFor:'tests'!

test01_crc32
    |h|

    h := CRC32Stream hashValueOf:''.
    self assert:(h = 0).

    h := CRC32Stream hashValueOf:'The quick brown fox jumps over the lazy dog'.
    self assert:(h = 16r414fa339).

    h := CRC32Stream hashValueOf:'resume'.
    self assert:(h = 16r60C1D0A0).

    h := (CRC32Stream new
                    nextPut:$r;
                    nextPut:$e;
                    nextPut:$s;
                    nextPut:$u;
                    nextPut:$m;
                    nextPut:$e;
                    hashValue).
    self assert:(h = 16r60C1D0A0).

    h := (CRC32Stream hashValueOf:#[1 2 3 4 5 6 7]).
    self assert:(h = 16r70E46888).

    h := (CRC32Stream hashValueOf:#[16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 
             16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF
             16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF
             16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF]).
    self assert:(h = 16r8CD04C73).

    h := (CRC32Stream new
                    next:100000 putAll:'12345678901234567890123456789012345678901234567890';
                    hashValue).
    self assert:(h = 16r86D7D79A).

    "
     self run:#test01_crc32
     self new test01_crc32
    "
!

test02_md5
    |h|

    h := MD5Stream hashValueOf:''.
    self assert:(h = (ByteArray fromHexString:'d41d8cd98f00b204e9800998ecf8427e')).

    h := MD5Stream hashValueOf:'The quick brown fox jumps over the lazy dog'.
    self assert:(h = (ByteArray fromHexString:'9e107d9d372bb6826bd81d3542a419d6')).

    h := MD5Stream hashValueOf:'abc'.
    self assert:(h = #[16r90 16r01 16r50 16r98 16r3C 16rD2 16r4F 16rB0   
                       16rD6 16r96 16r3F 16r7D 16r28 16rE1 16r7F 16r72]).

    h := MD5Stream hashValueOf:'abcdbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq'.
    self assert:(h = #[16r82 16r15 16rEF 16r07 16r96 16rA2 16r0B 16rCA 
                       16rAA 16rE1 16r16 16rD3 16r87 16r6C 16r66 16r4A]).

    h := (MD5Stream new
                next:1000000 put:$a;
                hashValue).
    self assert:(h = #[16r77 16r07 16rD6 16rAE 16r4E 16r02 16r7C 16r70 
                       16rEE 16rA2 16rA9 16r35 16rC2 16r29 16r6F 16r21]).

    "
     self run:#test02_md5
     self new test02_md5
    "
!

test03_sha1
    |h|

    h := SHA1Stream hashValueOf:''.
    self assert:(h = (ByteArray fromHexString:'da39a3ee5e6b4b0d3255bfef95601890afd80709')).

    h := SHA1Stream hashValueOf:'The quick brown fox jumps over the lazy dog'.
    self assert:(h = (ByteArray fromHexString:'2fd4e1c67a2d28fced849ee1bb76e7391b93eb12')).

    h := SHA1Stream hashValueOf:#[16r00 16r01 16r02 16r40 16r08 16r10 16r20 16r40 16r80
                                  16rFF 16rFE 16rFC 16rF8 16rF0 16rE0 16rC0 16r80].  
    self assert:(h = #[146 31 26 53 78 167 121 73 144 117 145 88 50 42 25 52 53 37 177 73]).

    "
     self run:#test03_sha1
     self new test03_sha1
    "

    "Modified: / 25-11-2013 / 11:42:46 / cg"
!

test04_md2
    |h|

    self 
        skipIf:(MD2Stream isBehavior not or:[MD2Stream isLoaded not]) 
        description:'MD2Stream/libcrypt is not loaded'.

    h := MD2Stream hashValueOf:''.
    self assert:(h = (ByteArray fromHexString:'8350e5a3e24c153df2275c9f80692773')).

    h := MD2Stream hashValueOf:'The quick brown fox jumps over the lazy dog'.
    self assert:(h = (ByteArray fromHexString:'03d85a0d629d2c442e987525319fc471')).

    "
     self run:#test04_md2
     self new test04_md2
    "
!

test05_md4
    |h|

    self 
        skipIf:(MD4Stream isBehavior not or:[MD4Stream isLoaded not]) 
        description:'MD4Stream/libcrypt is not loaded'.

    h := MD4Stream hashValueOf:''.
    self assert:(h = (ByteArray fromHexString:'31d6cfe0d16ae931b73c59d7e0c089c0')).

    h := MD4Stream hashValueOf:'The quick brown fox jumps over the lazy dog'.
    self assert:(h = (ByteArray fromHexString:'1bee69a46ba811185c194762abaeae90')).

    "
     self run:#test05_md4
     self new test05_md4
    "
!

test06_sha256
    |h|

    self 
        skipIf:(SHA256Stream isBehavior not or:[SHA256Stream isLoaded not]) 
        description:'SHA256Stream/libcrypt is not loaded'.

    h := SHA256Stream hashValueOf:''.
    self assert:(h = (ByteArray fromHexString:'e3b0c44298fc1c149afbf4c8996fb92427ae41e4649b934ca495991b7852b855')).

    h := SHA256Stream hashValueOf:'The quick brown fox jumps over the lazy dog'.
    self assert:(h = (ByteArray fromHexString:'d7a8fbb307d7809469ca9abcb0082e4f8d5651e46d3cdb762d02d0bf37c9e592')).

    "
     self run:#test06_sha256
     self new test06_sha256
    "
!

test07_sha224
    |h|

    self 
        skipIf:(SHA224Stream isBehavior not or:[SHA224Stream isLoaded not]) 
        description:'SHA224Stream/libcrypt is not loaded'.

    h := SHA224Stream hashValueOf:''.
    self assert:(h = (ByteArray fromHexString:'d14a028c2a3a2bc9476102bb288234c415a2b01f828ea62ac5b3e42f')).

    h := SHA224Stream hashValueOf:'The quick brown fox jumps over the lazy dog'.
    self assert:(h = (ByteArray fromHexString:'730e109bd7a8a32b1cb9d9a09aa2325d2430587ddbc0c38bad911525')).

    "
     self run:#test07_sha224
     self new test07_sha224
    "
!

test08_sha384
    |h|

    self 
        skipIf:(SHA384Stream isBehavior not or:[SHA384Stream isLoaded not]) 
        description:'SHA384Stream/libcrypt is not loaded'.

    h := SHA384Stream hashValueOf:''.
    self assert:(h = (ByteArray fromHexString:'38b060a751ac96384cd9327eb1b1e36a21fdb71114be07434c0cc7bf63f6e1da274edebfe76f65fbd51ad2f14898b95b')).

    h := SHA384Stream hashValueOf:'The quick brown fox jumps over the lazy dog'.
    self assert:(h = (ByteArray fromHexString:'ca737f1014a48f4c0b6dd43cb177b0afd9e5169367544c494011e3317dbf9a509cb1e5dc1e85a941bbee3d7f2afbc9b1')).

    "
     self run:#test08_sha384
     self new test08_sha384
    "
!

test09_sha512
    |h|

    self 
        skipIf:(SHA512Stream isBehavior not or:[SHA512Stream isLoaded not]) 
        description:'SHA512Stream/libcrypt is not loaded'.

    h := SHA512Stream hashValueOf:''.
    self assert:(h = (ByteArray fromHexString:'cf83e1357eefb8bdf1542850d66d8007d620e4050b5715dc83f4a921d36ce9ce47d0d13c5d85f2b0ff8318d2877eec2f63b931bd47417a81a538327af927da3e')).

    h := SHA512Stream hashValueOf:'The quick brown fox jumps over the lazy dog'.
    self assert:(h = (ByteArray fromHexString:'07e547d9586f6a73f73fbac0435ed76951218fb7d0c8d788a309d785436bbb642e93a252a954f23912547d1e8a3b5ed6e1bfd7097821233fa0538f3db854fee6')).

    "
     self run:#test09_sha512
     self new test09_sha512
    "
!

test10_des
    |des crypt s s2|    

    des := DesCipher new key:#[12 34 56 78 90 12 34 56].
    crypt := des encrypt:'12345678'.
    self assert:(crypt = #[85 205 168 117 136 155 222 239]).

    "/ ------------------------------------------------

    des := DesCipher new key:#[12 34 56 78 90 12 34 56].
    s := '12345678'.
    10 timesRepeat:[
        s2 := ByteArray new:s size.
        des cryptBlock:s from:1 into:s2 startingAt:1 encrypt:true.
        s := s2.
    ].
    self assert:(s = #[212 114 83 160 109 1 37 83]).

    "/ ------------------------------------------------

    des := DesCipher new key:#[16rFF 16r80 56 78 90 12 34 56].
    crypt := des encrypt:'12345678'.
    self assert:(crypt = #[54 60 159 218 32 8 70 60]).


    "
     self run:#test10_des
     self new test10_des
    "

    "Modified: / 25-11-2013 / 11:45:34 / cg"
!

test11_rsaKey
    |dir fn key ks plain cipher|

    dir := Smalltalk packageDirectoryForPackageId:'exept:expecco'.
    self skipIf:dir isNil description:'directory with test key is not present'.
    fn := dir asFilename construct:'license/expeccoKey.pem'.
    self skipIf:fn exists not description:'test key is not present'.

    key := RSASecretCryptKey fromPemStream:fn readStream.

    ks := RSACryptStream new.
    ks encryptWithSecretKey:true.
    ks key:key.
    ks stream:#[] writeStream.

    plain := '12345678901234567890'.
    ks encrypt:plain.
    cipher := ks stream contents.

    ks := RSACryptStream new.
    ks encryptWithSecretKey:true.
    ks key:key.
    ks stream:#[] writeStream.

    ks decrypt:cipher.

    self assert:(ks stream contents asString = plain).

    "/ -------------------------------------------

    ks := RSACryptStream new.
    ks encryptWithSecretKey:true.
    ks key:key.
    ks stream:#[] writeStream.

    plain := #[16rFF 16r80 16r00].
    ks encrypt:plain.
    cipher := ks stream contents.

    ks := RSACryptStream new.
    ks encryptWithSecretKey:true.
    ks key:key.
    ks stream:#[] writeStream.

    ks decrypt:cipher.

    self assert:(ks stream contents = plain).

    "
     self run:#test11_rsaKey
     self new test11_rsaKey
    "

    "Created: / 02-12-2013 / 12:58:19 / cg"
! !

!CryptTests class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !