extensions.st
author Claus Gittinger <cg@exept.de>
Wed, 29 Jun 2011 21:15:49 +0200
changeset 222 8e6f482297fa
parent 220 c2030e11e775
child 236 037f084beb1b
permissions -rw-r--r--
Jan's 4.1 version

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

!

!Behavior methodsFor:'deprecated'!

sunitAllSelectors

    <resource: #obsolete>
    self obsoleteMethodWarning: 'Use #testSelectors instead'.
    ^self allSelectors

    "Modified: / 11-09-2010 / 15:07:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !
!Behavior methodsFor:'Camp Smalltalk'!

sunitSelectors

    ^self selectors

    "Modified: / 11-09-2010 / 15:07:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !
!Block methodsFor:'Camp Smalltalk'!

sunitEnsure: aBlock
	
	^self ensure: aBlock
! !
!Block methodsFor:'Camp Smalltalk'!

sunitOn: aSignal do: anExceptionBlock
	
	^self on: aSignal do: anExceptionBlock
! !
!Class methodsFor:'Camp Smalltalk'!

sunitName
	
	^self name
! !
!Exception methodsFor:'Camp Smalltalk'!

sunitAnnounce: aTestCase toResult: aTestResult
	aTestResult addError: aTestCase.
	self sunitExitWith: false.
! !
!Exception methodsFor:'Camp Smalltalk'!

sunitExitWith: aValue
	
	^self return: aValue
! !
!Object methodsFor:'Camp Smalltalk'!

sunitAddDependent: anObject
	
	self addDependent: anObject
! !
!Object methodsFor:'Camp Smalltalk'!

sunitChanged: aspect
	
	self changed: aspect
! !
!Object methodsFor:'Camp Smalltalk'!

sunitRemoveDependent: anObject
	
	self removeDependent: anObject
! !
!String methodsFor:'Camp Smalltalk'!

sunitAsSymbol
	
	^self asSymbol
! !
!String methodsFor:'Camp Smalltalk'!

sunitMatch: aString
	
	^self match: aString
! !
!String methodsFor:'deprecated'!

sunitSubStrings

        <resource: #obsolete>
        
        | stream answer index |
        answer := OrderedCollection new.
        stream := ReadStream on: self.
        [stream atEnd]
                whileFalse:
                        [[stream atEnd ifTrue: [^answer asArray].
                        stream peek > Character space] whileFalse: [stream next].
                        index := stream position + 1.
                        [stream atEnd or: [stream peek <= Character space]] whileFalse: [stream next].
                        answer
                                add:
                                        (self
                                                copyFrom: index
                                                to: stream position)].
        ^answer asArray

    "Modified: / 11-09-2010 / 15:14:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !
!Symbol methodsFor:'Camp Smalltalk'!

sunitAsClass
	
	^SUnitNameResolver classNamed: self
! !
!GenericException class methodsFor:'Camp Smalltalk'!

sunitSignalWith: aString

    <resource: #skipInDebuggersWalkBack>

    ^self raiseSignal: aString

    "Modified: / 05-12-2009 / 18:29:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !