[squeak-dev] The Inbox: CryptoCore-rww.4.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Sep 23 08:32:19 UTC 2010


A new version of CryptoCore was added to project The Inbox:
http://source.squeak.org/inbox/CryptoCore-rww.4.mcz

==================== Summary ====================

Name: CryptoCore-rww.4
Author: rww
Time: 23 September 2010, 4:31:15.327 am
UUID: 66874a66-f65b-3343-b1e7-326774856d01
Ancestors: CryptoCore-rww.3

fixed RSA signing and moved ASN1 and PKCS11 into Core

=============== Diff against CryptoCore-rww.3 ===============

Item was added:
+ ----- Method: Boolean>>asAsn1Bytes (in category '*cryptocore') -----
+ asAsn1Bytes
+ 
+ 	^ ASN1Stream encode: self.
+ !

Item was added:
+ ----- Method: Boolean>>asn1Tag (in category '*cryptocore') -----
+ asn1Tag
+ 
+ 	^ 1
+ !

Item was added:
+ ----- Method: ByteArray>>asn1Tag (in category '*cryptocore') -----
+ asn1Tag
+ 
+ 	^ 4
+ !

Item was added:
+ ----- Method: DateAndTime>>asAsn1Bytes (in category '*cryptocore') -----
+ asAsn1Bytes
+ 
+ 	^ ASN1Stream encode: self.
+ !

Item was added:
+ ----- Method: DateAndTime>>asn1Tag (in category '*cryptocore') -----
+ asn1Tag
+ 
+ 	^ 23
+ !

Item was added:
+ ----- Method: Integer class>>asnDerLengthFromHexStreamWithBytes: (in category '*cryptocore') -----
+ asnDerLengthFromHexStreamWithBytes: aStream
+ 
+ 	| byte length bytes |
+ 	bytes := OrderedCollection new.
+ 	byte := (Number readFrom: ((bytes add: aStream next) ifNil: [^0->#()]) asUppercase base: 16).
+ 	byte <= 16r80
+ 		ifTrue: [^byte->bytes merge]
+ 		ifFalse: [
+ 			length := 0.
+ 			(byte bitAnd: 16r7F) timesRepeat: [
+ 				length := (length bitShift: 8) bitOr: (Number readFrom: (bytes add: aStream next) asUppercase base: 16).].
+ 			^ length->(bytes merge)].!

Item was added:
+ ----- Method: Integer>>asAsn1Bytes (in category '*cryptocore') -----
+ asAsn1Bytes
+ 
+ 	^ ASN1Stream encode: self.
+ !

Item was added:
+ ----- Method: Integer>>asn1Tag (in category '*cryptocore') -----
+ asn1Tag
+ 
+ 	^ 2
+ !

Item was added:
+ ----- Method: ReadStream>>formatASN1TabLevel: (in category '*cryptocore') -----
+ formatASN1TabLevel: aTabLevel 
+ 	| result tag aString size tabs sizeAndBytes bytes |
+ 	self atEnd
+ 		ifTrue: [^ String new].
+ 	tabs := ((1 to: aTabLevel)
+ 				collect: [:i | '.' , String tab]) merge.
+ 	result := tabs , (tag := self next) , String tab.
+ 	sizeAndBytes := tag = '00'
+ 				ifTrue: [(Number readFrom: (bytes := self next: 2) merge asUppercase base: 16) -> bytes merge]
+ 				ifFalse: [Integer asnDerLengthFromHexStreamWithBytes: self].
+ 	size := sizeAndBytes key.
+ 	aString := (self next: size) merge.
+ 	aString isEmpty
+ 		ifTrue: [aString := String new].
+ 	(tag = '30'
+ 			or: [tag = '31'
+ 					or: [tag first asLowercase = $a or: [tag = '00']]])
+ 		ifTrue: [result := result , sizeAndBytes value , ' (' , size asString , '): ' , String cr
+ 						, (aString formatASN1TabLevel: aTabLevel + 1)]
+ 		ifFalse: [result := result , sizeAndBytes value , ' (' , size asString , '): ' , String cr , tabs , String tab , aString , String cr
+ 						, (self formatASN1TabLevel: aTabLevel)].
+ 	^ result
+ 		, (self formatASN1TabLevel: aTabLevel)!

Item was added:
+ ----- Method: SequenceableCollection>>asAsn1Bytes (in category '*cryptocore') -----
+ asAsn1Bytes
+ 
+ 	^ ASN1Stream encode: self.
+ !

Item was added:
+ ----- Method: SequenceableCollection>>asn1Tag (in category '*cryptocore') -----
+ asn1Tag
+ 
+ 	^ 48
+ !

Item was added:
+ ----- Method: Set>>asAsn1Bytes (in category '*cryptocore') -----
+ asAsn1Bytes
+ 
+ 	^ ASN1Stream encode: self.
+ !

Item was added:
+ ----- Method: Set>>asn1Tag (in category '*cryptocore') -----
+ asn1Tag
+ 
+ 	^ 49
+ !

Item was added:
+ ----- Method: String>>asn1Tag (in category '*cryptocore') -----
+ asn1Tag
+ 
+ 	^ 12
+ !

Item was added:
+ ----- Method: String>>formatASN1 (in category '*cryptocore') -----
+ formatASN1
+ 	"return a asn1 tab formed string
+ 	'30818513818154686973206973206120313239206279746520737472696E672C2062757420746861742069732061207265616C6C79206C6F6E6720737472696E6720736F204920686176652061206C6F7420746F20747970652E20204E6F7065204920616D206E6F7420646F6E65207965742C207374696C6C206E6F7420646F6E6520616C6D6F' formatASN1
+ 	"
+ 	^self formatASN1TabLevel: 0!

Item was added:
+ ----- Method: String>>formatASN1TabLevel: (in category '*cryptocore') -----
+ formatASN1TabLevel: aTabLevel
+ 	| aReadStream aWriteStream | 
+ 	"return a asn1 tab formed string
+ 	'30818513818154686973206973206120313239206279746520737472696E672C2062757420746861742069732061207265616C6C79206C6F6E6720737472696E6720736F204920686176652061206C6F7420746F20747970652E20204E6F7065204920616D206E6F7420646F6E65207965742C207374696C6C206E6F7420646F6E6520616C6D6F' formatASN1
+ 	"
+ 	aReadStream := ((self copyWithoutAll: {Character space. Character tab. Character cr}) divideBySize: 2) readStream.
+ 	aWriteStream := String new writeStream.
+ 	aWriteStream nextPutAll: (aReadStream formatASN1TabLevel: aTabLevel).
+ 	^aWriteStream contents!

Item was added:
+ ----- Method: String>>tokensBasedOn: (in category '*cryptocore') -----
+ tokensBasedOn: aChar
+ 	"Answer an array of the substrings that compose the receiver."
+ 	| result end begin |
+ 
+ 	result := WriteStream on: (Array new: 10).
+ 
+ 	begin := 1.
+ 	"find one substring each time through this loop"
+ 	[ 
+ 		"find the beginning of the next substring"
+ 		end := self indexOf: aChar startingAt: begin ifAbsent: [ nil ].
+ 		end ~~ nil ] 
+ 	whileTrue: [
+ 		result nextPut: (self copyFrom: begin to: end - 1).
+ 		begin := end + 1].
+ 	result nextPut: (self copyFrom: begin to: self size).
+ 	^result contents
+ !

Item was added:
+ ----- Method: UndefinedObject>>asAsn1Bytes (in category '*cryptocore') -----
+ asAsn1Bytes
+ 
+ 	^ ASN1Stream encode: self.
+ !

Item was added:
+ ----- Method: UndefinedObject>>asn1Tag (in category '*cryptocore') -----
+ asn1Tag
+ 
+ 	^ 5!




More information about the Squeak-dev mailing list