RegressionTests__CECollectionExtensionTest.st
author Stefan Vogel <sv@exept.de>
Tue, 11 Jun 2019 10:34:41 +0200
changeset 2321 32ea6329f5ad
parent 1635 7fb3c947bad4
permissions -rw-r--r--
class: stx_goodies_regression class changed: #classNamesAndAttributes make classes autoloaded that stc cannot compile (yet)

"{ Package: 'stx:goodies/regression' }"

"{ NameSpace: RegressionTests }"

TestCase subclass:#CECollectionExtensionTest
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'tests-Regression-CollectionExtensions'
!


!CECollectionExtensionTest methodsFor:'as yet unclassified'!

testDetectIfOne
	| element result |
	result := #(1 2 3) detect: [:each | each = 2] ifOne: [:theOne | element := theOne ].
	self assert: element = 2.
	self assert: result = 2.

	element := nil.
	result := #(1 2 3) detect: [:each | each = 4] ifOne: [:theOne | element := theOne ].
	self assert: element isNil.
	self assert: result isNil.
!

testDetectIfOneIfNone
	| element |
	#(1 2 3) detect: [:each | each = 2] ifOne: [:theOne | element := theOne ] ifNone: [element := nil].
	self assert: element = 2.

	#(1 2 3) detect: [:each | each = 4] ifOne: [:theOne | element := theOne ] ifNone: [element := nil].
	self assert: element isNil.
! !

!CECollectionExtensionTest methodsFor:'collect as set'!

testCollectAsSet
	"self debug: #testCollectAsSet"

	self assert: ((#() collectAsSet: [:each | each odd]) = Set new).
	self assert: (#(1 2 3 4 5 6) collectAsSet: [:each | each odd])
					 = (Set with: true with: false).
	self assert: (#(1 3 5 7 9 11) collectAsSet: [:each | each odd])
					= (Set with: true).

	self assert: (#(1 2 3 4 5 4 3 2 1) collectAsSet: [:each | each]) = (1 to: 5) asSet.


!

testCollectAsSetUsingSymbol
	"self debug: #testCollectAsSetUsingSymbol"

	self assert: ((#() collectAsSet: #odd) = Set new).
	self assert: (#(1 2 3 4 5 6) collectAsSet: #odd)
					 = (Set with: true with: false).
	self assert: (#(1 3 5 7 9 11) collectAsSet: #odd)
					= (Set with: true).
! !

!CECollectionExtensionTest methodsFor:'flat collect'!

testFlatCollect
	"self debug: #testFlatCollect"


!

testFlatCollectArray
	"self debug: #testFlatCollectArray"

	self assert: ((#((1 2) (3 4) (5 3)) flatCollect: [ :each | each ]) = #(1 2 3 4 5 3)).
	self assert: ((#((1 2) (2 3) (1 3 4)) flatCollect: [:each | each]) = #(1 2 2 3 1 3 4)).

	self assert: ((#((1 2) (2 3) () ()) flatCollect: [:each | each]) = #(1 2 2 3)).

	self assert: ((#((1 2) (2 3) (1 3 4)) flatCollect: [:each| Array with: each])
					=  #(#(1 2) #(2 3) #(1 3 4))).

	self assert: ((#((1 2) (2 3) (1 3 4)) flatCollect: [:each| Set with: each])
					=  #(#(1 2) #(2 3) #(1 3 4))).

!

testFlatCollectSet
        "self debug: #testFlatCollectSet"

        self assert: ((#((1 2) (1 2) (1 3 4)) asSet  flatCollect: [:each | each]) = #(1 1 2 3 4) asSet).
        self assert: ((#() asSet flatCollect: [:each | each]) = #() asSet).

        self assert:  ((#((1 2) () (1 3 4)) asSet  flatCollect: [:each | each]) = #(1 1 2 3 4) asSet).
        self assert:  ((#((1 2) #((99)) (1 3 4)) asSet  flatCollect: [:each | each])
                                        = #(1 1 2 3 4 (99)) asSet).
        self assert:  ((#((1 2) #(()) (1 3 4)) asSet  flatCollect: [:each | each])
                                        = #(1 1 2 3 4 ()) asSet).

    "Modified: / 11-07-2017 / 19:51:47 / mawalch"
! !

!CECollectionExtensionTest methodsFor:'flatten'!

testDeepFlatten

	self assert: #(1 2 3)
		equals: #((1) (2) (3)) deepFlatten.
	self assert: #(1 2 3 1 2)
		equals: #((1 2) (3 1 2)) deepFlatten.
!

testDeepFlattenIsRecursive

	self assert: #(1 2 4 5 3)
		equals: #((1 2) ((4 5) 3)) deepFlatten.
!

testDeepFlattenOnFlatCollection

	self assert: #(1 2 4)
		equals: #(1 2 4) deepFlatten.
	self assert: #(5 3)
		equals: #(5 ((3))) deepFlatten.
!

testDeepFlattenOnString
	"don't flatten strings"

	self assert: #(a b c d e)
		equals: #((a b) ((c d) e)) deepFlatten.
	self assert: #('foo' 'bar' 'zorg')
		equals: #(('foo' ('bar')) 'zorg') deepFlatten
!

testFlatten

	self assert: #(1 2 3)
		equals: #((1) (2) (3)) flatten.
	self assert: #(1 2 3 1 2)
		equals: #((1 2) (3 1 2)) flatten.
	self assert: #(a b (c d))
		equals: #((a b) ((c d))) flatten.
	self should: [ #((1 2) 3) flatten ] raise: Error.
! !

!CECollectionExtensionTest methodsFor:'groupedBy'!

testGroupedBy
	"self debug: #testGroupedBy"

	| res |
	res := #(1 2 3 4 5) asOrderedCollection
				groupedBy: [:each | each odd].
	self assert:   (res at: true) = #(1 3 5) asOrderedCollection.
	self assert: (res at: false) = #(2 4) asOrderedCollection
!

testGroupedByArray
	"self debug: #testGroupedByArray"

	| res |
	res := #(1 2 3 4 5) groupedBy: [:each | each odd].
	self assert:   (res at: true) = #(1 3 5).
	self assert: (res at: false) = #(2 4)
!

testGroupedBySet
	"self debug: #testGroupedBySet"

	| res |
	res := #(1 2 3 4 5 3 4 5) asSet groupedBy: [:each | each odd].
	self assert: (res at: true) = #(1 3 5) asSet.
	self assert: (res at: false) = #(2 4) asSet
! !

!CECollectionExtensionTest methodsFor:'symbol - value'!

testSymbolInPlaceOfBlock
	"self debug: #testSymbolInPlaceOfBlock"

	self assert: (#(1 2 3 4) collect: #odd) =  #(true false true false).
	self assert: (#(1 2 3 4) select: #odd) =  #(1 3).
! !

!CECollectionExtensionTest class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !