The Inbox: JSON-ul.47.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Inbox: JSON-ul.47.mcz

commits-2
Levente Uzonyi uploaded a new version of JSON to project The Inbox:
http://source.squeak.org/inbox/JSON-ul.47.mcz

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

Name: JSON-ul.47
Author: ul
Time: 22 January 2018, 12:32:52.716166 am
UUID: f2d44ea2-c2a1-4da0-9dec-5a3b1823ab3b
Ancestors: JSON-ul.46, JSON-klub.46

- merged with JSON-klub.46
- ScaledDecimal>>jsonWriteOn: rounds the number instead of truncating it

=============== Diff against JSON-tonyg.39 ===============

Item was changed:
  Object subclass: #Json
+ instanceVariableNames: 'stream currentCharacter arrayBufferStream stringBufferStream numberParser ctorMap'
- instanceVariableNames: 'stream ctorMap'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'JSON'!
  Json class
+ instanceVariableNames: 'escapeArray escapeSet'!
- instanceVariableNames: 'escapeArray'!
 
+ !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 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 escapeSet'!
- instanceVariableNames: 'escapeArray'!

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

Item was added:
+ ----- Method: Json class>>escapeSet (in category 'accessing') -----
+ escapeSet
+
+ ^escapeSet!

Item was changed:
+ ----- Method: Json class>>initialize (in category 'class initialization') -----
- ----- Method: Json class>>initialize (in category 'as yet unclassified') -----
  initialize
  "Json initialize."
 
+ | newEscapeArray newEscapeSet |
+ newEscapeArray := Array new: 128.
+ newEscapeSet := CharacterSet new.
- escapeArray := Array new: 128.
  (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) ].
- escapeArray at: each + 1 put: '\u', (each printStringHex padded: #left to: 4 with: $0) ].
  {
  $" -> '\"'.
  $\ -> '\\'.
+ $/ -> '\/'. "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!
- escapeArray at: each key asciiValue + 1 put: each value ].
- !

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

Item was changed:
+ ----- Method: Json class>>newWithConstructors: (in category 'instance creation') -----
- ----- 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.!

Item was removed:
- ----- Method: Json class>>numbersMayContain: (in category 'as yet unclassified') -----
- numbersMayContain: aChar
- ^ aChar isDigit or: [#($- $+ $. $e $E) includes: aChar]!

Item was changed:
+ ----- Method: Json class>>readFrom: (in category 'instance creation') -----
- ----- Method: Json class>>readFrom: (in category 'as yet unclassified') -----
  readFrom: aStream
  ^ self new readFrom: aStream.!

Item was changed:
+ ----- Method: Json class>>render: (in category 'rendering') -----
- ----- Method: Json class>>render: (in category 'as yet unclassified') -----
  render: anObject
+
+ ^String streamContents: [ :stream |
+ anObject jsonWriteOn: stream ]!
- | s |
- s := WriteStream on: String new.
- anObject jsonWriteOn: s.
- ^ s contents.!

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

Item was changed:
+ ----- Method: Json class>>renderInstanceVariables:of:on: (in category 'rendering') -----
- ----- 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!

Item was added:
+ ----- Method: Json>>arrayBufferStream (in category 'private') -----
+ arrayBufferStream
+
+ ^arrayBufferStream ifNil: [ arrayBufferStream := (Array new: 10) writeStream ]!

Item was added:
+ ----- Method: Json>>consume: (in category 'private') -----
+ consume: aString
+
+ | message |
+ 1 to: aString size do: [ :index |
+ (currentCharacter := stream next) == (aString at: index) ifFalse: [
+ message := 'Expected ', (aString at: index)  printString.
+ currentCharacter
+ ifNil: [ self incomplete: message ]
+ ifNotNil: [ self invalid: message ] ] ].
+ currentCharacter := stream next!

Item was removed:
- ----- 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!

Item was added:
+ ----- Method: Json>>error: (in category 'error handling') -----
+ error: aString
+
+ (currentCharacter isNil and: [ stream atEnd ])
+ ifTrue: [ self incomplete: aString ]
+ ifFalse: [ self invalid: aString ]!

Item was added:
+ ----- Method: Json>>incomplete: (in category 'error handling') -----
+ incomplete: aString
+
+ JsonIncompleteError signal: aString!

Item was removed:
- ----- 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.!

Item was added:
+ ----- 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
+ !

Item was added:
+ ----- Method: Json>>invalid: (in category 'error handling') -----
+ invalid: aString
+
+ JsonInvalidError signal: aString!

Item was removed:
- ----- 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'.!

Item was changed:
+ ----- Method: Json>>readAny (in category 'private') -----
- ----- 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.
+ 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 invalid: 'Unknown Json input'!
- 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'!

Item was changed:
  ----- Method: Json>>readArray (in category 'private') -----
  readArray
+
+ | initialPosition |
+ currentCharacter := stream next.
- | a |
  self skipWhitespace.
+ currentCharacter == $] ifTrue: [
+ currentCharacter := stream next.
+ ^#() ].
+ initialPosition := self arrayBufferStream position.
- (stream peekFor: $]) ifTrue: [ ^ #() ].
- a := OrderedCollection new.
  [
+ arrayBufferStream nextPut: self readAny.
- a add: 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.
- (stream peekFor: $]) ifTrue: [ ^ a asArray].
- (stream peekFor: $, ) ifFalse: [JsonInvalidError signal: 'Missing comma'].
- ] repeat.
  !

Item was changed:
  ----- Method: Json>>readConstructor (in category 'private') -----
  readConstructor
+
+ ctorMap ifNil: [ ^self error: 'No constructors were declared.' ].
+ self resetStringBufferStream.
+ [ (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!
- | 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.
- !

Item was changed:
  ----- Method: Json>>readDictionary (in category 'private') -----
  readDictionary
+
+ | result key commaNeeded |
+ result := JsonObject new.
+ commaNeeded := false.
+ currentCharacter := stream next.
- | m k v needComma |
- m := JsonObject new.
- needComma := false.
  [
  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.
- (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.
+ currentCharacter == $: ifFalse: [ self error: 'Missing colon' ].
+ currentCharacter := stream next.
+ result at: key put: self readAny  ] repeat.
- (stream peekFor: $:) ifFalse: [JsonInvalidError signal: 'Missing colon'].
- v := self readAny.
- m at: k put: v.
- ] repeat.
  !

Item was changed:
  ----- 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!
- self stream: aStream.
- ^ self readAny!

Item was removed:
- ----- 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.!

Item was added:
+ ----- 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
+ !

Item was changed:
  ----- Method: Json>>readString (in category 'private') -----
  readString
+
+ self resetStringBufferStream.
- | s c |
- s := WriteStream on: ''.
  [
+ currentCharacter := stream next ifNil: [self incomplete: 'Unexpected end of string' ].
+ currentCharacter == $" ifTrue: [
+ currentCharacter := stream next.
+ ^stringBufferStream contents ].
+ currentCharacter == $\
+ ifTrue: [
+ stringBufferStream nextPut: (self interpretStringEscape: (stream next ifNil: [
+ self incomplete: 'Unexpected end of string' ])) ]
+ ifFalse: [ stringBufferStream nextPut: currentCharacter ] ] repeat!
- 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.!

Item was added:
+ ----- Method: Json>>resetStringBufferStream (in category 'private') -----
+ resetStringBufferStream
+
+ stringBufferStream
+ ifNil: [ stringBufferStream := ReadWriteStream on: (String new: 64) ]
+ ifNotNil: [ stringBufferStream resetToStart ]!

Item was removed:
- ----- 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']]]
- !

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

Item was removed:
- ----- 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!

Item was changed:
  ----- Method: Json>>skipWhitespace (in category 'private') -----
  skipWhitespace
+
+ currentCharacter ifNil: [
+ self incomplete: 'Input stream is empty' ].
+ [ currentCharacter isSeparator ] whileTrue: [
+ currentCharacter := stream next ifNil: [
+ self incomplete: 'Input stream is empty' ]. ]!
- |c|
- [
- c := stream peek.
- c ifNil: [JsonIncompleteError signal: 'Expected JSON input'].
- c isSeparator
- ] whileTrue: [stream next].
- self skipComment.!

Item was changed:
+ ----- Method: Json>>stream: (in category 'private') -----
+ stream: aStream
+ "For testing purposes only"
- ----- Method: Json>>stream: (in category 'accessing') -----
- stream: anObject
- "Set the value of stream"
 
+ stream := aStream.
+ numberParser ifNotNil: [ numberParser on: stream ].
+ currentCharacter := stream next!
- stream := anObject.
- (stream respondsTo: #reset) ifTrue: [
- stream reset.
- ].
- !

Item was changed:
  ----- Method: Json>>unescapeUnicode (in category 'private') -----
  unescapeUnicode
+
+ | code digitValue |
+ code := 0.
+ 1 to: 4 do: [ :index |
+ (digitValue := (stream next ifNil: [ self incomplete: 'Unexpected end of stream' ]) digitValue) < 0 ifTrue: [
+ self invalid: 'Invalid hexadecimal digit' ].
+ digitValue < 16
+ ifTrue: [ code := code * 16 + digitValue ]
+ ifFalse: [ self invalid: 'Invalid hexadecimal digit' ] ].
+ ^Character value: code!
- |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)!

Item was added:
+ NumberParser subclass: #JsonNumberParser
+ instanceVariableNames: 'fraction'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'JSON'!

Item was added:
+ ----- Method: JsonNumberParser>>allowPlusSign (in category 'accessing') -----
+ allowPlusSign
+
+ ^false!

Item was added:
+ ----- Method: JsonNumberParser>>allowPlusSignInExponent (in category 'accessing') -----
+ allowPlusSignInExponent
+
+ ^true!

Item was added:
+ ----- Method: JsonNumberParser>>error: (in category 'error') -----
+ error: aString
+
+ JsonSyntaxError signal: aString!

Item was added:
+ ----- Method: JsonNumberParser>>exponentLetters (in category 'accessing') -----
+ exponentLetters
+
+ ^'eE'!

Item was added:
+ ----- Method: JsonNumberParser>>initialize (in category 'initialize-release') -----
+ initialize
+
+ super initialize.
+ base := 10.
+ fraction := Fraction numerator: 0 denominator: 1!

Item was added:
+ ----- 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!

Item was added:
+ ----- 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!

Item was added:
+ ----- 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 * (self tenRaisedTo: numberOfNonZeroFractionDigits) + (fractionPart // (self tenRaisedTo: numberOfTrailingZeroInFractionPart)).
+ value := self makeFloatFromMantissa: mantissa exponent: exponent.
+ negative ifTrue: [ ^value negated ].
+ ^value!

Item was added:
+ ----- 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 * (self tenRaisedTo: nDigits) + low.
+ lastNonZero = 0 ifFalse: [lastNonZeroHigh := lastNonZero + nDigitsHigh].
+ nDigitsHigh := nDigitsHigh + nDigits.
+ low isLarge]
+ whileTrue: [nPackets := nPackets * 2].
+
+ nDigits := nDigitsHigh.
+ lastNonZero := lastNonZeroHigh.
+ ^high!

Item was added:
+ ----- 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!

Item was changed:
  ----- Method: JsonObject>>doesNotUnderstand: (in category 'as yet unclassified') -----
  doesNotUnderstand: aMessage
+
+ | key precedence |
- | key |
  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!
- 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]
-
- !

