Skip to content

Commit

Permalink
tamo
Browse files Browse the repository at this point in the history
  • Loading branch information
higlak committed May 16, 2022
1 parent 44bf8b3 commit 7b7ee82
Show file tree
Hide file tree
Showing 3 changed files with 717 additions and 31 deletions.
3 changes: 3 additions & 0 deletions 04-Stack/README.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
*Se pide además analizar cuál de los modelos anteriores cree que es más sencillo extender para representarla*

Nosotros decidimos utilizar la implementacion de la matafora de las torres de hannoi. Si bien no fue complicado extender el modelo para que contemple el caso del stack lleno, creemos que hubiera sido mas sencillo hacerlo con la implementacion de estados. Principalmente porque nosotros tuvimos que transformar una clase que era concreta en una abstracta que tenia dos subclases, lo que tambien nos obligo a cambiar la forma en la que se creaban las instancias y por eso tuvimos que refactorizar el codigo. De haberlo hecho con los estados, esto no hubiera sucedio ya que era tan simple como agregar una subclase mas. Y gracias al switch dinamico que se usa a la hora de la creacion, no hubiera habido que refactorizar nada. Es por esto que podemos concluir que por lo menos en este caso, la implentacion de estados resulto mas escalable.
130 changes: 99 additions & 31 deletions 04-Stack/Stack-Exercise.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,45 +14,90 @@ test01LimitedStackIsEmptyAndMaximumSizeIsCorrectWhenCreated

self assert: (limitedStack isEmpty and: [limitedStack limit = 5]).! !

!OOStackTest methodsFor: 'LimitedStack tests' stamp: 'pa 5/16/2022 16:03:07'!
test02CanNotPushIfStackIsFull

!OOStackTest methodsFor: 'general Stack tests' stamp: 'NR 5/13/2020 13:29:55'!
| limitedStack |

limitedStack := OOStack withLimit: 1.
limitedStack push:1.

self
should: [ limitedStack push: 1]
raise: Error - MessageNotUnderstood
withExceptionDo: [ :anError |
self assert: anError messageText = LimitedStack stackIsFullErrorDescription ]! !

!OOStackTest methodsFor: 'LimitedStack tests' stamp: 'pa 5/16/2022 16:11:58'!
test03LimitCanNotBeNegative

self
should: [ OOStack withLimit: -1.]
raise: Error - MessageNotUnderstood
withExceptionDo: [ :anError |
self assert: anError messageText = LimitedStack maximumSizeCanNotBeLessThanZeroErrorDescription ].! !

!OOStackTest methodsFor: 'LimitedStack tests' stamp: 'pa 5/16/2022 16:12:16'!
test04CanNeverPushIfLimitIsZero

| limitedStack |

limitedStack := OOStack withLimit: 0.

self
should: [ limitedStack push: 1]
raise: Error - MessageNotUnderstood
withExceptionDo: [ :anError |
self assert: anError messageText = LimitedStack stackIsFullErrorDescription ]! !


!OOStackTest methodsFor: 'general Stack tests' stamp: 'FRJ 5/16/2022 12:36:30'!
test01StackShouldBeEmptyWhenCreated

| unlimitedStack |

unlimitedStack := OOStack newUnlimited.

self assert: unlimitedStack isEmpty! !

!OOStackTest methodsFor: 'general Stack tests' stamp: 'pa 5/16/2022 15:27:13'!
test02PushAddElementsToTheStack

| stack |

stack := OOStack new.
stack := OOStack newUnlimited .
stack push: 'something'.

self deny: stack isEmpty! !

!OOStackTest methodsFor: 'general Stack tests' stamp: 'NR 5/13/2020 13:30:01'!
!OOStackTest methodsFor: 'general Stack tests' stamp: 'pa 5/16/2022 15:29:19'!
test03PopRemovesElementsFromTheStack

| stack |

stack := OOStack new.
stack := OOStack newUnlimited.
stack push: 'something'.
stack pop.

self assert: stack isEmpty! !

!OOStackTest methodsFor: 'general Stack tests' stamp: 'NR 5/13/2020 13:30:09'!
!OOStackTest methodsFor: 'general Stack tests' stamp: 'pa 5/16/2022 15:27:23'!
test04PopReturnsLastPushedObject

| stack pushedObject |

stack := OOStack new.
stack := OOStack newUnlimited .
pushedObject := 'something'.
stack push: pushedObject.

self assert: stack pop = pushedObject! !

!OOStackTest methodsFor: 'general Stack tests' stamp: 'NR 5/13/2020 13:30:48'!
!OOStackTest methodsFor: 'general Stack tests' stamp: 'pa 5/16/2022 15:27:38'!
test05StackBehavesLIFO

| stack firstPushedObject secondPushedObject |

stack := OOStack new.
stack := OOStack newUnlimited.
firstPushedObject := 'first'.
secondPushedObject := 'second'.

Expand All @@ -64,25 +109,25 @@ test05StackBehavesLIFO
self assert: stack isEmpty
! !

!OOStackTest methodsFor: 'general Stack tests' stamp: 'NR 5/13/2020 13:30:20'!
!OOStackTest methodsFor: 'general Stack tests' stamp: 'pa 5/16/2022 15:27:45'!
test06TopReturnsLastPushedObject

| stack pushedObject |

stack := OOStack new.
stack := OOStack newUnlimited .
pushedObject := 'something'.

stack push: pushedObject.

self assert: stack top = pushedObject.
! !

!OOStackTest methodsFor: 'general Stack tests' stamp: 'NR 5/13/2020 13:30:24'!
!OOStackTest methodsFor: 'general Stack tests' stamp: 'pa 5/16/2022 15:27:51'!
test07TopDoesNotRemoveObjectFromStack

| stack pushedObject |

stack := OOStack new.
stack := OOStack newUnlimited.
pushedObject := 'something'.

stack push: pushedObject.
Expand All @@ -92,12 +137,12 @@ test07TopDoesNotRemoveObjectFromStack
self assert: stack size = 1.
! !

!OOStackTest methodsFor: 'general Stack tests' stamp: 'HAW 4/14/2017 22:48:26'!
!OOStackTest methodsFor: 'general Stack tests' stamp: 'pa 5/16/2022 15:27:59'!
test08CanNotPopWhenThereAreNoObjectsInTheStack

| stack |

stack := OOStack new.
stack := OOStack newUnlimited .
self
should: [ stack pop ]
raise: Error - MessageNotUnderstood
Expand All @@ -106,12 +151,12 @@ test08CanNotPopWhenThereAreNoObjectsInTheStack

! !

!OOStackTest methodsFor: 'general Stack tests' stamp: 'NR 5/13/2020 13:30:31'!
!OOStackTest methodsFor: 'general Stack tests' stamp: 'pa 5/16/2022 15:28:09'!
test09CanNotPopWhenThereAreNoObjectsInTheStackAndTheStackHadObjects

| stack |

stack := OOStack new.
stack := OOStack newUnlimited .
stack push: 'something'.
stack pop.

Expand All @@ -123,12 +168,12 @@ test09CanNotPopWhenThereAreNoObjectsInTheStackAndTheStackHadObjects

! !

!OOStackTest methodsFor: 'general Stack tests' stamp: 'HAW 4/14/2017 22:48:44'!
!OOStackTest methodsFor: 'general Stack tests' stamp: 'pa 5/16/2022 15:28:19'!
test10CanNotTopWhenThereAreNoObjectsInTheStack

| stack |

stack := OOStack new.
stack := OOStack newUnlimited.
self
should: [ stack top ]
raise: Error - MessageNotUnderstood
Expand All @@ -137,16 +182,6 @@ test10CanNotTopWhenThereAreNoObjectsInTheStack

! !


!OOStackTest methodsFor: 'UnlimiteStack tests' stamp: 'FRJ 5/16/2022 12:36:30'!
test01StackShouldBeEmptyWhenCreated

| unlimitedStack |

unlimitedStack := OOStack newUnlimited.

self assert: unlimitedStack isEmpty! !


!classDefinition: #SentenceFinderByPrefixTest category: 'Stack-Exercise'!
TestCase subclass: #SentenceFinderByPrefixTest
Expand Down Expand Up @@ -418,6 +453,11 @@ Object subclass: #OOStack
poolDictionaries: ''
category: 'Stack-Exercise'!

!OOStack methodsFor: 'testing' stamp: 'pa 5/16/2022 15:47:09'!
canPush

self subclassResponsibility.! !

!OOStack methodsFor: 'testing' stamp: 'pa 5/13/2022 23:32:37'!
isEmpty

Expand All @@ -442,11 +482,16 @@ pop

^poppedElement .! !

!OOStack methodsFor: 'operations' stamp: 'pa 5/13/2022 23:31:37'!
!OOStack methodsFor: 'operations' stamp: 'pa 5/16/2022 16:04:26'!
push: anElement

self canPush ifFalse: [^self error: LimitedStack stackIsFullErrorDescription ].

lastNode := Node withElement: anElement andPreviouseNode: lastNode.
size := size + 1.



! !

!OOStack methodsFor: 'operations' stamp: 'pa 5/13/2022 23:40:36'!
Expand Down Expand Up @@ -504,15 +549,33 @@ limit

^maximumSize ! !


!LimitedStack methodsFor: 'testing' stamp: 'pa 5/16/2022 15:45:59'!
canPush

^size < maximumSize ! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

!classDefinition: 'LimitedStack class' category: 'Stack-Exercise'!
LimitedStack class
instanceVariableNames: ''!

!LimitedStack class methodsFor: 'instance creation' stamp: 'FRJ 5/16/2022 12:33:39'!
!LimitedStack class methodsFor: 'error descriptions' stamp: 'pa 5/16/2022 16:11:10'!
maximumSizeCanNotBeLessThanZeroErrorDescription

^'Maximum size can not be less than zero'! !

!LimitedStack class methodsFor: 'error descriptions' stamp: 'pa 5/16/2022 16:01:08'!
stackIsFullErrorDescription

^'Stack is full'! !


!LimitedStack class methodsFor: 'instance creation' stamp: 'pa 5/16/2022 16:10:33'!
withLimit: maximumCapacity

maximumCapacity < 0 ifTrue: [self error: self maximumSizeCanNotBeLessThanZeroErrorDescription].
^self new initializeWith: maximumCapacity.! !


Expand All @@ -523,13 +586,18 @@ OOStack subclass: #UnlimitedStack
poolDictionaries: ''
category: 'Stack-Exercise'!

!UnlimitedStack methodsFor: 'testing' stamp: 'pa 5/16/2022 15:45:21'!
canPush

^true! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

!classDefinition: 'UnlimitedStack class' category: 'Stack-Exercise'!
UnlimitedStack class
instanceVariableNames: ''!

!UnlimitedStack class methodsFor: 'as yet unclassified' stamp: 'FRJ 5/16/2022 12:34:03'!
!UnlimitedStack class methodsFor: 'instance creation' stamp: 'FRJ 5/16/2022 12:34:03'!
create

^self new! !
Expand Down
Loading

0 comments on commit 7b7ee82

Please sign in to comment.