Commit e0a6d984 authored by Natasha Martinelli's avatar Natasha Martinelli
Browse files

ultima iteracion de customer import

parent 92078e86
Object subclass: #Address instanceVariableNames: 'id streetName streetNumber town zipCode province' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !Address methodsFor: 'twon' stamp: 'HernanWilkinson 10/28/2016 16:12'!town ^town! ! !Address methodsFor: 'twon' stamp: 'HernanWilkinson 10/28/2016 16:07'!town: aTown town := aTown! ! !Address methodsFor: 'street' stamp: 'HernanWilkinson 10/28/2016 13:27'!streetName: aStreetName streetName := aStreetName ! ! !Address methodsFor: 'street' stamp: 'HernanWilkinson 10/28/2016 16:12'!streetName ^streetName ! ! !Address methodsFor: 'street' stamp: 'HernanWilkinson 10/28/2016 16:12'!streetNumber ^streetNumber ! ! !Address methodsFor: 'street' stamp: 'HernanWilkinson 10/28/2016 13:27'!streetNumber: aStreetNumber streetNumber := aStreetNumber ! ! !Address methodsFor: 'province' stamp: 'HernanWilkinson 10/28/2016 16:11'!province ^province! ! !Address methodsFor: 'province' stamp: 'HernanWilkinson 10/28/2016 16:08'!province: aProvince province := aProvince ! ! !Address methodsFor: 'testing' stamp: 'HernanWilkinson 11/1/2016 10:06'!isAt: aStreetName ^streetName = aStreetName ! ! !Address methodsFor: 'zip code' stamp: 'HernanWilkinson 10/28/2016 16:08'!zipCode: aZipCode zipCode := aZipCode! ! !Address methodsFor: 'zip code' stamp: 'HernanWilkinson 10/28/2016 16:13'!zipCode ^zipCode! ! Object subclass: #Customer instanceVariableNames: 'id firstName lastName identificationType identificationNumber addresses' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !Customer methodsFor: 'addresses' stamp: 'HernanWilkinson 11/1/2016 10:05'!addressAt: aStreetName ifNone: noneClosure ^addresses detect: [ :anAddress | anAddress isAt: aStreetName ] ifNone: noneClosure ! ! !Customer methodsFor: 'addresses' stamp: 'HernanWilkinson 10/28/2016 13:25'!addresses ^ addresses! ! !Customer methodsFor: 'addresses' stamp: 'HernanWilkinson 11/1/2016 09:43'!numberOfAddresses ^addresses size! ! !Customer methodsFor: 'addresses' stamp: 'HernanWilkinson 10/28/2016 13:27'!addAddress: anAddress addresses add: anAddress ! ! !Customer methodsFor: 'addresses' stamp: 'HernanWilkinson 11/1/2016 18:03'!addressesIsEmpty ^addresses isEmpty! ! !Customer methodsFor: 'identification' stamp: 'HernanWilkinson 11/4/2016 09:42'!isIdentifiedAs: anIdType numbered: anIdNumber ^identificationType = anIdType and: [ identificationNumber = anIdNumber ]! ! !Customer methodsFor: 'identification' stamp: 'HernanWilkinson 10/28/2016 16:13'!identificationNumber ^identificationNumber ! ! !Customer methodsFor: 'identification' stamp: 'HernanWilkinson 10/28/2016 13:10'!identificationNumber: anIdentificationNumber identificationNumber := anIdentificationNumber! ! !Customer methodsFor: 'identification' stamp: 'RominaYalovetzky 6/30/2018 18:16'!identifiedAs ^identificationType.! ! !Customer methodsFor: 'identification' stamp: 'HernanWilkinson 10/28/2016 16:13'!identificationType ^identificationType ! ! !Customer methodsFor: 'identification' stamp: 'RominaYalovetzky 6/30/2018 18:16'!idNumber ^identificationNumber! ! !Customer methodsFor: 'identification' stamp: 'HernanWilkinson 10/28/2016 13:10'!identificationType: anIdentificationType identificationType := anIdentificationType! ! !Customer methodsFor: 'name' stamp: 'HernanWilkinson 10/28/2016 16:15'!lastName ^lastName ! ! !Customer methodsFor: 'name' stamp: 'HernanWilkinson 10/28/2016 13:09'!lastName: aLastName lastName := aLastName! ! !Customer methodsFor: 'name' stamp: 'HernanWilkinson 10/28/2016 16:15'!firstName ^firstName ! ! !Customer methodsFor: 'name' stamp: 'HernanWilkinson 10/28/2016 13:09'!firstName: aName firstName := aName! ! !Customer methodsFor: 'initialization' stamp: 'HernanWilkinson 10/28/2016 13:26'!initialize super initialize. addresses := OrderedCollection new.! ! TestCase subclass: #CustomerImportTest instanceVariableNames: 'importer system' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !CustomerImportTest methodsFor: 'test data - customer' stamp: 'HernanWilkinson 11/2/2016 10:53'!customerRecordWithMoreThanFiveFieldsTestData ^ ReadStream on: self alwaysImportedCustomerRecord,',x'! ! !CustomerImportTest methodsFor: 'test data - customer' stamp: 'HernanWilkinson 11/1/2016 17:48'!customerRecordStartingWithMoreThanOneCTestData ^ ReadStream on:'CC,Pepe,Sanchez,D,22333444'! ! !CustomerImportTest methodsFor: 'test data - customer' stamp: 'HernanWilkinson 11/2/2016 10:50'!customerRecordWithLessThanFiveFieldsTestData ^ ReadStream on: 'C,Pepe,Sanchez,D'! ! !CustomerImportTest methodsFor: 'test data - customer' stamp: 'HernanWilkinson 11/2/2016 10:46'!alwaysImportedCustomerIdType ^ 'D'! ! !CustomerImportTest methodsFor: 'test data - customer' stamp: 'HernanWilkinson 11/3/2016 09:21'!alwaysImportedCustomer | anIdentificationNumber anIdentifycationType | anIdentifycationType := self alwaysImportedCustomerIdType. anIdentificationNumber := self alwaysImportedCustomerIdNumber. ^ system customerIdentifiedAs: anIdentifycationType numbered: anIdentificationNumber! ! !CustomerImportTest methodsFor: 'test data - customer' stamp: 'HernanWilkinson 11/2/2016 10:47'!alwaysImportedCustomerIdNumber ^ '22333444'! ! !CustomerImportTest methodsFor: 'test data - customer' stamp: 'HernanWilkinson 11/2/2016 10:47'!alwaysImportedCustomerRecord ^ 'C,Pepe,Sanchez,', self alwaysImportedCustomerIdType, ',', self alwaysImportedCustomerIdNumber ! ! !CustomerImportTest methodsFor: 'importing' stamp: 'HernanWilkinson 11/4/2016 09:27'!importCustomersFrom: inputStream (CustomerImporter from: inputStream using: system) import! ! !CustomerImportTest methodsFor: 'testing' stamp: 'HernanWilkinson 11/2/2016 10:41'!testCanNotImportAddressRecordWithLessThanSixFields self should: [ self importCustomersFrom: self addressRecordWithLessThanSixFieldsTestData ] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: CustomerImporter invalidAddressRecordErrorDescription. self assert: self alwaysImportedCustomer addressesIsEmpty ]! ! !CustomerImportTest methodsFor: 'testing' stamp: 'HernanWilkinson 11/2/2016 10:42'!testCanNotImportAddressRecordWithMoreThanSixFields self should: [ self importCustomersFrom: self addressRecordWithMoreThanSixFieldsTestData ] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: CustomerImporter invalidAddressRecordErrorDescription. self assert: self alwaysImportedCustomer addressesIsEmpty ] ! ! !CustomerImportTest methodsFor: 'testing' stamp: 'HernanWilkinson 11/3/2016 09:11'!testShouldNotImportCustomerRecordsStartingWithMoreThanC self should: [ self importCustomersFrom: self customerRecordStartingWithMoreThanOneCTestData ] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: CustomerImporter invalidRecordTypeErrorDescription. self assert: system customersIsEmpty ]! ! !CustomerImportTest methodsFor: 'testing' stamp: 'HernanWilkinson 11/2/2016 15:52'!testEmptyLinesAreRecognizedAsInvalidRecords self should: [ self importCustomersFrom: self dataWithEmptyLine ] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: CustomerImporter invalidRecordTypeErrorDescription. self assert: self alwaysImportedCustomer addressesIsEmpty ]! ! !CustomerImportTest methodsFor: 'testing' stamp: 'HernanWilkinson 11/3/2016 09:11'!testCanNotImportCustomerRecordWithMoreThanFiveFields self should: [ self importCustomersFrom: self customerRecordWithMoreThanFiveFieldsTestData ] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: CustomerImporter invalidCustomerRecordErrorDescription. self assert: system customersIsEmpty ]! ! !CustomerImportTest methodsFor: 'testing' stamp: 'HernanWilkinson 11/3/2016 09:11'!testCanNotImportAddressWithoutCustomer self should: [ self importCustomersFrom: self addressWithoutCustomerTestData ] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: CustomerImporter addressWithoutCustomerErrorDescription. self assert: system customersIsEmpty ]! ! !CustomerImportTest methodsFor: 'testing' stamp: 'HernanWilkinson 11/2/2016 10:42'!testShouldNotImportAddressRecordsStartingWithMoreThanA self should: [ self importCustomersFrom: self addressRecordStartingWithMoreThanOneATestData ] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: CustomerImporter invalidRecordTypeErrorDescription. self assert: self alwaysImportedCustomer addressesIsEmpty ] ! ! !CustomerImportTest methodsFor: 'testing' stamp: 'HernanWilkinson 11/3/2016 09:11'!testCanNotImportCustomerRecordWithLessThanFiveFields self should: [ self importCustomersFrom: self customerRecordWithLessThanFiveFieldsTestData ] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: CustomerImporter invalidCustomerRecordErrorDescription. self assert: system customersIsEmpty ]! ! !CustomerImportTest methodsFor: 'testing' stamp: 'HernanWilkinson 11/1/2016 15:56'!testImportCustomers self importCustomersFrom: self validTestData. self assertImportedCustomersSizeIsCorrect. self assertPepeSanchezWasImportedCorrectly. self assertJuanPerezWasImportedCorrectly! ! !CustomerImportTest methodsFor: 'setup-teardown' stamp: 'HernanWilkinson 11/4/2016 09:51'!setUp system := Environment current createCustomerSystem. system start. system beginTransaction! ! !CustomerImportTest methodsFor: 'setup-teardown' stamp: 'HernanWilkinson 11/4/2016 09:52'!tearDown system commit. system shutdown! ! !CustomerImportTest methodsFor: 'asserting' stamp: 'HernanWilkinson 11/1/2016 10:56'!assert: customer isNamed: firstName lastName: lastName identfiedAs: idType withNumber: idNumber andNumberOfAddresses: addressesSize self assert: customer firstName equals: firstName. self assert: customer lastName equals: lastName. self assert: customer identificationType equals: idType. self assert: customer identificationNumber equals: idNumber. self assert: customer numberOfAddresses equals: addressesSize .! ! !CustomerImportTest methodsFor: 'asserting' stamp: 'HernanWilkinson 11/3/2016 09:10'!assertImportedCustomersSizeIsCorrect self assert: system allCustomers size equals: 2! ! !CustomerImportTest methodsFor: 'asserting' stamp: 'HernanWilkinson 11/3/2016 09:20'!assertPepeSanchezWasImportedCorrectly | customer | customer := self alwaysImportedCustomer. self assert: customer isNamed: 'Pepe' lastName: 'Sanchez' identfiedAs: self alwaysImportedCustomerIdType withNumber: self alwaysImportedCustomerIdNumber andNumberOfAddresses: 2. self assert: customer hasAddressAt: 'San Martin' number: 3322 in: 'Olivos' zipCode: 1636 province: 'BsAs'. self assert: customer hasAddressAt: 'Maipu' number: 888 in: 'Florida' zipCode: 1122 province: 'Buenos Aires'! ! !CustomerImportTest methodsFor: 'asserting' stamp: 'HernanWilkinson 11/1/2016 11:00'!assert: customer hasAddressAt: streetName number: streetNumber in: town zipCode: zipCode province: province | address | address := customer addressAt: streetName ifNone: [ self fail ]. self assert: address streetName equals: streetName. self assert: address streetNumber equals: streetNumber. self assert: address town equals: town. self assert: address zipCode equals: zipCode. self assert: address province equals: province. ! ! !CustomerImportTest methodsFor: 'asserting' stamp: 'HernanWilkinson 11/3/2016 09:21'!assertJuanPerezWasImportedCorrectly | customer idType idNumber | idType := 'C'. idNumber := '23-25666777-9'. customer := system customerIdentifiedAs: idType numbered: idNumber. self assert: customer isNamed: 'Juan' lastName: 'Perez' identfiedAs: idType withNumber: idNumber andNumberOfAddresses: 1. self assert: customer hasAddressAt: 'Alem' number: 1122 in: 'CABA' zipCode: 1001 province: 'CABA'! ! !CustomerImportTest methodsFor: 'test data' stamp: 'HernanWilkinson 11/2/2016 10:46'!validTestData ^ ReadStream on: self alwaysImportedCustomerRecord,' A,San Martin,3322,Olivos,1636,BsAs A,Maipu,888,Florida,1122,Buenos Aires C,Juan,Perez,C,23-25666777-9 A,Alem,1122,CABA,1001,CABA'! ! !CustomerImportTest methodsFor: 'test data' stamp: 'HernanWilkinson 11/2/2016 15:52'!dataWithEmptyLine ^ ReadStream on: self alwaysImportedCustomerRecord,' A,San Martin,3322,Olivos,1636,BsAs'! ! !CustomerImportTest methodsFor: 'test data - address' stamp: 'HernanWilkinson 11/1/2016 15:59'!addressWithoutCustomerTestData ^ ReadStream on: 'A,San Martin,3322,Olivos,1636,BsAs'! ! !CustomerImportTest methodsFor: 'test data - address' stamp: 'HernanWilkinson 11/2/2016 10:45'!addressRecordWithLessThanSixFieldsTestData ^ ReadStream on: self alwaysImportedCustomerRecord,' A,San Martin,3322,Olivos,1636'! ! !CustomerImportTest methodsFor: 'test data - address' stamp: 'HernanWilkinson 11/2/2016 10:45'!addressRecordWithMoreThanSixFieldsTestData ^ ReadStream on: self alwaysImportedCustomerRecord,' A,San Martin,3322,Olivos,1636,BsAs,y otra cosa'! ! !CustomerImportTest methodsFor: 'test data - address' stamp: 'HernanWilkinson 11/2/2016 10:45'!addressRecordStartingWithMoreThanOneATestData ^ ReadStream on: self alwaysImportedCustomerRecord,' AA,San Martin,3322,Olivos,1636,BsAs'! ! Object subclass: #CustomerSystem instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !CustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/4/2016 09:35'!customerIdentifiedAs: anIdentifycationType numbered: anIdentificationNumber self subclassResponsibility! ! !CustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/4/2016 09:35'!customersIsEmpty self subclassResponsibility! ! !CustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/4/2016 09:35'!allCustomers self subclassResponsibility! ! !CustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/4/2016 09:35'!add: aCustomer self subclassResponsibility! ! !CustomerSystem methodsFor: 'transaction' stamp: 'HernanWilkinson 11/4/2016 09:35'!beginTransaction self subclassResponsibility! ! !CustomerSystem methodsFor: 'transaction' stamp: 'HernanWilkinson 11/4/2016 09:35'!commit self subclassResponsibility! ! !CustomerSystem methodsFor: 'system live cycle' stamp: 'HernanWilkinson 11/4/2016 09:52'!shutdown self subclassResponsibility! ! !CustomerSystem methodsFor: 'system live cycle' stamp: 'HernanWilkinson 11/4/2016 09:51'!start self subclassResponsibility! ! Object subclass: #Environment instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'!!Environment commentStamp: '<historical>' prior: 0!Please comment me using the following template inspired by Class Responsibility Collaborator (CRC) design: For the Class part: State a one line summary. For example, "I represent a paragraph of text". For the Responsibility part: Three sentences about my main responsibilities - what I do, what I know. For the Collaborators Part: State my main collaborators and one line about how I interact with them. Public API and Key Messages - message one - message two - (for bonus points) how to create instances. One simple example is simply gorgeous. Internal Representation and Key Implementation Points. Implementation Points! !Environment methodsFor: 'system creation' stamp: 'HernanWilkinson 11/4/2016 09:49'!createCustomerSystem self subclassResponsibility ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Environment class instanceVariableNames: ''! !Environment class methodsFor: 'enviroment selection' stamp: 'HernanWilkinson 11/4/2016 09:46'!current ^self allSubclasses detect: [ :anEnvironemntClass | anEnvironemntClass isCurrent ] ifFound: [ :anEnvironmentClass | anEnvironmentClass new ] ifNone: [ self error: 'No environment detected' ]! ! !Environment class methodsFor: 'enviroment selection' stamp: 'HernanWilkinson 11/4/2016 09:49'!isCurrent self subclassResponsibility ! ! Environment subclass: #DevelpmentEnvironment instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !DevelpmentEnvironment methodsFor: 'system creation' stamp: 'nm 6/28/2018 19:38'!createSupplierSystem ^ TransientSupplierSystem new.! ! !DevelpmentEnvironment methodsFor: 'system creation' stamp: 'nm 6/28/2018 19:40'!createCustomerSystem ^ TransientCustomerSystem new.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DevelpmentEnvironment class instanceVariableNames: ''! !DevelpmentEnvironment class methodsFor: 'as yet unclassified' stamp: 'HernanWilkinson 11/4/2016 09:47'!isCurrent ^IntegrationEnvironment isCurrent not! ! Environment subclass: #IntegrationEnvironment instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !IntegrationEnvironment methodsFor: 'as yet unclassified' stamp: 'HernanWilkinson 11/4/2016 09:45'!createCustomerSystem ^PersistentCustomerSystem new! ! !IntegrationEnvironment methodsFor: 'system creation' stamp: 'RominaYalovetzky 7/2/2018 14:10'!createSupplierSystem ^PersistentSupplierSystem new! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! IntegrationEnvironment class instanceVariableNames: ''! !IntegrationEnvironment class methodsFor: 'testing' stamp: 'nm 7/2/2018 01:14'!isCurrent ^true! ! Object subclass: #PartyImporter instanceVariableNames: 'line readStream record system' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !PartyImporter methodsFor: 'error signal' stamp: 'RominaYalovetzky 7/1/2018 13:05'!signalInvalidAddressRecord self error: self class invalidAddressRecordErrorDescription ! ! !PartyImporter methodsFor: 'error signal' stamp: 'RominaYalovetzky 7/1/2018 13:05'!signalInvalidCustomerRecord self error: self class invalidCustomerRecordErrorDescription ! ! !PartyImporter methodsFor: 'error signal' stamp: 'RominaYalovetzky 7/1/2018 13:05'!signalInvalidRecordType self error: self class invalidRecordTypeErrorDescription! ! !PartyImporter methodsFor: 'initialization' stamp: 'RominaYalovetzky 7/1/2018 13:19'!initializeOn: aReadStream using: aCustomerSystem self subclassResponsibility ! ! !PartyImporter methodsFor: 'importing' stamp: 'RominaYalovetzky 7/1/2018 13:03'!import [ self canImportNextLine ] whileTrue: [ self convertLineToRecord. self importRecord ]! ! !PartyImporter methodsFor: 'importing - private' stamp: 'RominaYalovetzky 7/1/2018 13:02'!importRecord
self subclassResponsibility! ! !PartyImporter methodsFor: 'importing - private' stamp: 'RominaYalovetzky 7/1/2018 13:04'!assertRecordNotEmpty record isEmpty ifTrue: [ self signalInvalidRecordType ]! ! !PartyImporter methodsFor: 'importing - private' stamp: 'RominaYalovetzky 7/1/2018 13:05'!canImportNextLine line := readStream nextLine. ^ line notNil! ! !PartyImporter methodsFor: 'importing - private' stamp: 'RominaYalovetzky 7/1/2018 13:05'!convertLineToRecord record := line substrings: {$,}. self assertRecordNotEmpty! ! !PartyImporter methodsFor: 'importing - private - customer' stamp: 'RominaYalovetzky 7/1/2018 13:04'!assertValidCustomerRecordSize record size ~= 5 ifTrue: [ self signalInvalidCustomerRecord ]. ! ! !PartyImporter methodsFor: 'importing - private - customer' stamp: 'RominaYalovetzky 7/1/2018 13:02'!importCustomer
self subclassResponsibility! ! !PartyImporter methodsFor: 'importing - private - customer' stamp: 'RominaYalovetzky 7/1/2018 13:36'!isCustomerRecord self subclassResponsibility ! ! !PartyImporter methodsFor: 'importing - private - address' stamp: 'RominaYalovetzky 7/1/2018 13:02'!assertThereIsCustsomerForAddress
self subclassResponsibility! ! !PartyImporter methodsFor: 'importing - private - address' stamp: 'RominaYalovetzky 7/1/2018 13:04'!assertValidAddressRecordSize record size ~= 6 ifTrue: [ self signalInvalidAddressRecord ]. ! ! !PartyImporter methodsFor: 'importing - private - address' stamp: 'RominaYalovetzky 7/1/2018 13:05'!isAddressRecord ^ record first = 'A'! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! PartyImporter class instanceVariableNames: ''! !PartyImporter class methodsFor: 'error descriptions' stamp: 'RominaYalovetzky 7/1/2018 13:02'!addressWithoutCustomerErrorDescription
self subclassResponsibility! ! PartyImporter subclass: #CustomerImporter instanceVariableNames: 'newCustomer' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !CustomerImporter methodsFor: 'importing - private - customer' stamp: 'HernanWilkinson 11/4/2016 09:33'!importCustomer self assertValidCustomerRecordSize. newCustomer := Customer new. newCustomer firstName: record second. newCustomer lastName: record third. newCustomer identificationType: record fourth. newCustomer identificationNumber: record fifth. system add: newCustomer! ! !CustomerImporter methodsFor: 'importing - private - customer' stamp: 'RominaYalovetzky 7/1/2018 13:36'!isCustomerRecord ^ record first = 'C'! ! !CustomerImporter methodsFor: 'initialization' stamp: 'RominaYalovetzky 7/1/2018 13:20'!initializeOn: aReadStream using: aCustomerSystem readStream := aReadStream. system := aCustomerSystem! ! !CustomerImporter methodsFor: 'importing - private - address' stamp: 'HernanWilkinson 11/2/2016 10:56'!assertThereIsCustsomerForAddress newCustomer isNil ifTrue: [ self signalAddressWithoutCustomerError ]. ! ! !CustomerImporter methodsFor: 'importing - private - address' stamp: 'RominaYalovetzky 7/1/2018 13:06'!importAddress | newAddress | self assertThereIsCustsomerForAddress. self assertValidAddressRecordSize. newAddress := Address new. newAddress streetName: record second. newAddress streetNumber: record third asInteger. newAddress town: record fourth. newAddress zipCode: record fifth asInteger. newAddress province: record sixth. ^ newCustomer addAddress: newAddress! ! !CustomerImporter methodsFor: 'importing - private' stamp: 'HernanWilkinson 11/1/2016 17:52'!importRecord self isCustomerRecord ifTrue: [ ^self importCustomer ]. self isAddressRecord ifTrue: [ ^self importAddress ]. self signalInvalidRecordType! ! !CustomerImporter methodsFor: 'error signal' stamp: 'HernanWilkinson 11/1/2016 16:01'!signalAddressWithoutCustomerError self error: self class addressWithoutCustomerErrorDescription.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CustomerImporter class instanceVariableNames: 'readStream system'! !CustomerImporter class methodsFor: 'instance creation' stamp: 'HernanWilkinson 11/4/2016 09:27'!from: aReadStream using: aCustomerSystem ^ self new initializeOn: aReadStream using: aCustomerSystem! ! !CustomerImporter class methodsFor: 'error descriptions' stamp: 'HernanWilkinson 11/1/2016 18:00'!invalidAddressRecordErrorDescription ^'Invalid address record'! ! !CustomerImporter class methodsFor: 'error descriptions' stamp: 'HernanWilkinson 11/1/2016 17:54'!invalidRecordTypeErrorDescription ^'Invalid record type'! ! !CustomerImporter class methodsFor: 'error descriptions' stamp: 'HernanWilkinson 11/1/2016 16:02'!addressWithoutCustomerErrorDescription ^'There is no Customer for the imported address'! ! !CustomerImporter class methodsFor: 'error descriptions' stamp: 'HernanWilkinson 11/2/2016 10:51'!invalidCustomerRecordErrorDescription ^'Invalid customer record'! ! CustomerSystem subclass: #PersistentCustomerSystem instanceVariableNames: 'session' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !PersistentCustomerSystem methodsFor: 'system live cycle' stamp: 'HernanWilkinson 11/4/2016 09:52'!shutdown session shutdown! ! !PersistentCustomerSystem methodsFor: 'system live cycle' stamp: 'HernanWilkinson 11/4/2016 09:51'!start session start! ! !PersistentCustomerSystem methodsFor: 'initialization' stamp: 'HernanWilkinson 11/3/2016 08:54'!initialize super initialize. self initializeSession. ! ! !PersistentCustomerSystem methodsFor: 'initialization' stamp: 'HernanWilkinson 11/4/2016 09:19'!initializeSession session := DataBaseSession for: (Array with: self addressMapping with: self customerMapping)! ! !PersistentCustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/4/2016 09:18'!customerIdentifiedAs: anIdentifycationType numbered: anIdentificationNumber | customers | customers := session select: [ :aCustomer | aCustomer identificationType = anIdentifycationType and: [ aCustomer identificationNumber = anIdentificationNumber ] ] ofType: Customer. customers size = 1 ifFalse: [ self error: 'No o more that one customer found' ]. ^ customers anyOne! ! !PersistentCustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/3/2016 09:11'!customersIsEmpty ^ self allCustomers isEmpty! ! !PersistentCustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/4/2016 09:18'!allCustomers ^ session selectAllOfType: Customer! ! !PersistentCustomerSystem methodsFor: 'customers' stamp: 'RominaYalovetzky 7/2/2018 15:51'!add: aCustomer session persist: aCustomer! ! !PersistentCustomerSystem methodsFor: 'mapping' stamp: 'HernanWilkinson 11/3/2016 08:52'!addressMapping ^ ClassMapping withDefaultTableNameFor: Address mappingAll: (Array with: (EmbededMapping withDefaultFieldNameFor: #streetName) with: (EmbededMapping withDefaultFieldNameFor: #streetNumber) with: (EmbededMapping withDefaultFieldNameFor: #town) with: (EmbededMapping withDefaultFieldNameFor: #zipCode) with: (EmbededMapping withDefaultFieldNameFor: #province))! ! !PersistentCustomerSystem methodsFor: 'mapping' stamp: 'HernanWilkinson 11/3/2016 08:52'!customerMapping ^ ClassMapping withDefaultTableNameFor: Customer mappingAll: (Array with: (EmbededMapping withDefaultFieldNameFor: #firstName) with: (EmbededMapping withDefaultFieldNameFor: #lastName) with: (EmbededMapping withDefaultFieldNameFor: #identificationType) with: (EmbededMapping withDefaultFieldNameFor: #identificationNumber) with: (OneToManyMapping withDefaultFieldNameFor: #addresses ofType: Address))! ! !PersistentCustomerSystem methodsFor: 'transaction' stamp: 'HernanWilkinson 11/4/2016 09:18'!beginTransaction session beginTransaction! ! !PersistentCustomerSystem methodsFor: 'transaction' stamp: 'HernanWilkinson 11/4/2016 09:18'!commit session commit! ! Object subclass: #Supplier instanceVariableNames: 'id fullName identificationType identificationNumber customers addresses' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !Supplier methodsFor: 'identification' stamp: 'RominaYalovetzky 7/2/2018 15:43'!idNumber ^identificationNumber! ! !Supplier methodsFor: 'adding' stamp: 'RominaYalovetzky 6/30/2018 16:33'!addCustomer: aCustomer customers add: aCustomer. ! ! !Supplier methodsFor: 'adding' stamp: 'RominaYalovetzky 7/1/2018 13:48'!addAddress: anAddress addresses add: anAddress. ! ! !Supplier methodsFor: 'adding' stamp: 'RominaYalovetzky 6/30/2018 16:29'!addAddress: anAddress for: aNewCustomer. ^ aNewCustomer addAddress: anAddress.! ! !Supplier methodsFor: 'as yet unclassified' stamp: 'nm 7/2/2018 00:44'!addressesIsEmpty ^addresses isEmpty! ! !Supplier methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 6/30/2018 15:44'!isIdentifiedAs: anIdType numbered: anIdNumber ^identificationType = anIdType and: [ identificationNumber = anIdNumber ]! ! !Supplier methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 7/1/2018 12:36'!customersIsEmpty ^customers isEmpty.! ! !Supplier methodsFor: 'initialization' stamp: 'RominaYalovetzky 7/1/2018 12:52'!initialize customers := OrderedCollection new. addresses := OrderedCollection new. ! ! !Supplier methodsFor: 'accessing' stamp: 'RominaYalovetzky 7/2/2018 15:43'!identificationNumber ^identificationNumber! ! !Supplier methodsFor: 'accessing' stamp: 'RominaYalovetzky 6/30/2018 15:26'!identificationNumber: anIdentificationNumber identificationNumber := anIdentificationNumber! ! !Supplier methodsFor: 'accessing' stamp: 'RominaYalovetzky 6/30/2018 15:25'!fullName: afullName fullName := afullName.! ! !Supplier methodsFor: 'accessing' stamp: 'RominaYalovetzky 7/1/2018 13:50'!addresses ^ addresses copy. ! ! !Supplier methodsFor: 'accessing' stamp: 'RominaYalovetzky 6/30/2018 15:42'!fullName ^fullName. ! ! !Supplier methodsFor: 'accessing' stamp: 'RominaYalovetzky 6/30/2018 17:20'!customers ^ customers copy. ! ! !Supplier methodsFor: 'accessing' stamp: 'RominaYalovetzky 7/2/2018 15:46'!identificationType ^identificationType ! ! !Supplier methodsFor: 'accessing' stamp: 'RominaYalovetzky 6/30/2018 15:26'!identificationType: anIdentificationType identificationType := anIdentificationType! ! TestCase subclass: #SupplierImportTest instanceVariableNames: 'importer system' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !SupplierImportTest methodsFor: 'asserting' stamp: 'RominaYalovetzky 6/30/2018 17:27'!assert: customer isNamed: firstName lastName: lastName identfiedAs: idType withNumber: idNumber andNumberOfAddresses: addressesSize self assert: customer firstName equals: firstName. self assert: customer lastName equals: lastName. self assert: customer identificationType equals: idType. self assert: customer identificationNumber equals: idNumber. self assert: customer numberOfAddresses equals: addressesSize .! ! !SupplierImportTest methodsFor: 'asserting' stamp: 'RominaYalovetzky 6/30/2018 17:29'!assert: customer hasAddressAt: streetName number: streetNumber in: town zipCode: zipCode province: province | address | address := customer addressAt: streetName ifNone: [ self fail ]. self assert: address streetName equals: streetName. self assert: address streetNumber equals: streetNumber. self assert: address town equals: town. self assert: address zipCode equals: zipCode. self assert: address province equals: province.! ! !SupplierImportTest methodsFor: 'asserting' stamp: 'RominaYalovetzky 6/30/2018 17:28'!assertPepeSanchezWasImportedCorrectlyFor: aSupplier | customer | "customer := self alwaysImportedCustomer. " customer := (aSupplier customers) last. self assert: customer isNamed: 'Pepe' lastName: 'Sanchez' identfiedAs: 'D' withNumber: '22333444' andNumberOfAddresses: 2. self assert: customer hasAddressAt: 'San Martin' number: 3322 in: 'Olivos' zipCode: 1636 province: 'BsAs'. self assert: customer hasAddressAt: 'Maipu' number: 888 in: 'Florida' zipCode: 1122 province: 'Buenos Aires'! ! !SupplierImportTest methodsFor: 'test data - address' stamp: 'RominaYalovetzky 7/1/2018 12:39'!addressRecordWithLessThanSixFieldsTestData ^ ReadStream on: self alwaysSupplierRecord,' A,San Martin,3322,Olivos,1636'.! ! !SupplierImportTest methodsFor: 'test data - address' stamp: 'RominaYalovetzky 6/30/2018 20:04'!addressRecordWithMoreThanSixFieldsTestData ^ ReadStream on: self alwaysSupplierRecord,' A,San Martin,3322,Olivos,1636,BsAs,y otra cosa'.! ! !SupplierImportTest methodsFor: 'test data - address' stamp: 'nm 7/2/2018 00:39'!addressRecordStartingWithMoreThanOneATestData ^ ReadStream on: self alwaysSupplierRecord,' AA,San Martin,3322,Olivos,1636,BsAs,y otra cosa'.! ! !SupplierImportTest methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 6/30/2018 18:07'!initialCustomer ^ ReadStream on: self alwaysSupplierRecord,' NC,Julieta,Diaz,D,5456774'.! ! !SupplierImportTest methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 6/30/2018 18:08'!alwaysSupplierRecord ^ 'S,Supplier1,D,123'.! ! !SupplierImportTest methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 7/1/2018 12:35'!alwaysImportedSupplier | anIdentificationNumber anIdentifycationType | anIdentifycationType := 'D'. anIdentificationNumber := '123'. ^ system supplierIdentifiedAs: anIdentifycationType numbered: anIdentificationNumber ! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/1/2018 13:33'!test04CanNotImportNewCustomerRecordWithMoreThanFiveFields self should: [(SupplierImporter from: (self newCustomerWithMoreThanFiveFields) using: system) import] raise: Error withExceptionDo: [ :anError| self assert: anError messageText equals: SupplierImporter invalidCustomerRecordErrorDescription. self assert: self alwaysImportedSupplier customersIsEmpty]. ! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/1/2018 12:36'!test05CanNotImportNewCustomerRecordWithLessThanFiveFields self should: [(SupplierImporter from: (self newCustomerRecordWithLessThanFiveFieldsTestData ) using: system) import] raise: Error withExceptionDo: [ :anError| self assert: anError messageText equals: SupplierImporter invalidCustomerRecordErrorDescription. self assert: self alwaysImportedSupplier customersIsEmpty]. ! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/2/2018 15:55'!test01ImportValidSupplier | supplier | (SupplierImporter from: self validSupplierDataTest using: system) import. self assert: (system allSuppliers) size equals: 1. supplier := system supplierIdentifiedAs: 'D' numbered: '123'. self assert: supplier fullName equals: 'Supplier1'! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/2/2018 15:55'!test02CanImportSupplierWithCustomersAndAddressesCorrectly | supplier | (SupplierImporter from: (self initialCustomer) using: system) import. supplier := system supplierIdentifiedAs: 'D' numbered: '123'. "previamente ya cree al proveedor con su primer cliente y ahora le agrego cosas" (SupplierImporter from: (self validTestDataToAdd) using: system) importFor: supplier. self assert: (system allSuppliers) size equals: 1. self assert: supplier customers size equals: 2. self assert: supplier addresses size equals: 2. "self assertImportedCustomersSizeIsCorrect." "self assertPepeSanchezWasImportedCorrectlyFor: supplier" "self assertExistingCustomerWasFoundCorrectly."! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/1/2018 13:20'!test08CanNotImportCustomerWithoutSupplier self should: [(SupplierImporter from: (ReadStream on: 'NC,Pepe,Sanchez,D,22333444') using: system) import] raise: Error withExceptionDo: [ :anError| self assert: anError messageText equals: SupplierImporter customerWithoutSupplierErrorDescription. self assert: system suppliersIsEmpty]. ! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/1/2018 12:39'!test07CanNotImportAddressRecordWithLessThanSixFields self should: [(SupplierImporter from: (self addressRecordWithLessThanSixFieldsTestData) using: system) import] raise: Error withExceptionDo: [ :anError| self assert: anError messageText equals: SupplierImporter invalidAddressRecordErrorDescription. "self assert: self alwaysImportedSupplier addressesIsEmpty"]. ! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/1/2018 12:39'!test06CanNotImportAddressRecordWithMoreThanSixFields self should: [(SupplierImporter from: (self addressRecordWithMoreThanSixFieldsTestData) using: system) import] raise: Error withExceptionDo: [ :anError| self assert: anError messageText equals: SupplierImporter invalidAddressRecordErrorDescription. "self assert: self alwaysImportedSupplier addressesIsEmpty"]. ! ! !SupplierImportTest methodsFor: 'tests' stamp: 'nm 7/2/2018 00:45'!test11ShouldNotImportAddressRecordsStartingWithMoreThanA self should: [ (SupplierImporter from: (self addressRecordStartingWithMoreThanOneATestData) using: system) import ] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: SupplierImporter invalidRecordTypeErrorDescription. self assert: self alwaysImportedSupplier addressesIsEmpty ]! ! !SupplierImportTest methodsFor: 'tests' stamp: 'nm 7/2/2018 00:55'!test12ShouldNotImportSupplierCustomerRecordsStartingWithMoreThanN self should: [ (SupplierImporter from: (self newCustomerStartingWithMoreThanOneNTestData) using: system) import] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: SupplierImporter invalidRecordTypeErrorDescription.]! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/1/2018 12:42'!test09CanNotImportAddressWithoutSupplier self should: [(SupplierImporter from: (ReadStream on: 'A,San Martin,3322,Olivos,1636,BsAs') using: system) import] raise: Error withExceptionDo: [ :anError| self assert: anError messageText equals: SupplierImporter addressWithoutSupplierErrorDescription. self assert: system suppliersIsEmpty]. ! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/1/2018 20:19'!test03CanNotImportUnexistedCustomerWhenItIsNot | supplier | (SupplierImporter from: (ReadStream on: 'S,Supplier1,D,123') using: system) import. supplier := system supplierIdentifiedAs: 'D' numbered: '123'. self should: [(SupplierImporter from: (self noExistingCustomerTestData) using: system) importFor: supplier] raise: Error withExceptionDo: [ :anError | self assert: anError messageText equals: SupplierImporter errorCustomerNotFound ]. ! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/1/2018 12:51'!test10EmptyLinesAreRecognizedAsInvalidRecords self should: [ (SupplierImporter from: (self dataWithEmptyLine) using: system) import] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: SupplierImporter invalidRecordTypeErrorDescription. self assert: self alwaysImportedSupplier customersIsEmpty. self assert: self alwaysImportedSupplier addressesIsEmpty ].! ! !SupplierImportTest methodsFor: 'tests' stamp: 'RominaYalovetzky 7/1/2018 20:16'!validSupplierDataTest ^ ReadStream on: 'S,Supplier1,D,123'! ! !SupplierImportTest methodsFor: 'tests' stamp: 'nm 7/2/2018 01:02'!test13ShouldNotImportSupplierRecordsStartingWithMoreThanOneS self should: [ (SupplierImporter from: (self newSupplierWithMoreThanOneS) using: system) import] raise: Error - MessageNotUnderstood withExceptionDo: [ :anError | self assert: anError messageText equals: SupplierImporter invalidRecordTypeErrorDescription.]! ! !SupplierImportTest methodsFor: 'test data' stamp: 'nm 7/1/2018 19:57'!noExistingCustomerTestData ^ ReadStream on: 'EC,D,5456774'! ! !SupplierImportTest methodsFor: 'test data' stamp: 'RominaYalovetzky 7/1/2018 12:51'!dataWithEmptyLine ^ ReadStream on: self alwaysSupplierRecord,' A,San Martin,3322,Olivos,1636,BsAs'! ! !SupplierImportTest methodsFor: 'test data' stamp: 'nm 7/2/2018 01:00'!newSupplierWithMoreThanOneS ^ ReadStream on: 'SS,Supplier1,D,123 NC,Pepe,Sanchez,D,22333444 EC,D,5456774 A,San Martin,3322,Olivos,1636,BsAs'! ! !SupplierImportTest methodsFor: 'test data' stamp: 'RominaYalovetzky 6/30/2018 19:28'!validTestData ^ ReadStream on: 'S,Supplier1,D,123 NC,Pepe,Sanchez,D,22333444 EC,D,5456774 A,San Martin,3322,Olivos,1636,BsAs A,Maipu,888,Florida,1122,Buenos Aires'! ! !SupplierImportTest methodsFor: 'test data' stamp: 'RominaYalovetzky 7/1/2018 12:25'!newCustomerRecordWithLessThanFiveFieldsTestData ^ ReadStream on: self alwaysSupplierRecord,' NC,Julieta,Diaz,D'! ! !SupplierImportTest methodsFor: 'test data' stamp: 'RominaYalovetzky 6/30/2018 19:53'!newCustomerWithMoreThanFiveFields ^ ReadStream on: self alwaysSupplierRecord,' NC,Julieta,Diaz,D,5456774,15'! ! !SupplierImportTest methodsFor: 'test data' stamp: 'RominaYalovetzky 6/30/2018 19:28'!validTestDataToAdd ^ ReadStream on: 'NC,Pepe,Sanchez,D,22333444 EC,D,5456774 A,San Martin,3322,Olivos,1636,BsAs A,Maipu,888,Florida,1122,Buenos Aires'! ! !SupplierImportTest methodsFor: 'test data' stamp: 'nm 7/2/2018 00:48'!newCustomerStartingWithMoreThanOneNTestData ^ ReadStream on: self alwaysSupplierRecord,' NNC,Julieta,Diaz,D,5456774,15'! ! !SupplierImportTest methodsFor: 'initialization' stamp: 'nm 6/28/2018 19:37'!setUp system := Environment current createSupplierSystem. system start. system beginTransaction.! ! PartyImporter subclass: #SupplierImporter instanceVariableNames: 'newSupplier' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !SupplierImporter methodsFor: 'importing' stamp: 'RominaYalovetzky 6/30/2018 19:01'!importFor: aSupplier [ self canImportNextLine ] whileTrue: [ self convertLineToRecord. self importRecordFor: aSupplier ].! ! !SupplierImporter methodsFor: 'signalling' stamp: 'nm 7/1/2018 19:49'!signalNotExistiedCustomer self error: self class errorCustomerNotFound.! ! !SupplierImporter methodsFor: 'signalling' stamp: 'RominaYalovetzky 6/30/2018 17:55'!signalNotExistingCustomer self error: self class NotExistingCustomerDescription! ! !SupplierImporter methodsFor: 'importing - private - address' stamp: 'RominaYalovetzky 7/1/2018 13:47'!importAddress | newAddress | self assertThereIsSupplierForAddress. "self assertThereIsCustomerForAddress." self assertValidAddressRecordSize. newAddress := Address new. newAddress streetName: record second. newAddress streetNumber: record third asInteger. newAddress town: record fourth. newAddress zipCode: record fifth asInteger. newAddress province: record sixth. ^ newSupplier addAddress: newAddress. "^ newSupplier addAddress: newAddress for: newCustomer. "! ! !SupplierImporter methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 7/1/2018 13:30'!importNewCustomer | newCustomer | self assertThereIsSupplierForCustsomer. self assertValidCustomerRecordSize. newCustomer := Customer new. newCustomer firstName: record second. newCustomer lastName: record third. newCustomer identificationType: record fourth. newCustomer identificationNumber: record fifth. newSupplier addCustomer: newCustomer.! ! !SupplierImporter methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 7/1/2018 12:16'!assertThereIsSupplierForCustsomer newSupplier isNil ifTrue: [ self signalCustomerWithoutSupplierError ].! ! !SupplierImporter methodsFor: 'as yet unclassified' stamp: 'nm 7/1/2018 19:58'!searchExistingCustomer "al cliente existente lo designa como EC,D,5456774" | idType idNumber | idType := record second. idNumber := record third. "self assertIsExistigCustomerFor: newSupplier. " "existingCustomer := (newSupplier customers) select: [ :aCustomer| aCustomer isIdentifiedAs: idType numbered: idNumber]. (existingCustomer isNil) ifTrue: [ self signalNotExistingCustomer ]." (newSupplier customers) detect: [ :aCustomer | (aCustomer isIdentifiedAs: idType numbered: idNumber)] ifNone: [ self signalNotExistiedCustomer. ]. "self signalNotExistingCustomer"! ! !SupplierImporter methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 7/1/2018 12:17'!signalCustomerWithoutSupplierError self error: self class customerWithoutSupplierErrorDescription.! ! !SupplierImporter methodsFor: 'asserting' stamp: 'RominaYalovetzky 7/1/2018 12:46'!signalAddressWithoutSupplierError self error: self class addressWithoutSupplierErrorDescription! ! !SupplierImporter methodsFor: 'asserting' stamp: 'RominaYalovetzky 6/30/2018 18:39'!assert: aCustomer isIdentifiedAs: anIdType numbered: anIdNumber ^ (aCustomer identifiedAs) = anIdType and: [ aCustomer idNumber = anIdNumber].! ! !SupplierImporter methodsFor: 'asserting' stamp: 'RominaYalovetzky 7/1/2018 12:46'!assertThereIsSupplierForAddress newSupplier isNil ifTrue: [ self signalAddressWithoutSupplierError ].! ! !SupplierImporter methodsFor: 'importing - private' stamp: 'RominaYalovetzky 6/30/2018 17:33'!importRecord self isSupplierRecord ifTrue: [ ^self importSupplier]. self isNewCustomerRecord ifTrue: [ ^self importNewCustomer]. self isExistingCustomerRecord ifTrue: [ ^self searchExistingCustomer]. self isAddressRecord ifTrue: [ ^self importAddress ]. self signalInvalidRecordType! ! !SupplierImporter methodsFor: 'importing - private' stamp: 'nm 6/28/2018 20:03'!importSupplier "self assertValidCustomerRecordSize." newSupplier := Supplier new. newSupplier fullName: record second. newSupplier identificationType: record third. newSupplier identificationNumber: record fourth. system add: newSupplier.! ! !SupplierImporter methodsFor: 'importing - private' stamp: 'RominaYalovetzky 6/30/2018 19:01'!importRecordFor: aSupplier. newSupplier := aSupplier. self isNewCustomerRecord ifTrue: [ ^self importNewCustomer]. self isExistingCustomerRecord ifTrue: [ ^self searchExistingCustomer]. self isAddressRecord ifTrue: [ ^self importAddress ]. self signalInvalidRecordType! ! !SupplierImporter methodsFor: 'testing' stamp: 'RominaYalovetzky 6/30/2018 15:13'!isSupplierRecord ^ record first = 'S'! ! !SupplierImporter methodsFor: 'testing' stamp: 'RominaYalovetzky 6/30/2018 15:20'!isExistingCustomerRecord ^ record first = 'EC'! ! !SupplierImporter methodsFor: 'testing' stamp: 'RominaYalovetzky 6/30/2018 15:20'!isNewCustomerRecord ^ record first = 'NC'! ! !SupplierImporter methodsFor: 'as yet unclassified ' stamp: 'nm 6/28/2018 19:52'!initializeOn: aReadStream using: aTransientSupplierSystem readStream := aReadStream. system := aTransientSupplierSystem.! ! !SupplierImporter methodsFor: 'as yet unclassified ' stamp: 'RominaYalovetzky 6/30/2018 19:00'!initializeOn: aReadStream using: aTransientSupplierSystem for: aSupplier. readStream := aReadStream. system := aTransientSupplierSystem.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! SupplierImporter class instanceVariableNames: ''! !SupplierImporter class methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 7/1/2018 12:13'!customerWithoutSupplierErrorDescription ^'There is no supplier for the imported Customer'! ! !SupplierImporter class methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 7/1/2018 12:44'!addressWithoutSupplierErrorDescription ^'There is no supplier for the imported address'.! ! !SupplierImporter class methodsFor: 'as yet unclassified' stamp: 'nm 6/28/2018 19:43'!from: aReadStream using: aTransientSupplierSystem ^ self new initializeOn: aReadStream using: aTransientSupplierSystem.! ! !SupplierImporter class methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 6/30/2018 17:55'!NotExistingCustomerDescription ^'Not existing customer'! ! !SupplierImporter class methodsFor: 'error descriptions' stamp: 'RominaYalovetzky 6/30/2018 20:02'!invalidAddressRecordErrorDescription ^'Invalid address record'! ! !SupplierImporter class methodsFor: 'error descriptions' stamp: 'RominaYalovetzky 7/1/2018 12:49'!invalidRecordTypeErrorDescription ^'There is an empty line'.! ! !SupplierImporter class methodsFor: 'error descriptions' stamp: 'nm 7/1/2018 19:49'!errorCustomerNotFound ^ 'No existe el cliente'.! ! !SupplierImporter class methodsFor: 'error descriptions' stamp: 'RominaYalovetzky 6/30/2018 19:57'!invalidCustomerRecordErrorDescription ^'Invalid customer record'! ! !SupplierImporter class methodsFor: 'instance creation' stamp: 'RominaYalovetzky 6/30/2018 18:59'!from: aReadStream using: aTransientSupplierSystem for: aSupplier ^ self new initializeOn: aReadStream using: aTransientSupplierSystem for: aSupplier.! ! Object subclass: #SupplierSystem instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !SupplierSystem methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 6/30/2018 15:34'!numberOfSupplier self shouldBeImplemented.! ! SupplierSystem subclass: #PersistentSupplierSystem instanceVariableNames: 'session suppliers' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !PersistentSupplierSystem methodsFor: 'customers' stamp: 'nm 7/2/2018 01:16'!add: aSupplier session persist: aSupplier! ! !PersistentSupplierSystem methodsFor: 'customers' stamp: 'RominaYalovetzky 7/2/2018 16:03'!suppliersIsEmpty ^ self allSuppliers isEmpty! ! !PersistentSupplierSystem methodsFor: 'customers' stamp: 'nm 7/2/2018 01:17'!allSuppliers ^ session selectAllOfType: Supplier! ! !PersistentSupplierSystem methodsFor: 'customers' stamp: 'RominaYalovetzky 7/2/2018 15:56'!supplierIdentifiedAs: anIdentifycationType numbered: anIdentificationNumber"TODO" | supplier | supplier := session select: [ :aSupplier | aSupplier identificationType = anIdentifycationType and: [ aSupplier identificationNumber = anIdentificationNumber ] ] ofType: Supplier . supplier size = 1 ifFalse: [ self error: 'No or more that one customer found' ]. ^ supplier anyOne! ! !PersistentSupplierSystem methodsFor: 'system live cycle' stamp: 'nm 7/2/2018 01:12'!shutdown session shutdown! ! !PersistentSupplierSystem methodsFor: 'system live cycle' stamp: 'nm 7/2/2018 01:12'!start session start! ! !PersistentSupplierSystem methodsFor: 'initialization' stamp: 'nm 7/2/2018 01:12'!initialize super initialize. self initializeSession. ! ! !PersistentSupplierSystem methodsFor: 'initialization' stamp: 'nm 7/2/2018 01:19'!initializeSession session := DataBaseSession for: (Array with: self addressMapping with: self customerMapping with: self supplierMapping)! ! !PersistentSupplierSystem methodsFor: 'mapping' stamp: 'RominaYalovetzky 7/2/2018 16:00'!supplierMapping ^ ClassMapping withDefaultTableNameFor: Supplier mappingAll: (Array with: (EmbededMapping withDefaultFieldNameFor: #fullName) with: (EmbededMapping withDefaultFieldNameFor: #identificationType) with: (EmbededMapping withDefaultFieldNameFor: #identificationNumber) with: (OneToManyMapping withDefaultFieldNameFor: #customers ofType: Customer) with: (OneToManyMapping withDefaultFieldNameFor: #addresses ofType: Address))! ! !PersistentSupplierSystem methodsFor: 'mapping' stamp: 'nm 7/2/2018 01:12'!addressMapping ^ ClassMapping withDefaultTableNameFor: Address mappingAll: (Array with: (EmbededMapping withDefaultFieldNameFor: #streetName) with: (EmbededMapping withDefaultFieldNameFor: #streetNumber) with: (EmbededMapping withDefaultFieldNameFor: #town) with: (EmbededMapping withDefaultFieldNameFor: #zipCode) with: (EmbededMapping withDefaultFieldNameFor: #province))! ! !PersistentSupplierSystem methodsFor: 'mapping' stamp: 'nm 7/2/2018 01:12'!customerMapping ^ ClassMapping withDefaultTableNameFor: Customer mappingAll: (Array with: (EmbededMapping withDefaultFieldNameFor: #firstName) with: (EmbededMapping withDefaultFieldNameFor: #lastName) with: (EmbededMapping withDefaultFieldNameFor: #identificationType) with: (EmbededMapping withDefaultFieldNameFor: #identificationNumber) with: (OneToManyMapping withDefaultFieldNameFor: #addresses ofType: Address))! ! !PersistentSupplierSystem methodsFor: 'transaction' stamp: 'nm 7/2/2018 01:12'!beginTransaction session beginTransaction! ! !PersistentSupplierSystem methodsFor: 'transaction' stamp: 'nm 7/2/2018 01:12'!commit session commit! ! CustomerSystem subclass: #TransientCustomerSystem instanceVariableNames: 'customers' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !TransientCustomerSystem methodsFor: 'initialization' stamp: 'HernanWilkinson 11/4/2016 09:41'!initialize customers := OrderedCollection new! ! !TransientCustomerSystem methodsFor: 'transaction' stamp: 'HernanWilkinson 11/4/2016 09:39'!beginTransaction ! ! !TransientCustomerSystem methodsFor: 'transaction' stamp: 'HernanWilkinson 11/4/2016 09:39'!commit ! ! !TransientCustomerSystem methodsFor: 'system live cycle' stamp: 'HernanWilkinson 11/4/2016 09:52'!shutdown ! ! !TransientCustomerSystem methodsFor: 'system live cycle' stamp: 'HernanWilkinson 11/4/2016 09:51'!start ! ! !TransientCustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/4/2016 09:40'!customerIdentifiedAs: anIdentifycationType numbered: anIdentificationNumber ^customers detect: [ :aCustomer | aCustomer isIdentifiedAs: anIdentifycationType numbered: anIdentificationNumber ]! ! !TransientCustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/4/2016 09:40'!customersIsEmpty ^ customers isEmpty ! ! !TransientCustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/4/2016 09:39'!allCustomers ^ customers copy! ! !TransientCustomerSystem methodsFor: 'customers' stamp: 'HernanWilkinson 11/4/2016 09:39'!add: aCustomer customers add: aCustomer! ! SupplierSystem subclass: #TransientSupplierSystem instanceVariableNames: 'suppliers' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-Model'! !TransientSupplierSystem methodsFor: 'adding' stamp: 'RominaYalovetzky 6/30/2018 15:32'!add: aSupplier suppliers add: aSupplier.! ! !TransientSupplierSystem methodsFor: 'initialization' stamp: 'RominaYalovetzky 6/30/2018 15:33'!initialize suppliers := OrderedCollection new! ! !TransientSupplierSystem methodsFor: 'as yet unclassified' stamp: 'nm 7/2/2018 00:52'!suppliersIsEmpty ^ suppliers isEmpty ! ! !TransientSupplierSystem methodsFor: 'as yet unclassified' stamp: 'nm 6/28/2018 19:41'!beginTransaction! ! !TransientSupplierSystem methodsFor: 'as yet unclassified' stamp: 'nm 6/28/2018 19:41'!start! ! !TransientSupplierSystem methodsFor: 'as yet unclassified' stamp: 'RominaYalovetzky 6/30/2018 15:37'!numberOfSupplier ^ suppliers size. ! ! !TransientSupplierSystem methodsFor: 'as yet unclassified' stamp: 'nm 7/1/2018 20:01'!allSuppliers ^ suppliers copy.! ! !TransientSupplierSystem methodsFor: 'as yet unclassified' stamp: 'nm 7/1/2018 19:45'!supplierIdentifiedAs: anIdentifycationType numbered: anIdentificationNumber ^suppliers detect: [ :aSupplier | aSupplier isIdentifiedAs: anIdentifycationType numbered: anIdentificationNumber ] ifNone: [ self signalNotExistiedCustomer. ]! !
\ No newline at end of file
Object subclass: #ClassMapping instanceVariableNames: 'mappedClass mappings tableName' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-PersistanceModel'! !ClassMapping methodsFor: 'table' stamp: 'HernanWilkinson 10/31/2016 23:25'!tableName
^tableName ! ! !ClassMapping methodsFor: 'mapping - private' stamp: 'HernanWilkinson 11/1/2016 00:40'!mapIdOf: anObject into: record using: aDataBaseSession
| newId |
newId := aDataBaseSession newIdFor: anObject.
anObject instVarNamed: #id put: newId.
record at: #id put: newId! ! !ClassMapping methodsFor: 'mapping - private' stamp: 'HernanWilkinson 11/1/2016 00:43'!unmap: aRecord into: unMappedObject using: aDataBaseSession
mappings do: [ :aMapping | aMapping unmap: aRecord into: unMappedObject using: aDataBaseSession ]! ! !ClassMapping methodsFor: 'mapping - private' stamp: 'HernanWilkinson 11/1/2016 00:40'!mapEmbededOf: anObject into: record
mappings do: [ :aMapping | aMapping embeded: anObject into: record ]! ! !ClassMapping methodsFor: 'mapping - private' stamp: 'HernanWilkinson 11/1/2016 00:40'!mapOneToManyRelationshipsOf: anObject using: aDataBaseSession
mappings do: [ :aMapping | aMapping mapOneToManyRelationshipsOf: anObject using: aDataBaseSession ]! ! !ClassMapping methodsFor: 'mapping - private' stamp: 'HernanWilkinson 11/1/2016 00:43'!unmapIdOf: aRecord into: unMappedObject
unMappedObject instVarNamed: #id put: (aRecord at: #id)! ! !ClassMapping methodsFor: 'initialization' stamp: 'HernanWilkinson 10/31/2016 23:25'!initializeFor: aClass into: aTableName mappingAll: aCollectionOfMappings
mappedClass := aClass.
tableName := aTableName.
mappings := aCollectionOfMappings ! ! !ClassMapping methodsFor: 'testing' stamp: 'HernanWilkinson 10/31/2016 23:02'!isFor: aClass
^mappedClass = aClass! ! !ClassMapping methodsFor: 'mapping' stamp: 'HernanWilkinson 11/1/2016 00:42'!unmap: aRecord using: aDataBaseSession
| unMappedObject |
unMappedObject := mappedClass basicNew.
self unmapIdOf: aRecord into: unMappedObject.
self unmap: aRecord into: unMappedObject using: aDataBaseSession.
^ unMappedObject! ! !ClassMapping methodsFor: 'mapping' stamp: 'HernanWilkinson 11/1/2016 00:40'!map: anObject using: aDataBaseSession
| record |
self toDo: 'se puede optimizar usando array para registros y guardando definicion de tabla una vez'.
record := Dictionary new.
self mapIdOf: anObject into: record using: aDataBaseSession.
self mapEmbededOf: anObject into: record.
"agrego aca el registro y no luego de mapear el id para que lo agrege completo. Lo agrego antes de mapear las rel one to many
porque si usuara una db de verdad habria foreign key constrain"
aDataBaseSession add: record on: self tableName.
self mapOneToManyRelationshipsOf: anObject using: aDataBaseSession! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassMapping class instanceVariableNames: ''! !ClassMapping class methodsFor: 'assertions' stamp: 'HernanWilkinson 10/31/2016 19:26'!assertValidMappings: aCollectionOfMappings for: aClass
self toDo: 'Lo mejor seria recolectar todos los erroes de mapeo y no parar en el primero'.
aCollectionOfMappings do: [ :aMapping | aMapping assertIsValidFor: aClass ]
! ! !ClassMapping class methodsFor: 'assertions' stamp: 'HernanWilkinson 10/31/2016 23:41'!assertValidTableName: aTableName
aTableName trimBoth isEmpty ifTrue: [ self error: 'Table name can not be empty' ]! ! !ClassMapping class methodsFor: 'assertions' stamp: 'HernanWilkinson 10/31/2016 21:15'!assertHasIdInstanceVariable: aClass
(aClass hasInstVarNamed: #id) ifFalse: [ self error: ('<1s> has no id instance variable' expandMacrosWith: aClass name) ]! ! !ClassMapping class methodsFor: 'instance creation' stamp: 'HernanWilkinson 11/1/2016 00:44'!defaultTableNameFor: aClass
^aClass name asString! ! !ClassMapping class methodsFor: 'instance creation' stamp: 'HernanWilkinson 10/31/2016 23:24'!for: aClass into: aTableName mappingAll: aCollectionOfMappings
self assertValidTableName: aTableName.
self assertHasIdInstanceVariable: aClass.
self assertValidMappings: aCollectionOfMappings for: aClass.
^self new initializeFor: aClass into: aTableName mappingAll: aCollectionOfMappings
! ! !ClassMapping class methodsFor: 'instance creation' stamp: 'HernanWilkinson 10/31/2016 23:23'!withDefaultTableNameFor: aClass mappingAll: aCollectionOfMappings
^self for: aClass into: (self defaultTableNameFor: aClass) mappingAll: aCollectionOfMappings
! ! Object subclass: #DataBaseSession instanceVariableNames: 'configuration tables id cache' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-PersistanceModel'! !DataBaseSession methodsFor: 'selecting' stamp: 'HernanWilkinson 10/31/2016 22:17'!selectAllOfType: aClass
^self select: [ :anObject | true ] ofType: aClass! ! !DataBaseSession methodsFor: 'selecting' stamp: 'HernanWilkinson 11/1/2016 01:26'!select: aCondition ofType: aClass
| mapper table |
self assertInTransaction.
self delay.
mapper := self mapperFor: aClass.
table := tables at: mapper tableName ifAbsent: [ ^ #() ].
^ table inject: OrderedCollection new into: [ :selected :record | self addInto: selected theOnesThatHold: aCondition unmapping: record with: mapper ]! ! !DataBaseSession methodsFor: 'selecting' stamp: 'HernanWilkinson 11/1/2016 01:15'!objectIdentifiedAs: anId ofType: aClass
self assertInTransaction.
self delay.
^ cache at: anId ifAbsentPut: [ self unmapRecordIdentifiedAs: anId ofType: aClass ]! ! !DataBaseSession methodsFor: 'initialization' stamp: 'HernanWilkinson 10/31/2016 22:55'!initializeFor: aConfiguration
configuration := aConfiguration.
id := 0.
tables := nil.
cache := nil.! ! !DataBaseSession methodsFor: 'persistence - private' stamp: 'HernanWilkinson 10/28/2016 16:41'!delay
(Delay forMilliseconds: 100) wait! ! !DataBaseSession methodsFor: 'persistence - private' stamp: 'HernanWilkinson 10/28/2016 16:35'!defineIdOf: anObject
anObject instVarNamed: 'id' put: (self newIdFor: anObject).! ! !DataBaseSession methodsFor: 'mapping - private' stamp: 'HernanWilkinson 11/1/2016 01:16'!unmapRecordIdentifiedAs: anId ofType: aClass
| record table mapper |
mapper := self mapperFor: aClass.
table := self tableNamed: mapper tableName.
record := table at: id ifAbsent: [ self error: ('Object identified as <1s> does not exist' expandMacrosWith: anId printString) ].
^ mapper unmap: record using: self! ! !DataBaseSession methodsFor: 'mapping - private' stamp: 'HernanWilkinson 11/1/2016 01:15'!relatedOfType: aRelatedClass for: anOwner
| table relatedIds |
table := self relationTableFor: anOwner class relatedTo: aRelatedClass.
relatedIds := table at: (self idOf: anOwner) ifAbsent: [ ^#() ].
^relatedIds collect: [ :aRelatedId | self objectIdentifiedAs: aRelatedId ofType: aRelatedClass ]
! ! !DataBaseSession methodsFor: 'mapping - private' stamp: 'HernanWilkinson 11/1/2016 01:14'!mapperFor: aClass
self toDo: 'se puede mejorar performanco usando un dictionary'.
^configuration
detect: [ :aClassMapper | aClassMapper isFor: aClass ]
ifNone: [ self error: ('There is no mapper for <1s>' expandMacrosWith: aClass name) ]! ! !DataBaseSession methodsFor: 'id' stamp: 'HernanWilkinson 11/1/2016 01:00'!idOf: anObject
^anObject instVarNamed: #id! ! !DataBaseSession methodsFor: 'id' stamp: 'HernanWilkinson 10/28/2016 16:35'!newIdFor: anObject
id := id + 1.
^id! ! !DataBaseSession methodsFor: 'id' stamp: 'HernanWilkinson 11/1/2016 01:04'!recordId: aRecord
^aRecord at: #id! ! !DataBaseSession methodsFor: 'persistance' stamp: 'HernanWilkinson 11/1/2016 01:28'!persist: anObject
| mapper |
self assertInTransaction.
self delay.
mapper := self mapperFor: anObject class.
mapper map: anObject using: self.
self addToCache: anObject ! ! !DataBaseSession methodsFor: 'open/close' stamp: 'HernanWilkinson 11/4/2016 09:52'!shutdown
self assertIsOpen.
tables := nil! ! !DataBaseSession methodsFor: 'open/close' stamp: 'HernanWilkinson 10/31/2016 18:37'!assertIsClose
tables isNil ifFalse: [ self error: 'Session must be close' ]! ! !DataBaseSession methodsFor: 'open/close' stamp: 'HernanWilkinson 11/4/2016 09:51'!start
self assertIsClose.
tables := Dictionary new.
! ! !DataBaseSession methodsFor: 'open/close' stamp: 'HernanWilkinson 10/31/2016 18:36'!assertIsOpen
tables isNil ifTrue: [ self error: 'Session must be open to colaborate with it' ]! ! !DataBaseSession methodsFor: 'selecting - private' stamp: 'HernanWilkinson 11/1/2016 01:28'!addInto: selected theOnesThatHold: aCondition unmapping: record with: mapper
| recordId aClassInstance |
recordId := self recordId: record.
aClassInstance := cache at: recordId ifAbsent: [ mapper unmap: record using: self ].
(aCondition value: aClassInstance) ifTrue: [
self addToCache: aClassInstance.
selected add: aClassInstance ].
^ selected! ! !DataBaseSession methodsFor: 'transaction management' stamp: 'HernanWilkinson 10/31/2016 22:57'!beginTransaction
self assertIsOpen.
self assertNotInTransasction.
cache := WeakKeyDictionary new.
! ! !DataBaseSession methodsFor: 'transaction management' stamp: 'HernanWilkinson 10/31/2016 22:55'!assertInTransaction
cache isNil ifTrue: [ self error: 'There is no transaction currently' ]! ! !DataBaseSession methodsFor: 'transaction management' stamp: 'HernanWilkinson 10/31/2016 22:55'!assertNotInTransasction
cache notNil ifTrue: [ self error: 'There is an open transaction already' ]! ! !DataBaseSession methodsFor: 'transaction management' stamp: 'HernanWilkinson 10/31/2016 22:57'!commit
self assertInTransaction.
cache := nil! ! !DataBaseSession methodsFor: 'tables - private' stamp: 'HernanWilkinson 11/1/2016 01:12'!relationTableFor: anOwnerClass relatedTo: aRelatedClass
| relationTableName table |
relationTableName := self relationTableNameOwnedBy: anOwnerClass relatedTo: aRelatedClass.
table := self tableNamed: relationTableName.
^ table! ! !DataBaseSession methodsFor: 'tables - private' stamp: 'HernanWilkinson 11/1/2016 01:12'!relationTableNameOwnedBy: anOwnerClass relatedTo: aRelatedClass
| ownerClassMapper relatedClassMapper |
ownerClassMapper := self mapperFor: anOwnerClass.
relatedClassMapper := self mapperFor: aRelatedClass.
^ownerClassMapper tableName,'_', relatedClassMapper tableName asPlural.! ! !DataBaseSession methodsFor: 'tables - private' stamp: 'HernanWilkinson 11/1/2016 00:48'!tableNamed: aTableName
^ tables at: aTableName ifAbsentPut: [ Dictionary new ]! ! !DataBaseSession methodsFor: 'adding - private' stamp: 'HernanWilkinson 11/1/2016 01:00'!signalRelationAlreadyExistBetween: anOwner and: aRelated
self error: ('Relation between id <1s> of type <2s> and id <3s> of type <4s> already exist'
expandMacrosWith: (self idOf: anOwner) printString
with: anOwner class name
with: (self idOf: aRelated) printString
with: aRelated class name)! ! !DataBaseSession methodsFor: 'adding - private' stamp: 'HernanWilkinson 11/1/2016 01:27'!addToCache: anObject
cache at: (self idOf: anObject) put: anObject ! ! !DataBaseSession methodsFor: 'adding - private' stamp: 'HernanWilkinson 11/1/2016 01:03'!addRelated: aRelated ownedBy: anOwner
| relatedIds relatedId |
relatedIds := self relatedIdsOwnedBy: anOwner forType: aRelated class.
relatedId := aRelated instVarNamed: #id.
self assertRelationOwnedBy: anOwner isUniqueFor: aRelated identifiedAs: relatedId in: relatedIds.
relatedIds add: relatedId! ! !DataBaseSession methodsFor: 'adding - private' stamp: 'HernanWilkinson 11/1/2016 01:10'!relatedIdsOwnedBy: anOwner forType: aRelatedClass
| relatedIds table |
table := self relationTableFor: anOwner class relatedTo: aRelatedClass.
relatedIds := self relatedIdOwnedBy: anOwner on: table.
^ relatedIds! ! !DataBaseSession methodsFor: 'adding - private' stamp: 'HernanWilkinson 11/1/2016 01:03'!add: aRecord on: aTableName
| table existingRecord |
table := self tableNamed: aTableName.
existingRecord := table at: (self recordId: aRecord) ifAbsentPut: [ aRecord ].
existingRecord == aRecord ifFalse: [ self error: 'Duplicated primary key' ]! ! !DataBaseSession methodsFor: 'adding - private' stamp: 'HernanWilkinson 11/1/2016 01:05'!assertRelationOwnedBy: anOwner isUniqueFor: aRelated identifiedAs: relatedId in: relatedIds
(relatedIds includes: relatedId) ifTrue: [ self signalRelationAlreadyExistBetween: anOwner and: aRelated ]! ! !DataBaseSession methodsFor: 'adding - private' stamp: 'HernanWilkinson 11/1/2016 01:06'!relatedIdOwnedBy: anOwner on: table
^ table at: (self idOf: anOwner) ifAbsentPut: [ Set new ]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DataBaseSession class instanceVariableNames: ''! !DataBaseSession class methodsFor: 'instance creation' stamp: 'HernanWilkinson 10/28/2016 13:07'!for: aConfiguration
^self new initializeFor: aConfiguration! ! Object subclass: #Mapping instanceVariableNames: 'instanceVariableName' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-PersistanceModel'! !Mapping methodsFor: 'assertions' stamp: 'HernanWilkinson 11/1/2016 01:31'!assertIsValidFor: aClass
(aClass hasInstVarNamed: instanceVariableName) ifFalse: [
self error: ('Invalid mapping for <1s> in class <2s>' expandMacrosWith: instanceVariableName with: aClass name) ] ! ! !Mapping methodsFor: 'mapping' stamp: 'HernanWilkinson 10/31/2016 23:26'!unmap: aRecord into: anObject using: aDataBaseSession
self subclassResponsibility! ! !Mapping methodsFor: 'mapping' stamp: 'HernanWilkinson 10/31/2016 23:26'!embeded: anObject into: aRecord
self subclassResponsibility! ! !Mapping methodsFor: 'mapping' stamp: 'HernanWilkinson 10/31/2016 23:26'!mapOneToManyRelationshipsOf: anObject using: aDataBaseSession
self subclassResponsibility! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Mapping class instanceVariableNames: ''! !Mapping class methodsFor: 'assertions' stamp: 'HernanWilkinson 10/31/2016 23:41'!assertValidFieldName: aFieldName
aFieldName trimBoth isEmpty ifTrue: [ self error: 'Field name can not be empty' ]! ! !Mapping class methodsFor: 'instance creation' stamp: 'HernanWilkinson 11/1/2016 01:32'!defaultFieldNameFor: anInstanceVariableName
^anInstanceVariableName asString! ! Mapping subclass: #EmbededMapping instanceVariableNames: 'fieldName' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-PersistanceModel'! !EmbededMapping methodsFor: 'initialization' stamp: 'HernanWilkinson 10/31/2016 23:30'!initializeFor: anInstanceVariableName into: aFieldName
instanceVariableName := anInstanceVariableName.
fieldName := aFieldName ! ! !EmbededMapping methodsFor: 'mapping' stamp: 'HernanWilkinson 10/31/2016 23:31'!unmap: aRecord into: anObject using: aDataBaseSession
anObject instVarNamed: instanceVariableName put: (aRecord at: fieldName)! ! !EmbededMapping methodsFor: 'mapping' stamp: 'HernanWilkinson 10/31/2016 23:31'!embeded: anObject into: aRecord
aRecord at: fieldName put: (anObject instVarNamed: instanceVariableName) ! ! !EmbededMapping methodsFor: 'mapping' stamp: 'HernanWilkinson 10/31/2016 21:23'!mapOneToManyRelationshipsOf: anObject using: aDataBaseSession
! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EmbededMapping class instanceVariableNames: ''! !EmbededMapping class methodsFor: 'instance creation' stamp: 'HernanWilkinson 10/31/2016 23:30'!for: anInstanceVariableName into: aFieldName
^self new initializeFor: anInstanceVariableName into: aFieldName ! ! !EmbededMapping class methodsFor: 'instance creation' stamp: 'HernanWilkinson 10/31/2016 23:29'!withDefaultFieldNameFor: anInstanceVariableName
^self for: anInstanceVariableName into: (self defaultFieldNameFor: anInstanceVariableName)! ! Mapping subclass: #OneToManyMapping instanceVariableNames: 'relatedType fieldName' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-PersistanceModel'! !OneToManyMapping methodsFor: 'mapping' stamp: 'HernanWilkinson 11/1/2016 01:37'!unmap: aRecord into: anObject using: aDataBaseSession
| newCollection related |
related := aDataBaseSession relatedOfType: relatedType for: anObject.
newCollection := self createRelationCollectionOn: aDataBaseSession ownedBy: anObject.
newCollection addAllNotPersisting: related.
anObject instVarNamed: instanceVariableName put: newCollection! ! !OneToManyMapping methodsFor: 'mapping' stamp: 'HernanWilkinson 10/31/2016 21:16'!embeded: anObject into: aRecord
! ! !OneToManyMapping methodsFor: 'mapping' stamp: 'HernanWilkinson 11/1/2016 01:37'!mapOneToManyRelationshipsOf: anObject using: aDataBaseSession
| oldCollection newCollection |
newCollection := self createRelationCollectionOn: aDataBaseSession ownedBy: anObject.
oldCollection := anObject instVarNamed: instanceVariableName.
newCollection addAll: oldCollection.
anObject instVarNamed: instanceVariableName put: newCollection! ! !OneToManyMapping methodsFor: 'mapping' stamp: 'HernanWilkinson 11/1/2016 01:35'!createRelationCollectionOn: aDataBaseSession ownedBy: anObject
^ OneToManySet on: aDataBaseSession ownedBy: anObject! ! !OneToManyMapping methodsFor: 'initialization' stamp: 'HernanWilkinson 10/31/2016 23:34'!initializeFor: anInstanceVariableName into: aFieldName ofType: aClass
instanceVariableName := anInstanceVariableName.
fieldName := aFieldName.
relatedType := aClass ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! OneToManyMapping class instanceVariableNames: ''! !OneToManyMapping class methodsFor: 'instance creation' stamp: 'HernanWilkinson 10/31/2016 23:32'!withDefaultFieldNameFor: anInstanceVariableName ofType: aClass
^self for: anInstanceVariableName into: (self defaultFieldNameFor: anInstanceVariableName) ofType: aClass! ! !OneToManyMapping class methodsFor: 'instance creation' stamp: 'HernanWilkinson 10/31/2016 23:40'!for: anInstanceVariableName into: aFieldName ofType: aClass
self assertValidFieldName: aFieldName.
^self new initializeFor: anInstanceVariableName into: aFieldName ofType: aClass! ! Set subclass: #OneToManySet instanceVariableNames: 'session owner' classVariableNames: '' poolDictionaries: '' category: 'IS1-CustomerImport-PersistanceModel'! !OneToManySet methodsFor: 'adding' stamp: 'HernanWilkinson 11/1/2016 00:03'!addAllNotPersisting: aCollection
^aCollection do: [ :anObjectToAdd | super add: anObjectToAdd ]! ! !OneToManySet methodsFor: 'adding' stamp: 'HernanWilkinson 11/1/2016 00:11'!add: anObject
session persist: anObject.
session addRelated: anObject ownedBy: owner.
super add: anObject.
! ! !OneToManySet methodsFor: 'removing' stamp: 'HernanWilkinson 10/31/2016 21:35'!remove: anObject ifAbsent: anAbsentBlock
self shouldBeImplemented ! ! !OneToManySet methodsFor: 'initialization' stamp: 'HernanWilkinson 11/1/2016 00:11'!initializeOn: aDataBaseSession ownedBy: anOwner
session := aDataBaseSession.
owner := anOwner ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! OneToManySet class instanceVariableNames: ''! !OneToManySet class methodsFor: 'instance creation' stamp: 'HernanWilkinson 11/1/2016 00:11'!on: aDataBaseSession ownedBy: anOwner
^self new initializeOn: aDataBaseSession ownedBy: anOwner ! !
\ No newline at end of file
'From Pharo6.0 of 13 May 2016 [Latest update: #60540] on 2 July 2018 at 4:04:16.515101 pm'! !String methodsFor: '*IS1-CustomerImport' stamp: 'HernanWilkinson 10/31/2016 23:57'!asPlural
^self last = $s
ifTrue: [ self, 'es' ]
ifFalse: [ self, 's' ]! !'From Pharo6.0 of 13 May 2016 [Latest update: #60540] on 2 July 2018 at 4:04:16.517101 pm'! !Object methodsFor: '*IS1-CustomerImport' stamp: 'HernanWilkinson 10/31/2016 19:27'!toDo: aString
! !
\ No newline at end of file
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