packages/PackageDetails.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 31 May 2018 10:52:50 +0100
branchjv
changeset 4330 998eb03f0736
parent 3011 1997ff6e7e55
permissions -rw-r--r--
Copyright updates

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

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

"{ Package: 'stx:libbasic3' }"

"{ NameSpace: Packages }"

AbstractPackageNotebookApplication subclass:#PackageDetails
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Package-Application'
!

AbstractPackageDetails subclass:#Class
	instanceVariableNames:'classList selectedClassHolder categoryList selectedCategoryHolder
		nonCriticalPrivateProcesses'
	classVariableNames:''
	poolDictionaries:''
	privateIn:PackageDetails
!

LabelAndIcon subclass:#ClassLabelAndIcon
	instanceVariableNames:'class'
	classVariableNames:''
	poolDictionaries:''
	privateIn:PackageDetails::Class
!

AbstractPackageDetails subclass:#Comment
	instanceVariableNames:'commentTextHolder commentTextModifiedChannel
		commentTextAcceptChannel editTextView'
	classVariableNames:''
	poolDictionaries:''
	privateIn:PackageDetails
!

AbstractPackageDetails subclass:#LooseMethod
	instanceVariableNames:'methodSelectedHolder currentMethodSourceHolder methodList
		tableColumns'
	classVariableNames:''
	poolDictionaries:''
	privateIn:PackageDetails
!

Object subclass:#PackageDetailsRow
	instanceVariableNames:'model'
	classVariableNames:''
	poolDictionaries:''
	privateIn:PackageDetails::LooseMethod
!

AbstractPackageDetails subclass:#Prerequisites
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:PackageDetails
!

AbstractPackageDetails subclass:#Scripts
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:PackageDetails
!

!PackageDetails class methodsFor:'documentation'!

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

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

!PackageDetails::Class class methodsFor:'constant values'!

applicationName
    ^ 'Classes' asSymbol
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Packages::PackageDetails::Class'
          #name: 'Packages::PackageDetails::Class'
          #visibilityChannel: #isVisible
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 29 59 329 359)
          #menu: #mainMenu
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VariableHorizontalPanelSpec
              #name: 'VariableHorizontalPanel1'
              #layout: #(#LayoutFrame 0 0 0 0 0 1 0 1)
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#SequenceViewSpec
                    #name: 'SelectionInListModelView2'
                    #model: #selectedCategoryHolder
                    #hasHorizontalScrollBar: true
                    #hasVerticalScrollBar: true
                    #isMultiSelect: true
                    #useIndex: false
                    #sequenceList: #categoryList
                  )
                 #(#SequenceViewSpec
                    #name: 'SelectedClassView1'
                    #model: #selectedClassHolder
                    #hasHorizontalScrollBar: true
                    #hasVerticalScrollBar: true
                    #isMultiSelect: true
                    #doubleClickSelector: #browseClassWithIndexes:
                    #useIndex: true
                    #sequenceList: #classList
                  )
                 )
               
              )
              #handles: #(#Any 0.5 1.0)
            )
           )
         
        )
      )
! !

!PackageDetails::Class class methodsFor:'menu specs'!

mainMenu
    "This resource specification was automatically generated by the CodeGeneratorTool."

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

    "
     MenuEditor new openOnClass:Packages::PackageDetails::Class andSelector:#mainMenu
    "

    <resource: #menu>

    ^ #(#Menu
           #(
             #(#MenuItem
                #label: 'File'
                #translateLabel: true
                #submenu: 
                 #(#Menu
                     #(
                       #(#MenuItem
                          #label: 'New'
                          #translateLabel: true
                          #value: #menuNew
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Open...'
                          #translateLabel: true
                          #value: #menuOpen
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Save'
                          #translateLabel: true
                          #value: #menuSave
                      )
                       #(#MenuItem
                          #label: 'Save As...'
                          #translateLabel: true
                          #value: #menuSaveAs
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Exit'
                          #translateLabel: true
                          #value: #closeRequest
                      )
                    ) nil
                    nil
                )
            )
             #(#MenuItem
                #label: 'Help'
                #translateLabel: true
                #startGroup: #right
                #submenu: 
                 #(#Menu
                     #(
                       #(#MenuItem
                          #label: 'Documentation'
                          #translateLabel: true
                          #value: #openDocumentation
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'About this Application'
                          #translateLabel: true
                          #value: #openAboutThisApplication
                      )
                    ) nil
                    nil
                )
            )
          ) nil
          nil
      )
! !

!PackageDetails::Class class methodsFor:'plugIn spec'!

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

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

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

    ^ #(
        #classList
        #selectedClassHolder
      ).

! !

!PackageDetails::Class methodsFor:'accessing'!

