Commit a8b4e6df authored by Joaquín P. Centeno's avatar Joaquín P. Centeno
Browse files

Add solución con ifs. pasa tests ej a

No related merge requests found
......@@ -139,24 +139,112 @@ test10CanNotTopWhenThereAreNoObjectsInTheStack
!classDefinition: #SentenceFinderByPrefixTest category: #'Stack-Exercise'!
TestCase subclass: #SentenceFinderByPrefixTest
instanceVariableNames: ''
instanceVariableNames: 'stack results'
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!SentenceFinderByPrefixTest methodsFor: 'setUp/tearDown' stamp: 'JPC 5/14/2020 23:56:31'!
setup
stack _ OOStack new.
stack push: 'winter is coming'.
stack push: 'winning is everything'.
stack push: 'The winds of Winter'.
stack push: 'Winter is here'.! !
!SentenceFinderByPrefixTest methodsFor: 'testing' stamp: 'JPC 5/15/2020 00:15:55'!
test01BuscarAlgoQueNoExisteDevuelveSetVacio
results _ SentenceFinderByPrefix find: 'foo' inOOStack: stack.
self assert: results equals: Set new.! !
!classDefinition: #Cons category: #'Stack-Exercise'!
Object subclass: #Cons
instanceVariableNames: 'head tail object elements_CHANGE_ME'
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!Cons methodsFor: 'initialization' stamp: 'JPC 5/14/2020 23:15:24'!
initializeWithHead: anObject tail: aCons
head _ anObject.
tail _ aCons.! !
!Cons methodsFor: 'accessing' stamp: 'JPC 5/14/2020 23:17:17'!
head
^head! !
!Cons methodsFor: 'accessing' stamp: 'JPC 5/14/2020 23:17:37'!
tail
^tail! !
!Cons methodsFor: 'as yet unclassified' stamp: 'JPC 5/14/2020 23:26:12'!
size
^ tail ifNil: [1] ifNotNil: [1 + tail size].! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'Cons class' category: #'Stack-Exercise'!
Cons class
instanceVariableNames: 'object elements_CHANGE_ME'!
!Cons class methodsFor: 'instance creation' stamp: 'JPC 5/14/2020 23:13:56'!
initializeWithHead: aString tail: anUndefinedObject
"DO NOT FORGET TO RENAME COLLABORATORS AND REMOVE THIS COMMENT!!!!"
self shouldBeImplemented.
^self new initializeInitializeWithHead: aString tail: anUndefinedObject ! !
!classDefinition: #OOStack category: #'Stack-Exercise'!
Object subclass: #OOStack
instanceVariableNames: ''
instanceVariableNames: 'elements'
classVariableNames: ''
poolDictionaries: ''
category: 'Stack-Exercise'!
!OOStack methodsFor: 'testing' stamp: 'JPC 5/14/2020 21:40:59'!
isEmpty
^ elements isNil.! !
!OOStack methodsFor: 'insertion' stamp: 'JPC 5/14/2020 23:14:36'!
push: anObject
elements _ Cons new initializeWithHead: anObject tail: elements.! !
!OOStack methodsFor: 'FIXME' stamp: 'JPC 5/14/2020 23:34:29'!
pop
| topObject |
elements ifNil: [^ self error: self class stackEmptyErrorDescription].
topObject _ elements head.
elements _ elements tail.
^ topObject.! !
!OOStack methodsFor: 'FIXME' stamp: 'JPC 5/14/2020 23:22:59'!
size
^ elements size.! !
!OOStack methodsFor: 'accessing' stamp: 'JPC 5/14/2020 23:35:28'!
top
elements ifNil: [^ self error: self class stackEmptyErrorDescription].
^ elements head.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'OOStack class' category: #'Stack-Exercise'!
OOStack class
instanceVariableNames: ''!
instanceVariableNames: 'elements'!
!OOStack class methodsFor: 'error descriptions' stamp: 'HernanWilkinson 5/7/2012 11:51'!
stackEmptyErrorDescription
......
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