xquery/trunk/XQuery__QueryInspectorUI.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 08 Apr 2008 19:47:42 +0000
changeset 0 5057afe1ec87
child 18 3476eed46de5
permissions -rw-r--r--
Initial import from CVS

"{ Package: 'stx:goodies/xmlsuite/xquery' }"

"{ NameSpace: XQuery }"

DomainModelUI subclass:#QueryInspectorUI
	instanceVariableNames:'sourceView'
	classVariableNames:''
	poolDictionaries:''
	category:'XQuery-UI'
!

HierarchicalItem subclass:#AstNodeItem
	instanceVariableNames:'astNode ivarName'
	classVariableNames:''
	poolDictionaries:''
	privateIn:QueryInspectorUI
!


!QueryInspectorUI 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:XQuery::QueryInspectorUI andSelector:#windowSpec
     XQuery::QueryInspectorUI new openInterface:#windowSpec
     XQuery::QueryInspectorUI open
    "

    <resource: #canvas>

    ^ 
     #(FullSpec
        name: windowSpec
        window: 
       (WindowSpec
          label: 'Query Inspector'
          name: 'Query Inspector'
          min: (Point 10 10)
          bounds: (Rectangle 0 0 630 322)
        )
        component: 
       (SpecCollection
          collection: (
           (VariableHorizontalPanelSpec
              name: 'QueryTreeAndSourcePanel'
              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
              showHandle: true
              snapMode: both
              handlePosition: right
              component: 
             (SpecCollection
                collection: (
                 (HierarchicalListViewSpec
                    name: 'QueryTree'
                    model: astNodeAspect
                    menu: queryTreeMenu
                    hasHorizontalScrollBar: true
                    hasVerticalScrollBar: true
                    listModel: queryTreeAspect
                    useIndex: false
                    highlightMode: line
                    useDefaultIcons: false
                  )
                 (TextEditorSpec
                    name: 'SourceView'
                    model: sourceStringAspect
                    hasHorizontalScrollBar: true
                    hasVerticalScrollBar: true
                    postBuildCallback: postBuildSourceView:
                  )
                 )
               
              )
              handles: (Any 0.4 1.0)
            )
           )
         
        )
      )

    "Modified: / 12-04-2007 / 12:39:55 / janfrog"
! !

!QueryInspectorUI class methodsFor:'menu specs'!

queryTreeMenu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

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

    "
     MenuEditor new openOnClass:XQuery::QueryInspectorUI andSelector:#queryTreeMenu
     (Menu new fromLiteralArrayEncoding:(XQuery::QueryInspectorUI queryTreeMenu)) startUp
    "

    <resource: #menu>

    ^ 
     #(Menu
        (
         (MenuItem
            label: 'Inspect AST node'
            itemValue: queryTreeMenuInspectAstNode
            translateLabel: true
          )
         )
        nil
        nil
      )

    "Created: / 12-04-2007 / 11:46:57 / janfrog"
! !

!QueryInspectorUI 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)."

    ^ #(
        #model
      ).

    "Modified: / 12-04-2007 / 12:28:30 / janfrog"
! !

!QueryInspectorUI methodsFor:'accessing'!

astNode

    | item |
    ^(item := self astNodeAspect value) ifNotNil:[item astNode]

    "Created: / 12-04-2007 / 12:29:08 / janfrog"
! !

!QueryInspectorUI methodsFor:'aspect'!

astNodeAspect

    ^self
        aspectAt: #astNodeAspect
        ifAbsentPut:
            [nil asValue
                onChangeSend:#updateSourceViewSelection to:self;
                yourself]

    "Created: / 28-03-2007 / 16:46:30 / janfrog"
    "Modified: / 12-04-2007 / 12:30:11 / janfrog"
!

queryTreeAspect

    ^self 
        aspectAt: #queryTreeAspect
        ifAbsentPut:
            [PluggableAdaptor on: self modelHolder getter:
                [:m|
                | rootAstNodeItem hl |
                rootAstNodeItem := AstNodeItem new 
                                        ivarName: 'query';
                                        astNode: self model.

                hl := HierarchicalList new
                        root: rootAstNodeItem;
                        showRoot: true.
                rootAstNodeItem expand.
                hl]]

    "Created: / 28-03-2007 / 15:58:31 / janfrog"
    "Modified: / 12-04-2007 / 11:36:11 / janfrog"
!

sourceStringAspect

    ^self
        aspectAt:#sourceStringAspect
        ifAbsentPut:[self aspectAdaptorFor:#sourceString]

    "Created: / 12-04-2007 / 12:24:19 / janfrog"
! !

!QueryInspectorUI methodsFor:'callbacks - post build'!

postBuildSourceView: aView

    sourceView := aView scrolledView

    "Created: / 12-04-2007 / 12:28:14 / janfrog"
! !

!QueryInspectorUI methodsFor:'change & update'!

updateSourceViewSelection

    | astNode startPosition stopPosition |
    sourceView ifNil:[^self].
    (astNode := self astNode) ifNil:[^self].
    (startPosition := astNode startPosition) 
        ifNil:[^sourceView unselect].
    (stopPosition := astNode stopPosition) 
        ifNil:[^sourceView unselect].

    sourceView 
        selectFromCharacterPosition: startPosition
        to: stopPosition

    "Created: / 12-04-2007 / 12:29:42 / janfrog"
! !

!QueryInspectorUI methodsFor:'menu actions'!

queryTreeMenuInspectAstNode

    ^Inspector openOn: self astNodeAspect value astNode

    "Created: / 12-04-2007 / 11:47:48 / janfrog"
! !

!QueryInspectorUI::AstNodeItem methodsFor:'accessing'!

astNode
    ^ astNode

    "Created: / 28-03-2007 / 15:51:49 / janfrog"
!

astNode:anAstNode
    astNode := anAstNode.

    "Created: / 28-03-2007 / 15:51:49 / janfrog"
!

astNodeName

    ^(astNode class nameWithoutPrefix asString copyFrom: 4)

    "Created: / 12-04-2007 / 11:29:57 / janfrog"
!

children

    ^children ifNil:
        [children := astNode childrenDictionary keysAndValuesCollect:
                        [:ivarName :astNode|
                        self class new
                            ivarName: ivarName;
                            astNode: astNode;
                            parent: self]].

    "Created: / 28-03-2007 / 15:55:24 / janfrog"
    "Modified: / 12-04-2007 / 11:35:24 / janfrog"
!

ivarName
    ^ ivarName ? '?'

    "Created: / 12-04-2007 / 11:29:28 / janfrog"
!

ivarName:something
    ivarName := something.

    "Created: / 12-04-2007 / 11:29:28 / janfrog"
!

label

    ^self ivarName ,' <', self astNodeName, '>'

    "Created: / 28-03-2007 / 15:53:18 / janfrog"
    "Modified: / 12-04-2007 / 11:30:23 / janfrog"
! !

!QueryInspectorUI class methodsFor:'documentation'!

version
    ^ '$Header: /opt/data/cvs/stx/goodies/xmlsuite/xquery/XQuery__QueryInspectorUI.st,v 1.2 2007-04-12 11:45:25 vranyj1 Exp $'
! !