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

ultima iteracion de customer import

parent 92078e86
This diff is collapsed.
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