Commit f1f2835e authored by julian ariel zylber's avatar julian ariel zylber
Browse files

portfolio

parent b424ad3c
!classDefinition: #PortfolioTest category: #'Portfolio-Ejercicio'!
TestCase subclass: #PortfolioTest
instanceVariableNames: 'portfolio account'
classVariableNames: ''
poolDictionaries: ''
category: 'Portfolio-Ejercicio'!
!PortfolioTest methodsFor: 'as yet unclassified' stamp: 'JZ 6/21/2020 18:04:57'!
setUp
portfolio := Portfolio new.
account := ReceptiveAccount new. ! !
!PortfolioTest methodsFor: 'as yet unclassified' stamp: 'JZ 6/21/2020 18:07:12'!
test01EmptyPortfolioHasBalanceZero
self assert: 0 equals: portfolio balance. ! !
!PortfolioTest methodsFor: 'as yet unclassified' stamp: 'JZ 6/21/2020 18:08:52'!
test02PortfoliosBalanceIsSumOfBalancesOfComponents
Deposit register: 100 on: account.
portfolio add: account.
self assert: 100 equals: portfolio balance. ! !
!PortfolioTest methodsFor: 'as yet unclassified' stamp: 'JZ 6/21/2020 18:10:24'!
test03PortfolioKnowsRegisteredTransactionsInComponents
|deposit|
deposit := Deposit register: 100 on: account.
portfolio add: account.
self assert: (portfolio hasRegistered: deposit).! !
!PortfolioTest methodsFor: 'as yet unclassified' stamp: 'JZ 6/21/2020 18:13:37'!
test04PortfolioDoesNotHaveTransactionsRegisteredThatDoNotBelongToPortfolio
| deposit |
deposit := Deposit register: 100 on: account.
self assert: (portfolio hasRegistered: deposit)not.! !
!PortfolioTest methodsFor: 'as yet unclassified' stamp: 'JZ 6/21/2020 18:18:04'!
test05PortfoliosTransactionsIncludeTransactionsOfComponents
|deposit |
deposit := Deposit register: 100 on: account.
portfolio add: account.
self assert: (portfolio transactions includes: deposit).! !
!PortfolioTest methodsFor: 'as yet unclassified' stamp: 'JZ 6/21/2020 18:17:09'!
test06CannotAddPortfolioThatContainsAccountsPresentInSelf
|anotherPorfolio|
anotherPorfolio := Portfolio new.
anotherPorfolio add: account.
portfolio add: account.
self should: [portfolio add: anotherPorfolio]
raise: Error
withMessageText: Portfolio redundantAccountMessageError.
self assert: 1 equals: portfolio uniqueAccounts size
! !
!PortfolioTest methodsFor: 'as yet unclassified' stamp: 'JZ 6/21/2020 18:27:12'!
test07CannotAddPortfolioThatContainsAccountsPresentInParent
|parentPortfolio childPortfolio|
parentPortfolio := Portfolio new.
childPortfolio := Portfolio new.
parentPortfolio add: childPortfolio.
parentPortfolio add: account.
portfolio add: account.
self should: [childPortfolio add: portfolio]
raise: Error
withMessageText: Portfolio redundantAccountMessageError.
self assert: 1 equals: parentPortfolio uniqueAccounts size.
self assert: 0 equals: childPortfolio uniqueAccounts size.
! !
!PortfolioTest methodsFor: 'as yet unclassified' stamp: 'JZ 6/21/2020 18:29:41'!
test08CannotAddAccountThatContainsAccountsPresentInChildren
|parentPortfolio childPortfolio anotherAccount|
parentPortfolio:= Portfolio new.
childPortfolio:= Portfolio new.
anotherAccount := ReceptiveAccount new.
parentPortfolio add: childPortfolio.
parentPortfolio add: account.
childPortfolio add: anotherAccount .
self should: [parentPortfolio add: anotherAccount ]
raise: Error
withMessageText: Portfolio redundantAccountMessageError.
! !
!PortfolioTest methodsFor: 'as yet unclassified' stamp: 'JZ 6/21/2020 18:35:04'!
test09CannotAddPortfolioThatContainsAccountsPresentInTheTree
|grandfatherPortfolio parentPortfolio childPortfolio |
grandfatherPortfolio := Portfolio new.
parentPortfolio:= Portfolio new.
childPortfolio:= Portfolio new.
grandfatherPortfolio add: account.
grandfatherPortfolio add: parentPortfolio.
parentPortfolio add: childPortfolio.
portfolio add: account.
self should: [childPortfolio add: portfolio]
raise: Error
withMessageText: Portfolio redundantAccountMessageError.
! !
!classDefinition: #ReceptiveAccountTest category: #'Portfolio-Ejercicio'!
TestCase subclass: #ReceptiveAccountTest
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Portfolio-Ejercicio'!
!ReceptiveAccountTest methodsFor: 'tests' stamp: 'HAW 5/23/2019 15:19:48'!
test01ReceptiveAccountHaveZeroAsBalanceWhenCreated
| account |
account := ReceptiveAccount new.
self assert: 0 equals: account balance .
! !
!ReceptiveAccountTest methodsFor: 'tests' stamp: 'HAW 5/23/2019 15:19:54'!
test02DepositIncreasesBalanceOnTransactionValue
| account |
account := ReceptiveAccount new.
Deposit register: 100 on: account.
self assert: 100 equals: account balance .
! !
!ReceptiveAccountTest methodsFor: 'tests' stamp: 'HAW 5/23/2019 15:20:02'!
test03WithdrawDecreasesBalanceOnTransactionValue
| account |
account := ReceptiveAccount new.
Deposit register: 100 on: account.
Withdraw register: 50 on: account.
self assert: 50 equals: account balance .
! !
!ReceptiveAccountTest methodsFor: 'tests' stamp: 'HAW 5/23/2019 15:20:32'!
test04WithdrawValueMustBePositive
| account withdrawValue |
account := ReceptiveAccount new.
withdrawValue := 50.
self assert: withdrawValue equals: (Withdraw register: withdrawValue on: account) value
! !
!ReceptiveAccountTest methodsFor: 'tests' stamp: 'HAW 5/23/2019 15:20:46'!
test05ReceptiveAccountKnowsRegisteredTransactions
| account deposit withdraw |
account := ReceptiveAccount new.
deposit := Deposit register: 100 on: account.
withdraw := Withdraw register: 50 on: account.
self assert: (account hasRegistered: deposit).
self assert: (account hasRegistered: withdraw).
! !
!ReceptiveAccountTest methodsFor: 'tests' stamp: 'HAW 5/23/2019 15:20:54'!
test06ReceptiveAccountDoNotKnowNotRegisteredTransactions
| account deposit withdraw |
account := ReceptiveAccount new.
deposit := Deposit for: 100.
withdraw := Withdraw for: 50.
self deny: (account hasRegistered: deposit).
self deny: (account hasRegistered:withdraw).
! !
!ReceptiveAccountTest methodsFor: 'tests' stamp: 'NR 6/18/2020 17:33:13'!
test07AccountKnowsItsTransactions
| account1 deposit1 |
account1 := ReceptiveAccount new.
deposit1 := Deposit register: 50 on: account1.
self assert: 1 equals: account1 transactions size .
self assert: (account1 transactions includes: deposit1).
! !
!classDefinition: #AccountTransaction category: #'Portfolio-Ejercicio'!
Object subclass: #AccountTransaction
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Portfolio-Ejercicio'!
!AccountTransaction methodsFor: 'value' stamp: 'JZ 6/18/2020 19:27:31'!
contributionToBalance
self subclassResponsibility ! !
!AccountTransaction methodsFor: 'value' stamp: 'HernanWilkinson 9/12/2011 12:25'!
value
self subclassResponsibility ! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'AccountTransaction class' category: #'Portfolio-Ejercicio'!
AccountTransaction class
instanceVariableNames: ''!
!AccountTransaction class methodsFor: 'instance creation' stamp: 'NR 10/17/2019 03:22:00'!
register: aValue on: account
| transaction |
transaction := self for: aValue.
account register: transaction.
^ transaction! !
!classDefinition: #Deposit category: #'Portfolio-Ejercicio'!
AccountTransaction subclass: #Deposit
instanceVariableNames: 'value'
classVariableNames: ''
poolDictionaries: ''
category: 'Portfolio-Ejercicio'!
!Deposit methodsFor: 'initialization' stamp: 'HernanWilkinson 7/13/2011 18:45'!
initializeFor: aValue
value := aValue ! !
!Deposit methodsFor: 'value' stamp: 'JZ 6/18/2020 19:29:27'!
contributionToBalance
^ value! !
!Deposit methodsFor: 'value' stamp: 'HernanWilkinson 7/13/2011 18:38'!
value
^ value! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'Deposit class' category: #'Portfolio-Ejercicio'!
Deposit class
instanceVariableNames: ''!
!Deposit class methodsFor: 'instance creation' stamp: 'HernanWilkinson 7/13/2011 18:38'!
for: aValue
^ self new initializeFor: aValue ! !
!classDefinition: #Withdraw category: #'Portfolio-Ejercicio'!
AccountTransaction subclass: #Withdraw
instanceVariableNames: 'value'
classVariableNames: ''
poolDictionaries: ''
category: 'Portfolio-Ejercicio'!
!Withdraw methodsFor: 'initialization' stamp: 'HernanWilkinson 7/13/2011 18:46'!
initializeFor: aValue
value := aValue ! !
!Withdraw methodsFor: 'value' stamp: 'JZ 6/18/2020 19:29:34'!
contributionToBalance
^ (-1 * value).! !
!Withdraw methodsFor: 'value' stamp: 'HernanWilkinson 7/13/2011 18:33'!
value
^ value! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'Withdraw class' category: #'Portfolio-Ejercicio'!
Withdraw class
instanceVariableNames: ''!
!Withdraw class methodsFor: 'instance creation' stamp: 'HernanWilkinson 7/13/2011 18:33'!
for: aValue
^ self new initializeFor: aValue ! !
!classDefinition: #Portfolio category: #'Portfolio-Ejercicio'!
Object subclass: #Portfolio
instanceVariableNames: 'components uniqueAccounts parentPortfolios'
classVariableNames: ''
poolDictionaries: ''
category: 'Portfolio-Ejercicio'!
!Portfolio methodsFor: 'adding' stamp: 'JZ 6/21/2020 17:50:50'!
add: anAccountOrPortfolio
(self hasUniqueAccountsInSelfOrParents: anAccountOrPortfolio uniqueAccounts) ifTrue: [self raiseRedundantAccountError].
components add: anAccountOrPortfolio.
anAccountOrPortfolio isBeingAddedTo: self.
self updateUniqueAccountsWith: anAccountOrPortfolio uniqueAccounts. ! !
!Portfolio methodsFor: 'adding' stamp: 'JZ 6/21/2020 17:24:03'!
isBeingAddedTo: aPortfolio
parentPortfolios add: aPortfolio.
! !
!Portfolio methodsFor: 'testing -- parents' stamp: 'JZ 6/21/2020 17:49:12'!
hasUniqueAccountsInSelfOrParents: aSetOfAccounts
| isInParents isInSelf |
isInSelf := self uniqueAccountsPresentInSelf: aSetOfAccounts.
isInParents := self uniqueAccountsPresentInParents: aSetOfAccounts.
^isInSelf or: [isInParents].
! !
!Portfolio methodsFor: 'testing -- parents' stamp: 'JZ 6/21/2020 17:48:29'!
uniqueAccountsPresentInParents: aSetOfAccounts
^parentPortfolios inject: false into: [:hasAccount :parentPortfolio | hasAccount or: [parentPortfolio hasUniqueAccountsInSelfOrParents: aSetOfAccounts ]].
! !
!Portfolio methodsFor: 'testing -- self' stamp: 'JZ 6/18/2020 20:08:18'!
hasRegistered: aTransaction
^components inject: false into: [:hasBeenFound :aComponent | hasBeenFound or: [aComponent hasRegistered: aTransaction]]. ! !
!Portfolio methodsFor: 'testing -- self' stamp: 'JZ 6/21/2020 17:47:50'!
uniqueAccountsPresentInSelf: aSetOfAccounts
^ (uniqueAccounts intersection: aSetOfAccounts) size > 0.
! !
!Portfolio methodsFor: 'initialization' stamp: 'JZ 6/21/2020 17:18:55'!
initialize
components := OrderedCollection new.
uniqueAccounts := Set new.
parentPortfolios := OrderedCollection new. ! !
!Portfolio methodsFor: 'errors' stamp: 'JZ 6/21/2020 17:11:31'!
raiseRedundantAccountError
^self error: self class redundantAccountMessageError. ! !
!Portfolio methodsFor: 'unique accounts' stamp: 'JZ 6/18/2020 21:03:09'!
uniqueAccounts
^uniqueAccounts.! !
!Portfolio methodsFor: 'unique accounts' stamp: 'JZ 6/21/2020 17:50:50'!
updateUniqueAccountsWith: anAccountOrPortfolioUniqueAccounts
uniqueAccounts addAll: anAccountOrPortfolioUniqueAccounts .
parentPortfolios do: [:aParentPortfolio | aParentPortfolio updateUniqueAccountsWith: anAccountOrPortfolioUniqueAccounts]
! !
!Portfolio methodsFor: 'transactions' stamp: 'JZ 6/21/2020 18:36:16'!
transactions
|transactions|
transactions := OrderedCollection new.
components do: [ :anAccount | transactions addAll: anAccount transactions ].
^ transactions.! !
!Portfolio methodsFor: 'balance' stamp: 'JZ 6/21/2020 18:35:53'!
balance
^components sum: [ :aComponent | aComponent balance ] ifEmpty: [ 0 ].! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'Portfolio class' category: #'Portfolio-Ejercicio'!
Portfolio class
instanceVariableNames: ''!
!Portfolio class methodsFor: 'error messages' stamp: 'JZ 6/21/2020 17:08:23'!
redundantAccountMessageError
^'Cannot add an account/portfolio that includes accounts that belong to this portfolio or portfolios that contain this portfolio'! !
!classDefinition: #ReceptiveAccount category: #'Portfolio-Ejercicio'!
Object subclass: #ReceptiveAccount
instanceVariableNames: 'transactions'
classVariableNames: ''
poolDictionaries: ''
category: 'Portfolio-Ejercicio'!
!ReceptiveAccount methodsFor: 'initialization' stamp: 'NR 10/17/2019 15:06:56'!
initialize
transactions := OrderedCollection new.! !
!ReceptiveAccount methodsFor: 'transactions' stamp: 'HernanWilkinson 7/13/2011 18:37'!
register: aTransaction
transactions add: aTransaction
! !
!ReceptiveAccount methodsFor: 'transactions' stamp: 'HernanWilkinson 7/13/2011 18:37'!
transactions
^ transactions copy! !
!ReceptiveAccount methodsFor: 'balance' stamp: 'JZ 6/18/2020 19:28:19'!
balance
^transactions sum: [ :aTransaction | aTransaction contributionToBalance ] ifEmpty: [ 0 ]! !
!ReceptiveAccount methodsFor: 'role in portfolio' stamp: 'JZ 6/21/2020 17:24:18'!
isBeingAddedTo: aPortfolio
^self.! !
!ReceptiveAccount methodsFor: 'role in portfolio' stamp: 'JZ 6/18/2020 21:09:49'!
uniqueAccounts
^ Set with: self.! !
!ReceptiveAccount methodsFor: 'testing' stamp: 'NR 10/17/2019 03:28:43'!
hasRegistered: aTransaction
^ transactions includes: aTransaction
! !
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