Item was added:
+ OrderedDictionary subclass: #OrderedJsonObject
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'JSON'!

Item was added:
+ ----- Method: OrderedJsonObject class>>fromAssociations: (in category 'as yet unclassified') -----
+ fromAssociations: collectionOfAssociations
+
+ | result |
+ result := self new.
+
+ collectionOfAssociations do: [:each |
+ result at: each key put: each value ].
+ ^ result!

Item was added:
+ ----- Method: OrderedJsonObject>>at: (in category 'accessing') -----
+ at: aKey
+
+ "make it work more like javascript objects"
+ ^ self at: aKey ifAbsent: [nil]!

Item was added:
+ ----- Method: OrderedJsonObject>>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!

Item was added:
+ ----- Method: OrderedJsonObject>>name (in category 'accessing') -----
+ name
+ "override 'cause Object defines this"
+ ^self at: 'name'!

Item was added:
+ ----- Method: OrderedJsonObject>>value (in category 'accessing') -----
+ value
+ "override 'cause Object defines this"
+ ^self at: 'value'!

Item was added:
+ ----- Method: ScaledDecimal>>jsonWriteOn: (in category '*JSON-writing') -----
+ jsonWriteOn: stream
+
+ self printOn: stream showingDecimalPlaces: scale!

Item was changed:
  ----- 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 ].
- self do: [ :ch |
- (Json escapeForCharacter: ch)
- ifNil: [ aStream nextPut: ch ]
- ifNotNil: [ :replacement |
- aStream nextPutAll: replacement ] ].
  aStream nextPut: $".
  !

Item was added:
+ ----- Method: Time>>jsonWriteOn: (in category '*JSON') -----
+ jsonWriteOn: stream
+
+ stream nextPut: $".
+ self print24: true showSeconds: true on: stream.
+ stream nextPut: $"!