Commit 3619776a authored by ivan guralnik's avatar ivan guralnik
Browse files

portfolio tree cambiando a abstracción correcta

parent 534f316d
......@@ -367,7 +367,7 @@ test23ShouldBeAbleToBeQueryTransferNet
self assert: 150 = (self accountTransferNetOf: fromAccount).
self assert: -150 = (self accountTransferNetOf: toAccount).! !
!PortfolioTest methodsFor: 'tests' stamp: 'HernanWilkinson 7/14/2011 06:58'!
!PortfolioTest methodsFor: 'tests' stamp: 'ig 5/14/2018 17:10:53'!
test24CertificateOfDepositShouldWithdrawInvestmentValue
| account toAccount |
......@@ -379,7 +379,7 @@ test24CertificateOfDepositShouldWithdrawInvestmentValue
Transfer register: 100 from: account to: toAccount.
CertificateOfDeposit register: 100 during: 30 at: 1/10 on: account.
self assert: 100 =(self investmentNetOf:account).
self assert: 100 =(self investmentNetOf: account).
self assert: 750 = account balance.! !
!PortfolioTest methodsFor: 'tests' stamp: 'HernanWilkinson 7/14/2011 06:58'!
......@@ -493,20 +493,20 @@ accountSummaryLinesOf: aReceptiveAccount
^aReceptiveAccount accountSummary! !
!PortfolioTest methodsFor: 'test support' stamp: 'HernanWilkinson 9/6/2016 19:43'!
!PortfolioTest methodsFor: 'test support' stamp: 'ig 5/14/2018 17:30:07'!
accountTransferNetOf: aReceptiveAccount
self shouldBeImplemented ! !
^aReceptiveAccount netTransfer! !
!PortfolioTest methodsFor: 'test support' stamp: 'HernanWilkinson 9/6/2016 19:43'!
investmentEarningsOf: aReceptiveAccount
self shouldBeImplemented ! !
!PortfolioTest methodsFor: 'test support' stamp: 'HernanWilkinson 9/6/2016 19:43'!
!PortfolioTest methodsFor: 'test support' stamp: 'ig 5/14/2018 17:30:59'!
investmentNetOf: aReceptiveAccount
self shouldBeImplemented ! !
^aReceptiveAccount netInvestment ! !
!PortfolioTest methodsFor: 'test support' stamp: 'HernanWilkinson 9/6/2016 19:43'!
portofolioTreeOf: aPortfolio namingAccountWith: aDictionary
......@@ -555,6 +555,40 @@ AccountTransaction subclass: #CertificateOfDeposit
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!CertificateOfDeposit methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 17:22:09'!
intiliazeWith: aValue during: aNumberOfDays at: aTna on: anAccount
value := aValue.
numberOfDays := aNumberOfDays.
tna := aTna.
account := anAccount.! !
!CertificateOfDeposit methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 17:35:34'!
value
^value! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'CertificateOfDeposit class' category: #'PortfolioTreePrinter-Ejercicio'!
CertificateOfDeposit class
instanceVariableNames: ''!
!CertificateOfDeposit class methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 18:02:44'!
register: aValue during: aNumberOfDays at: aTna on: anAccount
| certificate |
certificate := self with: aValue during: aNumberOfDays at: aTna on: anAccount.
anAccount register: certificate.
^ certificate! !
!CertificateOfDeposit class methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 17:22:28'!
with: aValue during: aNumberOfDays at: aTna on: anAccount
^self new intiliazeWith: aValue during: aNumberOfDays at: aTna on: anAccount! !
!classDefinition: #Deposit category: #'PortfolioTreePrinter-Ejercicio'!
AccountTransaction subclass: #Deposit
......@@ -585,6 +619,16 @@ transactionDescription
^'Deposito por ', self value asString! !
!Deposit methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 16:53:56'!
valueOfTransfer
^0! !
!Deposit methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 18:51:31'!
x: methodAccount
^methodAccount fromDeposit: self! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'Deposit class' category: #'PortfolioTreePrinter-Ejercicio'!
......@@ -596,15 +640,15 @@ for: aValue
^ self new initializeFor: aValue ! !
!Deposit class methodsFor: 'instance creation' stamp: 'HernanWilkinson 7/13/2011 19:41'!
!Deposit class methodsFor: 'instance creation' stamp: 'ig 5/14/2018 17:15:09'!
register: aValue on: account
| withdraw |
| deposit |
withdraw := self for: aValue.
account register: withdraw.
deposit := self for: aValue.
account register: deposit.
^ withdraw! !
^ deposit! !
!classDefinition: #TransferDeposit category: #'PortfolioTreePrinter-Ejercicio'!
......@@ -646,6 +690,11 @@ value
^value! !
!TransferDeposit methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 16:53:20'!
valueOfTransfer
^self value! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'TransferDeposit class' category: #'PortfolioTreePrinter-Ejercicio'!
......@@ -707,6 +756,11 @@ value
^value! !
!TransferWithdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 16:53:34'!
valueOfTransfer
^self value * -1! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'TransferWithdraw class' category: #'PortfolioTreePrinter-Ejercicio'!
......@@ -753,10 +807,20 @@ moneyForBalance
^self value * (-1)! !
!Withdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 21:55:34'!
!Withdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 16:35:02'!
transactionDescription
^'Extraccion por ', (self value * -1) asString! !
^'Extraccion por ', self value asString! !
!Withdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 16:53:47'!
valueOfTransfer
^0! !
!Withdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:12:29'!
x: methodAccount
^methodAccount fromWithdraw: self! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
......@@ -779,10 +843,66 @@ register: aValue on: account
^ withdraw! !
!classDefinition: #BalanceAccount category: #'PortfolioTreePrinter-Ejercicio'!
Object subclass: #BalanceAccount
instanceVariableNames: 'transactions'
classVariableNames: ''
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!BalanceAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:14:37'!
balance
^ transactions inject: 0 into: [ :balance :transaction | balance + (transaction x: self) ].
! !
!BalanceAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:15:08'!
fromDeposit: aDeposit
^aDeposit value! !
!BalanceAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:26:58'!
fromTransferDeposit: aTransferDeposit
^aTransferDeposit value! !
!BalanceAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:26:38'!
fromTransferWithdraw: aTransferWithdraw
^aTransferWithdraw value * -1! !
!BalanceAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:26:25'!
fromWithdraw: aWithdraw
^aWithdraw value * -1! !
!BalanceAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:13:34'!
initializeWith: someTransactions
transactions := someTransactions! !
!BalanceAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:26:03'!
value
^ transactions inject: 0 into: [ :balance :transaction | balance + (transaction x: self) ].
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'BalanceAccount class' category: #'PortfolioTreePrinter-Ejercicio'!
BalanceAccount class
instanceVariableNames: ''!
!BalanceAccount class methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:15:38'!
of: transactions
^self new initializeWith: transactions ! !
!classDefinition: #SummarizingAccount category: #'PortfolioTreePrinter-Ejercicio'!
Object subclass: #SummarizingAccount
instanceVariableNames: ''
instanceVariableNames: 'account'
classVariableNames: ''
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
......@@ -808,6 +928,7 @@ transactions
self subclassResponsibility ! !
!classDefinition: #Portfolio category: #'PortfolioTreePrinter-Ejercicio'!
SummarizingAccount subclass: #Portfolio
......@@ -922,17 +1043,20 @@ SummarizingAccount subclass: #ReceptiveAccount
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!ReceptiveAccount methodsFor: 'initialization' stamp: 'HernanWilkinson 7/13/2011 18:35'!
!ReceptiveAccount methodsFor: 'initialization' stamp: 'ig 5/14/2018 18:02:58'!
initialize
super initialize.
transactions := OrderedCollection new.! !
!ReceptiveAccount methodsFor: 'transactions' stamp: 'ig 5/10/2018 19:57:08'!
!ReceptiveAccount methodsFor: 'transactions' stamp: 'ig 5/14/2018 19:27:45'!
balance
^ transactions inject: 0 into: [ :balance :transaction | balance + (transaction moneyForBalance) ]! !
" ^ transactions inject: 0 into: [ :balance :transaction | balance + (transaction moneyForBalance) ]."
^(BalanceAccount of: self transactions) value
! !
!ReceptiveAccount methodsFor: 'transactions' stamp: 'HernanWilkinson 7/13/2011 18:37'!
register: aTransaction
......@@ -959,12 +1083,79 @@ registers: aTtransaction
! !
!ReceptiveAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 21:53:31'!
!ReceptiveAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:24:57'!
accountSummary
^ transactions
"^ transactions
inject: OrderedCollection new
into: [ :summary :transaction | summary , transaction transactionDescription. summary ]! !
into: [ :summary :transaction | summary add: transaction transactionDescription. summary ]"
^ (SummaryAccount of: self transactions) value.! !
!ReceptiveAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 18:03:32'!
netInvestment
| sum |
sum := 0.
transactions do: [:investment | sum := sum + ((investment value))].
^sum.! !
!ReceptiveAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 17:29:54'!
netTransfer
| sum |
sum := 0.
self transactions do: [:transaction | sum := sum + ((transaction valueOfTransfer))].
^sum.! !
!classDefinition: #SummaryAccount category: #'PortfolioTreePrinter-Ejercicio'!
Object subclass: #SummaryAccount
instanceVariableNames: 'transactions'
classVariableNames: ''
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!SummaryAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:09:13'!
fromDeposit: aDeposit
^'Deposito por ', aDeposit value asString.! !
!SummaryAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:11:55'!
fromWithdraw: aWithdraw
^'Extraccion por ', aWithdraw value asString.! !
!SummaryAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:07:34'!
initilalizeWith: someTransactions
transactions := someTransactions.! !
!SummaryAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:08:43'!
summary
^transactions inject: OrderedCollection new
into: [ :summary :transaction | summary add: (transaction x: self). summary ]! !
!SummaryAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:24:47'!
value
^transactions inject: OrderedCollection new
into: [ :summary :transaction | summary add: (transaction x: self). summary ]! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'SummaryAccount class' category: #'PortfolioTreePrinter-Ejercicio'!
SummaryAccount class
instanceVariableNames: ''!
!SummaryAccount class methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:09:36'!
of: transactions
^self new initializeWith: transactions.! !
!classDefinition: #Transfer category: #'PortfolioTreePrinter-Ejercicio'!
......
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