SmallSense__CriticsWindow.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 18 Jul 2014 07:01:21 +0100
changeset 252 feba6ee5c814
parent 249 8bc64027b189
child 306 798ea6162eba
permissions -rw-r--r--
Added copyright notice and license information (LGPL2)

"
stx:goodies/smallsense - A productivity plugin for Smalltalk/X IDE
Copyright (C) 2013-2014 Jan Vrany

This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Lesser General Public
License as published by the Free Software Foundation; either
version 2.1 of the License. 

This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
Lesser General Public License for more details.

You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
"
"{ Package: 'stx:goodies/smallsense' }"

"{ NameSpace: SmallSense }"

SimpleDialog subclass:#CriticsWindow
	instanceVariableNames:'ruleHolder ruleRationaleAndFixesHTMLHolder rationalView fixer
		entered codeView'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Core-Interface'
!

!CriticsWindow class methodsFor:'documentation'!

copyright
"
stx:goodies/smallsense - A productivity plugin for Smalltalk/X IDE
Copyright (C) 2013-2014 Jan Vrany

This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Lesser General Public
License as published by the Free Software Foundation; either
version 2.1 of the License. 

This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
Lesser General Public License for more details.

You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
"
! !

!CriticsWindow class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:SmallSense::CriticsWindow andSelector:#windowSpec
     SmallSense::CriticsWindow new openInterface:#windowSpec
     SmallSense::CriticsWindow open
    "

    <resource: #canvas>

    ^ 
    #(FullSpec
       name: windowSpec
       window: 
      (WindowSpec
         label: 'SmalllintRuleDetail'
         name: 'SmalllintRuleDetail'
         min: (Point 10 10)
         bounds: (Rectangle 0 0 418 219)
         backgroundColor: (Color 94.1176470588235 93.7254901960784 59.2156862745098)
         forceRecursiveBackgroundOfDefaultBackground: true
       )
       component: 
      (SpecCollection
         collection: (
          (LinkButtonSpec
             name: 'Button1'
             layout: (LayoutFrame -1 0 -29 1 1 1 0 1)
             activeHelpKey: ruleName
             level: 0
             backgroundColor: (Color 94.1176470588235 93.7254901960784 59.2156862745098)
             translateLabel: true
             labelChannel: ruleNameAspect
             adjust: left
             model: browseLintRule
             keepSpaceForOSXResizeHandleH: true
           )
          (HTMLViewSpec
             name: 'Rationale'
             layout: (LayoutFrame 0 0 0 0 0 1 -27 1)
             level: 0
             visibilityChannel: rationaleVisibleHolder
             hasHorizontalScrollBar: true
             hasVerticalScrollBar: true
             backgroundColor: (Color 94.1176470588235 93.7254901960784 59.2156862745098)
             htmlText: ruleRationaleAndFixesHTMLHolder
             postBuildCallback: setupHTMLView:
           )
          (ActionButtonSpec
             label: 'X'
             name: 'Button2'
             layout: (LayoutFrame -30 1 0 0 0 1 30 0)
             level: 0
             backgroundColor: (Color 94.1176470588235 93.7254901960784 59.2156862745098)
             translateLabel: true
             model: closeRequest
           )
          )
        
       )
     )
! !

!CriticsWindow class methodsFor:'plugIn spec'!

aspectSelectors
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this. If it is corrupted,
     the UIPainter may not be able to read the specification."

    "Return a description of exported aspects;
     these can be connected to aspects of an embedding application
     (if this app is embedded in a subCanvas)."

    ^ #(
        #ruleHolder
      ).

! !

!CriticsWindow methodsFor:'accessing'!

codeView
    ^ codeView
!

codeView:aCodeView2
    codeView := aCodeView2.
!

rule

    ^self ruleHolder value.

    "Created: / 30-01-2012 / 21:45:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

rule: anRBLintRule

    ^self ruleHolder value: anRBLintRule

    "Created: / 30-01-2012 / 21:45:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CriticsWindow methodsFor:'actions'!

browseLintRule
    |rule ruleClass sel|

    rule := self ruleHolder value.
    rule isNil ifTrue:[^ self].
    ruleClass := rule class.
    (ruleClass implements:#rationale) ifTrue:[
        sel := #rationale.
    ].
    self close.
    UserPreferences current systemBrowserClass
       openInClass:ruleClass selector:sel.

    "Created: / 07-09-2011 / 04:09:38 / cg"
    "Modified: / 31-01-2012 / 11:30:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

doQuickFix: quickFixNo

    self closeDownViews.
    [ fixer performFix: quickFixNo ] fork.

    "Created: / 16-02-2012 / 14:19:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CriticsWindow methodsFor:'aspects'!

