Commit d13b11d0 authored by geronimo romczyk's avatar geronimo romczyk
Browse files

el que hicimos en clase con la clase renombrada

parent 8a00cc6c
!classDefinition: #OOStackTest category: 'Stack-Exercise'!
TestCase subclass: #OOStackTest
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!OOStackTest methodsFor: 'test' stamp: 'GR 4/26/2021 18:44:01'!
test01StackShouldBeEmptyWhenCreated
| stack |
stack := AuxStackd new.
self assert: stack isEmpty! !
!OOStackTest methodsFor: 'test' stamp: 'GR 4/26/2021 18:44:00'!
test02PushAddElementsToTheStack
| stack |
stack := AuxStackd new.
stack push: 'something'.
self deny: stack isEmpty! !
!OOStackTest methodsFor: 'test' stamp: 'GR 4/26/2021 18:44:01'!
test03PopRemovesElementsFromTheStack
| stack |
stack := AuxStackd new.
stack push: 'something'.
stack pop.
self assert: stack isEmpty! !
!OOStackTest methodsFor: 'test' stamp: 'GR 4/26/2021 18:44:01'!
test04PopReturnsLastPushedObject
| stack pushedObject |
stack := AuxStackd new.
pushedObject := 'something'.
stack push: pushedObject.
self assert: stack pop = pushedObject! !
!OOStackTest methodsFor: 'test' stamp: 'GR 4/26/2021 18:44:00'!
test05StackBehavesLIFO
| stack firstPushedObject secondPushedObject |
stack := AuxStackd new.
firstPushedObject := 'firstObject'.
secondPushedObject := 'secondObject'.
stack push: firstPushedObject.
stack push: secondPushedObject.
self assert: stack pop = secondPushedObject.
self assert: stack pop = firstPushedObject.
self assert: stack isEmpty
! !
!OOStackTest methodsFor: 'test' stamp: 'GR 4/26/2021 18:44:00'!
test06TopReturnsLastPushedObject
| stack pushedObject |
stack := AuxStackd new.
pushedObject := 'something'.
stack push: pushedObject.
self assert: stack top = pushedObject.
! !
!OOStackTest methodsFor: 'test' stamp: 'GR 4/26/2021 18:44:00'!
test07TopDoesNotRemoveObjectFromStack
| stack pushedObject |
stack := AuxStackd new.
pushedObject := 'something'.
stack push: pushedObject.
self assert: stack size = 1.
stack top.
self assert: stack size = 1.
! !
!OOStackTest methodsFor: 'test' stamp: 'GR 4/26/2021 18:44:00'!
test08CanNotPopWhenThereAreNoObjectsInTheStack
| stack |
stack := AuxStackd new.
self
should: [ stack pop ]
raise: Error - MessageNotUnderstood
withExceptionDo: [ :anError |
self assert: anError messageText = AuxStackd stackEmptyErrorDescription ]
! !
!OOStackTest methodsFor: 'test' stamp: 'GR 4/26/2021 18:44:01'!
test09CanNotPopWhenThereAreNoObjectsInTheStackAndTheStackHadObjects
| stack |
stack := AuxStackd new.
stack push: 'something'.
stack pop.
self
should: [ stack pop ]
raise: Error - MessageNotUnderstood
withExceptionDo: [ :anError |
self assert: anError messageText = AuxStackd stackEmptyErrorDescription ]
! !
!OOStackTest methodsFor: 'test' stamp: 'GR 4/26/2021 18:44:00'!
test10CanNotTopWhenThereAreNoObjectsInTheStack
| stack |
stack := AuxStackd new.
self
should: [ stack top ]
raise: Error - MessageNotUnderstood
withExceptionDo: [ :anError |
self assert: anError messageText = AuxStackd stackEmptyErrorDescription ]
! !
!classDefinition: #SentenceFinderByPrefixTest category: 'Stack-Exercise'!
TestCase subclass: #SentenceFinderByPrefixTest
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!classDefinition: #AuxStackd category: 'Stack-Exercise'!
Object subclass: #AuxStackd
instanceVariableNames: 'elements'
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!AuxStackd methodsFor: 'operations' stamp: 'GR 4/26/2021 18:28:09'!
isEmpty
"elements ifNil: [^true] ifNotNil: [^false]."
self subclassResponsibility.
! !
!AuxStackd methodsFor: 'operations' stamp: 'GR 4/26/2021 18:00:52'!
pop
(self isEmpty) ifTrue:[
^self error: self class stackEmptyErrorDescription.
] ifFalse: [
|firstElement|
firstElement := elements first.
elements removeFirst.
(elements isEmpty) ifTrue:[elements := nil.].
^firstElement.
].
! !
!AuxStackd methodsFor: 'operations' stamp: 'GR 4/26/2021 18:27:33'!
push: element
"
(self isEmpty) ifTrue:[
elements := OrderedCollection new.
].
elements addFirst: element.
"
self subclassResponsibility.
! !
!AuxStackd methodsFor: 'operations' stamp: 'GR 4/26/2021 17:54:22'!
size
(self isEmpty) ifTrue:[
^0.
] ifFalse: [
^elements size.
].
! !
!AuxStackd methodsFor: 'operations' stamp: 'GR 4/26/2021 18:01:10'!
top
(self isEmpty) ifTrue:[
^self error: self class stackEmptyErrorDescription.
] ifFalse: [
^elements first.
].
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'AuxStackd class' category: 'Stack-Exercise'!
AuxStackd class
instanceVariableNames: ''!
!AuxStackd class methodsFor: 'error descriptions' stamp: 'NR 4/22/2021 17:22:41'!
stackEmptyErrorDescription
^ 'Stack is empty!!!!!!'! !
!classDefinition: #EmptyStack category: 'Stack-Exercise'!
AuxStackd subclass: #EmptyStack
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!EmptyStack methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:04:43'!
isEmpty
^true.! !
!EmptyStack methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:21:33'!
pop
^self error: self class stackEmptyErrorDescription.! !
!EmptyStack methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:29:04'!
push: element
^OneElementStack initializeWith: element.! !
!classDefinition: #NotEmptyStack category: 'Stack-Exercise'!
AuxStackd subclass: #NotEmptyStack
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!NotEmptyStack methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:06:48'!
isEmpty
^false! !
!NotEmptyStack methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:21:11'!
push: anElement
self subclassResponsibility ! !
!classDefinition: #MoreThanOneElementStack category: 'Stack-Exercise'!
NotEmptyStack subclass: #MoreThanOneElementStack
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!MoreThanOneElementStack methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:19:44'!
initializeWith: anElement andTop: topElement
elements := OrderedCollection new.
elements add: anElement.
elements addFirst: topElement.! !
!MoreThanOneElementStack methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:20:30'!
push: anElement
elements addFirst: anElement.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'MoreThanOneElementStack class' category: 'Stack-Exercise'!
MoreThanOneElementStack class
instanceVariableNames: ''!
!MoreThanOneElementStack class methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:18:11'!
initializeWith: anElement andTop: topElement
^self new initializeWith: anElement andTop: topElement.! !
!classDefinition: #OneElementStack category: 'Stack-Exercise'!
NotEmptyStack subclass: #OneElementStack
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!OneElementStack methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:16:05'!
initializeWith: element
elements := element.! !
!OneElementStack methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:17:21'!
push: element
^MoreThanOneElementStack initializeWith: elements andTop: element.
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'OneElementStack class' category: 'Stack-Exercise'!
OneElementStack class
instanceVariableNames: ''!
!OneElementStack class methodsFor: 'as yet unclassified' stamp: 'GR 4/26/2021 18:10:34'!
initializeWith: element
^self new initializeWith: element.! !
!classDefinition: #SentenceFinderByPrefix category: 'Stack-Exercise'!
Object subclass: #SentenceFinderByPrefix
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!classDefinition: #StackAuxiliar category: 'Stack-Exercise'!
Object subclass: #StackAuxiliar
instanceVariableNames: 'elements'
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!StackAuxiliar methodsFor: 'operations' stamp: 'GR 4/26/2021 18:37:58'!
isEmpty
"elements ifNil: [^true] ifNotNil: [^false]."
self subclassResponsibility.
! !
!StackAuxiliar methodsFor: 'operations' stamp: 'GR 4/26/2021 18:37:58'!
pop
(self isEmpty) ifTrue:[
^self error: self class stackEmptyErrorDescription.
] ifFalse: [
|firstElement|
firstElement := elements first.
elements removeFirst.
(elements isEmpty) ifTrue:[elements := nil.].
^firstElement.
].
! !
!StackAuxiliar methodsFor: 'operations' stamp: 'GR 4/26/2021 18:37:58'!
push: element
"
(self isEmpty) ifTrue:[
elements := OrderedCollection new.
].
elements addFirst: element.
"
self subclassResponsibility.
! !
!StackAuxiliar methodsFor: 'operations' stamp: 'GR 4/26/2021 18:37:58'!
size
(self isEmpty) ifTrue:[
^0.
] ifFalse: [
^elements size.
].
! !
!StackAuxiliar methodsFor: 'operations' stamp: 'GR 4/26/2021 18:37:58'!
top
(self isEmpty) ifTrue:[
^self error: self class stackEmptyErrorDescription.
] ifFalse: [
^elements first.
].
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'StackAuxiliar class' category: 'Stack-Exercise'!
StackAuxiliar class
instanceVariableNames: ''!
!StackAuxiliar class methodsFor: 'error descriptions' stamp: 'GR 4/26/2021 18:37:58'!
stackEmptyErrorDescription
^ 'Stack is empty!!!!!!'! !
Markdown is supported
0% or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment