Commit 2e0efe8e authored by istng's avatar istng
Browse files

pasando casi todos los tests, bien ordenado

parent 3619776a
......@@ -488,25 +488,25 @@ test29ReversePortfolioTreePrinterPrintsTheCompositeStartingFromTheLeaves
! !
!PortfolioTest methodsFor: 'test support' stamp: 'HAW 9/25/2017 21:44:47'!
!PortfolioTest methodsFor: 'test support' stamp: 'ig 5/15/2018 14:05:40'!
accountSummaryLinesOf: aReceptiveAccount
^aReceptiveAccount accountSummary! !
^(SummaryAccount of: aReceptiveAccount transactions) value! !
!PortfolioTest methodsFor: 'test support' stamp: 'ig 5/14/2018 17:30:07'!
!PortfolioTest methodsFor: 'test support' stamp: 'ig 5/15/2018 14:32:48'!
accountTransferNetOf: aReceptiveAccount
^aReceptiveAccount netTransfer! !
^(NetTransferAccount of: aReceptiveAccount transactions) value! !
!PortfolioTest methodsFor: 'test support' stamp: 'HernanWilkinson 9/6/2016 19:43'!
investmentEarningsOf: aReceptiveAccount
self shouldBeImplemented ! !
!PortfolioTest methodsFor: 'test support' stamp: 'ig 5/14/2018 17:30:59'!
!PortfolioTest methodsFor: 'test support' stamp: 'ig 5/15/2018 14:32:58'!
investmentNetOf: aReceptiveAccount
^aReceptiveAccount netInvestment ! !
^(NetInvestmentAccount of: aReceptiveAccount transactions) value! !
!PortfolioTest methodsFor: 'test support' stamp: 'HernanWilkinson 9/6/2016 19:43'!
portofolioTreeOf: aPortfolio namingAccountWith: aDictionary
......@@ -526,6 +526,7 @@ Object subclass: #AccountTransaction
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!AccountTransaction methodsFor: 'evaluating' stamp: 'HernanWilkinson 7/14/2011 06:48'!
value
......@@ -568,6 +569,11 @@ value
^value! !
!CertificateOfDeposit methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:25:54'!
x: methodAccount
^methodAccount fromCertificateOfDeposit: self! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'CertificateOfDeposit class' category: #'PortfolioTreePrinter-Ejercicio'!
......@@ -609,21 +615,6 @@ value
^ value! !
!Deposit methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 19:56:56'!
moneyForBalance
^self value! !
!Deposit methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 20:13:28'!
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
......@@ -670,16 +661,6 @@ initializeFor: aValue on: anAccount with: aTransfer
account := anAccount.
transfer := aTransfer.! !
!TransferDeposit methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 21:15:01'!
moneyForBalance
^self value! !
!TransferDeposit methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 21:56:25'!
transactionDescription
^'Transferencia por ', self value asString! !
!TransferDeposit methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 21:22:31'!
transfer
......@@ -690,10 +671,10 @@ value
^value! !
!TransferDeposit methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 16:53:20'!
valueOfTransfer
!TransferDeposit methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:13:29'!
x: methodAccount
^self value! !
^methodAccount fromTransferDeposit: self! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
......@@ -736,16 +717,6 @@ initializeFor: aValue on: anAccount with: aTransfer
account := anAccount.
transfer := aTransfer.! !
!TransferWithdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 21:15:06'!
moneyForBalance
^self value * (-1)! !
!TransferWithdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 21:56:17'!
transactionDescription
^'Transferencia por ', (self value * -1) asString! !
!TransferWithdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 21:22:35'!
transfer
......@@ -756,10 +727,10 @@ value
^value! !
!TransferWithdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 16:53:34'!
valueOfTransfer
!TransferWithdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:13:41'!
x: methodAccount
^self value * -1! !
^methodAccount fromTransferWithdraw: self! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
......@@ -802,21 +773,6 @@ value
^ value ! !
!Withdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 19:56:43'!
moneyForBalance
^self value * (-1)! !
!Withdraw methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 16:35:02'!
transactionDescription
^'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
......@@ -851,11 +807,10 @@ Object subclass: #BalanceAccount
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!BalanceAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:14:37'!
balance
!BalanceAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:26:24'!
fromCertificateOfDeposit: aCertificate
^ transactions inject: 0 into: [ :balance :transaction | balance + (transaction x: self) ].
! !
^aCertificate value * -1! !
!BalanceAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:15:08'!
fromDeposit: aDeposit
......@@ -899,6 +854,116 @@ of: transactions
^self new initializeWith: transactions ! !
!classDefinition: #NetInvestmentAccount category: #'PortfolioTreePrinter-Ejercicio'!
Object subclass: #NetInvestmentAccount
instanceVariableNames: 'transactions'
classVariableNames: ''
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!NetInvestmentAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:25:41'!
fromCertificateOfDeposit: aCertificate
^aCertificate value! !
!NetInvestmentAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:24:30'!
fromDeposit: aDeposit
^0! !
!NetInvestmentAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:24:34'!
fromTransferDeposit: aTransferDeposit
^0! !
!NetInvestmentAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:24:39'!
fromTransferWithdraw: aTransferWithdraw
^0! !
!NetInvestmentAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:24:43'!
fromWithdraw: aWithdraw
^0! !
!NetInvestmentAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:23:44'!
initializeWith: someTransactions
transactions := someTransactions! !
!NetInvestmentAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:25:02'!
value
^ transactions inject: 0 into: [ :netInvestment :transaction | netInvestment + (transaction x: self) ].
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'NetInvestmentAccount class' category: #'PortfolioTreePrinter-Ejercicio'!
NetInvestmentAccount class
instanceVariableNames: ''!
!NetInvestmentAccount class methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:23:44'!
of: transactions
^self new initializeWith: transactions ! !
!classDefinition: #NetTransferAccount category: #'PortfolioTreePrinter-Ejercicio'!
Object subclass: #NetTransferAccount
instanceVariableNames: 'transactions'
classVariableNames: ''
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!NetTransferAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:30:38'!
fromCertificateOfDeposit: aCertificate
^0! !
!NetTransferAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:29:43'!
fromDeposit: aDeposit
^0! !
!NetTransferAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:30:46'!
fromTransferDeposit: aTransferDeposit
^aTransferDeposit value! !
!NetTransferAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:30:54'!
fromTransferWithdraw: aTransferWithdraw
^aTransferWithdraw value * -1! !
!NetTransferAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:29:43'!
fromWithdraw: aWithdraw
^0! !
!NetTransferAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:29:43'!
initializeWith: someTransactions
transactions := someTransactions! !
!NetTransferAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:30:27'!
value
^ transactions inject: 0 into: [ :netTransfer :transaction | netTransfer + (transaction x: self) ].
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'NetTransferAccount class' category: #'PortfolioTreePrinter-Ejercicio'!
NetTransferAccount class
instanceVariableNames: ''!
!NetTransferAccount class methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:29:43'!
of: transactions
^self new initializeWith: transactions ! !
!classDefinition: #SummarizingAccount category: #'PortfolioTreePrinter-Ejercicio'!
Object subclass: #SummarizingAccount
......@@ -937,6 +1002,7 @@ SummarizingAccount subclass: #Portfolio
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!Portfolio methodsFor: 'testing' stamp: 'HernanWilkinson 7/13/2011 19:22'!
manages: anAccount
......@@ -971,6 +1037,12 @@ transactionsOf: anAccount
! !
!Portfolio methodsFor: 'initialize' stamp: 'ig 5/8/2018 16:09:27'!
initialize: accountsList
accounts := accountsList! !
!Portfolio methodsFor: 'initialization' stamp: 'HernanWilkinson 7/13/2011 19:19'!
initializeWithAll: aCollectionOfAccounts
......@@ -1000,6 +1072,17 @@ withAll: aCollectionOfAccounts
^self new initializeWithAll: aCollectionOfAccounts ! !
!Portfolio class methodsFor: 'error messages' stamp: 'HernanWilkinson 7/13/2011 19:28'!
accountAlreadyManagedErrorMessage
^ 'Account already managed'! !
!Portfolio class methodsFor: 'error messages' stamp: 'HernanWilkinson 7/13/2011 19:27'!
accountNotManagedMessageDescription
^ 'Account not managed'! !
!Portfolio class methodsFor: 'assertions' stamp: 'HernanWilkinson 9/18/2011 17:22'!
check: sourceAccount doesNotManagaAnyOf: aCollectionOfAccounts
......@@ -1024,17 +1107,6 @@ checkNoCircularReferencesIn: aCollectionOfAccounts
aCollectionOfAccounts do: [ :sourceAccount | self check: sourceAccount doesNotManagaAnyOf: aCollectionOfAccounts ]! !
!Portfolio class methodsFor: 'error messages' stamp: 'HernanWilkinson 7/13/2011 19:28'!
accountAlreadyManagedErrorMessage
^ 'Account already managed'! !
!Portfolio class methodsFor: 'error messages' stamp: 'HernanWilkinson 7/13/2011 19:27'!
accountNotManagedMessageDescription
^ 'Account not managed'! !
!classDefinition: #ReceptiveAccount category: #'PortfolioTreePrinter-Ejercicio'!
SummarizingAccount subclass: #ReceptiveAccount
......@@ -1050,13 +1122,11 @@ initialize
transactions := OrderedCollection new.! !
!ReceptiveAccount methodsFor: 'transactions' stamp: 'ig 5/14/2018 19:27:45'!
!ReceptiveAccount methodsFor: 'transactions' stamp: 'ig 5/15/2018 14:09:59'!
balance
" ^ transactions inject: 0 into: [ :balance :transaction | balance + (transaction moneyForBalance) ]."
^(BalanceAccount of: self transactions) value
! !
"^ transactions inject: 0 into: [ :balance :transaction | balance + transaction value ]"
^(BalanceAccount of: self transactions) value! !
!ReceptiveAccount methodsFor: 'transactions' stamp: 'HernanWilkinson 7/13/2011 18:37'!
register: aTransaction
......@@ -1070,6 +1140,7 @@ transactions
^ transactions copy! !
!ReceptiveAccount methodsFor: 'testing' stamp: 'HernanWilkinson 7/13/2011 18:37'!
manages: anAccount
......@@ -1083,34 +1154,6 @@ registers: aTtransaction
! !
!ReceptiveAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:24:57'!
accountSummary
"^ transactions
inject: OrderedCollection new
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
......@@ -1119,27 +1162,36 @@ Object subclass: #SummaryAccount
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!SummaryAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:27:42'!
fromCertificateOfDeposit: aCertificate
^'Plazo fijo por 1000 durante 30 dias a una tna de 10%'! !
!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/15/2018 14:16:20'!
fromTransferDeposit: aTransferDeposit
^'Transferencia por ', aTransferDeposit value asString.! !
!SummaryAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:17:57'!
fromTransferWithdraw: aTransferWithdraw
^'Transferencia por ', (aTransferWithdraw value * -1) 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
!SummaryAccount methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:20:48'!
initializeWith: 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
......@@ -1152,7 +1204,7 @@ value
SummaryAccount class
instanceVariableNames: ''!
!SummaryAccount class methodsFor: 'as yet unclassified' stamp: 'ig 5/14/2018 19:09:36'!
!SummaryAccount class methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:20:42'!
of: transactions
^self new initializeWith: transactions.! !
......@@ -1165,6 +1217,11 @@ Object subclass: #Transfer
poolDictionaries: ''
category: 'PortfolioTreePrinter-Ejercicio'!
!Transfer methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:34:08'!
deposit
^deposit ! !
!Transfer methodsFor: 'as yet unclassified' stamp: 'ig 5/10/2018 21:36:14'!
initializeWith: aValue withWithdraw: aWithdraw andDeposit: aDeposit
......@@ -1176,6 +1233,11 @@ initializeWith: aValue withWithdraw: aWithdraw andDeposit: aDeposit
value
^value! !
!Transfer methodsFor: 'as yet unclassified' stamp: 'ig 5/15/2018 14:34:01'!
withdraw
^withdraw ! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
!classDefinition: 'Transfer class' 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