classListAt:idx 
    ^ self classList at:idx
!

declareDependents
    super declareDependents
!

privateProcessesAt:aSymbol 
    ^ (nonCriticalPrivateProcesses at:aSymbol ifAbsentPut:[[nil]fork]).
!

privateProcessesAt:aSymbol put:aProcess
    ^ (nonCriticalPrivateProcesses at:aSymbol put:aProcess).
! !

!PackageDetails::Class methodsFor:'adding'!

addPrivateClassLabelAndIconForClass:aClass toClassList:aClassList level:aNumber
    aClass privateClasses do:[:aPrivateClass |
        aClassList add:(self newClassLabelAndIconWithClass:aPrivateClass).
        self addPrivateClassLabelAndIconForClass:aPrivateClass toClassList:aClassList level:(aNumber + 1).
    ].
!

putClassesNamesIn:aClassList fromPackages:collectionOfPackages inCategories:collectionOfCategoryNames 
    | classesWithoutPrivateClasses|
    classesWithoutPrivateClasses := OrderedCollection new.
    collectionOfCategoryNames do:[:aCategoryName |
        collectionOfPackages do:[:aPackage |
            (aPackage classesInCategory:aCategoryName) 
                do:[:aClass |  aClass isPrivate ifFalse:[
                                        classesWithoutPrivateClasses add:(self newClassLabelAndIconWithClass:aClass).
                                ].
            ].
        ].
    ].
    classesWithoutPrivateClasses sort:[:x :y |
        x asString < y asString
    ].
    classesWithoutPrivateClasses do:[:aLableAndIcon | | aClass |
        aClass := aLableAndIcon classModel.
        aClassList add:aLableAndIcon.
        self addPrivateClassLabelAndIconForClass:aClass toClassList:aClassList level:1
    ].
! !

!PackageDetails::Class methodsFor:'aspects'!

categoryList
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    categoryList isNil ifTrue:[
        categoryList := List new.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       categoryList addDependent:self.
"/       categoryList onChangeSend:#categoryListChanged to:self.
    ].
    ^ categoryList.
!

classList
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    classList isNil ifTrue:[
        classList := List new.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       classList addDependent:self.
"/       classList onChangeSend:#classListChanged to:self.
    ].
    ^ classList.
!

selectedCategoryHolder
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    selectedCategoryHolder isNil ifTrue:[
        selectedCategoryHolder := ValueHolder new.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
       selectedCategoryHolder addDependent:self.
"/       selectedCategoryHolder onChangeSend:#selectedCategoryHolderChanged to:self.
    ].
    ^ selectedCategoryHolder.
!

selectedClassHolder
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    selectedClassHolder isNil ifTrue:[
        selectedClassHolder := ValueHolder new.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       selectedClassHolder addDependent:self.
"/       selectedClassHolder onChangeSend:#selectedClassHolderChanged to:self.
    ].
    ^ selectedClassHolder.
! !

!PackageDetails::Class methodsFor:'aspects - exported'!

classList:something
    "automatically generated by UIPainter ..."

    "This method is used when I am embedded as subApplication,"
    "and the mainApp wants to connect its aspects to mine."

"/     classList notNil ifTrue:[
"/        classList removeDependent:self.
"/     ].
    classList := something.
"/     classList notNil ifTrue:[
"/        classList addDependent:self.
"/     ].
    ^ self.
!

selectedClassHolder:something
    "automatically generated by UIPainter ..."

    "This method is used when I am embedded as subApplication,"
    "and the mainApp wants to connect its aspects to mine."

"/     selectedClassHolder notNil ifTrue:[
"/        selectedClassHolder removeDependent:self.
"/     ].
    selectedClassHolder := something.
"/     selectedClassHolder notNil ifTrue:[
"/        selectedClassHolder addDependent:self.
"/     ].
    ^ self.
! !

!PackageDetails::Class methodsFor:'browsing'!

browseClassWithIndexes:aCollectionOfIndexes
    "An 'adapter method'. Calls #browserClass:. Is only used as there can be
    private classes with the same name and the selectionList cannot tell the difference
    otherwise."
    | classItems |
    classItems := aCollectionOfIndexes collect:[:idx |
        self classListAt:idx
    ].

    ^ self browseClasses:classItems
!

browseClasses:aCollection
    | theClass |
    theClass := aCollection first classModel.
    (Smalltalk classNamed:(theClass name)) browse
! !

!PackageDetails::Class methodsFor:'change & update'!

selectedCategoryChanged:aCollectionOfCategories 

    self withProcessNamed:#selectedCategoryChanged: do:[
        classList removeAll.
        self 
            putClassesNamesIn:classList 
            fromPackages:self packagesSelected 
            inCategories:aCollectionOfCategories.

    ].
