Skip to content

Commit

Permalink
Se agrega ejercicio de codigo repetido
Browse files Browse the repository at this point in the history
  • Loading branch information
Jose Camargo authored and Jose Camargo committed May 20, 2021
1 parent 3730cce commit 555f100
Show file tree
Hide file tree
Showing 3 changed files with 539 additions and 0 deletions.
273 changes: 273 additions & 0 deletions 02-Codigo Repetido/CodigoRepetido-Ejercicio.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,273 @@
!classDefinition: #CantSuspend category: 'CodigoRepetido-Ejercicio'!
Error subclass: #CantSuspend
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'CodigoRepetido-Ejercicio'!


!classDefinition: #NotFound category: 'CodigoRepetido-Ejercicio'!
Error subclass: #NotFound
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'CodigoRepetido-Ejercicio'!


!classDefinition: #CustomerBookTest category: 'CodigoRepetido-Ejercicio'!
TestCase subclass: #CustomerBookTest
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'CodigoRepetido-Ejercicio'!

!CustomerBookTest methodsFor: 'tests' stamp: 'NR 4/3/2019 10:50:19'!
test01AddingCustomerShouldNotTakeMoreThan50Milliseconds

| customerBook millisecondsBeforeRunning millisecondsAfterRunning |

customerBook := CustomerBook new.

millisecondsBeforeRunning := Time millisecondClockValue * millisecond.
customerBook addCustomerNamed: 'John Lennon'.
millisecondsAfterRunning := Time millisecondClockValue * millisecond.

self assert: (millisecondsAfterRunning-millisecondsBeforeRunning) < (50 * millisecond)

! !

!CustomerBookTest methodsFor: 'tests' stamp: 'NR 4/3/2019 10:50:13'!
test02RemovingCustomerShouldNotTakeMoreThan100Milliseconds

| customerBook millisecondsBeforeRunning millisecondsAfterRunning paulMcCartney |

customerBook := CustomerBook new.
paulMcCartney := 'Paul McCartney'.

customerBook addCustomerNamed: paulMcCartney.

millisecondsBeforeRunning := Time millisecondClockValue * millisecond.
customerBook removeCustomerNamed: paulMcCartney.
millisecondsAfterRunning := Time millisecondClockValue * millisecond.

self assert: (millisecondsAfterRunning-millisecondsBeforeRunning) < (100 * millisecond)

! !

!CustomerBookTest methodsFor: 'tests' stamp: 'HernanWilkinson 5/9/2012 18:12'!
test03CanNotAddACustomerWithEmptyName

| customerBook |

customerBook := CustomerBook new.

[ customerBook addCustomerNamed: ''.
self fail ]
on: Error
do: [ :anError |
self assert: anError messageText = CustomerBook customerCanNotBeEmptyErrorMessage.
self assert: customerBook isEmpty ]! !

!CustomerBookTest methodsFor: 'tests' stamp: 'HAW 8/28/2017 08:57:25'!
test04CanNotRemoveAnInvalidCustomer

| customerBook johnLennon |

customerBook := CustomerBook new.
johnLennon := 'John Lennon'.
customerBook addCustomerNamed: johnLennon.

[ customerBook removeCustomerNamed: 'Paul McCartney'.
self fail ]
on: NotFound
do: [ :anError |
self assert: customerBook numberOfCustomers = 1.
self assert: (customerBook includesCustomerNamed: johnLennon) ]
! !

!CustomerBookTest methodsFor: 'tests' stamp: 'NR 4/3/2019 10:50:25'!
test05SuspendingACustomerShouldNotRemoveItFromCustomerBook

| customerBook paulMcCartney|

customerBook := CustomerBook new.
paulMcCartney := 'Paul McCartney'.

customerBook addCustomerNamed: paulMcCartney.
customerBook suspendCustomerNamed: paulMcCartney.

self assert: 0 equals: customerBook numberOfActiveCustomers.
self assert: 1 equals: customerBook numberOfSuspendedCustomers.
self assert: 1 equals: customerBook numberOfCustomers.
self assert: (customerBook includesCustomerNamed: paulMcCartney).



! !

!CustomerBookTest methodsFor: 'tests' stamp: 'NR 4/3/2019 10:50:28'!
test06RemovingASuspendedCustomerShouldRemoveItFromCustomerBook

| customerBook paulMcCartney|

customerBook := CustomerBook new.
paulMcCartney := 'Paul McCartney'.

customerBook addCustomerNamed: paulMcCartney.
customerBook suspendCustomerNamed: paulMcCartney.
customerBook removeCustomerNamed: paulMcCartney.

self assert: 0 equals: customerBook numberOfActiveCustomers.
self assert: 0 equals: customerBook numberOfSuspendedCustomers.
self assert: 0 equals: customerBook numberOfCustomers.
self deny: (customerBook includesCustomerNamed: paulMcCartney).



