| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456 | Smalltalk current createPackage: 'Helios-Workspace'!Object subclass: #HLCodeModel instanceVariableNames: 'announcer environment receiver' package: 'Helios-Workspace'!!HLCodeModel methodsFor: 'accessing'!announcer	^ announcer ifNil: [ announcer := Announcer new ]!environment	^ environment ifNil: [ HLManager current environment ]!environment: anEnvironment	environment := anEnvironment!receiver	^ receiver ifNil: [ receiver := self defaultReceiver ]!receiver: anObject	receiver := anObject! !!HLCodeModel methodsFor: 'actions'!doIt: someCode	^ self environment eval: someCode on: self receiver!subscribe: aWidget	aWidget subscribeTo: self announcer! !!HLCodeModel methodsFor: 'defaults'!defaultReceiver	^ DoIt new! !!HLCodeModel class methodsFor: 'actions'!on: anEnvironment	^ self new    	environment: anEnvironment;        yourself! !HLWidget subclass: #HLCodeWidget instanceVariableNames: 'model wrapper code editor' package: 'Helios-Workspace'!!HLCodeWidget methodsFor: 'accessing'!announcer	^ self model announcer!contents	^ editor getValue!contents: aString	editor setValue: aString!currentLine    ^editor getLine: (editor getCursor line)!currentLineOrSelection    ^editor somethingSelected		ifFalse: [ self currentLine ]		ifTrue: [ self selection ]!model	^ model ifNil: [ model := HLCodeModel new ]!model: aModel	model := aModel!receiver	^ self model receiver!receiver: anObject	self model receiver: anObject!selection	^editor getSelection!selectionEnd   ^code element selectionEnd!selectionEnd: anInteger   code element selectionEnd: anInteger!selectionStart   ^code element selectionStart!selectionStart: anInteger   code element selectionStart: anInteger! !!HLCodeWidget methodsFor: 'actions'!clear      self contents: ''!configureEditor	self editor at: 'amberCodeWidget' put: self!doIt	| result |	self announcer announce: (HLDoItRequested on: model).	result:=  model doIt: self currentLineOrSelection.	self announcer announce: (HLDoItExecuted on: model).	^ result!editor	^editor!focus	editor focus!inspectIt	| newInspector |       	self announcer announce: (HLInspectItRequested on: model).	newInspector := self makeInspectorOn: self doIt.	newInspector open!makeInspectorOn: anObject	^ HLInspector new 		inspect: anObject;		yourself!print: aString	| start stop currentLine |    currentLine := (editor getCursor: false) line.	start := HashedCollection new.	start at: 'line' put: currentLine.	start at: 'ch' put: (editor getCursor: false) ch.    (editor getSelection) ifEmpty: [    	"select current line if selection is empty"    	start at: 'ch' put: (editor getLine: currentLine) size.        editor setSelection: #{'line' -> currentLine. 'ch' -> 0} end: start.    ].	stop := HashedCollection new.	stop at: 'line' put: currentLine.	stop at: 'ch' put: ((start at: 'ch') + aString size + 2).	editor replaceSelection: (editor getSelection, ' ', aString, ' ').	editor setCursor: (editor getCursor: true).	editor setSelection: stop end: start!printIt	| result |	result:=  self doIt.       	self announcer announce: (HLPrintItRequested on: model).    self print: result printString.	self focus.!saveIt	"I do not do anything"!setEditorOn: aTextarea	<self['@editor'] = CodeMirror.fromTextArea(aTextarea, {		theme: 'amber',                lineNumbers: true,                enterMode: 'flat',                indentWithTabs: true,				indentUnit: 4,                matchBrackets: true,                electricChars: false,				keyMap: 'Amber'	})>! !!HLCodeWidget methodsFor: 'reactions'!onDoIt	    self doIt!onInspectIt	self inspectIt!onPrintIt	self printIt!onSaveIt	"I do not do anything"! !!HLCodeWidget methodsFor: 'rendering'!renderContentOn: html    code := html textarea.    self setEditorOn: code element.    self configureEditor! !!HLCodeWidget methodsFor: 'testing'!canHaveFocus	^ true!hasFocus	^ code asJQuery is: ':active'! !!HLCodeWidget class methodsFor: 'accessing'!keyMap	^ HLManager current keyBinder systemIsMac		ifTrue: [ self macKeyMap ]		ifFalse: [ self pcKeyMap ]!macKeyMap	^ #{		'Alt-Backspace'		-> 'delWordBefore'.		'Alt-Delete'		-> 'delWordAfter'. 		'Alt-Left'		-> 'goWordBoundaryLeft'.		'Alt-Right'		-> 'goWordBoundaryRight'. 		'Cmd-A'			-> 'selectAll'. 		'Cmd-Alt-F'		-> 'replace'. 		'Cmd-D'			-> 'doIt'. 		'Cmd-Down'		-> 'goDocEnd'. 		'Cmd-End'		-> 'goDocEnd'. 		'Cmd-F'			-> 'find'.		'Cmd-G'			-> 'findNext'. 		'Cmd-I'			-> 'inspectIt'. 		'Cmd-Left'		-> 'goLineStart'. 		'Cmd-P'			-> 'printIt'. 		'Cmd-Right'		-> 'goLineEnd'. 		'Cmd-S'			-> 'saveIt'. 		'Cmd-Up'		-> 'goDocStart'. 		'Cmd-Y'			-> 'redo'.		'Cmd-Z'			-> 'undo'. 		'Cmd-['			-> 'indentLess'. 		'Cmd-]'			-> 'indentMore'.		'Ctrl-Alt-Backspace'	-> 'delWordAfter'. 		'Shift-Cmd-Alt-F'	-> 'replaceAll'.		'Shift-Cmd-G'		-> 'findPrev'. 		'Shift-Cmd-Z'		-> 'redo'.     	'fallthrough' 	-> { 'basic' }  }!pcKeyMap	^ {		'Alt-Left' -> 'goLineStart'. 		'Alt-Right' -> 'goLineEnd'.		'Alt-Up' -> 'goDocStart'. 		'Ctrl-A' -> 'selectAll'. 		'Ctrl-Backspace' -> 'delWordBefore'. 		'Ctrl-D' -> 'doIt'. 		'Ctrl-Delete' -> 'delWordAfter'. 		'Ctrl-Down' -> 'goDocEnd'.		'Ctrl-End' -> 'goDocEnd'. 		'Ctrl-F' -> 'find'.		'Ctrl-G' -> 'findNext'. 		'Ctrl-I' -> 'inspectIt'.		'Ctrl-Home' -> 'goDocStart'. 		'Ctrl-Left' -> 'goWordBoundaryLeft'. 		'Ctrl-P' -> 'printIt'.		'Ctrl-Right' -> 'goWordBoundaryRight'. 		'Ctrl-S' -> 'saveIt'. 		'Ctrl-Y' -> 'redo'.		'Ctrl-Z' -> 'undo'. 		'Ctrl-[' -> 'indentLess'. 		'Ctrl-]' -> 'indentMore'.		'Shift-Ctrl-F' -> 'replace'. 		'Shift-Ctrl-G' -> 'findPrev'. 		'Shift-Ctrl-R' -> 'replaceAll'.		'Shift-Ctrl-Z' -> 'redo'. 		'fallthrough' -> #('basic')}!tabLabel	^ 'Workspace'!tabPriority	^ 10! !!HLCodeWidget class methodsFor: 'initialization'!initialize	super initialize.	self 		setupCodeMirror;		setupCommands;		setupKeyMaps.!setupCodeMirror	< CodeMirror.keyMap.default.fallthrough = ["basic"] >!setupCommands	(CodeMirror basicAt: 'commands') 		at: 'doIt' put: [ :cm | cm amberCodeWidget doIt ];		at: 'inspectIt' put: [ :cm | cm amberCodeWidget inspectIt ];		at: 'printIt' put: [ :cm | cm amberCodeWidget printIt ];		at: 'saveIt' put: [ :cm | cm amberCodeWidget saveIt ]!setupKeyMaps	<CodeMirror.keyMap['Amber'] = self._keyMap()>! !!HLCodeWidget class methodsFor: 'testing'!canBeOpenAsTab	^ true! !HLCodeWidget subclass: #HLSourceCodeWidget instanceVariableNames: 'browserModel' package: 'Helios-Workspace'!!HLSourceCodeWidget methodsFor: 'accessing'!browserModel	^ browserModel!browserModel: aBrowserModel	browserModel := aBrowserModel.	self observeBrowserModel! !!HLSourceCodeWidget methodsFor: 'actions'!observeBrowserModel	self browserModel announcer		on: HLSaveSourceCode		do: [ :ann | self onSaveIt ];		on: HLParseErrorRaised		do: [ :ann | self onParseError: ann ];		on: HLCompileErrorRaised		do: [ :ann | self onCompileError: ann error ];		on: HLUnknownVariableErrorRaised		do: [ :ann | self onUnknownVariableError: ann error ];		on: HLInstVarAdded 		do: [ :ann | self onInstVarAdded ]!saveIt	self browserModel saveSourceCode! !!HLSourceCodeWidget methodsFor: 'reactions'!onCompileError: anError	self alert: anError messageText!onInstVarAdded	self  browserModel save: self contents!onParseError: anAnnouncement	| lineIndex newContents |		lineIndex := 1.		self contents: (String streamContents: [ :stream |		self contents linesDo: [ :each |			lineIndex = anAnnouncement line 				ifTrue: [ 					stream 						nextPutAll: (each copyFrom: 1 to: anAnnouncement column);						nextPutAll: '<- ';						nextPutAll: anAnnouncement message;						nextPutAll: ' ';						nextPutAll: (each copyFrom: anAnnouncement column + 1 to: each size) ]				ifFalse: [ stream nextPutAll: each ].			stream nextPutAll: String cr.			lineIndex := lineIndex + 1 ] ])!onSaveIt	self  browserModel save: self contents!onUnknownVariableError: anError	| confirm |	confirm := self confirm: (String streamContents: [ :stream |		stream 			nextPutAll: anError messageText;			nextPutAll: String cr;			nextPutAll: 'Would you like to define an instance variable?' ]).				confirm ifFalse: [ ^ self ].		self browserModel addInstVarNamed: anError variableName! !!HLSourceCodeWidget class methodsFor: 'instance creation'!on: aBrowserModel	^ self new		browserModel: aBrowserModel;		yourself! !!HLSourceCodeWidget class methodsFor: 'testing'!canBeOpenAsTab	^ false! !
 |