[squeak-dev] The Trunk: JSON-ul.45.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Sep 8 14:50:11 UTC 2022


Christoph Thiede uploaded a new version of JSON to project The Trunk:
http://source.squeak.org/trunk/JSON-ul.45.mcz

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

Name: JSON-ul.45
Author: ul
Time: 30 March 2016, 12:11:08.595786 am
UUID: 7ac5b7cd-8f53-40d3-92ad-46c2d3005dd3
Ancestors: JSON-ul.44

- further number parser tweaks

==================== Snapshot ====================

SystemOrganization addCategory: #JSON!

TestCase subclass: #JsonTests
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'JSON'!

!JsonTests commentStamp: '<historical>' prior: 0!
I provide a number of test cases for class Json.!

----- Method: JsonTests>>json:equals: (in category 'as yet unclassified') -----
json: aString equals: aValue
	| readValue |
	readValue := self readFrom: aString.
	self assert: readValue = aValue.!

----- Method: JsonTests>>readFrom: (in category 'as yet unclassified') -----
readFrom: aString
	^ (Json newWithConstructors: {JsonDummyTestObject.}) readFrom: aString readStream
!

----- Method: JsonTests>>render:equals: (in category 'as yet unclassified') -----
render: anObject equals: aString
	self assert: (Json render: anObject) = aString!

----- Method: JsonTests>>simpleDummyObject (in category 'as yet unclassified') -----
simpleDummyObject
	^ JsonDummyTestObject new a: 1; b: 2; c: 3; yourself!

----- Method: JsonTests>>testArray (in category 'as yet unclassified') -----
testArray
	self json: '[]' equals: #().
	self json: '[[]]' equals: #(#()).
	self json: '[[], []]' equals: #(#() #()).
	self json: '["hi", "there"]' equals: #('hi' 'there').
	self json: '[["a", "b", null]]' equals: #(('a' 'b' nil)).!

----- Method: JsonTests>>testAtomFalse (in category 'as yet unclassified') -----
testAtomFalse
	self json: 'false' equals: false.
	self json: '  false' equals: false.
	self json: 'false  ' equals: false.
	self json: '  false  ' equals: false.
!

----- Method: JsonTests>>testAtomNull (in category 'as yet unclassified') -----
testAtomNull
	self json: 'null' equals: nil.
	self json: '  null' equals: nil.
	self json: 'null  ' equals: nil.
	self json: '  null  ' equals: nil.
!

----- Method: JsonTests>>testAtomNumber (in category 'as yet unclassified') -----
testAtomNumber
	self json: '1' equals: 1.
	self json: '0123' equals: 123.
	self json: '1.23e2' equals: 123.
	self json: '-1' equals: -1.
	self json: '-0' equals: 0.
	self json: '[-1.2]' equals: #(-1.2).!

----- Method: JsonTests>>testAtomString (in category 'as yet unclassified') -----
testAtomString
	self json: '"hi"' equals: 'hi'.
	self json: '"\""' equals: '"'.
	self json: '"\\"' equals: '\'.
	self json: '""' equals: ''.
	self json: '"a\u0004b"' equals: ({$a. Character value: 4. $b} as: String).
	self json: '"a\nb"' equals: ({$a. Character lf. $b} as: String).!

----- Method: JsonTests>>testAtomTrue (in category 'as yet unclassified') -----
testAtomTrue
	self json: 'true' equals: true.
	self json: '  true' equals: true.
	self json: 'true  ' equals: true.
	self json: '  true  ' equals: true.
!

----- Method: JsonTests>>testCtor (in category 'as yet unclassified') -----
testCtor
	self json: '@JsonDummyTestObject {"a": 1, "b": 2, "c": 3}' equals: self simpleDummyObject.
	self json: (Json render: self simpleDummyObject) equals: self simpleDummyObject.!

----- Method: JsonTests>>testDictionary (in category 'as yet unclassified') -----
testDictionary
	self json: '{}' equals: (JsonObject new).
	self json: '{"a": "a"}' equals: (JsonObject new at: 'a' put: 'a'; yourself).
	self json: '{"a": [[]]}' equals: (JsonObject new at: 'a' put: #(#()); yourself).
	self json: '{"a":"b", "b":"a"}' equals: (JsonObject new add: 'a'->'b'; add: 'b'->'a';yourself).!

----- Method: JsonTests>>testMissingCtor (in category 'as yet unclassified') -----
testMissingCtor
	self 
		should: [self readFrom: '@Missing[]']
		raise: JsonSyntaxError
!

----- Method: JsonTests>>testMissingCtorNoMap (in category 'as yet unclassified') -----
testMissingCtorNoMap
	self 
		should: [Json new readFrom: '@Missing[]' readStream]
		raise: JsonSyntaxError!

----- Method: JsonTests>>testStringWithUnicode (in category 'as yet unclassified') -----
testStringWithUnicode

	| unicodeString |
	unicodeString := (Unicode value: 16r263A) asString.
	self json: '"\u263A"' equals:unicodeString.
	self json: '"', unicodeString, '"' equals: unicodeString.
	self render: unicodeString equals: '"', unicodeString, '"'.!

----- Method: JsonTests>>testWriteAssociation (in category 'as yet unclassified') -----
testWriteAssociation
	self render: 'key' -> 'value' equals: '"key": "value"'.
	self render: 'key' -> 2 equals: '"key": 2'.
	"keys should be strings"
	self render: 42 -> 2 equals: '"42": 2'.
	"try to do _something_ for more complex keys"
	self render: #(42 43 44) -> 2 equals:  '"#(42 43 44)": 2'.
	
	
	!

----- Method: JsonTests>>testWriteString (in category 'as yet unclassified') -----
testWriteString
	self render: '"' equals: '"\""'.
	self render: '\' equals: '"\\"'.
	self render: 'hi' equals: '"hi"'.
	self render: ({$a. Character lf. $b} as: String) equals: '"a\nb"'.
	self render: ({$a. Character value: 4. $b} as: String) equals: '"a\u0004b"'.!

Object subclass: #Json
	instanceVariableNames: 'stream currentCharacter arrayBufferStream stringBufferStream numberParser ctorMap'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'JSON'!
Json class
	instanceVariableNames: 'escapeArray escapeSet'!

!Json commentStamp: 'ul 3/29/2016 04:38' prior: 0!
I support reading and writing JSON (see http://json.org) formatted data - strings, numbers, boolean, nil, arrays and dictionaries.
The implementation is mainly based on RFC 7159 (https://www.ietf.org/rfc/rfc7159.txt). It has been extended with syntax for invoking a prearranged list of constructors on read objects.
Character encoding is not handled here. That's something you have to do before reading or after writing. Mixed processing is possible, but it's entirely your responsibility to keep things correct.

Instance Variables
	stream:				<PositionableStream>
	currentCharacter:	<Character>
	arrayBufferStream:	<WriteStream>
	stringBufferStream: <ReadWriteStream>
	numberParser: <ExtendedNumberParser>
	ctorMap: <Dictionary>

For parsing, stream has to be initialized by sending #readFrom: to my instance. The parser will pre-read one character, which will be stored in currentCharacter, so the stream is expected to support position manipulation, hence it should be a PositionableStream.
arrayBufferStream is WriteStream on an Array, which holds the values during array parsing (see #readArray). When there's a recursive call, this stream is used as a stack to separate the elements parsed in the previous invocation from the current one.
stringBufferStream is a ReadWriteStream on a String, which holds the currently parsed String (see #readString), the currently parsed number (see #readNumber) or the name of the currently parsed constructor (see #readConstructor). Recursion has no effect on this.
numberParser is a cached instance of ExtendedNumberParser. It's initialized on stringBufferStream, so it can quickly parse the number stored in it.
ctorMap is the Dictionary holding the constructor classes by name.

arrayBufferStream, stringBufferStream and numberParser are initialized lazily, and should not be accessed externally. Since these are shared objects, along with stream and currentCharacter, holding state, therefore a single instance of me shouldn't be used to parse multiple streams at the same time.

For writing, you can use the methods in the class-side rendering category. To convert individual objects to a string, you can use #asJsonString, to serialize it on a stream, you can use #jsonWriteOn:.
!
Json class
	instanceVariableNames: 'escapeArray escapeSet'!

----- Method: Json class>>escapeForCharacter: (in category 'accessing') -----
escapeForCharacter: c
	
	| asciiValue |
	(asciiValue := c asciiValue) < 128
		ifTrue: [ ^escapeArray at: asciiValue + 1 ].
	^nil!

----- Method: Json class>>escapeSet (in category 'accessing') -----
escapeSet 

	^escapeSet!

----- Method: Json class>>initialize (in category 'class initialization') -----
initialize
	"Json initialize."
	
	| newEscapeArray newEscapeSet |
	newEscapeArray := Array new: 128.
	newEscapeSet := CharacterSet new.
	(0 to: 31), #(127) do: [ :each |
		newEscapeArray at: each + 1 put: '\u', (each printStringHex padded: #left to: 4 with: $0).
		newEscapeSet add: (Character value: each) ].
	{
		$" -> '\"'.
		$\ -> '\\'.
		$/ -> '\/'. "A hack, so the generated JSON will always be HTML+Javascript compatible, because the generated JSON will not contain the seqence </script>."
		Character backspace -> '\b'.
		Character lf -> '\n'.
		Character newPage -> '\f'.
		Character cr -> '\r'.
		Character tab -> '\t'.
	} do: [ :each |
		newEscapeArray at: each key asciiValue + 1 put: each value.
		newEscapeSet add: each key ].
	escapeArray := newEscapeArray.
	escapeSet := newEscapeSet!

----- Method: Json class>>mimeType (in category 'accessing') -----
mimeType
	^ 'application/x-json'!

----- Method: Json class>>newWithConstructors: (in category 'instance creation') -----
newWithConstructors: aCollection
	| m |
	m := Dictionary new.
	aCollection do: [:each |
		(each isKindOf: Association)
			ifTrue: [m add: each]
			ifFalse: [m at: each name asString put: each]].
	^ self new ctorMap: m; yourself.!

----- Method: Json class>>readFrom: (in category 'instance creation') -----
readFrom: aStream
	^ self new readFrom: aStream.!

----- Method: Json class>>render: (in category 'rendering') -----
render: anObject

	^String streamContents: [ :stream |
		anObject jsonWriteOn: stream ]!

----- Method: Json class>>render:withConstructor:on: (in category 'rendering') -----
render: anObject withConstructor: aConstructorName on: aStream
	aStream nextPutAll: '@', aConstructorName.
	anObject jsonWriteOn: aStream.
!

----- Method: Json class>>renderInstanceVariables:of:on: (in category 'rendering') -----
renderInstanceVariables: aCollection of: anObject on: aStream
	| map |
	map := Dictionary new.
	aCollection do: [:ivarName | map at: ivarName put: (anObject instVarNamed: ivarName)].
	self render: map withConstructor: anObject class name asString on: aStream!

----- Method: Json>>arrayBufferStream (in category 'private') -----
arrayBufferStream

	^arrayBufferStream ifNil: [ arrayBufferStream := (Array new: 10) writeStream ]!

----- Method: Json>>consume: (in category 'private') -----
consume: aString

	1 to: aString size do: [ :index |
		stream next == (aString at: index) ifFalse: [
			self error: 'Expected ', (aString at: index)  printString ] ].
	currentCharacter := stream next!

----- Method: Json>>ctorMap (in category 'accessing') -----
ctorMap
	^ ctorMap!

----- Method: Json>>ctorMap: (in category 'accessing') -----
ctorMap: m
	ctorMap := m!

----- Method: Json>>error: (in category 'error handling') -----
error: aString

	JsonSyntaxError signal: aString!

----- Method: Json>>interpretStringEscape: (in category 'private') -----
interpretStringEscape: aCharacter

	aCharacter == $b ifTrue: [ ^Character backspace ].
	aCharacter == $n ifTrue: [ ^Character lf ].
	aCharacter == $f ifTrue: [ ^Character newPage ].
	aCharacter == $r ifTrue: [ ^Character cr ].
	aCharacter == $t ifTrue: [ ^Character tab ].
	aCharacter == $u ifTrue: [ ^self unescapeUnicode ].
	aCharacter == $" ifTrue: [ ^aCharacter ].
	aCharacter == $\ ifTrue: [ ^aCharacter ].
	aCharacter == $/ ifTrue: [ ^aCharacter ].
	self error: 'Unexpected escaped character: ', aCharacter asString
!

----- Method: Json>>readAny (in category 'private') -----
readAny

	self skipWhitespace.
	currentCharacter == ${ ifTrue: [ ^self readDictionary ].
	currentCharacter == $[ ifTrue: [ ^self readArray ].
	currentCharacter == $" ifTrue: [ ^self readString ].
	currentCharacter == $t ifTrue: [ self consume: 'rue'. ^true ].
	currentCharacter == $f ifTrue: [ self consume: 'alse'. ^false ].
	currentCharacter == $n ifTrue: [ self consume: 'ull'. ^nil ].
	currentCharacter == $- ifTrue: [ ^self readNumber: true ].
	(#($0 $1 $2 $3 $4 $5 $6 $7 $8 $9) instVarsInclude: currentCharacter) ifTrue: [
		^self readNumber: false ].
	currentCharacter == $@ ifTrue: [ ^self readConstructor ].
	^self error: 'Unknown Json input'!

----- Method: Json>>readArray (in category 'private') -----
readArray

	| initialPosition |
	currentCharacter := stream next.
	self skipWhitespace.
	currentCharacter == $] ifTrue: [
		currentCharacter := stream next.
		^#() ].
	initialPosition := self arrayBufferStream position.
	[
		arrayBufferStream nextPut: self readAny.
		self skipWhitespace.
		currentCharacter == $] ifTrue: [ 
			|  result |
			result := arrayBufferStream originalContents copyFrom: initialPosition + 1 to: arrayBufferStream position.
			arrayBufferStream position: initialPosition.
			currentCharacter := stream next.
			^result ].
		currentCharacter == $, ifFalse: [ self error: 'Unexpected character: ', currentCharacter asString ].
		currentCharacter := stream next ] repeat.
!

----- Method: Json>>readConstructor (in category 'private') -----
readConstructor

	ctorMap ifNil: [ ^self error: 'No constructors were declared.' ].
	self stringBufferStream resetToStart.
	[ (currentCharacter := stream next) == $. or: [ currentCharacter isLetter ] ] whileTrue: [
		stringBufferStream nextPut: currentCharacter ].
	(ctorMap at: stringBufferStream contents ifAbsent: nil) ifNotNil: [ :constructor |
		^constructor constructFromJson: self readAny ].	
	self error: 'Unknown constructor: ', stringBufferStream contents!

----- Method: Json>>readDictionary (in category 'private') -----
readDictionary

	| result key commaNeeded |
	result := JsonObject new.
	commaNeeded := false.
	currentCharacter := stream next.
	[
		self skipWhitespace.
		currentCharacter == $} ifTrue: [ 
			currentCharacter := stream next.
			^result ].
		commaNeeded
			ifFalse: [ commaNeeded := true ]
			ifTrue: [ 
				currentCharacter == $, ifFalse: [ self error: 'Missing comma' ].
				currentCharacter := stream next.
				self skipWhitespace ].
		currentCharacter == $" ifFalse: [  self error: 'Key in dictionary must be string' ].
		key := self readString.
		self skipWhitespace.
		currentCharacter == $: ifFalse: [ self error: 'Missing colon' ].
		currentCharacter := stream next.
		result at: key put: self readAny  ] repeat.
!

----- Method: Json>>readFrom: (in category 'parsing') -----
readFrom: aStream

	| result |
	stream := aStream.
	numberParser ifNotNil: [ numberParser on: stream ].
	currentCharacter := stream next.
	result := self readAny.
	stream atEnd ifFalse: [ stream skip: -1 ]. "Undo prereading."
	^result!

----- Method: Json>>readNumber: (in category 'private') -----
readNumber: negative

	| result |
	negative ifFalse: [ stream skip: -1 ].
	result := (numberParser ifNil: [
		numberParser := JsonNumberParser new
			on: stream;
			failBlock: [ self error: 'Invalid number.' ];
			yourself ])
		nextNumber: negative.
	currentCharacter := stream next.
	^result
	!

----- Method: Json>>readString (in category 'private') -----
readString

	self stringBufferStream resetToStart.
	[
		(currentCharacter := stream next) == $\
			ifTrue: [ stringBufferStream nextPut: (self interpretStringEscape: stream next) ]
			ifFalse: [ 
				currentCharacter == $" ifTrue: [ 
					currentCharacter := stream next.
					^stringBufferStream contents ].
				stringBufferStream nextPut: currentCharacter ] ] repeat!

----- Method: Json>>skipWhitespace (in category 'private') -----
skipWhitespace
	
	[ currentCharacter isSeparator ] whileTrue: [
		currentCharacter := stream next ]!

----- Method: Json>>stream (in category 'accessing') -----
stream
	"Answer the value of stream"

	^ stream!

----- Method: Json>>stringBufferStream (in category 'private') -----
stringBufferStream

	^stringBufferStream ifNil: [ stringBufferStream := ReadWriteStream on: (String new: 64) ]!

----- Method: Json>>unescapeUnicode (in category 'private') -----
unescapeUnicode

	| code digitValue |
	code := 0.
	1 to: 4 do: [ :index |
		(digitValue := stream next digitValue) < 0 ifTrue: [
			self error: 'Invalid hexadecimal digit' ].
		digitValue < 16
			ifTrue: [ code := code * 16 + digitValue ]
			ifFalse: [ self error: 'Invalid hexadecimal digit' ] ].
	^Character value: code!

Object subclass: #JsonDummyTestObject
	instanceVariableNames: 'a b c'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'JSON'!

----- Method: JsonDummyTestObject class>>constructFromJson: (in category 'as yet unclassified') -----
constructFromJson: j
	^ self new a: (j at: 'a'); b: (j at: 'b'); c: (j at: 'c'); yourself!

----- Method: JsonDummyTestObject>>= (in category 'as yet unclassified') -----
= other
	^ other class == self class and: [
		a = other a and: [
		b = other b and: [
		c = other c]]]!

----- Method: JsonDummyTestObject>>a (in category 'accessing') -----
a
	"Answer the value of a"

	^ a!

----- Method: JsonDummyTestObject>>a: (in category 'accessing') -----
a: anObject
	"Set the value of a"

	a := anObject!

----- Method: JsonDummyTestObject>>b (in category 'accessing') -----
b
	"Answer the value of b"

	^ b!

----- Method: JsonDummyTestObject>>b: (in category 'accessing') -----
b: anObject
	"Set the value of b"

	b := anObject!

----- Method: JsonDummyTestObject>>c (in category 'accessing') -----
c
	"Answer the value of c"

	^ c!

----- Method: JsonDummyTestObject>>c: (in category 'accessing') -----
c: anObject
	"Set the value of c"

	c := anObject!

----- Method: JsonDummyTestObject>>jsonWriteOn: (in category 'as yet unclassified') -----
jsonWriteOn: s
	Json renderInstanceVariables: {#a. #b. #c} of: self on: s
!

----- Method: Object>>asJsonString (in category '*JSON') -----
asJsonString

	^ String streamContents: [:str |
		self jsonWriteOn: str ]!

----- Method: True>>jsonWriteOn: (in category '*JSON-writing') -----
jsonWriteOn: aStream
	aStream nextPutAll: 'true'!

----- Method: Number>>jsonWriteOn: (in category '*JSON-writing') -----
jsonWriteOn: aWriteStream 

	self printOn: aWriteStream base: 10!

----- Method: Time>>jsonWriteOn: (in category '*JSON') -----
jsonWriteOn: stream

	stream nextPut: $".
	self print24: true showSeconds: true on: stream.
	stream nextPut: $"!

----- Method: Dictionary>>jsonWriteOn: (in category '*JSON-writing') -----
jsonWriteOn: aStream

	| needComma |
	needComma := false.
	aStream nextPut: ${.
	self associationsDo: [ :assoc |
		needComma
			ifTrue: [ aStream nextPut: $, ]
			ifFalse: [ needComma := true ].
		assoc key jsonWriteOn: aStream.
		aStream nextPut: $:.
		assoc value jsonWriteOn: aStream ].
	aStream nextPut: $}.!

Dictionary subclass: #JsonObject
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'JSON'!

----- Method: JsonObject class>>fromAssociations: (in category 'as yet unclassified') -----
fromAssociations: collectionOfAssociations

	| result |
	result := self new.
	
	collectionOfAssociations do: [:each |
		result at: each key put: each value ].
	^ result!

----- Method: JsonObject>>at: (in category 'accessing') -----
at: aKey

	"make it work more like javascript objects"
	^ self at: aKey ifAbsent: [nil]!

----- Method: JsonObject>>doesNotUnderstand: (in category 'as yet unclassified') -----
doesNotUnderstand: aMessage

	| key precedence |
	key := aMessage selector.
	(precedence := key precedence) = 1 ifTrue: [ ^self at: key ifAbsent: nil ].
	(precedence = 3 and: [ (key indexOf: $:) = key size ]) ifTrue: [
		^self
			at: key allButLast asSymbol
			put: aMessage arguments first ].
	^super doesNotUnderstand: aMessage!

----- Method: JsonObject>>name (in category 'accessing') -----
name
"override 'cause Object defines this"
	^self at: 'name'!

----- Method: JsonObject>>value (in category 'accessing') -----
value
"override 'cause Object defines this"
	^self at: 'value'!

----- Method: ScaledDecimal>>jsonWriteOn: (in category '*JSON-writing') -----
jsonWriteOn: stream

	self printFractionAsDecimalOn: stream!

----- Method: WriteStream>>jsonPrint: (in category '*json-printing') -----
jsonPrint: anObject
	anObject jsonWriteOn: self!

----- Method: Text>>jsonWriteOn: (in category '*json-printing') -----
jsonWriteOn: aStream
	self string jsonWriteOn: aStream!

----- Method: String>>jsonWriteOn: (in category '*JSON-writing') -----
jsonWriteOn: aStream

	| index start |
	aStream nextPut: $".
	start := 1.
	[ (index := self indexOfAnyOf: Json escapeSet startingAt: start) = 0 ] whileFalse: [
		aStream next: index - start putAll: self startingAt: start.
		aStream nextPutAll: (Json escapeForCharacter: (self at: index)).
		start := index + 1 ].
	start <= self size ifTrue: [
		aStream next: self size + 1 - start putAll: self startingAt: start ].
	aStream nextPut: $".
!

----- Method: Integer>>jsonWriteOn: (in category '*JSON-writing') -----
jsonWriteOn: aWriteStream
	^ self printOn: aWriteStream base: 10
!

----- Method: UndefinedObject>>jsonWriteOn: (in category '*JSON-writing') -----
jsonWriteOn: aWriteStream 
	aWriteStream nextPutAll: 'null'!

NumberParser subclass: #JsonNumberParser
	instanceVariableNames: 'fraction'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'JSON'!

----- Method: JsonNumberParser>>allowPlusSign (in category 'accessing') -----
allowPlusSign

	^false!

----- Method: JsonNumberParser>>allowPlusSignInExponent (in category 'accessing') -----
allowPlusSignInExponent

	^true!

----- Method: JsonNumberParser>>error: (in category 'error') -----
error: aString

	JsonSyntaxError signal: aString!

----- Method: JsonNumberParser>>exponentLetters (in category 'accessing') -----
exponentLetters

	^'eE'!

----- Method: JsonNumberParser>>initialize (in category 'initialize-release') -----
initialize

	super initialize.
	base := 10.
	fraction := Fraction numerator: 0 denominator: 1!

----- Method: JsonNumberParser>>makeFloatFromMantissa:exponent: (in category 'parsing-private') -----
makeFloatFromMantissa: mantissa exponent: exponent

	exponent = 0 ifTrue: [ ^mantissa asFloat ].
	exponent >= 16 ifTrue: [ ^(mantissa * (self tenRaisedTo: exponent)) asFloat ].
	(exponent >= -15 and: [ mantissa highBitOfMagnitude <= 54 ]) ifTrue: [
		exponent >= 1 ifTrue: [ ^mantissa asFloat * (self tenRaisedTo: exponent) asFloat ].
		^mantissa asFloat / (self tenRaisedTo: exponent negated) asFloat ].
	^(fraction setNumerator: mantissa denominator: (self tenRaisedTo: exponent negated)) asFloat!

----- Method: JsonNumberParser>>nextElementaryLargeInteger (in category 'parsing-large int') -----
nextElementaryLargeInteger
	"Form an unsigned integer with incoming digits from sourceStream.
	Return this integer, or zero if no digits found.
	Stop reading if end of digits or if a LargeInteger is formed.
	Count the number of digits and the position of lastNonZero digit and store them in instVar."

	| digit value |
	value := 0.
	nDigits := 0.
	lastNonZero := 0.
	[
		value isLarge ifTrue: [ ^value ].
		((digit := (sourceStream next ifNil: [ ^value ]) asInteger - 48 "$0 asInteger") < 0 
			or: [ digit >= 10 ]) ifTrue: [
			sourceStream skip: -1.
			^value ].
		nDigits := nDigits + 1.
		digit = 0
			ifFalse: [
				lastNonZero := nDigits.
				value := value * 10 + digit ]
			ifTrue: [ value := value * 10 ] ] repeat!

----- Method: JsonNumberParser>>nextNumber: (in category 'parsing-public') -----
nextNumber: negative

	| numberOfTrailingZeroInIntegerPart numberOfTrailingZeroInFractionPart numberOfNonZeroFractionDigits mantissa value |
	integerPart := self nextUnsignedIntegerOrNil ifNil: [ ^self error: 'Missing integer part!!' ].
	numberOfTrailingZeroInIntegerPart := nDigits - lastNonZero.
	(sourceStream peekFor: $.) ifFalse: [ "No fraction part"
		negative ifTrue: [ integerPart := integerPart negated ].
		self readExponent ifFalse: [ ^integerPart ].
		exponent > 0 ifTrue: [ ^integerPart * (self tenRaisedTo: exponent) ].
		^(Fraction numerator: integerPart denominator: (self tenRaisedTo: exponent negated)) asFloat ].
	fractionPart := self nextUnsignedIntegerOrNil ifNil: [ self error: 'Missing fraction part!!' ].
	fractionPart isZero ifTrue: [
		self readExponent ifFalse: [
			negative ifTrue: [
				integerPart isZero ifTrue: [ ^Float negativeZero ].
				^integerPart negated ].
			^integerPart ].
		exponent >= 0 ifTrue: [ 
			negative ifTrue: [ integerPart := integerPart negated ].
			^integerPart * (self tenRaisedTo: exponent) ].
		value := self makeFloatFromMantissa: integerPart exponent: exponent.
		negative ifTrue: [ ^value negated ].
		^value ].
	numberOfTrailingZeroInFractionPart := nDigits - lastNonZero.
	numberOfNonZeroFractionDigits := lastNonZero.
	self readExponent.
	exponent := exponent - numberOfNonZeroFractionDigits.
	mantissa := integerPart * (10 raisedToInteger: numberOfNonZeroFractionDigits) + (fractionPart // (10 raisedToInteger: numberOfTrailingZeroInFractionPart)).
	value := self makeFloatFromMantissa: mantissa exponent: exponent.
	negative ifTrue: [ ^value negated ].
	^value!

----- Method: JsonNumberParser>>nextUnsignedIntegerOrNil (in category 'parsing-public') -----
nextUnsignedIntegerOrNil
	"Form an unsigned integer with incoming digits from sourceStream.
	Answer this integer, or nil if no digit found.
	Count the number of digits and the position of lastNonZero digit and store them in instVar"
	
	| nPackets high nDigitsHigh lastNonZeroHigh low |
	"read no more digits than one elementary LargeInteger"
	high := self nextElementaryLargeInteger.
	nDigits = 0 ifTrue: [^nil].
	
	"Not enough digits to form a LargeInteger, stop iteration"
	high isLarge ifFalse: [^high].

	"We now have to engage arithmetic with LargeInteger
	Decompose the integer in a high and low packets of growing size:"
	nPackets := 1.
	nDigitsHigh := nDigits.
	lastNonZeroHigh := lastNonZero.
	[
	low := self nextLargeIntegerBase: 10 nPackets: nPackets .
	high := high * (10 raisedToInteger: nDigits) + low.
	lastNonZero = 0 ifFalse: [lastNonZeroHigh := lastNonZero + nDigitsHigh].
	nDigitsHigh := nDigitsHigh + nDigits.
	low isLarge]
		whileTrue: [nPackets := nPackets * 2].

	nDigits := nDigitsHigh.
	lastNonZero := lastNonZeroHigh.
	^high!

----- Method: JsonNumberParser>>tenRaisedTo: (in category 'parsing-private') -----
tenRaisedTo: anInteger

	anInteger >= 0 ifFalse: [ ^10 raisedToInteger: anInteger ].
	anInteger >= 16 ifTrue: [ ^10 raisedToInteger: anInteger ].
	^#(1 10 100 1000 10000 100000 1000000 10000000 100000000 1000000000 10000000000 100000000000 1000000000000 10000000000000 100000000000000 1000000000000000) at: anInteger + 1!

----- Method: Collection>>jsonWriteOn: (in category '*json') -----
jsonWriteOn: aStream
	"By default, use array braces "
	aStream nextPut: $[.
	
	self do: [:each |
		each jsonWriteOn: aStream
		  ] separatedBy: [ aStream nextPut: $, ].

	aStream nextPut: $]!

Error subclass: #JsonSyntaxError
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'JSON'!

!JsonSyntaxError commentStamp: '<historical>' prior: 0!
Class Json signals instances of me when an input stream contains invalid JSON input.!

----- Method: Association>>jsonWriteOn: (in category '*JSON-writing') -----
jsonWriteOn: aStream
	self key asString jsonWriteOn: aStream.
	aStream nextPut: $:; space.
	self value jsonWriteOn: aStream.!

----- Method: False>>jsonWriteOn: (in category '*JSON-writing') -----
jsonWriteOn: aStream
	aStream nextPutAll: 'false'!



More information about the Squeak-dev mailing list