tests/STONReaderTests.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 04 Jun 2019 12:33:53 +0100
changeset 0 8f9f6be6af89
permissions -rw-r--r--
Initial port from Pharo Based on 305ae856d4b551 from https://github.com/svenvc/ston.git

"{ Package: 'stx:goodies/ston/tests' }"

"{ NameSpace: Smalltalk }"

TestCase subclass:#STONReaderTests
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'STON-Tests-Reader'
!


!STONReaderTests methodsFor:'private'!

materialize: string
	^ STON reader 
		on: string readStream;
		next
! !

!STONReaderTests methodsFor:'tests'!

testAssociation
	self assert: (self materialize: '''foo'':1') = ('foo' -> 1).
	self assert: (self materialize: '#bar:2') = (#bar -> 2).
	self assert: (self materialize: '''foo bar'':#ok') = ('foo bar' -> #ok).
	self assert: (self materialize: '123:456') = (123 -> 456).
	
	self assert: (self materialize: '''foo'' : 1') = ('foo' -> 1).
	self assert: (self materialize: '#bar : 2') = (#bar -> 2).
	self assert: (self materialize: '''foo bar'' : #ok') = ('foo bar' -> #ok).
	self assert: (self materialize: '123 : -456') = (123 -> -456).
	
	self assert: (self materialize: '#foo : 1 : 2') = (#foo -> (1 -> 2))
!

testBag
	self 
		assert: (self materialize: 'Bag{#a:2,#b:3}') 
		equals: (Bag withAll: #(a a b b b)).
	self 
		assert: (self materialize: 'Bag{}') 
		equals: Bag new.
!

testBoolean
	self assert: (self materialize: 'true') equals: true.
	self assert: (self materialize: 'false') equals: false
!

testByteArray
	self assert: (self materialize: 'ByteArray[''010203'']') = #(1 2 3) asByteArray
!

testCharacter
	self assert: (self materialize: 'Character[''A'']') == $A.
!

testClass
	self assert: (self materialize: 'Class[#Point]') equals: Point
!

testClassWithUnderscore

        | cls data reader |

        cls := Class new.
        cls setName: #A_B_C123AnonClass.

        data := STON toString: cls new.
        reader := STONReader on: data readStream.

        (reader instVarNamed: #classes) 
                at: cls name 
                put: cls.

        self assert: reader next class equals: cls

    "Modified: / 20-05-2020 / 12:24:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testColor
        self 
                assert: (self materialize: 'Color[#red]')
                equals: Color red.
        self 
                assert: (self materialize: 'Color{#red:1.0,#green:0.0,#blue:0.0,#alpha:0.4}')
                equals: (Color red copy alpha: 0.4).
        self 
                assert: (self materialize: 'Color{#red:1.0,#green:0.79339284351873047,#blue:0.79339284351873047,#alpha:1.0}')
                equals: Color red lighter lighter.

    "Modified: / 20-05-2020 / 12:23:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testConvertingNewLines
        | input result output |
        input := '''line ending with CR', String return, 
                'line ending with LF', String lf, 
                'line ending with CRLF', String crlf, ''''.
        output := 'line ending with CR', String crlf, 
                'line ending with LF', String crlf, 
                'line ending with CRLF', String crlf.
        result := (STON reader on: input readStream) newLine: String crlf; convertNewLines: true; next.
        self assert: result equals: output.
        output := 'line ending with CR', String return, 
                'line ending with LF', String return, 
                'line ending with CRLF', String return.
        result := (STON reader on: input readStream) newLine: String return; convertNewLines: true; next.
        self assert: result equals: output

    "Modified: / 04-06-2019 / 10:51:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testDate
	| date |
	date := (Date year: 2012 month: 1 day: 1) translateToUTC.
	self assert: (self materialize: 'Date[''2012-01-01Z'']') equals: date.
	self assert: (self materialize: 'Date[''2012-01-01+00:00'']') equals: date.
	date := (Date year: 2012 month: 1 day: 1) translateTo: 1 hour.
	self assert: (self materialize: 'Date[''2012-01-01+01:00'']') equals: date.
	"a missing timezone offset results in the local timezone offset being used,
	this is never written by STON, but matches the first implementation for backwards compatibility"
	date := Date year: 2012 month: 1 day: 1.
	self assert: (self materialize: 'Date[''2012-01-01'']') equals: date.
!

testDateAndTime
	| dateAndTime |
	dateAndTime := DateAndTime year: 2012 month: 1 day: 1 hour: 6 minute: 30 second: 15 offset: 1 hour.
	self assert: (self materialize: 'DateAndTime[''2012-01-01T06:30:15+01:00'']') = dateAndTime
!

testDeepStructure
        | holder deepest structure writer ston reader result |

        self skip: 'Uses too much stack for stock St/X settings'.

        "Create a deep nested structure so that the deepest element is a reference back to a top level holder."
        holder := Array with: 42.
        deepest := Array with: holder.
        structure := deepest.
        1 * 1024 timesRepeat: [ structure := Array with: structure ].
        structure := Array with: holder with: structure.
        writer := STON writer optimizeForLargeStructures.
        ston := String streamContents: [ :out | (writer on: out) nextPut: structure ].
        "After reading, the second pass will have to go down the structure to resolve the reference."
        reader := STON reader optimizeForLargeStructures.
        result := (reader on: ston readStream) next.
        self assert: result equals: structure

    "Modified: / 20-05-2020 / 11:30:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testDictionary
	| collection |
	collection := STON mapClass new at: 1 put: 1; at: 2 put: 2; yourself.
	self assert: (self materialize: '{1:1,2:2}') = collection.
	self assert: (self materialize: '{}') = STON mapClass new.
!

testDictionaryWithComplexKeys
	| collection reader |
	collection := STON mapClass new at: true put: 1; at: #(foo) put: 2; yourself.
	"allowing complex map keys used to be optional, now it is always the default"
	reader := STONReader on: '{true:1,[#foo]:2}' readStream.
	self assert: reader next = collection
!

testDictionaryWithIndirectReferenceKeys
	| keysCollection dictionary ston object |
	keysCollection := OrderedCollection streamContents: [ :out |
		10 timesRepeat: [ out nextPut: UUID new ] ].
	dictionary := Dictionary new.
	keysCollection doWithIndex: [ :each :index | 
		dictionary at: (Array with: each) put: index ].
	object := Array with: keysCollection with: dictionary.
	ston := STON toStringPretty: object.
	object := (STON reader on: ston readStream) next.
	object first doWithIndex: [ :each :index |
		self assert: (object second at: (Array with: each)) equals: index ].
	self assert: object second isHealthy 
!

testDictionaryWithReferenceKeys
	| keysCollection dictionary ston object |
	keysCollection := OrderedCollection streamContents: [ :out |
		10 timesRepeat: [ out nextPut: UUID new ] ].
	dictionary := Dictionary new.
	keysCollection doWithIndex: [ :each :index | 
		dictionary at: each put: index ].
	object := Array with: keysCollection with: dictionary.
	ston := STON toStringPretty: object.
	object := (STON reader on: ston readStream) next.
	object first doWithIndex: [ :each :index |
		self assert: (object second at: each) equals: index ].
	self assert: object second isHealthy 
!

testDiskFile
        self assert: (self materialize: 'FILE[''foo.txt'']') equals: 'foo.txt' asFilename.
        self assert: (self materialize: 'FILE[''/tmp/foo.txt'']') equals: '/tmp/foo.txt' asFilename.
        self assert: (self materialize: 'FILE[''tmp/foo.txt'']') equals: 'tmp/foo.txt' asFilename.
        self assert: (self materialize: 'FILE[''/tmp'']') equals: '/tmp' asFilename.

    "Modified: / 20-05-2020 / 12:42:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testError
	#( 'foo' '{foo:}' '{foo,}' '[1,]' '+1' ']' '#' '' '  ' '	' 'nul' 'tru' 'fals' ) do: [ :each |
		self 
			should: [ self materialize: each ] 
			raise: STONReaderError ]
!

testFloat
	self assert: ((self materialize: '1.5') closeTo: 1.5).
	self assert: ((self materialize: '-1.5') closeTo: -1.5).
	self assert: (self materialize: '0.0') isZero.
	self assert: (Float pi closeTo: (self materialize: '3.14149')).
	self assert: (1/3 closeTo: (self materialize: '0.333333')).
	self assert: ((self materialize: '1.0e100') closeTo: (10 raisedTo: 100)).
	self assert: ((self materialize: '1.0e-100') closeTo: (10 raisedTo: -100)).
	self assert: ((self materialize: '-1.0e-100') closeTo: (10 raisedTo: -100) negated)
!

testFraction
	self assert: (self materialize: '1/3') equals: 1/3.
	self assert: (self materialize: '-1/3') equals: -1/3.
	self assert: (self materialize: '100/11') equals: 100/11.
!

testIdentityDictionary
	| collection |
	collection := IdentityDictionary new at: 1 put: 1; at: 2 put: 2; yourself.
	self assert: (self materialize: 'IdentityDictionary{1:1,2:2}') = collection.
	self assert: (self materialize: 'IdentityDictionary{}') = IdentityDictionary new.
!

testIllegalCharacterEscapes
	self should: [ STON fromString: '''\a''' ] raise: STONReaderError.
	self should: [ STON fromString: '''\u''' ] raise: STONReaderError.
	self should: [ STON fromString: '''\u00''' ] raise: STONReaderError.
	self should: [ STON fromString: '''\u000''' ] raise: STONReaderError.
	self should: [ STON fromString: '''\*''' ] raise: STONReaderError
!

testInteger
	self assert: (self materialize: '1') = 1.
	self assert: (self materialize: '-1') = -1.
	self assert: (self materialize: '0') = 0.
	self assert: (self materialize: '1234567890') = 1234567890.
	self assert: (self materialize: '-1234567890') = -1234567890
!

testList
	self assert: STON listClass = Array.
	self assert: (self materialize: '[1,2,3]') = (STON listClass with: 1 with: 2 with: 3).
	self assert: (self materialize: '[]') = STON listClass new
!

testMap
	self assert: (self materialize: '{#foo:1}') = (STON mapClass new at: #foo put: 1; yourself).
	self assert: (self materialize: '{}') = STON mapClass new
!

testMetaclass
	self assert: (self materialize: 'Metaclass[#Point]') equals: Point class
!

testMimeType
        self skip: 'No ZnMimeType in St/X'.

"/        self 
"/                assert: (self materialize: 'MimeType[''application/json'']') 
"/                equals: ZnMimeType applicationJson.
"/        self 
"/                assert: (self materialize: 'MimeType[''text/plain;charset=utf-8'']') 
"/                equals: ZnMimeType textPlain.

    "Modified: / 20-05-2020 / 12:06:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testMultiple
	| reader |
	reader := STON reader 
		on: '123 -123 nil #foo true [ 0 ] false { #one : 1 }' readStream.
	self deny: reader atEnd.
	self assert: reader next equals: 123. 
	self assert: reader next equals: -123. 
	self assert: reader next equals: nil. 
	self assert: reader next equals: #foo. 
	self assert: reader next equals: true. 
	self assert: reader next equals: { 0 }. 
	self assert: reader next equals: false. 
	self assert: reader next equals: (Dictionary with: #one -> 1). 
	self assert: reader atEnd.
!

testNewSymbol
	| n notASymbol shouldBeSymbol |
	
	"Find a name that has not yet been interned"
	n := 0.
	[ Symbol hasInterned: (notASymbol := 'notASymbol', n printString) ifTrue: [ :symbol | symbol ] ] 
		whileTrue: [ n := n + 1 ].
	"Parsing the new, not yet interned name should create a new Symbol"
	shouldBeSymbol := self materialize: '#', notASymbol.
	self assert: (shouldBeSymbol isSymbol and: [ notASymbol = shouldBeSymbol asString ])
!

testNil
	self assert: (self materialize: 'nil') isNil
!

testNonBMPCharacterDecoding
        "Characters not in the Basic Multilingual Plane are encoded as a UTF-16 surrogate pair"

        | string object |
        string := 16r1D11E asCharacter asString. "MUSICAL SYMBOL G CLEF"
        object := (STON fromString: '''\uD834\uDD1E''').
        self assert: object equals: string

    "Modified: / 20-05-2020 / 12:05:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testNull
	self assert: (self materialize: 'null') isNil
!

testObject
	self assert: (self materialize: 'Point[1,2]') = (1@2).
	self assert: (self materialize: 'Point[1.5,-0.5]') = (1.5 @ -0.5).
!

testOrderedCollection
	| collection |
	collection := OrderedCollection with: 1 with: 2 with: 3.
	self assert: (self materialize: 'OrderedCollection[1,2,3]') = collection.
	self assert: (self materialize: 'OrderedCollection[]') = OrderedCollection new.
!

testPoint
	self assert: (self materialize: 'Point[1,2]') = (1@2)
!

testReferenceCycle
	| array |
	array := (self materialize: '[1,@1]').
	self assert: array class = STON listClass.
	self assert: array size = 2.
	self assert: array first = 1.
	self assert: array second == array
!

testReferenceSharing
	| one array |
	one := { #one }.
	array := (self materialize: '[[#one],@2,@2]').
	self assert: array = (STON listClass with: one with: one with: one).
	self assert: array first == array second.
	self assert: array first == array third
!

testScaledDecimal
        self skip.

        self assert: (self materialize: '1/3s2') equals: 1/3s2.
        self assert: (self materialize: '-1/3s2') equals: -1/3s2.
        self assert: (self materialize: '1/3s10') equals: 1/3s10.
        self assert: (self materialize: '-1/3s10') equals: -1/3s10.

    "Modified: / 20-05-2020 / 12:03:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testSetWithIndirectReferenceElements
	| elementsCollection set ston object |
	elementsCollection := OrderedCollection streamContents: [ :out |
		10 timesRepeat: [ out nextPut: UUID new ] ].
	set := Set withAll: (elementsCollection collect: [ :each | Array with: each ]).
	object := Array with: elementsCollection with: set.
	ston := STON toStringPretty: object.
	object := STON fromString: ston readStream.
	object first do: [ :each |
		self assert: (object second includes: (Array with: each)) ].
	self assert: object second isHealthy 
!

testSetWithReferenceElements
	| elementsCollection set ston object |
	elementsCollection := OrderedCollection streamContents: [ :out |
		10 timesRepeat: [ out nextPut: UUID new ] ].
	set := Set withAll: elementsCollection.
	object := Array with: elementsCollection with: set.
	ston := STON toStringPretty: object.
	object := STON fromString: ston readStream.
	object first do: [ :each |
		self assert: (object second includes: each) ].
	self assert: object second isHealthy 
!

testStreaming
	| reader |
	reader := STON reader 
		on: '1 2 3 4 5 6 7 8 9 10' readStream.
	self 
		assert: (Array streamContents: [ :stream |
			[ reader atEnd] whileFalse: [ 
				stream nextPut: reader next ] ]) sum
		equals: #(1 2 3 4 5 6 7 8 9 10) sum
!

testString
        | string |
        self assert: (self materialize: '''foo''') = 'foo'.
        self assert: (self materialize: '''FOO''') = 'FOO'.
        self assert: (self materialize: '''\u00E9l\u00E8ve en Fran\u00E7ais''') = #[195 169 108 195 168 118 101 32 101 110 32 70 114 97 110 195 167 97 105 115] utf8Decoded .
        string := String withAll: { 
                $". $'. $\. $/. Character tab. Character cr. Character lf.  Character newPage. Character backspace }.
        self assert: (self materialize: '''\"\''\\\/\t\r\n\f\b''') = string.

    "Modified: / 20-05-2020 / 12:03:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testSymbol
	self assert: (self materialize: '#''foo''') = #foo.
	self assert: (self materialize: '#foo') = #foo
!

testTime
        | time |
        time := Time hour: 6 minute: 30 second: 15.
        self assert: (self materialize: 'Time[''06:30:15'']') equals: time.
        time := Time hours: 6 minutes: 30 seconds: 15 milliseconds: 123.
        self assert: (self materialize: 'Time[''06:30:15.123'']') equals: time.

    "Modified: / 20-05-2020 / 12:01:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testURL
	self 
		assert: (self materialize: 'URL[''https://pharo.org/files/pharo.png'']') 
		equals: 'https://pharo.org/files/pharo.png' asUrl.
	self 
		assert: (self materialize: 'URL[''mailto:sven@stfx.eu'']') 
		equals: 'mailto:sven@stfx.eu' asUrl.
	self 
		assert: (self materialize: 'URL[''file:///var/log/system.log'']') 
		equals: 'file:///var/log/system.log' asUrl.
	self 
		assert: (self materialize: 'URL[''scheme://user:password@host:123/var/log/system.log?foo=1&bar#frag'']') 
		equals: 'scheme://user:password@host:123/var/log/system.log?foo=1&bar#frag' asUrl.
!

testUnknownClasses
	| input object |
	input := 'FooBar { #foo : 1, #bar : true }'.
	self should: [ self materialize: input ] raise: STONReaderError.
	object := STON reader 
		acceptUnknownClasses: true; 
		on: input readStream; 
		next.
	self assert: object class equals: STON mapClass.
	self assert: (object at: #foo) equals: 1.
	self assert: (object at: #bar).
	self assert: (object at: STON classNameKey) equals: #FooBar
!

testUser
	| user |
	(user := STONTestUser new)
		username: 'john@foo.com';
		password: 'secret1'.
	self assert: (self materialize: 'STONTestUser{#username:''john@foo.com'',#password:''secret1'',#enabled:true}') = user
!

testUser2
	| user |
	(user := STONTestUser2 new)
		username: 'john@foo.com';
		password: 'secret1'.
	self assert: (self materialize: 'STONTestUser2{#username:''john@foo.com'',#password:''secret1'',#enabled:true}') = user
!

testWhitespace
	| whitespace |
	whitespace := { Character space. Character tab. Character cr. Character lf }.
	self assert: (self materialize: whitespace, '123') = 123
	
! !

!STONReaderTests class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !