|
@@ -119,7 +119,7 @@ initialize
|
|
addClass: 'jtalkBody'.
|
|
addClass: 'jtalkBody'.
|
|
self appendToJQuery: '#jtalk' asJQuery.
|
|
self appendToJQuery: '#jtalk' asJQuery.
|
|
self
|
|
self
|
|
- addTab: Transcript current;
|
|
|
|
|
|
+ addTab: IDETranscript current;
|
|
addTab: Workspace new;
|
|
addTab: Workspace new;
|
|
addTab: TestRunner new.
|
|
addTab: TestRunner new.
|
|
self selectTab: self tabs last.
|
|
self selectTab: self tabs last.
|
|
@@ -338,79 +338,8 @@ renderButtonsOn: html
|
|
onClick: [self clearWorkspace]
|
|
onClick: [self clearWorkspace]
|
|
! !
|
|
! !
|
|
|
|
|
|
-TabWidget subclass: #Transcript
|
|
|
|
- instanceVariableNames: 'textarea'
|
|
|
|
- category: 'IDE'!
|
|
|
|
-
|
|
|
|
-!Transcript methodsFor: 'accessing'!
|
|
|
|
-
|
|
|
|
-label
|
|
|
|
- ^'Transcript'
|
|
|
|
-! !
|
|
|
|
-
|
|
|
|
-!Transcript methodsFor: 'actions'!
|
|
|
|
-
|
|
|
|
-show: anObject
|
|
|
|
- textarea asJQuery val: textarea asJQuery val, anObject asString.
|
|
|
|
-!
|
|
|
|
-
|
|
|
|
-cr
|
|
|
|
- textarea asJQuery val: textarea asJQuery val, String cr.
|
|
|
|
-!
|
|
|
|
-
|
|
|
|
-clear
|
|
|
|
- textarea asJQuery val: ''
|
|
|
|
-! !
|
|
|
|
-
|
|
|
|
-!Transcript methodsFor: 'rendering'!
|
|
|
|
-
|
|
|
|
-renderBoxOn: html
|
|
|
|
- textarea := html textarea.
|
|
|
|
- textarea
|
|
|
|
- class: 'jt_transcript';
|
|
|
|
- at: 'spellcheck' put: 'false'
|
|
|
|
-!
|
|
|
|
-
|
|
|
|
-renderButtonsOn: html
|
|
|
|
- html button
|
|
|
|
- with: 'Clear transcript';
|
|
|
|
- onClick: [self clear]
|
|
|
|
-! !
|
|
|
|
-
|
|
|
|
-Transcript class instanceVariableNames: 'current'!
|
|
|
|
-
|
|
|
|
-!Transcript class methodsFor: 'instance creation'!
|
|
|
|
-
|
|
|
|
-open
|
|
|
|
- TabManager current
|
|
|
|
- open;
|
|
|
|
- selectTab: self current
|
|
|
|
-!
|
|
|
|
-
|
|
|
|
-new
|
|
|
|
- self shouldNotImplement
|
|
|
|
-!
|
|
|
|
-
|
|
|
|
-current
|
|
|
|
- ^current ifNil: [current := super new]
|
|
|
|
-! !
|
|
|
|
-
|
|
|
|
-!Transcript class methodsFor: 'printing'!
|
|
|
|
-
|
|
|
|
-show: anObject
|
|
|
|
- self current show: anObject
|
|
|
|
-!
|
|
|
|
-
|
|
|
|
-cr
|
|
|
|
- self current show: String cr
|
|
|
|
-!
|
|
|
|
-
|
|
|
|
-clear
|
|
|
|
- self current clear
|
|
|
|
-! !
|
|
|
|
-
|
|
|
|
TabWidget subclass: #Browser
|
|
TabWidget subclass: #Browser
|
|
- instanceVariableNames: 'selectedPackage selectedClass selectedProtocol selectedMethod commitButton packagesList classesList protocolsList methodsList sourceArea tabsList selectedTab saveButton classButtons methodButtons unsavedChanges renameButton deleteButton'
|
|
|
|
|
|
+ instanceVariableNames: 'selectedPackage selectedClass selectedProtocol selectedMethod commitButton packagesList classesList protocolsList methodsList sourceArea tabsList selectedTab saveButton classButtons methodButtons unsavedChanges renameButton deleteButton commitLocalButton'
|
|
category: 'IDE'!
|
|
category: 'IDE'!
|
|
|
|
|
|
!Browser methodsFor: 'accessing'!
|
|
!Browser methodsFor: 'accessing'!
|
|
@@ -587,7 +516,7 @@ compileMethodDefinition
|
|
!
|
|
!
|
|
|
|
|
|
compileMethodDefinitionFor: aClass
|
|
compileMethodDefinitionFor: aClass
|
|
- | compiler method source node |
|
|
|
|
|
|
+ | compiler method source node |
|
|
source := sourceArea val.
|
|
source := sourceArea val.
|
|
selectedProtocol ifNil: [selectedProtocol := selectedMethod category].
|
|
selectedProtocol ifNil: [selectedProtocol := selectedMethod category].
|
|
compiler := Compiler new.
|
|
compiler := Compiler new.
|
|
@@ -599,9 +528,9 @@ compileMethodDefinitionFor: aClass
|
|
method := compiler eval: (compiler compileNode: node).
|
|
method := compiler eval: (compiler compileNode: node).
|
|
method category: selectedProtocol.
|
|
method category: selectedProtocol.
|
|
compiler unknownVariables do: [:each |
|
|
compiler unknownVariables do: [:each |
|
|
- "Do not try to redeclare javascript's objects"
|
|
|
|
- (window at: each) ifNil: [
|
|
|
|
- (self confirm: 'Declare ''', each, ''' as instance variable?') ifTrue: [
|
|
|
|
|
|
+ "Do not try to redeclare javascript's objects"
|
|
|
|
+ (window at: each) ifNil: [
|
|
|
|
+ (self confirm: 'Declare ''', each, ''' as instance variable?') ifTrue: [
|
|
self addInstanceVariableNamed: each toClass: aClass.
|
|
self addInstanceVariableNamed: each toClass: aClass.
|
|
^self compileMethodDefinitionFor: aClass]]].
|
|
^self compileMethodDefinitionFor: aClass]]].
|
|
aClass addCompiledMethod: method.
|
|
aClass addCompiledMethod: method.
|
|
@@ -789,9 +718,10 @@ renamePackage
|
|
|
|
|
|
| newName |
|
|
| newName |
|
|
newName := self prompt: 'Rename package ', selectedPackage.
|
|
newName := self prompt: 'Rename package ', selectedPackage.
|
|
- newName notEmpty ifTrue: [
|
|
|
|
|
|
+ newName ifNotNil: [
|
|
|
|
+ newName notEmpty ifTrue: [
|
|
Smalltalk current renamePackage: selectedPackage to: newName.
|
|
Smalltalk current renamePackage: selectedPackage to: newName.
|
|
- self updateCategoriesList]
|
|
|
|
|
|
+ self updateCategoriesList]]
|
|
!
|
|
!
|
|
|
|
|
|
removePackage
|
|
removePackage
|
|
@@ -800,6 +730,14 @@ removePackage
|
|
ifTrue: [
|
|
ifTrue: [
|
|
Smalltalk current removePackage: selectedPackage.
|
|
Smalltalk current removePackage: selectedPackage.
|
|
self updateCategoriesList]
|
|
self updateCategoriesList]
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+commitPackageToLocalStorage
|
|
|
|
+ | key sourceCode |
|
|
|
|
+ selectedPackage ifNotNil: [
|
|
|
|
+ key := 'smalltalk.packages.' , selectedPackage.
|
|
|
|
+ sourceCode := (Exporter new exportPackage: selectedPackage).
|
|
|
|
+ <localStorage[key] = sourceCode>]
|
|
! !
|
|
! !
|
|
|
|
|
|
!Browser methodsFor: 'initialization'!
|
|
!Browser methodsFor: 'initialization'!
|
|
@@ -828,17 +766,22 @@ renderTopPanelOn: html
|
|
class: 'jt_commit';
|
|
class: 'jt_commit';
|
|
title: 'Commit classes in this package to disk';
|
|
title: 'Commit classes in this package to disk';
|
|
onClick: [self commitPackage];
|
|
onClick: [self commitPackage];
|
|
- with: 'Commit package'.
|
|
|
|
|
|
+ with: 'Commit'.
|
|
|
|
+ commitLocalButton := html button
|
|
|
|
+ class: 'jt_commit_local';
|
|
|
|
+ title: 'Commit classes in this package to local storage';
|
|
|
|
+ onClick: [self commitPackageToLocalStorage];
|
|
|
|
+ with: 'Local'.
|
|
renameButton := html button
|
|
renameButton := html button
|
|
class: 'jt_rename';
|
|
class: 'jt_rename';
|
|
- title: 'Rename this package';
|
|
|
|
|
|
+ title: 'Rename package';
|
|
onClick: [self renamePackage];
|
|
onClick: [self renamePackage];
|
|
- with: 'Rename package'.
|
|
|
|
|
|
+ with: 'Rename'.
|
|
deleteButton := html button
|
|
deleteButton := html button
|
|
class: 'jt_delete';
|
|
class: 'jt_delete';
|
|
title: 'Remove this package from the system';
|
|
title: 'Remove this package from the system';
|
|
onClick: [self removePackage];
|
|
onClick: [self removePackage];
|
|
- with: 'Remove package'.
|
|
|
|
|
|
+ with: 'Remove'.
|
|
classesList := ClassesList on: self.
|
|
classesList := ClassesList on: self.
|
|
classesList renderOn: html.
|
|
classesList renderOn: html.
|
|
protocolsList := html ul class: 'jt_column browser protocols'.
|
|
protocolsList := html ul class: 'jt_column browser protocols'.
|
|
@@ -2214,6 +2157,75 @@ updateStatusDiv
|
|
html span with: self statusInfo]
|
|
html span with: self statusInfo]
|
|
! !
|
|
! !
|
|
|
|
|
|
|
|
+TabWidget subclass: #IDETranscript
|
|
|
|
+ instanceVariableNames: 'textarea'
|
|
|
|
+ category: 'IDE'!
|
|
|
|
+
|
|
|
|
+!IDETranscript methodsFor: 'accessing'!
|
|
|
|
+
|
|
|
|
+label
|
|
|
|
+ ^'Transcript'
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+!IDETranscript methodsFor: 'actions'!
|
|
|
|
+
|
|
|
|
+clear
|
|
|
|
+ textarea asJQuery val: ''
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+cr
|
|
|
|
+ textarea asJQuery val: textarea asJQuery val, String cr.
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+show: anObject
|
|
|
|
+ textarea asJQuery val: textarea asJQuery val, anObject asString.
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+open
|
|
|
|
+ TabManager current
|
|
|
|
+ open;
|
|
|
|
+ selectTab: self
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+!IDETranscript methodsFor: 'rendering'!
|
|
|
|
+
|
|
|
|
+renderBoxOn: html
|
|
|
|
+ textarea := html textarea.
|
|
|
|
+ textarea
|
|
|
|
+ class: 'jt_transcript';
|
|
|
|
+ at: 'spellcheck' put: 'false'
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+renderButtonsOn: html
|
|
|
|
+ html button
|
|
|
|
+ with: 'Clear transcript';
|
|
|
|
+ onClick: [self clear]
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+IDETranscript class instanceVariableNames: 'current'!
|
|
|
|
+
|
|
|
|
+!IDETranscript class methodsFor: 'initialization'!
|
|
|
|
+
|
|
|
|
+initialize
|
|
|
|
+ Transcript register: self current
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+!IDETranscript class methodsFor: 'instance creation'!
|
|
|
|
+
|
|
|
|
+new
|
|
|
|
+ self shouldNotImplement
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+open
|
|
|
|
+ TabManager current
|
|
|
|
+ open;
|
|
|
|
+ selectTab: self current
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+current
|
|
|
|
+ ^current ifNil: [current := super new]
|
|
|
|
+! !
|
|
|
|
+
|
|
!Object methodsFor: '*IDE'!
|
|
!Object methodsFor: '*IDE'!
|
|
|
|
|
|
inspect
|
|
inspect
|