123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707 |
- 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.
- ## API
- 1. 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'!
- bindKeyDown: keyDownBlock up: keyUpBlock
- self wrapper asJQuery
- keydown: keyDownBlock;
- keyup: keyUpBlock
- !
- registerBindings
- self registerBindingsOn: self manager keyBinder bindings
- !
- registerBindingsOn: aBindingGroup
- !
- unbindKeyDownUp
- self wrapper asJQuery
- unbind: 'keydown';
- unbind: 'keyup'
- ! !
- !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
- ! !
- !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
- !
- hasFocus
- ^ self wrapper notNil and: [ self wrapper asJQuery hasClass: self focusClass ]
- ! !
- 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
- (HLRepeatingKeyBindingHandler forWidget: self)
- whileKeyPressed: 38 do: [ self activatePreviousListItem ];
- whileKeyPressed: 40 do: [ self activateNextListItem ];
- rebindKeys
- ! !
- !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.
- self clearKeydownEvent
- ! !
- !HLManager class methodsFor: 'instance creation'!
- new
- "Use current instead"
- self shouldNotImplement
- ! !
- !HLManager class methodsFor: 'private'!
- clearKeydownEvent
- "Prevent default keydown event with arrow key from scrolling the parent page
- when helios is run inside a frame."
-
- (window jQuery: 'body') keydown: [ :e |
- (e keyCode >= 37 and: [ e keyCode <= 40 ])
- ifTrue: [ false ] ]
- ! !
- 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
- ! !
|