SystemOrganization addCategory: #'TextLint-View-Wizard'! WizardPart subclass: #TLCheckboxPart instanceVariableNames: 'model label checkbox' classVariableNames: '' poolDictionaries: '' category: 'TextLint-View-Wizard'! !TLCheckboxPart class methodsFor: 'instance creation' stamp: 'FabrizioPerin 4/6/2010 17:42'! new: aString ^self new initialize: aString; yourself.! ! !TLCheckboxPart methodsFor: 'accessing' stamp: 'FabrizioPerin 4/7/2010 16:26'! checkboxContentMorph ^checkbox! ! !TLCheckboxPart methodsFor: 'as yet unclassified' stamp: 'FabrizioPerin 4/7/2010 15:24'! checkboxInitializer checkbox := self newCheckboxFor: (model := ValueHolder new contents: true) getSelected: #contents setSelected: #contents: label: label. checkbox buttonMorph selected: true. ^checkbox! ! !TLCheckboxPart methodsFor: 'initialization' stamp: 'FabrizioPerin 4/7/2010 15:24'! initialize: aString super initialize. label := aString. self populateContents: {( self checkboxInitializer )}.! ! !TLCheckboxPart methodsFor: 'as yet unclassified' stamp: 'FabrizioPerin 4/6/2010 17:42'! outputValue "this method is an abstract method as only the subclass itself know what is the information to send to the WizardPane which will send it to the wizarControl " "return true or false according the checkbox is selected or not" ^ model contents! ! !TLCheckboxPart methodsFor: 'accessing' stamp: 'FabrizioPerin 4/6/2010 17:42'! selected: trueOrFalse "select or unselect the checkbox according the value of trueOrFalse " checkbox buttonMorph selected: trueOrFalse.! ! WizardPart subclass: #TLChooseFilePart instanceVariableNames: 'folderDialog title fileDialog' classVariableNames: '' poolDictionaries: '' category: 'TextLint-View-Wizard'! !TLChooseFilePart methodsFor: 'as yet unclassified' stamp: 'FabrizioPerin 4/7/2010 16:38'! chooseFile fileDialog := FileDialogWindow basicNew initialize; title: title; answerOpenFile. ^self fileDialogContentMorph! ! !TLChooseFilePart methodsFor: 'as yet unclassified' stamp: 'FabrizioPerin 4/7/2010 16:37'! fileDialogContentMorph "exact copy of newContentMorph method but instead to create a new list of directory it uses the one already present" fileDialog directoryTreeMorph: fileDialog directoryTreeMorph; fileListMorph: fileDialog fileListMorph; previewMorph: fileDialog newPreviewMorph. ^(fileDialog newRow: { fileDialog newColumn: { fileDialog newGroupbox: 'Directory' translated for: fileDialog directoryTreeMorph. (fileDialog newLabelGroup: { 'File name' translated->fileDialog newFileNameTextEntry}) vResizing: #shrinkWrap}. fileDialog newGroupbox: 'File' translated forAll: { fileDialog fileListMorph. fileDialog newActionButtonRow}}, (fileDialog previewMorph notNil ifTrue: [{fileDialog newGroupbox: 'Preview' translated for: fileDialog previewMorph}] ifFalse: [#()])) vResizing: #spaceFill.! ! !TLChooseFilePart methodsFor: 'initialization' stamp: 'FabrizioPerin 4/7/2010 16:38'! initialize super initialize. title := ''. self populateContents: {( self chooseFile )}.! ! !TLChooseFilePart methodsFor: 'as yet unclassified' stamp: 'FabrizioPerin 4/7/2010 16:37'! outputValue "this method is an abstract method as only the subclass itself know what is the information to send to the WizardPane which will send it to the wizarControl " ^fileDialog selectedPathName! ! WizardPart subclass: #TLMultiCheckboxesPart instanceVariableNames: 'allCheckboxes' classVariableNames: '' poolDictionaries: '' category: 'TextLint-View-Wizard'! !TLMultiCheckboxesPart class methodsFor: 'instance creation' stamp: 'FabrizioPerin 4/7/2010 16:14'! groupName: aString withAll: aCollectionOfLabels super initialize. ^self new initialize: aCollectionOfLabels inGroupBoxNamed: aString. ! ! !TLMultiCheckboxesPart methodsFor: 'initialize-release' stamp: 'FabrizioPerin 4/7/2010 16:28'! initialize: aCollectionOfLabels inGroupBoxNamed: aName allCheckboxes := OrderedCollection new. aCollectionOfLabels do: [:each | allCheckboxes add: ((TLCheckboxPart new: each) checkboxContentMorph). ]. "elements := self addVerticalSeparatorAtTheMiddleOf: allCheckboxes ." self populateContents: {self newGroupboxNamed: aName WithAll: allCheckboxes} ! ! !TLMultiCheckboxesPart methodsFor: 'accessing - wizard mangement' stamp: 'FabrizioPerin 4/7/2010 16:05'! outputValue "this method is an abstract method as only the subclass itself know what is the information to send to the WizardPane which will send it to the wizarControl " ^ self selectedItems! ! !TLMultiCheckboxesPart methodsFor: 'accessing - wizard mangement' stamp: 'FabrizioPerin 4/7/2010 16:05'! selectedItems "return a collection containing symbols corresponding to the checkboxes selected" | result | result := OrderedCollection new. allCheckboxes do: [ :each | each buttonMorph selected ifTrue: [ result add: each label asSymbol ] ]. ^ result! ! WizardControl subclass: #TLWizardGUI instanceVariableNames: 'progBar' classVariableNames: '' poolDictionaries: '' category: 'TextLint-View-Wizard'! !TLWizardGUI methodsFor: 'as yet unclassified' stamp: 'FabrizioPerin 4/8/2010 14:59'! actionsToPerform | sourcePathName rulesList textLintChecker| sourcePathName := wizardInformations at: #sourceDirectoryPath. rulesList := wizardInformations at: #rules. rulesList isEmpty ifTrue:[DialogWindow new alert: 'Please select at least a rule'] ifFalse:[ textLintChecker := TLTextLintChecker new. rulesList do: [:ruleClassNameSymbol | textLintChecker addRule: ((Smalltalk at: ruleClassNameSymbol) perform: #new)]. progBar value: 3. textLintChecker checkDocument: (TLTextPhraser new parse: (TLTextTokenizer parse: (StandardFileStream readOnlyFileNamed: sourcePathName))). progBar value: 4. ]. textLintChecker results inspect.! ! !TLWizardGUI methodsFor: 'initialization' stamp: 'FabrizioPerin 4/8/2010 14:03'! buildWizardPanels | pane1 pane2 part1 part2 part3 part4 part5 | pane1 := WizardFirstPane named: 'Select the Latex file to check'. pane2 := WizardLastPane named: 'Select the Ruels to use'. part1 := TLChooseFilePart new. pane1 addPart: part1 associatedTo: #sourceDirectoryPath. part2 := TLMultiCheckboxesPart groupName: 'BARBAs RULZ' withAll: (TLTextLintRule allSubclasses collect: [:class | class name]). pane2 addPart: part2 associatedTo: #rules. self addPane: pane1. self addPane: pane2. ! ! !TLWizardGUI methodsFor: 'initialization' stamp: 'FabrizioPerin 4/7/2010 16:54'! initialize super initialize. self buildWizardPanels. ! ! !TLWizardGUI methodsFor: 'as yet unclassified' stamp: 'FabrizioPerin 4/7/2010 14:55'! performTerminateButtonAction "by default, just close the last current pane. Override this method if you want to create a subclass of WizardControl making a specific action" "^self subclassResponsibility" UIManager default displayProgress: 'Processing' at: Sensor cursorPoint from: 1 to: 10 during: [ :bar | progBar := bar. progBar value: 2. super performTerminateButtonAction . self actionsToPerform.].! !