[squeak-dev] The Inbox: JSON-tonyg.39.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Feb 11 16:10:08 UTC 2018


Tony Garnock-Jones uploaded a new version of JSON to project The Inbox:
http://source.squeak.org/inbox/JSON-tonyg.39.mcz

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

Name: JSON-tonyg.39
Author: tonyg
Time: 17 August 2016, 2:19:56.932763 pm
UUID: 4c0c7961-cd4f-49c5-b109-d34df81e4808
Ancestors: JSON-FabN.38

Change JsonTests>>testStreaming to compare to JsonObject new, rather than just testing isDictionary.

testStreaming should not only check that the result is a dictionary, but that it is empty.

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

SystemOrganization addCategory: #JSON!

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

Object subclass: #Json
	instanceVariableNames: 'stream ctorMap'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'JSON'!
Json class
	instanceVariableNames: 'escapeArray'!

!Json commentStamp: '<historical>' prior: 0!
This class reads and writes JSON format data - strings, numbers, boolean, nil, arrays and dictionaries. See http://www.crockford.com/JSON/index.html. It has been extended with syntax for invoking a prearranged list of constructors on read objects.!
Json class
	instanceVariableNames: 'escapeArray'!

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

----- Method: Json class>>initialize (in category 'as yet unclassified') -----
initialize
	"Json initialize."
	
	escapeArray := Array new: 128.
	(0 to: 31), #(127) do: [ :each |
		escapeArray at: each + 1 put: '\u', (each printStringHex padded: #left to: 4 with: $0) ].
	{
		$" -> '\"'.
		$\ -> '\\'.
		Character backspace -> '\b'.
		Character lf -> '\n'.
		Character newPage -> '\f'.
		Character cr -> '\r'.
		Character tab -> '\t'.
	} do: [ :each |
		escapeArray at: each key asciiValue + 1 put: each value ].
!

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

----- Method: Json class>>newWithConstructors: (in category 'as yet unclassified') -----
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>>numbersMayContain: (in category 'as yet unclassified') -----
numbersMayContain: aChar
	^ aChar isDigit or: [#($- $+ $. $e $E) includes: aChar]!

----- Method: Json class>>readFrom: (in category 'as yet unclassified') -----
readFrom: aStream
	^ self new readFrom: aStream.!

----- Method: Json class>>render: (in category 'as yet unclassified') -----
render: anObject
	| s |
	s := WriteStream on: String new.
	anObject jsonWriteOn: s.
	^ s contents.!

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

----- Method: Json class>>renderInstanceVariables:of:on: (in category 'as yet unclassified') -----
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>>consume:returning: (in category 'private') -----
consume: aString returning: anObject
	|v|
	aString do: [:c |
		v := stream next.
		v ifNil: [JsonIncompleteError signal: 'Incomplete ''', aString, ''' seen'].
		v == c ifFalse: [JsonInvalidError signal: 'Expected ''', aString, ''''] ].
	^ anObject!

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

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

----- Method: Json>>interpretStringEscape (in category 'private') -----
interpretStringEscape
	| c |
	c := stream next.
	c ifNil: [JsonIncompleteError signal: 'Expected character following ''\'' in string escape'].
	c == $b ifTrue: [^ Character backspace].
	c == $n ifTrue: [^ Character lf].
	c == $f ifTrue: [^ Character newPage].
	c == $r ifTrue: [^ Character cr].
	c == $t ifTrue: [^ Character tab].
	c == $u ifTrue: [^ self unescapeUnicode].
	^ c.!

----- Method: Json>>nextHexDigit (in category 'private') -----
nextHexDigit
	| c |
	c := stream next.
	c ifNil: [JsonIncompleteError signal: 'Expecting hex digit'].
	c := c asUppercase.
	(c isDigit or: [c >= $A and: [c <= $F]]) ifTrue: [^ c].
	JsonInvalidError signal: 'Expected hex digit'.!

----- Method: Json>>readAny (in category 'parsing') -----
readAny
	"This is the main entry point for the JSON parser. See also readFrom: on the class side."
	| c |
	self skipWhitespace.
	c := stream peek asLowercase.
	c == ${ ifTrue: [stream next. ^ self readDictionary].
	c == $[ ifTrue: [stream next. ^ self readArray].
	c == $" ifTrue: [stream next. ^ self readString].
	c == $t ifTrue: [^ self consume: 'true' returning: true].
	c == $f ifTrue: [^ self consume: 'false' returning: false].
	c == $n ifTrue: [^ self consume: 'null' returning: nil].
	c == $@ ifTrue: [stream next. ^ self readConstructor].
	(Json numbersMayContain: c) ifTrue: [^ self readNumber].
	JsonInvalidError signal: 'Unknown Json input'!

----- Method: Json>>readArray (in category 'private') -----
readArray
	| a |
	self skipWhitespace.
	(stream peekFor: $]) ifTrue: [ ^ #() ].	
	a := OrderedCollection new.
	[
		a add: self readAny.
		self skipWhitespace.
		(stream peekFor: $]) ifTrue: [ ^ a asArray].
		(stream peekFor: $, ) ifFalse: [JsonInvalidError signal: 'Missing comma'].
	] repeat.
!

----- Method: Json>>readConstructor (in category 'private') -----
readConstructor
	| s c v ctor |
	s := WriteStream on: ''.
	[
		c := stream peek.
		c ifNil: [JsonIncompleteError signal: 'Premature EOF reading constructor name'].
		((c == $.) or: [c isLetter])
			ifTrue: [s nextPut: c. stream next]
			ifFalse: [
				v := self readAny.
				s := s contents.
				ctor := ctorMap ifNotNil: [ctor := ctorMap at: s ifAbsent: [nil]].
				ctor ifNil: [JsonInvalidError signal: 'Unknown ctor ', s].
				^ ctor constructFromJson: v]
	] repeat.
!

----- Method: Json>>readDictionary (in category 'private') -----
readDictionary
	| m k v needComma |
	m := JsonObject new.
	needComma := false.
	[
		self skipWhitespace.
		(stream peekFor: $}) ifTrue: [ ^ m].
		needComma
			ifTrue: [ (stream peekFor: $,) ifFalse: [JsonInvalidError signal: 'Missing comma'].
					self skipWhitespace]
			ifFalse: [needComma := true].
"		k := self readAny. "
		(stream peekFor: $") ifFalse: [JsonInvalidError signal: 'Key in dictionary must be string'].
		k := self readString.
		self skipWhitespace.
		(stream peekFor: $:) ifFalse: [JsonInvalidError signal: 'Missing colon'].
		v := self readAny.
		m at: k put: v.
	] repeat.
!

----- Method: Json>>readFrom: (in category 'parsing') -----
readFrom: aStream
	self stream: aStream.
	^ self readAny!

----- Method: Json>>readNumber (in category 'private') -----
readNumber
	| acc c |
	acc := WriteStream on: ''.
	[
		c := stream peek.
		(c isNil not and: [Json numbersMayContain: c]) ifFalse: [
			[^ acc contents asNumber] on: Error do: [JsonInvalidError signal: 'Invalid number']].
		acc nextPut: c.
		stream next.
	] repeat.!

----- Method: Json>>readString (in category 'private') -----
readString
	| s c |
	s := WriteStream on: ''.
	[
		c := stream next.
		c ifNil: [JsonIncompleteError signal: 'Incomplete read of JSON string'].
		c == $\
			ifTrue: [s nextPut: self interpretStringEscape.]
			ifFalse: [c == $" ifTrue: [^ s contents.].
					s nextPut: c]
	] repeat.!

----- Method: Json>>skipComment (in category 'private') -----
skipComment
	stream peek == $/ ifTrue: [
		stream next.
		stream peek == $/
			ifTrue: [self skipToEndOfLine]
			ifFalse: [stream peek == $*
						ifTrue: [stream next. self skipCommentBody]
						ifFalse: [JsonInvalidError signal: 'Invalid comment syntax']]]
!

----- Method: Json>>skipCommentBody (in category 'private') -----
skipCommentBody
	[
		[stream next == $*] whileFalse.
		stream peek == $/
	] whileFalse.
	stream next. "skip that last slash"
	self skipWhitespace.!

----- Method: Json>>skipToEndOfLine (in category 'private') -----
skipToEndOfLine
	| cr lf |
	cr := Character cr. lf := Character lf.
	[ | c | (c := stream peek) == cr or: [ c == lf]] whileFalse: [stream next].
	self skipWhitespace!

----- Method: Json>>skipWhitespace (in category 'private') -----
skipWhitespace
	|c|
	[
		c := stream peek.
		c ifNil: [JsonIncompleteError signal: 'Expected JSON input'].
		c isSeparator
	] whileTrue: [stream next].
	self skipComment.!

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

	^ stream!

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

	stream := anObject.
	(stream respondsTo: #reset) ifTrue: [
		stream reset.
	].
!

----- Method: Json>>unescapeUnicode (in category 'private') -----
unescapeUnicode
	|string a b c d|
	a := self nextHexDigit.
	b := self nextHexDigit.
	c := self nextHexDigit.
	d := self nextHexDigit.
	string := String with: a with: b with: c with: d.
	^ Unicode value: (Integer readFrom: string readStream base: 16)!

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: Number>>jsonWriteOn: (in category '*JSON-writing') -----
jsonWriteOn: aWriteStream 

	self printOn: aWriteStream base: 10!

----- 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 |
	key := aMessage selector.
	key isUnary ifTrue: [^ self at: key ifAbsent: [nil]].
	^ (key isKeyword and: [(key occurrencesOf: $:) = 1])
		ifTrue: [key := key allButLast asSymbol.
				self at: key put: aMessage arguments first]
		ifFalse: [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: 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: $]!

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

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

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

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>>assertIncompleteJson: (in category 'as yet unclassified') -----
assertIncompleteJson: aString
	self should: [self readFrom: aString] raise: JsonIncompleteError!

----- Method: JsonTests>>assertInvalidJson: (in category 'as yet unclassified') -----
assertInvalidJson: aString
	self should: [self readFrom: aString] raise: JsonInvalidError!

----- 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>>testIncomplete (in category 'as yet unclassified') -----
testIncomplete
	self assertIncompleteJson: ''.
	self assertIncompleteJson: '  '.
	self assertIncompleteJson: '  tr'.
	self assertIncompleteJson: 'tru'.
	self assertIncompleteJson: '['.
	self assertIncompleteJson: '[true'.
	self assertIncompleteJson: '[true,'.
	self assertIncompleteJson: '{'.
	self assertIncompleteJson: '{"hi"'.
	self assertIncompleteJson: '{"hi":'.
	self assertIncompleteJson: '{"hi":true'.
	self assertIncompleteJson: '{"hi":true,'.
	self assertIncompleteJson: '{"hi":true,"'.
	self assertIncompleteJson: '"hello'.
	self assertIncompleteJson: '"hello '.
	self assertIncompleteJson: '"hello\'.
	self assertIncompleteJson: '"\u26'.!

----- Method: JsonTests>>testInvalid (in category 'as yet unclassified') -----
testInvalid
	self assertInvalidJson: 'x'.
	self assertInvalidJson: '  x'.
	self assertInvalidJson: '  trx'.
	self assertInvalidJson: 'trux'.
	self assertInvalidJson: '.'.
	self assertInvalidJson: ':'.
	self assertInvalidJson: ','.
	self assertInvalidJson: ']'.
	self assertInvalidJson: '}'.
	self assertInvalidJson: '[x'.
	self assertInvalidJson: '[true t'.
	self assertInvalidJson: '[true,]'.
	self assertInvalidJson: '{]'.
	self assertInvalidJson: '{,'.
	self assertInvalidJson: '{"hi",'.
	self assertInvalidJson: '{"hi":x'.
	self assertInvalidJson: '{"hi":,'.
	self assertInvalidJson: '{"hi":true "'.
	self assertInvalidJson: '{"hi":true,}'.
	self assertInvalidJson: '\u263A'.!

----- Method: JsonTests>>testInvalidUnicodeEscapes (in category 'as yet unclassified') -----
testInvalidUnicodeEscapes
	self assertInvalidJson: '"\u26"'. "Note that naively reading four chars runs off the end here, so we might see JsonIncompleteError, which would be wrong."
	self assertInvalidJson: '"\u2Z"'.
	self assertInvalidJson: '"\u2Z44"'.!

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

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

----- Method: JsonTests>>testStreaming (in category 'as yet unclassified') -----
testStreaming
	| j |
	j := Json new stream: 'truefalsetrue[]{}1.234 5.678"A""B"nullnull' readStream.
	self assert: j readAny equals: true.
	self assert: j readAny equals: false.
	self assert: j readAny equals: true.
	self assert: j readAny equals: #().
	self assert: j readAny equals: JsonObject new.
	self assert: j readAny equals: 1.234.
	self assert: j readAny equals: 5.678.
	self assert: j readAny equals: 'A'.
	self assert: j readAny equals: 'B'.
	self assert: j readAny equals: nil.
	self assert: j readAny equals: nil.!

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

	| unicodeString |
	unicodeString := (Unicode value: 16r263A) asString.
	self json: '"\u263A"' equals:unicodeString.
	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"'.!

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

	aStream nextPut: $".
	self do: [ :ch |
		(Json escapeForCharacter: ch)
			ifNil: [ aStream nextPut: ch ]
			ifNotNil: [ :replacement |
				aStream nextPutAll: replacement ] ].
	aStream nextPut: $".
!

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

!JsonSyntaxError commentStamp: 'tonyg 4/29/2016 11:06' prior: 0!
Class Json signals (possibly-indirect) instances of me when reading a JSON value from an input stream fails.!

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

!JsonIncompleteError commentStamp: 'tonyg 4/29/2016 11:37' prior: 0!
I signal that reading a JSON value failed because more input is required, but that the input seen so far was not incorrect. Compare to JsonInvalidError.

Be warned that reading numbers directly out of a stream can be ambiguous!!

Consider reading from '1234'. Is the result intended to be 1234, or is there missing input, and the next character will be '5', making the result (possibly) 12345?!

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

!JsonInvalidError commentStamp: 'tonyg 4/29/2016 11:06' prior: 0!
I signal that reading a JSON value failed because the input didn't match the (extended)JSON grammar implemented by class Json.!

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



More information about the Squeak-dev mailing list