WorkspaceApplication.st
author Claus Gittinger <cg@exept.de>
Thu, 09 Oct 2003 22:41:08 +0200
changeset 5262 99d5c5f7e4b8
parent 5261 5f0d35ddca9d
child 5295 e3c5a7b20d9d
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 2001 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

"{ Package: 'stx:libtool' }"

ToolApplicationModel subclass:#WorkspaceApplication
	instanceVariableNames:'workspaces tabList selectedWorkspaceIndexHolder workspaceHolder
		autoDefineWorkspaceVariables autoDefineVariables'
	classVariableNames:'LastFilterBlockString LastProcessingBlockString'
	poolDictionaries:''
	category:'Interface-Smalltalk'
!

!WorkspaceApplication class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2001 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    A simple wrapper around a WorkSpace-View, adding a pullDown menu.

    [author:]
        Claus Gittinger
"
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Workspace'
          #name: 'Workspace'
          #min: #(#Point 10 10)
          #bounds: #(#Rectangle 13 23 445 264)
          #menu: #mainMenu
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#NoteBookViewSpec
              #name: 'NoteBook1'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #model: #selectedWorkspaceIndexHolder
              #menu: #tabList
              #useIndex: true
              #accessTabMenuAction: #tabMenuAt:
              #canvas: #workspaceHolder
              #canvasInset: 0
              #canvasFrameLevel: 0
              #keepCanvasAlive: true
              #tabLevel: 1
            )
           )
         
        )
      )
! !

!WorkspaceApplication class methodsFor:'menu specs'!

mainMenu
    "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:WorkspaceApplication andSelector:#mainMenu
     (Menu new fromLiteralArrayEncoding:(WorkspaceApplication mainMenu)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #label: 'File'
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'New Workspace'
                  #itemValue: #newWorkspace
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: 'New SystemWorkspace'
                  #itemValue: #newSystemWorkspace
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Load File...'
                  #itemValue: #menuLoad
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Save As...'
                  #itemValue: #menuSaveAs
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasMultipleBuffersHolder
                  #label: 'Save all As...'
                  #itemValue: #menuSaveAllAs
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Exit'
                  #itemValue: #closeRequest
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Buffers'
            #nameKey: #Buffer
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'Add Buffer'
                  #itemValue: #addWorkspace
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #anyWorkspaceVariableIsDefined
                  #label: 'Add Buffer on Workspace Variables'
                  #itemValue: #addWorkspaceVariableInspector
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: 'Add Buffer on Global Variables'
                  #itemValue: #addGlobalVariableInspector
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: 'Rename...'
                  #itemValue: #renameWorkspace
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #enabled: #canRemoveWorkspace
                  #label: 'Remove Buffer'
                  #itemValue: #removeWorkspace
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Edit'
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #enabled: #hasSelectionInActiveWorkspace
                  #label: 'Cut'
                  #itemValue: #cutSelection
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelectionInActiveWorkspace
                  #label: 'Copy'
                  #itemValue: #copySelection
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: 'Paste'
                  #itemValue: #paste
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasHistory
                  #label: 'Paste Last'
                  #itemValue: #pasteLastDoIt
                  #translateLabel: true
                  #submenuChannel: #pasteRecentDoItMenu
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Select All'
                  #itemValue: #selectAll
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Filter Text...'
                  #itemValue: #filterText
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: 'Process Text...'
                  #itemValue: #processText
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Web Services'
                  #translateLabel: true
                  #submenu: 
                 #(#Menu
                    #(
                     #(#MenuItem
                        #enabled: #hasSelectionInActiveWorkspace
                        #label: 'Google Spell'
                        #itemValue: #googleSpellingSuggestion
                        #translateLabel: true
                      )
                     #(#MenuItem
                        #label: 'Translate'
                        #translateLabel: true
                        #submenu: 
                       #(#Menu
                          #(
                           #(#MenuItem
                              #enabled: #hasSelectionInActiveWorkspace
                              #label: 'English -> German'
                              #itemValue: #babelFishTranslate:
                              #translateLabel: true
                              #argument: 'en_de'
                            )
                           #(#MenuItem
                              #enabled: #hasSelectionInActiveWorkspace
                              #label: 'English -> French'
                              #itemValue: #babelFishTranslate:
                              #translateLabel: true
                              #argument: 'en_fr'
                            )
                           #(#MenuItem
                              #enabled: #hasSelectionInActiveWorkspace
                              #label: 'English -> Spanish'
                              #itemValue: #babelFishTranslate:
                              #translateLabel: true
                              #argument: 'en_es'
                            )
                           #(#MenuItem
                              #enabled: #hasSelectionInActiveWorkspace
                              #label: 'English -> Portuguese'
                              #itemValue: #babelFishTranslate:
                              #translateLabel: true
                              #argument: 'en_pt'
                            )
                           #(#MenuItem
                              #label: '-'
                            )
                           #(#MenuItem
                              #enabled: #hasSelectionInActiveWorkspace
                              #label: 'German -> English'
                              #itemValue: #babelFishTranslate:
                              #translateLabel: true
                              #argument: 'de_en'
                            )
                           #(#MenuItem
                              #enabled: #hasSelectionInActiveWorkspace
                              #label: 'French -> English'
                              #itemValue: #babelFishTranslate:
                              #translateLabel: true
                              #argument: 'fr_en'
                            )
                           #(#MenuItem
                              #enabled: #hasSelectionInActiveWorkspace
                              #label: 'Spanish -> English'
                              #itemValue: #babelFishTranslate:
                              #translateLabel: true
                              #argument: 'es_en'
                            )
                           #(#MenuItem
                              #enabled: #hasSelectionInActiveWorkspace
                              #label: 'Portuguese -> English'
                              #itemValue: #babelFishTranslate:
                              #translateLabel: true
                              #argument: 'pt_en'
                            )
                           #(#MenuItem
                              #enabled: #hasSelectionInActiveWorkspace
                              #label: 'Russian -> English'
                              #itemValue: #babelFishTranslate:
                              #translateLabel: true
                              #argument: 'ru_en'
                            )
                           )
                          nil
                          nil
                        )
                      )
                     )
                    nil
                    nil
                  )
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Workspace'
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'Add Workspace Variable...'
                  #itemValue: #addWorkspaceVariable
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #anyWorkspaceVariableIsDefined
                  #label: 'Remove Workspace Variable...'
                  #itemValue: #removeWorkspaceVariable
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #anyWorkspaceVariableIsDefined
                  #label: 'Remove all Workspace Variables...'
                  #itemValue: #removeAllWorkspaceVariables
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #enabled: #anyWorkspaceVariableIsDefined
                  #label: 'Inspect Workspace Variables'
                  #itemValue: #inspectWorkspaceVariables
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Settings'
                  #translateLabel: true
                  #submenu: 
                 #(#Menu
                    #(
                     #(#MenuItem
                        #label: 'Autodefine as Workspace Variable'
                        #translateLabel: true
                        #hideMenuOnActivated: false
                        #choice: #autoDefineVariables
                        #choiceValue: #workspace
                      )
                     #(#MenuItem
                        #label: 'Autodefine as DoIt Variable'
                        #translateLabel: true
                        #hideMenuOnActivated: false
                        #choice: #autoDefineVariables
                        #choiceValue: #doIt
                      )
                     #(#MenuItem
                        #label: 'Autodefine off'
                        #translateLabel: true
                        #hideMenuOnActivated: false
                        #choice: #autoDefineVariables
                      )
                     )
                    nil
                    nil
                  )
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Smalltalk'
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #enabled: #hasSelectionInActiveWorkspace
                  #label: 'DoIt'
                  #itemValue: #doIt
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelectionInActiveWorkspace
                  #label: 'PrintIt'
                  #itemValue: #printIt
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelectionInActiveWorkspace
                  #label: 'InspectIt'
                  #itemValue: #inspectIt
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #enabled: #hasHistory
                  #label: 'Redo Last'
                  #itemValue: #redoLastDoIt
                  #translateLabel: true
                  #submenuChannel: #redoRecentDoItMenu
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #enabled: #hasSelectionInActiveWorkspace
                  #label: 'TimeIt'
                  #itemValue: #timeIt
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelectionInActiveWorkspace
                  #label: 'SpyOnIt'
                  #itemValue: #spyOnIt
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #enabled: #hasSelectionInActiveWorkspace
                  #label: 'Browse Class'
                  #itemValue: #browseIt
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelectionInActiveWorkspace
                  #label: 'Browse Implementors of It'
                  #itemValue: #browseImplementorsOfIt
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelectionInActiveWorkspace
                  #label: 'Browse References to It'
                  #itemValue: #browseReferencesToIt
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'FileIn Text'
                  #itemValue: #fileInText
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Add Global Variable...'
                  #itemValue: #addGlobalVariable
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: 'Remove Global Variable...'
                  #itemValue: #removeGlobalVariable
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Help'
            #translateLabel: true
            #startGroup: #right
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'Documentation'
                  #itemValue: #openDocumentation
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'About this Application...'
                  #itemValue: #openAboutThisApplication
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         )
        nil
        nil
      )
!

tabMenu
    "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:WorkspaceApplication andSelector:#tabMenu
     (Menu new fromLiteralArrayEncoding:(WorkspaceApplication tabMenu)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #label: 'Add Buffer'
            #translateLabel: true
            "/ #triggerOnDown: true
            #value: #addWorkspace
          )
         #(#MenuItem
            #label: 'Rename...'
            #translateLabel: true
            "/ #triggerOnDown: true
            #value: #renameWorkspace:
          )
         #(#MenuItem
            #label: '-'
          )
         #(#MenuItem
            #label: 'Remove Buffer'
            #translateLabel: true
            "/ #triggerOnDown: true
            #value: #removeWorkspace:
            #enabled: #canRemoveWorkspace:
          )
         )
        nil
        nil
      )
! !

!WorkspaceApplication class methodsFor:'special startup'!

openSystemWorkspace
    |wsApp licenceView path needRemove|

    needRemove := true.

    wsApp := self new.
    wsApp allButOpen.
    wsApp window extent:640@400.

    path := (Smalltalk getSystemFileName:'README') ?  '../../README'.
    (path notNil and:[path asFilename exists]) ifTrue:[
        wsApp addWindow:(HVScrollableView for:Workspace) named:'README' asFirst:false.
        wsApp loadFile:path.
        wsApp removeWorkspace:1.  "/ the original Workspace
        wsApp renameWorkspace:1 to:'LICENCE README'.
        needRemove := false.
    ].

