MultiViewToolApplication.st
author Claus Gittinger <cg@exept.de>
Wed, 22 Oct 2003 19:15:40 +0200
changeset 5303 fe0d2165b716
parent 5302 615a0020e15c
child 6179 182d948dcf05
permissions -rw-r--r--
*** empty log message ***

"{ Package: 'stx:libtool' }"

ToolApplicationModel subclass:#MultiViewToolApplication
	instanceVariableNames:'workspaces tabList selectedWorkspaceIndexHolder workspaceHolder'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Smalltalk'
!

!MultiViewToolApplication class methodsFor:'documentation'!

documentation
"
    Common code for multiView applications (Workspace and Terminal app)

    [author:]
        Claus Gittinger
"
! !

!MultiViewToolApplication class methodsFor:'interface specs'!

windowSpec
    "raise an error: must be redefined in concrete subclass(es)"

    ^ self subclassResponsibility
! !

!MultiViewToolApplication class methodsFor:'menu specs'!

mainMenu
    "raise an error: must be redefined in concrete subclass(es)"

    ^ self subclassResponsibility
!

tabMenu
    "raise an error: must be redefined in concrete subclass(es)"

    ^ self subclassResponsibility
! !

!MultiViewToolApplication class methodsFor:'queries'!

isVisualStartable
    "return true, if this application can be started via #open.
     (to allow start of a change browser via double-click in the browser)"

    self == MultiViewToolApplication ifTrue:[^false].
    ^ super isVisualStartable
! !

!MultiViewToolApplication methodsFor:'accessing'!

selectedWorkspace
    |wsIndex|

    workspaces isNil ifTrue:[
        workspaces := OrderedCollection new.
    ].
    wsIndex := self selectedWorkspaceIndexHolder value.
    wsIndex == 0 ifTrue:[
        ^ nil
    ].

    workspaces size < wsIndex ifTrue:[
        workspaces grow:wsIndex.
        workspaces at:wsIndex put:(self createWorkspace).
    ].
    ^ workspaces at:wsIndex
!

tabMenuAt:index
    |m i ws|

    m := self class tabMenu.
    m := m decodeAsLiteralArray.
    i := m detectItem:[:item | item value == #removeWorkspace:] ifNone:nil.
    i notNil ifTrue:[
        i argument:index.
        index ~~ self selectedWorkspaceIndexHolder value ifTrue:[
            "/ for now: if that buffer is modified,
            "/ do not allow removing.
            "/ (must be brought to front, in order for check-for-modification to work)
            ws := workspaces at:index.
            (ws isKindOf:ScrollableView) ifTrue:[
                ws := ws scrolledView
            ].
            ((ws isKindOf:TextView) not
            or:[ ws modified ])
            ifTrue:[
                i disable
            ].
        ].
    ].
    i := m detectItem:[:item | item value == #renameWorkspace:] ifNone:nil.
    i notNil ifTrue:[
        i argument:index.
    ].

    m findGuiResourcesIn:self.
    ^ m
!

workspaceHolder
    workspaceHolder isNil ifTrue:[
        workspaceHolder := ValueHolder with:(self selectedWorkspace).
    ].
    ^ workspaceHolder
! !

!MultiViewToolApplication methodsFor:'aspects'!

selectedWorkspaceIndexHolder
    selectedWorkspaceIndexHolder isNil ifTrue:[
        selectedWorkspaceIndexHolder := 1 asValue.
        selectedWorkspaceIndexHolder onChangeSend:#workspaceSelectionChanged to:self.
    ].
    ^ selectedWorkspaceIndexHolder.
!

tabList
    tabList isNil ifTrue:[
        tabList := List new.
    ].
    ^ tabList.
! !

!MultiViewToolApplication methodsFor:'aspects-queries'!

canRemoveWorkspace
    ^ self canRemoveWorkspace:(self selectedWorkspaceIndexHolder value)
!

canRemoveWorkspace:idx
    ^ self tabList size > 1
"/       and:[ (self workspacesTextViewAt:(self selectedWorkspaceIndexHolder value))
!

hasMultipleBuffersHolder
    ^ [ workspaces size > 1 ]
!

hasSelectionInActiveWorkspace
    ^ self selectedWorkspacesTextView selectionAsString size > 0
! !

!MultiViewToolApplication methodsFor:'menu-actions'!

addWindow:aWindow named:name
    ^ self addWindow:aWindow named:name asFirst:false
!

addWindow:aWindow named:name asFirst:asFirst
    |tabList wsIndex newSelectedIndex|

    tabList := self tabList.
    wsIndex := tabList size + 1.
    wsIndex == 1 ifTrue:[
        "/ first - add a name for the first tab
        tabList add:(self window label). "/ 'Workspace'.
        wsIndex := wsIndex + 1.
    ].

    workspaces grow:wsIndex.
    asFirst ifTrue:[
        tabList addFirst:(name bindWith:wsIndex).
        workspaces replaceFrom:2 to:wsIndex with:workspaces startingAt:1.
        newSelectedIndex := 1.
    ] ifFalse:[
        tabList addLast:(name bindWith:wsIndex).
        newSelectedIndex := wsIndex.
    ].
    workspaces at:newSelectedIndex put:aWindow.
    self selectedWorkspaceIndexHolder value:newSelectedIndex.   
"/    workspaceHolder value:aWindow.
!

menuSaveAllAs
    self 
        askForFile:'Save all Buffers into:' 
        thenDo:[:file :doAppend |
            |ws append|

            append := doAppend.
            workspaces do:[:subView |
                |ws|

                ws := self workspaceViewOfView:subView.
                ws notNil ifTrue:[
                    ws saveAs:file doAppend:append.
                    ws modified:false.
                ].
                append := true.
            ].
        ]
!

menuSaveAs
    self 
        askForFile:'Save Buffer into:' 
        thenDo:[:file :doAppend |
            |ws|

            ws := self selectedWorkspacesTextView.
            ws saveAs:file doAppend:doAppend.
            ws modified:false.
        ]
!

newWorkspace
    self class open
!

removeWorkspace
    self removeWorkspace:(self selectedWorkspaceIndexHolder value)
!

removeWorkspace:wsIndex
    |tabList newWsIndex|

    wsIndex == self selectedWorkspaceIndexHolder value ifTrue:[
        (self askIfModified:'Text was modified. Remove anyway ?' yesButton:'Remove') ifFalse:[
            ^ self
        ].
    ].

    tabList := self tabList.

    wsIndex == tabList size ifTrue:[
        newWsIndex := wsIndex - 1.
    ] ifFalse:[
        newWsIndex := wsIndex.
    ].

    tabList removeIndex:wsIndex.
    (workspaces at:wsIndex) destroy.
    workspaces removeIndex:wsIndex.

    tabList size == 1 ifTrue:[
        self window label:(tabList at:1).
        tabList removeIndex:1
    ].

    workspaceHolder value:(workspaces at:newWsIndex).
    self selectedWorkspaceIndexHolder value:newWsIndex.
    "/ to force change (update workspaceHolder - even if same index)
    self selectedWorkspaceIndexHolder changed:#value.   
!

renameWorkspace
    self renameWorkspace:(self selectedWorkspaceIndexHolder value)
!

renameWorkspace:wsIndex
    |tabList oldName newName|

    tabList := self tabList.
    tabList isEmpty ifTrue:[
        oldName := self window label
    ] ifFalse:[
        oldName := tabList at:wsIndex.
    ].
    newName := Dialog request:(resources string:'New Name for %1:' with:oldName) initialAnswer:oldName.
    newName size == 0 ifTrue:[ ^ self].

    self renameWorkspace:wsIndex to:newName.
!

renameWorkspace:wsIndex to:newName
    |tabList|

    tabList := self tabList.
    tabList notEmpty ifTrue:[
        tabList at:wsIndex put:newName.
    ].
    wsIndex == self selectedWorkspaceIndexHolder value ifTrue:[
        self window label:newName.
    ].
! !

!MultiViewToolApplication methodsFor:'menu-actions-editing'!

copySelection
    self selectedWorkspacesTextView copySelection
!

cutSelection
    self selectedWorkspacesTextView cutSelection
!

paste
    self selectedWorkspacesTextView paste
!

paste:aString
    self selectedWorkspacesTextView paste:aString.
!

selectAll
    self selectedWorkspacesTextView selectAll.
! !

!MultiViewToolApplication methodsFor:'private'!

askForFile:question thenDo:aBlock
    Dialog
        requestSaveFileName:(resources string:question) 
        default:'file.wsp' 
        fromDirectory:nil 
        action:[:fileName | aBlock value:fileName value:false] 
        appendAction:[:fileName | aBlock value:fileName value:true]

"/    |file doAppend|
"/
"/    doAppend := false.
"/    Dialog aboutToOpenBoxNotificationSignal handle:[:n |
"/        |box|
"/
"/        box := n parameter.
"/        box addButton:(Button label:'Append' action:[doAppend := true. box okPressed]).
"/        n proceed.
"/    ] do:[
"/        file := Dialog requestFileName:question default:'file.wsp'. 
"/    ].
"/    file isEmptyOrNil ifFalse:[
"/        aBlock value:file value:doAppend
"/    ].
!

askIfAnyModified:arg1 yesButton:arg2 
    "raise an error: must be redefined in concrete subclass(es)"

    ^ self subclassResponsibility
!

askIfModified:question yesButton:yesButtonText
    "tell user, that code has been modified - let her confirm"

    |textView|

    textView := self selectedWorkspace.
    (self isModifiedWorkspace:textView) ifFalse:[^ true].

    (Dialog 
        confirm:(resources string:question) withCRs
        yesLabel:(resources at:yesButtonText)
        noLabel:(resources at:'Cancel'))
    ifTrue:[
        "/ reset modified flag so question is asked only once
        textView modified:false.
        ^ true
    ].
    ^ false

    "Modified: 2.10.1997 / 14:23:47 / stefan"
!

createWorkspace
    "raise an error: must be redefined in concrete subclass(es)"

    ^ self subclassResponsibility
!

isModifiedWorkspace:aView
    self subclassResponsibility
!

selectedWorkspacesTextView
    ^ self workspaceViewOfView:(self selectedWorkspace)
!

workspaceSelectionChanged
    |wsIndex windowLabel v|

    "/ self selected
    self workspaceHolder value:(v := self selectedWorkspace).
    wsIndex := self selectedWorkspaceIndexHolder value.

    wsIndex ~~ 0 ifTrue:[
        windowLabel := tabList at:wsIndex ifAbsent:nil.
        windowLabel notNil ifTrue:[self window label:windowLabel].
    ].
!

workspaceViewOfView:aView
    |view|

    view := aView.
    (view isScrollWrapper) ifTrue:[
        view := view scrolledView.
        view isNil ifTrue:[^ nil].
    ].
    (view isTextView) ifFalse:[
        (view isKindOf:InspectorView) ifFalse:[
            ^ nil
        ].
        view := view workspace.
        (view isScrollWrapper) ifTrue:[
            view := view scrolledView
        ].
    ].
    ^ view
! !

!MultiViewToolApplication class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/MultiViewToolApplication.st,v 1.2 2003-10-22 17:13:48 cg Exp $'
! !