Pārlūkot izejas kodu

fix protocol combo box that was not updated on protocol selection. New protocol was broken

Laurent Laffont 12 gadi atpakaļ
vecāks
revīzija
638ae24263
3 mainītis faili ar 1348 papildinājumiem un 1092 dzēšanām
  1. 438 438
      js/IDE.deploy.js
  2. 550 295
      js/IDE.js
  3. 360 359
      st/IDE.st

Failā izmaiņas netiks attēlotas, jo tās ir par lielu
+ 438 - 438
js/IDE.deploy.js


Failā izmaiņas netiks attēlotas, jo tās ir par lielu
+ 550 - 295
js/IDE.js


+ 360 - 359
st/IDE.st

@@ -1,185 +1,295 @@
 Smalltalk current createPackage: 'IDE' properties: #{}!
-ErrorHandler subclass: #DebugErrorHandler
-	instanceVariableNames: ''
-	category: 'IDE'!
-
-!DebugErrorHandler methodsFor: 'error handling'!
-
-handleError: anError
-	[Debugger new
-		error: anError;
-		open] on: Error do: [:error |
-			ErrorHandler new handleError: error]
-! !
-
-!DebugErrorHandler class methodsFor: 'initialization'!
-
-initialize
-	self register
-! !
-
-Widget subclass: #ClassesListNode
-	instanceVariableNames: 'browser theClass level nodes'
+Widget subclass: #TabManager
+	instanceVariableNames: 'selectedTab tabs opened ul input'
 	category: 'IDE'!
 
-!ClassesListNode methodsFor: ''!
-
-renderOn: html
-	| li cssClass |
-	cssClass := ''.
-	li := html li 
-		onClick: [self browser selectClass: self theClass]. 
-	li asJQuery html: self label.
-
-	self browser selectedClass = self theClass ifTrue:  [
-		cssClass := cssClass, ' selected'].
-
-	self theClass comment isEmpty ifFalse: [
-		cssClass := cssClass, ' commented'].
+!TabManager methodsFor: 'accessing'!
 
-	li class: cssClass.
+tabs
+    ^tabs ifNil: [tabs := Array new]
+!
 
-	self nodes do: [:each |
-		each renderOn: html]
+labelFor: aWidget
+	| label maxSize |
+	maxSize := 15.
+	label := aWidget label copyFrom: 0 to: (aWidget label size min: maxSize).
+	aWidget label size > maxSize ifTrue: [
+		label := label, '...'].
+	^label
 ! !
 
-!ClassesListNode methodsFor: 'accessing'!
-
-nodes
-	^nodes
-!
-
-theClass
-	^theClass
-!
+!TabManager methodsFor: 'actions'!
 
-theClass: aClass
-	theClass := aClass
+updateBodyMargin
+    self setBodyMargin: '#jtalk' asJQuery height
 !
 
-browser
-	^browser
+updatePosition
+    <jQuery('#jtalk').css('top', '').css('bottom', '0px')>
 !
 
-browser: aBrowser
-	browser := aBrowser
+removeBodyMargin
+    self setBodyMargin: 0
 !
 
-level
-	^level
+setBodyMargin: anInteger
+    '.jtalkBody' asJQuery css: 'margin-bottom' put: anInteger asString, 'px'
 !
 
-level: anInteger
-	level := anInteger
+onResize: aBlock
+    <jQuery('#jtalk').resizable({
+	handles: 'n', 
+	resize: aBlock,
+	minHeight: 230
+})>
 !
 
-label
-	| str |
-	str := String new writeStream.
-	self level timesRepeat: [
-		str nextPutAll: '&nbsp;&nbsp;&nbsp;&nbsp;'].
-	str nextPutAll: self theClass name.
-	^str contents
+onWindowResize: aBlock
+    <jQuery(window).resize(aBlock)>
 !
 
-getNodesFrom: aCollection
-	| children others |
-	children := #().
-	others := #().
-	aCollection do: [:each |
-		(each superclass = self theClass)
-			ifTrue: [children add: each]
-			ifFalse: [others add: each]].
-	nodes:= children collect: [:each |
-		ClassesListNode on: each browser: self browser classes: others level: self level + 1]
-! !
-
-!ClassesListNode class methodsFor: 'instance creation'!
-
-on: aClass browser: aBrowser classes: aCollection level: anInteger
-	^self new
-		theClass: aClass;
-		browser: aBrowser;
-		level: anInteger;
-		getNodesFrom: aCollection;
-		yourself
-! !
-
-Widget subclass: #ClassesList
-	instanceVariableNames: 'browser ul nodes'
-	category: 'IDE'!
-
-!ClassesList methodsFor: 'accessing'!
-
-category
-	^self browser selectedPackage
+open
+    opened ifFalse: [
+	'body' asJQuery addClass: 'jtalkBody'.
+	'#jtalk' asJQuery show.
+	ul asJQuery show.
+	self updateBodyMargin.
+	selectedTab show.
+	opened := true]
 !
 
-nodes
-	nodes ifNil: [nodes := self getNodes].
-	^nodes
+close
+    opened ifTrue: [
+	'#jtalk' asJQuery hide.
+	ul asJQuery hide.
+	selectedTab hide.
+	self removeBodyMargin.
+	'body' asJQuery removeClass: 'jtalkBody'.
+	opened := false]
 !
 
-browser
-	^browser
+newBrowserTab
+    Browser open
 !
 
-browser: aBrowser
-	browser := aBrowser
+selectTab: aWidget
+    self open.
+    selectedTab := aWidget.
+    self tabs do: [:each |
+	each hide].
+    aWidget show.
+	
+    self update
 !
 
-getNodes
-	| classes children others |
-	classes := self browser classes.
-	children := #().
-	others := #().
-	classes do: [:each |
-		(classes includes: each superclass)
-			ifFalse: [children add: each]
-			ifTrue: [others add: each]].
-	^children collect: [:each |
-		ClassesListNode on: each browser: self browser classes: others level: 0]
+closeTab: aWidget
+    self removeTab: aWidget.
+    self selectTab: self tabs last.
+    aWidget remove.
+    self update
 !
 
-resetNodes
-	nodes := nil
+search: aString
+	| searchedClass |
+	searchedClass := Smalltalk current at: aString.
+		searchedClass isClass
+			ifTrue: [Browser openOn: searchedClass]
+			ifFalse: [ReferencesBrowser search: aString]
 ! !
 
-!ClassesList methodsFor: 'rendering'!
+!TabManager methodsFor: 'adding/Removing'!
 
-renderOn: html
-	ul := html ul
-		class: 'jt_column browser classes';
-		yourself.
-	self updateNodes
+addTab: aWidget
+    self tabs add: aWidget.
+    aWidget appendToJQuery: '#jtalk' asJQuery.
+    aWidget hide
 !
 
-updateNodes
-	ul contents: [:html |
-		self nodes do: [:each |
-			each renderOn: html]]
+removeTab: aWidget
+    self tabs remove: aWidget.
+    self update
 ! !
 
-!ClassesList class methodsFor: 'instance creation'!
+!TabManager methodsFor: 'initialization'!
 
-on: aBrowser
-	^self new 
-		browser: aBrowser; 
-		yourself
+initialize
+    super initialize.
+    opened := true.
+    [:html | html div id: 'jtalk'] appendToJQuery: 'body' asJQuery.
+    'body' asJQuery 
+	addClass: 'jtalkBody'.
+    self appendToJQuery: '#jtalk' asJQuery.
+    self 
+	addTab: IDETranscript current;
+	addTab: Workspace new;
+	addTab: TestRunner new.
+    self selectTab: self tabs last.
+    self 
+	onResize: [self updateBodyMargin; updatePosition];
+	onWindowResize: [self updatePosition]
 ! !
 
-Widget subclass: #SourceArea
-	instanceVariableNames: 'editor div receiver onDoIt'
-	category: 'IDE'!
-
-!SourceArea methodsFor: 'accessing'!
+!TabManager methodsFor: 'rendering'!
 
-val
-    ^editor getValue
+renderOn: html
+	html div id: 'logo'.
+	self renderToolbarOn: html.
+	ul := html ul
+		id: 'jtalkTabs';
+		yourself.
+	self renderTabs
 !
 
-val: aString
-    editor setValue: aString
+renderTabFor: aWidget on: html
+	| li |
+	li := html li.
+	selectedTab = aWidget ifTrue: [
+	li class: 'selected'].
+	li with: [
+		html span class: 'ltab'.
+		html span
+			class: 'mtab';
+			with: [
+				aWidget canBeClosed ifTrue: [
+					html span 
+						class: 'close';
+						with: 'x';
+					onClick: [self closeTab: aWidget]].
+			html span with: (self labelFor: aWidget)].
+		html span class: 'rtab'];
+	onClick: [self selectTab: aWidget]
+!
+
+renderTabs
+	ul contents: [:html |
+	    self tabs do: [:each |
+		self renderTabFor: each on: html].
+	    html li
+		class: 'newtab';
+		with: [
+			html span class: 'ltab'.
+			html span class: 'mtab'; with: ' + '.
+			html span class: 'rtab'];
+		onClick: [self newBrowserTab]]
+!
+
+renderToolbarOn: html
+	html div 
+		id: 'jt_toolbar';
+		with: [
+			input := html input 
+				class: 'implementors';
+				yourself.
+			input onKeyPress: [:event |
+				event keyCode = 13 ifTrue: [
+				self search: input asJQuery val]].
+			html div id: 'jt_close'; onClick: [self close]]
+! !
+
+!TabManager methodsFor: 'updating'!
+
+update
+	self renderTabs
+! !
+
+TabManager class instanceVariableNames: 'current'!
+
+!TabManager class methodsFor: 'instance creation'!
+
+current
+    ^current ifNil: [current := super new]
+!
+
+new
+    self shouldNotImplement
+! !
+
+Widget subclass: #TabWidget
+	instanceVariableNames: 'div'
+	category: 'IDE'!
+
+!TabWidget methodsFor: 'accessing'!
+
+label
+    self subclassResponsibility
+! !
+
+!TabWidget methodsFor: 'actions'!
+
+open
+    TabManager current addTab: self.
+    TabManager current selectTab: self
+!
+
+show
+	div asJQuery show
+!
+
+hide
+	div asJQuery hide
+!
+
+remove
+	div asJQuery remove
+!
+
+close
+    TabManager current closeTab: self
+! !
+
+!TabWidget methodsFor: 'rendering'!
+
+renderOn: html
+	div := html div
+		class: 'jtalkTool';
+		yourself.
+	self renderTab
+!
+
+renderBoxOn: html
+!
+
+renderButtonsOn: html
+!
+
+update
+	self renderTab
+!
+
+renderTab
+	div contents: [:html |
+	    html div
+		class: 'jt_box';
+		with: [self renderBoxOn: html].
+	    html div
+		class: 'jt_buttons';
+		with: [self renderButtonsOn: html]]
+! !
+
+!TabWidget methodsFor: 'testing'!
+
+canBeClosed
+    ^false
+! !
+
+!TabWidget class methodsFor: 'instance creation'!
+
+open
+    ^self new open
+! !
+
+Widget subclass: #SourceArea
+	instanceVariableNames: 'editor div receiver onDoIt'
+	category: 'IDE'!
+
+!SourceArea methodsFor: 'accessing'!
+
+val
+    ^editor getValue
+!
+
+val: aString
+    editor setValue: aString
 !
 
 currentLine
@@ -328,283 +438,173 @@ renderOn: html
     div onKeyDown: [:e | self handleKeyDown: e]
 ! !
 
-Widget subclass: #TabWidget
-	instanceVariableNames: 'div'
+Widget subclass: #ClassesList
+	instanceVariableNames: 'browser ul nodes'
 	category: 'IDE'!
 
-!TabWidget methodsFor: 'accessing'!
-
-label
-    self subclassResponsibility
-! !
+!ClassesList methodsFor: 'accessing'!
 
-!TabWidget methodsFor: 'actions'!
+category
+	^self browser selectedPackage
+!
 
-open
-    TabManager current addTab: self.
-    TabManager current selectTab: self
+nodes
+	nodes ifNil: [nodes := self getNodes].
+	^nodes
 !
 
-show
-	div asJQuery show
+browser
+	^browser
 !
 
-hide
-	div asJQuery hide
+browser: aBrowser
+	browser := aBrowser
 !
 
-remove
-	div asJQuery remove
+getNodes
+	| classes children others |
+	classes := self browser classes.
+	children := #().
+	others := #().
+	classes do: [:each |
+		(classes includes: each superclass)
+			ifFalse: [children add: each]
+			ifTrue: [others add: each]].
+	^children collect: [:each |
+		ClassesListNode on: each browser: self browser classes: others level: 0]
 !
 
-close
-    TabManager current closeTab: self
+resetNodes
+	nodes := nil
 ! !
 
-!TabWidget methodsFor: 'rendering'!
+!ClassesList methodsFor: 'rendering'!
 
 renderOn: html
-	div := html div
-		class: 'jtalkTool';
+	ul := html ul
+		class: 'jt_column browser classes';
 		yourself.
-	self renderTab
-!
-
-renderBoxOn: html
-!
-
-renderButtonsOn: html
-!
-
-update
-	self renderTab
+	self updateNodes
 !
 
-renderTab
-	div contents: [:html |
-	    html div
-		class: 'jt_box';
-		with: [self renderBoxOn: html].
-	    html div
-		class: 'jt_buttons';
-		with: [self renderButtonsOn: html]]
-! !
-
-!TabWidget methodsFor: 'testing'!
-
-canBeClosed
-    ^false
+updateNodes
+	ul contents: [:html |
+		self nodes do: [:each |
+			each renderOn: html]]
 ! !
 
-!TabWidget class methodsFor: 'instance creation'!
+!ClassesList class methodsFor: 'instance creation'!
 
-open
-    ^self new open
+on: aBrowser
+	^self new 
+		browser: aBrowser; 
+		yourself
 ! !
 
-Widget subclass: #TabManager
-	instanceVariableNames: 'selectedTab tabs opened ul input'
+Widget subclass: #ClassesListNode
+	instanceVariableNames: 'browser theClass level nodes'
 	category: 'IDE'!
 
-!TabManager methodsFor: 'accessing'!
-
-tabs
-    ^tabs ifNil: [tabs := Array new]
-!
+!ClassesListNode methodsFor: ''!
 
-labelFor: aWidget
-	| label maxSize |
-	maxSize := 15.
-	label := aWidget label copyFrom: 0 to: (aWidget label size min: maxSize).
-	aWidget label size > maxSize ifTrue: [
-		label := label, '...'].
-	^label
-! !
+renderOn: html
+	| li cssClass |
+	cssClass := ''.
+	li := html li 
+		onClick: [self browser selectClass: self theClass]. 
+	li asJQuery html: self label.
 
-!TabManager methodsFor: 'actions'!
+	self browser selectedClass = self theClass ifTrue:  [
+		cssClass := cssClass, ' selected'].
 
-updateBodyMargin
-    self setBodyMargin: '#jtalk' asJQuery height
-!
+	self theClass comment isEmpty ifFalse: [
+		cssClass := cssClass, ' commented'].
 
-updatePosition
-    <jQuery('#jtalk').css('top', '').css('bottom', '0px')>
-!
+	li class: cssClass.
 
-removeBodyMargin
-    self setBodyMargin: 0
-!
+	self nodes do: [:each |
+		each renderOn: html]
+! !
 
-setBodyMargin: anInteger
-    '.jtalkBody' asJQuery css: 'margin-bottom' put: anInteger asString, 'px'
-!
+!ClassesListNode methodsFor: 'accessing'!
 
-onResize: aBlock
-    <jQuery('#jtalk').resizable({
-	handles: 'n', 
-	resize: aBlock,
-	minHeight: 230
-})>
+nodes
+	^nodes
 !
 
-onWindowResize: aBlock
-    <jQuery(window).resize(aBlock)>
+theClass
+	^theClass
 !
 
-open
-    opened ifFalse: [
-	'body' asJQuery addClass: 'jtalkBody'.
-	'#jtalk' asJQuery show.
-	ul asJQuery show.
-	self updateBodyMargin.
-	selectedTab show.
-	opened := true]
+theClass: aClass
+	theClass := aClass
 !
 
-close
-    opened ifTrue: [
-	'#jtalk' asJQuery hide.
-	ul asJQuery hide.
-	selectedTab hide.
-	self removeBodyMargin.
-	'body' asJQuery removeClass: 'jtalkBody'.
-	opened := false]
+browser
+	^browser
 !
 
-newBrowserTab
-    Browser open
+browser: aBrowser
+	browser := aBrowser
 !
 
-selectTab: aWidget
-    self open.
-    selectedTab := aWidget.
-    self tabs do: [:each |
-	each hide].
-    aWidget show.
-	
-    self update
+level
+	^level
 !
 
-closeTab: aWidget
-    self removeTab: aWidget.
-    self selectTab: self tabs last.
-    aWidget remove.
-    self update
+level: anInteger
+	level := anInteger
 !
 
-search: aString
-	| searchedClass |
-	searchedClass := Smalltalk current at: aString.
-		searchedClass isClass
-			ifTrue: [Browser openOn: searchedClass]
-			ifFalse: [ReferencesBrowser search: aString]
-! !
-
-!TabManager methodsFor: 'adding/Removing'!
-
-addTab: aWidget
-    self tabs add: aWidget.
-    aWidget appendToJQuery: '#jtalk' asJQuery.
-    aWidget hide
+label
+	| str |
+	str := String new writeStream.
+	self level timesRepeat: [
+		str nextPutAll: '&nbsp;&nbsp;&nbsp;&nbsp;'].
+	str nextPutAll: self theClass name.
+	^str contents
 !
 
-removeTab: aWidget
-    self tabs remove: aWidget.
-    self update
+getNodesFrom: aCollection
+	| children others |
+	children := #().
+	others := #().
+	aCollection do: [:each |
+		(each superclass = self theClass)
+			ifTrue: [children add: each]
+			ifFalse: [others add: each]].
+	nodes:= children collect: [:each |
+		ClassesListNode on: each browser: self browser classes: others level: self level + 1]
 ! !
 
-!TabManager methodsFor: 'initialization'!
+!ClassesListNode class methodsFor: 'instance creation'!
 
-initialize
-    super initialize.
-    opened := true.
-    [:html | html div id: 'jtalk'] appendToJQuery: 'body' asJQuery.
-    'body' asJQuery 
-	addClass: 'jtalkBody'.
-    self appendToJQuery: '#jtalk' asJQuery.
-    self 
-	addTab: IDETranscript current;
-	addTab: Workspace new;
-	addTab: TestRunner new.
-    self selectTab: self tabs last.
-    self 
-	onResize: [self updateBodyMargin; updatePosition];
-	onWindowResize: [self updatePosition]
+on: aClass browser: aBrowser classes: aCollection level: anInteger
+	^self new
+		theClass: aClass;
+		browser: aBrowser;
+		level: anInteger;
+		getNodesFrom: aCollection;
+		yourself
 ! !
 
-!TabManager methodsFor: 'rendering'!
-
-renderOn: html
-	html div id: 'logo'.
-	self renderToolbarOn: html.
-	ul := html ul
-		id: 'jtalkTabs';
-		yourself.
-	self renderTabs
-!
-
-renderTabFor: aWidget on: html
-	| li |
-	li := html li.
-	selectedTab = aWidget ifTrue: [
-	li class: 'selected'].
-	li with: [
-		html span class: 'ltab'.
-		html span
-			class: 'mtab';
-			with: [
-				aWidget canBeClosed ifTrue: [
-					html span 
-						class: 'close';
-						with: 'x';
-					onClick: [self closeTab: aWidget]].
-			html span with: (self labelFor: aWidget)].
-		html span class: 'rtab'];
-	onClick: [self selectTab: aWidget]
-!
-
-renderTabs
-	ul contents: [:html |
-	    self tabs do: [:each |
-		self renderTabFor: each on: html].
-	    html li
-		class: 'newtab';
-		with: [
-			html span class: 'ltab'.
-			html span class: 'mtab'; with: ' + '.
-			html span class: 'rtab'];
-		onClick: [self newBrowserTab]]
-!
-
-renderToolbarOn: html
-	html div 
-		id: 'jt_toolbar';
-		with: [
-			input := html input 
-				class: 'implementors';
-				yourself.
-			input onKeyPress: [:event |
-				event keyCode = 13 ifTrue: [
-				self search: input asJQuery val]].
-			html div id: 'jt_close'; onClick: [self close]]
-! !
+ErrorHandler subclass: #DebugErrorHandler
+	instanceVariableNames: ''
+	category: 'IDE'!
 
-!TabManager methodsFor: 'updating'!
+!DebugErrorHandler methodsFor: 'error handling'!
 
-update
-	self renderTabs
+handleError: anError
+	[Debugger new
+		error: anError;
+		open] on: Error do: [:error |
+			ErrorHandler new handleError: error]
 ! !
 
-TabManager class instanceVariableNames: 'current'!
-
-!TabManager class methodsFor: 'instance creation'!
-
-current
-    ^current ifNil: [current := super new]
-!
+!DebugErrorHandler class methodsFor: 'initialization'!
 
-new
-    self shouldNotImplement
+initialize
+	self register
 ! !
 
 TabWidget subclass: #Workspace
@@ -1289,12 +1289,13 @@ updateSourceAndButtons
 					class: 'important';
 					with: 'New...'.
 				self protocols do: [:each |
-					html option with: each]].
+					option := html option with: each.
+					selectedProtocol = each ifTrue: [ option at: 'selected' put: 'selected' ] ]].
 		selectedMethod isNil ifFalse: [
 			referencesSelect := html select.
                         referencesSelect
 				onChange: [self searchReferencesOf: referencesSelect asJQuery val];
-				with: [
+				with: [ |option|
 					html option
 						with: 'References';
 						at: 'disabled' put: 'disabled'.

Daži faili netika attēloti, jo izmaiņu fails ir pārāk liels