123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097209820992100210121022103210421052106210721082109211021112112211321142115211621172118211921202121212221232124212521262127212821292130213121322133213421352136213721382139214021412142214321442145214621472148214921502151215221532154215521562157215821592160216121622163216421652166216721682169217021712172217321742175217621772178217921802181218221832184218521862187218821892190219121922193219421952196219721982199220022012202220322042205220622072208220922102211221222132214221522162217221822192220222122222223222422252226222722282229223022312232223322342235223622372238223922402241224222432244224522462247224822492250225122522253225422552256225722582259226022612262226322642265226622672268226922702271227222732274227522762277227822792280228122822283228422852286228722882289229022912292229322942295229622972298229923002301230223032304230523062307230823092310231123122313231423152316231723182319232023212322232323242325232623272328232923302331233223332334233523362337233823392340234123422343234423452346234723482349235023512352235323542355235623572358235923602361236223632364236523662367236823692370237123722373237423752376237723782379238023812382238323842385238623872388238923902391239223932394239523962397239823992400240124022403240424052406240724082409241024112412241324142415241624172418241924202421242224232424242524262427242824292430243124322433243424352436243724382439244024412442244324442445244624472448244924502451245224532454245524562457 |
- Smalltalk createPackage: 'Helios-Core'!
- Object subclass: #HLModel
- slots: {#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;
- yourself).
- aBlock value.
- ]
- on: HLChangeForbidden
- do: [ :ex | ]
- ! !
- !HLModel methodsFor: 'testing'!
- isBrowserModel
- ^ false
- !
- isReferencesModel
- ^ false
- !
- isToolModel
- ^ false
- ! !
- HLModel subclass: #HLFinder
- slots: {}
- package: 'Helios-Core'!
- !HLFinder commentStamp!
- I am the `Finder` service handler of Helios.
- Finding a class will open a new class browser, while finding a method will open a references browser.!
- !HLFinder methodsFor: 'finding'!
- findClass: aClass
- HLBrowser openAsTab openClassNamed: aClass name
- !
- findMethod: aCompiledMethod
- HLBrowser openAsTab openMethod: aCompiledMethod
- !
- findString: aString
- | foundClass |
-
- foundClass := self environment classes
- detect: [ :each | each name = aString ]
- ifNone: [ nil ].
-
- foundClass
- ifNil: [ HLReferences openAsTab search: aString ]
- ifNotNil: [ self findClass: foundClass ]
- ! !
- HLModel subclass: #HLToolModel
- slots: {#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
- !
- packageToCommit
- "Answer the package to commit depending on the context:
- - if a Method is selected, answer its package
- - else answer the `selectedPackage`"
-
- ^ self selectedMethod
- ifNil: [ self selectedPackage ]
- ifNotNil: [ :method | method package ]
- !
- packages
- ^ self environment packages
- !
- selectedClass
- ^ selectedClass
- !
- selectedClass: aClass
- (self selectedClass = aClass and: [ aClass isNil ])
- ifTrue: [ ^ self ].
-
- self withChangesDo: [
- aClass
- ifNil: [ selectedClass := nil ]
- ifNotNil: [
- self selectedPackage: aClass theNonMetaClass package.
- self showInstance
- ifTrue: [ selectedClass := aClass theNonMetaClass ]
- ifFalse: [ selectedClass := aClass theMetaClass ] ].
- selectedProtocol := nil.
- self selectedProtocol: self allProtocol.
- 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: [
- selectedSelector := aCompiledMethod selector.
- (selectedClass notNil and: [ selectedClass methodDictionary includesKey: selectedSelector ]) ifFalse: [
- selectedClass := aCompiledMethod methodClass.
- selectedPackage := selectedClass theNonMetaClass package ] ].
- 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) ]
- !
- softSelectedClass: aClass
- self announcer announce: (HLClassSelected softOn: aClass)
- !
- softSelectedMethod: aMethod
- self announcer announce: (HLMethodSelected softOn: aMethod)
- !
- softSelectedPackage: aPackage
- self announcer announce: (HLPackageSelected softOn: aPackage)
- !
- softSelectedProtocol: aProtocol
- self announcer announce: (HLProtocolSelected softOn: aProtocol)
- ! !
- !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 shouldCompileDefinition: aString)
- ifTrue: [ self compileClassDefinition: aString ]
- ifFalse: [ self compileMethod: aString ]
- !
- saveSourceCode
- self announcer announce: HLSaveSourceCode new
- ! !
- !HLToolModel methodsFor: 'commands actions'!
- commitPackageOnSuccess: aBlock onError: anotherBlock
- self environment
- commitPackage: self packageToCommit
- onSuccess: aBlock
- onError: anotherBlock
- !
- copyClassTo: aClassName
- self withChangesDo: [
- self environment
- copyClass: self selectedClass theNonMetaClass
- to: aClassName.
- self selectedClass: (self environment classNamed: 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 theNonMetaClass name
- ifTrue: [ self environment removeClass: self selectedClass theNonMetaClass ] ]
- !
- removeMethod
- self withChangesDo: [
- self manager
- confirm: 'Do you REALLY want to remove method ', self selectedMethod origin 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 ]
- !
- renamePackageTo: aPackageName
- self withChangesDo: [
- self environment
- renamePackage: self selectedPackage name
- to: aPackageName ]
- !
- 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"
- '#helper' asJQuery remove.
- [ :html |
- html div
- id: 'helper';
- with: aString ] appendToJQuery: 'body' asJQuery.
-
- [
- aBlock value.
- '#helper' asJQuery remove ] fork
- ! !
- !HLToolModel methodsFor: 'testing'!
- isToolModel
- ^ true
- !
- shouldCompileDefinition: aString
- ^ self selectedClass isNil or: [
- aString match: '^\s*[A-Z]' ]
- ! !
- !HLToolModel class methodsFor: 'actions'!
- on: anEnvironment
- ^ self new
- environment: anEnvironment;
- yourself
- ! !
- Object subclass: #HLProgressHandler
- slots: {}
- 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: #HLWidget
- slots: {#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'!
- cssClass
- ^ 'hl_widget'
- !
- manager
- ^ HLManager current
- !
- removeTab
- self manager removeTabForWidget: self
- !
- setTabLabel: aString
- self manager announcer announce: (HLTabLabelChanged new
- widget: self;
- label: aString;
- yourself)
- !
- tabClass
- ^ self class tabClass
- !
- wrapper
- ^ wrapper
- ! !
- !HLWidget methodsFor: 'actions'!
- confirm: aString ifTrue: aBlock
- self manager confirm: aString ifTrue: aBlock
- !
- confirm: aString ifTrue: aBlock ifFalse: anotherBlock
- self manager
- confirm: aString
- ifTrue: aBlock
- ifFalse: anotherBlock
- !
- execute: aCommand
- HLManager current keyBinder
- activate;
- applyBinding: aCommand asBinding
- !
- inform: aString
- self manager inform: aString
- !
- openAsTab
- (HLTabWidget on: self labelled: self defaultTabLabel)
- add
- !
- 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: 'defaults'!
- defaultTabLabel
- ^ self class tabLabel
- ! !
- !HLWidget methodsFor: 'keybindings'!
- bindKeyDown: keyDownBlock keyUp: keyUpBlock
- self wrapper ifNotNil: [ :wrappr | wrappr asJQuery
- keydown: keyDownBlock;
- keyup: keyUpBlock ]
- !
- registerBindings
- self registerBindingsOn: self manager keyBinder bindings
- !
- registerBindingsOn: aBindingGroup
- !
- unbindKeyDownKeyUp
- self wrapper asJQuery
- unbind: 'keydown';
- unbind: 'keyup'
- ! !
- !HLWidget methodsFor: 'rendering'!
- renderContentOn: html
- !
- renderOn: html
- wrapper := html div
- class: self cssClass;
- yourself.
- "must do this later, as renderContentOn may want to use self wrapper"
- wrapper with: [ self renderContentOn: html ]
- ! !
- !HLWidget methodsFor: 'testing'!
- canHaveFocus
- ^ false
- ! !
- !HLWidget methodsFor: 'updating'!
- refresh
- self wrapper
- ifNotNil: [ :wrap | wrap contents: [ :html | self renderContentOn: html ] ]
- ! !
- !HLWidget class methodsFor: 'accessing'!
- openAsTab
- | instance |
-
- instance := self new.
- (HLTabWidget
- on: instance
- labelled: instance defaultTabLabel) add.
- ^ instance
- !
- tabClass
- ^ ''
- !
- tabLabel
- ^ 'Tab'
- !
- tabPriority
- ^ 500
- ! !
- !HLWidget class methodsFor: 'testing'!
- canBeOpenAsTab
- ^ false
- ! !
- HLWidget subclass: #HLFocusableWidget
- slots: {}
- 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: self cssClass;
- at: 'tabindex' put: '0';
- onBlur: [ self wrapper asJQuery removeClass: self focusClass ];
- onFocus: [ self wrapper asJQuery addClass: self focusClass ];
- yourself.
- "must do this later, as renderContentOn may want to use self wrapper"
- wrapper with: [ self renderContentOn: html ]
- ! !
- !HLFocusableWidget methodsFor: 'testing'!
- canHaveFocus
- ^ true
- !
- hasFocus
- ^ self wrapper notNil and: [ self wrapper asJQuery hasClass: self focusClass ]
- ! !
- HLFocusableWidget subclass: #HLListWidget
- slots: {#items. #selectedItem}
- package: 'Helios-Core'!
- !HLListWidget methodsFor: 'accessing'!
- activeItemCssClass
- ^'active'
- !
- buttonsDivCssClass
- ^ 'pane_actions form-group'
- !
- cssClassForItem: anObject
- ^ ''
- !
- findListItemFor: anObject
- ^ (((wrapper asJQuery find: 'li')
- filter: [ :thisArg :otherArg | (thisArg asJQuery data: 'item') = anObject ] currySelf) eq: 0)
- !
- items
- ^ items ifNil: [ items := self defaultItems ]
- !
- items: aCollection
- items := aCollection
- !
- listCssClass
- ^'nav nav-pills nav-stacked'
- !
- listCssClassForItem: anObject
- ^ self selectedItem = anObject
- ifTrue: [ self activeItemCssClass ]
- ifFalse: [ 'inactive' ]
- !
- positionOf: aListItem
- <inlineJS: '
- return aListItem.parent().children().get().indexOf(aListItem.get(0)) + 1
- '>
- !
- selectedItem
- ^ selectedItem
- !
- selectedItem: anObject
- selectedItem := anObject
- ! !
- !HLListWidget methodsFor: 'actions'!
- activateFirstListItem
- self activateListItem: ((wrapper asJQuery find: 'li.inactive') eq: 0)
- !
- activateItem: anObject
- self activateListItem: (self findListItemFor: anObject)
- !
- activateListItem: aListItem
- | item |
-
- (aListItem get: 0) ifNil: [ ^ self ].
- aListItem parent children removeClass: self activeItemCssClass.
- aListItem addClass: self activeItemCssClass.
-
- self ensureVisible: aListItem.
-
- "Activate the corresponding item"
- item := aListItem data: 'item'.
- self selectedItem == item ifFalse: [
- self selectItem: item ]
- !
- activateNextListItem
- self activateListItem: (self wrapper asJQuery find: ('li.', self activeItemCssClass)) next.
-
- "select the first item if none is selected"
- (self wrapper asJQuery find: (' .', self activeItemCssClass)) get ifEmpty: [
- self activateFirstListItem ]
- !
- activatePreviousListItem
- self activateListItem: (self wrapper asJQuery find: ('li.', self activeItemCssClass)) prev
- !
- ensureVisible: aListItem
- "Move the scrollbar to show the active element"
-
- | parent position |
- (aListItem get: 0) ifNil: [ ^ self ].
- 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 ifNotEmpty: [
- self selectedItem ifNil: [ self activateFirstListItem ] ]
- !
- reactivateListItem: aListItem
- self activateListItem: aListItem.
- self reselectItem: self selectedItem
- !
- refresh
- super refresh.
- self selectedItem ifNotNil: [self ensureVisible: (self findListItemFor: self selectedItem)].
- !
- reselectItem: anObject
- !
- selectItem: anObject
- self selectedItem: anObject
- ! !
- !HLListWidget methodsFor: 'defaults'!
- defaultItems
- ^ #()
- ! !
- !HLListWidget methodsFor: 'events'!
- setupKeyBindings
- (HLRepeatedKeyDownHandler on: self)
- whileKeyDown: 38 do: [ self activatePreviousListItem ];
- whileKeyDown: 40 do: [ self activateNextListItem ];
- rebindKeys.
-
- self wrapper asJQuery keydown: [ :e |
- e which = 13 ifTrue: [
- self reselectItem: self selectedItem ] ]
- ! !
- !HLListWidget methodsFor: 'rendering'!
- renderButtonsOn: html
- !
- renderContentOn: html
- |ul|
-
- ul := html ul
- class: self listCssClass;
- with: [ self renderListOn: html ];
- onClick: [ self focus ].
-
- ul asJQuery contextmenu: [ self toggleCommandsMenu. false].
-
- html div class: self buttonsDivCssClass; with: [
- self renderButtonsOn: html ].
-
- self setupKeyBindings
- !
- renderItemLabel: anObject on: html
- html with: anObject asString
- !
- renderItemModel: anObject viewModel: anotherObject on: html
- | li |
-
- li := html li.
- li asJQuery data: 'item' put: anObject.
- li
- class: (self listCssClassForItem: anObject);
- with: [
- html a
- with: [
- (html tag: 'i') class: (self cssClassForItem: anObject).
- self renderItemLabel: anotherObject on: html ];
- onClick: [
- self reactivateListItem: li asJQuery ] ]
- !
- renderListOn: html
- self items do: [ :each |
- self renderItemModel: each viewModel: each on: html ]
- ! !
- HLListWidget subclass: #HLNavigationListWidget
- slots: {#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 ifNotNil: [ wrapper onKeyDown: [ :e |
- e which = 39 ifTrue: [
- self nextFocus ].
- e which = 37 ifTrue: [
- self previousFocus ] ] ]
- ! !
- HLNavigationListWidget subclass: #HLToolListWidget
- slots: {#model. #commandsMenuElement}
- 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
- !
- reactivateListItem: anItem
- self model withChangesDo: [ super reactivateListItem: anItem ]
- !
- toggleCommandsMenu
- commandsMenuElement asJQuery dropdown: 'toggle'
- !
- 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 ifEmpty: [ ^ self ].
-
- html div
- class: 'btn-group cog';
- with: [
- commandsMenuElement := html a
- class: 'btn btn-default dropdown-toggle';
- at: 'data-toggle' put: 'dropdown';
- with: [ (html tag: 'i') class: 'glyphicon glyphicon-chevron-down' ].
- html ul
- class: 'dropdown-menu pull-right';
- with: [
- commands 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
- ! !
- HLListWidget subclass: #HLTabListWidget
- slots: {#callback}
- package: 'Helios-Core'!
- !HLTabListWidget commentStamp!
- I am a widget used to display a list of helios tabs.
- When a tab is selected, `callback` is evaluated with the selected tab as argument.!
- !HLTabListWidget methodsFor: 'accessing'!
- callback
- ^ callback ifNil: [ [] ]
- !
- callback: aBlock
- callback := aBlock
- ! !
- !HLTabListWidget methodsFor: 'actions'!
- selectItem: aTab
- super selectItem: aTab.
- self callback value: aTab
- ! !
- !HLTabListWidget methodsFor: 'rendering'!
- renderItemLabel: aTab on: html
- html span
- class: aTab cssClass;
- with: aTab label
- ! !
- HLWidget subclass: #HLInformationWidget
- slots: {#informationString}
- package: 'Helios-Core'!
- !HLInformationWidget commentStamp!
- I display an information dialog.
- ## API
- `HLWidget >> #inform:` is a convenience method for creating information dialogs.!
- !HLInformationWidget methodsFor: 'accessing'!
- informationString
- ^ informationString ifNil: [ '' ]
- !
- informationString: anObject
- informationString := anObject
- ! !
- !HLInformationWidget methodsFor: 'actions'!
- remove
- [
- self wrapper asJQuery fadeOut: 100.
- [ self wrapper asJQuery remove ]
- valueWithTimeout: 400.
- ]
- valueWithTimeout: 1500
- !
- show
- self appendToJQuery: 'body' asJQuery
- ! !
- !HLInformationWidget methodsFor: 'rendering'!
- renderContentOn: html
- html div
- class: 'growl';
- with: self informationString.
-
- self remove
- ! !
- HLWidget subclass: #HLManager
- slots: {#tabsWidget. #environment. #history. #announcer. #rendered}
- package: 'Helios-Core'!
- !HLManager commentStamp!
- HLManager is the entry point Class of Helios.
- Its `singleton` instance is created on startup, and rendered on body.!
- !HLManager methodsFor: 'accessing'!
- activeTab
- ^ self tabsWidget activeTab
- !
- announcer
- ^ announcer ifNil: [ announcer := Announcer new ]
- !
- 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
- ^ HLKeyBinder current
- !
- setEditorTheme: aTheme
- 'helios.editorTheme' asSetting value: aTheme
- !
- setTheme: aTheme
- | currentTheme |
- currentTheme := 'helios.theme' asSettingIfAbsent: 'default'.
-
- 'body' asJQuery
- removeClass: currentTheme value;
- addClass: aTheme.
-
-
- 'helios.theme' asSetting value: aTheme
- !
- tabWidth
- ^ (window asJQuery width - 90) / self tabs size
- !
- tabs
- ^ self tabsWidget tabs
- !
- tabsWidget
- ^ tabsWidget ifNil: [ tabsWidget := HLTabsWidget new ]
- ! !
- !HLManager methodsFor: 'actions'!
- activate: aTab
- self tabsWidget activate: aTab
- !
- addTab: aTab
- self tabsWidget addTab: aTab
- !
- confirm: aString ifFalse: aBlock
- self
- confirm: aString
- ifTrue: []
- ifFalse: aBlock
- !
- confirm: aString ifTrue: aBlock
- self
- confirm: aString
- ifTrue: aBlock
- ifFalse: []
- !
- confirm: aString ifTrue: aBlock ifFalse: anotherBlock
- HLConfirmationWidget new
- confirmationString: aString;
- actionBlock: aBlock;
- cancelBlock: anotherBlock;
- show
- !
- handleLossOfEnvironmentWithParent: parent
- parent at: 'onunload' put: [
- self removeBeforeUnloadMessage.
- window close ]
- !
- inform: aString
- HLInformationWidget new
- informationString: aString;
- show
- !
- removeActiveTab
- self tabsWidget removeActiveTab
- !
- removeBeforeUnloadMessage
- <inlineJS: 'window.onbeforeunload = null'>
- !
- removeTabForWidget: aWidget
- self tabsWidget removeTabForWidget: aWidget
- !
- request: aString do: aBlock
- self
- request: aString
- value: ''
- do: aBlock
- !
- request: aString value: valueString do: aBlock
- HLRequestWidget new
- confirmationString: aString;
- actionBlock: aBlock;
- value: valueString;
- show
- ! !
- !HLManager methodsFor: 'defaults'!
- defaultEnvironment
- "If helios is loaded from within a frame, answer the parent window environment"
-
- | parent parentSmalltalkGlobals |
-
- parent := window opener ifNil: [ window parent ].
- parent ifNil: [ ^ Environment new ].
-
- parentSmalltalkGlobals := ((parent at: 'requirejs') value: 'amber/boot') at: 'globals'.
- parentSmalltalkGlobals ifNil: [ ^ Environment new ].
-
- self handleLossOfEnvironmentWithParent: parent.
-
- ^ (parentSmalltalkGlobals at: 'Environment') new
- ! !
- !HLManager methodsFor: 'initialization'!
- initialize
- super initialize.
- rendered := false
- !
- setup
- self
- registerServices;
- setupEvents.
- self keyBinder setupEvents.
- self tabsWidget setupEvents.
- self setupTheme.
-
-
- '#helper' asJQuery fadeOut
- ! !
- !HLManager methodsFor: 'private'!
- registerServices
- self
- registerInspector;
- registerErrorHandler;
- registerProgressHandler;
- registerTranscript;
- registerFinder
- !
- setupEvents
- 'body' asJQuery keydown: [ :event |
-
- "On ctrl keydown, adds a 'navigation' css class to <body>
- for the CodeMirror navigation links. See `HLCodeWidget`."
- event ctrlKey ifTrue: [
- 'body' asJQuery addClass: 'navigation' ] ].
-
- 'body' asJQuery keyup: [ :event |
- 'body' asJQuery removeClass: 'navigation' ].
-
- window asJQuery resize: [ :event |
- self refresh ]
- !
- setupTheme
- "self
- setTheme: 'niflheim';
- setEditorTheme: 'niflheim'."
-
- self
- setTheme: 'default';
- setEditorTheme: 'default'.
- ! !
- !HLManager methodsFor: 'rendering'!
- renderContentOn: html
- html with: self tabsWidget.
- html with: HLWelcomeWidget new.
-
- self renderDefaultTabs.
- rendered := true
- !
- renderDefaultTabs
- rendered ifFalse: [
- HLWorkspace openAsTab.
- HLBrowser openAsTab ]
- ! !
- !HLManager methodsFor: 'services'!
- registerErrorHandler
- | handler |
- handler := HLErrorHandler new.
- self environment registerErrorHandler: handler.
- ErrorHandler register: handler
- !
- registerFinder
- self environment registerFinder: HLFinder new.
- Finder register: HLFinder new
- !
- registerInspector
- self environment registerInspector: HLInspector.
- Inspector register: HLInspector
- !
- registerProgressHandler
- self environment registerProgressHandler: HLProgressHandler new.
- ProgressHandler register: HLProgressHandler new
- !
- registerTranscript
- self environment registerTranscript: HLTranscriptHandler
- ! !
- HLManager class slots: {#current}!
- !HLManager class methodsFor: 'accessing'!
- current
- ^ current ifNil: [ current := self basicNew initialize ]
- ! !
- !HLManager class methodsFor: 'initialization'!
- setup
- self current
- setup;
- appendToJQuery: 'body' asJQuery.
-
- ('helios.confirmOnExit' settingValueIfAbsent: true) ifTrue: [
- window onbeforeunload: [ 'Do you want to close Amber? All uncommitted changes will be lost.' ] ]
- ! !
- !HLManager class methodsFor: 'instance creation'!
- new
- "Use current instead"
- self shouldNotImplement
- ! !
- HLWidget subclass: #HLModalWidget
- slots: {}
- package: 'Helios-Core'!
- !HLModalWidget commentStamp!
- I implement an abstract modal widget.!
- !HLModalWidget methodsFor: 'actions'!
- remove
- '.dialog' asJQuery removeClass: 'active'.
- HLModalWidget current: nil.
- '#overlay' asJQuery remove.
- [
- wrapper asJQuery remove
- ] valueWithTimeout: 300
- !
- show
- HLModalWidget current ifNotNil: [ :old | old remove ].
- HLModalWidget current: self.
- self appendToJQuery: 'body' asJQuery
- ! !
- !HLModalWidget methodsFor: 'private'!
- giveFocusToButton: aButton
- aButton asJQuery focus
- ! !
- !HLModalWidget methodsFor: 'rendering'!
- hasButtons
- ^ true
- !
- renderButtonsOn: html
- !
- renderContentOn: html
- | confirmButton |
-
- html div id: 'overlay'.
-
- html div
- class: 'dialog ', self cssClass;
- with: [
- self renderMainOn: html.
- self hasButtons ifTrue: [
- self renderButtonsOn: html ] ].
- '.dialog' asJQuery addClass: 'active'.
- self setupKeyBindings
- !
- renderMainOn: html
- !
- setupKeyBindings
- '.dialog' asJQuery keyup: [ :e |
- e keyCode = String esc asciiValue ifTrue: [ self cancel ] ]
- ! !
- HLModalWidget class slots: {#current}!
- !HLModalWidget class methodsFor: 'accessing'!
- current
- ^ current
- !
- current: anHLModelWidget
- current := anHLModelWidget
- ! !
- HLModalWidget subclass: #HLConfirmationWidget
- slots: {#cancelButtonLabel. #confirmButtonLabel. #confirmationString. #actionBlock. #cancelBlock}
- package: 'Helios-Core'!
- !HLConfirmationWidget commentStamp!
- I display confirmation dialog.
- ## API
- HLWidget contains convenience methods like `HLWidget >> #confirm:ifTrue:` for creating confirmation dialogs.!
- !HLConfirmationWidget methodsFor: 'accessing'!
- actionBlock
- ^ actionBlock ifNil: [ [] ]
- !
- actionBlock: aBlock
- actionBlock := aBlock
- !
- cancelBlock
- ^ cancelBlock ifNil: [ [] ]
- !
- cancelBlock: aBlock
- cancelBlock := aBlock
- !
- cancelButtonLabel
- ^ cancelButtonLabel ifNil: [ 'Cancel' ]
- !
- cancelButtonLabel: aString
- ^ cancelButtonLabel := aString
- !
- confirmButtonLabel
- ^ confirmButtonLabel ifNil: [ 'Confirm' ]
- !
- confirmButtonLabel: aString
- ^ confirmButtonLabel := aString
- !
- confirmationString
- ^ confirmationString ifNil: [ 'Confirm' ]
- !
- confirmationString: aString
- confirmationString := aString
- ! !
- !HLConfirmationWidget methodsFor: 'actions'!
- cancel
- self cancelBlock value.
- self remove
- !
- confirm
- self remove.
- self actionBlock value
- ! !
- !HLConfirmationWidget methodsFor: 'rendering'!
- renderButtonsOn: html
- | confirmButton |
-
- html div
- class: 'buttons';
- with: [
- html button
- class: 'button';
- with: self cancelButtonLabel;
- onClick: [ self cancel ].
- confirmButton := html button
- class: 'button default';
- with: self confirmButtonLabel;
- onClick: [ self confirm ] ].
- self giveFocusToButton:confirmButton
- !
- renderMainOn: html
- html span
- class: 'head';
- with: self confirmationString
- ! !
- HLConfirmationWidget subclass: #HLRequestWidget
- slots: {#input. #multiline. #value}
- package: 'Helios-Core'!
- !HLRequestWidget commentStamp!
- I display a modal window requesting user input.
- ## API
- `HLWidget >> #request:do:` and `#request:value:do:` are convenience methods for creating modal request dialogs.!
- !HLRequestWidget methodsFor: 'accessing'!
- beMultiline
- multiline := true
- !
- beSingleline
- multiline := false
- !
- cssClass
- ^ 'large'
- !
- value
- ^ value ifNil: [ '' ]
- !
- value: aString
- value := aString
- ! !
- !HLRequestWidget methodsFor: 'actions'!
- confirm
- | val |
- val := input asJQuery val.
- self remove.
- self actionBlock value: val
- ! !
- !HLRequestWidget methodsFor: 'private'!
- giveFocusToButton: aButton
- ! !
- !HLRequestWidget methodsFor: 'rendering'!
- renderMainOn: html
- super renderMainOn: html.
- self isMultiline
- ifTrue: [ input := html textarea ]
- ifFalse: [ input := html input
- type: 'text';
- onKeyDown: [ :event |
- event keyCode = 13 ifTrue: [
- self confirm ] ];
- yourself ].
- input asJQuery
- val: self value;
- focus
- ! !
- !HLRequestWidget methodsFor: 'testing'!
- isMultiline
- ^ multiline ifNil: [ true ]
- ! !
- HLModalWidget subclass: #HLProgressWidget
- slots: {#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.
- super show ]
- ! !
- !HLProgressWidget methodsFor: 'rendering'!
- renderMainOn: html
- self progressBars do: [ :each |
- html with: each ]
- ! !
- !HLProgressWidget methodsFor: 'testing'!
- hasButtons
- ^ false
- !
- isVisible
- ^ visible ifNil: [ false ]
- ! !
- HLProgressWidget class slots: {#default}!
- !HLProgressWidget class methodsFor: 'accessing'!
- default
- ^ default ifNil: [ default := self new ]
- ! !
- HLModalWidget subclass: #HLTabSelectionWidget
- slots: {#tabs. #tabList. #selectedTab. #selectCallback. #cancelCallback. #confirmCallback}
- package: 'Helios-Core'!
- !HLTabSelectionWidget commentStamp!
- I am a modal window used to select or create tabs.!
- !HLTabSelectionWidget methodsFor: 'accessing'!
- cancelCallback
- ^ cancelCallback ifNil: [ [] ]
- !
- cancelCallback: aBlock
- cancelCallback := aBlock
- !
- confirmCallback
- ^ confirmCallback ifNil: [ [] ]
- !
- confirmCallback: aBlock
- confirmCallback := aBlock
- !
- selectCallback
- ^ selectCallback ifNil: [ [] ]
- !
- selectCallback: aBlock
- selectCallback := aBlock
- !
- selectedTab
- ^ selectedTab
- !
- selectedTab: aTab
- selectedTab := aTab
- !
- tabs
- ^ tabs ifNil: [ #() ]
- !
- tabs: aCollection
- tabs := aCollection
- ! !
- !HLTabSelectionWidget methodsFor: 'actions'!
- cancel
- self remove.
- self cancelCallback value
- !
- confirm
- self remove.
- self confirmCallback value: self selectedTab
- !
- selectTab: aTab
- self selectedTab: aTab.
- self selectCallback value: aTab
- !
- setupKeyBindings
- super setupKeyBindings.
- '.dialog' asJQuery keyup: [ :e |
- e keyCode = String cr asciiValue ifTrue: [ self confirm ] ]
- ! !
- !HLTabSelectionWidget 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: 'Select tab';
- onClick: [ self confirm ] ].
- self giveFocusToButton:confirmButton
- !
- renderContentOn: html
- super renderContentOn: html.
- self tabList focus
- !
- renderMainOn: html
- html div
- class: 'title';
- with: 'Tab selection'.
-
- html with: self tabList
- !
- renderTab: aTab on: html
- html
- span
- class: aTab cssClass;
- with: aTab label
- !
- renderTabsOn: html
- self tabs do: [ :each |
- html li with: [
- html a
- with: [
- self renderTab: each on: html ];
- onClick: [ self selectTab: each ] ] ]
- !
- tabList
- tabList ifNil: [
- tabList := HLTabListWidget new.
- tabList
- callback: [ :tab | self selectTab: tab. tabList focus ];
- selectedItem: self selectedTab;
- items: self tabs ].
-
- ^ tabList
- ! !
- HLWidget subclass: #HLProgressBarWidget
- slots: {#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) rounded.
- anInteger <= self collection size
- ifTrue: [
- [
- self workBlock value: (self collection at: anInteger).
- self evaluateAt: anInteger + 1 ] fork ]
- 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: 'progress-bar';
- style: 'width: 0%' ]
- ! !
- HLProgressBarWidget class slots: {#default}!
- !HLProgressBarWidget class methodsFor: 'accessing'!
- default
- ^ default ifNil: [ default := self new ]
- ! !
- HLWidget subclass: #HLSpotlightWidget
- slots: {#input}
- package: 'Helios-Core'!
- !HLSpotlightWidget methodsFor: 'accessing'!
- ghostText
- ^ 'Search... (Ctrl+F)'
- !
- inputCompletion
- ^ self manager environment availableClassNames, self manager environment allSelectors
- ! !
- !HLSpotlightWidget methodsFor: 'actions'!
- findMatches: aQueryString andRender: aRenderCallback
- | matches |
- matches := self inputCompletion select: [ :each | each match: aQueryString ].
- aRenderCallback value: matches
- !
- search: aString
- "open a new Browser pointing to aString"
- aString ifNotEmpty: [
- Finder findString: aString ]
- ! !
- !HLSpotlightWidget methodsFor: 'rendering'!
- renderContentOn: html
- input := html input
- class: 'spotlight typeahead';
- placeholder: self ghostText;
- onKeyDown: [ :event |
- event which = 13 ifTrue: [
- self search: input asJQuery val ] ]
- yourself.
-
- input asJQuery
- typeahead: #{ 'hint' -> true }
- value: #{ 'name' -> 'classesAndSelectors'.
- 'displayKey' -> [ :suggestion | suggestion asString ].
- 'source' -> [ :query :callback | self findMatches: query andRender: callback ]}.
- "use additional datasets for grouping into classes and selectors"
- ! !
- HLWidget subclass: #HLTabWidget
- slots: {#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
- !
- cssClass
- ^ self widget tabClass
- !
- 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'!
- add
- self manager addTab: self.
- self observeManager
- !
- hide
- root ifNotNil: [ root asJQuery css: 'visibility' put: 'hidden' ]
- !
- observeManager
- self manager announcer
- on: HLTabLabelChanged
- send: #onTabLabelChanged:
- to: self
- !
- registerBindings
- self widget registerBindings
- !
- remove
- self unregister.
- self widget unregister.
- root ifNotNil: [ root asJQuery remove ]
- !
- show
- root
- ifNil: [ self appendToJQuery: 'body' asJQuery ]
- ifNotNil: [ root asJQuery css: 'visibility' put: 'visible' ]
- !
- unregister
- self manager announcer unsubscribe: self
- ! !
- !HLTabWidget methodsFor: 'reactions'!
- onTabLabelChanged: anAnnouncement
- anAnnouncement widget = self widget ifTrue: [
- self label = anAnnouncement label ifFalse: [
- self label: anAnnouncement label.
- self manager refresh ] ]
- ! !
- !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
- ! !
- HLWidget subclass: #HLTabsWidget
- slots: {#tabs. #activeTab. #history. #selectionDisabled. #spotlight}
- package: 'Helios-Core'!
- !HLTabsWidget methodsFor: 'accessing'!
- activeTab
- ^ activeTab
- !
- history
- ^ history ifNil: [ history := OrderedCollection new ]
- !
- history: aCollection
- history := aCollection
- !
- spotlight
- ^ spotlight ifNil: [ spotlight := HLSpotlightWidget new ]
- !
- tabWidth
- ^ (window asJQuery width - 250) / self tabs size
- !
- tabs
- ^ tabs ifNil: [ tabs := OrderedCollection new ]
- ! !
- !HLTabsWidget methodsFor: 'actions'!
- activate: aTab
- self isSelectionDisabled ifTrue: [ ^ self ].
- (self tabs includes: aTab) ifFalse: [ ^ self ].
- self manager keyBinder flushBindings.
- aTab registerBindings.
- activeTab := aTab.
-
- self
- refresh;
- addToHistory: aTab;
- show: aTab
- !
- activateNextTab
- | nextTab |
-
- self tabs ifEmpty: [ ^ self ].
-
- nextTab := self tabs
- at: (self tabs indexOf: self activeTab) + 1
- ifAbsent: [ self tabs first ].
-
- self activate: nextTab
- !
- activatePreviousTab
- | previousTab |
-
- self tabs ifEmpty: [ ^ self ].
-
- previousTab := self tabs
- at: (self tabs indexOf: self activeTab) - 1
- ifAbsent: [ self tabs last ].
-
- self activate: previousTab
- !
- addTab: aTab
- self tabs add: aTab.
- self activate: aTab
- !
- addToHistory: aTab
- self removeFromHistory: aTab.
- self history add: aTab
- !
- disableSelection
- selectionDisabled := true
- !
- enableSelection
- selectionDisabled := false
- !
- 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 manager keyBinder flushBindings.
- aTab remove.
- self refresh.
- self history ifNotEmpty: [
- self history last activate ]
- !
- removeTabForWidget: aWidget
- self removeTab: (self tabs
- detect: [ :each | each widget = aWidget ]
- ifNone: [ ^ self ])
- !
- updateTabsOrder
- tabs := '.nav-tabs li' asJQuery toArray
- collect: [ :each | each at: 'tab-data' ]
- ! !
- !HLTabsWidget methodsFor: 'private'!
- setupEvents
- 'body' asJQuery keydown: [ :event |
-
- "ctrl+> and ctrl+<"
- (event ctrlKey and: [ event which = 188 ]) ifTrue: [
- self activatePreviousTab.
- event preventDefault ].
- (event ctrlKey and: [ event which = 190 ]) ifTrue: [
- self activateNextTab.
- event preventDefault ] ]
- ! !
- !HLTabsWidget methodsFor: 'rendering'!
- renderAddOn: html
- html div
- class: 'dropdown new_tab';
- with: [
- html a
- class: 'dropdown-toggle';
- at: 'data-toggle' put: 'dropdown';
- with: [
- (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-header';
- at: 'role' put: 'tabpanel';
- with: [ self renderTabsOn: html ] ].
-
- html with: self spotlight.
- self renderAddOn: html
- !
- renderTab: aTab on: html
- | li |
- li := html li
- style: 'width: ', self tabWidth asString, 'px';
- class: (aTab isActive ifTrue: [ 'tab active' ] ifFalse: [ 'tab inactive' ]);
- with: [
- html a
- with: [
- ((html tag: 'i') class: 'close')
- onClick: [ self removeTab: aTab ].
- html span
- class: aTab cssClass;
- title: aTab label;
- with: aTab label ];
- at: 'role' put: 'tab'];
- onClick: [ aTab activate ].
-
- li asDomNode at: 'tab-data' put: aTab
- !
- renderTabsOn: html
- | ul |
- ul := html ul
- class: 'nav navbar-nav nav-tabs';
- at: 'role' put: 'tablist';
- with: [
- self tabs do: [ :each |
- self renderTab: each on: html ] ].
-
- ul asJQuery sortable: #{
- 'containment' -> 'parent'.
- 'start' -> [ self disableSelection ].
- 'stop' -> [ [ self enableSelection] valueWithTimeout: 300 ].
- 'update' -> [ self updateTabsOrder ]
- }
- !
- show: aTab
- self tabs do: [ :each | each hide ].
- aTab show; focus
- ! !
- !HLTabsWidget methodsFor: 'testing'!
- isSelectionDisabled
- ^ selectionDisabled ifNil: [ false ]
- ! !
- HLTabsWidget class slots: {#current}!
- HLWidget subclass: #HLWelcomeWidget
- slots: {}
- package: 'Helios-Core'!
- !HLWelcomeWidget methodsFor: 'accessing'!
- cssClass
- ^ 'welcome'
- ! !
- !HLWelcomeWidget methodsFor: 'actions'!
- openClassBrowser
- HLBrowser openAsTab
- !
- openHelp
- !
- openTestRunner
- HLSUnit openAsTab
- !
- openWorkspace
- HLWorkspace openAsTab
- ! !
- !HLWelcomeWidget methodsFor: 'rendering'!
- renderButtonsOn: html
- html button
- class: 'button';
- with: 'Class Browser';
- onClick: [ self openClassBrowser ].
- html button
- class: 'button';
- with: 'Workspace';
- onClick: [ self openWorkspace ].
- html button
- class: 'button';
- with: 'Test Runner';
- onClick: [ self openTestRunner ].
- "html button
- class: 'button';
- with: 'Help';
- onClick: [ self openHelp ]"
- !
- renderContentOn: html
- self
- renderHelpOn: html;
- renderButtonsOn: html
- !
- renderHelpOn: html
- html h2 with: 'No tools are open'.
- html ul with: [
- html li with: 'Perform actions with ctrl + space'.
- html li with: 'Open one of the common tools:' ]
- ! !
|