!

update:something with:aParameter from:changedObject

    changedObject == selectedCategoryHolder ifTrue:[
        self selectedCategoryChanged:aParameter        
    ].

    super update:something with:aParameter from:changedObject
!

updateWithPackages:packages
    | classCategoryNames |
    packages size = 1 ifTrue:[
        packages first ifNil:[
            ^ self.
        ]
    ].

    self withProcessNamed:#updateWithPackages: do:[ 
        classList removeAll.
        categoryList removeAll.
        classCategoryNames := Set new.
        packages do:[:aPackage |
            classCategoryNames addAll:aPackage classCategories   
        ].

        categoryList addAll:classCategoryNames.
        categoryList sort:[:x :y |
            x < y
        ]. 
    ].
"/    packages do:[:aPackage |
"/        categoryList addAll:aPackage classCategories   
"/    ].
! !

!PackageDetails::Class methodsFor:'factory'!

labelAndIconClass
    ^ ClassLabelAndIcon
!

newClassLabelAndIconWithClass:aClass
"/    aClass isPrivate ifTrue:[self halt.].
    ^ self labelAndIconClass class:aClass
! !

!PackageDetails::Class methodsFor:'initialization & release'!

closeDownViews
    "This is a hook method generated by the Browser.
     It will be invoked when your app/dialog-window is really closed.
     See also #closeDownViews, which is invoked before and may suppress the close
     or ask the user for confirmation."

    "/ change the code below as required ...
    "/ This should cleanup any leftover resources
    "/ (for example, temporary files)
    "/ super closeRequest will initiate the closeDown

    "/ add your code here

    "/ do not remove the one below ...
    ^ super closeDownViews
!

closeRequest
    "This is a hook method generated by the Browser.
     It will be invoked when your app/dialog-window is about to be
     closed (this method has a chance to suppress the close).
     See also #closeDownViews, which is invoked when the close is really done."

    "/ change the code below as required ...
    "/ Closing can be suppressed, by simply returning.
    "/ The 'super closeRequest' at the end will initiate the real closeDown

    ("self hasUnsavedChanges" true) ifTrue:[
        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
            ^ self
        ]
    ].

    ^ super closeRequest
!

initialize
    nonCriticalPrivateProcesses := Dictionary new
!

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

    ^ super postOpenWith:aBuilder
! !

!PackageDetails::Class methodsFor:'menu actions'!

menuNew
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'new' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''new'' available.'.
!

menuOpen
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'open' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''open'' available.'.
!

menuSave
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'save' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''save'' available.'.
!

menuSaveAs
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'saveAs' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''saveAs'' available.'.
!

openAboutThisApplication
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'help-about' is selected."

    "/ could open a customized aboutBox here ...
    super openAboutThisApplication
!

openDocumentation
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'help-documentation' is selected."

    "/ change below as required ...

    "/ to open an HTML viewer on some document (under 'doc/online/<language>/' ):
    HTMLDocumentView openFullOnDocumentationFile:'TOP.html'.

    "/ add application-specific help files under the 'doc/online/<language>/help/appName'
    "/ directory, and open a viewer with:
    "/ HTMLDocumentView openFullOnDocumentationFile:'help/<MyApplication>/TOP.html'.
! !

!PackageDetails::Class methodsFor:'process'!

withProcessNamed:aName do:aBlock 
    "stop unconditionally the process and replace with aBlock"
    (self privateProcessesAt:aName) terminate.
    self privateProcessesAt:aName put:aBlock fork.
! !

!PackageDetails::Class methodsFor:'queries'!

validateCanChange:arg 
! !

!PackageDetails::Class::ClassLabelAndIcon class methodsFor:'instance'!

class:aClass
    ^ (self basicNew) classModel:aClass; initialize
! !

!PackageDetails::Class::ClassLabelAndIcon methodsFor:'accessing'!

asString

    | aString |
    aString := String new.
    class isPrivate ifTrue:[
        aString := '    '.
        self privateClassDepth timesRepeat:[
            aString := aString , '  '.
        ].
        aString := aString , '::'. 
    ].

    aString := aString, class shortName asString. 

    ^ aString
!

classModel
    "return the value of the instance variable 'class' (automatically generated)"

    ^ class
!

classModel:something
    "set the value of the instance variable 'class' (automatically generated)"

    class := something.
    self string: self asString.
!

privateClassDepth
    | thisClass counter |
    thisClass := class.
    counter := 0.
    [thisClass isNameSpace] whileFalse:[
        thisClass := thisClass owningClass.
        thisClass ifNil:[thisClass := Smalltalk].
        counter := counter + 1.
    ].

    ^ counter - 1