"/    path := (Smalltalk getSystemFileName:'doc/online/english/LICENCE_STX.html') ?  '../../doc/online/english/LICENCE_STX.html'.
"/    path asFilename exists ifTrue:[
"/        wsApp addWindow:(licenceView := HVScrollableView for:HTMLDocumentView) named:'License' asFirst:false.
"/        licenceView homeDocument:'../../doc/online/english/LICENCE_STX.html'.
"/        licenceView updateLabelFlag:false.
"/        needRemove ifTrue:[wsApp removeWorkspace:1].  "/ the original Workspace
"/        needRemove := false.
"/    ].

    path := (Smalltalk getSystemFileName:'GettingStarted.wsp').
    (path notNil and:[path asFilename exists]) ifTrue:[
        wsApp addWindow:(HVScrollableView for:Workspace) named:'Getting Started' asFirst:false.
        wsApp loadFile:path.
        needRemove ifTrue:[wsApp removeWorkspace:1].  "/ the original Workspace
        needRemove := false.
    ].

    path := (Smalltalk getSystemFileName:'Keyboard.wsp').
    (path notNil and:[path asFilename exists]) ifTrue:[
        wsApp addWindow:(HVScrollableView for:Workspace) named:'Keyboard' asFirst:false.
        wsApp loadFile:path.
        needRemove ifTrue:[wsApp removeWorkspace:1].  "/ the original Workspace
        needRemove := false.
    ].

    path := (Smalltalk getSystemFileName:'Setup.wsp').
    (path notNil and:[path asFilename exists]) ifTrue:[
        wsApp addWindow:(HVScrollableView for:Workspace) named:'Setup' asFirst:false.
        wsApp loadFile:path.
        needRemove ifTrue:[wsApp removeWorkspace:1].  "/ the original Workspace
        needRemove := false.
    ].

    path := (Smalltalk getSystemFileName:'Hello.wsp').
    (path notNil and:[path asFilename exists]) ifTrue:[
        wsApp addWindow:(HVScrollableView for:Workspace) named:'Welcome' asFirst:false.
        wsApp loadFile:path.
        needRemove ifTrue:[wsApp removeWorkspace:1].  "/ the original Workspace
        needRemove := false.
    ].

    wsApp openWindow

    "
     self openSystemWorkspace
    "
!

openWith:initialText
    "launch a new workspace with some initial contents"

    ^ self openWith:initialText selected:false

    "
     WorkspaceApplication openWith:'Transcript showCR:''hello world'''
    "
!

openWith:initialText selected:selectedBoolean
    "launch a new workspace with some initial contents"

    |workspace|

    workspace := self new.
    workspace open.
    workspace selectedWorkspace contents:initialText selected:selectedBoolean.
    ^ workspace

    "
     WorkspaceApplication openWith:'Transcript showCR:''hello world'''
    "
! !

!WorkspaceApplication 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:(HVScrollableView for:Workspace).
    ].
    ^ 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
! !

!WorkspaceApplication methodsFor:'aspects'!

autoDefineVariables
    autoDefineVariables isNil ifTrue:[
        autoDefineVariables := ValueHolder new.
        (UserPreferences current autoDefineWorkspaceVariables) ifTrue:[
            autoDefineVariables value:#workspace
        ].
        autoDefineVariables onChangeSend:#autoDefineVariablesChanged to:self.
    ].
    ^ autoDefineVariables.
!

autoDefineWorkspaceVariables
    "does not work yet - needs more interaction with parser"

    autoDefineWorkspaceVariables isNil ifTrue:[
        autoDefineWorkspaceVariables := UserPreferences current autoDefineWorkspaceVariables asValue.
        autoDefineWorkspaceVariables onChangeSend:#autoDefineWorkspaceVariablesChanged to:self.
    ].
    ^ autoDefineWorkspaceVariables.
!

hasHistory
    ^ Workspace doItHistory size > 0.
!

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

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

!WorkspaceApplication methodsFor:'aspects-queries'!

anyWorkspaceVariableIsDefined
    ^ Workspace workspaceVariables size > 0
!

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
! !

!WorkspaceApplication methodsFor:'initialization & release'!

closeRequest
    (self askIfAnyModified:'Text was not saved. Close anyway ?' yesButton:'Close') ifFalse:[
        ^ self
    ].

    ^ super closeRequest
! !

!WorkspaceApplication methodsFor:'menu-actions'!

addGlobalVariable
    |name nameKey selection|

    selection := self selectedWorkspacesTextView selection ? ''.

    name := Dialog 
                request:'Name of new Global Variable:'
                initialAnswer:(selection asString string)
                okLabel:'Add'
                title:'Enter Variable Name'.
    name size == 0 ifTrue:[
        ^ self
    ].
    nameKey := name asSymbol.

    (Smalltalk includesKey:nameKey) ifTrue:[
        self warn:'Global named ''' , name , ''' already exists.'.
        ^ self.
    ].
    Smalltalk at:nameKey put:nil.
!

addGlobalVariableInspector
    |v|

    v := self addInspectorOn:(Smalltalk) basic:false suppressPseudoSlots:true.
    v fieldListLabel:'Name'.
    self renameWorkspace:(self selectedWorkspaceIndexHolder value) to:'Globals (Smalltalk)'.
!

addInspectorOn:aValue basic:isBasicInspector suppressPseudoSlots:suppressPseudoSlots
    |view cls resultString|

    isBasicInspector ifFalse:[
        cls := aValue inspectorClass.
    ].
    cls isNil ifTrue:[
        cls := InspectorView
    ].
    view := cls new.
    view suppressPseudoSlots:suppressPseudoSlots.
    view inspect:aValue.
    "/ v allowFollow:true.
    aValue isBehavior ifTrue:[
        resultString := aValue name
    ] ifFalse:[
        resultString := aValue classNameWithArticle
    ].
    self addWindow:view named:('Inspecting: ' , resultString).
    ^ view
!

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.
!

addWorkspace
    self addWindow:(HVScrollableView for:Workspace) named:'Workspace%1'
!

addWorkspaceVariable
    |name selection|

    selection := self selectedWorkspacesTextView selection ? ''.

    name := Dialog 
                request:'Name of new Workspace Variable:'
                initialAnswer:(selection asString string)
                okLabel:'Add'
                title:'Enter Variable Name'.
    name size == 0 ifTrue:[
        ^ self
    ].
    Workspace addWorkspaceVariable:name.
!

addWorkspaceVariableInspector
    |v|

    v := self addInspectorOn:(Workspace workspaceVariables) basic:false suppressPseudoSlots:true.
    v dereferenceValueHolders:true.
    v fieldListLabel:'Name'.
    self renameWorkspace:(self selectedWorkspaceIndexHolder value) to:'Variables'.
!

askForFilterBlock:message template:template rememberIn:nameOfClassVar
    |filterBlockString filterBlock dialog textHolder classVarValue|

    classVarValue := self class classVarAt:nameOfClassVar ifAbsent:nil.
    classVarValue isNil ifTrue:[
        self class classVarAt:nameOfClassVar put:template. 
        classVarValue := template.
    ].

    textHolder := ValueHolder new.
    dialog := Dialog 
                 forRequestText:(resources string:message)
                 lines:25 
                 columns:70
                 initialAnswer:classVarValue
                 model:textHolder.
    dialog addButton:(Button label:'Template' action:[textHolder value:template. textHolder changed:#value.]).
    dialog open.
    dialog accepted ifFalse:[^ nil].

    filterBlockString := textHolder value.
    self class classVarAt:nameOfClassVar put:filterBlockString. 

    filterBlock := Parser evaluate:filterBlockString.
    filterBlock isBlock ifFalse:[
        self halt:'oops - bad input'.
        ^ nil
    ].

    ^ filterBlock
!

autoDefineVariablesChanged
    |autoDefine|

    autoDefine := autoDefineVariables value.
    UserPreferences current autoDefineWorkspaceVariables:(autoDefine == #workspace).
    workspaces do:[:each |
        each autoDefineVariables:autoDefine
    ].
!

autoDefineWorkspaceVariablesChanged
    "does not work yet - needs more interaction with parser"

    |doAutoDefine|

    doAutoDefine := autoDefineWorkspaceVariables value.
    UserPreferences current autoDefineWorkspaceVariables:doAutoDefine.
    workspaces do:[:each |
        each autoDefineWorkspaceVariables:doAutoDefine
    ].
!

basicInspectIt
    self inspectIt:true
!

browseImplementorsOfIt
    self selectedWorkspacesTextView browseImplementorsOfIt
!

browseIt
    self selectedWorkspacesTextView browseIt
!

browseReferencesToIt
    self selectedWorkspacesTextView browseReferencesToIt
!

clearHistory
    Workspace clearDoItHistory
!

doIt
    self selectedWorkspacesTextView doIt
!

inspectIt
    self inspectIt:false
!

inspectIt:isBasicInspector
    |ws|

    ws := self selectedWorkspacesTextView.
    ws
        do:(ws selection) 
        withValueDo:[:result | 
                        self addInspectorOn:result basic:isBasicInspector suppressPseudoSlots:false
                    ]

"/    self selectedWorkspace inspectIt
!

inspectWorkspaceVariables
    |wsvars|

    wsvars := Workspace workspaceVariables.
    wsvars size == 0 ifTrue:[
        Dialog information:'No Workspace Variables are defined'.
        ^ self
    ].
    wsvars inspect
!

loadFile:aFileName 
    |file ws lbl|

    file := aFileName asFilename.
    file exists ifFalse:[
        Dialog warn:'File ',file asString,' does not exist'.
        ^ self
    ].

    (ws := self selectedWorkspacesTextView) contents:file contents.
    ws modified:false.

    lbl := file withoutSuffix baseName.
    tabList size <= 1 ifTrue:[
        self window label:lbl.
    ] ifFalse:[
        tabList at:self selectedWorkspaceIndexHolder value put:lbl
    ]
!

menuLoad
    |file|

    (self askIfModified:'Text was modified. Load anyway ?' yesButton:'Load') ifFalse:[ ^ self].

    file := Dialog requestFileName:'Load file' default:'file.wsp' pattern:'*.wsp'.
    file size > 0 ifTrue:[
        self loadFile:file
    ]
!

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.
        ]
!

newSystemWorkspace
    self class openSystemWorkspace
!

newWorkspace
    self class open
!

openDocumentation
    "opens the documentation file"

    self openHTMLDocument: 'tools/misc/TOP.html#WORKSPACE'
!

pasteAndExecute:aString
    self paste:aString.
    self printIt
!

printIt
    self selectedWorkspacesTextView printIt
!

processText
    |template filterBlock newList oldList answer nChanged changedLines flags|

    template :=
'"/ general text processor;
"/ the following block should evaluate to a new line, 
"/ given the original line as argument.
"/ Beginner warning: Smalltalk know-how is useful here.

[:line |
     "/ any processing on line.
     "/ Notice, that line might be a Text object (i.e. non-string),
     "/ 
     "/ Useful operations on the line are:
     "/     - '' .... '' ,                      concatenation of any prefix/suffix
     "/     - leftPaddedTo:size                 padding
     "/     - rightPaddedTo:size                padding
     "/     - copyTo:(size min:N)               
     "/     - asUppercase 
     "/     - asLowercase
     "/     - withoutSeparators                 remove whiteSpace
     "/     - asCollectionOfWords               words

     "/ makes everything bold
     "/
     "/ line allBold

     "/ first word only
     "/
     "/ line withoutSeparators asCollectionOfWords first

     "/ dummy filter (keeps all lines as-is)
     "/
     line
]
'.
    filterBlock := self askForFilterBlock:'Processing block:'
                        template:template
                        rememberIn:#LastProcessingBlockString.
    filterBlock isNil ifTrue:[^ self].

    oldList := self selectedWorkspacesTextView list.
    oldList := oldList collect:[:lineOrNil | lineOrNil ? ''].
    newList := oldList collect:[:line | |newLine|
                newLine := line.
                Error handle:[:ex |
                ] do:[
                    newLine := filterBlock value:line
                ].
                newLine
               ].
    newList := newList collect:[:line | (line isString and:[line size == 0]) ifTrue:[nil] ifFalse:[line]].

    flags := (1 to:oldList size) collect:[:i | (oldList at:i) ~= (newList at:i)].
    flags := flags select:[:flag | flag].
    nChanged := flags size.
    nChanged == 0 ifTrue:[
        self information:'No lines were changed.'.
        ^ self
    ].

    answer := Dialog confirmWithCancel:(resources 
                        string:'%1 lines changed. Change text ?'
                        with:nChanged)
                labels:#( 'Cancel' 'No, Show Changed' 'Yes').
    answer isNil ifTrue:[^ self].
    answer ifFalse:[
        changedLines := (1 to:oldList size) select:[:i | (oldList at:i) ~= (newList at:i)].
        changedLines := changedLines collect:[:i | (newList at:i)].
        TextBox openOn:(changedLines asStringCollection) title:'Changed lines'.
        ^ self.
    ].

    self selectedWorkspacesTextView list:newList.
!

redoLastDoIt
    |s|

    s := self lastDoItsString.
    s notNil ifTrue:[
        self pasteAndExecute:s
    ]
!

removeAllWorkspaceVariables
    (Dialog confirm:'Do you really want to remove all Workspace Variables ?')
    ifTrue:[
        Workspace removeAllWorkspaceVariables
   ].
!

removeGlobalVariable
    |name nameKey selection value|

    selection := self selectedWorkspacesTextView selection ? ''.

    name := Dialog 
                request:'Remove Global Variable:'
                initialAnswer:(selection asString string)
                okLabel:'Remove'
                title:'Remove Global'.

    name size == 0 ifTrue:[^ self].
    nameKey := name asSymbolIfInterned.
    nameKey isNil ifTrue:[^ self].

    (Smalltalk includesKey:nameKey) ifFalse:[
        self warn:('No such Global Binding: ''%1''.' bindWith:name).
        ^ self.
    ].

    value := Smalltalk at:nameKey.
    value notNil ifTrue:[
        (self confirm:('Global ''%1'' is currently bound to %2\\Remove Binding ?' bindWith:name with:value) withCRs)
        ifFalse:[
            ^ self.
        ].
    ].
    Smalltalk at:nameKey put:nil.
    Smalltalk removeKey:nameKey
!

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.   
!

removeWorkspaceVariable
    |name selection wsvars|

    wsvars := Workspace workspaceVariables.
    wsvars size == 0 ifTrue:[
        Dialog information:'No Workspace Variables are defined'.
        ^ self
    ].

    selection := self selectedWorkspacesTextView selection ? ''.

    name := Dialog 
                request:'Variable to remove:'
                initialAnswer:(selection asString string)
                okLabel:'Remove'
                title:'Enter Variable Name'
                list:(wsvars keys asOrderedCollection sort).      
    name size == 0 ifTrue:[
        ^ self
    ].
    Workspace removeWorkspaceVariable:name.
!

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.
    ].
!

spyOnIt
    self selectedWorkspacesTextView spyOnIt
!

timeIt
    self selectedWorkspacesTextView timeIt
! !

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

babelFishTranslate:fromToModeString
    "translate the selected text and paste it after the selection"

    self selectedWorkspace babelFishTranslate:fromToModeString
!

copySelection
    self selectedWorkspacesTextView copySelection
!

cutSelection
    self selectedWorkspacesTextView cutSelection
!

fileInText
    self selectedWorkspacesTextView contentsAsString readStream fileIn
!

filterText
    |template filterBlock newList oldList answer nDeleted deletedLines|

    template :=
'"/ general text filter;
"/ the following block should evaluate to true for all lines
"/ you want to keep - lines for which the block returns false will be removed.
"/ Beginner warning: Smalltalk know-how is useful here.

[:line |
     "/ any condition on line.
     "/ Notice, that line might be a Text object (i.e. non-string),
     "/ so you may want to use line string.
     "/ 
     "/ Useful queries on the line are:
     "/     - size                   the length of the line
     "/     - hasChangeOfEmphasis    any bold, italic etc.
     "/     - startsWith:someString
     "/     - endsWith:someString

     "/ example filter (removes all empty lines)
     "/
     "/ line size > 0

     "/ example filter (removes all lines which do not end with some suffix)
     "/
     "/ (line asLowercase endsWith:''foo'') not

     "/ dummy filter (keeps all lines)
     "/
     true
]
'.

    filterBlock := self askForFilterBlock:'Filter block:'
                        template:template
                        rememberIn:#LastFilterBlockString.
    filterBlock isNil ifTrue:[^ self].

    oldList := self selectedWorkspacesTextView list.
    oldList := oldList collect:[:lineOrNil | lineOrNil ? ''].
    newList := oldList select:filterBlock.
    newList := newList collect:[:line | (line isString and:[line size == 0]) ifTrue:[nil] ifFalse:[line]].
    nDeleted := oldList size - newList size.
    nDeleted == 0 ifTrue:[
        self information:'No lines were deleted.'.
        ^ self
    ].

    answer := Dialog confirmWithCancel:(resources 
                        string:'%1 lines remain (%2 deleted). Change text ?'
                        with:newList size
                        with:nDeleted)
                labels:#( 'Cancel' 'No, Show Deleted' 'Yes').
    answer isNil ifTrue:[^ self].
    answer ifFalse:[
        deletedLines := oldList reject:filterBlock.
        TextBox openOn:(deletedLines asStringCollection) title:'Filtered lines'.
        ^ self.
    ].

    self selectedWorkspacesTextView list:newList.
!

googleSpellingSuggestion
    self selectedWorkspacesTextView googleSpellingSuggestion
!

paste
    self selectedWorkspacesTextView paste
!

paste:aString
    self selectedWorkspacesTextView paste:aString.
!

pasteLastDoIt
    |s|

    s := self lastDoItsString.
    s notNil ifTrue:[
        self paste:s
    ]
!

selectAll
    self selectedWorkspacesTextView selectAll.
! !

!WorkspaceApplication methodsFor:'menu-dynamic'!

pasteRecentDoItMenu
    <resource: #programMenu >

    ^ self recentDoItsMenuFor:#'paste:'
!

recentDoItsMenuFor:aSelector
    <resource: #programMenu >

    ^ [
        |doIts m classHistory currentClass|

        doIts := Workspace doItHistory.
        doIts size > 0 ifTrue:[
            m := Menu new.
            doIts do:[:doItEntry |
                |lines label item|

                label := doItEntry withoutLeadingSeparators asStringCollection first.
                (label size > 20) ifTrue:[
                    label := (label contractTo:20)
                ] ifFalse:[
                    (lines size > 1) ifTrue:[
                        label := label , '...'
                    ].
                ].
                label := '''' , label , ''''.

                item := MenuItem label:label.
                m addItem:item.
                item value:aSelector.
                item argument:doItEntry.
            ].
            m addItem: (MenuItem new label:'-').
            m addItem: (MenuItem new 
                        label: 'Clear History'; 
                        value: #clearHistory; 
                        activeHelpKey: #historyEmptyMenu;
                        translateLabel:true).
       ].
        m
    ].
!

redoRecentDoItMenu
    <resource: #programMenu >

    ^ self recentDoItsMenuFor:#'pasteAndExecute:'
! !

!WorkspaceApplication 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:question yesButton:yesButtonText
    (workspaces contains:[:aView | self isModifiedWorkspace:aView]) 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
        (workspaces select:[:aView | (self isModifiedWorkspace:aView)])
        do:[:eachModifiedTextView |
                eachModifiedTextView modified:false.
        ].
        ^ true
    ].
    ^ false
!

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"
!

isModifiedWorkspace:aView
    |view|

    view := self workspaceViewOfView:aView.

    (view isNil
    or:[view modified not 
    or:[view contentsWasSaved
    or:[view contents withoutSeparators isEmpty]]]) ifTrue:[
        ^ false
    ].
    ^ true
!

lastDoItsString
    |history|

    history := Workspace doItHistory.
    history size > 0 ifFalse:[
        self selectedWorkspacesTextView flash.
        ^ nil
    ].
    ^ history first
!

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
! !

!WorkspaceApplication class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/WorkspaceApplication.st,v 1.67 2003-10-09 20:41:08 cg Exp $'
! !