! !

!CustomerBookTest methodsFor: 'tests' stamp: 'NR 4/30/2020 09:08:46'!
test07CanNotSuspendAnInvalidCustomer

| customerBook johnLennon |

customerBook := CustomerBook new.
johnLennon := 'John Lennon'.
customerBook addCustomerNamed: johnLennon.

[ customerBook suspendCustomerNamed: 'Ringo Starr'.
self fail ]
on: CantSuspend
do: [ :anError |
self assert: customerBook numberOfCustomers = 1.
self assert: (customerBook includesCustomerNamed: johnLennon) ]
! !

!CustomerBookTest methodsFor: 'tests' stamp: 'NR 9/19/2018 17:57:11'!
test08CanNotSuspendAnAlreadySuspendedCustomer

| customerBook johnLennon |

customerBook := CustomerBook new.
johnLennon := 'John Lennon'.
customerBook addCustomerNamed: johnLennon.
customerBook suspendCustomerNamed: johnLennon.

[ customerBook suspendCustomerNamed: johnLennon.
self fail ]
on: CantSuspend
do: [ :anError |
self assert: customerBook numberOfCustomers = 1.
self assert: (customerBook includesCustomerNamed: johnLennon) ]
! !


!classDefinition: #CustomerBook category: 'CodigoRepetido-Ejercicio'!
Object subclass: #CustomerBook
instanceVariableNames: 'suspended active'
classVariableNames: ''
poolDictionaries: ''
category: 'CodigoRepetido-Ejercicio'!

!CustomerBook methodsFor: 'initialization' stamp: 'LL 10/30/2020 12:22:04'!
initialize

active := OrderedCollection new.
suspended:= OrderedCollection new.! !


!CustomerBook methodsFor: 'customer management' stamp: 'NR 4/3/2019 10:14:26'!
addCustomerNamed: aName

aName isEmpty ifTrue: [ self signalCustomerNameCannotBeEmpty ].
((active includes: aName) or: [suspended includes: aName]) ifTrue: [ self signalCustomerAlreadyExists ].

active add: aName ! !

!CustomerBook methodsFor: 'customer management' stamp: 'NR 4/3/2019 10:14:26'!
removeCustomerNamed: aName

1 to: active size do:
[ :index |
aName = (active at: index)
ifTrue: [
active removeAt: index.
^ aName
]
].

1 to: suspended size do:
[ :index |
aName = (suspended at: index)
ifTrue: [
suspended removeAt: index.
^ aName
]
].

^ NotFound signal.
! !

!CustomerBook methodsFor: 'customer management' stamp: 'NR 4/3/2019 10:14:26'!
suspendCustomerNamed: aName

(active includes: aName) ifFalse: [^CantSuspend signal].

active remove: aName.

suspended add: aName
! !


!CustomerBook methodsFor: 'accessing' stamp: 'NR 4/3/2019 10:14:26'!
numberOfActiveCustomers

^active size! !

!CustomerBook methodsFor: 'accessing' stamp: 'NR 4/3/2019 10:14:26'!
numberOfCustomers

^active size + suspended size! !

!CustomerBook methodsFor: 'accessing' stamp: 'NR 9/19/2018 17:36:09'!
numberOfSuspendedCustomers

^suspended size! !


!CustomerBook methodsFor: 'testing' stamp: 'NR 4/3/2019 10:14:26'!
includesCustomerNamed: aName

^(active includes: aName) or: [ suspended includes: aName ]! !

!CustomerBook methodsFor: 'testing' stamp: 'NR 4/3/2019 10:14:26'!
isEmpty

^active isEmpty and: [ suspended isEmpty ]! !


!CustomerBook methodsFor: 'signal errors' stamp: 'HernanWilkinson 7/6/2011 17:52'!
signalCustomerAlreadyExists

self error: self class customerAlreadyExistsErrorMessage! !

!CustomerBook methodsFor: 'signal errors' stamp: 'HernanWilkinson 7/6/2011 17:51'!
signalCustomerNameCannotBeEmpty

self error: self class customerCanNotBeEmptyErrorMessage ! !

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

!classDefinition: 'CustomerBook class' category: 'CodigoRepetido-Ejercicio'!
CustomerBook class
instanceVariableNames: ''!

!CustomerBook class methodsFor: 'error messages' stamp: 'NR 4/30/2020 09:05:18'!
customerAlreadyExistsErrorMessage

^'Customer Already Exists'! !

!CustomerBook class methodsFor: 'error messages' stamp: 'NR 4/30/2020 09:05:25'!
customerCanNotBeEmptyErrorMessage

^'Customer Name Cannot Be Empty'! !
Loading

0 comments on commit 555f100

Please sign in to comment.