! !

!PackageDetails::Comment class methodsFor:'constant values'!

applicationName
    ^ 'Comment' asSymbol
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Packages::PackageDetails::Comment'
          #name: 'Packages::PackageDetails::Comment'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 29 59 329 359)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#TextEditorSpec
              #name: 'TextEditor1'
              #layout: #(#LayoutFrame 0 0 0 0 0 1 0 1)
              #model: #commentTextHolder
              #hasHorizontalScrollBar: true
              #hasVerticalScrollBar: true
              #modifiedChannel: #commentTextModifiedChannel
              #acceptCallBack: #commentAccepted:
              #postBuildCallback: #commentTextEditorCreated:
            )
           )
         
        )
      )
! !

!PackageDetails::Comment methodsFor:'accessing'!

declareDependents
    super declareDependents
! !

!PackageDetails::Comment methodsFor:'aspects'!

commentTextAcceptChannel
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    commentTextAcceptChannel isNil ifTrue:[
        commentTextAcceptChannel := TriggerValue new.
    ].
    ^ commentTextAcceptChannel.
!

commentTextHolder
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    commentTextHolder isNil ifTrue:[
        commentTextHolder := '' asValue.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       commentTextHolder addDependent:self.
"/       commentTextHolder onChangeSend:#commentTextHolderChanged to:self.
    ].
    ^ commentTextHolder.
!

commentTextModifiedChannel
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    commentTextModifiedChannel isNil ifTrue:[
        commentTextModifiedChannel := TriggerValue new.
    ].
    ^ commentTextModifiedChannel.
! !

!PackageDetails::Comment methodsFor:'callbacks'!

commentAccepted:aStringCollection 
    |packagesSelected|
    (packagesSelected := self packagesSelected) size > 1 ifTrue:[
        Smalltalk beep.
        ^ self.
    ].

    (self packagesNamed:self packagesSelected) first packageComment:aStringCollection asString.
!

commentTextEditorCreated:aScrolledViewWithTextEditor 
    "do with the text editor widget as you will...."
    editTextView := aScrolledViewWithTextEditor scrolledView.

! !

!PackageDetails::Comment methodsFor:'change & update'!

packagesSelectedHolderChanged:selectedPackages 
    |packagesSelected selectedSinglePackage |

    packagesSelected := self packagesSelected.

    selectedPackages size == 1 ifTrue:[
        selectedSinglePackage := selectedPackages first.
        ^ commentTextHolder value: selectedSinglePackage packageComment.
    ].
    selectedPackages size == 0 ifTrue:[
        ^ commentTextHolder value:'No package selected' 
    ].   
    "selectedPackages size > 1 ifTrue:["
        ^ commentTextHolder value:'Cannot show more than one comment!!'  
    "]."
!

validateCanChange:arg 
! !

!PackageDetails::Comment methodsFor:'defaults'!

commentForMultiplePackageSelect
    ^ String new
! !

!PackageDetails::Comment methodsFor:'initialization & release'!

closeDownViews
    "This is a hook method generated by the Browser.
     It will be invoked when your app/dialog-window is really closed.
     See also #closeDownViews, which is invoked before and may suppress the close
     or ask the user for confirmation."

    "/ change the code below as required ...
    "/ This should cleanup any leftover resources
    "/ (for example, temporary files)
    "/ super closeRequest will initiate the closeDown

    "/ add your code here

    "/ do not remove the one below ...
    ^ super closeDownViews
!

closeRequest
    "This is a hook method generated by the Browser.
     It will be invoked when your app/dialog-window is about to be
     closed (this method has a chance to suppress the close).
     See also #closeDownViews, which is invoked when the close is really done."

    "/ change the code below as required ...
    "/ Closing can be suppressed, by simply returning.
    "/ The 'super closeRequest' at the end will initiate the real closeDown

    ("self hasUnsavedChanges" true) ifTrue:[
        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
            ^ self
        ]
    ].

    ^ super closeRequest
!

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

    ^ super postOpenWith:aBuilder
! !

!PackageDetails::LooseMethod class methodsFor:'constant values'!

applicationName
    ^ 'Loose Method' asSymbol
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Packages::PackageDetails::LooseMethod'
          #name: 'Packages::PackageDetails::LooseMethod'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 29 59 329 359)
          #menu: #mainMenu
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VariableVerticalPanelSpec
              #name: 'VariableVerticalPanel1'
              #layout: #(#LayoutFrame 0 0 0 0 0 1 0 1)
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#DataSetSpec
                    #name: 'Table1'
                    #model: #methodSelectedHolder
                    #hasHorizontalScrollBar: true
                    #hasVerticalScrollBar: true
                    #dataList: #methodList
                    #has3Dsepartors: false
                    #columnHolder: #tableColumns
                    #multipleSelectOk: true
                    #verticalSpacing: 0
                  )
                 #(#TextEditorSpec
                    #name: 'SourceEditor'
                    #model: #currentMethodSourceHolder
                    #hasHorizontalScrollBar: true
                    #hasVerticalScrollBar: true
                  )
                 )
               
              )
              #handles: #(#Any 0.5 1.0)
            )
           )
         
        )
      )
