FileApplicationNoteBook.st
changeset 3892 321c1729db5b
child 3906 8a76cb4f5884
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/FileApplicationNoteBook.st	Wed Sep 25 10:00:32 2002 +0200
@@ -0,0 +1,4455 @@
+"{ Package: 'stx:libtool' }"
+
+AbstractFileBrowser subclass:#FileApplicationNoteBook
+	instanceVariableNames:'canvasHolder selectedEditorPage listOfApplications tabMenuIndex
+		tabList selectionHistoryList privateTabList'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Interface-Tools-File'
+!
+
+AbstractFileApplicationNoteBookComponent subclass:#ArchiveViewApplication
+	instanceVariableNames:'archiveFileList enableStopButton fileTable currentSortOrder
+		selectionHolder tableColumns commandProcess errorListHolder
+		viewErrorList temporaryDirectory enableRemoveErrorOutput
+		errorListVisibilityHolder hasListEntriesHolder archiver process
+		terminateByMe columnDescriptors'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:FileApplicationNoteBook
+!
+
+Object subclass:#ArchivItem
+	instanceVariableNames:'fileName size dateAndTime permissions icon ownerGroup method crc
+		compressSize ratio version type isDirectory'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:FileApplicationNoteBook::ArchiveViewApplication
+!
+
+AbstractFileApplicationNoteBookComponent subclass:#CommandResult
+	instanceVariableNames:'resultStream enableStopButton process labelHolder'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:FileApplicationNoteBook
+!
+
+AbstractFileApplicationNoteBookComponent subclass:#HtmlViewApplication
+	instanceVariableNames:'htmlView labelHolder infoLabelHolder'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:FileApplicationNoteBook
+!
+
+AbstractFileApplicationNoteBookComponent subclass:#ImageViewApplication
+	instanceVariableNames:'imageFile imageView image fitSize fitMode'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:FileApplicationNoteBook
+!
+
+AbstractFileApplicationNoteBookComponent subclass:#Terminal
+	instanceVariableNames:'terminalView'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:FileApplicationNoteBook
+!
+
+AbstractFileApplicationNoteBookComponent subclass:#TextEditor
+	instanceVariableNames:'fileContentsModel doSaveFile modifiedChannel editView enableSave
+		enableReload presentation changeItemProcess closeApplication
+		semaChangeItem printAsHexDump itemChanged itemRemoved
+		enableHexToggle textEditorChangeModificationTime'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:FileApplicationNoteBook
+!
+
+AbstractFileApplicationNoteBookComponent subclass:#XViewApplication
+	instanceVariableNames:'xView xFile vncServerPID vncPortNr vncConnection viewerPID
+		vncLock vncServerIsTerminated xItem ext'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:FileApplicationNoteBook
+!
+
+
+!FileApplicationNoteBook class methodsFor:'application list'!
+
+applicationList
+" returns a list of all applications to start by the NoteBookApplication with 
+                #className                         #type                    
+
+            example:
+            #(  #'FooEditor'                       nil                      )
+"
+
+    ^ #(
+            #(  #'TextEditor'                      #file                    )
+            #(  #'TextEditor'                      #directoryDescription    )
+            #(  #'HtmlViewApplication'             nil                      )
+            #(  #'FindFileApplication'             nil                      )
+            #(  #'Terminal'                        nil                      )
+            #(  #'ImageViewApplication'            nil                      )
+            #(  #'ArchiveViewApplication'          nil                      )
+            #(  #'CommandResult'                   nil                      )
+            #(  #'XViewApplication'                nil                      )
+       )
+!
+
+classFor:aApplicationListItem
+    |rawName cls|
+
+    rawName := aApplicationListItem at:1.
+    (cls := self privateClassesAt:rawName) isNil ifTrue:[
+        cls := Smalltalk at:rawName.
+    ].
+    ^ cls
+!
+
+defaultApplication
+" returns the application to be started if no itemQuery returns true or no supportedSuffix is supported
+"
+
+    ^ self applicationList detect:[: applItem|
+        (((self classFor:applItem) == self textEditorClass)
+        and:[(self typeFor:applItem) == #file])
+    ] ifNone:[nil].
+!
+
+typeFor:aApplicationListItem
+
+    ^ aApplicationListItem at:2
+! !
+
+!FileApplicationNoteBook class methodsFor:'classAccess'!
+
+textEditorClass
+
+    ^ TextEditor
+! !
+
+!FileApplicationNoteBook class methodsFor:'defaults'!
+
+openAnotherApplicationOnSameItem
+
+    ^ false
+! !
+
+!FileApplicationNoteBook 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:NoteBookApplication andSelector:#windowSpec
+     NoteBookApplication new openInterface:#windowSpec
+     NoteBookApplication open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'FileBrowserV2TextEditor'
+          #name: 'FileBrowserV2TextEditor'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 16 42 316 342)
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#NoteBookViewSpec
+              #name: 'CommandAndTextEditor'
+              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+              #model: #selectedEditorPage
+              #menu: #tabList
+              #useIndex: true
+              #accessTabMenuAction: #tabMenuAt:
+              #canvas: #canvasHolder
+              #keepCanvasAlive: true
+            )
+           )
+         
+        )
+      )
+! !
+
+!FileApplicationNoteBook class methodsFor:'menu specs'!
+
+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:FileApplicationNoteBook andSelector:#tabMenu
+     (Menu new fromLiteralArrayEncoding:(FileApplicationNoteBook tabMenu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(#Menu
+        #(
+         #(#MenuItem
+            #label: 'Close'
+            #translateLabel: true
+            #value: #doCloseApplication
+          )
+         )
+        nil
+        nil
+      )
+! !
+
+!FileApplicationNoteBook methodsFor:'accessing'!
+
+listOfApplications
+    "return the value of the instance variable 'listOfApplications' (automatically generated)"
+
+    listOfApplications isNil ifTrue:[
+        listOfApplications := OrderedCollection new.
+    ].
+    ^ listOfApplications
+!
+
+selectionHistoryList
+
+    selectionHistoryList isNil ifTrue:[
+        selectionHistoryList := OrderedCollection new.
+    ].
+    ^ selectionHistoryList
+!
+
+selectionHistoryList:aCol
+
+    selectionHistoryList := aCol 
+! !
+
+!FileApplicationNoteBook methodsFor:'accessing applications'!
+
+getAllApplicationsByClass:aClass andType:aType
+
+    ^ self listOfApplications select:[ : appl  |
+        ((appl class = aClass)
+        and:[appl type = aType])
+    ].
+!
+
+getApplicationByType:aType
+
+    ^ self listOfApplications detect:[ : appl  | 
+        (appl type == aType)
+    ] ifNone:[nil].
+!
+
+getIndexFor:aApplication
+
+    | index |
+
+    index := self listOfApplications indexOf:aApplication.
+    index ~~ 0 ifTrue:[
+        ^ index.
+    ].
+    ^ nil.
+!
+
+getSameApplicationsFor:aApplication
+
+    ^ self listOfApplications select:[ : appl |
+        ( (appl ~= aApplication)    
+        and:[ (appl isKindOf:(aApplication class)) 
+        and:[ (appl item = (aApplication item)) 
+        and:[ (appl type == aApplication type) ]]])
+    ].
+! !
+
+!FileApplicationNoteBook methodsFor:'actions-app-common'!
+
+changeItem:aItem for:aAppl
+
+    | applIndex string|
+
+    applIndex := self getIndexFor:aAppl.
+    (aItem notNil and:[aItem isDirectory not]) ifTrue:[
+        (aAppl changeItem:aItem) ifFalse:[ ^ self].
+        self fileHistory add:aItem.
+        self enableFileHistory value:true.
+    ].
+    string := aAppl getTabString.
+    self privateTabList at:applIndex put:string.
+    self doSelect:aAppl.
+!
+
+closeSubCanvas:aApplication
+
+    | applIndex historyList localHistoryList|
+
+    applIndex := self getIndexFor:aApplication.
+    applIndex notNil ifTrue:[
+"/        "/ UPDATE THE LAST SELECTION BECAUSE SEL INDEX IS DECREMENTED FOR HIGHER INDEXES
+"/        self lastSelection:applIndex.
+
+        historyList := self selectionHistoryList.
+        historyList remove:applIndex ifAbsent:nil.
+        localHistoryList := OrderedCollection new.
+        historyList notEmpty ifTrue:[
+            self selectedEditorPage value:(historyList last).
+        ] ifFalse:[
+            self selectedEditorPage value:1.
+        ].
+        historyList do:[ : index |
+            index <= applIndex ifTrue:[
+                localHistoryList add:index
+            ] ifFalse:[
+                localHistoryList add:(index - 1)
+            ]
+        ].
+        self selectionHistoryList:localHistoryList.
+        self listOfApplications removeIndex:applIndex.
+        self privateTabList removeIndex:applIndex.
+        self privateTabList isEmpty ifTrue:[
+            self viewNoteBookApplicationHolder value:false.
+            self enableViewNoteBookApplication value:false.
+        ] ifFalse:[
+            historyList notEmpty ifTrue:[
+                self selectedEditorPage value:(self selectionHistoryList last).
+            ]
+        ]
+    ].
+
+    "/ because subCanvas was configured to keep its view,
+    "/ we must destroy it here.
+    [aApplication window destroy] fork.
+!
+
+doCloseApplication
+
+    | appl |
+
+    appl := self listOfApplications at:tabMenuIndex.
+    appl doClose.
+!
+
+openApplByFileItem:aItem
+
+" use the default class list for open of applications by item "
+
+    | applList applItem itemClass|
+
+    aItem isNil ifTrue:[ ^ self ].
+    applList := self applicationList.
+    applItem := applList detect:[: aApplItem|
+        itemClass := self class classFor:aApplItem.
+        (itemClass canOpenItem:aItem).
+    ] ifNone:[nil].
+    applItem isNil ifTrue:[ ^ self openDefaultApplicationByItem:aItem].
+    applItem notNil ifTrue:[
+        |  itemType |
+        itemType := self class typeFor:applItem.
+        itemClass := self class classFor:applItem.
+        (self openApplicationClass:itemClass withItem:aItem withType:itemType) isNil ifTrue:[
+            ^ self openDefaultApplicationByItem:aItem.            
+        ].
+    ].
+!
+
+openApplicationClass:aClass withItem:aItem withType:aType
+
+    | existingAppl newAppl|
+
+    " do not open not readable items "
+    (aItem notNil and:[aItem isDirectory not and:[aItem fileName isReadable not]]) ifTrue:[
+        Dialog warn:'Can not open unreadable file ', aItem fileName baseName.
+        AbortSignal raise.
+    ].
+    existingAppl := self tryToGetExistingApplFor:aClass withItem:aItem withType:aType.
+    existingAppl notNil ifTrue:[
+        self doSelect:existingAppl.
+        ^ existingAppl
+    ].
+    newAppl := aClass new.
+    newAppl type:aType.
+    (newAppl item:aItem) ifFalse:[ ^ nil ].
+    (aItem notNil and:[aItem isDirectory not]) ifTrue:[
+        self fileHistory add:aItem.
+        self enableFileHistory value:true.
+    ].
+    self setSameFileIndexFor:newAppl.
+    self startApplication:newAppl.
+    ^ newAppl
+!
+
+openDefaultApplicationByItem:aItem
+" open the default application if no application for item is available or the start of the
+  available application failed
+"
+    | applItem |
+
+    applItem := self class defaultApplication.
+    applItem notNil ifTrue:[
+        |  itemType itemClass|
+        itemType := self class typeFor:applItem.
+        itemClass := self class classFor:applItem.
+        ^ self openApplicationClass:itemClass withItem:aItem withType:itemType.
+    ].
+    ^ nil
+!
+
+setSameFileIndexFor:anAppl
+
+    |sameFiles index item|
+
+    self class openAnotherApplicationOnSameItem not ifTrue:[
+        anAppl sameFileIndex:nil.
+        ^ self.
+    ].
+    item := anAppl item.
+    item notNil ifTrue:[
+        | hasSameFiles |
+        sameFiles := self getSameApplicationsFor:anAppl.
+        hasSameFiles := sameFiles notEmpty.
+        hasSameFiles ifTrue:[
+            (sameFiles size == 1 and:[sameFiles first sameFileIndex isNil]) ifTrue:[
+                anAppl sameFileIndex:1.
+                ^ self
+            ] ifFalse:[
+                index :=  (sameFiles collect:[:el | (el sameFileIndex ? 1)]) max.
+                anAppl sameFileIndex:index + 1.
+                ^ self
+            ]
+        ]. 
+        anAppl sameFileIndex:nil.
+    ].
+!
+
+startApplication:aApplication
+
+    | window|
+
+    aApplication masterApplication:self.
+    aApplication window ifNil:[
+        window := ApplicationSubView new.
+        aApplication createBuilder.
+        window client:aApplication.
+    ].
+    self listOfApplications add:aApplication.
+    self privateTabList add:(aApplication getTabString).
+    self viewNoteBookApplicationHolder value:true.
+    self enableViewNoteBookApplication value:true.
+    self doSelect:aApplication.
+    [
+        aApplication postOpenWith:aApplication builder.
+    ] forkAt:Processor activePriority.
+!
+
+tabStringAdd:aString for:aAppl
+
+    | index text stream|
+
+    index := self getIndexFor:aAppl.
+    index isNil ifTrue:[ ^ self].
+    text := self privateTabList at:index.
+    stream := WriteStream on:''.
+    stream nextPutAll:text.
+    stream space.
+    stream nextPutAll:aString.
+    self privateTabList at:index put:stream contents.
+    stream close.
+!
+
+tabStringChangeTo:aString for:aAppl
+
+    | index|
+
+    index := self getIndexFor:aAppl.
+    index isNil ifTrue:[ ^ self].
+    self privateTabList at:index put:aString.
+!
+
+tryToGetExistingApplFor:aClass withItem:aItem withType:aType
+
+
+    |sameAppl changeAppl selAppl|
+
+    aClass wantNewApplicationAnyway ifTrue:[^ nil].
+    sameAppl := self getAllApplicationsByClass:aClass andType:aType.
+    sameAppl isEmpty ifTrue:[^ nil].
+    ((aType == #directoryDescription) or:[aType == #commandResult]) ifTrue:[
+        changeAppl := sameAppl first.
+    ] ifFalse:[
+        (self openMultipleApplicationsForType value) ifTrue:[
+        "/ open more than one application for a class and a type
+            (self class openAnotherApplicationOnSameItem) ifTrue:[
+                "/ open a new application anyway, no matters if item already open
+                ^ nil
+            ] ifFalse:[
+                "/ if item already changed select the application
+                selAppl := sameAppl detect:[ : appl  | 
+                        (appl item = aItem) 
+                ] ifNone:[nil].
+            ].
+        ] ifFalse:[
+            "/ keep in same application change the first application of the same class and type - if item not changed otherwise open new
+                changeAppl := sameAppl detect:[ : appl  | 
+                        (appl isModified not)
+                ] ifNone:[nil].
+        ].
+    ].
+    changeAppl notNil ifTrue:[
+        self changeItem:aItem for:changeAppl.
+        selAppl := changeAppl.
+    ].
+    ^ selAppl.
+! !
+
+!FileApplicationNoteBook methodsFor:'actions-app-spec'!
+
+changeDirectoryDescription
+
+    | aInfoItem|
+
+    aInfoItem := self getInfoItem.
+    aInfoItem isNil ifTrue:[ ^ self closeDirectoryDescription ].
+    self openDirectoryDescription.
+!
+
+closeDirectoryDescription
+
+    | dirContApll |
+
+    dirContApll := self getApplicationByType:#directoryDescription.
+    dirContApll notNil ifTrue:[
+        dirContApll doClose.
+    ].
+!
+
+openArchiveViewApplication:aItem
+
+    | result |
+    result := self openApplicationClass:ArchiveViewApplication withItem:aItem withType:nil.
+    result isNil ifTrue:[
+        Dialog warn:'file type of ', aItem fileName baseName, ' not yet supported'.
+        ^ self.
+    ].
+!
+
+openCommandResultApplication
+
+
+    ^ self openApplicationClass:CommandResult withItem:nil withType:#commandResult
+!
+
+openDirectoryDescription
+
+    | appl aInfoItem|
+
+    aInfoItem := self getInfoItem.
+    aInfoItem notNil ifTrue:[
+        appl := self openTextEditorOn:aInfoItem type:#directoryDescription.
+    ].
+!
+
+openSearchFileOn:aItem
+
+    ^ self openApplicationClass:FindFileApplication withItem:aItem withType:nil
+!
+
+openTerminalApplication:aItem
+
+    ^ self openApplicationClass:Terminal withItem:aItem withType:nil
+!
+
+openTextEditorOn:aItem 
+
+    ^ self openTextEditorOn:aItem type:#file 
+!
+
+openTextEditorOn:aItem type:aDirDescrOrFile
+
+    ^ self openApplicationClass:TextEditor withItem:aItem withType:aDirDescrOrFile
+! !
+
+!FileApplicationNoteBook methodsFor:'applicationlist access'!
+
+applicationList
+    ^ self class applicationList
+! !
+
+!FileApplicationNoteBook methodsFor:'aspects'!
+
+canvasHolder
+
+    canvasHolder isNil ifTrue:[
+        canvasHolder := ValueHolder new.
+    ].
+    ^ canvasHolder.
+!
+
+privateTabList
+
+    privateTabList isNil ifTrue:[
+        privateTabList := List new.
+        privateTabList addDependent:self.
+    ].
+    ^ privateTabList.
+!
+
+selectedEditorPage
+
+    selectedEditorPage isNil ifTrue:[
+        selectedEditorPage := ValueHolder new.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+       selectedEditorPage addDependent:self.
+"/       selectedEditorPage onChangeSend:#selectedEditorPageChanged to:self.
+    ].
+    ^ selectedEditorPage.
+!
+
+tabList
+
+    tabList isNil ifTrue:[
+        tabList := (List new) asValue.
+    ].
+    ^ tabList.
+!
+
+tabList:aValue
+
+    tabList := aValue.
+! !
+
+!FileApplicationNoteBook methodsFor:'change & update'!
+
+update:something with:aParameter from:changedObject
+    "Invoked when an object that I depend upon sends a change notification."
+
+    "stub code automatically generated - please change as required"
+
+    | appl sel viewDirDescr|
+
+
+    changedObject == self currentDirectories ifTrue:[
+        self viewDirectoryDescription value ifTrue:[
+            self changeDirectoryDescription.  
+        ].
+        ^ self.
+    ].
+    changedObject == self viewDirectoryDescription ifTrue:[
+        viewDirDescr := changedObject value.
+        viewDirDescr ifTrue:[
+            self openDirectoryDescription.
+        ] ifFalse:[
+            self closeDirectoryDescription.
+        ].
+        ^ self.
+    ].
+    changedObject == self privateTabList ifTrue:[
+        | privateListOfTabs |
+        privateListOfTabs := changedObject.
+        privateListOfTabs size > 1 ifTrue:[
+            self tabList value:privateListOfTabs.
+            self tabList changed.
+        ] ifFalse:[
+            self tabList value:nil.
+        ].
+        ^ self
+    ].
+    changedObject == self selectedEditorPage ifTrue:[
+        | listOfEdits indexOfLastSel list |
+
+        sel := changedObject value.
+        "/ dont want the tabs with one application - thats why i have to change my tablist
+        "/ sel goes to if - i want select the last selection
+        sel = 0 ifTrue:[
+            ^ self.
+        ].
+        list := self selectionHistoryList.
+        (list includes:sel) ifTrue:[
+            list remove:sel
+        ].
+        list add:sel.
+        self selectionHistoryList:list.
+        appl := self listOfApplications at:sel.
+        self doSelect:appl.
+    ].
+
+    ^ super update:something with:aParameter from:changedObject
+! !
+
+!FileApplicationNoteBook methodsFor:'menu & actions'!
+
+tabMenuAt:aTab
+
+    |menu|
+
+    menu :=  Menu new fromLiteralArrayEncoding:self class tabMenu.
+    menu ifNil:[ ^ nil ].
+    tabMenuIndex := aTab.
+    menu receiver:self.
+    ^ menu
+! !
+
+!FileApplicationNoteBook methodsFor:'queries'!
+
+getSameFilesModifiedFor:aAppl
+
+    | sameFileAppl colOfChanged |
+
+    sameFileAppl := self getSameApplicationsFor:aAppl.
+    sameFileAppl notEmpty ifTrue:[
+        colOfChanged := OrderedCollection new.
+        sameFileAppl do:[ : el |
+            el modifiedChannel value ifTrue:[
+                colOfChanged add:el.
+            ]
+        ]
+    ].
+    ^ colOfChanged
+! !
+
+!FileApplicationNoteBook methodsFor:'selection'!
+
+doSelect:anAppl
+
+    | index fileName|
+
+    fileName := anAppl fileName.
+    fileName notNil ifTrue:[
+        self changeFileBrowserTitleTo:fileName baseName.
+    ].
+    index := self getIndexFor:anAppl.
+
+    index notNil ifTrue:[
+        canvasHolder value:(anAppl window).
+        self selectedEditorPage value:index.
+    ]
+! !
+
+!FileApplicationNoteBook methodsFor:'startup & release'!
+
+makeDependent
+
+    self viewDirectoryDescription addDependent:self.
+    self currentDirectories addDependent:self.
+!
+
+postOpenAsSubcanvasWith:aBuilder
+
+    self viewDirectoryDescription changed.
+    ^ super postOpenAsSubcanvasWith:aBuilder.
+!
+
+postOpenWith:aBuilder
+
+    "
+    only invoked if the application not started from a master
+    "
+    self openTextEditorOn:(DirectoryContentsBrowser itemClass with:(Filename homeDirectory construct:'.bashrc')).
+    ^ super postOpenWith:aBuilder
+!
+
+preBuildWith:aBuilder
+
+    self masterApplication isNil ifTrue:[
+        self masterApplication:nil.
+    ].
+    ^ super preBuildWith:aBuilder.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication class methodsFor:'common options'!
+
+SupportedFiles
+
+    | dict |
+    dict := Dictionary new.
+
+    #(
+        'application/x-tar-compressed'      tarGZipArchive
+        'application/x-tar'                 tarArchive
+        'application/x-gzip-compressed'     gzipArchive
+        'application/x-zip-compressed'      zipArchive
+    ) pairWiseDo:[ : mimeType :classSelector |
+        dict at:mimeType put:classSelector.
+    ].
+    ^ dict
+!
+
+classSelectorFor:aItem
+
+    | class |
+    aItem hasMimeType ifFalse:[^nil].
+    class := self SupportedFiles at:(aItem mimeType) ifAbsent:nil.
+    class isNil ifTrue:[
+        (aItem lastButOneSuffix = 'tar' and:[aItem lastSuffix = 'gz']) ifTrue:[
+            class := #tarGZipArchive.
+        ].
+    ].
+    ^ class.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication class methodsFor:'defaults'!
+
+tabStringFor:aApplicationType
+
+    ^ 'Archive for:'
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication class methodsFor:'image specs'!
+
+removeError
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self removeError inspect
+     ImageEditor openOnClass:self andSelector:#removeError
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:#'FileApplicationNoteBook::ArchiveViewApplication class removeError'
+        ifAbsentPut:[(Depth8Image new) width: 28; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@FA @@@@@@@@XF@@@@@@@@@@@@@@@@@@@@@@@@@@XF@@@@@@XF@@@@@@@@@@@@@@@@@@@@@@@@@@@@A X@@@XF@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@FA XF@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@XF@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@XFA X@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@XF
+@@@FA @@@@@@@@@@@@@@@@@@@@@@@@@@@@XF@@@@@@XF@@@@@@@@@@@@@@@@@@@@@@@@@@XF@@@@@@@@A X@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 8 4 8 105 133 190 121 133 157 129 129 129 194 194 194 255 0 0]; mask:((Depth1Image new) width: 28; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@LC@@@A!! @@@L0@@@A8@@@@L@@@@G @@@CL@@@A!! @@@0L@@@@@@@BY=5LAIUUT S5UU8D!!UUPAFU\#@@@@@@@LR9@@D)J @A:R(@@P$*@@CIN @@@@@@@@@a') ; yourself); yourself]
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication 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:NoteBookApplication::ArchiveViewApplication andSelector:#windowSpec
+     NoteBookApplication::ArchiveViewApplication new openInterface:#windowSpec
+     NoteBookApplication::ArchiveViewApplication open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'Archive Application'
+          #name: 'Archive Application'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 12 22 688 514)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#MenuPanelSpec
+              #name: 'MenuTerminal'
+              #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 32 0)
+              #menu: #menu
+              #textDefault: true
+            )
+           #(#'FileBrowserV2UISpecifications::PanelSpec'
+              #name: 'VerticalPanel'
+              #layout: #(#LayoutFrame 0 0.0 32 0.0 0 1.0 0 1.0)
+              #borderWidth: 1
+              #whichView: #last
+              #orientation: #vertical
+              #visibility: #errorListVisibilityHolder
+              #component: 
+             #(#SpecCollection
+                #collection: #(
+                 #(#DataSetSpec
+                    #name: 'Table1'
+                    #model: #selectionHolder
+                    #menu: #fileListMenu
+                    #hasHorizontalScrollBar: true
+                    #hasVerticalScrollBar: true
+                    #dataList: #archiveFileList
+                    #useIndex: false
+                    #has3Dsepartors: false
+                    #doubleClickSelector: #dblClick
+                    #columnHolder: #tableColumns
+                    #multipleSelectOk: true
+                    #verticalSpacing: 0
+                    #postBuildCallback: #postBuildFileTable:
+                    #properties: 
+                   #(#PropertyListDictionary
+                      #dragArgument: #archivApplication
+                      #startDragSelector: #doStartDrag:in:
+                      #displayObjectSelector: #getDisplayObjects:
+                      #dropObjectSelector: #getDropObjects:
+                      #dropArgument: #archivApplication
+                      #canDropSelector: #canDrop:argument:
+                      #dropSelector: #doDrop:argument:
+                    )
+                  )
+                 #(#SequenceViewSpec
+                    #name: 'ErrorList'
+                    #initiallyDisabled: true
+                    #hasHorizontalScrollBar: true
+                    #hasVerticalScrollBar: true
+                    #backgroundColor: #(#Color 100.0 100.0 100.0)
+                    #isMultiSelect: true
+                    #useIndex: false
+                    #sequenceList: #errorListHolder
+                  )
+                 )
+               
+              )
+              #handles: #(#Any 0.5 1.0)
+            )
+           )
+         
+        )
+      )
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication class methodsFor:'menu specs'!
+
+fileListMenu
+    "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:NoteBookApplication::ArchiveViewApplication andSelector:#fileListMenu
+     (Menu new fromLiteralArrayEncoding:(NoteBookApplication::ArchiveViewApplication fileListMenu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(#Menu
+        #(
+         #(#MenuItem
+            #label: 'Extract to Directory'
+            #translateLabel: true
+            #value: #extractAll
+            #enabled: #hasSelectionInList
+          )
+         #(#MenuItem
+            #label: 'Delete from Archiv'
+            #translateLabel: true
+            #value: #removeFilesFromArchiv
+            #enabled: #canDelete
+            #shortcutKeyCharacter: #Delete
+          )
+         #(#MenuItem
+            #label: 'View'
+            #translateLabel: true
+            #isVisible: #isEmbeddedApplication
+            #value: #viewFile
+            #enabled: #hasOneSelectionInList
+          )
+         #(#MenuItem
+            #label: 'Copy Filenames'
+            #translateLabel: true
+            #value: #copyFilesToClipboard
+            #enabled: #hasSelectionInList
+          )
+         #(#MenuItem
+            #label: 'Select All'
+            #translateLabel: true
+            #value: #selectAll
+            #enabled: #hasListEntriesHolder
+          )
+         )
+        nil
+        nil
+      )
+!
+
+menu
+    "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:FileApplicationNoteBook::ArchiveViewApplication andSelector:#menu
+     (Menu new fromLiteralArrayEncoding:(FileApplicationNoteBook::ArchiveViewApplication menu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(#Menu
+        #(
+         #(#MenuItem
+            #label: 'Stop'
+            #translateLabel: true
+            #isButton: true
+            #nameKey: #Stop
+            #value: #doStopProcess
+            #enabled: #enableStopButton
+            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #stop22x22Icon)
+          )
+         #(#MenuItem
+            #label: 'Exctract'
+            #translateLabel: true
+            #isButton: true
+            #value: #extractAll
+            #enabled: #hasListEntriesHolder
+            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #extract28x28Icon)
+          )
+         #(#MenuItem
+            #label: 'Remove Output'
+            #translateLabel: true
+            #isButton: true
+            #value: #removeErrorOutput
+            #enabled: #enableRemoveErrorOutput
+            #labelImage: #(#ResourceRetriever nil #removeError)
+          )
+         #(#MenuItem
+            #label: 'Close'
+            #translateLabel: true
+            #isButton: true
+            #hideMenuOnActivated: false
+            #isVisible: #isEmbeddedApplication
+            #startGroup: #right
+            #value: #doClose
+            #labelImage: #(#ResourceRetriever #AbstractFileBrowser #closeIcon)
+          )
+         )
+        nil
+        nil
+      )
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication class methodsFor:'queries'!
+
+canOpenItem:aItem
+
+    ^ (aItem hasMimeType and:[(aItem mimeType isArchiv) and:[OperatingSystem isUNIXlike]])
+!
+
+wantNewApplicationAnyway
+
+    ^ false
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication class methodsFor:'tableColumns specs'!
+
+tableColumns
+    "This resource specification was automatically generated
+     by the DataSetBuilder of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the DataSetBuilder may not be able to read the specification."
+
+    "
+     DataSetBuilder new openOnClass:NoteBookApplication::ArchiveViewApplication andSelector:#tableColumns
+    "
+
+    <resource: #tableColumns>
+
+    ^#(
+      #(#DataSetColumnSpec
+         #id: 'icon'
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'directory'
+         #width: 25
+         #minWidth: 20
+         #height: 16
+         #model: #icon
+         #canSelect: false
+         #isResizeable: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'File Name'
+         #id: 'fileName'
+         #labelAlignment: #left
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'fileName'
+         #model: #fileName
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Perm'
+         #id: 'permissions'
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'permissions'
+         #usePreferredWidth: true
+         #width: 75
+         #model: #permissions
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Version'
+         #id: 'version'
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'version'
+         #columnAlignment: #right
+         #width: 100
+         #minWidth: 50
+         #model: #version
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Type'
+         #id: 'type'
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'type'
+         #columnAlignment: #right
+         #width: 100
+         #minWidth: 50
+         #model: #type
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Owner/Group'
+         #id: 'ownerGroup'
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'ownerGroup'
+         #columnAlignment: #right
+         #width: 100
+         #minWidth: 50
+         #model: #ownerGroup
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Size'
+         #id: 'size'
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'sizeAsNumber'
+         #columnAlignment: #right
+         #width: 80
+         #model: #size
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Date & Time'
+         #id: 'dateAndTime'
+         #labelAlignment: #right
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'dateAndTime'
+         #columnAlignment: #right
+         #usePreferredWidth: true
+         #width: 140
+         #model: #dateAndTime
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Method'
+         #id: 'method'
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'method'
+         #columnAlignment: #center
+         #usePreferredWidth: true
+         #width: 140
+         #model: #method
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'CRC'
+         #id: 'crc'
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'crc'
+         #usePreferredWidth: true
+         #width: 140
+         #model: #crc
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Compress Size'
+         #id: 'compressSize'
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'compressSize'
+         #usePreferredWidth: true
+         #width: 140
+         #model: #compressSize
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Ratio'
+         #id: 'ratio'
+         #labelButtonType: #Button
+         #labelActionSelector: #sortList:
+         #labelActionArgument: 'ratio'
+         #usePreferredWidth: true
+         #width: 140
+         #model: #ratio
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      )
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'accessing'!
+
+archiver
+    "return the value of the instance variable 'archiver' (automatically generated)"
+
+    ^ archiver
+!
+
+archiver:something
+    "set the value of the instance variable 'archiver' (automatically generated)"
+
+    archiver := something.
+!
+
+columnDescriptors
+    "return the value of the instance variable 'columnDescriptors' (automatically generated)"
+
+    ^ columnDescriptors
+!
+
+columnDescriptors:aListOfColumns
+    "set the value of the instance variable 'columnDescriptors' (automatically generated)"
+
+    columnDescriptors = aListOfColumns ifTrue:[
+        ^ self
+    ].
+
+    columnDescriptors    := OrderedCollection new.
+
+    aListOfColumns keysAndValuesDo:[:anIndex :aDesc| |col|
+        col := aDesc isSequenceable ifTrue:[DataSetColumnSpec new fromLiteralArrayEncoding:aDesc]
+                                   ifFalse:[aDesc].
+        columnDescriptors add:col.
+    ].
+!
+
+item:aItem
+    "set the value of the instance variable 'item' (automatically generated)"
+
+    | classSelector|
+    
+    super item:aItem.
+    classSelector := self class classSelectorFor:aItem.
+    (classSelector notNil and:[(Archiver respondsTo:classSelector) notNil]) ifTrue:[
+        self makeProcessFor:[
+            self archiver:((Archiver perform:classSelector) with:(self fileName)).
+            self setColumnsForArchiver.
+        ] with:'setup archiv'.
+        ^ true
+    ]. 
+    ^ false
+!
+
+temporaryDirectory
+    "return the value of the instance variable 'temporaryDirectory' (automatically generated)"
+
+    temporaryDirectory isNil ifTrue:[
+        temporaryDirectory := Filename newTemporary.
+        temporaryDirectory makeDirectory.
+    ].
+    ^ temporaryDirectory
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'actions'!
+
+changeItem:aItem
+
+    self item:aItem.
+    self emptyList.
+    self listAllFilesFromArchiv.
+    ^ true
+!
+
+copyFilesToClipboard
+
+
+    |sel list stream|
+
+    sel := self selectionHolder value.
+    list := self archiveFileList.
+    (sel notNil and:[sel notEmpty]) ifTrue:[
+        stream := WriteStream on:''.
+        sel do:[: key |
+            stream nextPutAll:(key fileName asString).
+            stream cr.
+        ].
+        self window setTextSelection:stream contents.
+        stream close.
+    ].
+!
+
+dblClick
+
+    self viewFile.
+!
+
+doStopProcess
+
+    | archiver |
+    self stopProcess.
+    archiver := self archiver.
+    archiver notNil ifTrue:[
+        self archiver stopProcess.
+    ].
+    self enableStopButton value:false.
+!
+
+emptyList
+
+    self archiveFileList value removeAll.
+!
+
+removeErrorOutput
+
+    self viewErrorList value:false.
+    self errorListHolder removeAll.
+!
+
+removeTemporaryDirectory
+
+    | tmp |
+
+    temporaryDirectory notNil ifTrue:[
+        tmp := self temporaryDirectory.
+        (FileDirectory directoryNamed:(tmp directory)) removeDirectory:tmp baseName.
+        temporaryDirectory := nil.
+    ].
+!
+
+selectAll
+
+    | sel listOfFiles|
+
+    sel := OrderedCollection new.
+    listOfFiles := self archiveFileList value.
+    1 to:(listOfFiles size) do:[ : el |
+        sel add:el
+    ].
+    self selectionHolder value:sel.
+!
+
+updateFileBrowserIfPresentWith:aDirectory
+
+    | master|
+
+    master := self masterApplication.
+    master notNil ifTrue:[
+        master updateAndSelect:(OrderedCollection with:aDirectory).
+    ].
+!
+
+viewFile
+
+    | master item file tempDir|
+
+    master := self masterApplication.
+    self selectionHolder value size = 1 ifFalse:[
+        Dialog warn:'only one file have to be selected'.
+        ^ self.
+    ].
+    tempDir := self temporaryDirectory.
+    self extractSelectedFilesTo:tempDir askForExtractOptions:false.
+    process notNil ifTrue:[
+        process waitUntilTerminated.
+    ].
+    file := tempDir construct:self selectionHolder value first fileName.
+    file exists ifTrue:[
+        item := DirectoryContentsBrowser itemClass with:file.
+    ].
+    master notNil ifTrue:[
+        master openApplByFileItem:item.
+    ].
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'aspects'!
+
+archiveFileList
+
+    archiveFileList isNil ifTrue:[
+        archiveFileList := List new.
+        archiveFileList addDependent:self.
+    ].
+    ^ archiveFileList.
+!
+
+enableRemoveErrorOutput
+    "return/create the 'enableRemoveErrorOutput' value holder (automatically generated)"
+
+    enableRemoveErrorOutput isNil ifTrue:[
+        enableRemoveErrorOutput := false asValue.
+    ].
+    ^ enableRemoveErrorOutput
+!
+
+enableStopButton
+
+    enableStopButton isNil ifTrue:[
+        enableStopButton := false asValue.
+    ].
+    ^ enableStopButton
+!
+
+errorListHolder
+
+    errorListHolder isNil ifTrue:[
+        errorListHolder := List new.
+    ].
+    ^ errorListHolder.
+!
+
+errorListVisibilityHolder
+
+    errorListVisibilityHolder isNil ifTrue:[
+        errorListVisibilityHolder := false asValue.
+    ].
+    ^ errorListVisibilityHolder
+!
+
+hasListEntriesHolder
+    "return/create the 'hasListEntriesHolder' value holder (automatically generated)"
+
+    hasListEntriesHolder isNil ifTrue:[
+        hasListEntriesHolder := false asValue.
+    ].
+    ^ hasListEntriesHolder
+!
+
+hasOneSelectionInList
+
+    | sel |
+    sel := self selectionHolder value.
+    ^ (sel notNil and:[sel notEmpty and:[sel size = 1]])
+!
+
+hasSelectionInList
+
+    | sel |
+    sel := self selectionHolder value.
+    ^ (sel notNil and:[sel notEmpty])
+!
+
+selectionHolder
+
+    selectionHolder isNil ifTrue:[
+        selectionHolder := ValueHolder new.
+        selectionHolder addDependent:self.
+    ].
+    ^ selectionHolder.
+!
+
+tableColumns
+
+    tableColumns isNil ifTrue:[
+        tableColumns := self class tableColumns asValue.
+    ].
+    ^ tableColumns.
+!
+
+viewErrorList
+    "return/create the 'viewErrorList' value holder (automatically generated)"
+
+    viewErrorList isNil ifTrue:[
+        viewErrorList := false asValue.
+        viewErrorList onChangeSend:#viewErrorListChanged to:self.
+    ].
+    ^ viewErrorList
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'change & update'!
+
+update:something with:aParameter from:changedObject
+    "Invoked when an object that I depend upon sends a change notification."
+
+    "stub code automatically generated - please change as required"
+
+    changedObject == self archiveFileList ifTrue:[
+        self hasListEntriesHolder value:(changedObject notEmpty).
+        ^ self
+    ].
+    super update:something with:aParameter from:changedObject
+!
+
+viewErrorListChanged
+
+    | viewListValue|
+
+    viewListValue := self viewErrorList value.
+    self enableRemoveErrorOutput value:viewListValue.
+    self errorListVisibilityHolder value:viewListValue.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'command execution'!
+
+getErrorBlock
+
+    ^
+    [: x |
+        self viewErrorList value:true.
+        self errorListHolder value add:x.
+    ]
+!
+
+getErrorStream
+
+    |errStream|
+
+    errStream := ActorStream new.
+    errStream nextPutLineBlock:(self getErrorBlock).
+    ^ errStream
+!
+
+getOutBlock
+
+    |firstLineNotReaded key|
+
+    firstLineNotReaded := true.
+    ^ [: line |
+        | words ownerGroup item archiverColumns itemWriter index itemWordCount|
+
+        (firstLineNotReaded and:[archiver class hasTitleLine]) ifTrue:[
+            firstLineNotReaded := false.
+        ]ifFalse:[
+            words := line asCollectionOfWords.
+            archiverColumns := archiver class columns.
+            item := ArchivItem new.
+            index := 1.
+            archiverColumns do:[:colDescr |
+                | itemStream |
+                itemWordCount := colDescr second.
+                itemWriter := ((colDescr first) asString, ':') asSymbol.
+                itemStream := WriteStream on:''.
+                index to:(index + itemWordCount - 1) do:[:i|
+                    itemStream nextPutAll:(words at:i).
+                    itemStream space.
+                ].
+                item perform:itemWriter with:(itemStream contents).
+                itemStream close.
+                index := index + itemWordCount.
+            ].
+            ((archiverColumns collect:[:el| el first]) includes:#permissions) ifTrue:[
+                (item permissions startsWith:$d) ifTrue:[
+                    key := #directory.
+                    item isDirectory:true.
+                ] ifFalse:[
+                    key := MIMETypes mimeTypeForFilename:(item fileName asFilename baseName).
+                    item isDirectory:false.
+                ].
+            ] ifFalse:[
+                key := MIMETypes mimeTypeForFilename:(item fileName asFilename baseName).
+            ].
+            item icon:(FileBrowser iconForKeyMatching:key).
+            self archiveFileList value add:item
+        ].
+    ]
+!
+
+getOutStream
+
+    |outStream|
+
+    outStream := ActorStream new.
+    outStream nextPutLineBlock:(self getOutBlock).
+    ^ outStream
+!
+
+makeProcessFor:aBlock
+
+    self makeProcessFor:aBlock with:''
+!
+
+makeProcessFor:aBlock with:string
+
+    | locBlock |
+
+    process notNil ifTrue:[
+        process waitUntilTerminated.
+        terminateByMe ifTrue:[
+            terminateByMe := false.
+            ^ self
+        ].
+    ].
+    locBlock := [   [        
+                    self notifyChannel value:string.
+                    aBlock value.
+                    self notifyChannel value:''.
+                    ] valueNowOrOnUnwindDo:[ 
+                        process := nil.
+                        self enableStopButton value:false.
+                    ] 
+                ].
+    process := locBlock newProcess.
+    process priority:(Processor systemBackgroundPriority).
+    process name:'ArchiveApplicationProcess'.
+    self enableStopButton value:true.
+    process resume.
+!
+
+setColumnsForArchiver
+
+    | newColumns archiverColumns allColumns iconColumn|
+
+    archiverColumns := archiver class columns collect:[:el| el  first].
+    allColumns := OrderedCollection new.
+    newColumns := OrderedCollection new.
+    self class tableColumns do:[:el|
+        allColumns add:(DataSetColumnSpec new fromLiteralArrayEncoding:el).
+    ].
+    iconColumn := allColumns detect:[: col | (col id asSymbol) = #icon] ifNone:[nil].
+    iconColumn notNil ifTrue:[
+        newColumns add:iconColumn.
+    ].
+    allColumns do:[:col|
+        (archiverColumns includes:(col id asSymbol)) ifTrue:[
+            newColumns add:col.
+        ].
+    ].
+    self tableColumns value:newColumns.
+    self columnDescriptors:(self tableColumns value).
+!
+
+stopProcess
+
+    |task|
+
+    terminateByMe := true.
+    (task := process) notNil ifTrue:[
+        process := nil.
+
+        Object errorSignal handle:[:ex|
+            Dialog warn:ex description.
+        ]do:[
+            task isDead ifFalse:[
+                task terminateWithAllSubprocesses.
+                task waitUntilTerminated.
+            ]
+        ]
+    ].
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'command helper'!
+
+selectDirectoryDialog
+
+    | dir directory haveDirectory|
+
+    directory := self fileName directory.
+    haveDirectory := false.
+    [haveDirectory] whileFalse:[
+        dir := Dialog requestDirectoryName:'Which directory ?' default:dir.
+        dir isEmpty ifTrue:[ ^ self].
+        dir := dir asFilename.
+        (dir isExecutable not or:[dir isWritable not]) ifTrue:[
+            Dialog warn:'cant write to: ', dir asString.
+        ].
+        haveDirectory := true.
+    ].
+    ^ dir
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'commands add'!
+
+addFilesToArchiv:colOfFiles
+
+
+    self archiver outStream:nil errorStream:(self getErrorStream) synchron:true.
+    self makeProcessFor:[
+        self archiver addFilesToArchiv:colOfFiles.
+    ] with:'add Files to archiv'.
+    (self archiver class == Archiver zipArchive) ifTrue:[
+        self listAllFilesFromArchiv.
+    ] ifFalse:[
+        self listFilesFromArchiv:colOfFiles.
+    ].
+    ^ true.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'commands extract'!
+
+extractAll
+
+    self extractSelectedFilesTo:nil withSelection:#all
+!
+
+extractSelectedFilesTo:aDirectory askForExtractOptions:askForExtractOptionsBoolean
+
+    self extractSelectedFilesTo:aDirectory withSelection:#selection askForExtractOptions:askForExtractOptionsBoolean
+!
+
+extractSelectedFilesTo:aDirectory withSelection:selectOrAll
+
+    self extractSelectedFilesTo:aDirectory withSelection:selectOrAll askForExtractOptions:true.
+!
+
+extractSelectedFilesTo:aDirectory withSelection:selectOrAll askForExtractOptions:askForExtractOptionsBoolean
+
+    | dir|
+
+    aDirectory isNil ifTrue:[
+        dir := self selectDirectoryDialog.
+        dir isNil ifTrue:[^ self].
+    ] ifFalse:[
+        dir := aDirectory.
+    ].
+    selectOrAll == #all ifTrue:[
+       self extractAllTo:dir.
+    ].
+    selectOrAll == #selection ifTrue:[
+        self extractSelectionTo:dir askForExtractOptions:askForExtractOptionsBoolean
+    ].
+    self updateFileBrowserIfPresentWith:dir.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'commands extract private'!
+
+extractAllTo:aDirectory 
+
+    self archiver outStream:nil errorStream:(self getErrorStream) synchron:true.
+    self makeProcessFor:[
+        self archiver extractTo:aDirectory.
+    ] with:'extract all files'.
+    ^ true.
+!
+
+extractSelectionTo:aDirectory askForExtractOptions:askForExtractOptionsBoolean
+
+    |  sel index extractWithDirectoryPart extractAllFilesInSelectedDirectories extractFiles|
+
+    extractWithDirectoryPart := true.
+    extractAllFilesInSelectedDirectories := false.
+    sel := self selectionHolder value.
+    (sel isNil or:[sel isEmpty]) ifTrue:[
+        sel := self archiveFileList value.
+    ].
+    sel := sel do:[:item|
+        item fileName: item fileName
+    ].
+    (askForExtractOptionsBoolean and:[self archiver class ~= Archiver zipArchive]) ifTrue:[
+        extractFiles := self selRemoveFilesForDirs:sel.
+    ] ifFalse:[
+        extractFiles := sel.
+    ].
+    
+    askForExtractOptionsBoolean ifTrue:[
+        index := extractFiles findFirst:[: el | el hasDirectoryPart].
+        index ~= 0 ifTrue:[
+            extractWithDirectoryPart := (Dialog confirmWithCancel:'Extract with directory part?' default:true).
+            extractWithDirectoryPart isNil ifTrue:[^ false].
+        ].
+    ].
+    extractWithDirectoryPart ifTrue:[
+        self extractWithDirectoryPartTo:aDirectory with:extractFiles.
+    ] ifFalse:[
+        self extractWithOutDirectoryPartTo:aDirectory with:extractFiles.
+    ].
+    ^ true
+!
+
+extractWithDirectoryPartTo:aDirectory with:extractFiles
+
+    self archiver outStream:nil errorStream:(self getErrorStream) synchron:true.
+    self makeProcessFor:[
+        self archiver extractTo:aDirectory with:extractFiles.
+    ] with:('extract Files to ', aDirectory asString).
+    ^ true.
+!
+
+extractWithOutDirectoryPartTo:aDirectory with:extractFiles
+
+    self archiver outStream:nil errorStream:(self getErrorStream) synchron:true.
+    self makeProcessFor:[
+        self archiver extractWithOutDirectoryTo:aDirectory 
+                      with:(extractFiles collect:[:item| item fileName]).
+    ] with:('extract Files to ', aDirectory asString).
+    ^ true.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'commands list'!
+
+listAllFilesFromArchiv
+
+    self archiveFileList value removeAll.
+    self listFilesFromArchiv:nil
+!
+
+listFilesFromArchiv:newColOfFiles
+
+    process notNil ifTrue:[
+        process waitUntilTerminated.
+    ].
+    self archiver outStream:(self getOutStream) errorStream:(self getErrorStream) synchron:true.
+    self makeProcessFor:[
+        self archiver listFilesFromArchiv:newColOfFiles.
+    ] with:'list Files'.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'commands remove'!
+
+removeFilesFromArchiv
+
+    | sel realSel list firtsPre stringCol stringRealSel|
+
+    sel := self selectionHolder value.
+    stringCol := sel collect:[: item| item fileName].
+    firtsPre := stringCol at:1.
+    stringCol from:2 do:[:el|
+         firtsPre :=  firtsPre commonPrefixWith:el.
+    ].
+    list := self archiveFileList value.
+    realSel := OrderedCollection new.
+    list do:[:item|
+        ((item fileName) startsWith:firtsPre) ifTrue:[
+            realSel add:item.
+        ].
+    ].
+    stringRealSel := realSel collect:[: item| item fileName].
+
+    self archiver outStream:nil errorStream:(self getErrorStream) synchron:true.
+    self makeProcessFor:[
+        self archiver removeFilesFromArchiv:stringCol.
+    ] with:'remove files'.
+
+    self archiveFileList value removeAll:realSel
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'drag & drop'!
+
+canDrop:aContext argument:arg2 
+
+
+    |arg |
+    archiver class canAddFiles ifFalse:[^ false].
+    arg := aContext dropSource argument.
+    (arg == #browser or:[arg == #directoryTreeBrowser]) ifTrue:[
+        ^ true
+    ].
+    ^ false.
+!
+
+doDrop:aContext
+
+    |col source arg objects|
+
+    source := aContext dropSource.
+    arg := source argument.
+    objects := aContext dropObjects.
+    col := OrderedCollection new.
+    objects do:[:obj|
+        col add:(obj theObject).
+    ].
+    ^ self addFilesToArchiv:col.
+!
+
+doDrop:aContext argument:arg2 
+
+    | aBoolean |
+
+    aBoolean := self doDrop:aContext.
+    ^ aBoolean.
+!
+
+doStartDrag:aDropSource in:aView
+    "set the cursors before starting the drag & drop operation
+    "
+    |hdl sel|
+
+    archiver class canRemoveFiles ifFalse:[^ self].
+    sel := self selectionHolder value.
+
+    hdl := DragAndDropManager new.
+
+    hdl disabledCursor:self class DisabledCursorImage.
+    hdl enabledCursor:self class EnabledCursorImage.
+    hdl alienCursor:nil.
+
+    hdl startDragFrom:aView dropSource:aDropSource offset:#topLeft
+!
+
+getDisplayObjects:anArgument
+
+    | sel string size fnName stream|
+    sel := self selectionHolder value.
+    size := sel size.
+    size == 0  ifTrue:[^ ''].
+    stream := WriteStream on:''.
+    stream nextPutAll:(sel first fileName asFilename baseName asString).
+    size == 1 ifTrue:[
+        fnName := 'ui_menuitem.xpm'.
+    ] ifFalse:[
+        fnName := 'ui_submenu_open.xpm'.
+        stream nextPutAll:' ... '.
+        stream nextPutAll:(sel last fileName asFilename baseName asString).
+    ].
+    string := stream contents.
+    stream close.
+    ^ Array with:(LabelAndIcon icon:(Image fromFile:fnName)
+                             string:(Text string:string emphasis:#bold)
+                 )
+!
+
+getDropObjects:anArgument
+
+    | sel ret|
+    sel := self selectionHolder value.
+    ret := sel collect:[:el| 
+        DropObject new:(el fileName)
+    ].
+    ^ ret
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'event handling'!
+
+processEvent:anEvent
+    "filter keyboard events.
+     Return true, if I have eaten the event"
+
+    |focusView key rawKey|
+
+    anEvent isKeyPressEvent ifTrue:[
+        focusView := anEvent targetView.
+        key := anEvent key.
+        rawKey := anEvent rawKey.
+
+        (focusView isSameOrComponentOf:self window) ifTrue:[
+"/            (key ~= #'Alt_L') ifTrue:[self halt.].
+            (key == #Delete) ifTrue:[
+                self removeFilesFromArchiv.
+                ^ true
+            ].
+        ]
+    ].
+    ^ false
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'initialization & release'!
+
+postBuildFileTable:aWidget
+
+    fileTable := aWidget scrolledView.
+    fileTable wantsFocusWithPointerEnter.
+"/    FileBrowser icons keysAndValuesDo:[:aKey :anIcon|
+"/        fileTable registerImage:anIcon key:aKey.
+"/    ].
+    self columnDescriptors:(self class tableColumns).
+!
+
+postOpenWith:aBuilder
+
+    | currentDir contents suffix fileName file archivItem|
+
+    self windowGroup addPreEventHook:self.
+    self masterApplication isNil ifTrue:[
+        self masterApplication:nil.
+        currentDir := Filename homeDirectory.
+        contents := currentDir directoryContents.
+        fileName := contents detect:[: file |
+            suffix := file asFilename suffix asLowercase.
+            suffix = 'tgz'
+        ] ifNone:[nil].
+        fileName isNil ifTrue:[ 
+            Dialog warn:'cant find a Zip file in ', currentDir asString.
+            ^ self
+        ].
+        file := currentDir construct:fileName.
+        archivItem := DirectoryContentsBrowser itemClass with:file.
+        (self item:archivItem) ifFalse:[
+            Dialog warn:'file type of ', item fileName asString, ' not supported'.
+            ^ self.
+        ].
+    ].
+    self listAllFilesFromArchiv.
+    ^ super postOpenWith:aBuilder.
+!
+
+release
+
+    self archiver release.
+    ^ super release.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'queries'!
+
+archivType
+
+    | file firstsuffix secondsuffix|
+
+    file := self fileName.
+    firstsuffix := file withoutSuffix suffix.
+    secondsuffix := file suffix.
+    (secondsuffix = 'tgz' or:[firstsuffix = 'tar' and:[secondsuffix = 'gz']]) ifTrue:[
+        ^ #tarFileCompressed
+    ].
+    (secondsuffix = 'tar') ifTrue:[
+        ^ #tarFile
+    ].
+    (secondsuffix = 'gz') ifTrue:[
+        ^ #gzipFile
+    ].
+    (secondsuffix = 'zip') ifTrue:[
+        ^ #zipFile
+    ].
+!
+
+canDelete
+
+    ^ (self hasOneSelectionInList and:[archiver class canRemoveFiles])
+!
+
+selRemoveFilesForDirs:aSel
+
+    |stringCol newSel string|
+
+    stringCol := (aSel collect:[: item| item fileName]).
+    newSel := aSel copy.
+    aSel do:[:item |
+        item isDirectory ifTrue:[
+            string := item fileName.
+            stringCol doWithIndex:[:filename : index|
+                (filename ~= string and:[filename startsWith:string]) ifTrue:[
+                    newSel remove:(aSel at:index) ifAbsent:[nil].
+                ]
+            ]
+        ].
+    ].
+    ^ newSel.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication methodsFor:'sorting'!
+
+generateSortBlock:instanceName
+
+    | aSymbol cmpOp sortCaselessLocal|
+
+    aSymbol := instanceName asSymbol.
+    sortCaselessLocal := self sortCaseless value.
+    currentSortOrder isNil ifTrue:[
+        currentSortOrder := aSymbol.
+        currentSortOrder := Dictionary new.
+        currentSortOrder at:#column put:aSymbol.
+        currentSortOrder at:#reverse put:false.
+        currentSortOrder at:#sortCaseless put:sortCaselessLocal.
+    ] ifFalse:[
+        (currentSortOrder at:#column) = aSymbol ifTrue:[
+            "/ same column like before - change sort order
+            | isReverse |
+            isReverse := currentSortOrder at:#reverse.
+            currentSortOrder at:#reverse put:(isReverse not).
+        ] ifFalse:[
+            "/ another column - remark column
+            currentSortOrder at:#column put:aSymbol.
+        ]
+    ].
+    (currentSortOrder at:#reverse) ifTrue:[
+        cmpOp := #'>'
+    ] ifFalse:[
+        cmpOp := #'<'
+    ].
+    ^ [:a :b | 
+            |entry1 entry2|
+
+            entry1 := (a perform:aSymbol).
+            entry2 := (b perform:aSymbol).
+            aSymbol = #fileName ifTrue:[
+                sortCaselessLocal ifTrue:[
+                    entry1 := entry1 asString asLowercase.
+                    entry2 := entry2 asString asLowercase.
+                ] ifFalse:[
+                    entry1 := entry1 asString.
+                    entry2 := entry2 asString.
+                ].
+            ].
+            entry1 perform:cmpOp with:entry2
+    ].
+!
+
+sortList:instanceName 
+
+
+    |sortBlock fileList sortCol|
+
+    sortBlock := self generateSortBlock:instanceName.
+    fileList := self archiveFileList value.
+    sortCol := SortedCollection sortBlock:sortBlock.
+    sortCol addAll:fileList.
+    fileList removeAll.
+    fileList addAll:sortCol.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication::ArchivItem methodsFor:'accessing'!
+
+compressSize
+    "return the value of the instance variable 'compressSize' (automatically generated)"
+
+    ^ compressSize
+!
+
+compressSize:something
+    "set the value of the instance variable 'compressSize' (automatically generated)"
+
+    compressSize := something.
+!
+
+crc
+    "return the value of the instance variable 'crc' (automatically generated)"
+
+    ^ crc
+!
+
+crc:something
+    "set the value of the instance variable 'crc' (automatically generated)"
+
+    crc := something.
+!
+
+dateAndTime
+    "return the value of the instance variable 'dateAndTime' (automatically generated)"
+
+    ^ dateAndTime
+!
+
+dateAndTime:something
+    "set the value of the instance variable 'dateAndTime' (automatically generated)"
+
+    dateAndTime := something.
+!
+
+fileName
+    "return the value of the instance variable 'fileName' (automatically generated)"
+
+    ^ fileName
+!
+
+fileName:something
+    "set the value of the instance variable 'fileName' (automatically generated)"
+
+    fileName := something withoutSpaces.
+!
+
+icon
+    "return the value of the instance variable 'icon' (automatically generated)"
+
+    ^ icon
+!
+
+icon:something
+    "set the value of the instance variable 'icon' (automatically generated)"
+
+    icon := something.
+!
+
+isDirectory
+    "return the value of the instance variable 'directory' (automatically generated)"
+
+    ^ isDirectory
+!
+
+isDirectory:something
+    "set the value of the instance variable 'isDirectory' (automatically generated)"
+
+    isDirectory := something.
+!
+
+method
+    "return the value of the instance variable 'method' (automatically generated)"
+
+    ^ method
+!
+
+method:something
+    "set the value of the instance variable 'method' (automatically generated)"
+
+    method := something.
+!
+
+ownerGroup
+    "return the value of the instance variable 'owner' (automatically generated)"
+
+    ^ ownerGroup
+!
+
+ownerGroup:something
+    "set the value of the instance variable 'owner' (automatically generated)"
+
+    ownerGroup := something.
+!
+
+permissions
+    "return the value of the instance variable 'permissions' (automatically generated)"
+
+    ^ permissions
+!
+
+permissions:something
+    "set the value of the instance variable 'permissions' (automatically generated)"
+
+    permissions := something.
+!
+
+ratio
+    "return the value of the instance variable 'ratio' (automatically generated)"
+
+    ^ ratio
+!
+
+ratio:something
+    "set the value of the instance variable 'ratio' (automatically generated)"
+
+    ratio := something.
+!
+
+size
+    "return the value of the instance variable 'size' (automatically generated)"
+
+    ^ size
+!
+
+size:something
+    "set the value of the instance variable 'size' (automatically generated)"
+
+    size := something.
+!
+
+sizeAsNumber
+    "return the value of the instance variable 'size' (automatically generated)"
+
+    ^ size asInteger
+!
+
+type
+    "return the value of the instance variable 'type' (automatically generated)"
+
+    ^ type
+!
+
+type:something
+    "set the value of the instance variable 'type' (automatically generated)"
+
+    type := something.
+!
+
+version
+    "return the value of the instance variable 'version' (automatically generated)"
+
+    ^ version
+!
+
+version:something
+    "set the value of the instance variable 'version' (automatically generated)"
+
+    version := something.
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication::ArchivItem methodsFor:'printing'!
+
+printString
+
+    ^ self fileName asString
+! !
+
+!FileApplicationNoteBook::ArchiveViewApplication::ArchivItem methodsFor:'queries'!
+
+hasDirectoryPart
+
+    ^ self fileName asFilename components size ~= 1
+! !
+
+!FileApplicationNoteBook::CommandResult class methodsFor:'defaults'!
+
+tabStringFor:aApplicationType
+
+    ^ 'Execution result'
+!
+
+wantNewApplicationAnyway
+
+    ^ false
+! !
+
+!FileApplicationNoteBook::CommandResult 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:NoteBookApplication::CommandResult andSelector:#windowSpec
+     NoteBookApplication::CommandResult new openInterface:#windowSpec
+     NoteBookApplication::CommandResult open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'NoteBookApplication::CommandResult'
+          #name: 'NoteBookApplication::CommandResult'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 16 42 519 395)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#MenuPanelSpec
+              #name: 'ToolBar1'
+              #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 32 0)
+              #menu: #menu
+              #textDefault: true
+            )
+           #(#ArbitraryComponentSpec
+              #name: 'ArbitraryComponent1'
+              #layout: #(#LayoutFrame 0 0.0 32 0 0 1.0 0 1)
+              #hasHorizontalScrollBar: true
+              #hasVerticalScrollBar: true
+              #hasBorder: false
+              #component: #TextCollector
+              #postBuildCallback: #postBuildTextCollector:
+            )
+           #(#LabelSpec
+              #label: 'FileLabel'
+              #name: 'FileLabel'
+              #layout: #(#LayoutFrame 87 0 2 0 -36 1 30 0)
+              #level: -1
+              #translateLabel: true
+              #labelChannel: #labelHolder
+              #adjust: #left
+            )
+           )
+         
+        )
+      )
+! !
+
+!FileApplicationNoteBook::CommandResult class methodsFor:'menu specs'!
+
+menu
+    "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:FileApplicationNoteBook::CommandResult andSelector:#menu
+     (Menu new fromLiteralArrayEncoding:(FileApplicationNoteBook::CommandResult menu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(#Menu
+        #(
+         #(#MenuItem
+            #label: 'Stop'
+            #translateLabel: true
+            #isButton: true
+            #nameKey: #Stop
+            #value: #doStopProcess
+            #enabled: #enableStopButton
+            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #stop22x22Icon 'Stop')
+          )
+         #(#MenuItem
+            #label: 'Close'
+            #translateLabel: true
+            #isButton: true
+            #nameKey: #Close
+            #isVisible: #isEmbeddedApplication
+            #startGroup: #right
+            #value: #doClose
+            #labelImage: #(#ResourceRetriever #AbstractFileBrowser #closeIcon)
+          )
+         )
+        nil
+        nil
+      )
+! !
+
+!FileApplicationNoteBook::CommandResult methodsFor:'accessing'!
+
+resultStream
+    "return the value of the instance variable 'resultStream' (automatically generated)"
+
+    ^ resultStream
+!
+
+resultStream:something
+    "set the value of the instance variable 'resultStream' (automatically generated)"
+
+    resultStream := something.
+! !
+
+!FileApplicationNoteBook::CommandResult methodsFor:'actions'!
+
+changeTabTo:aString 
+
+    | masterApplication |
+
+    self labelHolder value:aString.
+    masterApplication := self masterApplication.
+    masterApplication isNil ifFalse:[
+        masterApplication tabStringChangeTo:aString for:self.
+    ].
+!
+
+doStopProcess
+
+    | myProcess |
+
+    myProcess := self process value.
+    myProcess notNil ifTrue:[
+        self notifyChannel value:('kill ', myProcess name).
+        myProcess terminate.    
+        self backgroundProcesses remove:myProcess ifAbsent:[].
+    ].
+! !
+
+!FileApplicationNoteBook::CommandResult methodsFor:'aspects'!
+
+enableStopButton
+
+    enableStopButton isNil ifTrue:[
+        enableStopButton := false asValue.
+    ].
+    ^ enableStopButton
+!
+
+labelHolder
+
+    labelHolder isNil ifTrue:[
+        labelHolder := '' asValue.
+    ].
+    ^ labelHolder.
+!
+
+process
+    "return/create the 'process' value holder (automatically generated)"
+
+    process isNil ifTrue:[
+        process := ValueHolder new.
+        process addDependent:self.
+    ].
+    ^ process
+! !
+
+!FileApplicationNoteBook::CommandResult methodsFor:'change & update'!
+
+update:something with:aParameter from:changedObject
+    "Invoked when an object that I depend upon sends a change notification."
+
+    "stub code automatically generated - please change as required"
+
+    changedObject == self process ifTrue:[
+        self enableStopButton value:changedObject value notNil.
+        ^ self
+    ].
+    super update:something with:aParameter from:changedObject
+! !
+
+!FileApplicationNoteBook::CommandResult methodsFor:'initialization & release'!
+
+postBuildTextCollector:aBuilder
+
+    self resultStream:aBuilder scrolledView.
+!
+
+postBuildWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked during the initialization of your app/dialog,
+     after all of the visual components have been built, 
+     but BEFORE the top window is made visible.
+     Add any app-specific actions here (reading files, setting up values etc.)
+     See also #postOpenWith:, which is invoked after opening."
+
+    "/ add any code here ...
+
+    ^ super postBuildWith:aBuilder
+!
+
+postOpenWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked right after the applications window has been opened.
+     Add any app-specific actions here (starting background processes etc.).
+     See also #postBuildWith:, which is invoked before opening."
+
+    "/ add any code here ...
+
+    self masterApplication isNil ifTrue:[
+        self masterApplication:nil.
+    ].
+    ^ super postOpenWith:aBuilder
+!
+
+release
+
+    self doStopProcess.
+    ^ super release
+! !
+
+!FileApplicationNoteBook::CommandResult methodsFor:'printing'!
+
+printString
+
+    ^ 'CommandResult Application'
+! !
+
+!FileApplicationNoteBook::HtmlViewApplication class methodsFor:'defaults'!
+
+tabStringFor:aApplicationType
+
+    ^ 'HTML View for:'
+! !
+
+!FileApplicationNoteBook::HtmlViewApplication 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:NoteBookApplication::HtmlViewApplication andSelector:#windowSpec
+     NoteBookApplication::HtmlViewApplication new openInterface:#windowSpec
+     NoteBookApplication::HtmlViewApplication open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'NoteBookApplication::HtmlView'
+          #name: 'NoteBookApplication::HtmlView'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 16 42 692 534)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#MenuPanelSpec
+              #name: 'MenuHtml'
+              #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 32 0)
+              #visibilityChannel: #isEmbeddedApplication
+              #menu: #menu
+              #textDefault: true
+            )
+           #(#ArbitraryComponentSpec
+              #name: 'HTMLView'
+              #layout: #(#LayoutFrame 0 0.0 32 0.0 0 1.0 0 1)
+              #hasHorizontalScrollBar: true
+              #hasVerticalScrollBar: true
+              #miniScrollerHorizontal: false
+              #miniScrollerVertical: false
+              #hasBorder: false
+              #component: #HTMLDocumentView
+              #postBuildCallback: #postBuildHtmlView:
+            )
+           #(#LabelSpec
+              #label: 'FileLabel'
+              #name: 'FileLabel'
+              #layout: #(#LayoutFrame 212 0 2 0 -73 1 30 0)
+              #level: -1
+              #translateLabel: true
+              #labelChannel: #labelHolder
+              #adjust: #left
+            )
+           )
+         
+        )
+      )
+! !
+
+!FileApplicationNoteBook::HtmlViewApplication class methodsFor:'menu specs'!
+
+menu
+    "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:FileApplicationNoteBook::HtmlViewApplication andSelector:#menu
+     (Menu new fromLiteralArrayEncoding:(FileApplicationNoteBook::HtmlViewApplication menu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(#Menu
+        #(
+         #(#MenuItem
+            #label: 'Reload'
+            #translateLabel: true
+            #isButton: true
+            #value: #doReload
+            #labelImage: #(#ResourceRetriever nil #htmlReloadIcon)
+          )
+         #(#MenuItem
+            #label: 'Back'
+            #translateLabel: true
+            #isButton: true
+            #value: #doGoBack
+            #labelImage: #(#ResourceRetriever #Icon #leftIcon)
+          )
+         #(#MenuItem
+            #label: 'Print'
+            #translateLabel: true
+            #isButton: true
+            #value: #doPrint
+            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #printer22x22Icon)
+          )
+         #(#MenuItem
+            #label: 'Close'
+            #translateLabel: true
+            #isButton: true
+            #hideMenuOnActivated: false
+            #startGroup: #right
+            #value: #doClose
+            #labelImage: #(#ResourceRetriever #AbstractFileBrowser #closeIcon)
+          )
+         )
+        nil
+        nil
+      )
+! !
+
+!FileApplicationNoteBook::HtmlViewApplication class methodsFor:'queries'!
+
+canOpenItem:aItem
+
+    ^ (aItem hasMimeType and:[aItem mimeType isHtml])
+!
+
+wantNewApplicationAnyway
+
+    ^ false
+! !
+
+!FileApplicationNoteBook::HtmlViewApplication methodsFor:'accessing'!
+
+htmlView
+    "return the value of the instance variable 'imageView' (automatically generated)"
+
+    ^ htmlView
+!
+
+htmlView:something
+    "set the value of the instance variable 'imageView' (automatically generated)"
+
+    htmlView := something.
+!
+
+item:aItem 
+
+    |retVal|
+
+    self labelHolder value:aItem fileName asString.
+    retVal := super item:aItem.
+    self setupHtmlView.
+    ^ retVal
+! !
+
+!FileApplicationNoteBook::HtmlViewApplication methodsFor:'actions'!
+
+doGoBack
+
+    self htmlView menu_back.
+!
+
+doGoHome
+
+    self htmlView menu_home.
+!
+
+doHelp
+
+    self htmlView menu_help.
+!
+
+doPrint
+
+    self htmlView menu_print.
+!
+
+doReload
+
+    self htmlView menu_reload.
+!
+
+setupHtmlView
+
+    | html file directory|
+
+    html := self htmlView.
+    html isNil ifTrue:[^ self].
+    file := self fileName.
+    directory := file directoryName.
+    html homeDocument:(file asString).
+    html setTopDirectoryName:directory.
+    html uriHolder:self labelHolder.
+    html infoHolder:self notifyChannel.
+    html linkButtonPanel:nil.
+    ^ html
+! !
+
+!FileApplicationNoteBook::HtmlViewApplication methodsFor:'aspects'!
+
+labelHolder
+
+    labelHolder isNil ifTrue:[
+        labelHolder := '' asValue.
+    ].
+    ^ labelHolder.
+! !
+
+!FileApplicationNoteBook::HtmlViewApplication methodsFor:'initialization & release'!
+
+postBuildHtmlView:aWidget
+
+    self htmlView: aWidget scrolledView.
+    self htmlView wantsFocusWithPointerEnter.
+!
+
+postOpenWith:aBuilder 
+    "
+    only invoked if the application not started from a master
+    "
+
+    |currentDir contents suffix fileName|
+
+    self masterApplication isNil ifTrue:[
+        self masterApplication:nil.
+        currentDir := Filename homeDirectory.
+
+        contents := currentDir directoryContents.
+        fileName := contents 
+                    detect:[:file | 
+                        suffix := file asFilename suffix asLowercase.
+                        suffix = 'html'
+                    ]
+                    ifNone:[nil].
+        fileName isNil ifTrue:[
+            Dialog warn:'cant find a HTML file in ' , currentDir asString.
+            ^ self
+        ].
+        self item:(DirectoryContentsBrowser itemClass with:('../../doc/online/english/TOP.html' asFilename)).
+    ].
+    self setupHtmlView.
+    ^ super postOpenWith:aBuilder
+! !
+
+!FileApplicationNoteBook::ImageViewApplication class methodsFor:'defaults'!
+
+tabStringFor:aApplicationType
+
+    ^ 'Image for:'
+! !
+
+!FileApplicationNoteBook::ImageViewApplication class methodsFor:'image specs'!
+
+fitSize20x20Icon
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self fitSize20x20Icon inspect
+     ImageEditor openOnClass:self andSelector:#fitSize20x20Icon
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:#'FileApplicationNoteBook::ImageViewApplication class fitSize20x20Icon'
+        ifAbsentPut:[(Depth4Image new) width: 20; height: 20; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@DQDQDQDQDP@@@PDQDQDQDQ@P@A@ADQDQDQDP@PD@@PDQDQDPD@@QDQ@ADQDQ@@DQDQD@@@@@@@@@DQDQDPQDQDQ@DQDQDQDDQUUTPADQDQDQAEUUUT@QDQ
+DQDPQEUUQ@DQDQDQDDQFQDPADQDQDQADQ$QD@QDQDQDPL3X3Q@DQDQDQDCL3L3LADQDQD@@@@@@@@@DQDQD@DQDQDP@QDQ@@DADQDQDA@@DA@ADQDQDQDP@P
+@@@QDQDQDQDA@@@ADQDQDQDQD@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 255 255 255 0 0 0 0 137 0 174 218 230 0 206 0 133 60 36]; mask:((Depth1Image new) width: 20; height: 20; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+8@A00@@0(@APE@J@C@L@G?>@A?8@A?8@A?8@A?8@A?8@A?8@A?8@A?8@G?>@C@L@E@J@(@AP0@@08@A0@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; yourself); yourself]
+! !
+
+!FileApplicationNoteBook::ImageViewApplication 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:FileApplicationNoteBook::ImageViewApplication andSelector:#windowSpec
+     FileApplicationNoteBook::ImageViewApplication new openInterface:#windowSpec
+     FileApplicationNoteBook::ImageViewApplication open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'ImageViewer'
+          #name: 'ImageViewer'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 16 42 692 534)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#MenuPanelSpec
+              #name: 'MenuTerminal'
+              #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 32 0)
+              #visibilityChannel: #isEmbeddedApplication
+              #menu: #menu
+              #textDefault: true
+            )
+           #(#ArbitraryComponentSpec
+              #name: 'TerminalView'
+              #layout: #(#LayoutFrame 0 0.0 32 0.0 0 1.0 0 1.0)
+              #hasHorizontalScrollBar: true
+              #hasVerticalScrollBar: true
+              #miniScrollerHorizontal: false
+              #miniScrollerVertical: false
+              #hasBorder: false
+              #component: #ImageView
+              #postBuildCallback: #postBuildImageView:
+            )
+           )
+         
+        )
+      )
+! !
+
+!FileApplicationNoteBook::ImageViewApplication class methodsFor:'menu specs'!
+
+menu
+    "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:FileApplicationNoteBook::ImageViewApplication andSelector:#menu
+     (Menu new fromLiteralArrayEncoding:(FileApplicationNoteBook::ImageViewApplication menu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(#Menu
+        #(
+         #(#MenuItem
+            #label: 'Edit'
+            #translateLabel: true
+            #isButton: true
+            #nameKey: #EditImage
+            #value: #editImage
+          )
+         #(#MenuItem
+            #label: '-'
+          )
+         #(#MenuItem
+            #label: 'FitSize'
+            #translateLabel: true
+            #isButton: true
+            #triggerOnDown: true
+            #labelImage: #(#ResourceRetriever #'FileApplicationNoteBook::ImageViewApplication' #fitSize20x20Icon)
+            #indication: #fitSize
+          )
+         #(#MenuItem
+            #label: '-'
+          )
+         #(#MenuItem
+            #label: 'Close'
+            #translateLabel: true
+            #isButton: true
+            #hideMenuOnActivated: false
+            #startGroup: #right
+            #value: #doClose
+            #labelImage: #(#ResourceRetriever #AbstractFileBrowser #closeIcon)
+          )
+         )
+        nil
+        nil
+      )
+! !
+
+!FileApplicationNoteBook::ImageViewApplication class methodsFor:'queries'!
+
+canOpenItem:aItem
+
+    ^ (aItem hasMimeType and:[aItem mimeType isImage])
+!
+
+wantNewApplicationAnyway
+
+    ^ false
+! !
+
+!FileApplicationNoteBook::ImageViewApplication methodsFor:'accessing'!
+
+image:something
+    "set the value of the instance variable 'image' (automatically generated)"
+
+    image := something.
+!
+
+imageView
+    "return the value of the instance variable 'imageView' (automatically generated)"
+
+    ^ imageView
+!
+
+imageView:something
+    "set the value of the instance variable 'imageView' (automatically generated)"
+
+    imageView := something.
+! !
+
+!FileApplicationNoteBook::ImageViewApplication methodsFor:'actions'!
+
+changeItem:aItem
+
+    self item:aItem.
+    self setupImageView.
+    ^ true
+!
+
+editImage
+    |img|
+
+    img := self image.
+    img notNil ifTrue:[
+        img edit.
+    ].
+!
+
+image
+    |img fn e|
+
+    fn := self fileName.
+    img := Image fromFile:fn.
+    img isNil ifTrue:[
+        fn exists ifTrue:[
+            e := 'Unknown/unsupported image format'
+        ] ifFalse:[
+            e := 'No such image'
+        ].
+        Dialog warn:e.
+        ^ nil
+    ].
+    ^ img.
+!
+
+setupImageView
+    |img|
+
+    self window topView withWaitCursorDo:[
+        img := self image.
+        img notNil ifTrue:[
+            self image:img.
+            imageView image:img
+        ]
+    ]
+! !
+
+!FileApplicationNoteBook::ImageViewApplication methodsFor:'aspects'!
+
+fitSize
+    "return/create the 'fitSize' value holder (automatically generated)"
+
+    fitSize isNil ifTrue:[
+        fitSize := ValueHolder new.
+        fitSize addDependent:self.
+    ].
+    ^ fitSize
+! !
+
+!FileApplicationNoteBook::ImageViewApplication methodsFor:'change & update'!
+
+update:something with:aParameter from:changedObject
+    changedObject == self fitSize ifTrue:[
+        changedObject value ifTrue:[
+            imageView adjust:#fitBig.
+        ] ifFalse:[
+            imageView adjust:nil.
+        ].
+        ^ self
+    ].
+    super update:something with:aParameter from:changedObject
+! !
+
+!FileApplicationNoteBook::ImageViewApplication methodsFor:'initialization & release'!
+
+postBuildImageView:aWidget
+
+    self imageView: aWidget scrolledView.
+    self imageView wantsFocusWithPointerEnter.
+!
+
+postOpenWith:aBuilder 
+    "
+    only invoked if the application not started from a master
+    "
+
+    |currentDir contents suffix fileName|
+
+    self masterApplication isNil ifTrue:[
+        self masterApplication:nil.
+        currentDir := Filename currentDirectory.
+        contents := currentDir directoryContents.
+        fileName := contents 
+                    detect:[:file | 
+                        suffix := file asFilename suffix asLowercase.
+                        Image isImageFileSuffix:suffix
+                    ]
+                    ifNone:[nil].
+        fileName isNil ifTrue:[
+            Dialog warn:'cant find a Image in ' , currentDir asString.
+            ^ self
+        ].
+        self item:(DirectoryContentsBrowser itemClass with:(currentDir construct:fileName))
+    ].
+    self setupImageView.
+    ^ super postOpenWith:aBuilder
+! !
+
+!FileApplicationNoteBook::Terminal class methodsFor:'defaults'!
+
+tabStringFor:aApplicationType
+
+    ^ 'Terminal in:'
+! !
+
+!FileApplicationNoteBook::Terminal 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:NoteBookApplication::Terminal andSelector:#windowSpec
+     NoteBookApplication::Terminal new openInterface:#windowSpec
+     NoteBookApplication::Terminal open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'NoteBookApplication::Terminal'
+          #name: 'NoteBookApplication::Terminal'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 16 42 692 534)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#MenuPanelSpec
+              #name: 'MenuTerminal'
+              #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 32 0)
+              #menu: #menu
+              #textDefault: true
+            )
+           #(#ArbitraryComponentSpec
+              #name: 'TerminalView'
+              #layout: #(#LayoutFrame 0 0.0 32 0.0 0 1.0 0 1.0)
+              #hasHorizontalScrollBar: true
+              #hasVerticalScrollBar: true
+              #miniScrollerHorizontal: false
+              #miniScrollerVertical: false
+              #hasBorder: false
+              #component: #terminalView
+            )
+           )
+         
+        )
+      )
+! !
+
+!FileApplicationNoteBook::Terminal class methodsFor:'menu specs'!
+
+menu
+    "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:FileApplicationNoteBook::Terminal andSelector:#menu
+     (Menu new fromLiteralArrayEncoding:(FileApplicationNoteBook::Terminal menu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(#Menu
+        #(
+         #(#MenuItem
+            #label: 'Save'
+            #translateLabel: true
+            #isButton: true
+            #nameKey: #Save
+            #value: #saveAs
+            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #saveToFile28x22Icon)
+          )
+         #(#MenuItem
+            #label: 'Close'
+            #translateLabel: true
+            #isButton: true
+            #hideMenuOnActivated: false
+            #isVisible: #isEmbeddedApplication
+            #startGroup: #right
+            #value: #doClose
+            #labelImage: #(#ResourceRetriever #AbstractFileBrowser #closeIcon)
+          )
+         )
+        nil
+        nil
+      )
+! !
+
+!FileApplicationNoteBook::Terminal methodsFor:'accessing'!
+
+terminalView
+
+    terminalView isNil ifTrue:[
+        terminalView := VT100TerminalView new.
+    ].
+    ^ terminalView.
+! !
+
+!FileApplicationNoteBook::Terminal methodsFor:'actions'!
+
+saveAs
+
+    self terminalView save.
+! !
+
+!FileApplicationNoteBook::Terminal methodsFor:'initialization & release'!
+
+postBuildWith:aBuilder
+
+    ^ super postBuildWith:aBuilder
+!
+
+shellFinished
+
+    | master text string|
+
+    master := self masterApplication.
+    master notNil ifTrue:[
+        string := ' - closed'.
+        master tabStringAdd:string for:self.
+    ].
+    self notifyChannel value:'shell in ' , self fileName asString, ' finished'.
+    terminalView cr.
+    text := '>> shell closed' asText allBold.
+    text colorizeAllWith:Color red.
+    terminalView nextPutAll:text.
+!
+
+startShell
+    |vt100|
+
+    vt100 := self terminalView.
+    vt100 shellTerminateAction:[ self shellFinished ].
+    vt100 startShellIn:(self fileName).
+! !
+
+!FileApplicationNoteBook::Terminal methodsFor:'printing'!
+
+printString
+
+    ^ ('Terminal on:', self fileName baseName)
+! !
+
+!FileApplicationNoteBook::Terminal methodsFor:'queries'!
+
+getTabStringEnd
+
+" get the tab string from the application list on the class side "
+
+    ^ '..', OperatingSystem fileSeparator, self fileName baseName, OperatingSystem fileSeparator
+! !
+
+!FileApplicationNoteBook::Terminal methodsFor:'startup & release'!
+
+postOpenWith:aBuilder
+
+    "
+    only invoked if the application not started from a master
+    "
+    self masterApplication isNil ifTrue:[
+        self masterApplication:nil.
+        self item:(DirectoryContentsBrowser itemClass with:(Filename currentDirectory asAbsoluteFilename)).
+    ].
+    self startShell.
+    ^ super postOpenWith:aBuilder.
+! !
+
+!FileApplicationNoteBook::TextEditor class methodsFor:'defaults'!
+
+tabStringFor:aApplicationType
+
+    aApplicationType == #directoryDescription ifTrue:[
+        ^ 'Directory description for:'
+    ] ifFalse:[
+        ^ 'Editor on:'
+    ].
+!
+
+wantNewApplicationAnyway
+
+    ^ false
+! !
+
+!FileApplicationNoteBook::TextEditor 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:NoteBookApplication::TextEditor andSelector:#windowSpec
+     NoteBookApplication::TextEditor new openInterface:#windowSpec
+     NoteBookApplication::TextEditor open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'TextEditor'
+          #name: 'TextEditor'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 12 22 662 322)
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#MenuPanelSpec
+              #name: 'MenuTextEditor'
+              #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 32 0)
+              #menu: #menu
+              #textDefault: true
+            )
+           #(#TextEditorSpec
+              #name: 'TextEditor'
+              #layout: #(#LayoutFrame 0 0.0 32 0 0 1.0 0 1.0)
+              #model: #fileContentsModel
+              #hasHorizontalScrollBar: true
+              #hasVerticalScrollBar: true
+              #modifiedChannel: #modifiedChannel
+              #acceptCallBack: #accept
+              #postBuildCallback: #postBuildTextEditor:
+            )
+           )
+         
+        )
+      )
+! !
+
+!FileApplicationNoteBook::TextEditor class methodsFor:'menu specs'!
+
+menu
+    "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:FileApplicationNoteBook::TextEditor andSelector:#menu
+     (Menu new fromLiteralArrayEncoding:(FileApplicationNoteBook::TextEditor menu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(#Menu
+        #(
+         #(#MenuItem
+            #label: 'Save'
+            #translateLabel: true
+            #isButton: true
+            #nameKey: #Save
+            #value: #accept
+            #enabled: #enableSave
+            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #saveToFile28x22Icon)
+          )
+         #(#MenuItem
+            #label: 'Reload'
+            #translateLabel: true
+            #isButton: true
+            #nameKey: #Reload
+            #value: #reload
+            #enabled: #enableReload
+            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #reloadFromFile28x22Icon)
+          )
+         #(#MenuItem
+            #label: ''
+          )
+         #(#MenuItem
+            #label: 'Print'
+            #translateLabel: true
+            #isButton: true
+            #nameKey: #Print
+            #value: #doPrint
+            #enabled: #enableHexToggle
+            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #printer22x22Icon)
+          )
+         #(#MenuItem
+            #label: ''
+          )
+         #(#MenuItem
+            #label: 'Hex'
+            #translateLabel: true
+            #isButton: true
+            #enabled: #enableHexToggle
+            #labelImage: #(#ResourceRetriever #AbstractFileBrowser #hexToggle22x22Icon)
+            #indication: #printAsHexDump
+          )
+         #(#MenuItem
+            #label: 'Close'
+            #translateLabel: true
+            #isButton: true
+            #hideMenuOnActivated: false
+            #isVisible: #isEmbeddedApplication
+            #startGroup: #right
+            #value: #doClose
+            #labelImage: #(#ResourceRetriever #AbstractFileBrowser #closeIcon)
+          )
+         )
+        nil
+        nil
+      )
+! !
+
+!FileApplicationNoteBook::TextEditor methodsFor:'accessing'!
+
+item:aDirContentsItem
+
+
+    self stopChangeItemProcess.
+    super item:aDirContentsItem.
+    (self askForChange) isNil ifTrue:[ ^ false].
+    self setContents.
+    self startChangeItemProcess.
+    ^ true
+!
+
+presentation
+    "return the value of the instance variable 'presentation' (automatically generated)"
+
+    presentation isNil ifTrue:[
+        presentation := #asText.
+    ].
+    ^ presentation
+!
+
+presentation:something
+    "set the value of the instance variable 'presentation' (automatically generated)"
+
+    presentation := something.
+!
+
+semaChangeItem
+
+    semaChangeItem isNil ifTrue:[
+        semaChangeItem := Semaphore forMutualExclusion.
+    ].
+    ^ semaChangeItem
+! !
+
+!FileApplicationNoteBook::TextEditor methodsFor:'actions'!
+
+accept
+
+    | dir |
+
+    self masterApplication class openAnotherApplicationOnSameItem ifTrue:[
+        self updateSameFiles ifFalse:[ ^ self ].
+    ].
+    self notifyChannel value:self fileName asString, ' saved'.
+    dir := self fileName directory.
+    dir exists not ifTrue:[
+        dir recursiveMakeDirectory.
+    ].
+    editView saveAs:(self fileName).
+    self notifyChannel value:self fileName asString, ' saved'.
+    self semaChangeItem critical:[
+        self item resetItemForTextEditorChange.
+        textEditorChangeModificationTime := nil.
+        self itemChanged value:false.
+    ].
+    self modifiedChannel value:false.
+    self itemRemoved value:false.
+!
+
+askForChange
+    "ask for save changes
+    "
+
+    |answer string|
+
+    answer := false.
+    self modifiedChannel value ifTrue:[
+        self itemChanged value ifTrue:[
+            string := self fileName asString , ' was changed by someone else' 
+                        , Character cr , 'want to save your changes anyway ?'
+        ].
+        self itemRemoved value ifTrue:[
+            string := self fileName asString , ' was removed by someone else' 
+                        , Character cr , 'want to save your changes anyway ?'
+        ].
+        string := 'save changed file ' , self fileName asString , ' ?'
+    ].
+    string notNil ifTrue:[
+        answer := (Dialog confirmWithCancel:string).
+        answer isNil ifTrue:[^ answer].
+        answer == true ifTrue:[
+            self accept
+        ] ifFalse:[
+            self setContents.
+        ]
+    ].
+    ^ answer
+!
+
+changeInformation 
+
+    | stream |
+
+    stream := WriteStream with:(self getTabString).
+    masterApplication isNil ifTrue:[
+        self window label:stream contents.
+
+    ] ifFalse:[
+        masterApplication tabStringChangeTo:stream contents for:self.
+    ].
+    stream close.
+!
+
+doClose
+
+    (self askForChange) isNil ifTrue:[ ^ false].
+    self masterApplication notNil ifTrue:[
+        super doClose
+    ].
+    ^ true
+!
+
+doPrint
+    "print the contents
+    "
+    (Dialog confirm:'printing ?') ifTrue:[
+        editView doPrint.
+    ].
+!
+
+reload
+
+    self setContents.
+!
+
+setContents
+
+
+    |file contents present|
+
+    file := self fileName.
+    RecursionInterruptSignal handle:[ : ex |
+        Dialog warn:file asString, ' is too big to be loaded !!'.
+        ^ false.
+    ] do:[
+        present := self presentation.
+        present == #asText ifTrue:[
+            contents := file contents.
+        ] ifFalse:[
+            present == #hexDump ifTrue:[
+                contents := self getFileHexContents:file.
+            ]
+        ]
+    ].
+    self fileContentsModel value:contents.
+    self enableReload value:false.
+    self itemChanged value:false.
+    self modifiedChannel setValue:false.
+    self modifiedChannel changed.
+    ^ true
+!
+
+updateSameFiles
+
+    | master modifiedApplications stream filename action|
+
+    master := self masterApplication.
+    master notNil ifTrue:[
+        modifiedApplications := master getSameFilesModifiedFor:self.
+        (modifiedApplications isNil or:[modifiedApplications isEmpty]) ifTrue:[^ true ].
+        filename := self fileName asString.
+        stream := WriteStream on:''.
+        stream nextPutAll:filename.
+        stream nextPutAll:' is modified in tab'.
+        modifiedApplications size > 1 ifTrue:[
+            stream nextPutAll:'s'.
+        ].
+        stream cr.
+        modifiedApplications do:[ : el |
+            stream space.
+            stream nextPutAll:filename.
+            stream space.
+            el sameFileIndex notNil ifTrue:[
+                stream nextPutAll:el sameFileIndex asString.        
+            ].
+            stream cr.
+        ].
+        stream nextPutAll:'forget changes on other tab'.        
+        modifiedApplications size > 1 ifTrue:[
+            stream nextPutAll:'s'.
+        ].
+        stream nextPutAll:' ?'.        
+        action := Dialog 
+            choose:stream contents 
+            labels:#('cancel' 'no' 'yes') 
+            values:#(#cancel #no #yes) 
+            default:#cancel. 
+
+        stream close.
+        action == #cancel ifTrue:[ ^ false ].
+        action == #yes ifTrue:[
+            "/ here force reload for other applications
+            modifiedApplications do:[ : el |
+                el reload.
+            ]            
+        ].
+    ].
+    ^ true.
+! !
+
+!FileApplicationNoteBook::TextEditor methodsFor:'aspects'!
+
+doSaveFile
+
+    doSaveFile isNil ifTrue:[
+        doSaveFile := ValueHolder new.
+    ].
+    ^ doSaveFile.
+!
+
+enableHexToggle
+
+    enableHexToggle isNil ifTrue:[
+        enableHexToggle := true asValue.
+    ].
+    ^ enableHexToggle
+!
+
+enableReload
+
+    enableReload isNil ifTrue:[
+        enableReload := false asValue.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       enableReload addDependent:self.
+"/       enableReload onChangeSend:#enableReloadChanged to:self.
+    ].
+    ^ enableReload.
+!
+
+enableSave
+
+    enableSave isNil ifTrue:[
+        enableSave := false asValue.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       enableSave addDependent:self.
+"/       enableSave onChangeSend:#enableSaveChanged to:self.
+    ].
+    ^ enableSave.
+!
+
+fileContentsModel
+
+    fileContentsModel isNil ifTrue:[
+        fileContentsModel := ValueHolder new.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       fileContentsModel addDependent:self.
+"/       fileContentsModel onChangeSend:#fileContentsModelChanged to:self.
+    ].
+    ^ fileContentsModel.
+!
+
+itemChanged
+
+    itemChanged isNil ifTrue:[
+        itemChanged := false asValue.
+        itemChanged addDependent:self.
+    ].
+    ^ itemChanged
+!
+
+itemRemoved
+
+    itemRemoved isNil ifTrue:[
+        itemRemoved := false asValue.
+        itemRemoved addDependent:self.
+    ].
+    ^ itemRemoved
+!
+
+modifiedChannel
+
+    modifiedChannel isNil ifTrue:[
+        modifiedChannel := false asValue.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+        modifiedChannel addDependent:self.
+"/       modifiedChannel onChangeSend:#modifiedChannelChanged to:self.
+    ].
+    ^ modifiedChannel.
+!
+
+printAsHexDump
+
+    printAsHexDump isNil ifTrue:[
+        printAsHexDump := false asValue.
+        printAsHexDump addDependent:self.
+    ].
+    ^ printAsHexDump.
+! !
+
+!FileApplicationNoteBook::TextEditor methodsFor:'change & update'!
+
+changeEnableReload
+
+    | modified changed removed |
+
+    modified := self modifiedChannel value.
+    changed := self itemChanged value.    
+    removed := self itemRemoved value.    
+
+    self enableReload value:((modified or:[changed]) and:[removed not]).
+!
+
+update:something with:aParameter from:changedObject
+    "Invoked when an object that I depend upon sends a change notification."
+
+    "stub code automatically generated - please change as required"
+
+    |modified itemRem|
+
+    changedObject == self modifiedChannel ifTrue:[
+        modified := changedObject value.
+        self enableSave value:modified.
+        self changeEnableReload.
+        ^ self
+    ].
+    changedObject == self itemRemoved ifTrue:[
+        itemRem := changedObject value.
+        itemRem == true ifTrue:[
+            self enableSave value:true.
+        ].
+        self enableHexToggle value:itemRem not.
+        self changeEnableReload.
+        ^ self
+    ].
+    changedObject == self itemChanged ifTrue:[
+        self changeEnableReload.
+        changedObject value == true ifTrue:[
+            self enableSave value:true.
+        ].
+        ^ self
+    ].
+    changedObject == self printAsHexDump ifTrue:[
+        (self askForChange) isNil ifTrue:[ 
+            self printAsHexDump value:changedObject value not withoutNotifying:self.
+            ^ self
+        ].
+        changedObject value ifTrue:[
+            self presentation:#hexDump.
+        ] ifFalse:[
+            self presentation:#asText.
+        ].
+        self changeInformation.
+        self setContents.
+        (self presentation == #hexDump) ifTrue:[
+            editView readOnly:true.   
+        ] ifFalse:[
+            editView readOnly:false.   
+        ].
+         ^ self
+    ].
+
+    super update:something with:aParameter from:changedObject
+! !
+
+!FileApplicationNoteBook::TextEditor methodsFor:'printing'!
+
+printString
+
+    ^ ('TextEditor for:', self fileName baseName)
+! !
+
+!FileApplicationNoteBook::TextEditor methodsFor:'privat-process'!
+
+checkMyItemForChanges
+
+    | dir exist myItem|
+
+    dir := self fileName directory.
+    myItem := self item.
+    exist := myItem exists.
+    self itemRemoved value:(exist not).
+    exist ifTrue:[
+        self semaChangeItem critical:[
+            | time info|
+            info := self fileName asAbsoluteFilename info.
+            time := info modified.
+            textEditorChangeModificationTime isNil ifTrue:[
+                textEditorChangeModificationTime := time.
+            ].
+            ((textEditorChangeModificationTime = time) not) ifTrue:[
+                "/ contents changed by someone else
+                textEditorChangeModificationTime := time.
+                self notifyChannel value:item fileName asString, ' was changed by someone else'.
+                self itemChanged value:true.
+            ].
+        ]
+    ]
+!
+
+getFileHexContents:f
+
+    |fileName stream data offs 
+     addrDigits col line lineStream asciiLineStream lines|
+    
+    fileName := f baseName.
+    f isDirectory ifTrue:[
+        ^ Dialog warn:(resources string:'%1 is a directory.' with:fileName).
+    ].
+    f exists ifFalse:[
+        Dialog warn:(resources string:'oops, ''%1'' is gone or unreadable.' with:fileName).
+        ^ self
+    ].
+    f isReadable ifFalse:[
+        Dialog warn:(resources string:'''%1'' is unreadable.' with:fileName).
+        ^ self
+    ].
+    f fileSize > (512*1024) ifTrue:[
+        (Dialog confirm:'Warning: the file is big (', (f fileSize//1024) printString , 'Kb). Show anyway ?')
+        ifFalse:[
+            ^ self
+        ]
+    ].
+    stream := f readStream binary.
+    data := stream contents.
+    stream close.
+
+"/        subView list:nil.
+    col := 1.
+    offs := 0.
+    lines := StringCollection new.
+
+    addrDigits := ((f fileSize + 1) log:16) truncated + 1.
+
+    lineStream := '' writeStream.
+    asciiLineStream := '' writeStream.
+
+    lineStream nextPutAll:(offs hexPrintString:addrDigits).
+    lineStream nextPutAll:': '.
+
+    data do:[:byte |
+        lineStream nextPutAll:(byte hexPrintString:2).
+        (byte between:32 and:127) ifTrue:[
+            asciiLineStream nextPut:(Character value:byte)
+        ] ifFalse:[
+            asciiLineStream nextPut:$.
+        ].
+
+        offs := offs + 1.
+        col := col + 1.
+        col > 16 ifTrue:[
+            lineStream nextPutAll:'        '.
+            lineStream nextPutAll:asciiLineStream contents.
+            lines add:(lineStream contents).
+            (offs bitAnd:16rFF) == 0 ifTrue:[
+                lines add:nil
+            ].
+            lineStream reset.
+            asciiLineStream reset.
+
+            lineStream nextPutAll:(offs hexPrintString:addrDigits).
+            lineStream nextPutAll:': '.
+            col := 1.
+        ] ifFalse:[
+            lineStream space
+        ]
+    ].
+    line := lineStream contents paddedTo:(3*16 + addrDigits + 1).
+    lines add:(line , '        ' , asciiLineStream contents).
+    ^ lines
+!
+
+startChangeItemProcess
+
+    changeItemProcess isNil ifTrue:[
+        self itemRemoved value:false.
+        self itemChanged value:false.
+        changeItemProcess := Process for:[ [   [true] whileTrue:[
+
+                                            self checkMyItemForChanges.
+                                            Delay waitForSeconds:1.0
+                                    ]
+                                ] valueNowOrOnUnwindDo:[
+                                    changeItemProcess := nil.
+                                    textEditorChangeModificationTime := nil.
+                                ]
+                              ]
+                     priority:(Processor systemBackgroundPriority).
+
+        changeItemProcess name:('TextEditorLookForModify[', self fileName baseName, ']').
+        changeItemProcess resume.
+    ].
+!
+
+stopChangeItemProcess
+
+    | task |
+
+    task := changeItemProcess.
+    task notNil ifTrue:[
+        changeItemProcess := nil.
+
+        Object errorSignal handle:[:ex|
+            Dialog warn:ex description.
+        ]do:[
+            task isDead ifFalse:[
+                task terminate.
+                task waitUntilTerminated.
+            ]
+        ]
+    ].
+! !
+
+!FileApplicationNoteBook::TextEditor methodsFor:'queries'!
+
+isModified
+
+    ^ self modifiedChannel value
+! !
+
+!FileApplicationNoteBook::TextEditor methodsFor:'startup & release'!
+
+closeRequest
+
+    (self doClose) ifTrue:[
+        ^ super closeRequest.
+    ].
+!
+
+postBuildTextEditor:aWidget
+
+    editView       := aWidget scrolledView.
+!
+
+postBuildWith:aBuilder
+
+    super postBuildWith:aBuilder.
+!
+
+postOpenWith:aBuilder
+
+    self masterApplication isNil ifTrue:[
+        self masterApplication:nil.
+        self item:(DirectoryContentsBrowser itemClass with:(Filename homeDirectory construct:'/lala/.bashrc')).
+    ].
+    self setUpTextView.
+    self changeInformation.
+    ^ super postOpenWith:aBuilder
+!
+
+release
+    "release my resources
+    "                    
+    self stopChangeItemProcess.
+    super release.
+!
+
+setUpTextView
+
+    |paranthesis col|
+
+    self item hasMimeType ifFalse:[^nil].
+    (self item mimeType isHtml) ifTrue:[
+        paranthesis := editView parenthesisSpecification.
+        ((paranthesis at:#open) includes:$<) ifFalse:[
+            col := (paranthesis at:#open) asOrderedCollection add:$<.
+            paranthesis at:#open put:col.
+        ].
+        ((paranthesis at:#close) includes:$>) ifFalse:[
+            col := (paranthesis at:#close) asOrderedCollection add:$>.
+            paranthesis at:#close put:col.
+        ]
+    ].
+! !
+
+!FileApplicationNoteBook::XViewApplication class methodsFor:'defaults'!
+
+maxNumberOfVNCRestarts
+
+    ^ 10
+!
+
+mimeTypeUnixApplicationMapping
+
+" here insert the application and mime type pairs to open by XviewApplication
+"
+
+    ^
+    #(
+        #(#'application/postscript'     #gv            )
+        #(#'application/pdf'            #acroread      )
+    )
+!
+
+tabStringFor:aApplicationType
+
+    ^ 'VNC for:'
+!
+
+wantNewApplicationAnyway
+
+    ^ false
+! !
+
+!FileApplicationNoteBook::XViewApplication 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:NoteBookApplication::XViewApplication andSelector:#windowSpec
+     NoteBookApplication::XViewApplication new openInterface:#windowSpec
+     NoteBookApplication::XViewApplication open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'XView'
+          #name: 'XView'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 12 22 688 514)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#MenuPanelSpec
+              #name: 'MenuTerminal'
+              #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 32 0)
+              #visibilityChannel: #isEmbeddedApplication
+              #menu: #menu
+              #textDefault: true
+            )
+           #(#ArbitraryComponentSpec
+              #name: 'TerminalView'
+              #layout: #(#LayoutFrame 0 0.0 32 0.0 0 1.0 0 1.0)
+              #hasHorizontalScrollBar: true
+              #hasVerticalScrollBar: true
+              #miniScrollerHorizontal: false
+              #miniScrollerVertical: false
+              #hasBorder: false
+              #component: #VNCFrameBufferView
+              #postBuildCallback: #postBuildXView:
+            )
+           )
+         
+        )
+      )
+! !
+
+!FileApplicationNoteBook::XViewApplication class methodsFor:'menu specs'!
+
+menu
+    "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:NoteBookApplication::ImageViewApplication andSelector:#menu
+     (Menu new fromLiteralArrayEncoding:(NoteBookApplication::ImageViewApplication menu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(#Menu
+        #(
+         #(#MenuItem
+            #label: 'Close'
+            #translateLabel: true
+            #isButton: true
+            #hideMenuOnActivated: false
+            #startGroup: #right
+            #value: #doClose
+            #labelImage: #(#ResourceRetriever #AbstractFileBrowser #closeIcon)
+          )
+         )
+        nil
+        nil
+      )
+! !
+
+!FileApplicationNoteBook::XViewApplication class methodsFor:'queries'!
+
+canOpenItem:aItem
+
+    | keySym canOpen|
+    
+    keySym := aItem mimeType asSymbol.
+    (OperatingSystem isUNIXlike) not ifTrue:[^ false].
+    canOpen := self mimeTypeUnixApplicationMapping detect:[ : el | (el at:1) == keySym ] ifNone:[nil].
+    canOpen isNil ifTrue:[^ false].
+     (OperatingSystem executeCommand:('which ', self UnixVNCCommand)) ifTrue:[
+        ^ true
+    ] ifFalse:[
+        (Dialog warn:'cant start viewer for '
+                        , aItem fileName baseName
+        )
+    ].
+    ^ false.
+! !
+
+!FileApplicationNoteBook::XViewApplication methodsFor:'accessing'!
+
+xView
+    "return the value of the instance variable 'imageView' (automatically generated)"
+
+    ^ xView
+!
+
+xView:something
+    "set the value of the instance variable 'imageView' (automatically generated)"
+
+    xView := something.
+! !
+
+!FileApplicationNoteBook::XViewApplication methodsFor:'actions'!
+
+changeInformation 
+
+    | stream|
+
+    stream := WriteStream on:''.
+    stream nextPutAll:'XView on: '.
+    stream nextPutAll:self fileName baseName.
+    masterApplication isNil ifTrue:[
+        self window label:stream contents.
+
+    ] ifFalse:[
+        masterApplication tabStringChangeTo:stream contents for:self.
+    ].
+    stream close.
+!
+
+setupXView
+
+    |xExt yExt fileBrowserWindow|
+
+    self startVNCserver.
+    xExt := self xView width asString.
+    fileBrowserWindow := self application:#FileBrowserV2 do:#window.
+    fileBrowserWindow isNil ifTrue:[
+        yExt := self xView height asString.
+    ] ifFalse:[
+        yExt := fileBrowserWindow height asString.
+    ].
+    ext := xExt, 'x', yExt.    
+    self startViewer.
+! !
+
+!FileApplicationNoteBook::XViewApplication methodsFor:'actions VNC'!
+
+setupView
+    |  renderer view|
+
+    view := xView.
+    renderer := VNCRenderer for:vncConnection targetWindow:view device:xView device.
+
+    view renderer:renderer.
+    view connection:vncConnection.
+
+    VNCException handle:[:ex|
+        self stopViewer.
+    ] do:[
+        vncConnection 
+            startMessageHandlerProcessForRenderer:renderer
+            errorHandler:[:ex | self stopViewer].
+    ].
+!
+
+startVNCserver
+    |cmd blocked connected numberOfVncStarts|
+
+    connected := false.
+    numberOfVncStarts isNil ifTrue:[
+        numberOfVncStarts := 1.
+    ] ifFalse:[
+        numberOfVncStarts := numberOfVncStarts + 1.
+    ].
+
+    vncLock isNil ifTrue:[vncLock := Semaphore forMutualExclusion].
+
+    vncServerPID isNil ifTrue:[
+        cmd := ('/usr/X11R6/bin/', self class UnixVNCCommand).
+        cmd asFilename exists ifFalse:[
+            cmd := self class UnixVNCCommand.
+        ].
+        vncPortNr isNil ifTrue:[
+            vncPortNr := 29
+        ].
+        cmd := cmd , ' :' , vncPortNr printString , ' nologo -nevershared -localhost -depth 16 -geometry 1024x1024'.
+
+        blocked := OperatingSystem blockInterrupts.
+
+        vncServerPID := Processor
+                   monitor:[
+                      vncServerIsTerminated := false.
+                      OperatingSystem
+                          exec:'/bin/sh'
+                          withArguments:(Array with:'sh' with:'-c' with:cmd)
+                          fileDescriptors:#()
+                          closeDescriptors:#()
+                          fork:true
+                          newPgrp:true
+                          inDirectory:nil.
+                   ]
+                   action:[:status |
+                      status stillAlive ifFalse:[
+                          OperatingSystem closePid:vncServerPID.
+                          vncLock critical:[  
+                             vncServerPID := nil.
+                             self vncServerTerminated.
+                          ].
+                      ].
+                  ].
+
+        blocked ifFalse:[
+            OperatingSystem unblockInterrupts
+        ].
+    ].
+
+    self waitForTerminationOfServer ifTrue:[
+"/        Transcript showCR:'server has terminated really - try with next port'.
+        (numberOfVncStarts < self class maxNumberOfVNCRestarts) ifTrue:[
+            vncPortNr := vncPortNr + 1.
+"/            Transcript showCR:'try next port ', vncPortNr asString.
+            self startVNCserver.
+        ] ifFalse:[
+            Dialog warn:'have started servers from port '
+                      , (vncPortNr - self class maxNumberOfVNCRestarts) asString
+                      , ' to '
+                      , vncPortNr
+                      , ' - cant connect anyway'.
+"/            Transcript showCR:'have started servers from port ', vncPortNr - self class maxNumberOfVNCRestarts, ' to ', vncPortNr.
+        ].
+    ] ifFalse:[
+        vncLock critical:[  
+            vncServerPID isNil ifTrue:[
+                Dialog warn:'Cannot start Xvnc'.
+            ] ifFalse:[
+                VNCAuthenticationFailure handle:[:ex |
+                    Dialog warn:'Wrong password'.
+                ] do:[
+                    connected := self vncConnect.
+                ].
+                connected ifTrue:[self setupView].
+            ].
+        ].
+    ].
+!
+
+stopVNCServer
+
+    vncServerPID notNil ifTrue:[
+        OperatingSystem terminateProcess:vncServerPID.
+        Delay waitForSeconds:0.2.
+        vncServerPID notNil ifTrue:[
+            OperatingSystem killProcess:vncServerPID.
+            vncServerPID := nil.
+        ].
+    ].
+    self vncServerTerminated.
+!
+
+vncConnect
+    |  tryConnects|
+
+    vncConnection notNil ifTrue:[
+        vncConnection close
+    ].
+
+    vncConnection := VNCServerConnection new.
+    tryConnects := 1.
+    [tryConnects < 3] whileTrue:[
+        VNCConnectionFailure handle:[:ex |
+            Delay waitForSeconds:0.5.
+            tryConnects := tryConnects + 1.
+        ] do:[
+            vncConnection connectTo:'localhost' port:vncPortNr.
+            ^ true.
+        ].
+    ].
+    ^ false
+!
+
+vncServerTerminated
+"/    Transcript showCR:'vnc server has terminated'.
+"/    'vnc server has terminated' errorPrintCR.
+    "/ Dialog information:'vnc server has terminated'.
+
+    self stopViewer.
+    vncConnection notNil ifTrue:[
+        vncConnection close.
+        vncConnection := nil
+    ].
+    vncServerIsTerminated := true.
+!
+
+waitForTerminationOfServer
+    | cycles |
+
+    cycles := 1.
+    [vncServerIsTerminated] whileFalse:[
+        (cycles > 3) ifTrue:[^ false].
+        cycles := cycles + 1.
+        Delay waitForSeconds:0.5.
+    ].
+    ^ true
+! !
+
+!FileApplicationNoteBook::XViewApplication methodsFor:'actions viewer'!
+
+startViewer
+    |cmd keySym applItem |
+
+    keySym := self item mimeType asSymbol.
+    applItem := self class mimeTypeUnixApplicationMapping detect:[ : el | (el at:1) == keySym ] ifNone:[nil].
+    applItem isNil ifTrue:[ ^ self].
+    
+    cmd := (applItem at:2) asString, ' -geometry ', ext, ' -display :' , vncPortNr printString , ' ' , self fileName asString.
+    self startViewer:cmd
+!
+
+startViewer:viewerCommand
+    |blocked|
+
+    viewerPID notNil ifTrue:[
+        ^ self
+    ].
+
+    blocked := OperatingSystem blockInterrupts.
+
+    viewerPID := Processor
+               monitor:[
+                  OperatingSystem
+                      exec:'/bin/sh'
+                      withArguments:(Array with:'sh' with:'-c' with:viewerCommand)
+                      fileDescriptors:#()
+                      closeDescriptors:#()
+                      fork:true
+                      newPgrp:true
+                      inDirectory:nil.
+               ]
+               action:[:status |
+                  status stillAlive ifFalse:[
+                      OperatingSystem closePid:viewerPID.
+                      viewerPID := nil.
+                      self viewerTerminated.
+                  ].
+               ].
+
+    blocked ifFalse:[
+        OperatingSystem unblockInterrupts
+    ].
+
+    viewerPID isNil ifTrue:[
+        Dialog warn:'Cannot start ', viewerCommand.
+    ].
+!
+
+startXterm
+    |cmd|
+
+    cmd := 'xterm -geometry 600x800 -display :' , vncPortNr printString.
+    self startViewer:cmd
+!
+
+stopViewer
+    viewerPID notNil ifTrue:[
+        OperatingSystem terminateProcess:viewerPID.
+        Delay waitForSeconds:0.2.
+        viewerPID notNil ifTrue:[
+            OperatingSystem killProcess:viewerPID.
+            viewerPID := nil.
+        ]
+    ].
+!
+
+viewerTerminated
+"/    Transcript showCR:'viewer has terminated'.
+"/    'viewer has terminated' errorPrintCR.
+    "/ Dialog information:'viewer has terminated'.
+! !
+
+!FileApplicationNoteBook::XViewApplication methodsFor:'initialization & release'!
+
+postBuildXView:aWidget
+
+    self xView:aWidget scrolledView.
+    self xView wantsFocusWithPointerEnter.
+    aWidget autoHideScrollBars:true.
+!
+
+postOpenWith:aBuilder 
+    "
+    only invoked if the application not started from a master
+    "
+
+    |currentDir contents suffix fileName|
+
+    self masterApplication isNil ifTrue:[
+        self masterApplication:nil.
+        currentDir := Filename homeDirectory.
+        contents := currentDir directoryContents.
+        fileName := contents 
+                    detect:[:file | 
+                        suffix := file asFilename suffix asLowercase.
+                        suffix = 'pdf'
+                    ]
+                    ifNone:[nil].
+        fileName isNil ifTrue:[
+            Dialog warn:'cant find a PDF File in ' , currentDir asString.
+            ^ self
+        ].
+        self item:(DirectoryContentsBrowser itemClass with:(currentDir construct:fileName)).
+    ].
+    self changeInformation.
+    self setupXView.
+    ^ super postOpenWith:aBuilder
+!
+
+release
+"/Transcript showCR:'release'.
+    self stopViewer.
+    self stopVNCServer.
+    ^ super release
+! !
+
+!FileApplicationNoteBook class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libtool/FileApplicationNoteBook.st,v 1.1 2002-09-25 07:59:29 penk Exp $'
+! !