Ver código fonte

- New #copyClass:named: method in CLassBuilder
- New button 'copy class' in the class browser
- Fixed wrong indenting of SourceArea

Nicolas Petton 12 anos atrás
pai
commit
7554167b6e
6 arquivos alterados com 1072 adições e 4 exclusões
  1. 1 1
      js/IDE.deploy.js
  2. 1 1
      js/IDE.js
  3. 362 0
      js/Kernel.deploy.js
  4. 486 0
      js/Kernel.js
  5. 15 2
      st/IDE.st
  6. 207 0
      st/Kernel.st

Diferenças do arquivo suprimidas por serem muito extensas
+ 1 - 1
js/IDE.deploy.js


Diferenças do arquivo suprimidas por serem muito extensas
+ 1 - 1
js/IDE.js


+ 362 - 0
js/Kernel.deploy.js

@@ -5316,6 +5316,23 @@ return self;}
 }),
 smalltalk.ClassBuilder);
 
+smalltalk.addMethod(
+'_copyClass_named_',
+smalltalk.method({
+selector: 'copyClass:named:',
+fn: function (aClass, aString){
+var self=this;
+var newClass=nil;
+newClass=smalltalk.send(self, "_addSubclassOf_named_instanceVariableNames_package_", [smalltalk.send(aClass, "_superclass", []), aString, smalltalk.send(aClass, "_instanceVariableNames", []), smalltalk.send(smalltalk.send(aClass, "_package", []), "_name", [])]);
+smalltalk.send(self, "_setupClass_", [newClass]);
+smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_methodDictionary", []), "_values", []), "_do_", [(function(each){smalltalk.send(newClass, "_addCompiledMethod_", [smalltalk.send(smalltalk.send((smalltalk.Compiler || Compiler), "_new", []), "_load_forClass_", [smalltalk.send(each, "_source", []), newClass])]);return smalltalk.send(smalltalk.send(smalltalk.send(newClass, "_methodDictionary", []), "_at_", [smalltalk.send(each, "_selector", [])]), "_category_", [smalltalk.send(each, "_category", [])]);})]);
+smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_methodDictionary", []), "_values", []), "_do_", [(function(each){smalltalk.send(smalltalk.send(newClass, "_class", []), "_addCompiledMethod_", [smalltalk.send(smalltalk.send((smalltalk.Compiler || Compiler), "_new", []), "_load_forClass_", [smalltalk.send(each, "_source", []), smalltalk.send(newClass, "_class", [])])]);return smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(newClass, "_class", []), "_methodDictionary", []), "_at_", [smalltalk.send(each, "_selector", [])]), "_category_", [smalltalk.send(each, "_category", [])]);})]);
+smalltalk.send(self, "_setupClass_", [newClass]);
+return newClass;
+return self;}
+}),
+smalltalk.ClassBuilder);
+
 
 
 smalltalk.addClass('ClassCategoryReader', smalltalk.Object, ['class', 'category', 'chunkParser'], 'Kernel');
@@ -6521,3 +6538,348 @@ return self;}
 smalltalk.ConsoleTranscript.klass);
 
 
+smalltalk.addClass('Dictionary2', smalltalk.Dictionary, ['keys'], 'Kernel');
+smalltalk.addMethod(
+'__eq',
+smalltalk.method({
+selector: '=',
+fn: function (aDictionary){
+var self=this;
+try{((($receiver = smalltalk.send(smalltalk.send(self, "_class", []), "__eq", [smalltalk.send(aDictionary, "_class", [])])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return (function(){throw({name: 'stReturn', selector: '__eq', fn: function(){return false}})})();})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return (function(){throw({name: 'stReturn', selector: '__eq', fn: function(){return false}})})();})]));
+((($receiver = smalltalk.send(smalltalk.send(self, "_size", []), "__eq", [smalltalk.send(aDictionary, "_size", [])])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return (function(){throw({name: 'stReturn', selector: '__eq', fn: function(){return false}})})();})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return (function(){throw({name: 'stReturn', selector: '__eq', fn: function(){return false}})})();})]));
+(function(){throw({name: 'stReturn', selector: '__eq', fn: function(){return smalltalk.send(smalltalk.send(self, "_associations", []), "__eq", [smalltalk.send(aDictionary, "_associations", [])])}})})();
+return self;
+} catch(e) {if(e.name === 'stReturn' && e.selector === '__eq'){return e.fn()} throw(e)}}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_shallowCopy',
+smalltalk.method({
+selector: 'shallowCopy',
+fn: function (){
+var self=this;
+var copy=nil;
+copy=smalltalk.send(smalltalk.send(self, "_class", []), "_new", []);
+smalltalk.send(self, "_associationsDo_", [(function(each){return smalltalk.send(copy, "_at_put_", [smalltalk.send(each, "_key", []), smalltalk.send(each, "_value", [])]);})]);
+return copy;
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_initialize',
+smalltalk.method({
+selector: 'initialize',
+fn: function (){
+var self=this;
+smalltalk.send(self, "_initialize", [], smalltalk.Dictionary);
+self['@keys']=[];
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_size',
+smalltalk.method({
+selector: 'size',
+fn: function (){
+var self=this;
+return smalltalk.send(self['@keys'], "_size", []);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_associations',
+smalltalk.method({
+selector: 'associations',
+fn: function (){
+var self=this;
+var associations=nil;
+associations=[];
+smalltalk.send(self['@keys'], "_do_", [(function(each){return smalltalk.send(associations, "_add_", [smalltalk.send((smalltalk.Association || Association), "_key_value_", [each, smalltalk.send(self, "_at_", [each])])]);})]);
+return associations;
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_keys',
+smalltalk.method({
+selector: 'keys',
+fn: function (){
+var self=this;
+return smalltalk.send(self['@keys'], "_copy", []);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_values',
+smalltalk.method({
+selector: 'values',
+fn: function (){
+var self=this;
+return smalltalk.send(self['@keys'], "_collect_", [(function(each){return smalltalk.send(self, "_at_", [each]);})]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_at_put_',
+smalltalk.method({
+selector: 'at:put:',
+fn: function (aKey, aValue){
+var self=this;
+((($receiver = smalltalk.send(self['@keys'], "_includes_", [aKey])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self['@keys'], "_add_", [aKey]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self['@keys'], "_add_", [aKey]);})]));
+return smalltalk.send(self, "_basicAt_put_", [aKey, aValue]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_at_ifAbsent_',
+smalltalk.method({
+selector: 'at:ifAbsent:',
+fn: function (aKey, aBlock){
+var self=this;
+return smalltalk.send(smalltalk.send(smalltalk.send(self, "_keys", []), "_includes_", [aKey]), "_ifTrue_ifFalse_", [(function(){return smalltalk.send(self, "_basicAt_", [aKey]);}), aBlock]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_at_ifAbsentPut_',
+smalltalk.method({
+selector: 'at:ifAbsentPut:',
+fn: function (aKey, aBlock){
+var self=this;
+return smalltalk.send(self, "_at_ifAbsent_", [aKey, (function(){return smalltalk.send(self, "_at_put_", [aKey, smalltalk.send(aBlock, "_value", [])]);})]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_at_ifPresent_',
+smalltalk.method({
+selector: 'at:ifPresent:',
+fn: function (aKey, aBlock){
+var self=this;
+return (($receiver = smalltalk.send(self, "_basicAt_", [aKey])) != nil && $receiver != undefined) ? (function(){return smalltalk.send(aBlock, "_value_", [smalltalk.send(self, "_at_", [aKey])]);})() : nil;
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_at_ifPresent_ifAbsent_',
+smalltalk.method({
+selector: 'at:ifPresent:ifAbsent:',
+fn: function (aKey, aBlock, anotherBlock){
+var self=this;
+return smalltalk.send(smalltalk.send(self, "_basicAt_", [aKey]), "_ifNil_ifNotNil_", [anotherBlock, (function(){return smalltalk.send(aBlock, "_value_", [smalltalk.send(self, "_at_", [aKey])]);})]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_add_',
+smalltalk.method({
+selector: 'add:',
+fn: function (anAssociation){
+var self=this;
+smalltalk.send(self, "_at_put_", [smalltalk.send(anAssociation, "_key", []), smalltalk.send(anAssociation, "_value", [])]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_addAll_',
+smalltalk.method({
+selector: 'addAll:',
+fn: function (aDictionary){
+var self=this;
+smalltalk.send(self, "_addAll_", [smalltalk.send(aDictionary, "_associations", [])], smalltalk.Dictionary);
+return aDictionary;
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'__comma',
+smalltalk.method({
+selector: ',',
+fn: function (aCollection){
+var self=this;
+smalltalk.send(self, "_shouldNotImplement", []);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_copyFrom_to_',
+smalltalk.method({
+selector: 'copyFrom:to:',
+fn: function (anIndex, anotherIndex){
+var self=this;
+smalltalk.send(self, "_shouldNotImplement", []);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_associationsDo_',
+smalltalk.method({
+selector: 'associationsDo:',
+fn: function (aBlock){
+var self=this;
+smalltalk.send(smalltalk.send(self, "_associations", []), "_do_", [aBlock]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_keysAndValuesDo_',
+smalltalk.method({
+selector: 'keysAndValuesDo:',
+fn: function (aBlock){
+var self=this;
+smalltalk.send(self, "_associationsDo_", [(function(each){return smalltalk.send(aBlock, "_value_value_", [smalltalk.send(each, "_key", []), smalltalk.send(each, "_value", [])]);})]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_do_',
+smalltalk.method({
+selector: 'do:',
+fn: function (aBlock){
+var self=this;
+smalltalk.send(smalltalk.send(self, "_values", []), "_do_", [aBlock]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_select_',
+smalltalk.method({
+selector: 'select:',
+fn: function (aBlock){
+var self=this;
+var newDict=nil;
+newDict=smalltalk.send(smalltalk.send(self, "_class", []), "_new", []);
+smalltalk.send(self, "_keysAndValuesDo_", [(function(key, value){return ((($receiver = smalltalk.send(aBlock, "_value_", [value])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(newDict, "_at_put_", [key, value]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return smalltalk.send(newDict, "_at_put_", [key, value]);})]));})]);
+return newDict;
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_collect_',
+smalltalk.method({
+selector: 'collect:',
+fn: function (aBlock){
+var self=this;
+var newDict=nil;
+newDict=smalltalk.send(smalltalk.send(self, "_class", []), "_new", []);
+smalltalk.send(self, "_keysAndValuesDo_", [(function(key, value){return smalltalk.send(newDict, "_at_put_", [key, smalltalk.send(aBlock, "_value_", [value])]);})]);
+return newDict;
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_detect_ifNone_',
+smalltalk.method({
+selector: 'detect:ifNone:',
+fn: function (aBlock, anotherBlock){
+var self=this;
+return smalltalk.send(smalltalk.send(self, "_values", []), "_detect_ifNone_", [aBlock, anotherBlock]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_includes_',
+smalltalk.method({
+selector: 'includes:',
+fn: function (anObject){
+var self=this;
+return smalltalk.send(smalltalk.send(self, "_values", []), "_includes_", [anObject]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_remove_',
+smalltalk.method({
+selector: 'remove:',
+fn: function (aKey){
+var self=this;
+smalltalk.send(self, "_removeKey_", [aKey]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_removeKey_',
+smalltalk.method({
+selector: 'removeKey:',
+fn: function (aKey){
+var self=this;
+smalltalk.send(self['@keys'], "_remove_", [aKey]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_at_',
+smalltalk.method({
+selector: 'at:',
+fn: function (aKey){
+var self=this;
+return smalltalk.send(self, "_at_ifAbsent_", [aKey, (function(){return smalltalk.send(self, "_errorNotFound", []);})]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_asJSONObject',
+smalltalk.method({
+selector: 'asJSONObject',
+fn: function (){
+var self=this;
+var object=nil;
+object=smalltalk.send((smalltalk.Object || Object), "_new", []);
+smalltalk.send(self, "_keysAndValuesDo_", [(function(key, value){return smalltalk.send(object, "_basicAt_put_", [key, smalltalk.send(value, "_asJSONObject", [])]);})]);
+return object;
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_printString',
+smalltalk.method({
+selector: 'printString',
+fn: function (){
+var self=this;
+return smalltalk.send((smalltalk.String || String), "_streamContents_", [(function(aStream){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_printString", [], smalltalk.Dictionary)]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%28")]);})(aStream);smalltalk.send(smalltalk.send(self, "_associations", []), "_do_separatedBy_", [(function(anAssociation){return (function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(anAssociation, "_key", []), "_printString", [])]);smalltalk.send($rec, "_nextPutAll_", [unescape("%20-%3E%20")]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(anAssociation, "_value", []), "_printString", [])]);})(aStream);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%20%2C%20")]);})]);return smalltalk.send(aStream, "_nextPutAll_", [unescape("%29")]);})]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+smalltalk.addMethod(
+'_storeOn_',
+smalltalk.method({
+selector: 'storeOn:',
+fn: function (aStream){
+var self=this;
+smalltalk.send(aStream, "_nextPutAll_", [unescape("%23%7B")]);
+smalltalk.send(smalltalk.send(self, "_associations", []), "_do_separatedBy_", [(function(each){return smalltalk.send(each, "_storeOn_", [aStream]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [". "]);})]);
+smalltalk.send(aStream, "_nextPutAll_", [unescape("%7D")]);
+return self;}
+}),
+smalltalk.Dictionary2);
+
+
+

Diferenças do arquivo suprimidas por serem muito extensas
+ 486 - 0
js/Kernel.js


+ 15 - 2
st/IDE.st

@@ -1,5 +1,4 @@
 Smalltalk current createPackage: 'IDE' properties: #{}!
-
 Widget subclass: #TabManager
 	instanceVariableNames: 'selectedTab tabs opened ul input'
 	category: 'IDE'!
@@ -762,6 +761,17 @@ addNewClass
 			resetClassesList;
 			updateClassesList.
 		self selectClass: (Smalltalk current at: className)]
+!
+
+copyClass
+	| className |
+	className := window prompt: 'Copy class'.
+	(className notNil and: [className notEmpty]) ifTrue: [
+		ClassBuilder new copyClass: self selectedClass named: className.
+          	 self 
+			resetClassesList;
+			updateClassesList.
+		self selectClass: (Smalltalk current at: className)]
 ! !
 
 !Browser methodsFor: 'initialization'!
@@ -948,6 +958,9 @@ updateSourceAndButtons
 		html button
 			with: 'Rename class';
 			onClick: [self renameClass].
+		html button
+			with: 'Copy class';
+			onClick: [self copyClass].
 		html button
 			with: 'Remove class';
 			onClick: [self removeClass].
@@ -1406,7 +1419,7 @@ setEditorOn: aTextarea
 	<self['@editor'] = CodeMirror.fromTextArea(aTextarea, {
 		theme: 'jtalk',
                 lineNumbers: true,
-                enterMode: 'classic',
+                enterMode: 'flat',
                 matchBrackets: true,
                 electricChars: false
 	})>

+ 207 - 0
st/Kernel.st

@@ -2649,6 +2649,29 @@ setupClass: aClass
 addSubclassOf: aClass named: aString instanceVariableNames: aCollection package: packageName
 	<smalltalk.addClass(aString, aClass, aCollection, packageName);
 	    return smalltalk[aString]>
+!
+
+copyClass: aClass named: aString
+	| newClass |
+
+	newClass := self 
+		addSubclassOf: aClass superclass
+		named: aString 
+		instanceVariableNames: aClass instanceVariableNames 
+		package: aClass package name.
+
+	self setupClass: newClass.
+
+	aClass methodDictionary values do: [:each |
+		newClass addCompiledMethod: (Compiler new load: each source forClass: newClass).
+		(newClass methodDictionary at: each selector) category: each category].
+
+	aClass class methodDictionary values do: [:each |
+		newClass class addCompiledMethod: (Compiler new load: each source forClass: newClass class).
+		(newClass class methodDictionary at: each selector) category: each category].
+
+	self setupClass: newClass.
+	^newClass
 ! !
 
 Object subclass: #ClassCategoryReader
@@ -3283,3 +3306,187 @@ initialize
 	Transcript register: self new
 ! !
 
+Dictionary subclass: #Dictionary2
+	instanceVariableNames: 'keys'
+	category: 'Kernel'!
+
+!Dictionary2 methodsFor: 'accessing'!
+
+size
+	^keys size
+!
+
+associations
+	| associations |
+	associations := #().
+	keys do: [:each |
+	    associations add: (Association key: each value: (self at: each))].
+	^associations
+!
+
+keys
+	^keys copy
+!
+
+values
+    	^keys collect: [:each | self at: each]
+!
+
+at: aKey put: aValue
+	(keys includes: aKey) ifFalse: [keys add: aKey].
+	^self basicAt: aKey put: aValue
+!
+
+at: aKey ifAbsent: aBlock
+	^(self keys includes: aKey)
+		ifTrue: [self basicAt: aKey]
+		ifFalse: aBlock
+!
+
+at: aKey ifAbsentPut: aBlock
+    	^self at: aKey ifAbsent: [
+    	    self at: aKey put: aBlock value]
+!
+
+at: aKey ifPresent: aBlock
+	^(self basicAt: aKey) ifNotNil: [aBlock value: (self at: aKey)]
+!
+
+at: aKey ifPresent: aBlock ifAbsent: anotherBlock
+	^(self basicAt: aKey)
+	    ifNil: anotherBlock
+	    ifNotNil: [aBlock value: (self at: aKey)]
+!
+
+at: aKey
+	^self at: aKey ifAbsent: [self errorNotFound]
+! !
+
+!Dictionary2 methodsFor: 'adding/removing'!
+
+add: anAssociation
+    	self at: anAssociation key put: anAssociation value
+!
+
+addAll: aDictionary
+    	super addAll: aDictionary associations.
+    	^aDictionary
+!
+
+remove: aKey
+    self removeKey: aKey
+!
+
+removeKey: aKey
+    keys remove: aKey
+! !
+
+!Dictionary2 methodsFor: 'comparing'!
+
+= aDictionary
+	self class = aDictionary class ifFalse: [^false].
+	self size = aDictionary size ifFalse: [^false].
+	^self associations = aDictionary associations
+! !
+
+!Dictionary2 methodsFor: 'converting'!
+
+asJSONObject
+	| object |
+	object := Object new.
+	self keysAndValuesDo: [:key :value |
+		object basicAt: key put: value asJSONObject].
+	^object
+! !
+
+!Dictionary2 methodsFor: 'copying'!
+
+shallowCopy
+	| copy |
+	copy := self class new.
+	self associationsDo: [:each |
+	    copy at: each key  put: each value].
+	^copy
+!
+
+, aCollection
+	self shouldNotImplement
+!
+
+copyFrom: anIndex to: anotherIndex
+	self shouldNotImplement
+! !
+
+!Dictionary2 methodsFor: 'enumerating'!
+
+associationsDo: aBlock
+    	self associations do: aBlock
+!
+
+keysAndValuesDo: aBlock
+    	self associationsDo: [:each |
+    	    aBlock value: each key value: each value]
+!
+
+do: aBlock
+    	self values do: aBlock
+!
+
+select: aBlock
+    	| newDict |
+    	newDict := self class new.
+    	self keysAndValuesDo: [:key :value |
+    	    (aBlock value: value) ifTrue: [newDict at: key put: value]].
+    	^newDict
+!
+
+collect: aBlock
+    	| newDict |
+    	newDict := self class new.
+    	self keysAndValuesDo: [:key :value |
+    	    newDict at: key put: (aBlock value: value)].
+    	^newDict
+!
+
+detect: aBlock ifNone: anotherBlock
+	^self values detect: aBlock ifNone: anotherBlock
+!
+
+includes: anObject
+	^self values includes: anObject
+! !
+
+!Dictionary2 methodsFor: 'initialization'!
+
+initialize
+    	super initialize.
+    	keys := #()
+! !
+
+!Dictionary2 methodsFor: 'printing'!
+
+printString
+	^ String streamContents: [:aStream|  
+                                  		aStream 
+                                  			nextPutAll: super printString;
+                                  			nextPutAll: '('.
+                                  		self associations 
+                                  			do: [:anAssociation|  
+                                                                      	aStream 
+                                                                      		nextPutAll: anAssociation key printString;
+                                                                      		nextPutAll: ' -> ';
+                                                                      		nextPutAll: anAssociation value printString]
+                                  
+                                 			separatedBy: [aStream nextPutAll: ' , '].
+                                  		aStream nextPutAll: ')'.
+                                 ]
+!
+
+storeOn: aStream
+	aStream nextPutAll: '#{'.
+	self associations
+		do: [:each | each storeOn: aStream]
+		separatedBy: [ aStream nextPutAll: '. '].
+	aStream nextPutAll: '}'
+! !
+

Alguns arquivos não foram mostrados porque muitos arquivos mudaram nesse diff