! !

!PackageDetails::LooseMethod class methodsFor:'menu specs'!

mainMenu
    "This resource specification was automatically generated by the CodeGeneratorTool."

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

    "
     MenuEditor new openOnClass:Packages::PackageDetails::LooseMethod andSelector:#mainMenu
    "

    <resource: #menu>

    ^ #(#Menu
           #(
             #(#MenuItem
                #label: 'File'
                #translateLabel: true
                #submenu: 
                 #(#Menu
                     #(
                       #(#MenuItem
                          #label: 'New'
                          #translateLabel: true
                          #value: #menuNew
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Open...'
                          #translateLabel: true
                          #value: #menuOpen
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Save'
                          #translateLabel: true
                          #value: #menuSave
                      )
                       #(#MenuItem
                          #label: 'Save As...'
                          #translateLabel: true
                          #value: #menuSaveAs
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Exit'
                          #translateLabel: true
                          #value: #closeRequest
                      )
                    ) nil
                    nil
                )
            )
             #(#MenuItem
                #label: 'Help'
                #translateLabel: true
                #startGroup: #right
                #submenu: 
                 #(#Menu
                     #(
                       #(#MenuItem
                          #label: 'Documentation'
                          #translateLabel: true
                          #value: #openDocumentation
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'About this Application'
                          #translateLabel: true
                          #value: #openAboutThisApplication
                      )
                    ) nil
                    nil
                )
            )
          ) nil
          nil
      )
! !

!PackageDetails::LooseMethod 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:Packages::PackageDetails::LooseMethod andSelector:#tableColumns
    "

    <resource: #tableColumns>

    ^#(
      #(#DataSetColumnSpec
         #label: ''
         #id: 'Icon'
         #labelButtonType: #Button
         #model: #icon
         #canSelect: false
         #showRowSeparator: false
         #showColSeparator: false
       )
      #(#DataSetColumnSpec
         #label: 'Selector'
         #id: 'Selector'
         #labelAlignment: #left
         #labelButtonType: #Button
         #model: #selector
         #canSelect: false
         #showRowSeparator: false
         #showColSeparator: false
       )
      #(#DataSetColumnSpec
         #label: 'Class'
         #id: 'Class'
         #labelAlignment: #left
         #labelButtonType: #Button
         #model: #myClass
         #canSelect: false
         #showRowSeparator: false
         #showColSeparator: false
       )
      #(#DataSetColumnSpec
         #label: 'Package'
         #id: 'Package'
         #labelButtonType: #Button
         #model: #myPackage
         #canSelect: false
         #showRowSeparator: false
         #showColSeparator: false
       )
      )
!

tableColumnsOld
    "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:Packages::PackageDetails::LooseMethod andSelector:#tableColumns
    "

    <resource: #tableColumns>

    ^#(
      #(#DataSetColumnSpec
         #label: ''
         #id: 'Icon'
         #labelButtonType: #Button
         #model: #icon
         #canSelect: false
       )
      #(#DataSetColumnSpec
         #label: 'Selector'
         #id: 'Selector'
         #labelAlignment: #left
         #labelButtonType: #Button
         #model: #selector
         #canSelect: false
       )
      #(#DataSetColumnSpec
         #label: 'Class'
         #id: 'Class'
         #labelAlignment: #left
         #labelButtonType: #Button
         #model: #myClass
         #canSelect: false
       )
      #(#DataSetColumnSpec
         #label: 'Package'
         #id: 'Package'
         #labelButtonType: #Button
         #model: #myPackage
         #canSelect: false
       )
      )
! !

!PackageDetails::LooseMethod methodsFor:'accessing'!

currentMethodSource:aString 
    self currentMethodSourceHolder value:aString
!

declareDependents
    super declareDependents
! !

!PackageDetails::LooseMethod methodsFor:'aspects'!

currentMethodSourceHolder
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    currentMethodSourceHolder isNil ifTrue:[
        currentMethodSourceHolder := '' asValue.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       currentMethodSourceHolder addDependent:self.
"/       currentMethodSourceHolder onChangeSend:#currentMethodSourceHolderChanged to:self.
    ].
    ^ currentMethodSourceHolder.
