| 12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106110711081109111011111112111311141115111611171118111911201121112211231124112511261127112811291130113111321133113411351136113711381139114011411142114311441145114611471148114911501151115211531154115511561157115811591160116111621163116411651166116711681169117011711172117311741175117611771178117911801181118211831184118511861187118811891190119111921193119411951196119711981199120012011202120312041205120612071208120912101211121212131214121512161217121812191220122112221223122412251226122712281229123012311232123312341235123612371238123912401241124212431244124512461247124812491250125112521253125412551256125712581259126012611262126312641265126612671268126912701271127212731274127512761277127812791280128112821283128412851286128712881289129012911292129312941295129612971298129913001301130213031304130513061307130813091310131113121313131413151316131713181319132013211322132313241325132613271328132913301331133213331334133513361337133813391340134113421343134413451346134713481349135013511352135313541355135613571358135913601361136213631364136513661367136813691370137113721373137413751376137713781379138013811382138313841385138613871388138913901391139213931394139513961397139813991400140114021403140414051406140714081409141014111412141314141415141614171418141914201421142214231424142514261427142814291430143114321433143414351436143714381439144014411442144314441445144614471448144914501451145214531454145514561457145814591460146114621463146414651466146714681469147014711472147314741475147614771478147914801481148214831484148514861487148814891490149114921493149414951496149714981499150015011502150315041505150615071508150915101511151215131514151515161517151815191520152115221523152415251526152715281529153015311532153315341535153615371538153915401541154215431544154515461547154815491550155115521553155415551556155715581559156015611562156315641565156615671568156915701571157215731574157515761577157815791580158115821583158415851586158715881589159015911592159315941595159615971598159916001601160216031604160516061607160816091610161116121613161416151616161716181619162016211622162316241625162616271628162916301631163216331634163516361637163816391640164116421643164416451646164716481649165016511652165316541655165616571658165916601661166216631664166516661667166816691670167116721673167416751676167716781679168016811682168316841685168616871688168916901691169216931694169516961697169816991700170117021703170417051706170717081709171017111712171317141715171617171718171917201721172217231724 | Smalltalk current createPackage: 'Helios-Core'!Object subclass: #HLModel	instanceVariableNames: 'announcer environment'	package: 'Helios-Core'!!HLModel commentStamp!I am the abstract superclass of all models of Helios.I am the "Model" part of the MVC pattern implementation in Helios.I provide access to an `Environment` object and both a local (model-specific) and global (system-specific) announcer.The `#withChangesDo:` method is handy for performing model changes ensuring that all widgets are aware of the change and can prevent it from happening.Modifications of the system should be done via commands (see `HLCommand` and subclasses).!!HLModel methodsFor: 'accessing'!announcer	^ announcer ifNil: [ announcer := Announcer new ]!environment	^ environment ifNil: [ self manager environment ]!environment: anEnvironment	environment := anEnvironment!manager	^ HLManager current!systemAnnouncer	^ self environment systemAnnouncer! !!HLModel methodsFor: 'error handling'!withChangesDo: aBlock	[ 		self announcer announce: (HLAboutToChange new			actionBlock: aBlock).		aBlock value.	]		on: HLChangeForbidden 		do: [ :ex | ]! !!HLModel methodsFor: 'testing'!isBrowserModel	^ false!isReferencesModel	^ false!isToolModel	^ false! !HLModel subclass: #HLToolModel	instanceVariableNames: 'selectedClass selectedPackage selectedProtocol selectedSelector'	package: 'Helios-Core'!!HLToolModel commentStamp!I am a model specific to package and class manipulation. All browsers should either use me or a subclass as their model.I provide methods for package, class, protocol and method manipulation and access, forwarding to my environment.I also handle compilation of classes and methods as well as compilation and parsing errors.!!HLToolModel methodsFor: 'accessing'!allSelectors	^ self environment allSelectors!availableClassNames	^ self environment availableClassNames!availablePackageNames	^ self environment availablePackageNames!availablePackages	^ self environment availablePackageNames!availableProtocols	^ self environment availableProtocolsFor: self selectedClass!packages	^ self environment packages!selectedClass	^ selectedClass!selectedClass: aClass	(self selectedClass = aClass and: [ aClass isNil ]) 		ifTrue: [ ^ self ].		self withChangesDo: [		selectedClass = aClass ifTrue: [ 			self selectedProtocol: nil ].    		aClass    			ifNil: [ selectedClass := nil ]    		ifNotNil: [				self selectedPackage: aClass theNonMetaClass package.				self showInstance    					ifTrue: [ selectedClass := aClass theNonMetaClass ]     				ifFalse: [ selectedClass := aClass theMetaClass ] ].		self selectedProtocol: nil.		self announcer announce: (HLClassSelected on: self selectedClass) ]!selectedMethod	^ self selectedClass ifNotNil: [ 		self selectedClass methodDictionary 			at: selectedSelector 			ifAbsent: [ nil ] ]!selectedMethod: aCompiledMethod	selectedSelector = aCompiledMethod ifTrue: [ ^ self ].        self withChangesDo: [		aCompiledMethod    		ifNil: [ selectedSelector := nil ]      		ifNotNil: [				selectedClass := aCompiledMethod methodClass.				selectedPackage := selectedClass theNonMetaClass package.				selectedSelector := aCompiledMethod selector ].		self announcer announce: (HLMethodSelected on: aCompiledMethod) ]!selectedPackage	^ selectedPackage!selectedPackage: aPackage	selectedPackage = aPackage ifTrue: [ ^ self ].    	self withChangesDo: [		selectedPackage := aPackage.		self selectedClass: nil.		self announcer announce: (HLPackageSelected on: aPackage) ]!selectedProtocol	^ selectedProtocol!selectedProtocol: aString	selectedProtocol = aString ifTrue: [ ^ self ].	self withChangesDo: [		selectedProtocol := aString.		self selectedMethod: nil.		self announcer announce: (HLProtocolSelected on: aString) ]! !!HLToolModel methodsFor: 'actions'!addInstVarNamed: aString	self environment addInstVarNamed: aString to: self selectedClass.	self announcer announce: (HLInstVarAdded new		theClass: self selectedClass;		variableName: aString;		yourself)!save: aString	self announcer announce: HLSourceCodeSaved new.		(self shouldCompileClassDefinition: aString)		ifTrue: [ self compileClassDefinition: aString ]		ifFalse: [ self compileMethod: aString ]!saveSourceCode	self announcer announce: HLSaveSourceCode new! !!HLToolModel methodsFor: 'commands actions'!commitPackage	"self 		withHelperLabelled: 'Committing package ', self selectedPackage name, '...'		do: [ "self environment commitPackage: self selectedPackage" ]"!copyClassTo: aClassName	self withChangesDo: [ 		self environment 			copyClass: self selectedClass theNonMetaClass			to: aClassName ]!moveClassToPackage: aPackageName	self withChangesDo: [		self environment 			moveClass: self selectedClass theNonMetaClass			toPackage: aPackageName ]!moveMethodToClass: aClassName	self withChangesDo: [		self environment 			moveMethod: self selectedMethod 			toClass: aClassName ]!moveMethodToProtocol: aProtocol	self withChangesDo: [		self environment 			moveMethod: self selectedMethod 			toProtocol: aProtocol ]!openClassNamed: aString	| class |		self withChangesDo: [		class := self environment classNamed: aString.		self selectedPackage: class package.		self selectedClass: class ]!removeClass	self withChangesDo: [		self manager 			confirm: 'Do you REALLY want to remove class ', self selectedClass name			ifTrue: [ self environment removeClass: self selectedClass ] ]!removeMethod	self withChangesDo: [		self manager 			confirm: 'Do you REALLY want to remove method ', self selectedMethod methodClass name,' >> #', self selectedMethod selector			ifTrue: [ self environment removeMethod: self selectedMethod ] ]!removeProtocol	self withChangesDo: [		self manager 			confirm: 'Do you REALLY want to remove protocol ', self selectedProtocol			ifTrue: [ self environment 				removeProtocol: self selectedProtocol 				from: self selectedClass ] ]!renameClassTo: aClassName	self withChangesDo: [		self environment 			renameClass: self selectedClass theNonMetaClass			to: aClassName ]!renameProtocolTo: aString	self withChangesDo: [		self environment 			renameProtocol: self selectedProtocol			to: aString			in: self selectedClass ]! !!HLToolModel methodsFor: 'compiling'!compileClassComment: aString	self environment 		compileClassComment: aString 		for: self selectedClass!compileClassDefinition: aString	self environment compileClassDefinition: aString!compileMethod: aString	| method |		self withCompileErrorHandling: [ 		method := self environment 			compileMethod: aString 			for: self selectedClass			protocol: self compilationProtocol.		self selectedMethod: method ]! !!HLToolModel methodsFor: 'defaults'!allProtocol	^ '-- all --'!unclassifiedProtocol	^ 'as yet unclassified'! !!HLToolModel methodsFor: 'error handling'!handleCompileError: anError	self announcer announce: (HLCompileErrorRaised new		error: anError;		yourself)!handleParseError: anError	| split line column messageToInsert |		split := anError messageText tokenize: ' : '.	messageToInsert := split second.	"21 = 'Parse error on line ' size + 1"	split := split first copyFrom: 21 to: split first size.		split := split tokenize: ' column '.	line := split first.	column := split second.		self announcer announce: (HLParseErrorRaised new		line: line asNumber;		column: column asNumber;		message: messageToInsert;		error: anError;		yourself)!handleUnkownVariableError: anError	self announcer announce: (HLUnknownVariableErrorRaised new		error: anError;		yourself)!withCompileErrorHandling: aBlock	self environment		evaluate: [			self environment 			evaluate: [				self environment 					evaluate: aBlock					on: ParseError					do: [:ex | self handleParseError: ex ] ]			on: UnknownVariableError			do: [ :ex | self handleUnkownVariableError: ex ] ]		on: CompilerError		do: [ :ex | self handleCompileError: ex ]! !!HLToolModel methodsFor: 'private'!compilationProtocol	| currentProtocol |		currentProtocol := self selectedProtocol.	currentProtocol ifNil: [ currentProtocol := self unclassifiedProtocol ].	self selectedMethod ifNotNil: [ currentProtocol := self selectedMethod protocol ].	^ currentProtocol = self allProtocol		ifTrue: [ self unclassifiedProtocol ]		ifFalse: [ currentProtocol ]!withHelperLabelled: aString do: aBlock	"TODO: doesn't belong here"	(window jQuery: '#helper') remove.	[ :html |		html div 			id: 'helper';			with: aString ] appendToJQuery: 'body' asJQuery.		[		aBlock value.		(window jQuery: '#helper') remove	] 		valueWithTimeout: 10! !!HLToolModel methodsFor: 'testing'!isToolModel	^ true!shouldCompileClassDefinition: aString	^ self selectedClass isNil or: [		aString match: '^[A-Z]' ]! !!HLToolModel class methodsFor: 'actions'!on: anEnvironment	^ self new    	environment: anEnvironment;        yourself! !ProgressHandler subclass: #HLProgressHandler	instanceVariableNames: ''	package: 'Helios-Core'!!HLProgressHandler commentStamp!I am a specific progress handler for Helios, displaying progresses in a modal window.!!HLProgressHandler methodsFor: 'progress handling'!do: aBlock on: aCollection displaying: aString	HLProgressWidget default		do: aBlock 		on: aCollection 		displaying: aString! !Widget subclass: #HLTabWidget	instanceVariableNames: 'widget label root'	package: 'Helios-Core'!!HLTabWidget commentStamp!I am a widget specialized into building another widget as an Helios tab.I should not be used directly, `HLWidget class >> #openAsTab` should be used instead.## Example    HLWorkspace openAsTab!!HLTabWidget methodsFor: 'accessing'!activate	self manager activate: self!add	self manager addTab: self!cssClass	^ self widget tabClass!displayLabel	^ self label size > 20 		ifTrue: [ (self label first: 20), '...' ]		ifFalse: [ self label ]!focus	self widget canHaveFocus ifTrue: [		self widget focus ]!label	^ label ifNil: [ '' ]!label: aString	label := aString!manager	^ HLManager current!widget	^ widget!widget: aWidget	widget := aWidget! !!HLTabWidget methodsFor: 'actions'!hide	root ifNotNil: [ root asJQuery css: 'visibility' put: 'hidden' ]!registerBindings	self widget registerBindings!remove	self widget unregister.	root ifNotNil: [ root asJQuery remove ]!show	root		ifNil: [ self appendToJQuery: 'body' asJQuery ]		ifNotNil: [ root asJQuery css: 'visibility' put: 'visible' ]! !!HLTabWidget methodsFor: 'rendering'!renderOn: html	root := html div		class: 'tab';		yourself.	self renderTab!renderTab	root contents: [ :html |		html div			class: 'amber_box';			with: [ self widget renderOn: html ] ]! !!HLTabWidget methodsFor: 'testing'!isActive	^ self manager activeTab = self! !!HLTabWidget class methodsFor: 'instance creation'!on: aWidget labelled: aString	^ self new		widget: aWidget;		label: aString;		yourself! !Widget subclass: #HLWidget	instanceVariableNames: 'wrapper'	package: 'Helios-Core'!!HLWidget commentStamp!I am the abstract superclass of all Helios widgets.I provide common methods, additional behavior to widgets useful for Helios, like dialog creation, command execution and tab creation.## API1. Rendering    Instead of overriding `#renderOn:` as with other Widget subclasses, my subclasses should override `#renderContentOn:`.2. Refreshing    To re-render a widget, use `#refresh`.3. Key bindings registration and tabs    When displayed as a tab, the widget has a chance to register keybindings with the `#registerBindingsOn:` hook method.    4. Unregistration    When a widget has subscribed to announcements or other actions that need to be cleared when closing the tab, the hook method `#unregister` will be called by helios.5. Tabs   To enable a widget class to be open as a tab, override the class-side `#canBeOpenAsTab` method to answer `true`. `#tabClass` and `#tabPriority` can be overridden too to respectively change the css class of the tab and the order of tabs in the main menu.6. Command execution    An helios command (instance of `HLCommand` or one of its subclass) can be executed with `#execute:`.!!HLWidget methodsFor: 'accessing'!manager	^ HLManager current!tabClass	^ self class tabClass!wrapper	^ wrapper! !!HLWidget methodsFor: 'actions'!alert: aString	window alert: aString!confirm: aString ifTrue: aBlock	self manager confirm: aString ifTrue: aBlock!execute: aCommand	HLManager current keyBinder		activate;		applyBinding: aCommand asBinding!openAsTab	HLManager current addTab: (HLTabWidget on: self labelled: self class tabLabel)!request: aString do: aBlock	self manager request: aString do: aBlock!request: aString value: valueString do: aBlock	self manager 		request: aString 		value: valueString		do: aBlock!unregister	"This method is called whenever the receiver is closed (as a tab).	Widgets subscribing to announcements should unregister there"! !!HLWidget methodsFor: 'keybindings'!registerBindings	self registerBindingsOn: self manager keyBinder bindings!registerBindingsOn: aBindingGroup! !!HLWidget methodsFor: 'rendering'!renderContentOn: html!renderOn: html	wrapper := html div.    [ :renderer | self renderContentOn: renderer ] appendToJQuery: wrapper asJQuery! !!HLWidget methodsFor: 'testing'!canHaveFocus	^ false! !!HLWidget methodsFor: 'updating'!refresh	self wrapper ifNil: [ ^ self ].    	self wrapper asJQuery empty.    [ :html | self renderContentOn: html ] appendToJQuery: self wrapper asJQuery! !!HLWidget class methodsFor: 'accessing'!openAsTab	HLManager current addTab: (HLTabWidget on: self new labelled: self tabLabel)!tabClass	^ ''!tabLabel	^ 'Tab'!tabPriority	^ 500! !!HLWidget class methodsFor: 'testing'!canBeOpenAsTab	^ false! !HLWidget subclass: #HLFocusableWidget	instanceVariableNames: ''	package: 'Helios-Core'!!HLFocusableWidget commentStamp!I am a widget that can be focused.## API Instead of overriding `#renderOn:` as with other `Widget` subclasses, my subclasses should override `#renderContentOn:`.To bring the focus to the widget, use the `#focus` method.!!HLFocusableWidget methodsFor: 'accessing'!focusClass	^ 'focused'! !!HLFocusableWidget methodsFor: 'events'!blur	self wrapper asJQuery blur!focus	self wrapper asJQuery focus!hasFocus	^ self wrapper notNil and: [ self wrapper asJQuery is: ':focus' ]! !!HLFocusableWidget methodsFor: 'rendering'!renderContentOn: html!renderOn: html    wrapper := html div     	class: 'hl_widget';		yourself.		       wrapper with: [ self renderContentOn: html ].		wrapper		at: 'tabindex' put: '0';		onBlur: [ self wrapper asJQuery removeClass: self focusClass ];        onFocus: [ self wrapper asJQuery addClass: self focusClass ]! !!HLFocusableWidget methodsFor: 'testing'!canHaveFocus	^ true! !HLFocusableWidget subclass: #HLListWidget	instanceVariableNames: 'items selectedItem mapping'	package: 'Helios-Core'!!HLListWidget methodsFor: 'accessing'!cssClassForItem: anObject	^ ''!items	^ items ifNil: [ items := self defaultItems ]!items: aCollection	items := aCollection!listCssClassForItem: anObject	^ self selectedItem = anObject		ifTrue: [ 'active' ]		ifFalse: [ 'inactive' ]!positionOf: aListItem	<    	return aListItem.parent().children().get().indexOf(aListItem.get(0)) + 1	>!selectedItem	^ selectedItem!selectedItem: anObject	selectedItem := anObject! !!HLListWidget methodsFor: 'actions'!activateFirstListItem	self activateListItem: (window jQuery: ((wrapper asJQuery find: 'li.inactive') get: 0))!activateItem: anObject	self activateListItem: (mapping 		at: anObject		ifAbsent: [ ^ self ]) asJQuery!activateListItem: aListItem	| item |		(aListItem get: 0) ifNil: [ ^self ].	aListItem parent children removeClass: 'active'.	aListItem addClass: 'active'.    	self ensureVisible: aListItem.       "Activate the corresponding item"   item := (self items at: (aListItem attr: 'list-data') asNumber).   self selectedItem == item ifFalse: [	   self selectItem: item ]!activateNextListItem	self activateListItem: (self wrapper asJQuery find: 'li.active') next.		"select the first item if none is selected"	(self wrapper asJQuery find: ' .active') get ifEmpty: [		self activateFirstListItem ]!activatePreviousListItem	self activateListItem: (self wrapper asJQuery find: 'li.active') prev!ensureVisible: aListItem		"Move the scrollbar to show the active element"		| perent position |		position := self positionOf: aListItem.	parent := aListItem parent.	    aListItem position top < 0 ifTrue: [		(parent get: 0) scrollTop: ((parent get: 0) scrollTop + aListItem position top - 10) ].    aListItem position top + aListItem height > parent height ifTrue: [ 		(parent get: 0) scrollTop: ((parent get: 0) scrollTop + aListItem height - (parent height - aListItem position top)) +10 ]!focus	super focus.    self items isEmpty ifFalse: [ 		self selectedItem ifNil: [ self activateFirstListItem ] ]!refresh	super refresh.		self ensureVisible: (mapping 		at: self selectedItem		ifAbsent: [ ^ self ]) asJQuery!selectItem: anObject	self selectedItem: anObject! !!HLListWidget methodsFor: 'defaults'!defaultItems	^ #()! !!HLListWidget methodsFor: 'events'!setupKeyBindings	"TODO: refactor this!!"		| active interval delay repeatInterval |		active := false.	repeatInterval := 70.	self wrapper asJQuery unbind: 'keydown'.	self wrapper asJQuery keydown: [ :e |		        (e which = 38 and: [ active = false ]) ifTrue: [ 			active := true.			self activatePreviousListItem.        	delay := [				interval := [					(self wrapper asJQuery hasClass: self focusClass)						ifTrue: [							self activatePreviousListItem ]						ifFalse: [							active := false.							interval ifNotNil: [ interval clearInterval ].							delay ifNotNil: [ delay clearTimeout] ] ]					valueWithInterval: repeatInterval ]						valueWithTimeout: 300 ].			      	(e which = 40 and: [ active = false ]) ifTrue: [            active := true.			self activateNextListItem.        	delay := [				interval := [ 					(self wrapper asJQuery hasClass: self focusClass)						ifTrue: [							self activateNextListItem ]						ifFalse: [							active := false.							interval ifNotNil: [ interval clearInterval ].							delay ifNotNil: [ delay clearTimeout] ] ]					valueWithInterval: repeatInterval ]						valueWithTimeout: 300 ] ].		self wrapper asJQuery keyup: [ :e |		active ifTrue: [			active := false.			interval ifNotNil: [ interval clearInterval ].			delay ifNotNil: [ delay clearTimeout] ] ]! !!HLListWidget methodsFor: 'initialization'!initialize	super initialize.		mapping := Dictionary new.! !!HLListWidget methodsFor: 'private'!registerMappingFrom: anObject to: aTag	mapping at: anObject put: aTag! !!HLListWidget methodsFor: 'rendering'!renderButtonsOn: html!renderContentOn: html	html ul     	class: 'nav nav-pills nav-stacked';        with: [ self renderListOn: html ].    html div class: 'pane_actions form-actions'; with: [      	self renderButtonsOn: html ].           self setupKeyBindings!renderItem: anObject on: html	| li |    	li := html li.	self registerMappingFrom: anObject to: li.	    li        at: 'list-data' put: (self items indexOf: anObject) asString;		class: (self listCssClassForItem: anObject);        with: [         	html a            	with: [             		(html tag: 'i') class: (self cssClassForItem: anObject).  					self renderItemLabel: anObject on: html ];				onClick: [                  	self activateListItem: li asJQuery ] ]!renderItemLabel: anObject on: html	html with: anObject asString!renderListOn: html	mapping := Dictionary new.		self items do: [ :each |     	self renderItem: each on: html ]! !HLListWidget subclass: #HLNavigationListWidget	instanceVariableNames: 'previous next'	package: 'Helios-Core'!!HLNavigationListWidget methodsFor: 'accessing'!next	^ next!next: aWidget	next := aWidget.    aWidget previous = self ifFalse: [ aWidget previous: self ]!previous	^ previous!previous: aWidget	previous := aWidget.    aWidget next = self ifFalse: [ aWidget next: self ]! !!HLNavigationListWidget methodsFor: 'actions'!nextFocus	self next ifNotNil: [ self next focus ]!previousFocus	self previous ifNotNil: [ self previous focus ]! !!HLNavigationListWidget methodsFor: 'events'!setupKeyBindings	super setupKeyBindings.	self wrapper asJQuery keydown: [ :e |        e which = 39 ifTrue: [         	self nextFocus ].		e which = 37 ifTrue: [         	self previousFocus ] ]! !HLNavigationListWidget subclass: #HLToolListWidget	instanceVariableNames: 'model'	package: 'Helios-Core'!!HLToolListWidget methodsFor: 'accessing'!commandCategory	^ self label!label	^ 'List'!menuCommands	"Answer a collection of commands to be put in the cog menu"		^ ((HLToolCommand concreteClasses		select: [ :each | each isValidFor: self model ])			collect: [ :each | each for: self model ])			select: [ :each | 				each category = self commandCategory and: [ 					each isAction and: [ each isActive ] ] ]!model	^ model!model: aBrowserModel	model := aBrowserModel.        self 		observeSystem;		observeModel!selectedItem: anItem	"Selection changed, update the cog menu"		super selectedItem: anItem.	self updateMenu! !!HLToolListWidget methodsFor: 'actions'!activateListItem: anItem	self model withChangesDo: [ super activateListItem: anItem ]!activateNextListItem	self model withChangesDo: [ super activateNextListItem ]!activatePreviousListItem	self model withChangesDo: [ super activatePreviousListItem ]!observeModel!observeSystem!unregister	super unregister.		self model announcer unsubscribe: self.	self model systemAnnouncer unsubscribe: self! !!HLToolListWidget methodsFor: 'rendering'!renderContentOn: html	self renderHeadOn: html.		super renderContentOn: html!renderHeadOn: html	html div 		class: 'list-label';		with: [			html with: self label.			self renderMenuOn: html ]!renderMenuOn: html	| commands |		commands := self menuCommands.	commands isEmpty ifTrue: [ ^ self ].		html div 		class: 'btn-group cog';		with: [			html a				class: 'btn dropdown-toggle';				at: 'data-toggle' put: 'dropdown';				with: [ (html tag: 'i') class: 'icon-cog' ].		html ul 			class: 'dropdown-menu pull-right';			with: [ 				self menuCommands do: [ :each | 					html li with: [ html a 						with: each menuLabel;						onClick: [ self execute: each ] ] ] ] ]! !!HLToolListWidget methodsFor: 'updating'!updateMenu	(self wrapper asJQuery find: '.cog') remove.		[ :html | self renderMenuOn: html ] 		appendToJQuery: (self wrapper asJQuery find: '.list-label')! !!HLToolListWidget class methodsFor: 'instance creation'!on: aModel	^ self new     	model: aModel;        yourself! !HLWidget subclass: #HLManager	instanceVariableNames: 'tabs activeTab keyBinder environment history'	package: 'Helios-Core'!!HLManager methodsFor: 'accessing'!activeTab	^ activeTab!environment	"The default environment used by all Helios objects"    	^ environment ifNil: [ environment := self defaultEnvironment ]!environment: anEnvironment	environment := anEnvironment!history	^ history ifNil: [ history := OrderedCollection new ]!history: aCollection	history := aCollection!keyBinder	^ keyBinder ifNil: [ keyBinder := HLKeyBinder new ]!tabs	^ tabs ifNil: [ tabs := OrderedCollection new ]! !!HLManager methodsFor: 'actions'!activate: aTab	self keyBinder flushBindings.	aTab registerBindings.	activeTab := aTab.		self 		refresh;		addToHistory: aTab;		show: aTab!addTab: aTab	self tabs add: aTab.    self activate: aTab!addToHistory: aTab	self removeFromHistory: aTab.	self history add: aTab!confirm: aString ifFalse: aBlock	(HLConfirmationWidget new		confirmationString: aString;		cancelBlock: aBlock;		yourself)			appendToJQuery: 'body' asJQuery!confirm: aString ifTrue: aBlock	(HLConfirmationWidget new		confirmationString: aString;		actionBlock: aBlock;		yourself)			appendToJQuery: 'body' asJQuery!registerErrorHandler: anErrorHandler	self environment registerErrorHandler: anErrorHandler!registerInspector: anInspector	self environment registerInspector: anInspector!registerProgressHandler: aProgressHandler	self environment registerProgressHandler: aProgressHandler!removeActiveTab	self removeTab: self activeTab!removeFromHistory: aTab	self history: (self history reject: [ :each | each == aTab ])!removeTab: aTab	(self tabs includes: aTab) ifFalse: [ ^ self ].	self removeFromHistory: aTab.	self tabs remove: aTab.	self keyBinder flushBindings.	aTab remove.	self refresh.	self history ifNotEmpty: [		self history last activate ]!request: aString do: aBlock	self 		request: aString		value: ''		do: aBlock!request: aString value: valueString do: aBlock	(HLRequestWidget new		confirmationString: aString;		actionBlock: aBlock;		value: valueString;		yourself)			appendToJQuery: 'body' asJQuery! !!HLManager methodsFor: 'defaults'!defaultEnvironment	"If helios is loaded from within a frame, answer the parent window environment"		| parent |		parent := window opener ifNil: [ window parent ].	parent ifNil: [ ^ Environment new ].		^ ((parent at: 'smalltalk')		at: 'Environment') new! !!HLManager methodsFor: 'initialization'!initialize	super initialize.		HLErrorHandler register.	HLProgressHandler register.		self registerInspector: HLInspector.	self registerErrorHandler: ErrorHandler current.	self registerProgressHandler: ProgressHandler current.    self keyBinder setupEvents! !!HLManager methodsFor: 'rendering'!refresh	(window jQuery: '.navbar') remove.	self appendToJQuery: 'body' asJQuery!renderAddOn: html    html li     	class: 'dropdown';        with: [ 			html a         		class: 'dropdown-toggle';           	 	at: 'data-toggle' put: 'dropdown';            	with: [             		html with: 'Open...'.  					(html tag: 'b') class: 'caret' ].           html ul            		class: 'dropdown-menu';                with: [                  	((HLWidget withAllSubclasses                    	select: [ :each | each canBeOpenAsTab ])                        sorted: [ :a :b | a tabPriority < b tabPriority ])                        do: [ :each |  							html li with: [                      			html a                                 	with: each tabLabel;      								onClick: [ each openAsTab ] ] ] ] ]!renderContentOn: html	html div 		class: 'navbar navbar-fixed-top';		with: [ html div 			class: 'navbar-inner';			with: [ self renderTabsOn: html ] ]!renderTabsOn: html	html ul 		class: 'nav';		with: [         	self tabs do: [ :each |				html li 					class: (each isActive ifTrue: [ 'active' ] ifFalse: [ 'inactive' ]);					with: [						html a							with: [      							((html tag: 'i') class: 'close')  									onClick: [ self removeTab: each ].                              	html span 									class: each cssClass;									with: each displayLabel ];							onClick: [ each activate ] ] ].			self renderAddOn: html ]!show: aTab	self tabs do: [ :each | each hide ].	aTab show; focus! !HLManager class instanceVariableNames: 'current'!!HLManager class methodsFor: 'accessing'!current	^ current ifNil: [ current := self basicNew initialize ]! !!HLManager class methodsFor: 'initialization'!initialize	self current appendToJQuery: 'body' asJQuery! !!HLManager class methodsFor: 'instance creation'!new	"Use current instead"	self shouldNotImplement! !HLWidget subclass: #HLModalWidget	instanceVariableNames: ''	package: 'Helios-Core'!!HLModalWidget commentStamp!I implement an abstract modal widget.!!HLModalWidget methodsFor: 'accessing'!cssClass	^ ''! !!HLModalWidget methodsFor: 'actions'!cancel	self remove!remove	(window jQuery: '.dialog') removeClass: 'active'.	[ 		(window jQuery: '#overlay') remove.		(window jQuery: '.dialog') remove	] valueWithTimeout: 300! !!HLModalWidget methodsFor: 'rendering'!renderButtonsOn: html!renderContentOn: html	| confirmButton |		html div id: 'overlay'.	html div 		class: 'dialog ', self cssClass;		with: [			self				renderMainOn: html;				renderButtonsOn: html ].	(window jQuery: '.dialog') addClass: 'active'.	self setupKeyBindings!renderMainOn: html!setupKeyBindings	(window jQuery: '.dialog') keyup: [ :e |		e keyCode = 27 ifTrue: [ self cancel ] ]! !HLModalWidget subclass: #HLConfirmationWidget	instanceVariableNames: 'confirmationString actionBlock cancelBlock'	package: 'Helios-Core'!!HLConfirmationWidget commentStamp!I display confirmation messages. Instead of creating an instance directly, use `HLWidget >> #confirm:ifTrue:`.!!HLConfirmationWidget methodsFor: 'accessing'!actionBlock	^ actionBlock ifNil: [ [] ]!actionBlock: aBlock	actionBlock := aBlock!cancelBlock	^ cancelBlock ifNil: [ [] ]!cancelBlock: aBlock	cancelBlock := aBlock!confirmationString	^ confirmationString ifNil: [ 'Confirm' ]!confirmationString: aString	confirmationString := aString! !!HLConfirmationWidget methodsFor: 'actions'!cancel	self cancelBlock value.	self remove!confirm	self actionBlock value.	self remove!remove	(window jQuery: '.dialog') removeClass: 'active'.	[ 		(window jQuery: '#overlay') remove.		(window jQuery: '.dialog') remove	] valueWithTimeout: 300! !!HLConfirmationWidget methodsFor: 'rendering'!renderButtonsOn: html	| confirmButton |		html div 		class: 'buttons';		with: [			html button				class: 'button';				with: 'Cancel';				onClick: [ self cancel ].			confirmButton := html button				class: 'button default';				with: 'Confirm';				onClick: [ self confirm ] ].	confirmButton asJQuery focus!renderMainOn: html	html span with: self confirmationString! !HLConfirmationWidget subclass: #HLRequestWidget	instanceVariableNames: 'input value'	package: 'Helios-Core'!!HLRequestWidget commentStamp!I display a modal window requesting user input.Instead of creating instances manually, use `HLWidget >> #request:do:` and `#request:value:do:`.!!HLRequestWidget methodsFor: 'accessing'!cssClass	^ 'large'!value	^ value ifNil: [ '' ]!value: aString	value := aString! !!HLRequestWidget methodsFor: 'actions'!confirm	self actionBlock value: input asJQuery val.	self remove! !!HLRequestWidget methodsFor: 'rendering'!renderMainOn: html	super renderMainOn: html.	input := html textarea.	input asJQuery val: self value! !HLModalWidget subclass: #HLProgressWidget	instanceVariableNames: 'progressBars visible'	package: 'Helios-Core'!!HLProgressWidget commentStamp!I am a widget used to display progress modal dialogs.My default instance is accessed with `HLProgressWidget class >> #default`.See `HLProgressHandler` for usage.!!HLProgressWidget methodsFor: 'accessing'!progressBars	^ progressBars ifNil: [ progressBars := OrderedCollection new ]! !!HLProgressWidget methodsFor: 'actions'!addProgressBar: aProgressBar	self show.	self progressBars add: aProgressBar.	aProgressBar appendToJQuery: (self wrapper asJQuery find: '.dialog')!do: aBlock on: aCollection displaying: aString	| progressBar |		progressBar := HLProgressBarWidget new		parent: self;		label: aString;		workBlock: aBlock;		collection: aCollection;		yourself.		self addProgressBar: progressBar.	progressBar start!flush	self progressBars do: [ :each |		self removeProgressBar: each ]!remove	self isVisible ifTrue: [		visible := false.		super remove ]!removeProgressBar: aProgressBar	self progressBars remove: aProgressBar ifAbsent: [].	aProgressBar wrapper asJQuery remove.		self progressBars ifEmpty: [ self remove ]!show	self isVisible ifFalse: [		visible := true.		self appendToJQuery: 'body' asJQuery ]! !!HLProgressWidget methodsFor: 'rendering'!renderButtonsOn: html!renderMainOn: html	self progressBars do: [ :each |		html with: each ]! !!HLProgressWidget methodsFor: 'testing'!isVisible	^ visible ifNil: [ false ]! !HLProgressWidget class instanceVariableNames: 'default'!!HLProgressWidget class methodsFor: 'accessing'!default	^ default ifNil: [ default := self new ]! !HLWidget subclass: #HLProgressBarWidget	instanceVariableNames: 'label parent workBlock collection bar'	package: 'Helios-Core'!!HLProgressBarWidget commentStamp!I am a widget used to display a progress bar while iterating over a collection.!!HLProgressBarWidget methodsFor: 'accessing'!collection	^ collection!collection: aCollection	collection := aCollection!label	^ label!label: aString	label := aString!parent	^ parent!parent: aProgress	parent := aProgress!workBlock	^ workBlock!workBlock: aBlock	workBlock := aBlock! !!HLProgressBarWidget methodsFor: 'actions'!evaluateAt: anInteger	self updateProgress: (anInteger / self collection size) * 100.	anInteger <= self collection size		ifTrue: [ 			[ 				self workBlock value: (self collection at: anInteger).				self evaluateAt: anInteger + 1 ] valueWithTimeout: 10 ]		ifFalse: [ [ self remove ] valueWithTimeout: 500 ]!remove	self parent removeProgressBar: self!start	"Make sure the UI has some time to update itself between each iteration"		self evaluateAt: 1!updateProgress: anInteger	bar asJQuery css: 'width' put: anInteger asString, '%'! !!HLProgressBarWidget methodsFor: 'rendering'!renderContentOn: html	html span with: self label.	html div 		class: 'progress';		with: [			bar := html div 				class: 'bar';				style: 'width: 0%' ]! !HLProgressBarWidget class instanceVariableNames: 'default'!!HLProgressBarWidget class methodsFor: 'accessing'!default	^ default ifNil: [ default := self new ]! !HLWidget subclass: #HLSUnit	instanceVariableNames: ''	package: 'Helios-Core'!!HLSUnit class methodsFor: 'accessing'!tabClass	^ 'sunit'!tabLabel	^ 'SUnit'!tabPriority	^ 1000! !!HLSUnit class methodsFor: 'testing'!canBeOpenAsTab	^ true! !
 |