ruleHolder
    "return/create the 'ruleHolder' value holder (automatically generated)"

    ruleHolder isNil ifTrue:[
        ruleHolder := ValueHolder with: (RBDebuggingCodeLeftInMethodsRule new)
    ].
    ^ ruleHolder

    "Modified: / 30-01-2012 / 21:43:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

ruleHolder:something
    "set the 'ruleHolder' value holder (automatically generated)"

    |oldValue newValue|

    ruleHolder notNil ifTrue:[
	oldValue := ruleHolder value.
	ruleHolder removeDependent:self.
    ].
    ruleHolder := something.
    ruleHolder notNil ifTrue:[
	ruleHolder addDependent:self.
    ].
    newValue := ruleHolder value.
    oldValue ~~ newValue ifTrue:[
	self update:#value with:newValue from:ruleHolder.
    ].
!

ruleNameAspect
    <resource: #uiAspect>

    |holder|

    (holder := builder bindingAt:#ruleNameAspect) isNil ifTrue:[
        holder := BlockValue
                    with:[:h | 
                        "/ h displayString , ' ' , (('[browse]' actionForAll:[ self browseLintRule]) colorizeAllWith:Color blue) 
                        'browse ',h displayString actionForAll:[ self browseLintRule] 
                    ]
                    argument: self ruleHolder.
        builder aspectAt:#ruleNameAspect put:holder.
    ].
    ^ holder.

    "Modified: / 05-02-2010 / 12:51:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-09-2011 / 04:54:24 / cg"
!

ruleRationaleAndFixesHTMLHolder
    "return/create the 'ruleRationaleAndFixesHTMLHolder' value holder (automatically generated)"

    ruleRationaleAndFixesHTMLHolder isNil ifTrue:[
        ruleRationaleAndFixesHTMLHolder := ValueHolder new.
    ].
    ^ ruleRationaleAndFixesHTMLHolder

    "Modified (format): / 01-02-2012 / 10:57:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CriticsWindow methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    "Invoked when an object that I depend upon sends a change notification."

    changedObject == ruleHolder ifTrue:[
         self updateRationaleAndFixes.
         ^ self.
    ].
    super update:something with:aParameter from:changedObject

    "Modified: / 01-02-2012 / 10:56:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

updateRationaleAndFixes
    | rule html |

    rule := self ruleHolder value.
    rule isNil ifTrue:[
        fixer := nil.
        html :=  'No rule...'.
    ] ifFalse:[
        fixer := SmalltalkQuickFixer for: rule view: codeView.
        html := String streamContents:[:s|
                    s 
                        nextPutAll: rule name; 
                        nextPutAll:'<P>';  
                        nextPutLine: rule rationale.
                    fixer printHtmlOn: s.
                ]
    ].

    self ruleRationaleAndFixesHTMLHolder value: html

    "Created: / 01-02-2012 / 10:56:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-09-2013 / 09:37:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CriticsWindow methodsFor:'event processing'!

processEvent: anEvent

    anEvent isKeyReleaseEvent ifTrue:[ 
        anEvent key == #Escape ifTrue:[ 
            self closeRequest. "/ closeDownViews.
            ^true.         
        ].
    ].



"/    entered ifFalse:[
"/        anEvent isPointerLeaveEvent ifTrue:[
"/            anEvent view == self window ifTrue:[
"/                entered := true.
"/            ]
"/        ]
"/    ] ifTrue:[
        anEvent isPointerLeaveEvent ifTrue:[
            anEvent view == self window ifTrue:[
                self closeRequest. "/ closeDownViews.
                ^true.
            ]
        ].
"/    ].

    ^false

    "Created: / 16-02-2012 / 14:09:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 31-03-2014 / 16:53:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CriticsWindow methodsFor:'hooks'!

postBuildWith: aBuilder
    super postBuildWith:aBuilder.

    entered := false.
    self updateRationaleAndFixes.
    aBuilder window 
        "windowGroup: codeView windowGroup;"
        bePopUpView; 
        beSlave.

    "Created: / 03-04-2011 / 10:45:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-02-2012 / 14:14:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

postOpenWith: bldr
    super postOpenWith: bldr.
    self windowGroup addPreEventHook: self.

    "Created: / 16-02-2012 / 14:09:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CriticsWindow methodsFor:'initialization'!

setupHTMLView:aView
    rationalView := aView.
    aView painter
        leftMargin:20;
        topMargin:5.

    "Created: / 04-08-2011 / 18:00:36 / cg"
! !

!CriticsWindow class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
!

version_SVN
    ^ '$Id: SmallSense__CriticsWindow.st,v 1.3 2014/02/26 15:09:03 cg Exp $'
! !