!

methodList
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    methodList isNil ifTrue:[
        methodList := List new.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       methodList addDependent:self.
"/       methodList onChangeSend:#methodListChanged to:self.
    ].
    ^ methodList.
!

methodSelectedHolder
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    methodSelectedHolder isNil ifTrue:[
        methodSelectedHolder := ValueHolder new.
        methodSelectedHolder onChangeEvaluate:[| methodSelectedHolderValue|
            (methodSelectedHolderValue := methodSelectedHolder value) ifNotNil:[
                self currentMethodSourceChangedToIndex:methodSelectedHolderValue
            ].

        ]
    ].
    ^ methodSelectedHolder.
!

tableColumns
    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    tableColumns isNil ifTrue:[
        tableColumns := self class tableColumns asValue.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       tableColumns addDependent:self.
"/       tableColumns onChangeSend:#tableColumnsChanged to:self.
    ].
    ^ tableColumns.
! !

!PackageDetails::LooseMethod methodsFor:'change & update'!

currentMethodSourceChangedToIndex:aCollection
    | currentPackageDetailsRow |
    aCollection size > 1 ifTrue:[
        self currentMethodSource: self moreThanOneMethodCode.
        ^ self.
    ].
    currentPackageDetailsRow := (self methodList at:aCollection first).
    self currentMethodSourceHolder value:(currentPackageDetailsRow model source).
!

updateWithPackages:packages
    | methodNames |
    methodList removeAll.
    currentMethodSourceHolder value:String new.
    methodNames := OrderedCollection new.

    packages do:[:aPackage | 
        methodNames addAll:(aPackage looseMethods collect:[:aMethod| self newPackageDetailsRowWithModel:aMethod]).   
    ].

    methodList addAll:methodNames.
!

validateCanChange:arg 
! !

!PackageDetails::LooseMethod methodsFor:'defaults'!

moreThanOneMethodCode
    ^ String new
! !

!PackageDetails::LooseMethod methodsFor:'factory'!

newPackageDetailsRowWithModel:aModel 
    ^ PackageDetailsRow new model: aModel
! !

!PackageDetails::LooseMethod methodsFor:'initialization & release'!

closeDownViews
    "This is a hook method generated by the Browser.
     It will be invoked when your app/dialog-window is really closed.
     See also #closeDownViews, which is invoked before and may suppress the close
     or ask the user for confirmation."

    "/ change the code below as required ...
    "/ This should cleanup any leftover resources
    "/ (for example, temporary files)
    "/ super closeRequest will initiate the closeDown

    "/ add your code here

    "/ do not remove the one below ...
    ^ super closeDownViews
!

closeRequest
    "This is a hook method generated by the Browser.
     It will be invoked when your app/dialog-window is about to be
     closed (this method has a chance to suppress the close).
     See also #closeDownViews, which is invoked when the close is really done."

    "/ change the code below as required ...
    "/ Closing can be suppressed, by simply returning.
    "/ The 'super closeRequest' at the end will initiate the real closeDown

    ("self hasUnsavedChanges" true) ifTrue:[
        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
            ^ self
        ]
    ].

    ^ super closeRequest
!

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

    ^ super postOpenWith:aBuilder
! !

!PackageDetails::LooseMethod methodsFor:'menu actions'!

menuNew
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'new' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''new'' available.'.
!

menuOpen
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'open' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''open'' available.'.
!

menuSave
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'save' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''save'' available.'.
!

menuSaveAs
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'saveAs' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''saveAs'' available.'.
!

openAboutThisApplication
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'help-about' is selected."

    "/ could open a customized aboutBox here ...
    super openAboutThisApplication
!

openDocumentation
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'help-documentation' is selected."

    "/ change below as required ...

    "/ to open an HTML viewer on some document (under 'doc/online/<language>/' ):
    HTMLDocumentView openFullOnDocumentationFile:'TOP.html'.

    "/ add application-specific help files under the 'doc/online/<language>/help/appName'
    "/ directory, and open a viewer with:
    "/ HTMLDocumentView openFullOnDocumentationFile:'help/<MyApplication>/TOP.html'.
! !

!PackageDetails::LooseMethod::PackageDetailsRow methodsFor:'accessing'!

icon
    "automatically generated by DataSetBuilder ..."

    "get value"

    ^ ''
!

model
    "return the value of the instance variable 'model' (automatically generated)"

    ^ model
!

model:arg 
    model:= arg.
!

myClass
    "automatically generated by DataSetBuilder ..."

    "get value"

    ^ model mclass
!

myPackage
    "automatically generated by DataSetBuilder ..."

    "get value"

    ^ model package
!

selector
    "automatically generated by DataSetBuilder ..."

    "get value"

    ^ model selector
! !

!PackageDetails::Prerequisites class methodsFor:'constant values'!

applicationName
    ^ 'Prerequisites' asSymbol
! !

!PackageDetails::Prerequisites class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated by the CodeGeneratorTool."

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

    "
     UIPainter new openOnClass:Packages::PackageDetails::Prerequisites andSelector:#windowSpec
    "

    <resource: #canvas>

    ^ #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'Packages::PackageDetails::Prerequisites'
              #layout: #(#LayoutFrame 204 0 162 0 503 0 461 0)
              #label: 'Packages::PackageDetails::Prerequisites'
              #min: #(#Point 10 10)
              #max: #(#Point 1024 768)
              #bounds: #(#Rectangle 204 162 504 462)
              #menu: #mainMenu
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: #()
          )
      )
! !

!PackageDetails::Prerequisites class methodsFor:'menu specs'!

mainMenu
    "This resource specification was automatically generated by the CodeGeneratorTool."

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

    "
     MenuEditor new openOnClass:Packages::PackageDetails::Prerequisites andSelector:#mainMenu
    "

    <resource: #menu>

    ^ #(#Menu
           #(
             #(#MenuItem
                #label: 'File'
                #translateLabel: true
                #submenu: 
                 #(#Menu
                     #(
                       #(#MenuItem
                          #label: 'New'
                          #translateLabel: true
                          #value: #menuNew
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Open...'
                          #translateLabel: true
                          #value: #menuOpen
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Save'
                          #translateLabel: true
                          #value: #menuSave
                      )
                       #(#MenuItem
                          #label: 'Save As...'
                          #translateLabel: true
                          #value: #menuSaveAs
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Exit'
                          #translateLabel: true
                          #value: #closeRequest
                      )
                    ) nil
                    nil
                )
            )
             #(#MenuItem
                #label: 'Help'
                #translateLabel: true
                #startGroup: #right
                #submenu: 
                 #(#Menu
                     #(
                       #(#MenuItem
                          #label: 'Documentation'
                          #translateLabel: true
                          #value: #openDocumentation
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'About this Application'
                          #translateLabel: true
                          #value: #openAboutThisApplication
                      )
                    ) nil
                    nil
                )
            )
          ) nil
          nil
      )
! !

!PackageDetails::Prerequisites methodsFor:'accessing'!

declareDependents
    super declareDependents
! !

!PackageDetails::Prerequisites methodsFor:'change & update'!

packagesSelectedHolderChanged:aCollection 
!

validateCanChange:arg 
! !

!PackageDetails::Prerequisites methodsFor:'initialization & release'!

closeDownViews
    "This is a hook method generated by the Browser.
     It will be invoked when your app/dialog-window is really closed.
     See also #closeDownViews, which is invoked before and may suppress the close
     or ask the user for confirmation."

    "/ change the code below as required ...
    "/ This should cleanup any leftover resources
    "/ (for example, temporary files)
    "/ super closeRequest will initiate the closeDown

    "/ add your code here

    "/ do not remove the one below ...
    ^ super closeDownViews
!

closeRequest
    "This is a hook method generated by the Browser.
     It will be invoked when your app/dialog-window is about to be
     closed (this method has a chance to suppress the close).
     See also #closeDownViews, which is invoked when the close is really done."

    "/ change the code below as required ...
    "/ Closing can be suppressed, by simply returning.
    "/ The 'super closeRequest' at the end will initiate the real closeDown

    ("self hasUnsavedChanges" true) ifTrue:[
        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
            ^ self
        ]
    ].

    ^ super closeRequest
!

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

    ^ super postOpenWith:aBuilder
! !

!PackageDetails::Prerequisites methodsFor:'menu actions'!

menuNew
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'new' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''new'' available.'.
!

menuOpen
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'open' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''open'' available.'.
!

menuSave
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'save' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''save'' available.'.
!

menuSaveAs
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'saveAs' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''saveAs'' available.'.
!

openAboutThisApplication
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'help-about' is selected."

    "/ could open a customized aboutBox here ...
    super openAboutThisApplication
!

openDocumentation
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'help-documentation' is selected."

    "/ change below as required ...

    "/ to open an HTML viewer on some document (under 'doc/online/<language>/' ):
    HTMLDocumentView openFullOnDocumentationFile:'TOP.html'.

    "/ add application-specific help files under the 'doc/online/<language>/help/appName'
    "/ directory, and open a viewer with:
    "/ HTMLDocumentView openFullOnDocumentationFile:'help/<MyApplication>/TOP.html'.
! !

!PackageDetails::Scripts class methodsFor:'constant values'!

applicationName
    ^ 'Scripts' asSymbol
! !

!PackageDetails::Scripts class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated by the CodeGeneratorTool."

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

    "
     UIPainter new openOnClass:Packages::PackageDetails::Scripts andSelector:#windowSpec
    "

    <resource: #canvas>

    ^ #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'Packages::PackageDetails::Scripts'
              #layout: #(#LayoutFrame 204 0 162 0 503 0 461 0)
              #label: 'Packages::PackageDetails::Scripts'
              #min: #(#Point 10 10)
              #max: #(#Point 1024 768)
              #bounds: #(#Rectangle 204 162 504 462)
              #menu: #mainMenu
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: #()
          )
      )
! !

!PackageDetails::Scripts class methodsFor:'menu specs'!

mainMenu
    "This resource specification was automatically generated by the CodeGeneratorTool."

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

    "
     MenuEditor new openOnClass:Packages::PackageDetails::Scripts andSelector:#mainMenu
    "

    <resource: #menu>

    ^ #(#Menu
           #(
             #(#MenuItem
                #label: 'File'
                #translateLabel: true
                #submenu: 
                 #(#Menu
                     #(
                       #(#MenuItem
                          #label: 'New'
                          #translateLabel: true
                          #value: #menuNew
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Open...'
                          #translateLabel: true
                          #value: #menuOpen
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Save'
                          #translateLabel: true
                          #value: #menuSave
                      )
                       #(#MenuItem
                          #label: 'Save As...'
                          #translateLabel: true
                          #value: #menuSaveAs
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Exit'
                          #translateLabel: true
                          #value: #closeRequest
                      )
                    ) nil
                    nil
                )
            )
             #(#MenuItem
                #label: 'Help'
                #translateLabel: true
                #startGroup: #right
                #submenu: 
                 #(#Menu
                     #(
                       #(#MenuItem
                          #label: 'Documentation'
                          #translateLabel: true
                          #value: #openDocumentation
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'About this Application'
                          #translateLabel: true
                          #value: #openAboutThisApplication
                      )
                    ) nil
                    nil
                )
            )
          ) nil
          nil
      )
! !

!PackageDetails::Scripts methodsFor:'accessing'!

declareDependents
    super declareDependents
! !

!PackageDetails::Scripts methodsFor:'change & update'!

packagesSelectedHolderChanged:aCollection 
    self breakPoint:''.
!

validateCanChange:arg 
! !

!PackageDetails::Scripts methodsFor:'initialization & release'!

closeDownViews
    "This is a hook method generated by the Browser.
     It will be invoked when your app/dialog-window is really closed.
     See also #closeDownViews, which is invoked before and may suppress the close
     or ask the user for confirmation."

    "/ change the code below as required ...
    "/ This should cleanup any leftover resources
    "/ (for example, temporary files)
    "/ super closeRequest will initiate the closeDown

    "/ add your code here

    "/ do not remove the one below ...
    ^ super closeDownViews
!

closeRequest
    "This is a hook method generated by the Browser.
     It will be invoked when your app/dialog-window is about to be
     closed (this method has a chance to suppress the close).
     See also #closeDownViews, which is invoked when the close is really done."

    "/ change the code below as required ...
    "/ Closing can be suppressed, by simply returning.
    "/ The 'super closeRequest' at the end will initiate the real closeDown

    ("self hasUnsavedChanges" true) ifTrue:[
        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
            ^ self
        ]
    ].

    ^ super closeRequest
!

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

    ^ super postOpenWith:aBuilder
! !

!PackageDetails::Scripts methodsFor:'menu actions'!

menuNew
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'new' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''new'' available.'.
!

menuOpen
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'open' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''open'' available.'.
!

menuSave
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'save' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''save'' available.'.
!

menuSaveAs
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'saveAs' is selected."

    "/ change below and add any actions as required here ...
    self warn:'no action for ''saveAs'' available.'.
!

openAboutThisApplication
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'help-about' is selected."

    "/ could open a customized aboutBox here ...
    super openAboutThisApplication
!

openDocumentation
    "This method was generated by the Browser.
     It will be invoked when the menu-item 'help-documentation' is selected."

    "/ change below as required ...

    "/ to open an HTML viewer on some document (under 'doc/online/<language>/' ):
    HTMLDocumentView openFullOnDocumentationFile:'TOP.html'.

    "/ add application-specific help files under the 'doc/online/<language>/help/appName'
    "/ directory, and open a viewer with:
    "/ HTMLDocumentView openFullOnDocumentationFile:'help/<MyApplication>/TOP.html'.
! !

!PackageDetails class methodsFor:'documentation'!

version
    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageDetails.st,v 1.4 2006-01-10 09:25:03 cg Exp $'
! !