AbstractSettingsApplication.st
author Claus Gittinger <cg@exept.de>
Wed, 07 May 2003 16:52:53 +0200
changeset 4867 269d62a1ed27
parent 4851 359312a95673
child 4873 3ffb8a8812ec
permissions -rw-r--r--
method category rename

"{ Package: 'stx:libtool' }"

ApplicationModel subclass:#AbstractSettingsApplication
	instanceVariableNames:'settingsString currentUserPrefs modifiedChannel requestor'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Smalltalk'
!

AbstractSettingsApplication subclass:#ByteCodeCompilerSettingsAppl
	instanceVariableNames:'allowQualifiedNames warnDollar warnOldStyle fullDebugSupport
		warnCommonMistakes warnUnderscore keepSource constantFolding
		warnCompatibility constantFoldingOptions warnings warnSTX
		allowDollar allowReservedWordsAsSelectors immutableArrays
		allowOldStyleAssignment allowUnderscore allowDolphinExtensions
		warnUnusedVars allowSqueakExtensions justInTimeCompilation
		canLoadBinaries constantFoldingSelection enableUnderscore
		enableDollar'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#DebuggerSettingsAppl
	instanceVariableNames:'showErrorNotifier showVerboseStack allowSendMailFromDebugger'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#DisplaySettingsAppl
	instanceVariableNames:'isColorMonitor useFixGrayPaletteLabel useFixPalette sizeY
		clipEncodingListSelection sizeX monitorList ditherList
		clipEncodingList ditherListSelection deepIcons monitorSelection
		useFixPaletteLabel visualIsPseudoColor ditherSymsNotNil
		useFixGrayPalette sizeInfos screen ditherStyles ditherSyms
		screenDepthVisualLabelHolder'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#EditSettingsAppl
	instanceVariableNames:'st80EditingMode tabsIs4 st80DoubleClickSelectMode
		searchDialogIsModal startTextDragWithControl'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#FontSettingsAppl
	instanceVariableNames:'filter allOfThem labelDef buttonDef listDef menuDef textDef
		allFontLabelHolder buttonsFontLabelHolder textFontLabelHolder
		labelsFontLabelHolder listsFontLabelHolder menusFontLabelHolder
		allLabel buttonsLabel textLabel labelLabel listsLabel menuLabel'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#GeneralCompilerSettingsAppl
	instanceVariableNames:'st80EditingMode tabsIs4 st80DoubleClickSelectMode
		searchDialogIsModal startTextDragWithControl catchClassRedefs
		fullHistoryUpdate historyLines keepSourceSelection keepSource
		hasHistoryManager canLoadBinaries loadBinaries catchMethodRedefs'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#HTTPStartServerSettingsApplication
	instanceVariableNames:'portNumberChannel informationLabel hasNoCreatedServerChannel
		hasCreatedServerChannel'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#KbdMappingSettingsAppl
	instanceVariableNames:'selectedRawKey macroTextHolder selectedFunctionKey
		labelTextHolder functionKeyList rawKeyList mappings'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#LanguageSettingsAppl
	instanceVariableNames:'languageHolder languageList listOfLanguages translatedLanguages
		noticeLabelHolder currentLanguageChannel currentLanguageLabel'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#MemorySettingsAppl
	instanceVariableNames:'newSpaceSize maxOldSpace fastMoreLimit warningLabelHolder
		codeTrigger codeLimit oldIncr compressLimit igcFreeLimit igcLimit
		igcFreeAmount stackLimit supportsJustInTimeCompilation'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#MiscCommunicationSettingsAppl
	instanceVariableNames:'remoteBrowsingEnabled windowMigrationEnabled
		windowMigrationPassword windowMigrationAuthenticate
		enablePasswordCheck'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#MiscDisplaySettingsAppl
	instanceVariableNames:'returnFocus focusFollowsMouse beepEnabled takeFocus
		activateOnClick shadows opaqueVariablePanelResize
		formatHostNameinWindowLabels opaqueTableColumnResize
		hostNameInLabelHolder showAccelerators newWindowLabelFormat
		formatHostNameWindowLabel'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#OsiSettingsAppl
	instanceVariableNames:'osiACSEConnectionLogging osiROSEErrorLogging osiCMISEErrorLogging
		osiACSEErrorLogging osiROSEPresent osiCMISEPresent
		osiCMISEMessageLogging osiACSEDataLogging
		osiROSEInvokationLogging osiACSEPresent osiROSEResponseLogging'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#PrinterSettingsAppl
	instanceVariableNames:'selectedUnit supportsColor topMargin rightMargin bottomMargin
		landscape pageFormatList pageFormat unitList leftMargin
		possiblePrinters printerType printerTypeSelection
		printCommandList commandList printCommand enableFormat
		enablelandscape enableMargins enableColorBox'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#ProcessorSchedulerSettingsAppl
	instanceVariableNames:'dynamicPrios preemptive'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#RDoItServerSettingsAppl
	instanceVariableNames:'rDoitLogging rDoitsEnabled rDoitErrorLogging hasRDoitServer
		rDoitErrorDebugging rDoitServerPort'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#STCCompilerSettingsAppl
	instanceVariableNames:'cc ccOptions stcIncludes linkCommand stc linkArgs canLoadBinaries
		stcDefines stcLibraries stcOptions stcLibraryPath
		stcCompilationSelection stcCompilationList'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#SourceCodeFormatSettingsAppl
	instanceVariableNames:'spaceAfterKeywordSelector emptyLineAfterTemporaries tabIndent
		autoFormat cStyleBlocks editorText maxLengthForSingleLineBlocks
		blockArgumentsOnNewLine spaceAfterReturnToken
		spaceAroundTemporaries oldUserPreferences reformatLocked'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#SourceCodeManagementSettingsAppl
	instanceVariableNames:'sourceCacheDir useManager condenseSourceCache
		syntaxColorConfiguration setupSourceCodeManager
		checkClassesWhenCheckingIn formattingConfiguration
		flushSourceCache localSourceFirst cvsIsSetup repositoryHolder
		manager repository listOfModules cvsRootPrototypeList
		addPerModuleRoot removeEnabled perModuleRootModule acceptChannel
		removePerModuleRoot perModuleRoot cvsRootHolder
		selectedPerModuleRoot cvsBinDirectoryHolder rootsPerModule'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#StyleSettingsAppl
	instanceVariableNames:'showStandardStylesOnly styleList selectedStyle
		styleDirectoryContents infoLabelHolder noticeLabelHolder'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#SyntaxColorSettingsAppl
	instanceVariableNames:'coloredText syntaxColor syntaxColors resetList resetListSelection
		fullSelectorCheck syntaxColoring oldUserPreferences
		syntaxFontSelector syntaxFonts syntaxElementList
		syntaxElementSelection syntaxEmphasisList syntaxEmphasisSelection
		emphasisDictionary resetListDictionary'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#SystemMessageSettingsAppl
	instanceVariableNames:'classInfos vmInfo vmErrors displayErrors logDoits updChanges
		changeFileName'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

AbstractSettingsApplication subclass:#ToolsSettingsAppl
	instanceVariableNames:'useNewVersionDiffBrowser transcriptBufferSize useNewInspector
		showClockInLauncher useNewChangesBrowser useNewFileBrowser
		useNewSystemBrowser useNewFileDialog useNewSettingsApplication
		useProcessMonitorV2'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSettingsApplication
!

!AbstractSettingsApplication class methodsFor:'documentation'!

windowSpec

    self subclassResponsibility
! !

!AbstractSettingsApplication class methodsFor:'defaults'!

classResources

    ^ AbstractLauncherApplication classResources
! !

!AbstractSettingsApplication methodsFor:'accessing'!

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

    ^ requestor
!

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

    requestor := something.
! !

!AbstractSettingsApplication methodsFor:'actions'!

evaluateModified
    self hasUnsavedChanges ifTrue:[
        self modifiedChannel value:true
    ].
!

saveRequest
    |result|

    (self hasUnsavedChanges) ifTrue:[
        self askForChangeOnRealease ifTrue:[
            result := self confirmWithCancel:(resources 
                                string:'Save changed ' , settingsString , ' ?').
        ] ifFalse:[
            result := true.
        ].
        result isNil ifTrue:[
            ^ false
        ].
        result ifTrue:[
            self saveSettings
        ] ifFalse:[
            self readSettings
        ]
    ].
    ^ true
!

saveSettingsIfUnsavedChangesArePresent
    self hasUnsavedChanges ifTrue:[
        self saveSettings.
        self modifiedChannel value:false
    ].
! !

!AbstractSettingsApplication methodsFor:'aspects'!

modifiedChannel

    modifiedChannel isNil ifTrue:[
        modifiedChannel := false asValue.
    ].
    ^ modifiedChannel
! !

!AbstractSettingsApplication methodsFor:'initialization'!

initialize
    super initialize.
    resources := self class classResources.
    currentUserPrefs := UserPreferences current.
    settingsString := (UISpecification from:(self class windowSpec)) window label.
    self readSettings.
! !

!AbstractSettingsApplication methodsFor:'protocol'!

askForChangeOnRealease
    ^ false
!

basicSaveSettings

    self subclassResponsibility.
!

hasUnsavedChanges

    ^ self subclassResponsibility
!

help

    self subclassResponsibility.
"/    self warn:'no help available here'.
"/    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/keyboardSetting.html'].
!

readSettings
    self subclassResponsibility
!

saveSettings

    self basicSaveSettings.
    currentUserPrefs := UserPreferences current.
    self modifiedChannel value:false.
! !

!AbstractSettingsApplication::ByteCodeCompilerSettingsAppl class methodsFor:'defaults'!

constantFoldingOptions

    ^ #( nil #level1 #level2 #full )
!

constantFoldingStrings

    ^ #('disabled' 'level1 (always safe)' 'level2 (usually safe)' 'full')
! !

!AbstractSettingsApplication::ByteCodeCompilerSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::CompilerSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@H@@@@@@@@@@@@@@@@@@@@@@@@@@@@B@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@H@
@@DA@PD@@PDA@@DA@PD@@PDA@@@B@@@A@PDA@@DA@P@A@PDA@@DA@P@@@ @@@P@@@P@A@@D@@P@@@P@A@@D@@@H@@@DA@PD@@PDA@@DA@PD@@PDA@@@B@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@ @@@PDA@PDA@PDA@PDA@PD@@PD@@@H@@@D@@@@@@PDA@@@@@PDA@@DA@@@B@@@A@PDA@PDA@@DA@P@A@P@A@P@@@ @@@P@@
@@@A@P@A@PDA@PD@@PD@@@H@@@DA@PDA@PD@@PDA@PDA@@DA@@@B@@@A@@@@@@DA@@DA@PDA@P@A@P@@@ @@@PDA@PDA@P@A@PD@@PD@@PD@@@H@@@D@@@@@
@PDA@@@@@PDA@@DA@@@B@@@A@PDA@PDA@PDA@PDA@P@A@P@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 255 255 255 0 0 0]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8@@@@@@@@@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Byte Code Compiler Settings'
          #name: 'Byte Code Compiler Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 46 616 560)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel1'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#CheckBoxSpec
                    #label: 'Just in Time Compilation to Machine Code'
                    #name: 'JustInTimeCompilation'
                    #model: #justInTimeCompilation
                    #translateLabel: true
                    #extent: #(#Point 600 25)
                  )
                 #(#DividerSpec
                    #name: 'Separator3'
                    #extent: #(#Point 600 3)
                  )
                 #(#CheckBoxSpec
                    #label: 'Allow Underscore in Identifiers'
                    #name: 'AllowUnderscoreInIdentifiers'
                    #model: #allowUnderscore
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#CheckBoxSpec
                    #label: 'Allow Dollar in Identifiers'
                    #name: 'AllowDollarInIdentifiers'
                    #model: #allowDollar
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#CheckBoxSpec
                    #label: 'Allow VW3 QualifiedNames'
                    #name: 'AllowVW3QualifiedNames'
                    #model: #allowQualifiedNames
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#CheckBoxSpec
                    #label: 'Allow Squeak Extensions'
                    #name: 'AllowSqueakExtensions'
                    #model: #allowSqueakExtensions
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#CheckBoxSpec
                    #label: 'Allow Dolphin Extensions'
                    #name: 'AllowDolphinExtensions'
                    #model: #allowDolphinExtensions
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#CheckBoxSpec
                    #label: 'Allow OldStyle Assignment (_)'
                    #name: 'AllowOldStyleAssignment'
                    #model: #allowOldStyleAssignment
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#CheckBoxSpec
                    #label: 'Allow Reserved Words as Selector (self)'
                    #name: 'AllowReservedWordsAsSelector'
                    #model: #allowReservedWordsAsSelectors
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#DividerSpec
                    #name: 'Separator4'
                    #extent: #(#Point 600 3)
                  )
                 #(#CheckBoxSpec
                    #label: 'Warnings'
                    #name: 'Warnings'
                    #model: #warnings
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#ViewSpec
                    #name: 'Box2'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#VerticalPanelViewSpec
                          #name: 'VerticalPanel2'
                          #layout: #(#LayoutFrame 20 0 0 0 600 0 150 0)
                          #horizontalLayout: #left
                          #verticalLayout: #center
                          #horizontalSpace: 3
                          #verticalSpace: 3
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'ST/X Extensions'
                                #name: 'STXExtensions'
                                #enableChannel: #warnings
                                #model: #warnSTX
                                #translateLabel: true
                                #extent: #(#Point 600 22)
                              )
                             #(#CheckBoxSpec
                                #label: 'Underscores in Identifiers'
                                #name: 'UnderscoresInIdentifiers'
                                #enableChannel: #enableUnderscore
                                #model: #warnUnderscore
                                #translateLabel: true
                                #extent: #(#Point 600 22)
                              )
                             #(#CheckBoxSpec
                                #label: 'Dollars in Identifiers'
                                #name: 'DollarsInIdentifiers'
                                #enableChannel: #enableDollar
                                #model: #warnDollar
                                #translateLabel: true
                                #extent: #(#Point 600 22)
                              )
                             #(#CheckBoxSpec
                                #label: 'Unused Method Variables'
                                #name: 'UnusedMethodVariables'
                                #enableChannel: #warnings
                                #model: #warnUnusedVars
                                #translateLabel: true
                                #extent: #(#Point 600 22)
                              )
                             #(#CheckBoxSpec
                                #label: 'OldStyle Assignment'
                                #name: 'OldStyleAssignment'
                                #enableChannel: #warnings
                                #model: #warnOldStyle
                                #translateLabel: true
                                #extent: #(#Point 600 22)
                              )
                             #(#CheckBoxSpec
                                #label: 'Common Mistakes'
                                #name: 'CommonMistakes'
                                #enableChannel: #warnings
                                #model: #warnCommonMistakes
                                #translateLabel: true
                                #extent: #(#Point 600 22)
                              )
                             #(#CheckBoxSpec
                                #label: 'Possible Incompatibilities'
                                #name: 'PossibleIncompatibilities'
                                #enableChannel: #warnings
                                #model: #warnCompatibility
                                #translateLabel: true
                                #extent: #(#Point 600 22)
                              )
                             )
                           
                          )
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 160)
                  )
                 #(#DividerSpec
                    #name: 'Separator5'
                    #extent: #(#Point 600 2)
                  )
                 #(#CheckBoxSpec
                    #label: 'Literal Arrays are Immutable'
                    #name: 'LiteralArraysAreImmutable'
                    #model: #immutableArrays
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#CheckBoxSpec
                    #label: 'Full Debug Info'
                    #name: 'FullDebugInfo'
                    #model: #fullDebugSupport
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#DividerSpec
                    #name: 'Separator6'
                    #extent: #(#Point 600 2)
                  )
                 #(#ViewSpec
                    #name: 'Box1'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Constant Folding:'
                          #name: 'ConstantFoldingLabel'
                          #layout: #(#LayoutFrame 0 0 0 0 150 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#PopUpListSpec
                          #label: 'PopUp List'
                          #name: 'ConstantFolding'
                          #layout: #(#LayoutFrame 170 0 0 0 -5 1 22 0)
                          #tabable: true
                          #model: #constantFoldingSelection
                          #menu: #constantFolding
                          #useIndex: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 22)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::ByteCodeCompilerSettingsAppl methodsFor:'actions'!

basicSaveSettings

    Compiler warnings:self warnings value.
    Compiler warnSTXSpecials:self warnSTX value.
    Compiler warnOldStyleAssignment:self warnOldStyle value.
    Compiler warnUnderscoreInIdentifier:self warnUnderscore value.
    Compiler warnDollarInIdentifier:self warnDollar value.
    Compiler warnCommonMistakes:self warnCommonMistakes value.
    Compiler warnPossibleIncompatibilities:self warnCompatibility value.
    Compiler warnUnusedVars:self warnUnusedVars value.
    Compiler allowUnderscoreInIdentifier:self allowUnderscore value.
    Compiler allowDollarInIdentifier:self allowDollar value.
    Compiler allowSqueakExtensions:self allowSqueakExtensions value.
    Compiler allowDolphinExtensions:self allowDolphinExtensions value.
    Compiler allowQualifiedNames:self allowQualifiedNames value.
    Compiler allowOldStyleAssignment:self allowOldStyleAssignment value.
    Compiler allowReservedWordsAsSelectors:self allowReservedWordsAsSelectors value.

    Compiler arraysAreImmutable:self immutableArrays value.
    self fullDebugSupport value ifTrue:[
        Compiler lineNumberInfo:#full.
    ] ifFalse:[
        Compiler lineNumberInfo:true
    ].

    Compiler foldConstants:(self class constantFoldingOptions at:self constantFoldingSelection value).

    self supportsJustInTimeCompilation ifTrue:[
        | justInTime |
        justInTime := self justInTimeCompilation value.
        justInTime ifTrue:[
            Method allInstancesDo:[:m | m checked:false].
        ].
        ObjectMemory justInTimeCompilation:justInTime.
        ObjectMemory fullSingleStepSupport:self fullDebugSupport value.
    ].
!

help

    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/compilerSettings.html'].
!

readSettings
    self allowDollar value:(Compiler allowDollarInIdentifier ? false).
    self allowDolphinExtensions 
        value:(Compiler allowDolphinExtensions ? false).
    self allowOldStyleAssignment 
        value:(Compiler allowOldStyleAssignment ? false).
    self allowQualifiedNames value:(Compiler allowQualifiedNames ? false).
    self allowReservedWordsAsSelectors 
        value:(Compiler allowReservedWordsAsSelectors ? false).
    self allowSqueakExtensions value:(Compiler allowSqueakExtensions ? false).
    self allowUnderscore value:(Compiler allowUnderscoreInIdentifier ? false).
    self constantFoldingSelection 
        value:(self class constantFoldingOptions indexOf:Compiler foldConstants
                ifAbsent:3).
    self supportsJustInTimeCompilation ifTrue:[
        self fullDebugSupport value:(ObjectMemory fullSingleStepSupport ? false)
    ] ifFalse:[
        self fullDebugSupport value:(Compiler lineNumberInfo == #full)
    ].
    self immutableArrays value:(Compiler arraysAreImmutable ? false).
    self supportsJustInTimeCompilation ifTrue:[
        self justInTimeCompilation 
            value:(ObjectMemory justInTimeCompilation ? false)
    ] ifFalse:[
        self justInTimeCompilation value:false
    ].
    self warnCommonMistakes value:(Compiler warnCommonMistakes ? false).
    self warnCompatibility 
        value:(Compiler warnPossibleIncompatibilities ? false).
    self warnDollar value:(Compiler warnDollarInIdentifier ? false).
    self warnOldStyle value:(Compiler warnOldStyleAssignment ? false).
    self warnSTX value:(Compiler warnSTXSpecials ? false).
    self warnUnderscore value:(Compiler warnUnderscoreInIdentifier ? false).
    self warnUnusedVars value:(Compiler warnUnusedVars ? false).
    self warnings value:(Compiler warnings ? false).
    self modifiedChannel value:false
!

stcCompilerSettings

    AbstractLauncherApplication::LauncherDialogs stcCompilerSettings
! !

!AbstractSettingsApplication::ByteCodeCompilerSettingsAppl methodsFor:'aspects'!

allowDollar

    allowDollar isNil ifTrue:[
        allowDollar := (Compiler allowDollarInIdentifier ? false) asValue.
        allowDollar onChangeSend:#evaluateModified to:self.
        allowDollar addDependent:self.
    ].
    ^ allowDollar.
!

allowDolphinExtensions

    allowDolphinExtensions isNil ifTrue:[
        allowDolphinExtensions := (Compiler allowDolphinExtensions ? false) asValue.
        allowDolphinExtensions onChangeSend:#evaluateModified to:self.
    ].
    ^ allowDolphinExtensions.
!

allowOldStyleAssignment

    allowOldStyleAssignment isNil ifTrue:[
        allowOldStyleAssignment := (Compiler allowOldStyleAssignment ? false) asValue.
        allowOldStyleAssignment onChangeSend:#evaluateModified to:self.
    ].
    ^ allowOldStyleAssignment.
!

allowQualifiedNames

    allowQualifiedNames isNil ifTrue:[
        allowQualifiedNames := (Compiler allowQualifiedNames ? false) asValue.
        allowQualifiedNames onChangeSend:#evaluateModified to:self.
    ].
    ^ allowQualifiedNames.
!

allowReservedWordsAsSelectors

    allowReservedWordsAsSelectors isNil ifTrue:[
        allowReservedWordsAsSelectors := (Compiler allowReservedWordsAsSelectors ? false) asValue.
        allowReservedWordsAsSelectors onChangeSend:#evaluateModified to:self.
    ].
    ^ allowReservedWordsAsSelectors.
!

allowSqueakExtensions

    allowSqueakExtensions isNil ifTrue:[
        allowSqueakExtensions := (Compiler allowSqueakExtensions ? false) asValue.
        allowSqueakExtensions onChangeSend:#evaluateModified to:self.
    ].
    ^ allowSqueakExtensions.
!

allowUnderscore

    allowUnderscore isNil ifTrue:[
        allowUnderscore := (Compiler allowUnderscoreInIdentifier ? false) asValue.
        allowUnderscore onChangeSend:#evaluateModified to:self.
        allowUnderscore addDependent:self.
    ].
    ^ allowUnderscore.
!

constantFolding

    constantFolding isNil ifTrue:[
        constantFolding := (resources array:(self class constantFoldingStrings)) asList.
    ].
    ^ constantFolding.
!

constantFoldingOptions

    constantFoldingOptions isNil ifTrue:[
        constantFoldingOptions := self class constantFoldingOptions.
    ].
    ^ constantFoldingOptions.
!

constantFoldingSelection

    constantFoldingSelection isNil ifTrue:[
        | index |
        index := self class constantFoldingOptions indexOf:Compiler foldConstants ifAbsent:3.
        constantFoldingSelection := index asValue.
        constantFoldingSelection onChangeSend:#evaluateModified to:self.
    ].
    ^ constantFoldingSelection.
!

enableDollar

    enableDollar isNil ifTrue:[
        enableDollar := true asValue.
        enableDollar addDependent:self.
    ].
    ^ enableDollar.
!

enableUnderscore
    "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 ;-)"

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

fullDebugSupport

    fullDebugSupport isNil ifTrue:[
        self supportsJustInTimeCompilation ifTrue:[
            fullDebugSupport := (ObjectMemory fullSingleStepSupport ? false) asValue.
        ] ifFalse:[ 
            fullDebugSupport := (Compiler lineNumberInfo == #full) asValue.
        ].
        fullDebugSupport onChangeSend:#evaluateModified to:self.
    ].
    ^ fullDebugSupport.
!

immutableArrays

    immutableArrays isNil ifTrue:[
        immutableArrays := (Compiler arraysAreImmutable ? false) asValue.
        immutableArrays onChangeSend:#evaluateModified to:self.
    ].
    ^ immutableArrays.
!

justInTimeCompilation

    justInTimeCompilation isNil ifTrue:[
        self supportsJustInTimeCompilation ifTrue:[
            justInTimeCompilation := (ObjectMemory justInTimeCompilation ? false) asValue.
        ] ifFalse:[ 
            justInTimeCompilation := false asValue.
        ].
        justInTimeCompilation onChangeSend:#evaluateModified to:self.
    ].
    ^ justInTimeCompilation.
!

warnCommonMistakes

    warnCommonMistakes isNil ifTrue:[
        warnCommonMistakes := (Compiler warnCommonMistakes ? false) asValue.
        warnCommonMistakes onChangeSend:#evaluateModified to:self.
    ].
    ^ warnCommonMistakes.
!

warnCompatibility

    warnCompatibility isNil ifTrue:[
        warnCompatibility := (Compiler warnPossibleIncompatibilities ? false) asValue.
        warnCompatibility onChangeSend:#evaluateModified to:self.
    ].
    ^ warnCompatibility.
!

warnDollar

    warnDollar isNil ifTrue:[
        warnDollar := (Compiler warnDollarInIdentifier ? false) asValue.
        warnDollar onChangeSend:#evaluateModified to:self.
    ].
    ^ warnDollar.
!

warnOldStyle

    warnOldStyle isNil ifTrue:[
        warnOldStyle := (Compiler warnOldStyleAssignment ? false) asValue.
        warnOldStyle onChangeSend:#evaluateModified to:self.
    ].
    ^ warnOldStyle.
!

warnSTX

    warnSTX isNil ifTrue:[
        warnSTX := (Compiler warnSTXSpecials ? false) asValue.
        warnSTX onChangeSend:#evaluateModified to:self.
    ].
    ^ warnSTX.
!

warnUnderscore

    warnUnderscore isNil ifTrue:[
        warnUnderscore := (Compiler warnUnderscoreInIdentifier ? false) asValue.
        warnUnderscore onChangeSend:#evaluateModified to:self.
    ].
    ^ warnUnderscore.
!

warnUnusedVars

    warnUnusedVars isNil ifTrue:[
        warnUnusedVars := (Compiler warnUnusedVars ? false) asValue.
        warnUnusedVars onChangeSend:#evaluateModified to:self.
    ].
    ^ warnUnusedVars.
!

warnings

    warnings isNil ifTrue:[
        warnings := (Compiler warnings ? false) asValue.
        warnings addDependent:self.
        warnings changed.
        warnings onChangeSend:#evaluateModified to:self.
    ].
    ^ warnings.
! !

!AbstractSettingsApplication::ByteCodeCompilerSettingsAppl methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    changedObject == self warnings ifTrue:[
        changedObject value ifTrue:[
            self enableUnderscore value:self allowUnderscore value.
            self enableDollar value:self allowDollar value.
        ] ifFalse:[
            self enableUnderscore value:false.
            self enableDollar value:false.
        ].
        ^ self
    ].
    (changedObject == self allowDollar or:[changedObject == self allowUnderscore]) ifTrue:[
        self warnings changed.
        ^ self
    ].

    super update:something with:aParameter from:changedObject
! !

!AbstractSettingsApplication::ByteCodeCompilerSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ 
        (
        ((Compiler warnings ? false) ~= self warnings value) or:[
        ((Compiler warnSTXSpecials ? false) ~= self warnSTX value) or:[
        ((Compiler warnOldStyleAssignment ? false) ~= self warnOldStyle value) or:[
        ((Compiler warnUnderscoreInIdentifier ? false) ~= self warnUnderscore value) or:[
        ((Compiler warnDollarInIdentifier ? false) ~= self warnDollar value) or:[
        ((Compiler warnCommonMistakes ? false) ~= self warnCommonMistakes value) or:[
        ((Compiler warnPossibleIncompatibilities ? false) ~= self warnCompatibility value) or:[
        ((Compiler warnUnusedVars ? false) ~= self warnUnusedVars value)  or:[
        ((Compiler allowUnderscoreInIdentifier ? false) ~= self allowUnderscore value) or:[
        ((Compiler allowDollarInIdentifier ? false) ~= self allowDollar value) or:[
        ((Compiler allowSqueakExtensions ? false) ~= self allowSqueakExtensions value) or:[
        ((Compiler allowDolphinExtensions ? false) ~= self allowDolphinExtensions value) or:[
        ((Compiler allowQualifiedNames ? false) ~= self allowQualifiedNames value) or:[
        ((Compiler allowOldStyleAssignment ? false) ~= self allowOldStyleAssignment value) or:[
        ((Compiler allowReservedWordsAsSelectors ? false) ~= self allowReservedWordsAsSelectors value) or:[
        ((Compiler arraysAreImmutable ? false) ~= self immutableArrays value) or:[
        ((self supportsJustInTimeCompilation value ifTrue:[ObjectMemory fullSingleStepSupport ? false] ifFalse:[Compiler lineNumberInfo == #full]) ~= self fullDebugSupport value) or:[
        ((Compiler foldConstants) ~= (self class constantFoldingOptions at:self constantFoldingSelection value)) or:[
        ((ObjectMemory justInTimeCompilation ? false) ~= self justInTimeCompilation value)]]]]]]]]]]]]]]]]]])
!

supportsJustInTimeCompilation

    ^ ObjectMemory supportsJustInTimeCompilation
! !

!AbstractSettingsApplication::DebuggerSettingsAppl class methodsFor:'image specs'!

defaultIcon
    <resource: #programImage>

    ^ ToolbarIconLibrary bugReporter24x24Icon    
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Debugger Settings'
          #name: 'Debugger Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 616 362)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #top
              #horizontalSpace: 3
              #verticalSpace: 5
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel5'
                    #horizontalLayout: #fit
                    #verticalLayout: #topSpace
                    #horizontalSpace: 3
                    #verticalSpace: 3
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#ViewSpec
                          #name: 'Box10'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Show Error Notifier before Opening Debugger'
                                #name: 'ShowErrorNotifierCheckBox'
                                #layout: #(#LayoutFrame 5 0 5 0 -5 1 27 0)
                                #model: #showErrorNotifier
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 30)
                        )
                       #(#ViewSpec
                          #name: 'Box11'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Verbose Backtrace by Default in Debugger'
                                #name: 'ShowVerboseStackCheckBox'
                                #layout: #(#LayoutFrame 5 0 5 0 -5 1 27 0)
                                #model: #showVerboseStack
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 30)
                        )
                       #(#ViewSpec
                          #name: 'Box12'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Allow send Error Report from Debugger'
                                #name: 'CheckBox6'
                                #layout: #(#LayoutFrame 5 0 5 0 -5 1 27 0)
                                #model: #allowSendMailFromDebugger
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 30)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 320)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::DebuggerSettingsAppl methodsFor:'actions'!

basicSaveSettings

    currentUserPrefs allowSendMailFromDebugger:self allowSendMailFromDebugger value.
    self showErrorNotifier value ifFalse:[
        Exception emergencyHandler:nil
    ] ifTrue:[
        Exception emergencyHandler:(AbstractLauncherApplication notifyingEmergencyHandler)
    ].
    DebugView defaultVerboseBacktrace:self showVerboseStack value.
!

help

    self warn:'no help available here'.
"/    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/editSettings.html'].
!

readSettings
    self allowSendMailFromDebugger 
        value:currentUserPrefs allowSendMailFromDebugger.
    self showErrorNotifier value:(NoHandlerError emergencyHandler 
                == AbstractLauncherApplication notifyingEmergencyHandler).
    self showVerboseStack value:(DebugView defaultVerboseBacktrace ? false).
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::DebuggerSettingsAppl methodsFor:'aspects'!

allowSendMailFromDebugger

    allowSendMailFromDebugger isNil ifTrue:[
        allowSendMailFromDebugger := currentUserPrefs allowSendMailFromDebugger asValue.
        allowSendMailFromDebugger onChangeSend:#evaluateModified to:self
    ].
    ^ allowSendMailFromDebugger.
!

showErrorNotifier

    showErrorNotifier isNil ifTrue:[
        showErrorNotifier := (NoHandlerError emergencyHandler == AbstractLauncherApplication notifyingEmergencyHandler) asValue.
        showErrorNotifier onChangeSend:#evaluateModified to:self
    ].
    ^ showErrorNotifier.
!

showVerboseStack

    showVerboseStack isNil ifTrue:[
        showVerboseStack := (DebugView defaultVerboseBacktrace ? false) asValue.
        showVerboseStack onChangeSend:#evaluateModified to:self
    ].
    ^ showVerboseStack.
! !

!AbstractSettingsApplication::DebuggerSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ (
        self showErrorNotifier value ~= (NoHandlerError emergencyHandler == AbstractLauncherApplication notifyingEmergencyHandler) or:[
        DebugView defaultVerboseBacktrace ? false ~= self showVerboseStack value or:[
        (UserPreferences current at:#allowSendMailFromDebugger ifAbsent:true) ~= self allowSendMailFromDebugger value 
        ]]
    )
! !

!AbstractSettingsApplication::DisplaySettingsAppl class methodsFor:'defaults'!

clipEncodingStrings

    ^ #('untranslated' 'iso8859' 'jis' 'jis7' 'shift-JIS' 'EUC' 'big5')
!

clipEncodingSyms

    ^ #(nil #iso8859 #jis #jis7 #sjis #euc #big5)
!

staticGrayOrGrayScaleDitherStrings

    ^ #('threshold' 'ordered dither' 'error diffusion')
!

staticGrayOrGrayScaleDitherSyms

    ^ #(threshold ordered floydSteinberg)
!

trueColorDitherStrings

    ^ #('nearest color' 'error diffusion')
!

trueColorDitherSyms

    ^ #(ordered floydSteinberg)
! !

!AbstractSettingsApplication::DisplaySettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::DisplaySettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@JB (JB (JB (JB (JB (I2\@@@@@
@B (JB (JB (JB (JB (JB\''@@@@@@@(JA@ZFA YE@,KC@,KA0P''I1T@@@@@JB RH2D!!HRD HA(MCP\DI2\U@@@@@B (GRT#H2D"H2L^C0<HAB\''EP@@@@@(
JA4%H2L!!H"L#G <OB@P''I1T@@@@@JB ZH2P$H1<_G1$OC0XDI2\U@@@@@B (C!!$ HA,\FQ$OC0<FAB\''EP@@@@@(JA@WE!!XWFQ XC <OBPT''I1T@@@@@JB P
E1XVE1$XF@8OC0$EI2\U@@@@@B (A!!DSD0(CB (B@PDAAB\''EP@@@@@''I2\''I"X''I2\''I2\''I2\''I1T@@@@@I2\''I2X&I2\''I2\''I2\''I2\U@@@@@@@@EQTU
ER ''I2\''EQTUEQTUEP@@@@@@@@@@@@@(I2\''I1TU@@@@@@@@@@@@@@@@JB\''I2\''I2\''I2\U@@@@@@@@@@@@@B ''I2\''I2\''I2\''EP@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 60 78 83 61 77 82 63 79 84 63 81 86 66 83 87 66 84 89 66 85 91 67 86 92 68 86 91 69 87 92 69 88 94 70 90 95 71 91 96 71 92 98 72 93 99 73 94 100 74 92 97 74 95 101 75 93 98 75 96 102 76 76 76 76 97 103 77 98 104 77 99 106 79 101 108 80 103 109 81 104 110 82 105 111 83 106 112 83 107 114 86 110 117 87 111 118 88 113 121 89 114 122 90 116 123 91 117 124 92 118 125 126 126 126 127 127 127 139 139 139]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@G??0G??0G??8G??8G??8G??8G??8G??8G??8G??8G??8G??8G??8A??8@G<@@??@@??@@@@@@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Display Screen Settings'
          #name: 'Display Screen Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 616 390)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#LabelSpec
              #label: 'Actual Visible Screen Area:'
              #name: 'ActualVisibleScreenAreaLabel'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 22 0)
              #translateLabel: true
              #adjust: #left
            )
           #(#LabelSpec
              #label: 'Common Sizes:'
              #name: 'CommonSizesLabel'
              #layout: #(#LayoutFrame 0 0 39 0 205 0 61 0)
              #translateLabel: true
              #adjust: #right
            )
           #(#PopUpListSpec
              #label: 'monitor size'
              #name: 'MonitorSelectionPopUpList'
              #layout: #(#LayoutFrame 205 0 39 0 -5 1 61 0)
              #tabable: true
              #model: #monitorSelection
              #menu: #monitorList
              #useIndex: true
            )
           #(#LabelSpec
              #label: 'Screen Size:'
              #name: 'ScreenSizeLabel'
              #layout: #(#LayoutFrame 0 0 72 0 205 0 94 0)
              #translateLabel: true
              #adjust: #right
            )
           #(#InputFieldSpec
              #name: 'SizeXEntryField'
              #layout: #(#LayoutFrame 205 0 72 0 300 0 94 0)
              #model: #sizeX
              #type: #number
              #immediateAccept: true
              #acceptOnReturn: true
              #acceptOnTab: true
              #acceptOnLostFocus: true
              #acceptOnPointerLeave: true
            )
           #(#LabelSpec
              #label: ' x '
              #name: 'xLabel'
              #layout: #(#LayoutFrame 314 0 72 0 360 0 94 0)
              #translateLabel: true
              #adjust: #right
            )
           #(#InputFieldSpec
              #name: 'SizeYEntryField'
              #layout: #(#LayoutFrame 379 0 72 0 474 0 94 0)
              #model: #sizeY
              #type: #number
              #immediateAccept: true
              #acceptOnReturn: true
              #acceptOnTab: true
              #acceptOnLostFocus: true
              #acceptOnPointerLeave: true
            )
           #(#LabelSpec
              #label: '(mm)'
              #name: 'mmLabel'
              #layout: #(#LayoutFrame 491 0 72 0 537 0 94 0)
              #translateLabel: true
              #adjust: #right
            )
           #(#DividerSpec
              #name: 'Separator1'
              #layout: #(#LayoutFrame 0 0.0 105 0 0 1.0 109 0)
            )
           #(#LabelSpec
              #name: 'ScreenDepthVisualLabel'
              #layout: #(#LayoutFrame 0 0.0 113 0.0 0 1.0 135 0)
              #translateLabel: true
              #labelChannel: #screenDepthVisualLabelHolder
              #adjust: #left
            )
           #(#DividerSpec
              #name: 'Separator2'
              #layout: #(#LayoutFrame 0 0.0 139 0 0 1.0 143 0)
            )
           #(#CheckBoxSpec
              #label: 'Color Monitor'
              #name: 'ColorMonitorCheckBox'
              #layout: #(#LayoutFrame 5 0 150 0 250 0 172 0)
              #model: #isColorMonitor
              #translateLabel: true
            )
           #(#CheckBoxSpec
              #label: 'Use Fix Color Palette'
              #name: 'FixColorPaletteCheckBox'
              #layout: #(#LayoutFrame 5 0 175 0 301 0 197 0)
              #enableChannel: #visualIsPseudoColor
              #model: #useFixPalette
              #translateLabel: true
              #labelChannel: #useFixPaletteLabel
            )
           #(#CheckBoxSpec
              #label: 'Use Fix Gray Color Palette'
              #name: 'UseFixGrayPaletteCheckBox'
              #layout: #(#LayoutFrame 5 0 201 0 301 0 223 0)
              #enableChannel: #visualIsPseudoColor
              #model: #useFixGrayPalette
              #translateLabel: true
              #labelChannel: #useFixGrayPaletteLabel
            )
           #(#LabelSpec
              #label: 'Image Display:'
              #name: 'ImageDisplayLabel'
              #layout: #(#LayoutFrame 0 0 230 0 205 0 252 0)
              #translateLabel: true
              #adjust: #right
            )
           #(#PopUpListSpec
              #label: 'image display'
              #name: 'DitherListPopUpList'
              #layout: #(#LayoutFrame 205 0 230 0 -5 1 252 0)
              #tabable: true
              #model: #ditherListSelection
              #enableChannel: #ditherSymsNotNil
              #menu: #ditherList
              #useIndex: true
            )
           #(#CheckBoxSpec
              #label: 'Allow Colored/Grayscale Icons'
              #name: 'AllowColoredGrayscaleIconsCheckBox'
              #layout: #(#LayoutFrame 5 0 262 0 301 0 284 0)
              #model: #deepIcons
              #translateLabel: true
            )
           #(#DividerSpec
              #name: 'Separator3'
              #layout: #(#LayoutFrame 0 0.0 288 0 0 1.0 292 0)
            )
           #(#LabelSpec
              #label: 'ClipBoard Encoding:'
              #name: 'ClipBoardEncodingLabel'
              #layout: #(#LayoutFrame 0 0 303 0 205 0 325 0)
              #translateLabel: true
              #adjust: #right
            )
           #(#PopUpListSpec
              #label: 'image display'
              #name: 'ClipEncodingListPopUpList'
              #layout: #(#LayoutFrame 205 0 303 0 -5 1 325 0)
              #tabable: true
              #model: #clipEncodingListSelection
              #menu: #clipEncodingList
              #useIndex: true
            )
           #(#DividerSpec
              #name: 'Separator4'
              #layout: #(#LayoutFrame 0 0.0 333 0 0 1.0 337 0)
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::DisplaySettingsAppl methodsFor:'actions'!

basicSaveSettings

    Image flushDeviceImages.

    screen visualType == #PseudoColor ifTrue:[
        self useFixPalette value ifTrue:[
            Color colorAllocationFailSignal handle:[:ex |
                self warn:'Could not allocate colors.'.
            ] do:[
                Color getColorsRed:4 green:8 blue:4 on:screen
            ]
        ] ifFalse:[
            screen releaseFixColors
        ].

        self useFixGrayPalette value ifTrue:[
            Color colorAllocationFailSignal handle:[:ex |
                self warn:'Could not allocate colors.'.
            ] do:[
                Color getGrayColors:32 on:screen
            ]
        ] ifFalse:[
            screen releaseFixGrayColors
        ]
    ].
    screen hasColors:self isColorMonitor value.
    screen widthInMillimeter:self sizeX value.
    screen heightInMillimeter:self sizeY value.

    screen supportsDeepIcons:self deepIcons value.
    ditherSyms notNil ifTrue:[
        Image ditherAlgorithm:(ditherSyms at:self ditherListSelection value).
    ].

    WindowGroup activeGroup withWaitCursorDo:[
        View defaultStyle:(View defaultStyle).
    ].

    screen clipBoardEncoding:(self class clipEncodingSyms at:self clipEncodingListSelection value).
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/screenSettings.html'].
!

readSettings
    self useFixPalette value:screen fixColors notNil.
    self useFixGrayPalette value:screen fixGrayColors notNil.
    self isColorMonitor value:screen hasColors.
    self sizeX value:screen widthInMillimeter.
    self sizeY value:screen heightInMillimeter.
    self deepIcons value:screen supportsDeepIcons.
    ditherSyms notNil ifTrue:[
        self ditherListSelection 
            value:(ditherSyms indexOf:(Image ditherAlgorithm) ifAbsent:#threshold)
    ].
    self clipEncodingListSelection 
        value:(self class clipEncodingSyms indexOf:screen clipBoardEncoding
                ifAbsent:1).
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::DisplaySettingsAppl methodsFor:'aspects'!

clipEncodingList

    clipEncodingList isNil ifTrue:[
        clipEncodingList := (resources array:self class clipEncodingStrings) asValue.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       clipEncodingList addDependent:self.
"/       clipEncodingList onChangeSend:#clipEncodingListChanged to:self.
    ].
    ^ clipEncodingList.
!

clipEncodingListSelection

    clipEncodingListSelection isNil ifTrue:[
        clipEncodingListSelection := (self class clipEncodingSyms indexOf:screen clipBoardEncoding ifAbsent:1) asValue.
        clipEncodingListSelection onChangeSend:#evaluateModified to:self.
    ].
    ^ clipEncodingListSelection.
!

deepIcons

    deepIcons isNil ifTrue:[
        deepIcons := screen supportsDeepIcons asValue.
        deepIcons onChangeSend:#evaluateModified to:self.
    ].
    ^ deepIcons.
!

ditherList

    ditherList isNil ifTrue:[
        ditherList := ValueHolder new.
    ].
    ^ ditherList.
!

ditherListSelection

    ditherListSelection isNil ifTrue:[
        ditherSyms notNil ifTrue:[
            ditherListSelection := (ditherSyms indexOf:(Image ditherAlgorithm) ifAbsent:#threshold) asValue.
        ] ifFalse:[
            ditherListSelection := ValueHolder new.
        ].
        ditherListSelection onChangeSend:#evaluateModified to:self.
    ].
    ^ ditherListSelection.
!

ditherSymsNotNil

    ditherSymsNotNil isNil ifTrue:[
        ditherSymsNotNil := ditherSyms notNil asValue.
    ].
    ^ ditherSymsNotNil.
!

isColorMonitor

    isColorMonitor isNil ifTrue:[
        isColorMonitor := screen hasColors asValue.
        isColorMonitor onChangeSend:#evaluateModified to:self.
    ].
    ^ isColorMonitor.
!

monitorList

    monitorList isNil ifTrue:[
        monitorList := (resources array:(sizeInfos collect:[:entry | entry at:1])) asList.
    ].
    ^ monitorList.
!

monitorSelection

    monitorSelection isNil ifTrue:[
        monitorSelection := ValueHolder new.
        monitorSelection addDependent:self.
        monitorSelection onChangeSend:#evaluateModified to:self.
        monitorSelection changed.
    ].
    ^ monitorSelection.
!

screenDepthVisualLabelHolder

    screenDepthVisualLabelHolder isNil ifTrue:[
        screenDepthVisualLabelHolder := (resources string:'Screen: Depth: %1 Visual: %2  (%3)'
                                 with:screen depth printString
                                 with:screen visualType
                                 with:screen serverVendor) asValue.
    ].
    ^ screenDepthVisualLabelHolder.
!

sizeX

    sizeX isNil ifTrue:[
        sizeX := screen widthInMillimeter asValue.
        sizeX addDependent:self.
        sizeX changed.
        sizeX onChangeSend:#evaluateModified to:self.
    ].
    ^ sizeX.
!

sizeY

    sizeY isNil ifTrue:[
        sizeY := screen heightInMillimeter asValue.
        sizeY addDependent:self.
        sizeY changed.
        sizeY onChangeSend:#evaluateModified to:self.
    ].
    ^ sizeY.
!

useFixGrayPalette

    useFixGrayPalette isNil ifTrue:[
        useFixGrayPalette := screen fixGrayColors notNil asValue.
        useFixGrayPalette onChangeSend:#evaluateModified to:self.
    ].
    ^ useFixGrayPalette.
!

useFixGrayPaletteLabel

    useFixGrayPaletteLabel isNil ifTrue:[
        useFixGrayPaletteLabel := (resources string:'Use Fix Gray Color Palette %1' with:'(32)') asValue.
    ].
    ^ useFixGrayPaletteLabel.
!

useFixPalette

    useFixPalette isNil ifTrue:[
        useFixPalette := screen fixColors notNil asValue.
        useFixPalette onChangeSend:#evaluateModified to:self.
    ].
    ^ useFixPalette.
!

useFixPaletteLabel

    useFixPaletteLabel isNil ifTrue:[
        useFixPaletteLabel := (resources string:'Use Fix Color Palette %1' with:'(4x8x4)') asValue.
    ].
    ^ useFixPaletteLabel.
!

visualIsPseudoColor

    visualIsPseudoColor isNil ifTrue:[
        visualIsPseudoColor := (screen visualType == #PseudoColor) asValue.
        visualIsPseudoColor onChangeSend:#evaluateModified to:self.
    ].
    ^ visualIsPseudoColor.
! !

!AbstractSettingsApplication::DisplaySettingsAppl methodsFor:'change & update'!

monitorSelectionChanged

    | sel sizeInfoEntry sizes|

    sel := self monitorSelection value.
    (sel notNil and:[sel ~~ 0]) ifTrue:[
        sizeInfoEntry := sizeInfos at:sel.
        sizes := sizeInfoEntry at:2.
        self sizeX value:(sizes at:1).
        self sizeY value:(sizes at:2).
    ].
!

sizeXorYChanged
    | sizes idx|

    sizes := sizeInfos collect:[:entry | entry at:2].
    idx := sizes findFirst:[:entry |
                                ((entry at:1) = sizeX value)
                                and:[((entry at:2) = sizeY value)]
                           ].
    idx ~~ 0 ifTrue:[
        self monitorSelection value:idx
    ].
!

update:something with:aParameter from:changedObject
    changedObject == self monitorSelection ifTrue:[
        self monitorSelectionChanged.
        ^ self.
    ].
    (changedObject == self sizeX or:[self sizeY]) ifTrue:[
        self sizeXorYChanged.
        ^ self.
    ].

    super update:something with:aParameter from:changedObject
! !

!AbstractSettingsApplication::DisplaySettingsAppl methodsFor:'initialization & release'!

initialize

    | listOfSizes visual|

    screen := Screen current.

    listOfSizes := self class classResources at:'LIST_OF_OFFERED_SCREEN_SIZES' default:#default.
    listOfSizes == #default ifTrue:[
        "/ nothing in resource file; offer at least some.
        sizeInfos := #(
                           ( '11.3'' (235mm x 175mm) LCD'   (235 175)    )
                           ( '17''   (325mm x 245mm)'       (325 245)    )
                           ( '19''   (340mm x 270mm)'       (340 270)    )
                           ( '20''   (350mm x 280mm)'       (350 280)    )
                           ( '21''   (365mm x 285mm)'       (365 285)    )
                       ).
    ] ifFalse:[
        sizeInfos := resources array:listOfSizes.
    ].
    visual := screen visualType.
    (visual == #StaticGray or:[visual == #GrayScale]) ifTrue:[
        ditherStyles := self class staticGrayOrGrayScaleDitherStrings.
        ditherSyms := self class staticGrayOrGrayScaleDitherSyms.
    ] ifFalse:[
        visual ~~ #TrueColor ifTrue:[
            ditherStyles := self class trueColorDitherStrings.
            ditherSyms := self class trueColorDitherSyms.
        ]
    ].
    super initialize.

!

postOpen
!

postOpenAsSubcanvasWith:aBuilder

    self postOpen.
    ^ super postOpenAsSubcanvasWith:aBuilder
!

postOpenWith:aBuilder

    self postOpen.
    ^ super postOpenWith:aBuilder
! !

!AbstractSettingsApplication::DisplaySettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ (
        self useFixPalette value ~= screen fixColors notNil or:[
        self useFixGrayPalette value ~= screen fixGrayColors notNil or:[
        self isColorMonitor value ~= screen hasColors or:[
        self sizeX value ~= screen widthInMillimeter or:[
        self sizeY value ~= screen heightInMillimeter or:[

        self deepIcons value ~= screen supportsDeepIcons or:[
        (ditherSyms notNil and:[
            self ditherListSelection value ~= (ditherSyms indexOf:(Image ditherAlgorithm) ifAbsent:#threshold).
        ]) or:[
        self clipEncodingListSelection value ~= (self class clipEncodingSyms indexOf:screen clipBoardEncoding ifAbsent:1)
        ]]]]]]]
    )
! !

!AbstractSettingsApplication::EditSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::EditSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@JB (JB (JB (JB (JB (@@@TE@@@@B (IBP$IBPXIBP$IBP$IAPTE@0@@
@@(JBP$IBP$FBP$IBP$IAPTE@0L@@@@JB $IBP$IA $IBP$IBPTEAPLC@@@@B (FA XFA XFA XFA TE@0LC@0@@@@(JBP$IBP$FBP$IAPTE@0LC@0P@@@@J
B $IBP$IA $IAPTE@0LC@0PK@@@@B (IBP$IBPXIBPTEAPLC@0LDB0@@@@(JA XFA XFA TH@0LC@0PD@ @@@@@JB $IBP$I@@ HB@LC@0PB@ @@@@@@B (I
BP$IBPXHB@ HB@ K@PD@@@@@@@(JA XFA @HB@ HB@ F@@DA@@@@@@@JB XFA X@B@ HB@ FA @A@P@@@@@@B (IBP$I@P HB@XFA (I@PD@@@@@@@(JBP$I
@PHKA XJBP$IBPDA@@@@@@@JB @@@@D@@@@@@@@@@@@A@P@@@@@@B (@@@D@@@@@@@@@@@@@@PD@@@@@@@(JBP$IBP$@BP$IBP$IBPDA@@@@@@HA@PDA@PDA
@PDA@PDA@PDA@P@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[160 160 160 0 0 0 48 48 48 255 128 0 192 88 0 255 168 88 195 195 195 88 88 88 255 220 168 255 255 255 220 220 220 64 0 0]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@G??LG??<G??<G??<G??<G??<G??<G??<G??8G??0G??0G??0G??0G??0G??0G??0G??0G??0O??0@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Editor Settings'
          #name: 'Editor Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 616 362)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel1'
                    #horizontalLayout: #fit
                    #verticalLayout: #top
                    #horizontalSpace: 3
                    #verticalSpace: 3
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#CheckBoxSpec
                          #label: 'CTRL-Key to Start TextDrag'
                          #name: 'CTRLKeyStTextDragCheckBox'
                          #model: #startTextDragWithControl
                          #translateLabel: true
                          #extent: #(#Point 600 23)
                        )
                       #(#CheckBoxSpec
                          #label: 'SearchBox is Modal'
                          #name: 'SearchBoxModalCheckBox'
                          #model: #searchDialogIsModal
                          #translateLabel: true
                          #extent: #(#Point 600 23)
                        )
                       #(#CheckBoxSpec
                          #label: 'Tab Stops in Multiples of 4'
                          #name: 'TabStopsMultiples4CheckBox'
                          #model: #tabsIs4
                          #translateLabel: true
                          #extent: #(#Point 600 23)
                        )
                       #(#CheckBoxSpec
                          #label: 'Double Click Select Behavior as in ST80'
                          #name: 'DoubleClickSelectBehaviorST80CheckBox'
                          #model: #st80DoubleClickSelectMode
                          #translateLabel: true
                          #extent: #(#Point 600 23)
                        )
                       #(#CheckBoxSpec
                          #label: 'Cursor has ST80 Line-end Behavior'
                          #name: 'CursorST80LineEndBehaviorCheckBox'
                          #model: #st80EditingMode
                          #translateLabel: true
                          #extent: #(#Point 600 23)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 127)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::EditSettingsAppl methodsFor:'actions'!

basicSaveSettings

    UserPreferences current st80EditMode:(self st80EditingMode value).
    TextView st80SelectMode:(self st80DoubleClickSelectMode value).
    tabsIs4 value ~~ (ListView userDefaultTabPositions = ListView tab4Positions) ifTrue:[
        ListView userDefaultTabPositions:(self tabsIs4 value ifTrue:[ListView tab4Positions] ifFalse:[ListView tab8Positions]).
        ListView allSubInstancesDo:[:eachKindOfListView |
            self tabsIs4 value ifTrue:[eachKindOfListView setTab4] ifFalse:[eachKindOfListView setTab8]
        ].
    ].
    UserPreferences current searchDialogIsModal:self searchDialogIsModal value.
    UserPreferences current startTextDragWithControl:self startTextDragWithControl value.
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/editSettings.html'].
!

readSettings
    self st80EditingMode value:UserPreferences current st80EditMode.
    self st80DoubleClickSelectMode value:TextView st80SelectMode.
    self tabsIs4 
        value:(ListView userDefaultTabPositions = ListView tab4Positions).
    self searchDialogIsModal 
        value:UserPreferences current searchDialogIsModal.
    self startTextDragWithControl 
        value:UserPreferences current startTextDragWithControl.
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::EditSettingsAppl methodsFor:'aspects'!

searchDialogIsModal

    searchDialogIsModal isNil ifTrue:[
        searchDialogIsModal := true asValue.
        searchDialogIsModal onChangeSend:#evaluateModified to:self.
    ].
    ^ searchDialogIsModal.
!

st80DoubleClickSelectMode

    st80DoubleClickSelectMode isNil ifTrue:[
        st80DoubleClickSelectMode := true asValue.
        st80DoubleClickSelectMode onChangeSend:#evaluateModified to:self.
    ].
    ^ st80DoubleClickSelectMode.
!

st80EditingMode

    st80EditingMode isNil ifTrue:[
        st80EditingMode := true asValue.
        st80EditingMode onChangeSend:#evaluateModified to:self.
    ].
    ^ st80EditingMode.
!

startTextDragWithControl

    startTextDragWithControl isNil ifTrue:[
        startTextDragWithControl := true asValue.
        startTextDragWithControl onChangeSend:#evaluateModified to:self.
    ].
    ^ startTextDragWithControl.
!

tabsIs4

    tabsIs4 isNil ifTrue:[
        tabsIs4 := true asValue.
        tabsIs4 onChangeSend:#evaluateModified to:self.
    ].
    ^ tabsIs4.
! !

!AbstractSettingsApplication::EditSettingsAppl methodsFor:'initialization & release'!

postOpen
!

postOpenAsSubcanvasWith:aBuilder

    self postOpen.
    ^ super postOpenAsSubcanvasWith:aBuilder
!

postOpenWith:aBuilder

    self postOpen.
    ^ super postOpenWith:aBuilder
! !

!AbstractSettingsApplication::EditSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ (
        UserPreferences current st80EditMode ~= (self st80EditingMode value) or:[
        TextView st80SelectMode ~= (self st80DoubleClickSelectMode value) or:[
        (tabsIs4 value ~~ (ListView userDefaultTabPositions = ListView tab4Positions) and:[
            ListView userDefaultTabPositions ~= (self tabsIs4 value ifTrue:[ListView tab4Positions] ifFalse:[ListView tab8Positions]) or:[
        ]]) or:[
        UserPreferences current searchDialogIsModal ~= self searchDialogIsModal value or:[
        UserPreferences current startTextDragWithControl ~= self startTextDragWithControl value ]]]]
    )
! !

!AbstractSettingsApplication::FontSettingsAppl class methodsFor:'defaults'!

widgetList

    ^  #(
        'All' 
        'Labels' 
        'Buttons' 
        'Lists' 
        'Menus' 
        'Edited Text'
       )
! !

!AbstractSettingsApplication::FontSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::FontSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth4Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@!!X @@@@@@@!!X @@@6H@@@@@@DP6H@@@Y!!H@@@@@QDY"@@@BY"@@@@ADQBY"@@@FX @@@@@DQCX @@@6H@@@@@QEP6H@@@@ @@@@
ADUDP @C@@@@@@@DQSH@@@L @@@@@@QEL @@@2@@@@@@ADT2@@@CH@@@@@@DQSH@@@L @@@@@@QEL @@@2@@@@@@QDT2@@@CH@@@@@QDQSH@@@@ @@@@@DQE
P @@@@@@@@@@@DQ@@@@@@@@@@@@@@D@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 255 255 150 150 150 213 213 213 215 48 48 134 54 54 240 240 240]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@G @OG0@O''<@O7>@O<?@A>? A?? A??@A<?@A<>@A<>@A<>@A=>@C?>@G<>@C<\@@8D@@H@@@@@@@@@@@@@@') ; yourself); yourself]
!

defaultIcon2
    "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 defaultIcon2 inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon2
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::FontSettingsAppl class defaultIcon2'
        ifAbsentPut:[(Depth4Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@!!X @@@@@@@!!X @@@6H@@@@@@DP6H@@@Y!!H@@@@@QDY"@@@BY"@@@@ADQBY"@@@FX @@@@@DQCX @@@6H@@@@@QEP6H@@@@ @@@@
ADUDP @C@@@@@@@DQSH@@@L @@@@@@QEL @@@2@@@@@@ADT2@@@CH@@@@@@DQSH@@@L @@@@@@QEL @@@2@@@@@@QDT2@@@CH@@@@@QDQSH@@@@ @@@@@DQE
P @@@@@@@@@@@DQ@@@@@@@@@@@@@@D@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 255 255 150 150 150 213 213 213 215 48 48 134 54 54 240 240 240]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@G @OG0@O''<@O7>@O<?@A>? A?? A??@A<?@A<>@A<>@A<>@A=>@C?>@G<>@C<\@@8D@@H@@@@@@@@@@@@@@') ; yourself); yourself]
! !

!AbstractSettingsApplication::FontSettingsAppl class methodsFor:'instance creation'!

fontForEncoding:encodingMatch

    | inst |

    inst := self new.
    inst encodingMatch:encodingMatch.
    self initialize.
    self open.
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Font Settings'
          #name: 'Font Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 46 512 658)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel1'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fitSpace
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#ViewSpec
                    #name: 'AllBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'All (Others)'
                          #name: 'All'
                          #layout: #(#LayoutFrame 0 0.0 0 0 100 0 20 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#LabelSpec
                          #label: 'Label'
                          #name: 'AllFont'
                          #layout: #(#LayoutFrame 105 0 22 0 -5 1 44 0)
                          #translateLabel: true
                          #labelChannel: #allFontLabelHolder
                          #adjust: #left
                          #postBuildCallback: #postBuildAllFontLabel:
                        )
                       #(#ActionButtonSpec
                          #label: 'Change ...'
                          #name: 'ChangeAll'
                          #layout: #(#LayoutFrame 0 0.0 22 0 105 0 44 0)
                          #translateLabel: true
                          #model: #changeAllFont
                        )
                       #(#DividerSpec
                          #name: 'Separator1'
                          #layout: #(#LayoutFrame 0 0.0 -3 1 0 1.0 0 1)
                        )
                       )
                     
                    )
                    #extent: #(#Point 490 50)
                  )
                 #(#ViewSpec
                    #name: 'LabelsBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Labels'
                          #name: 'Labels'
                          #layout: #(#LayoutFrame 0 0.0 0 0 100 0 20 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#LabelSpec
                          #label: 'Labels'
                          #name: 'LabelsFont'
                          #layout: #(#LayoutFrame 105 0 22 0 -5 1 44 0)
                          #translateLabel: true
                          #labelChannel: #labelsFontLabelHolder
                          #adjust: #left
                          #postBuildCallback: #postBuildLabelsFontLabel:
                        )
                       #(#ActionButtonSpec
                          #label: 'Change ...'
                          #name: 'ChangeLabels'
                          #layout: #(#LayoutFrame 0 0.0 22 0 105 0 44 0)
                          #translateLabel: true
                          #model: #changeLabelsFont
                        )
                       #(#DividerSpec
                          #name: 'Separator6'
                          #layout: #(#LayoutFrame 0 0.0 -3 1 0 1.0 0 1)
                        )
                       )
                     
                    )
                    #extent: #(#Point 490 50)
                  )
                 #(#ViewSpec
                    #name: 'ButtonsBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Buttons'
                          #name: 'Buttons'
                          #layout: #(#LayoutFrame 0 0.0 0 0 100 0 20 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#LabelSpec
                          #label: 'Buttons Font'
                          #name: 'ButtonsFont'
                          #layout: #(#LayoutFrame 105 0 22 0 -5 1 44 0)
                          #translateLabel: true
                          #labelChannel: #buttonsFontLabelHolder
                          #adjust: #left
                          #postBuildCallback: #postBuildButtonsFontLabel:
                        )
                       #(#ActionButtonSpec
                          #label: 'Change ...'
                          #name: 'Change Buttons'
                          #layout: #(#LayoutFrame 0 0.0 22 0 105 0 44 0)
                          #translateLabel: true
                          #model: #changeButtonsFont
                        )
                       #(#DividerSpec
                          #name: 'Separator7'
                          #layout: #(#LayoutFrame 0 0.0 -3 1 0 1.0 0 1)
                        )
                       )
                     
                    )
                    #extent: #(#Point 490 50)
                  )
                 #(#ViewSpec
                    #name: 'ListsBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Lists'
                          #name: 'Lists'
                          #layout: #(#LayoutFrame 0 0.0 0 0 100 0 20 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#LabelSpec
                          #label: 'Lists Font'
                          #name: 'ListsFont'
                          #layout: #(#LayoutFrame 105 0 22 0 -5 1 44 0)
                          #translateLabel: true
                          #labelChannel: #listsFontLabelHolder
                          #adjust: #left
                          #postBuildCallback: #postBuildListsFontLabel:
                        )
                       #(#ActionButtonSpec
                          #label: 'Change ...'
                          #name: 'ChangeLists'
                          #layout: #(#LayoutFrame 0 0.0 22 0 105 0 44 0)
                          #translateLabel: true
                          #model: #changeListsFont
                        )
                       #(#DividerSpec
                          #name: 'Separator8'
                          #layout: #(#LayoutFrame 0 0.0 -3 1 0 1.0 0 1)
                        )
                       )
                     
                    )
                    #extent: #(#Point 490 50)
                  )
                 #(#ViewSpec
                    #name: 'MenusBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Menus'
                          #name: 'Menus'
                          #layout: #(#LayoutFrame 0 0.0 0 0 100 0 20 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#LabelSpec
                          #label: 'Menus Font'
                          #name: 'MenusFont'
                          #layout: #(#LayoutFrame 105 0 22 0 -5 1 44 0)
                          #translateLabel: true
                          #labelChannel: #menusFontLabelHolder
                          #adjust: #left
                          #postBuildCallback: #postBuildMenuesFontLabel:
                        )
                       #(#ActionButtonSpec
                          #label: 'Change ...'
                          #name: 'ChangeMenus'
                          #layout: #(#LayoutFrame 0 0.0 22 0 105 0 44 0)
                          #translateLabel: true
                          #model: #changeMenusFont
                        )
                       #(#DividerSpec
                          #name: 'Separator9'
                          #layout: #(#LayoutFrame 0 0.0 -3 1 0 1.0 0 1)
                        )
                       )
                     
                    )
                    #extent: #(#Point 490 50)
                  )
                 #(#ViewSpec
                    #name: 'TextBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Text'
                          #name: 'Text'
                          #layout: #(#LayoutFrame 0 0.0 0 0 100 0 20 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#LabelSpec
                          #label: 'Text Font'
                          #name: 'TextFont'
                          #layout: #(#LayoutFrame 105 0 22 0 -5 1 44 0)
                          #translateLabel: true
                          #labelChannel: #textFontLabelHolder
                          #adjust: #left
                          #postBuildCallback: #postBuildTextFontLabel:
                        )
                       #(#ActionButtonSpec
                          #label: 'Change ...'
                          #name: 'ChangeText'
                          #layout: #(#LayoutFrame 0 0.0 22 0 105 0 44 0)
                          #translateLabel: true
                          #model: #changeTextFont
                        )
                       #(#DividerSpec
                          #name: 'Separator10'
                          #layout: #(#LayoutFrame 0 0.0 -3 1 0 1.0 0 1)
                        )
                       )
                     
                    )
                    #extent: #(#Point 490 50)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::FontSettingsAppl methodsFor:'accessing'!

encodingMatch:aEncodingMatch

    aEncodingMatch notNil ifTrue:[
        filter := [:f | f encoding notNil 
                        and:[aEncodingMatch match:f encoding]].
    ].
! !

!AbstractSettingsApplication::FontSettingsAppl methodsFor:'actions'!

basicSaveSettings

    Label defaultFont:self labelDef value.
    Button defaultFont:self buttonDef value.
    Toggle defaultFont:self buttonDef value.
    TextView withAllSubclasses do:[:cls | cls defaultFont:self textDef value].
    SelectionInListView withAllSubclasses do:[:cls | cls defaultFont:self listDef value].
    MenuView defaultFont:self menuDef value.
    PullDownMenu defaultFont:self menuDef value.
!

changeAllFont
    |f|

    f := FontPanel 
        fontFromUserInitial:(self allOfThem value) 
                      title:(resources string:'Font for %1' with:'All')
                     filter:filter.
    f notNil ifTrue:[
        self allOfThem value:(f onDevice:allLabel device).
        self labelDef value:(f onDevice:labelLabel device).
        self buttonDef value:(f onDevice:buttonsLabel device).
        self listDef value:(f onDevice:listsLabel device).
        self menuDef value:(f onDevice:menuLabel device).
        self textDef value:(f onDevice:textLabel device).
    ]
!

changeButtonsFont

    |f|

    f := FontPanel 
        fontFromUserInitial:(self buttonDef value) 
                      title:(resources string:'Font for %1' with:'All')
                     filter:filter.
    f notNil ifTrue:[
        self buttonDef value:(f onDevice:buttonsLabel device).
    ]
!

changeLabelsFont
    |f |

    f := FontPanel 
        fontFromUserInitial:(self labelDef value) 
                      title:(resources string:'Font for %1' with:'Labels')
                     filter:filter.
    f notNil ifTrue:[
        self labelDef value:(f onDevice:labelLabel device).
    ].
!

changeListsFont
    |f|

    f := FontPanel 
        fontFromUserInitial:(self listDef value) 
                      title:(resources string:'Font for %1' with:'Lists')
                     filter:filter.
    f notNil ifTrue:[
        self listDef value:(f onDevice:listsLabel device).
    ]
!

changeMenusFont
    |f|

    f := FontPanel 
        fontFromUserInitial:(self menuDef value) 
                      title:(resources string:'Font for %1' with:'Menus')
                     filter:filter.
    f notNil ifTrue:[
        self menuDef value:(f onDevice:menuLabel device).
    ]
!

changeTextFont
    |f|

    f := FontPanel 
        fontFromUserInitial:(self textDef value) 
                      title:(resources string:'Font for %1' with:'Edited Text')
                     filter:filter.
    f notNil ifTrue:[
        self textDef value:(f onDevice:textLabel device).
    ]
!

help

    self warn:'no help available here'.
"/    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/keyboardSetting.html'].
!

readSettings
    View readStyleSheetAndUpdateAllStyleCaches.
    self labelDef value:Label defaultFont.
    self buttonDef value:Button defaultFont.
    self listDef value:SelectionInListView defaultFont.
    self menuDef value:MenuView defaultFont.
    self textDef value:TextView defaultFont.
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::FontSettingsAppl methodsFor:'aspects'!

allFontLabelHolder

    allFontLabelHolder isNil ifTrue:[
        allFontLabelHolder := '' asValue.
    ].
    ^ allFontLabelHolder.
!

allOfThem
    "return/create the 'allOfThem' value holder (automatically generated)"

    allOfThem isNil ifTrue:[
        allOfThem := ValueHolder new.
        allOfThem addDependent:self.
    ].
    ^ allOfThem
!

buttonDef
    "return/create the 'buttonDef' value holder (automatically generated)"

    buttonDef isNil ifTrue:[
        buttonDef := ValueHolder new.
        buttonDef addDependent:self.
    ].
    ^ buttonDef
!

buttonsFontLabelHolder

    buttonsFontLabelHolder isNil ifTrue:[
        buttonsFontLabelHolder := '' asValue.
    ].
    ^ buttonsFontLabelHolder.
!

labelDef
    "return/create the 'labelDef' value holder (automatically generated)"

    labelDef isNil ifTrue:[
        labelDef := ValueHolder new.
        labelDef addDependent:self.
    ].
    ^ labelDef
!

labelsFontLabelHolder

    labelsFontLabelHolder isNil ifTrue:[
        labelsFontLabelHolder := '' asValue.
    ].
    ^ labelsFontLabelHolder.
!

listDef
    "return/create the 'listDef' value holder (automatically generated)"

    listDef isNil ifTrue:[
        listDef := ValueHolder new.
        listDef addDependent:self.
    ].
    ^ listDef
!

listsFontLabelHolder

    listsFontLabelHolder isNil ifTrue:[
        listsFontLabelHolder := '' asValue.
    ].
    ^ listsFontLabelHolder.
!

menuDef
    "return/create the 'menuDef' value holder (automatically generated)"

    menuDef isNil ifTrue:[
        menuDef := ValueHolder new.
        menuDef addDependent:self.
    ].
    ^ menuDef
!

menusFontLabelHolder

    menusFontLabelHolder isNil ifTrue:[
        menusFontLabelHolder := '' asValue.
    ].
    ^ menusFontLabelHolder.
!

textDef
    "return/create the 'textDef' value holder (automatically generated)"

    textDef isNil ifTrue:[
        textDef := ValueHolder new.
        textDef addDependent:self.
    ].
    ^ textDef
!

textFontLabelHolder

    textFontLabelHolder isNil ifTrue:[
        textFontLabelHolder := '' asValue.
    ].
    ^ textFontLabelHolder.
! !

!AbstractSettingsApplication::FontSettingsAppl methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    builder notNil ifTrue:[
        changedObject == self allOfThem ifTrue:[
            self updateFontOfLabel:allLabel andFontNameHolder:(self allFontLabelHolder) from:changedObject.
            ^ self.
        ].
        changedObject == self labelDef ifTrue:[
            self updateFontOfLabel:labelLabel andFontNameHolder:(self labelsFontLabelHolder) from:changedObject.
            ^ self.
        ].
        changedObject == self buttonDef ifTrue:[
            self updateFontOfLabel:buttonsLabel andFontNameHolder:(self buttonsFontLabelHolder) from:changedObject.
            ^ self.
        ].
        changedObject == self listDef ifTrue:[
            self updateFontOfLabel:listsLabel andFontNameHolder:(self listsFontLabelHolder) from:changedObject.
            ^ self.
        ].
        changedObject == self menuDef ifTrue:[
            self updateFontOfLabel:menuLabel andFontNameHolder:(self menusFontLabelHolder) from:changedObject.
            ^ self.
        ].
        changedObject == self textDef ifTrue:[
            self updateFontOfLabel:textLabel andFontNameHolder:(self textFontLabelHolder) from:changedObject.
            ^ self.
        ].
    ].
    super update:something with:aParameter from:changedObject
!

updateAllFontLabels
    self update:#value with:nil from:self allOfThem.
    self update:#value with:nil from:self labelDef.
    self update:#value with:nil from:self buttonDef.
    self update:#value with:nil from:self listDef.
    self update:#value with:nil from:self menuDef.
    self update:#value with:nil from:self textDef.
!

updateFontOfLabel:labelWidget andFontNameHolder:fontNameHolder from:changedObject 
    | f label|

    f := changedObject value.

    labelWidget font:f.
    label := f isNil ifTrue:[
        ''
    ] ifFalse:[
        f userFriendlyName
    ].
    fontNameHolder value:label.
    self evaluateModified.
! !

!AbstractSettingsApplication::FontSettingsAppl methodsFor:'initialization & release'!

postBuildAllFontLabel:aWidget

    allLabel := aWidget.
!

postBuildButtonsFontLabel:aWidget

    buttonsLabel := aWidget.
!

postBuildLabelsFontLabel:aWidget

    labelLabel := aWidget.
!

postBuildListsFontLabel:aWidget

    listsLabel := aWidget.
!

postBuildMenuesFontLabel:aWidget

    menuLabel := aWidget.
!

postBuildTextFontLabel:aWidget

    textLabel := aWidget.
!

postBuildWith:aBuilder 
"/    self readSettings.
    self updateAllFontLabels.
    super postBuildWith:aBuilder
! !

!AbstractSettingsApplication::FontSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ (self labelDef value ~= Label defaultFont) or:[
       self buttonDef value ~= Button defaultFont or:[
       self listDef value ~= SelectionInListView defaultFont or:[
       self menuDef value ~= MenuView defaultFont or:[
       self textDef value ~= TextView defaultFont ]]]]
! !

!AbstractSettingsApplication::GeneralCompilerSettingsAppl class methodsFor:'defaults'!

keepSourceOptions

    ^ #( keep reference absReference sourceReference discard )
!

keepSourceStrings

    ^ #('Keep as String' 'Reference to Filename' 'Reference to Full Path' 'Append and Ref in `st.src''' 'Discard' )
! !

!AbstractSettingsApplication::GeneralCompilerSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::GeneralCompilerSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@H@@@@@@@@@@@@@@@@@@@@@@@@@@@@B@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@H@
@@DA@PD@@PDA@@DA@PD@@PDA@@@B@@@A@PDA@@DA@P@A@PDA@@DA@P@@@ @@@P@@@P@A@@D@@P@@@P@A@@D@@@H@@@DA@PD@@PDA@@DA@PD@@PDA@@@B@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@ @@@PDA@PDA@PDA@PDA@PDA@PD@@@H@@@DA@P@@@@@A@PD@@@@A@PDA@@@B@@@A@PD@@PDA@@D@@PDA@@DA@P@@@ @@@PDA
@@DA@P@A@@DA@PDA@PD@@@H@@@DA@P@@@@@A@P@A@PDA@PDA@@@B@@@A@PD@@PDA@@D@@PDA@PDA@P@@@ @@@PDA@@DA@P@A@@DA@P@A@PD@@@H@@@DA@P@@
@@@A@PD@@@@A@PDA@@@B@@@A@PDA@PDA@PDA@PDA@PDA@P@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 255 255 255 0 0 0]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8@@@@@@@@@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'General Compiler Settings'
          #name: 'General Compiler Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 616 362)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#CheckBoxSpec
                    #label: 'Catch Method Redefinitions'
                    #name: 'CatchMethodRedefinitions'
                    #model: #catchMethodRedefs
                    #translateLabel: true
                    #extent: #(#Point 600 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Catch Class Redefinitions'
                    #name: 'CatchClassRedefinitions'
                    #model: #catchClassRedefs
                    #translateLabel: true
                    #extent: #(#Point 600 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Keep History Line in Methods'
                    #name: 'KeepHistoryLineinMethods'
                    #model: #historyLines
                    #translateLabel: true
                    #extent: #(#Point 600 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Keep Full Class History'
                    #name: 'KeepFullClassHistory'
                    #enableChannel: #hasHistoryManager
                    #model: #fullHistoryUpdate
                    #translateLabel: true
                    #extent: #(#Point 600 25)
                  )
                 #(#ViewSpec
                    #name: 'Box1'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#PopUpListSpec
                          #label: 'PopUp List'
                          #name: 'KeepSourceSelection'
                          #layout: #(#LayoutFrame 200 0 0 0 -5 1 22 0)
                          #tabable: true
                          #model: #keepSourceSelection
                          #menu: #keepSource
                          #useIndex: true
                        )
                       #(#LabelSpec
                          #label: 'FileIn Source Mode:'
                          #name: 'FileInSourceModeLabel'
                          #layout: #(#LayoutFrame 0 0 0 0 200 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 30)
                  )
                 #(#DividerSpec
                    #name: 'Separator1'
                    #extent: #(#Point 600 3)
                  )
                 #(#CheckBoxSpec
                    #label: 'If Present, Load Binary Objects when Autoloading'
                    #name: 'LoadBinaryObjectsWhenAutoloading'
                    #enableChannel: #canLoadBinaries
                    #model: #loadBinaries
                    #translateLabel: true
                    #extent: #(#Point 600 25)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::GeneralCompilerSettingsAppl methodsFor:'actions'!

basicSaveSettings

    ClassCategoryReader sourceMode:(self class keepSourceOptions at:self keepSourceSelection value).
    Class catchClassRedefinitions:self catchClassRedefs value.
    Class catchMethodRedefinitions:self catchMethodRedefs value.
    HistoryManager notNil ifTrue:[
        HistoryManager fullHistoryUpdate:self fullHistoryUpdate value.
        self historyLines value ifTrue:[
            HistoryManager activate
        ] ifFalse:[
            HistoryManager deactivate
        ].
    ].
    Smalltalk loadBinaries:self loadBinaries value.
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/compilerSettings.html'].
!

readSettings
    self keepSourceSelection value:(self class keepSourceOptions 
                indexOf:ClassCategoryReader sourceMode
                ifAbsent:1).
    self catchClassRedefs value:(Class catchClassRedefinitions ? false).
    self catchMethodRedefs value:(Class catchMethodRedefinitions ? false).
    self canLoadBinaries ifTrue:[
        self loadBinaries value:Smalltalk loadBinaries
    ] ifFalse:[
        self loadBinaries value:false
    ].
    self hasHistoryManager ifTrue:[
        self fullHistoryUpdate value:(HistoryManager fullHistoryUpdate ? false)
    ] ifFalse:[
        self fullHistoryUpdate value:false
    ].
    self historyLines value:self hasHistoryManager.
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::GeneralCompilerSettingsAppl methodsFor:'aspects'!

canLoadBinaries

    canLoadBinaries isNil ifTrue:[
        canLoadBinaries := (ObjectFileLoader notNil and:[ObjectFileLoader canLoadObjectFiles]) asValue.
    ].
    ^ canLoadBinaries.
!

catchClassRedefs

    catchClassRedefs isNil ifTrue:[
        catchClassRedefs := (Class catchClassRedefinitions ? false) asValue.
        catchClassRedefs onChangeSend:#evaluateModified to:self.
    ].
    ^ catchClassRedefs.
!

catchMethodRedefs

    catchMethodRedefs isNil ifTrue:[
        catchMethodRedefs := (Class catchMethodRedefinitions ? false) asValue.
        catchMethodRedefs onChangeSend:#evaluateModified to:self.
    ].
    ^ catchMethodRedefs.
!

fullHistoryUpdate

    fullHistoryUpdate isNil ifTrue:[
        self hasHistoryManager ifTrue:[
            fullHistoryUpdate := (HistoryManager fullHistoryUpdate ? false) asValue.
        ] ifFalse:[
            fullHistoryUpdate := false asValue.
        ].
        fullHistoryUpdate onChangeSend:#evaluateModified to:self.
    ].
    ^ fullHistoryUpdate.
!

hasHistoryManager

    ^ HistoryManager notNil and:[HistoryManager isLoaded and:[HistoryManager isActive]]
!

historyLines

    historyLines isNil ifTrue:[
        historyLines := self hasHistoryManager asValue.
        historyLines onChangeSend:#evaluateModified to:self.
    ].
    ^ historyLines.
!

keepSource

    keepSource isNil ifTrue:[
        keepSource := (resources array:(self class keepSourceStrings)) asList.
    ].
    ^ keepSource.
!

keepSourceSelection

    keepSourceSelection isNil ifTrue:[
        keepSourceSelection := (self class keepSourceOptions indexOf:ClassCategoryReader sourceMode ifAbsent:1) asValue.
        keepSourceSelection onChangeSend:#evaluateModified to:self.
    ].
    ^ keepSourceSelection.
!

loadBinaries

    loadBinaries isNil ifTrue:[
        self canLoadBinaries ifTrue:[ 
            loadBinaries:=  Smalltalk loadBinaries asValue
        ] ifFalse:[
            loadBinaries:=  false asValue
        ].
        loadBinaries onChangeSend:#evaluateModified to:self.
    ].
    ^ loadBinaries.
! !

!AbstractSettingsApplication::GeneralCompilerSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ ( 
        ((HistoryManager fullHistoryUpdate ? false) ~= self fullHistoryUpdate value) or:[
        ((ClassCategoryReader sourceMode) ~= (self class keepSourceOptions at:self keepSourceSelection value)) or:[
        ((Class catchMethodRedefinitions ? false) ~= self catchMethodRedefs value) or:[
        ((Class catchClassRedefinitions ? false) ~= self catchClassRedefs value) or:[
        ((Smalltalk loadBinaries ? false) ~= self loadBinaries value) or:[
        ((self hasHistoryManager) ~= self historyLines value) 
        ]]]]]
    )
! !

!AbstractSettingsApplication::HTTPStartServerSettingsApplication class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/AbstractSettingsApplication.st,v 1.59 2003-04-29 10:07:20 penk Exp $'
! !

!AbstractSettingsApplication::HTTPStartServerSettingsApplication class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'HTTPStartServerSettingsApplication class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@HQ-M!!T6M&5-\@@@@@@@@@@@@@@@@GT4HB,1DS$9NUQ0@@@@@@@@@@@@@F<3JP\MG X9NSL9RG@@@@@@@@@@@GT2GQ\C@0LIJ%L3O11J\@@@@@@@(XP4
LA$C@0LCAA<''F"8,F4V3@KT@+0A-JCD]@0LCNT-MSEAPS49V$7L@@@@@MQ@XFPLCNE!!XVE!!XVE!!XVE!!X@@@@@AT$APLC@5"9-K6?1LSD1LFJQ@@@@@@KEBT&
CPMX**R-+Z2+(JZX\DP@@@@@@RL1LR,NVJ8:.K"7-%&I%GAD@@@@@D$OK3D1HU"[%IRT%IRT%I]0Q@@@@@A=@!!L1KQYX*J"(*J"(.8:T\DP@@@@@)THRLQ$C
VJ"(*J"(*IBO%''AD@@@@@@B:P2HL@5"K"8.K"8.K"8M0Q@@@@@@@@J]FB@MX0K0:N#(:N,B2\DP@@@@@@@@@,T\;VJ#B0<OC0<N>&GAD@@@@@@@@@@@@*U"(
0<OC0<OC0I!!0Q@@@@@@@@@@@@@AX*LU<#HVF$,BX\DP@@@@@@@@@@@@@VJ#C@@@@@@CC&GAD@@@@@@@@@@@@@E"(''92\''I2\(9!!0Q@@@@@@@@@@@@@AX*IVO
#8>O#9*X\DP@@@@@@@@@@@@@VJ!!>&Y:B"I:M&GAD@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 0 80 0 0 159 0 0 255 0 2 253 0 7 248 0 8 235 0 8 247 0 14 223 0 16 239 0 20 55 0 20 60 0 32 223 0 35 220 0 47 207 0 50 205 0 60 195 0 64 175 0 64 181 0 64 191 0 74 181 0 80 0 0 87 167 0 90 164 0 92 163 0 97 157 0 102 142 0 103 133 0 107 112 0 111 143 0 114 140 0 115 139 0 127 79 0 127 127 0 150 76 0 159 95 0 165 89 0 184 71 0 191 64 0 200 33 0 207 0 0 208 45 0 213 0 0 225 30 0 235 20 0 240 15 0 243 0 0 244 11 0 245 8 0 255 0 6 132 42 6 168 6 10 149 10 17 41 72 17 96 17 25 25 25 25 25 232 28 28 227 30 30 30 33 32 152 35 35 35 35 35 133 40 40 40 42 131 42 45 45 45 50 50 50 51 51 111 51 55 105 52 52 52 54 60 76 54 116 54 60 60 88 60 60 103 62 61 141 62 62 125 65 64 193 65 104 153 65 112 145 65 136 121 65 160 97 65 192 65 68 68 68 71 111 71 76 121 76 77 76 205 80 80 80 85 100 85 95 95 95 97 97 97 98 207 98 103 103 103 104 104 104 107 105 186 107 106 235 109 108 236 109 109 109 111 109 147 111 111 111 111 111 255 114 113 162 114 114 210 116 116 116 117 117 117 118 116 165 118 117 245 118 118 118 119 117 158 119 119 119 120 120 120 120 159 120 127 127 127 130 146 130 131 129 131 132 131 191 135 135 135 136 135 136 138 138 246 142 142 142 143 143 143 143 143 255 147 145 147 147 146 174 147 146 227 150 148 230 151 149 151 151 151 151 153 150 153 155 153 155 156 154 156 156 155 240 157 156 157 159 157 86 159 159 159 162 160 162 162 161 162 162 162 242 163 161 163 164 163 164 165 164 165 166 164 76 166 164 166 168 165 168 168 166 168 172 169 172 173 170 173 173 171 222 174 172 174 175 174 175 176 173 176 178 175 178 181 178 181 182 179 182 184 181 184 184 182 184 186 183 186 187 184 187 187 187 251 188 186 188 189 188 189 189 188 237 189 197 189 190 190 190 191 189 191 192 191 220 194 192 194 194 194 194 195 193 195 196 196 196 197 194 197 197 197 197 198 195 198 200 191 194 200 192 195 200 197 200 201 199 201 202 202 202 203 202 203 204 204 204 205 203 205 206 206 206 207 204 207 207 207 207 208 147 148 208 157 158 208 207 208 211 208 211 211 211 211 214 213 214 215 213 224 217 215 217 218 217 218 219 217 219 222 220 222 223 222 223 224 223 229 228 227 236 229 228 229 233 232 233]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'C? @G?0@O?8@_?<D??>(???@???@???@???@???@???@???@???@_??@O??@G??@A??@@??@@??@@??@@??@@??@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'HTTP Server Settings'
          #name: 'HTTP Server Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 2048 1024)
          #bounds: #(#Rectangle 16 42 555 672)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel1'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #top
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel4'
                    #horizontalLayout: #fit
                    #verticalLayout: #topSpace
                    #horizontalSpace: 3
                    #verticalSpace: 3
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#ViewSpec
                          #name: 'Box19'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#LabelSpec
                                #label: 'Label'
                                #name: 'Label2'
                                #layout: #(#LayoutFrame 5 0.0 0 0.0 -5 1 0 1.0)
                                #translateLabel: true
                                #labelChannel: #informationLabel
                                #resizeForLabel: false
                                #adjust: #left
                              )
                             )
                           
                          )
                          #extent: #(#Point 539 200)
                        )
                       #(#ViewSpec
                          #name: 'Box18'
                          #extent: #(#Point 539 20)
                        )
                       #(#ViewSpec
                          #name: 'Box17'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#LabelSpec
                                #label: 'Port:'
                                #name: 'Label1'
                                #layout: #(#LayoutFrame 3 0 21 0 40 0 43 0)
                                #translateLabel: true
                                #adjust: #right
                              )
                             #(#InputFieldSpec
                                #name: 'EntryField1'
                                #layout: #(#LayoutFrame 40 0 20 0 100 0 42 0)
                                #model: #portNumberChannel
                                #type: #number
                                #immediateAccept: true
                                #acceptOnReturn: true
                                #acceptOnTab: true
                                #acceptOnLostFocus: true
                                #acceptOnPointerLeave: false
                              )
                             #(#ActionButtonSpec
                                #label: 'Create new HTTP Server'
                                #name: 'Button4'
                                #layout: #(#LayoutFrame 125 0 20 0 -5 1 42 0)
                                #translateLabel: true
                                #model: #createServer
                              )
                             #(#ActionButtonSpec
                                #label: 'Remove all HTTP Servers'
                                #name: 'Button5'
                                #layout: #(#LayoutFrame 125 0 51 0 -5 1 73 0)
                                #translateLabel: true
                                #model: #removeAllServer
                                #enableChannel: #hasCreatedServerChannel
                              )
                             )
                           
                          )
                          #extent: #(#Point 539 90)
                        )
                       )
                     
                    )
                    #extent: #(#Point 539 620)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::HTTPStartServerSettingsApplication methodsFor:'actions'!

basicSaveSettings

    ^ self
!

createServer

    | newServer port runningServers|

    port := self portNumberChannel value.
    runningServers := HTTPServer runningServers.
    runningServers notEmpty ifTrue:[
        runningServers do:[:aServer |
            aServer port = port asInteger ifTrue:[
                Dialog warn:'There is already a Server for port ', port asString.
                ^ self
            ]
        ]
    ].
    self withWaitCursorDo:[
        newServer := HTTPServer new.
        newServer port:port.
        newServer setupDefaults.
        self createServerApplication:newServer forDefault:false.
    ]
!

createServerApplication:aServerInstance

    self createServerApplication:aServerInstance forDefault:false.
!

createServerApplication:aServerInstance forDefault:isDefaultApplication


    |settingsApp settingsAppPosition newItem openApps|

    openApps := self requestor getAllChildrenAppsForApplication:self childrenClass:HTTPServerSettingsAppl.
    ((openApps detect:[:app | app httpServerInstance == aServerInstance] ifNone:[nil]) notNil) ifTrue:[
        " already have an Item for this application "
        ^ self 
    ].
    settingsApp := HTTPServerSettingsAppl basicNew.
    settingsApp requestor:self requestor.
    isDefaultApplication ifTrue:[
        settingsApp isDefaultSettingsDialog:isDefaultApplication
    ] ifFalse:[
        settingsApp httpServerInstance:aServerInstance.
    ].
    settingsApp basicInitialize.
    settingsAppPosition := requestor getNameOfApplication:self.
    isDefaultApplication ifTrue:[
        settingsAppPosition := settingsAppPosition , '/HTTPServer Default Settings'.
    ] ifFalse:[
        settingsAppPosition := settingsAppPosition , '/HTTPServer Port ', aServerInstance port asString.
    ].
    newItem := requestor addApplClass:#'HTTPServerSettingsAppl' withName:settingsAppPosition.
    newItem application:settingsApp.
    self createdServerChanged.
    requestor expandItemForApplication:self.
    settingsApp initialize.
!

createServerSubApplicationsForRunningServer

    |runningServers|

    self createServerApplication:nil forDefault:true.
    runningServers := HTTPServer runningServers asOrderedCollection.
    runningServers isEmpty ifTrue:[ ^ self].
    runningServers sort:[:a :b | a port < b port].
    runningServers do:[:aHttpServerInstance |
        self createServerApplication:aHttpServerInstance forDefault:false.
    ]
!

readSettings

    HTTPServer runningServers removeDependent:self.
    HTTPServer runningServers addDependent:self.
    self createServerSubApplicationsForRunningServer.
    self createdServerChanged.
    self modifiedChannel value:false.
!

removeAllServer

    HTTPServer terminateAllServers.
    self removeAllServerSubApplications.
    self createdServerChanged.
!

removeAllServerSubApplications

    |apps|

    apps := requestor getApplicationsByClass:HTTPServerSettingsAppl.
    apps do:[:aApp |
        aApp isDefaultSettingsDialog ifFalse:[
            requestor removeByApplication:aApp.
        ]
    ].
!

setPortOnFreePort

    | createdServer |
    createdServer := (self requestor getAllChildrenAppsForApplication:self childrenClass:HTTPServerSettingsAppl) collect:[:setApp |
        setApp httpServerInstance.
    ].
    createdServer size = 1 ifTrue:[
        self portNumberChannel value:(HTTPServer defaultPort).
        ^ self
    ].
    self portNumberChannel value:0.
    createdServer do:[:aHttpServer |
        (aHttpServer notNil and:[aHttpServer port >= (self portNumberChannel value asInteger)]) ifTrue:[
            self portNumberChannel value:(aHttpServer port + 1).
        ].
    ]
! !

!AbstractSettingsApplication::HTTPStartServerSettingsApplication methodsFor:'aspects'!

hasCreatedServerChannel
    "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 ;-)"

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

informationLabel
    ^ resources 
        string:'HTTPSTARTINFO'
        default:
'These dialogs provides two things 
1. Setup the default server settings 
2. control individual running servers (if you want to handle 
   multiple servers on multiple ports).
The default servers settings are specified in the 
"HTTPServer Default Settings" entry.
The settings for a new created server are taken from
the default server or from the http server instance 
settings file'
!

portNumberChannel

    portNumberChannel isNil ifTrue:[
        portNumberChannel := ValueHolder new.
    ].
    ^ portNumberChannel.
! !

!AbstractSettingsApplication::HTTPStartServerSettingsApplication methodsFor:'change & update'!

createdServerChanged

    self hasCreatedServerChannel value:self hasCreatedServer.
    self setPortOnFreePort.
!

runningServersChanged

    |runningServers|

    runningServers := HTTPServer runningServers.
    self createServerSubApplicationsForRunningServer.
    self setPortOnFreePort.
!

update:something with:aParameter from:changedObject
    changedObject == HTTPServer runningServers ifTrue:[
        self runningServersChanged.
        ^ self.
    ].
    super update:something with:aParameter from:changedObject
! !

!AbstractSettingsApplication::HTTPStartServerSettingsApplication methodsFor:'initialization & release'!

release

    HTTPServer runningServers removeDependent:self.
! !

!AbstractSettingsApplication::HTTPStartServerSettingsApplication methodsFor:'queries'!

hasCreatedServer

    ^ ((self requestor getAllChildrenAppsForApplication:self childrenClass:HTTPServerSettingsAppl) size > 1)
!

hasUnsavedChanges

    ^ false
!

help

    self warn:'no help available here'.
"/    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/compilerSettings.html'].
! !

!AbstractSettingsApplication::KbdMappingSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::KbdMappingSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@HB@ @@@@@@@@@@@@@@@@@@@@@@@@HBA@PD@@@@@@@@@@@@@@@@@@@@@@HBA@PDA@P@@@@@@@@@@@@@@@@@@@HBA@PD@@@DA@@@@@@@@@@@@@@@
@@HDA@PDA@@D@@PD@@@@@@@@@@@@@@PDA@P@A@P@A@@DA@L@@@@@@@@@@@@B@ PD@@PD@@PDA@LC@0@@@@@@@@@@@ HBA@@@@@@DA@LC@0@@@@@@@@@@@@@B
@ HDA@PDA@LC@0@@@@@@@@@@@@@@@@HB@ PDA@LC@0@@@@@@@@@@@@@@@@@@@ HBA@LC@0@@@@@@@@@@@@@@@@@@@@@B@ PC@0@@@@@@@@@@@@@@@@@@@@@@
@@HD@0@@@@@@@@@@@@@@@@@@@@@@@@@@A@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 0 0 128 128 128 192 192 192 255 255 255]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@G@@@O @@_0@@?8@A?<@C?>@G??@G?? G??@C?>@A?<@@?8@@_0@@O @@G@@@B@@@@@@@@@@@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Keyboard Mapping Settings'
          #name: 'Keyboard Mapping Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 491 650)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VariableVerticalPanelSpec
              #name: 'VariableVerticalPanel1'
              #layout: #(#LayoutFrame 0 0.0 60 0 0 1.0 0 1.0)
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VariableHorizontalPanelSpec
                    #name: 'VariableHorizontalPanel1'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#SequenceViewSpec
                          #name: 'RawKeyList'
                          #model: #selectedRawKey
                          #hasHorizontalScrollBar: true
                          #hasVerticalScrollBar: true
                          #useIndex: false
                          #sequenceList: #rawKeyList
                        )
                       #(#SequenceViewSpec
                          #name: 'FunctionKeyList'
                          #model: #selectedFunctionKey
                          #hasHorizontalScrollBar: true
                          #hasVerticalScrollBar: true
                          #useIndex: false
                          #sequenceList: #functionKeyList
                        )
                       )
                     
                    )
                    #handles: #(#Any 0.5 1.0)
                  )
                 #(#ViewSpec
                    #name: 'Box1'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#TextEditorSpec
                          #name: 'MacroText'
                          #layout: #(#LayoutFrame 0 0.0 20 0 0 1.0 0 1.0)
                          #model: #macroTextHolder
                          #hasHorizontalScrollBar: true
                          #hasVerticalScrollBar: true
                          #isReadOnly: true
                        )
                       #(#LabelSpec
                          #label: 'Macro text (if any):'
                          #name: 'MacroTextLabel'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 20 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       )
                     
                    )
                  )
                 )
               
              )
              #handles: #(#Any 0.5 1.0)
            )
           #(#LabelSpec
              #label: 'NoticeText'
              #name: 'Text'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 60 0)
              #translateLabel: true
              #labelChannel: #labelTextHolder
              #resizeForLabel: true
              #adjust: #left
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::KbdMappingSettingsAppl methodsFor:'actions'!

basicSaveSettings
!

help

    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/keyboardSetting.html'].
!

readSettings
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::KbdMappingSettingsAppl methodsFor:'aspects'!

functionKeyList
    "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 ;-)"

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

labelTextHolder
    "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 ;-)"

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

macroTextHolder
    "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 ;-)"

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

rawKeyList

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

selectedFunctionKey

    selectedFunctionKey isNil ifTrue:[
        selectedFunctionKey := ValueHolder new.
        selectedFunctionKey addDependent:self.
    ].
    ^ selectedFunctionKey.
!

selectedRawKey

    selectedRawKey isNil ifTrue:[
        selectedRawKey := ValueHolder new.
        selectedRawKey addDependent:self.
    ].
    ^ selectedRawKey.
! !

!AbstractSettingsApplication::KbdMappingSettingsAppl methodsFor:'change & update'!

changeFunctionKeySelection

    |raw|
    raw := self selectedRawKey value.
    self selectedFunctionKey value:(mappings at:raw asSymbol) asString.
!

changeMacroText

    |f macro indent|

    f := self selectedFunctionKey value.
    (f startsWith:'Cmd') ifTrue:[
        f := f copyFrom:4
    ].
    macro := UserPreferences current functionKeySequences 
                at:(f asSymbol) ifAbsent:nil.
    macro notNil ifTrue:[
        macro := macro asStringCollection.
        indent := macro
                     inject:99999 into:[:min :element |
                         |stripped|

                         stripped := element withoutLeadingSeparators.
                         stripped size == 0 ifTrue:[
                             min
                         ] ifFalse:[
                             min min:(element size - stripped size)
                         ]
                     ].
        indent ~~ 0 ifTrue:[
            macro := macro collect:[:line | 
                         line size > indent ifTrue:[
                            line copyFrom:indent+1
                         ] ifFalse:[
                            line
                         ].
                    ]
        ].                        
    ].
    macroTextHolder value:macro.
!

changeRawKeySelection
    |f raw|

    f := self selectedFunctionKey value.
    raw := mappings keyAtValue:f asString.
    raw isNil ifTrue:[
        raw := mappings keyAtValue:f first.
        raw isNil ifTrue:[
            raw := mappings keyAtValue:f asSymbol.
        ]
    ].
    self selectedRawKey value:raw.
!

update:something with:aParameter from:changedObject
    changedObject == self selectedFunctionKey ifTrue:[
        self changeRawKeySelection.
        self changeMacroText.
        ^ self
    ].
    changedObject == self selectedRawKey ifTrue:[
        self changeFunctionKeySelection.
        ^ self
    ].
    super update:something with:aParameter from:changedObject
! !

!AbstractSettingsApplication::KbdMappingSettingsAppl 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
!

initialize

    super initialize.
    
    mappings := Screen current keyboardMap.

    rawKeyList := (mappings keys asArray collect:[:key | key asString]) sort.
    functionKeyList := (mappings values asSet asArray collect:[:key | key asString]) sort.

    self labelTextHolder value:(resources at:'KEY_MSG2' default:'keyboard mapping:') withCRs.
! !

!AbstractSettingsApplication::KbdMappingSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ false
! !

!AbstractSettingsApplication::LanguageSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::LanguageSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@PDA@PD@@@@@@@@A@PD@@@@@@@@A@R,+J2,+@PDA@PDAF1@P@P@@@@@@@PD[J2,+GQ4]GQ4+J2,WE0D@@@@@@@DA
F2,+J14]GQ4]GR,+E1\A@@@@@@@A@Q,+J14]GQ4]GQ4]J1,[@P@@@@@@@PD[J2,]GQ4]GQ4]GR,+J0DA@PD@@@DAF2,+@PX]GPXAGQ4+J2,B@PDA@@@A@Q,+
J0DFB0,F@P(J@P(J@ DA@P@@@PD[J2,A@PXFB0XA@PTEAPTE@PDA@@DAF2,+@QPFA!!8T@0LBAPTEB@DA@P@A@QXA@PD^IBP$G <OD!!PTHBDXF@$@@PDV@PDA
G"@ HB@OC1HTEB@ FA I@@DAA@@@@QP^G"PTD1LNGA0 HB@ BP@A@P@@@@DTF!!(*JR (EQPTH"T_G0$@@PD@@@@AEA(#H2L(JATTEBH%G2LI@@DA@@@@@QT#
H2$#H2L#H2L#H2L#A0@A@P@@@@DQFQ$LA2L#CBL#JR(#H00@@@@@@@@AC@0L@@@GA00GA00LA0\@@@@@@@@@@P@@@@@@@@@@@@@@@@@@@@@@@@@@@@D@@@@@
@@@@@@@@@@@@@@@@@@@@@@@A@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 0 0 32 32 32 48 48 48 49 48 49 54 54 54 69 69 69 75 67 22 82 82 82 85 14 14 89 89 89 105 105 105 106 88 25 107 107 107 110 19 19 113 19 19 131 129 131 134 122 39 149 25 25 149 26 26 158 27 27 158 140 45 164 161 164 164 161 172 165 43 43 177 161 52 196 175 0 197 194 197 204 36 36 204 75 75 205 36 36 205 113 38 212 66 66 216 81 81 223 72 72 227 202 66 231 120 120 231 123 123 233 135 135 235 146 146 255 129 0 255 238 162 255 251 229 255 255 255]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@O \@??>@??>@??>@??>@???0???0???0???8???8???8???89??81??81??81??81??8A9?0A@@@A@@@A@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Language Settings'
          #name: 'Language Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 46 491 717)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#InputFieldSpec
              #name: 'EntryField1'
              #layout: #(#LayoutFrame 2 0.0 105 0 -2 1.0 125 0)
              #model: #languageHolder
              #acceptOnReturn: true
              #acceptOnTab: true
              #acceptOnLostFocus: true
              #acceptOnPointerLeave: true
            )
           #(#SequenceViewSpec
              #name: 'List1'
              #layout: #(#LayoutFrame 2 0.0 125 0 -2 1.0 -30 1.0)
              #model: #languageHolder
              #hasHorizontalScrollBar: true
              #hasVerticalScrollBar: true
              #doubleClickSelector: #doubleClick:
              #useIndex: false
              #sequenceList: #languageList
            )
           #(#LabelSpec
              #label: 'Notice:'
              #name: 'Notice'
              #layout: #(#LayoutFrame 0 0 0 0 0 1.0 105 0)
              #translateLabel: true
              #labelChannel: #noticeLabelHolder
              #adjust: #left
            )
           #(#LabelSpec
              #label: 'Label'
              #name: 'CurrentLang'
              #layout: #(#LayoutFrame -150 1 0 0 0 1 20 0)
              #style: #(#FontDescription #helvetica #bold #roman 12)
              #translateLabel: true
              #labelChannel: #currentLanguageChannel
              #adjust: #left
            )
           #(#LabelSpec
              #label: 'Current Language:'
              #name: 'Label1'
              #layout: #(#LayoutFrame 190 0 0 0 -150 1 20 0)
              #translateLabel: true
              #labelChannel: #currentLanguageLabel
              #adjust: #right
            )
           #(#HorizontalPanelViewSpec
              #name: 'HorizontalPanel1'
              #layout: #(#LayoutFrame 0 0 -30 1 0 1 0 1)
              #horizontalLayout: #center
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#ActionButtonSpec
                    #label: 'Reread Language Resources'
                    #name: 'RereadResourcesButton'
                    #translateLabel: true
                    #model: #rereadResourceFiles
                    #extent: #(#Point 228 22)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::LanguageSettingsAppl methodsFor:'accessing'!

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

    ^ languageList
! !

!AbstractSettingsApplication::LanguageSettingsAppl methodsFor:'actions'!

basicSaveSettings

    |fontPref idx language oldLanguage territory enc 
     answer matchingFonts l screen newLanguage switch|

    newLanguage := self languageHolder value.
    self withWaitCursorDo:[
        idx := translatedLanguages indexOf:newLanguage.
        idx ~~ 0 ifTrue:[
            language := listOfLanguages at:idx
        ] ifFalse:[
            language := newLanguage
        ].
        (language includes:$-) ifTrue:[
            l := language asCollectionOfSubstringsSeparatedBy:$-.
            language := l at:1.
            territory := l at:2.
        ].
        territory isNil ifTrue:[
            territory := language copyTo:2
        ].

        "/ check if the new language needs a differently encoded font;
        "/ ask user to switch font and allow cancellation.
        "/ Otherwise, you are left with unreadable menu & button items ...

        oldLanguage := Smalltalk language.
        Smalltalk language:language asSymbol.
        ResourcePack flushCachedResourcePacks.
        "/ refetch resources ...
        resources := AbstractLauncherApplication classResources.
        fontPref := resources at:'PREFERRED_FONT_ENCODING' default:'iso8859*'.
        fontPref := fontPref asLowercase.    
        Smalltalk language:oldLanguage.

        switch := true.
        enc := MenuView defaultFont encoding.
        (fontPref match:enc asLowercase) ifFalse:[
            "/ look if there is one at all.
            screen := Screen current.
            matchingFonts := screen listOfAvailableFonts select:[:f | fontPref match:f encoding asLowercase].
            matchingFonts size == 0 ifTrue:[
                "/ flush and try again - just in case, the font path has changed.
                screen flushListOfAvailableFonts.
                matchingFonts := screen listOfAvailableFonts select:[:f | fontPref match:f encoding asLowercase].
            ].
            matchingFonts size == 0 ifTrue:[
                (Dialog 
                    confirm:(resources 
                                string:'Your display does not offer any %1-encoded font.\\Change the language anyway ?\ (texts will probably be unreadable then)'
                                  with:fontPref) withCRs)
                ifFalse:[
                    switch := false
                ]
            ] ifFalse:[
                answer := Dialog 
                            confirmWithCancel:(resources 
                                                    string:'menu font is not %1-encoded.\\Change it ?'
                                                    with:fontPref) withCRs
                                       labels:(resources
                                                    array:#('cancel' 'no' 'yes'))
                                       default:3.
                answer isNil ifTrue:[
                    switch := false
                ] ifFalse:[
                    answer ifTrue:[
                        switch := ( self requestor fontBoxForEncoding:fontPref)
                    ]
                ].
            ].
        ].

        switch ifTrue:[
            Transcript showCR:'change language to ' , newLanguage , ' ...'.
            Smalltalk language:language asSymbol.
            Smalltalk languageTerritory:territory asSymbol.
            "/ ResourcePack flushCachedResourcePacks - already done by language-change
        ].
    ].
    switch ifTrue:[       
        self requestor notNil ifTrue:[
            self requestor reopenLauncher.
        ] ifFalse:[
            NewLauncher current reopenLauncher.
        ].
        DebugView newDebugger.
    ].
    self currentLanguageChannel value:self currentLanguage.
!

doubleClick:aEntry

    self saveSettingsIfUnsavedChangesArePresent.
!

help

    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/languageSetting.html'].
!

readSettings
    self languageHolder value:self currentLanguage.
    self currentLanguageChannel value:self currentLanguage.
    self modifiedChannel value:false
!

rereadResourceFiles
    ResourcePack flushCachedResourcePacks.

"/    Smalltalk language:(Smalltalk language).
"/    Smalltalk languageTerritory:(Smalltalk languageTerritory).

    Smalltalk changed:#Language.
    Smalltalk changed:#LanguageTerritory.
! !

!AbstractSettingsApplication::LanguageSettingsAppl methodsFor:'aspects'!

currentLanguageChannel

    currentLanguageChannel isNil ifTrue:[
        currentLanguageChannel := self currentLanguage asValue.
    ].
    ^ currentLanguageChannel.
!

currentLanguageLabel

    currentLanguageLabel isNil ifTrue:[
        currentLanguageLabel := (resources string:'Current Language:') asValue.
    ].
    ^ currentLanguageLabel.
!

languageHolder

    languageHolder isNil ifTrue:[
        languageHolder := self currentLanguage asValue.
        languageHolder onChangeSend:#evaluateModified to:self.
    ].
    ^ languageHolder.
!

noticeLabelHolder

    noticeLabelHolder isNil ifTrue:[
        noticeLabelHolder := ((resources at:'LANG_MSG' default:'Select a Language') withCRs) asValue.
    ].
    ^ noticeLabelHolder.
! !

!AbstractSettingsApplication::LanguageSettingsAppl 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
!

initialize

    |flags|

    listOfLanguages := self class classResources at:'LIST_OF_OFFERED_LANGUAGES' default:#('default').
    listOfLanguages := listOfLanguages asOrderedCollection.
    translatedLanguages := listOfLanguages collect:[:lang | |item|
                                        item := resources at:lang.
                                        item isString ifTrue:[
                                            item
                                        ] ifFalse:[
                                            item at:1
                                        ]
                                ].
    flags := listOfLanguages collect:[:lang | |item|
                                        item := resources at:lang.
                                        item isArray ifTrue:[
                                            item at:2
                                        ] ifFalse:[
                                            nil
                                        ]
                                ].
    flags := flags collect:[:nm | |img d| nm notNil ifTrue:[
                                            img := Image fromFile:nm.
                                            img isNil ifTrue:[
                                                d := Smalltalk getPackageDirectoryForPackage:'stx:goodies'.
                                                img := Image fromFile:(d construct:nm).
                                            ].
                                        ] ifFalse:[
                                            nil
                                        ]
                           ].
    listOfLanguages := listOfLanguages collect:[:nm | nm copyFrom:'LANG_' size + 1].
    languageList := translatedLanguages with:flags collect:[:lang :flag | LabelAndIcon icon:flag string:lang.].

    super initialize.
! !

!AbstractSettingsApplication::LanguageSettingsAppl methodsFor:'queries'!

currentLanguage

    | lang |

    lang := Language ~= LanguageTerritory ifTrue:[
        Language , '-' , LanguageTerritory
    ] ifFalse:[
        Language
    ].
    ^ languageList at:(listOfLanguages indexOf:lang)
!

hasUnsavedChanges

    ^ (self languageHolder value) ~= (self currentLanguage)  
! !

!AbstractSettingsApplication::MemorySettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::MemorySettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@RD\@@@@@@@@@@@@@@@@@@@@@@@ARIT(*IRL]R0@@@@@@@@@@@@@@@@@@M2-VUQ<UD4QV@@@@@@@@
@@@@@@AURQ<WI!!<UEQTVS%@@@@@@@@@@@@AXI3=CH!!4QDA!!DJAT[SP@@@@@@@@AXRDQSI1,OC <QE1TRHQ @@@@@@@AUR2XWGQ MCP<OC <QHATEN0@@@@@@
RC-VGQ\JB0,MCP0NGQPEUQ4@@@ARM14>IA\HB $JB0,MF!!TGO%,6T0@@RSMAF!!TGA0 HB $JFQL@AR9ZRTX@RDAWHALEAPTGA0 HE1HGPA<;FC@@@B$&I1LA
@ LEA@TGE1L@NU1EOQ=M@@@''L LXB@@A@ LEEQDHB1!!ERC!!U@@@@P#,@AQ\G@@@AEA@@OB5FGT!!T@@@@@@AYF0@EE0\AD1D@G5D4S%UG@@@@@@@@@C(F@@PW
E1@@GQYHH"1ET @@@@@@@@@@M0\@B!!$GMTP8S"EO@@@@@@@@@@@@@@@:B@@UET$1H$D/@@@@@@@@@@@@@@@@@C OD14\G$9ST@@@@@@@@@@@@@@@@@@@@@@@
SAMM@@@@@@@@@@@@@@@@@@@@@@@@@@@V@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 1 1 1 3 3 3 5 5 5 9 9 9 10 10 10 14 14 14 15 15 15 20 20 20 23 23 23 25 25 25 30 30 30 34 34 34 35 35 35 39 39 39 40 40 40 44 44 44 45 45 45 49 49 49 50 50 50 57 57 57 60 60 60 69 69 69 70 70 70 80 80 80 82 82 82 83 83 83 84 84 84 89 89 89 90 90 90 93 93 93 94 94 94 95 95 95 98 98 98 99 99 99 101 101 101 106 106 106 109 109 109 113 113 113 114 114 114 119 119 120 128 128 128 134 134 134 137 137 137 137 137 139 139 139 139 143 143 143 144 144 144 145 145 145 146 146 146 147 147 147 147 147 148 148 148 148 149 149 149 150 150 150 155 155 155 156 156 156 157 157 157 158 158 158 160 160 160 162 162 162 163 163 164 165 165 165 166 166 168 167 167 167 168 168 168 172 172 172 173 173 173 175 175 175 177 177 177 178 178 178 179 179 179 180 180 180 182 182 182 182 182 184 192 192 192 193 193 196 198 198 198 200 200 200 200 200 201 201 201 201 202 202 202 203 203 203 204 204 204 204 204 206 205 205 205 206 206 206 207 207 207 209 209 209 213 213 213 225 225 225 247 247 247 255 255 255]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@A @@G>@@G?@@_? @??0A??0C??8C??8O??<O??<_??8_??8_??0_?? O??@G??@C?<@A?8@@?8@@C @@A@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Memory Manager Settings'
          #name: 'Memory Manager Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 616 592)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#LabelSpec
              #label: 'Label'
              #name: 'Label1'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 50 0)
              #translateLabel: true
              #labelChannel: #warningLabelHolder
              #adjust: #left
            )
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel1'
              #layout: #(#LayoutFrame 0 0.0 50 0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#ViewSpec
                    #name: 'NewSpaceSizeBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField23'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1 25 0)
                          #model: #newSpaceSize
                          #type: #number
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Size of NewSpace:'
                          #name: 'Label44'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Size of newSpace where objects are created'
                          #name: 'Label45'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator24'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 49)
                  )
                 #(#ViewSpec
                    #name: 'MaximumMemoryLimitBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField24'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1 25 0)
                          #model: #maxOldSpace
                          #type: #number
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Maximum Memory Limit:'
                          #name: 'Label46'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Never allocate more than this amount of memory'
                          #name: 'Label47'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator25'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 49)
                  )
                 #(#ViewSpec
                    #name: 'QuickAllocationLimitBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField14'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1 25 0)
                          #model: #fastMoreLimit
                          #type: #number
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Quick Allocation Limit:'
                          #name: 'Label26'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Quickly allocate more memory (suppress GC) up to this limit'
                          #name: 'Label27'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator15'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 50)
                  )
                 #(#ViewSpec
                    #name: 'IncrementalGCAllocationTriggerBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField25'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1 25 0)
                          #model: #igcLimit
                          #type: #number
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Incremental GC Allocation Trigger:'
                          #name: 'Label48'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Start IGC whenever this amount has been allocated'
                          #name: 'Label49'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator26'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 49)
                  )
                 #(#ViewSpec
                    #name: 'IncrementalGCFreespaceTriggerBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField26'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1 25 0)
                          #model: #igcFreeLimit
                          #type: #number
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Incremental GC Freespace Trigger:'
                          #name: 'Label50'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Start IGC whenever freespace drops below this'
                          #name: 'Label51'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator27'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 48)
                  )
                 #(#ViewSpec
                    #name: 'GCAmountBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField17'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1 25 0)
                          #model: #igcFreeAmount
                          #type: #number
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Incremental GC Amount:'
                          #name: 'Label32'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Try to keep this amount for peak requests'
                          #name: 'Label33'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator18'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 50)
                  )
                 #(#ViewSpec
                    #name: 'OldspaceIncrementBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField18'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1.0 25 0)
                          #model: #oldIncr
                          #type: #number
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Oldspace Increment:'
                          #name: 'Label34'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Increase oldSpace in chunks of this size'
                          #name: 'Label35'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator19'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 50)
                  )
                 #(#ViewSpec
                    #name: 'OldSpaceCompressLimitBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField19'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1 25 0)
                          #model: #compressLimit
                          #type: #number
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Oldspace Compress Limit:'
                          #name: 'Label36'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Use 2-pass compressing GC if > 0 and more memory is in use'
                          #name: 'Label37'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator20'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 50)
                  )
                 #(#ViewSpec
                    #name: 'StackLimitBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField20'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1 25 0)
                          #enableChannel: #supportsJustInTimeCompilation
                          #model: #stackLimit
                          #type: #number
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Stack Limit:'
                          #name: 'Label38'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Trigger recursionInterrupt if more stack is used by a process'
                          #name: 'Label39'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator21'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 550)
                  )
                 #(#ViewSpec
                    #name: 'CodeLimitBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField21'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1 25 0)
                          #enableChannel: #supportsJustInTimeCompilation
                          #model: #codeLimit
                          #type: #numberOrNil
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Dynamic code Limit:'
                          #name: 'Label40'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Flush dynamic compiled code to stay within this limit'
                          #name: 'Label41'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator22'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 50)
                  )
                 #(#ViewSpec
                    #name: 'CodeTriggerBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#InputFieldSpec
                          #name: 'EntryField22'
                          #layout: #(#LayoutFrame -95 1 3 0 -5 1 25 0)
                          #model: #codeTrigger
                          #type: #number
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       #(#LabelSpec
                          #label: 'Dynamic code Limit:'
                          #name: 'Label42'
                          #layout: #(#LayoutFrame 0 0 3 0 -95 1 25 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#LabelSpec
                          #label: 'Start incremental GC whenever this amount of code has been allocated'
                          #name: 'Label43'
                          #layout: #(#LayoutFrame 0 0.0 25 0 0 1.0 47 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#DividerSpec
                          #name: 'Separator23'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 3 0)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 50)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::MemorySettingsAppl methodsFor:'actions'!

basicSaveSettings

    ObjectMemory freeSpaceGCAmount:self igcFreeAmount value.
    ObjectMemory freeSpaceGCLimit:self igcFreeLimit value.
    ObjectMemory incrementalGCLimit:self igcLimit value.
    ObjectMemory newSpaceSize:self newSpaceSize value.
    ObjectMemory oldSpaceIncrement:self oldIncr value.
    Process defaultMaximumStackSize:self stackLimit value.
    ObjectMemory fastMoreOldSpaceLimit:self fastMoreLimit value.
    ObjectMemory maxOldSpace:self maxOldSpace value.
    ObjectMemory oldSpaceCompressLimit:self compressLimit value.
    ObjectMemory dynamicCodeLimit:self codeLimit value.
    ObjectMemory dynamicCodeGCTrigger:self codeTrigger value.
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/memorySettings.html'].
!

readSettings
    self igcLimit value:ObjectMemory incrementalGCLimit.
    self igcFreeLimit value:ObjectMemory freeSpaceGCLimit.
    self igcFreeAmount value:ObjectMemory freeSpaceGCAmount.
    self newSpaceSize value:ObjectMemory newSpaceSize.
    self oldIncr value:ObjectMemory oldSpaceIncrement.
    self compressLimit value:ObjectMemory oldSpaceCompressLimit.
    self codeLimit value:ObjectMemory dynamicCodeLimit.
    self codeTrigger value:ObjectMemory dynamicCodeGCTrigger.
    self stackLimit value:Process defaultMaximumStackSize.
    self fastMoreLimit value:(ObjectMemory fastMoreOldSpaceLimit:-1).
    self maxOldSpace value:ObjectMemory maxOldSpace.
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::MemorySettingsAppl methodsFor:'aspects'!

codeLimit

    codeLimit isNil ifTrue:[
        codeLimit := ObjectMemory dynamicCodeLimit asValue.
        codeLimit onChangeSend:#evaluateModified to:self
    ].
    ^ codeLimit.
!

codeTrigger

    codeTrigger isNil ifTrue:[
        codeTrigger := ObjectMemory dynamicCodeGCTrigger asValue.
        codeTrigger onChangeSend:#evaluateModified to:self
    ].
    ^ codeTrigger.
!

compressLimit

    compressLimit isNil ifTrue:[
        compressLimit := ObjectMemory oldSpaceCompressLimit asValue.
        compressLimit onChangeSend:#evaluateModified to:self
    ].
    ^ compressLimit.
!

fastMoreLimit

    fastMoreLimit isNil ifTrue:[
        fastMoreLimit := (ObjectMemory fastMoreOldSpaceLimit:-1) asValue.
        fastMoreLimit onChangeSend:#evaluateModified to:self
    ].
    ^ fastMoreLimit.
!

igcFreeAmount

    igcFreeAmount isNil ifTrue:[
        igcFreeAmount := ObjectMemory freeSpaceGCAmount asValue.
        igcFreeAmount onChangeSend:#evaluateModified to:self
    ].
    ^ igcFreeAmount.
!

igcFreeLimit

    igcFreeLimit isNil ifTrue:[
        igcFreeLimit := ObjectMemory freeSpaceGCLimit asValue.
        igcFreeLimit onChangeSend:#evaluateModified to:self
    ].
    ^ igcFreeLimit.
!

igcLimit

    igcLimit isNil ifTrue:[
        igcLimit := ObjectMemory incrementalGCLimit asValue.
        igcLimit onChangeSend:#evaluateModified to:self
    ].
    ^ igcLimit.
!

maxOldSpace

    maxOldSpace isNil ifTrue:[
        maxOldSpace := ObjectMemory maxOldSpace asValue.
        maxOldSpace onChangeSend:#evaluateModified to:self
    ].
    ^ maxOldSpace.
!

newSpaceSize

    newSpaceSize isNil ifTrue:[
        newSpaceSize := ObjectMemory newSpaceSize asValue.
        newSpaceSize onChangeSend:#evaluateModified to:self
    ].
    ^ newSpaceSize.
!

oldIncr

    oldIncr isNil ifTrue:[
        oldIncr := ObjectMemory oldSpaceIncrement asValue.
        oldIncr onChangeSend:#evaluateModified to:self
    ].
    ^ oldIncr.
!

stackLimit

    stackLimit isNil ifTrue:[
        stackLimit := Process defaultMaximumStackSize asValue.
        stackLimit onChangeSend:#evaluateModified to:self
    ].
    ^ stackLimit.
!

supportsJustInTimeCompilation

    ^ ObjectMemory supportsJustInTimeCompilation.
!

warningLabelHolder

    warningLabelHolder isNil ifTrue:[
        warningLabelHolder := ValueHolder new.
    ].
    ^ warningLabelHolder.
! !

!AbstractSettingsApplication::MemorySettingsAppl methodsFor:'initialization & release'!

initialize

    super initialize.
    self warningLabelHolder value:'Warning - invalid settings may result in failures or poor performance
' , 'You have been warned' allBold , '.'.
! !

!AbstractSettingsApplication::MemorySettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^   (
        ObjectMemory freeSpaceGCAmount ~= self igcFreeAmount value or:[
        ObjectMemory freeSpaceGCLimit ~= self igcFreeLimit value or:[
        ObjectMemory incrementalGCLimit ~= self igcLimit value or:[
        ObjectMemory newSpaceSize ~= self newSpaceSize value or:[
        ObjectMemory oldSpaceIncrement ~= self oldIncr value or:[
        Process defaultMaximumStackSize ~= self stackLimit value or:[
        (ObjectMemory fastMoreOldSpaceLimit:-1) ~= self fastMoreLimit value or:[
        ObjectMemory maxOldSpace ~= self maxOldSpace value or:[
        ObjectMemory oldSpaceCompressLimit ~= self compressLimit value or:[
        ObjectMemory dynamicCodeLimit ~= self codeLimit value or:[
        ObjectMemory dynamicCodeGCTrigger ~= self codeTrigger value ]]]]]]]]]]
        )
! !

!AbstractSettingsApplication::MiscCommunicationSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::MiscCommunicationSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@_$RA@@@@@@@@@@@@@HED_ @@@@@@ U2+UX\@@@@@@@@@@H]U*52A@@@@ U*9^S-A  @@@@@@@HIT.HD4O8D@_%29^#6JZE"B@@@@@HIX-(@9!!&-\_"Z+
.+QKZ(0@J @@@@@*@K*5SV2B*2XDQ+":,XR5WP8@@@@@BDJ5.+V@.E4KEA46-+*5U9TVHRD!!HP<+JKV:-%*SG1@Y@R8@WYV)I@A/@@@SH D$@E>K*BP-$PUH
QH60)2U0[$:]KYPJN$RK,JX''[TFW]BB*)*4Z\K)[Q''L6''GD *JZ.HF4UV;H_**U6\+)%T7,WDUB3G:^%_E<@WB%RG*)8\+*BL(=Q#@(!!R!!2-_P5-@@AUNA!!4
BGV:.(IQ)I<LQS@R^VE([P@@(E9OZQT/[[*:-9=YO8M''S6B ZF4@@@@@[0@[M0I5.)!!!!(4NE@F<@&$&C@@@@@@@@G&PCBGYV&;@<!!P@@#$^P@@@@@@@@@FN@
[R<#+J2,PHT@%$2E@@@@@@@@@@BEA7>"I;B/''$*H%$"I@@@@@@@@@@@@$#D]^RF''*F]5$D2I@@@@@@@@@@@@@@BIKB<F(VHIHSNE@@@@@@@@@@@@@@@@@I$>
MVY7@@@@@@@@@@@@@@@@@@@@@@@@!!3Y9@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 0 0 7 7 7 12 12 12 20 20 20 23 23 23 24 24 24 28 28 28 30 30 30 32 32 32 35 35 35 40 40 40 41 41 41 43 43 43 45 45 45 48 47 48 50 49 50 51 50 51 52 52 52 54 53 54 55 54 55 56 56 56 58 57 58 58 58 58 59 59 59 60 59 60 60 60 60 61 61 61 62 62 62 66 65 66 66 66 66 67 66 67 68 67 68 69 69 69 70 69 70 70 70 70 71 71 71 72 71 72 73 73 73 74 73 74 75 75 75 76 75 76 76 76 76 77 76 77 78 78 78 79 79 79 80 80 80 85 84 85 86 84 86 86 85 86 87 86 87 87 87 87 88 87 88 89 88 89 89 89 89 90 88 90 90 89 90 93 91 93 93 93 93 94 92 94 94 93 94 96 94 96 97 96 97 98 97 98 99 98 99 99 99 99 100 99 100 100 100 100 102 102 102 103 103 103 104 103 104 104 104 104 105 105 105 106 106 106 108 107 108 109 109 109 110 110 110 111 110 111 113 113 113 114 113 114 114 114 114 115 115 115 116 116 116 117 115 117 118 118 118 120 120 120 121 121 121 122 121 122 122 122 122 123 122 123 123 123 123 124 124 124 125 125 125 127 127 127 128 128 128 129 129 129 130 130 130 131 131 131 132 131 132 132 132 132 133 132 133 134 134 134 135 135 135 136 136 136 137 137 137 138 138 138 140 139 140 142 142 142 147 147 147 151 151 151 153 153 153 154 154 154 155 155 155 156 155 156 156 156 156 159 159 159 164 163 164 165 165 165 167 167 167 168 168 168 170 170 170 172 172 172 174 174 174 175 174 175 177 177 177 178 178 178 181 181 181 182 182 182 183 183 183 185 185 185 189 189 189 190 190 190 191 191 191 192 192 192 194 192 194 194 194 194 195 195 195 196 196 196 198 196 198 199 198 199 200 200 200 201 200 201 201 201 201 202 201 202 202 202 202 203 203 203 204 204 204 205 204 205 205 205 205 206 205 206 206 206 206 209 209 209 210 210 210 211 211 211 212 212 212 213 212 213 213 213 213 214 214 214 215 213 215 215 215 215 216 216 216 217 216 217 217 217 217 218 217 218 219 219 219 221 219 221 222 221 222 224 222 224 224 223 224 225 223 225 225 224 225 225 225 225 226 224 226 226 225 226 227 226 227 228 226 228 229 228 229 231 231 231 232 231 232 235 234 235 237 237 237 239 239 239 241 241 241 244 244 244 247 247 247 248 248 248 255 255 255]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'G@C O G0_0O8?8_<?(W<?8_<???<=:^<???<???<???<_??<O??<O??<B?=\@?<8@?=0@?? @??@@_>@@O @@G@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Communication Settings'
          #name: 'Communication Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 46 616 560)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel1'
                    #horizontalLayout: #fit
                    #verticalLayout: #center
                    #horizontalSpace: 3
                    #verticalSpace: 3
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Remote browsing'
                          #name: 'Label1'
                          #translateLabel: true
                          #extent: #(#Point 600 22)
                        )
                       #(#ViewSpec
                          #name: 'Box1'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Remote browsing enabled'
                                #name: 'CheckBox1'
                                #layout: #(#LayoutFrame 5 0 0 0 600 0 22 0)
                                #enableChannel: #hasRemoteBrowsingSupport
                                #model: #remoteBrowsingEnabled
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 23)
                        )
                       #(#DividerSpec
                          #name: 'Separator1'
                          #extent: #(#Point 600 4)
                        )
                       #(#LabelSpec
                          #label: 'Window migration'
                          #name: 'Label2'
                          #translateLabel: true
                          #extent: #(#Point 600 22)
                        )
                       #(#ViewSpec
                          #name: 'Box2'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Window migration enabled'
                                #name: 'CheckBox2'
                                #layout: #(#LayoutFrame 5 0 0 0 600 0 22 0)
                                #enableChannel: #hasWindowMigrationServer
                                #model: #windowMigrationEnabled
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 23)
                        )
                       #(#ViewSpec
                          #name: 'Box3'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Password check'
                                #name: 'CheckBox3'
                                #layout: #(#LayoutFrame 5 0 0 0 600 0 22 0)
                                #enableChannel: #enablePasswordCheck
                                #model: #windowMigrationAuthenticate
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 22)
                        )
                       #(#ViewSpec
                          #name: 'Box4'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#LabelSpec
                                #label: 'Password:'
                                #name: 'Label3'
                                #layout: #(#LayoutFrame 0 0 0 0 150 0 22 0)
                                #translateLabel: true
                                #adjust: #right
                              )
                             #(#InputFieldSpec
                                #name: 'EntryField1'
                                #layout: #(#LayoutFrame 150 0 0 0 -5 1 22 0)
                                #enableChannel: #windowMigrationAuthenticate
                                #model: #windowMigrationPassword
                                #type: #password
                                #acceptOnReturn: true
                                #acceptOnTab: true
                                #acceptOnLostFocus: true
                                #acceptOnPointerLeave: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 22)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 250)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::MiscCommunicationSettingsAppl methodsFor:'actions'!

basicSaveSettings

    self hasRemoteBrowsingSupport ifTrue:[
        self remoteBrowsingEnabled value ifTrue:[
            SmalltalkShareServer serverRunning ifTrue:[
                SmalltalkShareServer killAll
            ].
        ] ifFalse:[
            SmalltalkShareServer serverRunning not ifTrue:[
                SmalltalkShareServer start.
                "/ must wait a bit; give it a chance to
                "/ really start (before checking)
                Delay waitForSeconds:0.5.
                SmalltalkShareServer serverRunning ifFalse:[
                    self warn:'SmalltalkShareServer startup failed (see stderr).'
                ]
            ].
        ].
    ].
    self hasWindowMigrationServer ifTrue:[
        self windowMigrationAuthenticate value ifTrue:[
            WindowMigrationServer password:self windowMigrationPassword value.
        ] ifFalse:[
            WindowMigrationServer password:nil    
        ].
        self windowMigrationEnabled value ifTrue:[
            WindowMigrationServer serverRunning ifTrue:[
                WindowMigrationServer stop
            ].
        ] ifFalse:[
            WindowMigrationServer serverRunning not ifTrue:[
                WindowMigrationServer start.
                "/ must wait a bit; give it a chance to
                "/ really start (before checking)
                Delay waitForSeconds:0.5.
                WindowMigrationServer serverRunning ifFalse:[
                    self warn:'WindowMigrationServer startup failed (see stderr).'
                ]
            ].
        ].
    ].
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/communicationsSettings.html'].
!

readSettings
    self remoteBrowsingEnabled value:(self hasRemoteBrowsingSupport 
                and:[SmalltalkShareServer isLoaded and:[SmalltalkShareServer serverRunning]]).
    self windowMigrationEnabled value:(self hasWindowMigrationServer 
                and:[
                    WindowMigrationServer isLoaded and:[WindowMigrationServer serverRunning]
                ]).
    (self hasWindowMigrationServer and:[WindowMigrationServer isLoaded]) ifTrue:[
        self windowMigrationPassword value:WindowMigrationServer password.
        self windowMigrationAuthenticate 
            value:self windowMigrationPassword value notNil
    ] ifFalse:[
        self windowMigrationPassword value:nil.
        self windowMigrationAuthenticate value:false
    ].
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::MiscCommunicationSettingsAppl methodsFor:'aspects'!

enablePasswordCheck

    enablePasswordCheck isNil ifTrue:[
        self hasWindowMigrationServer not ifTrue:[
            enablePasswordCheck := false asValue.
        ] ifFalse:[
            enablePasswordCheck := self windowMigrationEnabled.
        ].
    ].
    ^ enablePasswordCheck.
!

remoteBrowsingEnabled

    remoteBrowsingEnabled isNil ifTrue:[
        remoteBrowsingEnabled := true asValue.
        remoteBrowsingEnabled onChangeSend:#evaluateModified to:self.
    ].
    ^ remoteBrowsingEnabled.
!

windowMigrationAuthenticate

    windowMigrationAuthenticate isNil ifTrue:[
        windowMigrationAuthenticate := true asValue.
        windowMigrationAuthenticate onChangeSend:#evaluateModified to:self.
    ].
    ^ windowMigrationAuthenticate.
!

windowMigrationEnabled

    windowMigrationEnabled isNil ifTrue:[
        windowMigrationEnabled := true asValue.
        windowMigrationEnabled onChangeSend:#evaluateModified to:self.
    ].
    ^ windowMigrationEnabled.
!

windowMigrationPassword

    windowMigrationPassword isNil ifTrue:[
        windowMigrationPassword := ValueHolder new.
        windowMigrationPassword onChangeSend:#evaluateModified to:self.
    ].
    ^ windowMigrationPassword.
! !

!AbstractSettingsApplication::MiscCommunicationSettingsAppl 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 allOfThem ifTrue:[
"/        ^ self.
"/    ].

    super update:something with:aParameter from:changedObject
! !

!AbstractSettingsApplication::MiscCommunicationSettingsAppl methodsFor:'initialization & release'!

initialize
    super initialize.
    self readSettings.
! !

!AbstractSettingsApplication::MiscCommunicationSettingsAppl methodsFor:'queries'!

hasRemoteBrowsingSupport

    ^ SmalltalkShareServer notNil
!

hasUnsavedChanges

    ^ (
        self remoteBrowsingEnabled value ~= (self hasRemoteBrowsingSupport and:[SmalltalkShareServer isLoaded and:[SmalltalkShareServer serverRunning]]) or:[
        self windowMigrationEnabled value ~= (self hasWindowMigrationServer and:[WindowMigrationServer isLoaded and:[WindowMigrationServer serverRunning]]) or:[
        self windowMigrationPassword value ~= WindowMigrationServer password or:[
        self windowMigrationAuthenticate value ~= self windowMigrationPassword value notNil ]]]
    )
!

hasWindowMigrationServer

    ^ WindowMigrationServer notNil
! !

!AbstractSettingsApplication::MiscDisplaySettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::MiscDisplaySettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@DA@@@@@@@@@@@@@@@@@@@@@@@@@@DBAPD@@@@@@@@@@@@@@@@@@@@@@@DBAPTF@P@@@@@@@@@@@@@@@@@@@@DBAPTFA DA@@@@@@@@@@@@
@@@@@@LB@ HFA \G@PD@@@@@@@@@@@@@@@LB@ HB@  GA0(J@P@@@@@@@@@@@@LB@ HB@ HBB \IB ,A@@@@@@@@@@LB@ HB@ HB@ 4NB ,OC0DE@@@@@@LB
@ HB@ HB@ HB@ 8OC0TE@P@@@@@@@0HB@ HB@ HBCQDQC0TEAPHP@AHRD!!HRD!!HRD!!HRD!!HRD!!HAA@HC@@@RD HED1LTEQXVE1 BAPTR@ DC@@@@D!!HBAQLS
EATVE!!\X@ TED HC@@@@@AHRAPPYFQ([GA0]G TDAAHC@@@@@@@C@0HB@ HB@ HB@!!<MDQDC@@@@@@@@@0LB@ HB@ HB@ H_CQDQ@0@@@@@@@@LC@ HB@ HB
@ HBCP4QDPL@@@@@@@@C@0HB@ HB@ HB@ 4MDQDC@@@@@@@@@0LB@ HB@ HB@!!<MDQDQ@0@@@@@@@@LC@ HB@ HB@ H_CQDQDPL@@@@@@@@C@0HB@ HB@ HB
CP4QDQDC@@@@@@@@@0LC@0LC@0LC@0LC@0LC@0@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 32 96 88 248 248 248 80 80 80 128 128 128 192 192 192 64 144 136 48 120 112 56 136 128 56 128 120 40 104 96 40 104 104 32 96 96 232 232 232 32 88 88 32 88 80 64 104 104 224 224 224 0 88 128 24 152 192 16 136 184 16 128 168 8 120 160 8 112 152 8 104 144 16 120 152 16 112 144 8 104 136 8 96 128 8 88 120 0 80 112 240 240 240]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@C@@@G @@O0@@_8@@?<@A?>@C??@G??0O??0G??8???0??? ???@??>@??<@??<@??<@??<@??<@??<@??<@??<@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Display settings'
          #name: 'Display settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 46 526 612)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel1'
                    #horizontalLayout: #fitSpace
                    #verticalLayout: #topSpace
                    #horizontalSpace: 5
                    #verticalSpace: 3
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#CheckBoxSpec
                          #label: 'Shadows under PopUp Views'
                          #name: 'CheckBox1'
                          #model: #shadows
                          #translateLabel: true
                          #extent: #(#Point 500 22)
                        )
                       #(#CheckBoxSpec
                          #label: 'Beeper enabled'
                          #name: 'CheckBox2'
                          #model: #beepEnabled
                          #translateLabel: true
                          #extent: #(#Point 500 22)
                        )
                       #(#CheckBoxSpec
                          #label: 'Boxes Return Focus to Previously Active View'
                          #name: 'CheckBox3'
                          #model: #returnFocus
                          #translateLabel: true
                          #extent: #(#Point 500 22)
                        )
                       #(#CheckBoxSpec
                          #label: 'Views Catch Focus when Mapped'
                          #name: 'CheckBox4'
                          #model: #takeFocus
                          #translateLabel: true
                          #extent: #(#Point 500 22)
                        )
                       #(#CheckBoxSpec
                          #label: 'Show Accelerator Keys in Menus'
                          #name: 'CheckBox6'
                          #model: #showAccelerators
                          #translateLabel: true
                          #extent: #(#Point 500 22)
                        )
                       #(#CheckBoxSpec
                          #label: 'Raise & Activate Windows on Click'
                          #name: 'CheckBox7'
                          #model: #activateOnClick
                          #translateLabel: true
                          #extent: #(#Point 500 22)
                        )
                       #(#CheckBoxSpec
                          #label: 'Focus Follows Mouse'
                          #name: 'CheckBox8'
                          #model: #focusFollowsMouse
                          #translateLabel: true
                          #extent: #(#Point 500 22)
                        )
                       #(#CheckBoxSpec
                          #label: 'Opaque Variable Panel Resizing'
                          #name: 'CheckBox9'
                          #model: #opaqueVariablePanelResize
                          #translateLabel: true
                          #extent: #(#Point 500 22)
                        )
                       #(#CheckBoxSpec
                          #label: 'Opaque Table Column Resizing'
                          #name: 'CheckBox10'
                          #model: #opaqueTableColumnResize
                          #translateLabel: true
                          #extent: #(#Point 500 22)
                        )
                       #(#ViewSpec
                          #name: 'Box1'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#LabelSpec
                                #label: 'Label'
                                #name: 'Label1'
                                #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 -22 1)
                                #translateLabel: true
                                #labelChannel: #formatHostNameWindowLabel
                                #adjust: #leftRight
                              )
                             #(#CheckBoxSpec
                                #label: 'Hostname in Window Labels'
                                #name: 'CheckBox5'
                                #layout: #(#LayoutFrame 0 0 -22 1 216 0 0 1)
                                #model: #hostNameInLabelHolder
                                #translateLabel: true
                              )
                             #(#InputFieldSpec
                                #name: 'EntryField1'
                                #layout: #(#LayoutFrame 218 0 -22 1 -5 1 0 1)
                                #enableChannel: #hostNameInLabelHolder
                                #model: #newWindowLabelFormat
                                #immediateAccept: true
                                #acceptOnReturn: true
                                #acceptOnTab: true
                                #acceptOnLostFocus: true
                                #acceptOnPointerLeave: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 500 120)
                        )
                       )
                     
                    )
                    #extent: #(#Point 510 550)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::MiscDisplaySettingsAppl methodsFor:'actions'!

basicSaveSettings

    PopUpView shadows:self shadows value.
    (self hostNameInLabelHolder value ~= StandardSystemView includeHostNameInLabel 
    or:[self newWindowLabelFormat value ~= StandardSystemView windowLabelFormat]) ifTrue:[ 
        StandardSystemView includeHostNameInLabel:self hostNameInLabelHolder value.
        self newWindowLabelFormat value notNil ifTrue:[
            StandardSystemView windowLabelFormat:self newWindowLabelFormat value
        ].

        Screen allScreens do:[:aDisplay |
            aDisplay allViewsDo:[:aView |
                |l|

                aView isTopView ifTrue:[
                    l := aView label.
                    l notNil ifTrue:[
                        aView label:(l , ' '); label:l.  "/ force a change
                    ]
                ]
            ]
        ]
    ].

    currentUserPrefs opaqueVariablePanelResizing:self opaqueVariablePanelResize value.
    currentUserPrefs opaqueTableColumnResizing:self opaqueTableColumnResize value.

    currentUserPrefs beepEnabled:self beepEnabled value.

    StandardSystemView returnFocusWhenClosingModalBoxes:self returnFocus value.
    StandardSystemView takeFocusWhenMapped:self takeFocus value.
    currentUserPrefs focusFollowsMouse:self focusFollowsMouse value.
    Screen current activateOnClick:self activateOnClick value.

    MenuView showAcceleratorKeys:self showAccelerators value.

    "Modified: / 16.12.2002 / 18:06:31 / penk"
!

formatHostNameinWindowLabels
   |newFormat|

   newFormat := Dialog request:
                    'Define the Format of Window Labels:\\  %1 - Label\  %2 - Hostname\  %3 - Username\  %4 - ProcessId\'  
                       withCRs initialAnswer:newWindowLabelFormat.

   newFormat size > 0 ifTrue:[
       newWindowLabelFormat := newFormat.
       self evaluateModified.
   ].
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/miscSettings.html'].
!

readSettings
    self shadows value:PopUpView shadows.
    self beepEnabled value:currentUserPrefs beepEnabled.
    self newWindowLabelFormat value:StandardSystemView windowLabelFormat.
    self hostNameInLabelHolder 
        value:StandardSystemView includeHostNameInLabel.
    self returnFocus 
        value:StandardSystemView returnFocusWhenClosingModalBoxes.
    self takeFocus value:StandardSystemView takeFocusWhenMapped.
    self focusFollowsMouse value:(currentUserPrefs focusFollowsMouse ? true).
    self activateOnClick value:(Display activateOnClick:nil).
    self opaqueVariablePanelResize 
        value:currentUserPrefs opaqueVariablePanelResizing.
    self opaqueTableColumnResize 
        value:currentUserPrefs opaqueTableColumnResizing.
    self showAccelerators value:MenuView showAcceleratorKeys.
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::MiscDisplaySettingsAppl methodsFor:'aspects'!

activateOnClick

    activateOnClick isNil ifTrue:[
        activateOnClick := true asValue.
        activateOnClick onChangeSend:#evaluateModified to:self
    ].
    ^ activateOnClick.
!

beepEnabled

    beepEnabled isNil ifTrue:[
        beepEnabled := true asValue.
        beepEnabled onChangeSend:#evaluateModified to:self
    ].
    ^ beepEnabled.
!

focusFollowsMouse

    focusFollowsMouse isNil ifTrue:[
        focusFollowsMouse := true asValue.
        focusFollowsMouse onChangeSend:#evaluateModified to:self
    ].
    ^ focusFollowsMouse.
!

formatHostNameWindowLabel

    formatHostNameWindowLabel isNil ifTrue:[
        formatHostNameWindowLabel := 
                ('Define the Format of Window Labels:\\  %1 - Label\  %2 - Hostname\  %3 - Username\  %4 - ProcessId\' withCRs)
                     asValue.
    ].
    ^ formatHostNameWindowLabel.

    "Created: / 16.12.2002 / 17:50:49 / penk"
    "Modified: / 16.12.2002 / 17:55:18 / penk"
!

hostNameInLabelHolder

    hostNameInLabelHolder isNil ifTrue:[
        hostNameInLabelHolder := true asValue.
        hostNameInLabelHolder onChangeSend:#evaluateModified to:self
    ].
    ^ hostNameInLabelHolder.
!

newWindowLabelFormat

    newWindowLabelFormat isNil ifTrue:[
        newWindowLabelFormat := true asValue.
        newWindowLabelFormat onChangeSend:#evaluateModified to:self
    ].
    ^ newWindowLabelFormat.

    "Created: / 16.12.2002 / 17:50:49 / penk"
!

opaqueTableColumnResize

    opaqueTableColumnResize isNil ifTrue:[
        opaqueTableColumnResize := true asValue.
        opaqueTableColumnResize onChangeSend:#evaluateModified to:self
    ].
    ^ opaqueTableColumnResize.
!

opaqueVariablePanelResize

    opaqueVariablePanelResize isNil ifTrue:[
        opaqueVariablePanelResize := true asValue.
        opaqueVariablePanelResize onChangeSend:#evaluateModified to:self
    ].
    ^ opaqueVariablePanelResize.
!

returnFocus

    returnFocus isNil ifTrue:[
        returnFocus := true asValue.
        returnFocus onChangeSend:#evaluateModified to:self
    ].
    ^ returnFocus.
!

shadows

    shadows isNil ifTrue:[
        shadows := true asValue.
        shadows onChangeSend:#evaluateModified to:self
    ].
    ^ shadows.
!

showAccelerators

    showAccelerators isNil ifTrue:[
        showAccelerators := true asValue.
        showAccelerators onChangeSend:#evaluateModified to:self
    ].
    ^ showAccelerators.
!

takeFocus

    takeFocus isNil ifTrue:[
        takeFocus := true asValue.
        takeFocus onChangeSend:#evaluateModified to:self
    ].
    ^ takeFocus.
! !

!AbstractSettingsApplication::MiscDisplaySettingsAppl methodsFor:'initialization & release'!

postOpen
!

postOpenAsSubcanvasWith:aBuilder

    self postOpen.
    ^ super postOpenAsSubcanvasWith:aBuilder
!

postOpenWith:aBuilder

    self postOpen.
    ^ super postOpenWith:aBuilder
! !

!AbstractSettingsApplication::MiscDisplaySettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ (
    self newWindowLabelFormat value ~= StandardSystemView windowLabelFormat or:[
    self shadows value ~= PopUpView shadows or:[
    self beepEnabled value ~= currentUserPrefs beepEnabled or:[
    self hostNameInLabelHolder value ~= StandardSystemView includeHostNameInLabel or:[
    self returnFocus value ~= StandardSystemView returnFocusWhenClosingModalBoxes or:[
    self takeFocus value ~= StandardSystemView takeFocusWhenMapped or:[
    self focusFollowsMouse value ~= (currentUserPrefs focusFollowsMouse ? true) or:[
    self activateOnClick value ~= (Display activateOnClick:nil) or:[
    self opaqueVariablePanelResize value ~= currentUserPrefs opaqueVariablePanelResizing or:[
    self opaqueTableColumnResize value ~= currentUserPrefs opaqueTableColumnResizing or:[
    self showAccelerators value ~= MenuView showAcceleratorKeys
    ]]]]]]]]]]
    )

    "Modified: / 16.12.2002 / 18:09:42 / penk"
! !

!AbstractSettingsApplication::OsiSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::OsiSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@_$RA@@@@@@@@@@@@@HED_ @@@@@@ U2+UX\@@@@@@@@@@H]U*52A@@@@ U*9^S-A  @@@@@@@HIT.HD4O8D@_%29^#6JZE"B@@@@@HIX-(@9!!&-\_"Z+
.+QKZ(0@J @@@@@*@K*5SV2B*2XDQ+":,XR5WP8@@@@@BDJ5.+V@.E4KEA46-+*5U9TVHRD!!HP<+JKV:-%*SG1@Y@R8@WYV)I@A/@@@SH D$@E>K*BP-$PUH
QH60)2U0[$:]KYPJN$RK,JX''[TFW]BB*)*4Z\K)[Q''L6''GD *JZ.HF4UV;H_**U6\+)%T7,WDUB3G:^%_E<@WB%RG*)8\+*BL(=Q#@(!!R!!2-_P5-@@AUNA!!4
BGV:.(IQ)I<LQS@R^VE([P@@(E9OZQT/[[*:-9=YO8M''S6B ZF4@@@@@[0@[M0I5.)!!!!(4NE@F<@&$&C@@@@@@@@G&PCBGYV&;@<!!P@@#$^P@@@@@@@@@FN@
[R<#+J2,PHT@%$2E@@@@@@@@@@BEA7>"I;B/''$*H%$"I@@@@@@@@@@@@$#D]^RF''*F]5$D2I@@@@@@@@@@@@@@BIKB<F(VHIHSNE@@@@@@@@@@@@@@@@@I$>
MVY7@@@@@@@@@@@@@@@@@@@@@@@@!!3Y9@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 0 0 7 7 7 12 12 12 20 20 20 23 23 23 24 24 24 28 28 28 30 30 30 32 32 32 35 35 35 40 40 40 41 41 41 43 43 43 45 45 45 48 47 48 50 49 50 51 50 51 52 52 52 54 53 54 55 54 55 56 56 56 58 57 58 58 58 58 59 59 59 60 59 60 60 60 60 61 61 61 62 62 62 66 65 66 66 66 66 67 66 67 68 67 68 69 69 69 70 69 70 70 70 70 71 71 71 72 71 72 73 73 73 74 73 74 75 75 75 76 75 76 76 76 76 77 76 77 78 78 78 79 79 79 80 80 80 85 84 85 86 84 86 86 85 86 87 86 87 87 87 87 88 87 88 89 88 89 89 89 89 90 88 90 90 89 90 93 91 93 93 93 93 94 92 94 94 93 94 96 94 96 97 96 97 98 97 98 99 98 99 99 99 99 100 99 100 100 100 100 102 102 102 103 103 103 104 103 104 104 104 104 105 105 105 106 106 106 108 107 108 109 109 109 110 110 110 111 110 111 113 113 113 114 113 114 114 114 114 115 115 115 116 116 116 117 115 117 118 118 118 120 120 120 121 121 121 122 121 122 122 122 122 123 122 123 123 123 123 124 124 124 125 125 125 127 127 127 128 128 128 129 129 129 130 130 130 131 131 131 132 131 132 132 132 132 133 132 133 134 134 134 135 135 135 136 136 136 137 137 137 138 138 138 140 139 140 142 142 142 147 147 147 151 151 151 153 153 153 154 154 154 155 155 155 156 155 156 156 156 156 159 159 159 164 163 164 165 165 165 167 167 167 168 168 168 170 170 170 172 172 172 174 174 174 175 174 175 177 177 177 178 178 178 181 181 181 182 182 182 183 183 183 185 185 185 189 189 189 190 190 190 191 191 191 192 192 192 194 192 194 194 194 194 195 195 195 196 196 196 198 196 198 199 198 199 200 200 200 201 200 201 201 201 201 202 201 202 202 202 202 203 203 203 204 204 204 205 204 205 205 205 205 206 205 206 206 206 206 209 209 209 210 210 210 211 211 211 212 212 212 213 212 213 213 213 213 214 214 214 215 213 215 215 215 215 216 216 216 217 216 217 217 217 217 218 217 218 219 219 219 221 219 221 222 221 222 224 222 224 224 223 224 225 223 225 225 224 225 225 225 225 226 224 226 226 225 226 227 226 227 228 226 228 229 228 229 231 231 231 232 231 232 235 234 235 237 237 237 239 239 239 241 241 241 244 244 244 247 247 247 248 248 248 255 255 255]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'G@C O G0_0O8?8_<?(W<?8_<???<=:^<???<???<???<_??<O??<O??<B?=\@?<8@?=0@?? @??@@_>@@O @@G@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'OSI Protocols Settings'
          #name: 'OSI Protocols Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 46 616 596)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel1'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel2'
                    #horizontalLayout: #fit
                    #verticalLayout: #center
                    #horizontalSpace: 3
                    #verticalSpace: 3
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'ACSE'
                          #name: 'Label1'
                          #translateLabel: true
                          #extent: #(#Point 600 22)
                        )
                       #(#ViewSpec
                          #name: 'Box1'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Log Errors'
                                #name: 'CheckBox1'
                                #layout: #(#LayoutFrame 5 0 0 0 -2 0.33 22 0)
                                #enableChannel: #osiACSEPresent
                                #model: #osiACSEErrorLogging
                                #translateLabel: true
                              )
                             #(#CheckBoxSpec
                                #label: 'Log Connections'
                                #name: 'CheckBox2'
                                #layout: #(#LayoutFrame 2 0.33 0 0 -2 0.66 22 0)
                                #enableChannel: #osiACSEPresent
                                #model: #osiACSEConnectionLogging
                                #translateLabel: true
                              )
                             #(#CheckBoxSpec
                                #label: 'Log Data Xfer'
                                #name: 'CheckBox3'
                                #layout: #(#LayoutFrame 2 0.66 0 0 -2 1 22 0)
                                #enableChannel: #osiACSEPresent
                                #model: #osiACSEDataLogging
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 27)
                        )
                       #(#ViewSpec
                          #name: 'Box9'
                          #extent: #(#Point 600 22)
                        )
                       #(#LabelSpec
                          #label: 'ROSE'
                          #name: 'Label2'
                          #translateLabel: true
                          #extent: #(#Point 600 22)
                        )
                       #(#ViewSpec
                          #name: 'Box4'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Log Errors'
                                #name: 'CheckBox4'
                                #layout: #(#LayoutFrame 5 0 0 0 -2 0.33 22 0)
                                #enableChannel: #osiROSEPresent
                                #model: #osiROSEErrorLogging
                                #translateLabel: true
                              )
                             #(#CheckBoxSpec
                                #label: 'Log Invoactions'
                                #name: 'CheckBox5'
                                #layout: #(#LayoutFrame 2 0.33 0 0 -2 0.66 22 0)
                                #enableChannel: #osiROSEPresent
                                #model: #osiROSEInvokationLogging
                                #translateLabel: true
                              )
                             #(#CheckBoxSpec
                                #label: 'Log Responses'
                                #name: 'CheckBox6'
                                #layout: #(#LayoutFrame 0 0.66 0 0 -2 1 22 0)
                                #enableChannel: #osiROSEPresent
                                #model: #osiROSEResponseLogging
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 25)
                        )
                       #(#ViewSpec
                          #name: 'Box6'
                          #extent: #(#Point 600 23)
                        )
                       #(#LabelSpec
                          #label: 'CMISE'
                          #name: 'Label3'
                          #translateLabel: true
                          #extent: #(#Point 600 22)
                        )
                       #(#ViewSpec
                          #name: 'Box7'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Log Errors'
                                #name: 'CheckBox7'
                                #layout: #(#LayoutFrame 2 0 0 0 -2 0.33 22 0)
                                #enableChannel: #osiCMISEPresent
                                #model: #osiCMISEErrorLogging
                                #translateLabel: true
                              )
                             #(#CheckBoxSpec
                                #label: 'Log Messages'
                                #name: 'CheckBox8'
                                #layout: #(#LayoutFrame 2 0.33 0 0 -2 0.66 22 0)
                                #enableChannel: #osiCMISEPresent
                                #model: #osiCMISEMessageLogging
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 22)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 250)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::OsiSettingsAppl methodsFor:'actions'!

basicSaveSettings

    self osiACSEPresent value ifTrue:[
        OSI::ACSE errorLogging:self osiACSEErrorLogging value.
        OSI::ACSE connectionLogging:self osiACSEConnectionLogging value.
        OSI::ACSE dataLogging:self osiACSEDataLogging value.
    ].
    self osiROSEPresent value ifTrue:[
        OSI::ROSE errorLogging:self osiROSEErrorLogging value.
        OSI::ROSE invocationLogging:self osiROSEInvokationLogging value.
        OSI::ROSE responseLogging:self osiROSEResponseLogging value.
    ].
    self osiCMISEPresent value ifTrue:[
        OSI::CMISE errorLogging:self osiCMISEErrorLogging value.
        OSI::CMISE messageLogging:self osiCMISEMessageLogging value.
    ].
!

help

    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/communicationsSettings.html'].
!

readSettings
    self osiACSEPresent value:(OSI::ACSE notNil and:[OSI::ACSE isLoaded]).
    self osiROSEPresent value:(OSI::ROSE notNil and:[OSI::ROSE isLoaded]).
    self osiCMISEPresent value:(OSI::CMISE notNil and:[OSI::CMISE isLoaded]).
    self osiACSEPresent value ifTrue:[
        self osiACSEErrorLogging value:OSI::ACSE errorLogging.
        self osiACSEConnectionLogging value:OSI::ACSE connectionLogging.
        self osiACSEDataLogging value:OSI::ACSE dataLogging
    ].
    self osiROSEPresent value ifTrue:[
        self osiROSEErrorLogging value:OSI::ROSE errorLogging.
        self osiROSEInvokationLogging value:OSI::ROSE invocationLogging.
        self osiROSEResponseLogging value:OSI::ROSE responseLogging
    ].
    self osiCMISEPresent value ifTrue:[
        self osiCMISEErrorLogging value:OSI::CMISE errorLogging.
        self osiCMISEMessageLogging value:OSI::CMISE messageLogging
    ].
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::OsiSettingsAppl methodsFor:'aspects'!

osiACSEConnectionLogging
    "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 ;-)"

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

osiACSEDataLogging
    "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 ;-)"

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

osiACSEErrorLogging
    "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 ;-)"

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

osiACSEPresent
    "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 ;-)"

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

osiCMISEErrorLogging
    "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 ;-)"

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

osiCMISEMessageLogging
    "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 ;-)"

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

osiCMISEPresent
    "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 ;-)"

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

osiROSEErrorLogging
    "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 ;-)"

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

osiROSEInvokationLogging
    "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 ;-)"

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

osiROSEPresent
    "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 ;-)"

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

osiROSEResponseLogging
    "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 ;-)"

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

!AbstractSettingsApplication::OsiSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ ((
        (self osiACSEPresent value and:[
        self osiACSEErrorLogging value ~= OSI::ACSE errorLogging or:[
        self osiACSEConnectionLogging value ~= OSI::ACSE connectionLogging or:[
        self osiACSEDataLogging value ~= OSI::ACSE dataLogging]]]) or:[
        self osiROSEPresent value and:[
            self osiROSEErrorLogging value ~= OSI::ROSE errorLogging or:[
            self osiROSEInvokationLogging value ~= OSI::ROSE invocationLogging or:[
            self osiROSEResponseLogging value ~= OSI::ROSE responseLogging]]]]) or:[
        (self osiCMISEPresent value) and:[
        self osiCMISEErrorLogging value ~= OSI::CMISE errorLogging or:[
        self osiCMISEMessageLogging value ~= OSI::CMISE messageLogging]]])
! !

!AbstractSettingsApplication::PrinterSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::PrinterSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@A@PDA@PDA@PDA@PDA@P@@@@@@@@@A@@@@@@@@@@@@@@@@@P@@@@@@@@@@@P@@@PDA@P@@@PDA@@D@@@@@@@@@
@P@@@@@@@@@@@@@@@@D@@@@@@@@@@@D@@PDA@@DA@@DA@@DA@PD@@@@@@@D@@@@@@@@@@@@@@@@AA@DD@P@@@@DA@PDA@PDA@PDA@PDAA@DD@PD@@@DDA@PD
A@PDA@PDA@PDA@DD@PTA@@@A@PDA@PDA@PDA@PDA@PDA@PTE@P@@@PTEAPTEAPTEAPTB@ HEAPDE@P@@@@DEAPTEAPTEAPTE@ HBAPTA@P@@@@@A@PDA@PDA
@PDA@PDA@PDA@P@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[255 255 255 0 0 0 255 255 0 129 129 129 194 194 194 105 133 190]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@??0A?? A?? C??@C??0G??8O??8_??8_??8_??0_?? _??@@@@@@@@@@@@@@@@@@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Printer Settings'
          #name: 'Printer Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 46 616 386)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel1'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#ViewSpec
                    #name: 'PrinterSelectBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Printer Type:'
                          #name: 'PrinterTypeLabel'
                          #layout: #(#LayoutFrame 0 0 5 0 150 0 27 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#ComboListSpec
                          #name: 'PrinterTypeComboList'
                          #layout: #(#LayoutFrame 150 0 5 0 -5 1 27 0)
                          #model: #printerTypeSelection
                          #comboList: #printerType
                          #useIndex: true
                        )
                       #(#LabelSpec
                          #label: 'Printer Command:'
                          #name: 'PrinterCommandLabel'
                          #layout: #(#LayoutFrame 0 0 45 0 150 0 67 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#ComboBoxSpec
                          #name: 'CommandComboBox'
                          #layout: #(#LayoutFrame 150 0 45 0 -5 1 67 0)
                          #model: #printCommand
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: false
                          #comboList: #printCommandList
                          #useIndex: false
                        )
                       #(#DividerSpec
                          #name: 'Separator1'
                          #layout: #(#LayoutFrame 0 0.0 -3 1 0 1.0 0 1)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 84)
                  )
                 #(#ViewSpec
                    #name: 'FormatBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Page Format:'
                          #name: 'PageFormatLabel'
                          #layout: #(#LayoutFrame 0 0 0 0 150 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#PopUpListSpec
                          #label: 'PopUp List'
                          #name: 'PageFormatPopUpList'
                          #layout: #(#LayoutFrame 150 0 0 0 300 0 22 0)
                          #tabable: true
                          #model: #pageFormat
                          #enableChannel: #enableFormat
                          #menu: #pageFormatList
                        )
                       #(#CheckBoxSpec
                          #label: 'Landscape'
                          #name: 'LandscapeCheckBox'
                          #layout: #(#LayoutFrame 380 0 0 0 -5 1 22 0)
                          #enableChannel: #enablelandscape
                          #model: #landscape
                          #translateLabel: true
                        )
                       #(#DividerSpec
                          #name: 'Separator5'
                          #layout: #(#LayoutFrame 0 0.0 -3 1 0 1.0 0 1)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 30)
                  )
                 #(#ViewSpec
                    #name: 'MarginBox'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#VerticalPanelViewSpec
                          #name: 'VerticalPanel2'
                          #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
                          #horizontalLayout: #fit
                          #verticalLayout: #center
                          #horizontalSpace: 3
                          #verticalSpace: 3
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#ViewSpec
                                #name: 'Box1'
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#LabelSpec
                                      #label: 'Top Margin:'
                                      #name: 'TopMarginLabel'
                                      #layout: #(#LayoutFrame 0 0 0 0 150 0 21 0)
                                      #translateLabel: true
                                      #adjust: #right
                                    )
                                   #(#InputFieldSpec
                                      #name: 'TopMarginEntryField'
                                      #layout: #(#LayoutFrame 150 0 0 0 250 0 21 0)
                                      #enableChannel: #enableMargins
                                      #model: #topMargin
                                      #type: #numberOrNil
                                      #acceptOnReturn: true
                                      #acceptOnTab: true
                                      #acceptOnLostFocus: true
                                      #acceptOnPointerLeave: true
                                    )
                                   #(#PopUpListSpec
                                      #label: 'PopUp List'
                                      #name: 'PopUpList2'
                                      #layout: #(#LayoutFrame -155 1 0 0 -5 1 21 0)
                                      #tabable: true
                                      #model: #selectedUnit
                                      #menu: #unitList
                                      #useIndex: true
                                    )
                                   )
                                 
                                )
                                #extent: #(#Point 600 24)
                              )
                             #(#ViewSpec
                                #name: 'Box2'
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#LabelSpec
                                      #label: 'Left Margin:'
                                      #name: 'LeftMarginLabel'
                                      #layout: #(#LayoutFrame 0 0 0 0 150 0 21 0)
                                      #translateLabel: true
                                      #adjust: #right
                                    )
                                   #(#InputFieldSpec
                                      #name: 'LeftMarginEntryField'
                                      #layout: #(#LayoutFrame 150 0 0 0 250 0 21 0)
                                      #enableChannel: #enableMargins
                                      #model: #leftMargin
                                      #type: #numberOrNil
                                      #acceptOnReturn: true
                                      #acceptOnTab: true
                                      #acceptOnLostFocus: true
                                      #acceptOnPointerLeave: true
                                    )
                                   )
                                 
                                )
                                #extent: #(#Point 600 24)
                              )
                             #(#ViewSpec
                                #name: 'Box3'
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#LabelSpec
                                      #label: 'Right Margin:'
                                      #name: 'RightMarginLabel'
                                      #layout: #(#LayoutFrame 0 0 0 0 150 0 21 0)
                                      #translateLabel: true
                                      #adjust: #right
                                    )
                                   #(#InputFieldSpec
                                      #name: 'RightMarginEntryField'
                                      #layout: #(#LayoutFrame 150 0 0 0 250 0 21 0)
                                      #enableChannel: #enableMargins
                                      #model: #rightMargin
                                      #type: #numberOrNil
                                      #acceptOnReturn: true
                                      #acceptOnTab: true
                                      #acceptOnLostFocus: true
                                      #acceptOnPointerLeave: true
                                    )
                                   )
                                 
                                )
                                #extent: #(#Point 600 24)
                              )
                             #(#ViewSpec
                                #name: 'Box4'
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#LabelSpec
                                      #label: 'Bottom Margin:'
                                      #name: 'BottomMarginLabel'
                                      #layout: #(#LayoutFrame 0 0 0 0 150 0 21 0)
                                      #translateLabel: true
                                      #adjust: #right
                                    )
                                   #(#InputFieldSpec
                                      #name: 'BottomMarginEntryField'
                                      #layout: #(#LayoutFrame 150 0 0 0 250 0 21 0)
                                      #enableChannel: #enableMargins
                                      #model: #bottomMargin
                                      #type: #numberOrNil
                                      #acceptOnReturn: true
                                      #acceptOnTab: true
                                      #acceptOnLostFocus: true
                                      #acceptOnPointerLeave: true
                                    )
                                   )
                                 
                                )
                                #extent: #(#Point 600 24)
                              )
                             )
                           
                          )
                        )
                       #(#DividerSpec
                          #name: 'Separator6'
                          #layout: #(#LayoutFrame 0 0.0 -3 1 0 1.0 0 1)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 100)
                  )
                 #(#ViewSpec
                    #name: 'Box5'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#CheckBoxSpec
                          #label: 'Color Printer'
                          #name: 'ColorPrinterCheckBox'
                          #layout: #(#LayoutFrame 0 0 0 0 599 0 21 0)
                          #enableChannel: #enableColorBox
                          #model: #supportsColor
                          #translateLabel: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 27)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::PrinterSettingsAppl methodsFor:'actions'!

basicSaveSettings

    Printer := self possiblePrinters at:(self printerTypeSelection value).
    Printer printCommand:self printCommand value.

    Printer supportsPageSizes ifTrue:[
        Printer pageFormat:(self pageFormat value).
        Printer landscape:(self landscape value).
    ].
    Printer supportsMargins ifTrue:[
        | unit |
        self selectedUnit value == 2 ifTrue:[
            unit := #mm
        ] ifFalse:[
            unit := #inch
        ].
        Printer topMargin:(UnitConverter convert:(self topMargin value) from:unit to:#inch).
        Printer leftMargin:(UnitConverter convert:(self leftMargin value) from:unit to:#inch).
        Printer rightMargin:(UnitConverter convert:(self rightMargin value) from:unit to:#inch).
        Printer bottomMargin:(UnitConverter convert:(self bottomMargin value) from:unit to:#inch).
    ].
    Printer supportsPostscript ifTrue:[
        Printer supportsColor:self supportsColor value.
    ].
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/printerSettings.html'].
!

readSettings
    self bottomMargin value:Printer bottomMargin.
    self landscape value:Printer landscape.
    self leftMargin value:Printer leftMargin.
    self rightMargin value:Printer rightMargin.
    self topMargin value:Printer topMargin.
    self printCommand value:Printer printCommand.
    self printerTypeSelection 
        value:(self possiblePrinters identityIndexOf:Printer).
    self supportsColor value:Printer supportsColor.
    self pageFormatList notEmpty ifTrue:[
        self pageFormat value:Printer pageFormat
    ].
    self printerTypeSelectionOrUnitListChanged.
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::PrinterSettingsAppl methodsFor:'aspects'!

bottomMargin

    bottomMargin isNil ifTrue:[
        bottomMargin := Printer bottomMargin asValue.
        bottomMargin onChangeSend:#evaluateModified to:self
    ].
    ^ bottomMargin.
!

enableColorBox

    enableColorBox isNil ifTrue:[
        enableColorBox := true asValue.
    ].
    ^ enableColorBox.
!

enableFormat

    enableFormat isNil ifTrue:[
        enableFormat := true asValue.
    ].
    ^ enableFormat.
!

enableMargins

    enableMargins isNil ifTrue:[
        enableMargins := true asValue.
    ].
    ^ enableMargins.
!

enablelandscape

    enablelandscape isNil ifTrue:[
        enablelandscape := true asValue.
    ].
    ^ enablelandscape.
!

landscape

    landscape isNil ifTrue:[
        landscape := Printer landscape asValue.
        landscape onChangeSend:#evaluateModified to:self
    ].
    ^ landscape.
!

leftMargin

    leftMargin isNil ifTrue:[
        leftMargin := Printer leftMargin asValue.
        leftMargin onChangeSend:#evaluateModified to:self
    ].
    ^ leftMargin.
!

pageFormat

    pageFormat isNil ifTrue:[
        self pageFormatList notEmpty ifTrue:[
            | index |
            (index := self pageFormatList indexOf:#a4) ~~ 0 ifTrue:[
                pageFormat := index asValue.
            ] ifFalse:[
                pageFormat := 1 asValue.
            ]
        ].
        pageFormat onChangeSend:#evaluateModified to:self
    ].
    ^ pageFormat.
!

pageFormatList

    pageFormatList isNil ifTrue:[
        pageFormatList := Printer defaultPageFormats asList.
    ].
    ^ pageFormatList.
!

printCommand

    printCommand isNil ifTrue:[
        printCommand := Printer printCommand asValue.
        printCommand onChangeSend:#evaluateModified to:self
    ].
    ^ printCommand.
!

printCommandList

    printCommandList isNil ifTrue:[
        printCommandList := self commandList asList.
    ].
    ^ printCommandList.
!

printerType

    printerType isNil ifTrue:[
        printerType := (self possiblePrinters collect:[:cls | cls printerTypeName]) asList.
        printerType onChangeSend:#evaluateModified to:self
    ].
    ^ printerType.
!

printerTypeSelection

    printerTypeSelection isNil ifTrue:[
        printerTypeSelection := (self possiblePrinters identityIndexOf:Printer) asValue.
"/       printerTypeSelection onChangeSend:#printerTypeSelectionChanged to:self.
        printerTypeSelection addDependent:self.
        printerTypeSelection changed.
        printerTypeSelection onChangeSend:#evaluateModified to:self
    ].
    ^ printerTypeSelection.
!

rightMargin

    rightMargin isNil ifTrue:[
        rightMargin := Printer rightMargin asValue.
        rightMargin onChangeSend:#evaluateModified to:self
    ].
    ^ rightMargin.
!

selectedUnit

    selectedUnit isNil ifTrue:[
        selectedUnit := 1 asValue.
        selectedUnit addDependent:self.
        selectedUnit changed.
        selectedUnit onChangeSend:#evaluateModified to:self
    ].
    ^ selectedUnit.
!

supportsColor

    supportsColor isNil ifTrue:[
        supportsColor := Printer supportsColor asValue.
        supportsColor onChangeSend:#evaluateModified to:self
    ].
    ^ supportsColor.
!

topMargin

    topMargin isNil ifTrue:[
        topMargin := Printer topMargin asValue.
        topMargin onChangeSend:#evaluateModified to:self
    ].
    ^ topMargin.
!

unitList

    unitList isNil ifTrue:[
        unitList := #('inch' 'mm') asList.
    ].
    ^ unitList.
! !

!AbstractSettingsApplication::PrinterSettingsAppl methodsFor:'change & update'!

printerTypeSelectionChanged

    | p hasPageSize hasMargins|
    self printerType selectionIndex ~~ 0 ifTrue:[
        p := self possiblePrinters at:(self printerType selectionIndex).
        hasPageSize := p supportsPageSizes. 
        hasMargins := p supportsMargins. 
    ] ifFalse:[
        hasPageSize := false.
        hasMargins := false.
    ].
!

printerTypeSelectionOrUnitListChanged

    | p hasPageSize hasMargins unit|

    self printerTypeSelection value ~~ 0 ifTrue:[
        p := self possiblePrinters at:(self printerTypeSelection value).
        hasPageSize := p supportsPageSizes. 
        hasMargins := p supportsMargins. 
    ] ifFalse:[
        hasPageSize := false.
        hasMargins := false.
    ].
    self enablelandscape value:hasPageSize.
    self enableFormat value:hasPageSize.
    hasPageSize ifTrue:[
        self pageFormat value:(p pageFormat).
        self landscape value:(p landscape).
    ] ifFalse:[ 
       self landscape value:false.
    ].
    hasMargins ifTrue:[
       self selectedUnit value == 2 ifTrue:[
           unit := #mm
       ] ifFalse:[
           unit := #inch
       ].

       self topMargin value:(UnitConverter convert:p topMargin from:#inch to:unit).
       self leftMargin value:(UnitConverter convert:p leftMargin from:#inch to:unit).
       self rightMargin value:(UnitConverter convert:p rightMargin from:#inch to:unit).
       self bottomMargin value:(UnitConverter convert:p bottomMargin from:#inch to:unit).

    ] ifFalse:[ 
    ].
    self enableMargins value:hasMargins.

    p notNil ifTrue:[ 
        | newCommandList |
        newCommandList := p defaultCommands.
        newCommandList notNil ifTrue:[
            self printCommandList contents:(newCommandList asList).
            self printCommandList changed.
        ].
        self printCommand value:(p printCommand).
    ].
    self enableColorBox value:p supportsPostscript.
    p supportsPostscript ifFalse:[
        self supportsColor value:false
    ] ifTrue:[
        self supportsColor value:(Printer supportsColor).
    ]
!

unitListChanged
!

update:something with:aParameter from:changedObject
    (changedObject == self selectedUnit or:[changedObject == self printerTypeSelection]) ifTrue:[
        self printerTypeSelectionOrUnitListChanged.
        ^ self.
    ].

    super update:something with:aParameter from:changedObject
! !

!AbstractSettingsApplication::PrinterSettingsAppl methodsFor:'initialization & release'!

postOpen
!

postOpenAsSubcanvasWith:aBuilder

    self postOpen.
    ^ super postOpenAsSubcanvasWith:aBuilder
!

postOpenWith:aBuilder

    self postOpen.
    ^ super postOpenWith:aBuilder
! !

!AbstractSettingsApplication::PrinterSettingsAppl methodsFor:'queries'!

commandList
    commandList isNil ifTrue:[
        commandList := resources at:'PRINT_COMMANDS' ifAbsent:nil.
        commandList isNil ifTrue:[
            commandList := PrinterStream defaultCommands.
            commandList isNil ifTrue:[
                commandList := #('lpr' 
                                 'lp' 
                                ) asOrderedCollection.
            ].
            (commandList includes:self printCommand value) not ifTrue:[
                commandList add:self printCommand value.
            ].
        ].
    ].
    ^ commandList
!

hasUnsavedChanges


    | printer unit|
    self selectedUnit value == 2 ifTrue:[
        unit := #mm
    ] ifFalse:[
        unit := #inch
    ].
    printer := self possiblePrinters at:(self printerTypeSelection value).
    ^ (
        printer ~= Printer or:[
        Printer printCommand ~= self printCommand value or:[
        (Printer supportsPageSizes and:[
            Printer pageFormat ~= self pageFormat value or:[
            Printer landscape ~= (self landscape value) or:[
        ]]]) or:[
        (Printer supportsMargins and:[
            Printer topMargin ~= ((UnitConverter convert:(self topMargin value asFloat) from:unit to:#inch) asFloat) or:[
            Printer leftMargin ~= ((UnitConverter convert:(self leftMargin value asFloat) from:unit to:#inch) asFloat) or:[
            Printer rightMargin ~= ((UnitConverter convert:(self rightMargin value asFloat) from:unit to:#inch) asFloat) or:[
            Printer bottomMargin ~= ((UnitConverter convert:(self bottomMargin value asFloat) from:unit to:#inch) asFloat) or:[
        ]]]]]) or:[
        Printer supportsPostscript and:[
            Printer supportsColor ~= self supportsColor value
        ]]]]]
    )
!

possiblePrinters
    possiblePrinters isNil ifTrue:[
        possiblePrinters := PrinterStream withAllSubclasses asArray.
    ].
    ^ possiblePrinters
! !

!AbstractSettingsApplication::ProcessorSchedulerSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::ProcessorSchedulerSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@LC@0L@@@@@@@@@@@@@@@@@@@@C@0LB@PDB@0LC@@@@@@@@@@@@@@@C@ HBA@DAA@HB@ L@@@@@@@@@
@@@C@ PDA@PA@PPDA@PB@0@@@@@@@@@C@ PDA@PDA@PDA@PDA@HC@@@@@@@C@ PDA@PDA@PDA@PDA@PD@ L@@@@@@0HDA@PDA@PDA@PDA@PDA@HC@@@@@@LB
A@PDA@PDA@PD@PPDA@PB@0@@@@LBA@PDA@PDA@PD@PPDA@PDA@HC@@@C@ PDA@PDA@PA@PPDA@PDA@PB@0@@@0HDA@PDA@PD@PDDA@PDA@PD@ L@@@LBA@PD
A@PDA@PD@PPDA@PDA@HC@@@@@0HDA@PDA@PDA@PAA@PDA@HC@@@@@@LBA@PDA@PDA@PDA@DDA@PB@0@@@@@C@ PDA@PDA@PDA@PD@PPD@ L@@@@@@@LBA@PD
A@PDA@PDA@PD@ L@@@@@@@@@@0HDA@PDA@PDA@PD@ L@@@@@@@@@@@@C@ HBA@PDA@HB@ L@@@@@@@@@@@@@@@LC@0HB@ HC@0L@@@@@@@@@@@@@@@@@@@@C
@0LC@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 128 128 128 128 128 192 192 192 255 255 255]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@G @@?<@A?>@C??@G?? O??0O??0O??0_??8_??8_??8_??8O??0O??0O??0G?? C??@A?>@@?<@@G @@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Processor and Scheduler Settings'
          #name: 'Processor and Scheduler Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 616 362)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #topSpace
              #horizontalSpace: 3
              #verticalSpace: 5
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#CheckBoxSpec
                    #label: 'Preemptive Scheduling'
                    #name: 'CheckBox11'
                    #model: #preemptive
                    #translateLabel: true
                    #extent: #(#Point 600 22)
                  )
                 #(#ViewSpec
                    #name: 'Box2'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#CheckBoxSpec
                          #label: 'Dynamic Priorities'
                          #name: 'CheckBox12'
                          #layout: #(#LayoutFrame 30 0.0 0 0 0 1.0 22 0)
                          #enableChannel: #preemptive
                          #model: #dynamicPrios
                          #translateLabel: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 23)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::ProcessorSchedulerSettingsAppl methodsFor:'actions'!

basicSaveSettings

    Processor isTimeSlicing ~~ self preemptive value ifTrue:[
        self preemptive value ifTrue:[
            Processor startTimeSlicing
        ] ifFalse:[
            Processor stopTimeSlicing
        ]
    ].
    Processor supportDynamicPriorities ~~ self dynamicPrios value ifTrue:[
        Processor supportDynamicPriorities:self dynamicPrios value
    ].
!

help

    self warn:'no help available here'.
"/    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/editSettings.html'].
!

readSettings
    self preemptive value:Processor isTimeSlicing.
    self dynamicPrios value:Processor supportDynamicPriorities.
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::ProcessorSchedulerSettingsAppl methodsFor:'aspects'!

dynamicPrios
    "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 ;-)"

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

preemptive
    "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 ;-)"

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

!AbstractSettingsApplication::ProcessorSchedulerSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ (
        self preemptive value ~= Processor isTimeSlicing or:[
        self dynamicPrios value ~= Processor supportDynamicPriorities]
    )
! !

!AbstractSettingsApplication::RDoItServerSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::RDoItServerSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@JB (JB (JB (JB (JB (I2\@@@@@
@B (JB (JB (JB (JB (JB\''@@@@@@@(JA@ZFA YE@,KC@,KA0P''I1T@@@@@JB RH2D!!HRD HA(MCP\DI2\U@@@@@B (GRT#H2D"H2L^C0<HAB\''EP@@@@@(
JA4%H2L!!H"L#G <OB@P''I1T@@@@@JB ZH2H"H"H)JP@@E!!XWJ"\U@@@@@B (C!!$"H"$)JR,)@@@@E2X''EP@@@@@(JA@WH"$+@B$,@B0)JP@&I1T@@@@@JB P
E1 )KB,,J20+JR$@I"\U@@@@@B (A!!DXJR,,JP@+J @@@BX''EP@@@@@''I2\''JR,,JR0)@B,,JR$@I1T@@@@@I2\''I2$,J2$+JP@,J2$)@B\U@@@@@@@@EQTB
JR0+JP@,JP@@@@HUEP@@@@@@@@@@@B$+KB,,J20)JP@@@@@@@@@@@@@@@@@)K@@)J0@+JR$@@@@@@@@@@@@@@@@@@@@@JR0)@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 60 78 83 61 77 82 63 79 84 63 81 86 66 83 87 66 84 89 66 85 91 67 86 92 68 86 91 69 87 92 69 88 94 70 90 95 71 91 96 71 92 98 72 93 99 73 94 100 74 92 97 74 95 101 75 93 98 75 96 102 76 76 76 76 97 103 77 98 104 77 99 106 79 101 108 80 103 109 81 104 110 82 105 111 83 106 112 83 107 114 86 110 117 87 111 118 88 113 121 89 114 122 90 116 123 91 117 124 92 118 125 126 126 126 127 127 127 139 139 139 131 129 0 131 129 131 255 255 0 255 255 255]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@G??0G??0G??8G??8G??8G??8G??8G??8G??8G??8G??8G??8G??8A??8@O?@@O?@@G>@@A0@@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'RDoIt Server Settings'
          #name: 'RDoIt Server Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 46 616 596)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel1'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel2'
                    #horizontalLayout: #fit
                    #verticalLayout: #center
                    #horizontalSpace: 3
                    #verticalSpace: 3
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#ViewSpec
                          #name: 'Box1'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Remote doits enabled'
                                #name: 'CheckBox1'
                                #layout: #(#LayoutFrame 5 0 0 0 -5 1 22 0)
                                #enableChannel: #hasRDoitServerClass
                                #model: #rDoitsEnabled
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 25)
                        )
                       #(#ViewSpec
                          #name: 'Box2'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#LabelSpec
                                #label: 'Port:'
                                #name: 'Label2'
                                #layout: #(#LayoutFrame 5 0 0 0 150 0 22 0)
                                #translateLabel: true
                                #adjust: #right
                              )
                             #(#InputFieldSpec
                                #name: 'EntryField1'
                                #layout: #(#LayoutFrame 150 0 0 0 -5 1 22 0)
                                #enableChannel: #rDoitsEnabled
                                #model: #rDoitServerPort
                                #type: #number
                                #acceptOnReturn: true
                                #acceptOnTab: true
                                #acceptOnLostFocus: true
                                #acceptOnPointerLeave: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 25)
                        )
                       #(#ViewSpec
                          #name: 'Box3'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Log errors'
                                #name: 'CheckBox2'
                                #layout: #(#LayoutFrame 25 0 0 0 -5 1 22 0)
                                #enableChannel: #rDoitsEnabled
                                #model: #rDoitErrorLogging
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 25)
                        )
                       #(#ViewSpec
                          #name: 'Box4'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Log requests'
                                #name: 'CheckBox3'
                                #layout: #(#LayoutFrame 25 0 0 0 -5 1 22 0)
                                #enableChannel: #rDoitsEnabled
                                #model: #rDoitLogging
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 24)
                        )
                       #(#ViewSpec
                          #name: 'Box5'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Debug errors'
                                #name: 'CheckBox4'
                                #layout: #(#LayoutFrame 25 0 0 0 -5 1 22 0)
                                #enableChannel: #rDoitsEnabled
                                #model: #rDoitErrorDebugging
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 600 23)
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 300)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::RDoItServerSettingsAppl methodsFor:'actions'!

basicSaveSettings

    |rDoits|

    RDoItServer defaultPortNumber:self rDoitServerPort value.
    RDoItServer logging:self rDoitLogging value.
    RDoItServer errorLogging:self rDoitErrorLogging value.
    RDoItServer errorCatching:(self rDoitErrorDebugging value not).
    rDoits := self rDoitsEnabled value.
    rDoits ~~ RDoItServer serverRunning ifTrue:[
        rDoits ifFalse:[
            RDoItServer stop
        ] ifTrue:[
            RDoItServer start.
            "/ must wait a bit; give it a chance to
            "/ really start (before checking)
            Delay waitForSeconds:0.5.
            RDoItServer serverRunning ifFalse:[
                self warn:'RDoit startup failed (see stderr).'
            ]
        ]
    ].
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/communicationsSettings.html'].
!

readSettings
    (self hasRDoitServer and:[RDoItServer isLoaded]) ifTrue:[
        self rDoitsEnabled value:RDoItServer serverRunning.
        self rDoitLogging value:RDoItServer isLogging.
        self rDoitErrorLogging value:RDoItServer isErrorLogging.
        self rDoitErrorDebugging value:RDoItServer isErrorCatching not.
        self rDoitServerPort value:RDoItServer defaultPortNumber
    ] ifFalse:[
        self rDoitsEnabled value:false.
        self rDoitLogging value:false.
        self rDoitErrorLogging value:false.
        self rDoitErrorDebugging value:false.
        self rDoitServerPort value:nil
    ].
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::RDoItServerSettingsAppl methodsFor:'aspects'!

rDoitErrorDebugging

    rDoitErrorDebugging isNil ifTrue:[
        rDoitErrorDebugging := true asValue.
        rDoitErrorDebugging onChangeSend:#evaluateModified to:self
    ].
    ^ rDoitErrorDebugging.
!

rDoitErrorLogging

    rDoitErrorLogging isNil ifTrue:[
        rDoitErrorLogging := true asValue.
        rDoitErrorLogging onChangeSend:#evaluateModified to:self
    ].
    ^ rDoitErrorLogging.
!

rDoitLogging

    rDoitLogging isNil ifTrue:[
        rDoitLogging := true asValue.
        rDoitLogging onChangeSend:#evaluateModified to:self
    ].
    ^ rDoitLogging.
!

rDoitServerPort

    rDoitServerPort isNil ifTrue:[
        rDoitServerPort := ValueHolder new.
        rDoitServerPort onChangeSend:#evaluateModified to:self
    ].
    ^ rDoitServerPort.
!

rDoitsEnabled

    rDoitsEnabled isNil ifTrue:[
        rDoitsEnabled := true asValue.
        rDoitsEnabled onChangeSend:#rDoitsEnabledChanged to:self
    ].
    ^ rDoitsEnabled.
! !

!AbstractSettingsApplication::RDoItServerSettingsAppl methodsFor:'change & update'!

rDoitsEnabledChanged
    self evaluateModified.
    self rDoitsEnabled value ifTrue:[
        RDoItServer autoload.
        rDoitServerPort value isNil ifTrue:[
            rDoitServerPort value:(RDoItServer defaultPortNumber).
        ]
    ].
!

update:something with:aParameter from:changedObject
    changedObject == self rDoitsEnabled ifTrue:[
        self rDoitsEnabledChanged.
        ^ self.
    ].

    super update:something with:aParameter from:changedObject
! !

!AbstractSettingsApplication::RDoItServerSettingsAppl methodsFor:'initialization & release'!

postOpen
!

postOpenAsSubcanvasWith:aBuilder

    self postOpen.
    ^ super postOpenAsSubcanvasWith:aBuilder
!

postOpenWith:aBuilder

    self postOpen.
    ^ super postOpenWith:aBuilder
! !

!AbstractSettingsApplication::RDoItServerSettingsAppl methodsFor:'queries'!

hasRDoitServer

    ^ RDoItServer notNil and:[RDoItServer isLoaded]
!

hasRDoitServerClass
    ^ RDoItServer notNil
!

hasUnsavedChanges

    (self hasRDoitServer and:[RDoItServer isLoaded]) ifTrue:[
        ^ (
            self rDoitsEnabled value ~= RDoItServer serverRunning or:[
            RDoItServer serverRunning and:[
            (self rDoitLogging value ~= RDoItServer isLogging or:[
            self rDoitErrorLogging value ~= RDoItServer isErrorLogging or:[
            self rDoitErrorDebugging value ~= RDoItServer isErrorCatching not or:[
            self rDoitServerPort value ~= RDoItServer defaultPortNumber]]])]]
        )
    ].
    ^ false
! !

!AbstractSettingsApplication::STCCompilerSettingsAppl class methodsFor:'defaults'!

stcCompilationDemoStrings

    ^ #('never')
!

stcCompilationFullVersionStrings

    ^ #('always' 'primitive code only' 'never')
!

stcCompilationOptions

    ^ #( always default never)
! !

!AbstractSettingsApplication::STCCompilerSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::STCCompilerSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@H@@@@@@@@@@@@@@@@@@@@@@@@@@@@B@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@H@
@@DA@PD@@PDA@@DA@PD@@PDA@@@B@@@A@PDA@@DA@P@A@PDA@@DA@P@@@ @@@P@@@P@A@@D@@P@@@P@A@@D@@@H@@@DA@PD@@PDA@@DA@PD@@PDA@@@B@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@ @@@PDA@PDA@PDA@PDA@PDA@PD@@@H@@@DA@@@@@P@@@@@@@P@@@@DA@@@B@@@A@@DA@PDA@P@A@P@A@PD@@P@@@ @@@P@A
@PDA@PD@@PD@@PDA@PD@@@H@@@DA@@@A@PDA@@DA@@DA@PDA@@@B@@@A@PDA@@DA@P@A@P@A@PDA@P@@@ @@@PDA@P@A@PD@@PD@@PDA@@D@@@H@@@D@@@@A
@PDA@@DA@P@@@@DA@@@B@@@A@PDA@PDA@PDA@PDA@PDA@P@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 255 255 255 0 0 0]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8O??8@@@@@@@@@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'STC Compiler Settings'
          #name: 'STC Compiler Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 14 46 614 660)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#ViewSpec
                    #name: 'Box11'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'STC Compilation to Machine Code'
                          #name: 'Label11'
                          #layout: #(#LayoutFrame 0 0 0 0 200 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#PopUpListSpec
                          #label: 'PopUp List'
                          #name: 'StcCompilation'
                          #layout: #(#LayoutFrame 201 0 0 0 -5 1 22 0)
                          #tabable: true
                          #model: #stcCompilationSelection
                          #enableChannel: #canLoadBinaries
                          #menu: #stcCompilationList
                          #useIndex: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 29)
                  )
                 #(#ViewSpec
                    #name: 'Box1'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'STC Command:'
                          #name: 'Label1'
                          #layout: #(#LayoutFrame 5 0 0 0 132 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'EntryField1'
                          #layout: #(#LayoutFrame 139 0 0 0 -5 1 22 0)
                          #enableChannel: #canLoadBinaries
                          #model: #stc
                          #acceptOnLeave: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 35)
                  )
                 #(#ViewSpec
                    #name: 'Box2'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'STC Options:'
                          #name: 'Label2'
                          #layout: #(#LayoutFrame 5 0 0 0 132 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'EntryField2'
                          #layout: #(#LayoutFrame 139 0 0 0 -5 1 22 0)
                          #enableChannel: #canLoadBinaries
                          #model: #stcOptions
                          #acceptOnLeave: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 35)
                  )
                 #(#ViewSpec
                    #name: 'Box3'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'CC Command:'
                          #name: 'Label3'
                          #layout: #(#LayoutFrame 5 0 0 0 132 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'EntryField3'
                          #layout: #(#LayoutFrame 139 0 0 0 -5 1 22 0)
                          #enableChannel: #canLoadBinaries
                          #model: #cc
                          #acceptOnLeave: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 35)
                  )
                 #(#ViewSpec
                    #name: 'Box4'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'CC Options:'
                          #name: 'Label4'
                          #layout: #(#LayoutFrame 5 0 0 0 132 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'EntryField4'
                          #layout: #(#LayoutFrame 139 0 0 0 -5 1 22 0)
                          #enableChannel: #canLoadBinaries
                          #model: #ccOptions
                          #acceptOnLeave: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 35)
                  )
                 #(#ViewSpec
                    #name: 'Box5'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Include Directories:'
                          #name: 'Label5'
                          #layout: #(#LayoutFrame 5 0 0 0 132 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'EntryField5'
                          #layout: #(#LayoutFrame 139 0 0 0 -5 1 22 0)
                          #enableChannel: #canLoadBinaries
                          #model: #stcIncludes
                          #acceptOnLeave: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 35)
                  )
                 #(#ViewSpec
                    #name: 'Box6'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Defines:'
                          #name: 'Label6'
                          #layout: #(#LayoutFrame 5 0 0 0 132 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'EntryField6'
                          #layout: #(#LayoutFrame 139 0 0 0 -5 1 22 0)
                          #enableChannel: #canLoadBinaries
                          #model: #stcDefines
                          #acceptOnLeave: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 34)
                  )
                 #(#ViewSpec
                    #name: 'Box7'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Link Command:'
                          #name: 'Label7'
                          #layout: #(#LayoutFrame 5 0 0 0 132 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'EntryField7'
                          #layout: #(#LayoutFrame 139 0 0 0 -5 1 22 0)
                          #enableChannel: #canLoadBinaries
                          #model: #linkCommand
                          #acceptOnLeave: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 33)
                  )
                 #(#ViewSpec
                    #name: 'Box8'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Link Arguments:'
                          #name: 'Label8'
                          #layout: #(#LayoutFrame 5 0 0 0 132 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'EntryField8'
                          #layout: #(#LayoutFrame 139 0 0 0 -5 1 22 0)
                          #enableChannel: #canLoadBinaries
                          #model: #linkArgs
                          #acceptOnLeave: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 32)
                  )
                 #(#ViewSpec
                    #name: 'Box9'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'C-Libraries:'
                          #name: 'Label9'
                          #layout: #(#LayoutFrame 5 0 0 0 132 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'EntryField9'
                          #layout: #(#LayoutFrame 139 0 0 0 -5 1 22 0)
                          #enableChannel: #canLoadBinaries
                          #model: #stcLibraries
                          #acceptOnLeave: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 31)
                  )
                 #(#ViewSpec
                    #name: 'Box10'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'STC Library Path:'
                          #name: 'Label10'
                          #layout: #(#LayoutFrame 5 0 0 0 132 0 22 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'EntryField10'
                          #layout: #(#LayoutFrame 139 0 0 0 -5 1 22 0)
                          #enableChannel: #enableStcLibraryPath
                          #model: #stcLibraryPath
                          #acceptOnLeave: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 600 30)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::STCCompilerSettingsAppl methodsFor:'actions'!

basicSaveSettings

    Compiler stcCompilation:(self class stcCompilationOptions at:self stcCompilationSelection value).
    Compiler stcCompilationIncludes:self stcIncludes value.
    Compiler stcCompilationDefines:self stcDefines value.
    Compiler stcCompilationOptions:self stcOptions value.
    Compiler ccCompilationOptions:self ccOptions value.
    Compiler ccPath:self cc value.
    self stc value ~= Compiler stcPath ifTrue:[
        Compiler stcPath:self stc value
    ].
    ObjectFileLoader linkCommand:self linkCommand value.
    ObjectFileLoader linkArgs:self linkArgs value.
    ObjectFileLoader notNil ifTrue:[
        self stcLibraries value notNil ifTrue:[
            ObjectFileLoader searchedLibraries:(self stcLibraries value asCollectionOfWords).
        ].
        stcLibraryPath notNil ifTrue:[
            ObjectFileLoader libPath:(self stcLibraryPath value).
        ]
    ].
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/compilerSettings.html'].
!

readSettings
    self canLoadBinaries 
        value:(ObjectFileLoader notNil and:[ObjectFileLoader canLoadObjectFiles]).
    self stcIncludes value:Compiler stcCompilationIncludes.
    self stcDefines value:Compiler stcCompilationDefines.
    self stcOptions value:Compiler stcCompilationOptions.
    self ccOptions value:Compiler ccCompilationOptions.
    self cc value:Compiler ccPath.
    self stc value:Compiler stcPath.
    self linkCommand value:ObjectFileLoader linkCommand.
    self linkArgs value:ObjectFileLoader linkArgs.
    ObjectFileLoader notNil ifTrue:[
        |t|

        (t := ObjectFileLoader searchedLibraries) notNil ifTrue:[
            self stcLibraries value:(String fromStringCollection:t separatedBy:' ')
        ].
        (t := ObjectFileLoader libPath) notNil ifTrue:[
            self stcLibraryPath value:t
        ]
    ].
    self thisIsADemoVersion ifTrue:[
        self stcCompilationSelection value:(self class stcCompilationOptions 
                    indexOf:(Compiler stcCompilation)
                    ifAbsent:2)
    ] ifFalse:[
        self stcCompilationSelection value:2
    ].
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::STCCompilerSettingsAppl methodsFor:'aspects'!

canLoadBinaries

    canLoadBinaries isNil ifTrue:[
        canLoadBinaries := (ObjectFileLoader notNil and:[ObjectFileLoader canLoadObjectFiles]) asValue.
    ].
    ^ canLoadBinaries.
!

cc

    cc isNil ifTrue:[
        cc := ValueHolder new.
        cc onChangeSend:#evaluateModified to:self.
    ].
    ^ cc.
!

ccOptions

    ccOptions isNil ifTrue:[
        ccOptions := ValueHolder new.
        ccOptions onChangeSend:#evaluateModified to:self.
    ].
    ^ ccOptions.
!

enableStcLibraryPath

    ^ (ObjectFileLoader libPath notNil and:[self canLoadBinaries])
!

linkArgs

    linkArgs isNil ifTrue:[
        linkArgs := ValueHolder new.
        linkArgs onChangeSend:#evaluateModified to:self.
    ].
    ^ linkArgs.
!

linkCommand

    linkCommand isNil ifTrue:[
        linkCommand := ValueHolder new.
        linkCommand onChangeSend:#evaluateModified to:self.
    ].
    ^ linkCommand.
!

stc

    stc isNil ifTrue:[
        stc := ValueHolder new.
        stc onChangeSend:#evaluateModified to:self.
    ].
    ^ stc.
!

stcCompilationList

    stcCompilationList isNil ifTrue:[
        self thisIsADemoVersion ifTrue:[
            stcCompilationList := (resources array:(self class stcCompilationDemoStrings)) asList.
        ] ifFalse:[
            stcCompilationList := (resources array:(self class stcCompilationFullVersionStrings)) asList.
        ]
    ].
    ^ stcCompilationList.
!

stcCompilationSelection

    stcCompilationSelection isNil ifTrue:[
        self thisIsADemoVersion ifTrue:[
            stcCompilationSelection := (self class stcCompilationOptions indexOf:(Compiler stcCompilation) ifAbsent:2) asValue.
        ] ifFalse:[
            stcCompilationSelection := 2 asValue.
        ].
        stcCompilationSelection onChangeSend:#evaluateModified to:self.
    ].
    ^ stcCompilationSelection.
!

stcDefines

    stcDefines isNil ifTrue:[
        stcDefines := ValueHolder new.
        stcDefines onChangeSend:#evaluateModified to:self.
    ].
    ^ stcDefines.
!

stcIncludes

    stcIncludes isNil ifTrue:[
        stcIncludes := ValueHolder new.
        stcIncludes onChangeSend:#evaluateModified to:self.
    ].
    ^ stcIncludes.
!

stcLibraries

    stcLibraries isNil ifTrue:[
        stcLibraries := ValueHolder new.
        stcLibraries onChangeSend:#evaluateModified to:self.
    ].
    ^ stcLibraries.
!

stcLibraryPath

    stcLibraryPath isNil ifTrue:[
        stcLibraryPath := ValueHolder new.
        stcLibraryPath onChangeSend:#evaluateModified to:self.
    ].
    ^ stcLibraryPath.
!

stcOptions

    stcOptions isNil ifTrue:[
        stcOptions := ValueHolder new.
        stcOptions onChangeSend:#evaluateModified to:self.
    ].
    ^ stcOptions.
! !

!AbstractSettingsApplication::STCCompilerSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    | searchedLibs |
    searchedLibs := ObjectFileLoader searchedLibraries.
    ^ (
        ((Compiler stcCompilation) ~= (self class stcCompilationOptions at:self stcCompilationSelection value)) or:[
        ((ObjectFileLoader notNil and:[ObjectFileLoader canLoadObjectFiles]) ~= self canLoadBinaries value ) or:[
        ((Compiler stcCompilationIncludes) ~= self stcIncludes value) or:[
        ((Compiler stcCompilationDefines) ~= self stcDefines value) or:[
        ((Compiler stcCompilationOptions) ~= self stcOptions value) or:[
        ((Compiler ccCompilationOptions) ~= self ccOptions value) or:[
        ((Compiler ccPath) ~= self cc value) or:[
        ((Compiler stcPath) ~= self stc value) or:[
        ((ObjectFileLoader linkCommand) ~= self linkCommand value) or:[
        ((ObjectFileLoader linkArgs) ~= self linkArgs value) or:[
        ObjectFileLoader notNil and:[
            ((searchedLibs notNil and:[
                (String fromStringCollection:searchedLibs separatedBy:' ') ~= self stcLibraries value
            ]) or:[
            (ObjectFileLoader libPath notNil and:[
                ObjectFileLoader libPath ~= self stcLibraryPath value 
            ])]) 
        ]]]]]]]]]]] 
    )
!

thisIsADemoVersion

    ^ Smalltalk releaseIdentification = 'ST/X_free_demo_vsn'
! !

!AbstractSettingsApplication::SourceCodeFormatSettingsAppl class methodsFor:'defaults'!

exampleText

    ^  'methodSelector:methodArg
    "method comment:
     some stupid code to show the current settings"

    |index|

    "/ another comment ...
    self at:index.                      "/ a message
    self at:index put:methodArg.        "/ a two arg message
    self from:1 to:index put:methodArg. "/ a three arg message
    methodArg ifTrue:[
        Transcript showCR:''hello''.      "/ condition
    ].
    methodArg ifTrue:[
        Transcript showCR:''hello''.      "/ condition
    ] ifFalse:[
        Transcript showCR:''world''.      
    ].
    [methodArg] whileTrue:[
        Transcript showCR:''hello''.      "/ looping
    ].
    [self aVeryLongConditionBlock and:[self toMakeBlockLonger]] whileTrue:[
        Transcript showCR:''hello''.      "/ long blocks
    ].
    methodArg do:[:element |
        Transcript showCR:''hello''.      "/ looping
    ].
    1 to:methodArg size do:[:index |
        Transcript showCR:''hello''.      "/ looping
    ].
    methodArg keysAndValuesDo:[:index |
        Transcript showCR:''hello''.      "/ looping
    ].
    Object errorSignal handle:[:ex |      
        ex return                         
    ] do:[                                "/ exception handling
        self someAction                   "/ blocks
    ].
    ^ self.
'.
! !

!AbstractSettingsApplication::SourceCodeFormatSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::EditSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@JB (JB (JB (JB (JB (@@@TE@@@@B (IBP$IBPXIBP$IBP$IAPTE@0@@
@@(JBP$IBP$FBP$IBP$IAPTE@0L@@@@JB $IBP$IA $IBP$IBPTEAPLC@@@@B (FA XFA XFA XFA TE@0LC@0@@@@(JBP$IBP$FBP$IAPTE@0LC@0P@@@@J
B $IBP$IA $IAPTE@0LC@0PK@@@@B (IBP$IBPXIBPTEAPLC@0LDB0@@@@(JA XFA XFA TH@0LC@0PD@ @@@@@JB $IBP$I@@ HB@LC@0PB@ @@@@@@B (I
BP$IBPXHB@ HB@ K@PD@@@@@@@(JA XFA @HB@ HB@ F@@DA@@@@@@@JB XFA X@B@ HB@ FA @A@P@@@@@@B (IBP$I@P HB@XFA (I@PD@@@@@@@(JBP$I
@PHKA XJBP$IBPDA@@@@@@@JB @@@@D@@@@@@@@@@@@A@P@@@@@@B (@@@D@@@@@@@@@@@@@@PD@@@@@@@(JBP$IBP$@BP$IBP$IBPDA@@@@@@HA@PDA@PDA
@PDA@PDA@PDA@P@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[160 160 160 0 0 0 48 48 48 255 128 0 192 88 0 255 168 88 195 195 195 88 88 88 255 220 168 255 255 255 220 220 220 64 0 0]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@G??LG??<G??<G??<G??<G??<G??<G??<G??8G??0G??0G??0G??0G??0G??0G??0G??0G??0O??0@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Code Format Settings'
          #name: 'Code Format Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 620 718)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel3'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #topSpace
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel2'
                    #horizontalLayout: #fitSpace
                    #verticalLayout: #topSpace
                    #horizontalSpace: 5
                    #verticalSpace: 10
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#CheckBoxSpec
                          #label: 'Auto Format'
                          #name: 'CheckBox2'
                          #model: #autoFormat
                          #translateLabel: true
                          #extent: #(#Point 594 22)
                        )
                       #(#ViewSpec
                          #name: 'Box14'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#LabelSpec
                                #label: 'Sample Output:'
                                #name: 'Label3'
                                #layout: #(#LayoutFrame 0 0 0 0 0 1 22 0)
                                #style: #(#FontDescription #helvetica #medium #roman 12)
                                #translateLabel: true
                                #adjust: #left
                              )
                             #(#TextEditorSpec
                                #name: 'TextEditor3'
                                #layout: #(#LayoutFrame 0 0 22 0 0 1 300 0)
                                #model: #editorText
                                #hasHorizontalScrollBar: true
                                #hasVerticalScrollBar: true
                                #isReadOnly: true
                                #postBuildCallback: #postBuildTextEditor:
                              )
                             )
                           
                          )
                          #extent: #(#Point 594 300)
                        )
                       #(#VerticalPanelViewSpec
                          #name: 'VerticalPanel1'
                          #horizontalLayout: #fit
                          #verticalLayout: #bottom
                          #horizontalSpace: 3
                          #verticalSpace: 3
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#ViewSpec
                                #name: 'Box1'
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#CheckBoxSpec
                                      #label: 'Space around Temporaries'
                                      #name: 'CheckBox3'
                                      #layout: #(#LayoutFrame 0 0 0 0 250 0 22 0)
                                      #model: #spaceAroundTemporaries
                                      #translateLabel: true
                                    )
                                   #(#CheckBoxSpec
                                      #label: 'Blank line after local Var Declaration'
                                      #name: 'CheckBox4'
                                      #layout: #(#LayoutFrame 250 0 0 0 0 1 22 0)
                                      #model: #emptyLineAfterTemporaries
                                      #translateLabel: true
                                    )
                                   )
                                 
                                )
                                #extent: #(#Point 594 22)
                              )
                             #(#ViewSpec
                                #name: 'Box11'
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#CheckBoxSpec
                                      #label: 'Space after ''^'''
                                      #name: 'CheckBox5'
                                      #layout: #(#LayoutFrame 0 0 0 0 250 0 22 0)
                                      #model: #spaceAfterReturnToken
                                      #translateLabel: true
                                    )
                                   #(#CheckBoxSpec
                                      #label: 'Space after '':'' in Keywords'
                                      #name: 'CheckBox6'
                                      #layout: #(#LayoutFrame 250 0 0 0 -5 1 22 0)
                                      #model: #spaceAfterKeywordSelector
                                      #translateLabel: true
                                    )
                                   )
                                 
                                )
                                #extent: #(#Point 594 22)
                              )
                             #(#ViewSpec
                                #name: 'Box12'
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#CheckBoxSpec
                                      #label: 'Block Args on new Line'
                                      #name: 'CheckBox7'
                                      #layout: #(#LayoutFrame 250 0 0 0 -5 1 22 0)
                                      #model: #blockArgumentsOnNewLine
                                      #translateLabel: true
                                    )
                                   #(#CheckBoxSpec
                                      #label: 'C-Style Blocks'
                                      #name: 'CheckBox8'
                                      #layout: #(#LayoutFrame 0 0 0 0 250 0 22 0)
                                      #model: #cStyleBlocks
                                      #translateLabel: true
                                    )
                                   )
                                 
                                )
                                #extent: #(#Point 594 22)
                              )
                             #(#ViewSpec
                                #name: 'Box13'
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#LabelSpec
                                      #label: 'Ident:'
                                      #name: 'Label1'
                                      #layout: #(#LayoutFrame 0 0 0 0 100 0 22 0)
                                      #translateLabel: true
                                      #adjust: #right
                                    )
                                   #(#InputFieldSpec
                                      #name: 'EntryField1'
                                      #layout: #(#LayoutFrame 100 0 0 0 200 0 22 0)
                                      #model: #tabIndent
                                      #type: #number
                                      #acceptOnReturn: true
                                      #acceptOnTab: true
                                      #acceptOnLostFocus: true
                                      #acceptOnPointerLeave: true
                                    )
                                   #(#LabelSpec
                                      #label: 'Max Length for single line Blocks:'
                                      #name: 'Label2'
                                      #layout: #(#LayoutFrame 200 0 0 0 400 0 22 0)
                                      #translateLabel: true
                                      #adjust: #right
                                    )
                                   #(#InputFieldSpec
                                      #name: 'EntryField2'
                                      #layout: #(#LayoutFrame 400 0 0 0 500 0 22 0)
                                      #model: #maxLengthForSingleLineBlocks
                                      #type: #number
                                      #acceptOnReturn: true
                                      #acceptOnTab: true
                                      #acceptOnLostFocus: true
                                      #acceptOnPointerLeave: true
                                    )
                                   )
                                 
                                )
                                #extent: #(#Point 594 30)
                              )
                             #(#HorizontalPanelViewSpec
                                #name: 'HorizontalPanel1'
                                #horizontalLayout: #fitSpace
                                #verticalLayout: #bottom
                                #horizontalSpace: 3
                                #verticalSpace: 3
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#ActionButtonSpec
                                      #label: 'Reset to ST/X Default'
                                      #name: 'Button1'
                                      #translateLabel: true
                                      #model: #resetToStxDefault
                                      #extent: #(#Point 292 22)
                                    )
                                   #(#ActionButtonSpec
                                      #label: 'Reset to RB Default'
                                      #name: 'Button2'
                                      #translateLabel: true
                                      #model: #resetToRBDefault
                                      #extent: #(#Point 293 22)
                                    )
                                   )
                                 
                                )
                                #extent: #(#Point 594 30)
                              )
                             )
                           
                          )
                          #extent: #(#Point 594 150)
                        )
                       )
                     
                    )
                    #extent: #(#Point 604 676)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::SourceCodeFormatSettingsAppl methodsFor:'actions'!

basicSaveSettings

    currentUserPrefs autoFormatting:self autoFormat value.
    currentUserPrefs at:#'formatter.tabIndent' put:self tabIndent value.
    currentUserPrefs at:#'formatter.spaceAroundTemporaries' put:self spaceAroundTemporaries value.
    currentUserPrefs at:#'formatter.emptyLineAfterTemporaries' put:self emptyLineAfterTemporaries value.
    currentUserPrefs at:#'formatter.spaceAfterReturnToken' put:self spaceAfterReturnToken value.
    currentUserPrefs at:#'formatter.spaceAfterKeywordSelector' put:self spaceAfterKeywordSelector value.
    currentUserPrefs at:#'formatter.cStyleBlocks' put:self cStyleBlocks value.
    currentUserPrefs at:#'formatter.blockArgumentsOnNewLine' put:self blockArgumentsOnNewLine value.
    currentUserPrefs at:#'formatter.maxLengthForSingleLineBlocks' put:self maxLengthForSingleLineBlocks value.
    RBFormatter 
        tabIndent:self tabIndent value;
        spaceAroundTemporaries:self spaceAroundTemporaries value;
        emptyLineAfterTemporaries:self emptyLineAfterTemporaries value;
        spaceAfterReturnToken:self spaceAfterReturnToken value;
        spaceAfterKeywordSelector:self spaceAfterKeywordSelector value;
        cStyleBlocks:self cStyleBlocks value;
        blockArgumentsOnNewLine:self blockArgumentsOnNewLine value;
        maxLengthForSingleLineBlocks:self maxLengthForSingleLineBlocks value asInteger.
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/sourceFormatSettings.html'].
!

readSettings
    reformatLocked := true.
    self autoFormat value:currentUserPrefs autoFormatting.
    self tabIndent value:RBFormatter tabIndent.
    self spaceAroundTemporaries value:RBFormatter spaceAroundTemporaries.
    self emptyLineAfterTemporaries 
        value:RBFormatter emptyLineAfterTemporaries.
    self spaceAfterReturnToken value:RBFormatter spaceAfterReturnToken.
    self spaceAfterKeywordSelector 
        value:RBFormatter spaceAfterKeywordSelector.
    self cStyleBlocks value:RBFormatter cStyleBlocks.
    self blockArgumentsOnNewLine value:RBFormatter blockArgumentsOnNewLine.
    self maxLengthForSingleLineBlocks 
        value:RBFormatter maxLengthForSingleLineBlocks.
    self evaluateModified.
    reformatLocked := false.
    self reformat.
    self modifiedChannel value:false
!

reformat

    |tree s_tabIndent s_spaceAroundTemporaries s_emptyLineAfterTemporaries
     s_spaceAfterReturnToken s_spaceAfterKeywordSelector s_cStyleBlocks
     s_maxLengthForSingleLineBlocks s_blockArgumentsOnNewLine|

    reformatLocked ifFalse:[
        "/
        "/ temporary change the RBFormatters settings ...
        "/
        s_tabIndent := RBFormatter tabIndent.
        s_spaceAroundTemporaries := RBFormatter spaceAroundTemporaries.
        s_emptyLineAfterTemporaries := RBFormatter emptyLineAfterTemporaries.
        s_spaceAfterReturnToken := RBFormatter spaceAfterReturnToken.
        s_spaceAfterKeywordSelector := RBFormatter spaceAfterKeywordSelector.
        s_cStyleBlocks := RBFormatter cStyleBlocks.
        s_blockArgumentsOnNewLine := RBFormatter blockArgumentsOnNewLine.
        s_maxLengthForSingleLineBlocks := RBFormatter maxLengthForSingleLineBlocks.

        RBFormatter 
            tabIndent:self tabIndent value;
            spaceAroundTemporaries:self spaceAroundTemporaries value;
            emptyLineAfterTemporaries:self emptyLineAfterTemporaries value;
            spaceAfterReturnToken:self spaceAfterReturnToken value;
            spaceAfterKeywordSelector:self spaceAfterKeywordSelector value;
            cStyleBlocks:self cStyleBlocks value;
            blockArgumentsOnNewLine:self blockArgumentsOnNewLine value;
            maxLengthForSingleLineBlocks:self maxLengthForSingleLineBlocks value.

        tree := RBParser 
                    parseMethod:self class exampleText
                    onError: [:aString :position | nil].
        tree do:[:node |
            (node ~~ tree and:[node parent isNil]) ifTrue:[
                self error:'No parent for node'.
            ]
        ].
        self editorText value:tree printString.

        RBFormatter 
            tabIndent:s_tabIndent;
            spaceAroundTemporaries:s_spaceAroundTemporaries;
            emptyLineAfterTemporaries:s_emptyLineAfterTemporaries;
            spaceAfterReturnToken:s_spaceAfterReturnToken;
            spaceAfterKeywordSelector:s_spaceAfterKeywordSelector;
            cStyleBlocks:s_cStyleBlocks;
            blockArgumentsOnNewLine:s_blockArgumentsOnNewLine;
            maxLengthForSingleLineBlocks:s_maxLengthForSingleLineBlocks.
      ].
!

resetToRBDefault

    reformatLocked := true.
    self tabIndent value: 8.
    self spaceAfterReturnToken value:false.
    self spaceAfterKeywordSelector value:true.
    self spaceAroundTemporaries value:true.
    self emptyLineAfterTemporaries value:false.
    self cStyleBlocks value:false.
    self blockArgumentsOnNewLine value:false.
    self maxLengthForSingleLineBlocks value: 20.
    reformatLocked := false.
    self reformat.
!

resetToStxDefault

    reformatLocked := true.
    self tabIndent value: 4.
    self spaceAfterReturnToken value: true.
    self spaceAfterKeywordSelector value: false.
    self spaceAroundTemporaries value: false.
    self emptyLineAfterTemporaries value: true.
    self cStyleBlocks value: true.
    self blockArgumentsOnNewLine value:false.
    self maxLengthForSingleLineBlocks value: 20.
    reformatLocked := false.
    self reformat.
! !

!AbstractSettingsApplication::SourceCodeFormatSettingsAppl methodsFor:'aspects'!

autoFormat

    autoFormat isNil ifTrue:[
        autoFormat := currentUserPrefs autoFormatting asValue.
        autoFormat onChangeSend:#evaluateModified to:self
    ].
    ^ autoFormat.
!

blockArgumentsOnNewLine

    blockArgumentsOnNewLine isNil ifTrue:[
        blockArgumentsOnNewLine := true asValue.
        blockArgumentsOnNewLine addDependent:self.
    ].
    ^ blockArgumentsOnNewLine.
!

cStyleBlocks

    cStyleBlocks isNil ifTrue:[
        cStyleBlocks := true asValue.
        cStyleBlocks addDependent:self.
    ].
    ^ cStyleBlocks.
!

editorText

    editorText isNil ifTrue:[
        editorText := ValueHolder new.
    ].
    ^ editorText.
!

emptyLineAfterTemporaries

    emptyLineAfterTemporaries isNil ifTrue:[
        emptyLineAfterTemporaries := true asValue.
        emptyLineAfterTemporaries addDependent:self.
    ].
    ^ emptyLineAfterTemporaries.
!

maxLengthForSingleLineBlocks

    maxLengthForSingleLineBlocks isNil ifTrue:[
        maxLengthForSingleLineBlocks := ValueHolder new.
        maxLengthForSingleLineBlocks addDependent:self.
    ].
    ^ maxLengthForSingleLineBlocks.
!

spaceAfterKeywordSelector

    spaceAfterKeywordSelector isNil ifTrue:[
        spaceAfterKeywordSelector := true asValue.
        spaceAfterKeywordSelector addDependent:self.
    ].
    ^ spaceAfterKeywordSelector.
!

spaceAfterReturnToken

    spaceAfterReturnToken isNil ifTrue:[
        spaceAfterReturnToken := true asValue.
        spaceAfterReturnToken addDependent:self.
    ].
    ^ spaceAfterReturnToken.
!

spaceAroundTemporaries

    spaceAroundTemporaries isNil ifTrue:[
        spaceAroundTemporaries := true asValue.
        spaceAroundTemporaries addDependent:self.
    ].
    ^ spaceAroundTemporaries.
!

tabIndent

    tabIndent isNil ifTrue:[
        tabIndent := ValueHolder new.
        tabIndent addDependent:self.
    ].
    ^ tabIndent.
! !

!AbstractSettingsApplication::SourceCodeFormatSettingsAppl methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    (changedObject == self blockArgumentsOnNewLine or:[
    changedObject == self cStyleBlocks or:[
    changedObject == self emptyLineAfterTemporaries or:[
    changedObject == self maxLengthForSingleLineBlocks or:[
    changedObject == self spaceAfterKeywordSelector or:[
    changedObject == self spaceAfterReturnToken or:[
    changedObject == self spaceAroundTemporaries or:[
    changedObject == self tabIndent 
    ]]]]]]]) ifTrue:[
        self evaluateModified.
        self reformat.
        ^ self.
    ].
    super update:something with:aParameter from:changedObject
! !

!AbstractSettingsApplication::SourceCodeFormatSettingsAppl methodsFor:'initialization & release'!

initialize
    super initialize.
    RBFormatter isNil ifTrue:[
        ^ self warn:'Sorry, no RBFormatter class'
    ].
    RBFormatter isLoaded ifFalse:[
        WindowGroup activeGroup withWaitCursorDo:[RBFormatter autoload]
    ].
    reformatLocked := false.
!

postBuildTextEditor:aWidget

    aWidget cursorMovementWhenUpdating:nil;
    scrollWhenUpdating:nil.
! !

!AbstractSettingsApplication::SourceCodeFormatSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ (
        self autoFormat value ~= currentUserPrefs autoFormatting ? false or:[
        self tabIndent value ~= RBFormatter tabIndent or:[
        self spaceAroundTemporaries value ~= RBFormatter spaceAroundTemporaries or:[
        self emptyLineAfterTemporaries value ~= RBFormatter emptyLineAfterTemporaries or:[
        self spaceAfterReturnToken value ~= RBFormatter spaceAfterReturnToken or:[
        self spaceAfterKeywordSelector value ~= RBFormatter spaceAfterKeywordSelector or:[
        self cStyleBlocks value ~= RBFormatter cStyleBlocks or:[
        self blockArgumentsOnNewLine value ~= RBFormatter blockArgumentsOnNewLine or:[
        self maxLengthForSingleLineBlocks value ~= RBFormatter maxLengthForSingleLineBlocks
        ]]]]]]]]
    )
! !

!AbstractSettingsApplication::SourceCodeManagementSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::SourceCodeManagementSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@TEA@PD00F@@@@@@@@@@@@@@@@@A@YMT]AN"(/J1DO@@@@@@@@@@@@@A@"RDL.GQ@EAAHFDP @@@@@@@@@@@@YR$@.LPXF@@@@@@XHA @@@@@@
@@@QMTT5H0$@@@@@@@@@@@ F@@@@@@@@FT(>GPX@@@@@@@@@@@@@A @@@@@@@A!!HMR4H@@@@@@@@@@@@@@@@@@XNE1\ QSL]B0XFA @@@@@@@@@@@@@FGDAI
Q#\(I3)EGP$@@@@AA0@@@@@@@@X&HRP_JCT]E X@@@@AOS@M@@@@@@@@A"X^IC\]E X@@@@AP#X;K@\@@@@@@@@FH2\]E X@@@@AQCX)LC00B @@@@@@@@X&
F X@@@@AP#X%EQ,0OB0G@@@@@@@@A P@@@@[OSX,KA,[F3@8F0L@@@@@@@@@@@@@@PDA@S$)L!!TA@PDA@@@@@@@@@@@@@@@@@@D<KCPU@@@@@@@@@P@@@@@@
@@@@@@@AOR$2B @@@@@@@@DA@@@@@@@@@@@AO3X,K@H@@@@@@@@@@PDA@@@@@@DAO3,,L@\@@@@@@@@@@@@CEPLM@PD9O3,2LA,C@@@@@@@@@@@@@@DMLCX9
OSP,L LA@@@@@@@@@@@@@@@@@@LGCQTUCPD@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 0 0 1 8 0 10 10 10 16 24 0 17 36 5 20 20 0 20 20 20 20 42 9 22 49 12 23 23 27 25 44 11 26 51 13 27 27 27 27 62 15 28 63 16 28 69 18 30 73 23 33 33 6 33 59 20 33 80 23 34 34 34 37 96 34 40 73 25 41 108 39 42 115 47 43 86 35 44 44 44 44 127 57 44 129 58 47 141 67 47 160 87 49 158 82 50 166 92 50 168 93 51 127 58 51 179 100 52 52 52 54 109 47 55 136 67 58 146 76 59 59 59 61 143 75 65 112 54 67 67 67 70 145 79 70 182 112 71 125 64 74 74 74 80 133 74 82 82 82 85 189 122 94 94 94 100 194 131 106 106 106 108 196 133 114 114 114 121 121 121 125 203 143 130 130 130 139 139 139 162 162 162 163 218 174 175 175 175 178 224 184 184 227 189 188 188 188 190 229 193 202 202 202 204 234 204 212 244 212 216 240 214 221 242 219 224 243 221 227 244 225]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@O8@@?>@A??@A?C C<@0C8@PC8@@??@@??F@_>O@O<_ G8?0C1?8A#?<@C?<@@_@H@_@L@?@GC>@C?>@A?<@@_0@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Source Code Manager Settings'
          #name: 'Source Code Manager Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 677 810)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #topSpace
              #horizontalSpace: 3
              #verticalSpace: 20
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel3'
                    #horizontalLayout: #fit
                    #verticalLayout: #top
                    #horizontalSpace: 3
                    #verticalSpace: 10
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#ViewSpec
                          #name: 'Box3'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Sourcecode Management'
                                #name: 'SourcecodeManagementCheckBox'
                                #layout: #(#LayoutFrame 5 0 5 0.0 300 0 27 0)
                                #enableChannel: #cvsIsSetup
                                #model: #useManager
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 661 30)
                        )
                       #(#FramedBoxSpec
                          #label: 'Source Code Manager Setup'
                          #name: 'FramedBox1'
                          #labelPosition: #topLeft
                          #translateLabel: true
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#ViewSpec
                                #name: 'Box1'
                                #layout: #(#LayoutFrame 0 0 0 0 0 1 32 0)
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#LabelSpec
                                      #label: 'CVS BinDirectory:'
                                      #name: 'Label1'
                                      #layout: #(#LayoutFrame 0 0.0 0 0 40 0.25 22 0)
                                      #level: 0
                                      #translateLabel: true
                                      #adjust: #right
                                    )
                                   #(#InputFieldSpec
                                      #name: 'BinDirectoryField'
                                      #layout: #(#LayoutFrame 44 0.25 0 0 -5 1 22 0)
                                      #enableChannel: #useManager
                                      #tabable: true
                                      #model: #cvsBinDirectoryHolder
                                      #acceptChannel: #acceptChannel
                                      #acceptOnPointerLeave: true
                                    )
                                   )
                                 
                                )
                              )
                             #(#ViewSpec
                                #name: 'Box7'
                                #layout: #(#LayoutFrame 0 0.0 27 0 0 1 52 0)
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#LabelSpec
                                      #label: 'CVSRoot default:'
                                      #name: 'defaultCvsRootLabel'
                                      #layout: #(#LayoutFrame 0 0.0 0 0 40 0.25 22 0)
                                      #level: 0
                                      #translateLabel: true
                                      #adjust: #right
                                    )
                                   #(#ComboBoxSpec
                                      #name: 'cvsRootComboBox'
                                      #layout: #(#LayoutFrame 44 0.25 0 0 -5 1 22 0)
                                      #enableChannel: #useManager
                                      #tabable: true
                                      #model: #cvsRootHolder
                                      #immediateAccept: true
                                      #acceptOnLeave: true
                                      #acceptOnReturn: true
                                      #acceptOnTab: true
                                      #acceptOnLostFocus: true
                                      #acceptChannel: #acceptChannel
                                      #acceptOnPointerLeave: true
                                      #comboList: #cvsRootPrototypeList
                                    )
                                   )
                                 
                                )
                              )
                             #(#LabelSpec
                                #label: 'CVSRoot per Module:'
                                #name: 'knownModulesLabel'
                                #layout: #(#LayoutFrame 0 0.0 66 0 40 0.25 88 0)
                                #translateLabel: true
                                #adjust: #right
                              )
                             #(#SequenceViewSpec
                                #name: 'List1'
                                #layout: #(#LayoutFrame 44 0.25 66 0 -5 1 191 0)
                                #enableChannel: #useManager
                                #tabable: true
                                #model: #selectedPerModuleRoot
                                #hasHorizontalScrollBar: true
                                #hasVerticalScrollBar: true
                                #miniScrollerHorizontal: true
                                #useIndex: false
                                #sequenceList: #listOfModules
                              )
                             #(#LabelSpec
                                #label: 'Module:'
                                #name: 'moduleLabel'
                                #layout: #(#LayoutFrame 0 0.0 209 0 40 0.25 226 0)
                                #translateLabel: true
                                #adjust: #right
                              )
                             #(#InputFieldSpec
                                #name: 'perModuleRootModuleEntryField'
                                #layout: #(#LayoutFrame 44 0.25 205 0 -1 1 227 0)
                                #enableChannel: #useManager
                                #tabable: true
                                #model: #perModuleRootModule
                                #acceptChannel: #acceptChannel
                                #acceptOnPointerLeave: true
                              )
                             #(#LabelSpec
                                #label: 'CVSRoot:'
                                #name: 'cvsRootLabel'
                                #layout: #(#LayoutFrame 0 0.0 236 0 40 0.25 253 0)
                                #translateLabel: true
                                #adjust: #right
                              )
                             #(#ComboBoxSpec
                                #name: 'perModuleRootComboBox'
                                #layout: #(#LayoutFrame 44 0.25 232 0 -1 1.0 254 0)
                                #enableChannel: #useManager
                                #tabable: true
                                #model: #perModuleRoot
                                #immediateAccept: true
                                #acceptOnLeave: true
                                #acceptOnReturn: true
                                #acceptOnTab: true
                                #acceptOnLostFocus: true
                                #acceptChannel: #acceptChannel
                                #acceptOnPointerLeave: true
                                #comboList: #cvsRootPrototypeList
                              )
                             #(#HorizontalPanelViewSpec
                                #name: 'HorizontalPanel2'
                                #layout: #(#LayoutFrame 44 0.25 258 0 -1 1 289 0)
                                #horizontalLayout: #fitSpace
                                #verticalLayout: #center
                                #horizontalSpace: 3
                                #verticalSpace: 3
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#ActionButtonSpec
                                      #label: 'Add/Apply'
                                      #name: 'Button1'
                                      #translateLabel: true
                                      #tabable: true
                                      #model: #addPerModuleRoot
                                      #enableChannel: #useManager
                                      #extent: #(#Point 209 22)
                                    )
                                   #(#ActionButtonSpec
                                      #label: 'Remove'
                                      #name: 'removeButton'
                                      #translateLabel: true
                                      #tabable: true
                                      #model: #removePerModuleRoot
                                      #enableChannel: #removeEnabled
                                      #extent: #(#Point 209 22)
                                    )
                                   )
                                 
                                )
                              )
                             )
                           
                          )
                          #extent: #(#Point 661 321)
                        )
                       #(#ViewSpec
                          #name: 'Box4'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#LabelSpec
                                #label: 'Source Cache Dir:'
                                #name: 'SourceCacheDirLabel'
                                #layout: #(#LayoutFrame 0 0.0 0 0 40 0.25 22 0)
                                #translateLabel: true
                                #adjust: #right
                              )
                             #(#InputFieldSpec
                                #name: 'SourceCacheDirEntryField'
                                #layout: #(#LayoutFrame 44 0.25 0 0 -5 1 22 0)
                                #enableChannel: #useManager
                                #model: #sourceCacheDir
                                #immediateAccept: false
                                #acceptOnReturn: true
                                #acceptOnTab: true
                                #acceptOnLostFocus: true
                                #acceptOnPointerLeave: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 661 30)
                        )
                       #(#HorizontalPanelViewSpec
                          #name: 'HorizontalPanel1'
                          #horizontalLayout: #fitSpace
                          #verticalLayout: #center
                          #horizontalSpace: 30
                          #verticalSpace: 3
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#ActionButtonSpec
                                #label: 'Flush Cache now'
                                #name: 'FlushCacheNowButton'
                                #translateLabel: true
                                #model: #flushSourceCache
                                #enableChannel: #useManager
                                #extent: #(#Point 285 22)
                              )
                             #(#ActionButtonSpec
                                #label: 'Condense Cache now'
                                #name: 'CondenseCacheNowButton'
                                #translateLabel: true
                                #model: #condenseSourceCache
                                #enableChannel: #useManager
                                #extent: #(#Point 286 22)
                              )
                             )
                           
                          )
                          #extent: #(#Point 661 40)
                        )
                       #(#ViewSpec
                          #name: 'Box5'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'If Present, Use Local Source (Suppress Checkout)'
                                #name: 'CheckBox4'
                                #layout: #(#LayoutFrame 30 0 5 0 -5 1 27 0)
                                #enableChannel: #useManager
                                #model: #localSourceFirst
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 661 25)
                        )
                       #(#ViewSpec
                          #name: 'Box6'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Check for halt/error-Sends when Checking in'
                                #name: 'CheckBox5'
                                #layout: #(#LayoutFrame 30 0 5 0 -5 1 27 0)
                                #enableChannel: #useManager
                                #model: #checkClassesWhenCheckingIn
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 661 25)
                        )
                       )
                     
                    )
                    #extent: #(#Point 661 768)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::SourceCodeManagementSettingsAppl methodsFor:'accessing'!

manager

    ^ Smalltalk at:#SourceCodeManager
! !

!AbstractSettingsApplication::SourceCodeManagementSettingsAppl methodsFor:'actions'!

addPerModuleRoot

    |module cvsRoot|

    acceptChannel value:true.    
    module := self perModuleRootModule value.
    cvsRoot := self perModuleRoot value.
    (listOfModules includes:module) ifFalse:[
        listOfModules add:module.
        listOfModules sort.
    ].
    cvsRoot size > 0 ifTrue:[
        rootsPerModule at:module put:cvsRoot.
    ].
!

basicSaveSettings

    (self hasManager and:[self useManager value]) ifTrue:[
        manager isNil ifTrue:[
            Smalltalk at:#SourceCodeManager put:(AbstractSourceCodeManager defaultManager).
            manager := Smalltalk at:#SourceCodeManager.
        ].
        Class tryLocalSourceFirst:self localSourceFirst value.

        manager notNil ifTrue:[
            | nm fn|
            nm := self sourceCacheDir value.
            nm size > 0 ifTrue:[
                (fn := nm asFilename) exists ifFalse:[
                    (self confirm:('CVS cache directory ''' , nm , ''' does not exists\create ?' withCRs)) ifTrue:[
                        fn makeDirectory; 
                           makeReadableForAll;
                           makeWritableForAll;
                           makeExecutableForAll.
                    ]
                ].
                (fn exists 
                and:[fn isDirectory
                and:[fn isReadable
                and:[fn isWritable]]]) ifTrue:[
                    AbstractSourceCodeManager cacheDirectoryName:(self sourceCacheDir value).
                ] ifFalse:[
                    self warn:'Invalid sourceCache directory.'
                ]
            ]
        ].

        repositoryHolder notNil ifTrue:[
            repositoryHolder value size > 0 ifTrue:[
                manager notNil ifTrue:[
                    manager initializeForRepository:repositoryHolder value.
                ]
            ].
        ].
        self cvsBinDirectoryHolder value size > 0 ifTrue:[
            CVSSourceCodeManager cvsBinDirectory:self cvsBinDirectoryHolder value.
        ].
        CVSSourceCodeManager initializeForRepository:self cvsRootHolder value.
        self cvsBinDirectoryHolder value:CVSSourceCodeManager cvsBinDirectory.
        CVSSourceCodeManager repositoryNamesPerModule:rootsPerModule.
        self sourceCacheDir value:(AbstractSourceCodeManager cacheDirectoryName).
        DebugView newDebugger.
    ] ifFalse:[
        Smalltalk at:#SourceCodeManager put:nil
    ].

    UserPreferences current at:#checkClassesWhenCheckingIn put:self checkClassesWhenCheckingIn value.
    self acceptChannel value.    
!

condenseSourceCache

    self withWaitCursorDo:[ AbstractSourceCodeManager condenseSourceCache ]
!

flushSourceCache

    self withWaitCursorDo:[ AbstractSourceCodeManager flushSourceCache ]
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/cvsSetup.html'].
!

readSettings
    self hasManager ifTrue:[
        self useManager value:(manager := Smalltalk at:#SourceCodeManager) notNil.
        self localSourceFirst value:Class tryLocalSourceFirst.
        self sourceCacheDir value:(AbstractSourceCodeManager cacheDirectoryName).
        manager notNil ifTrue:[
            manager forgetDisabledModules.
            repository := manager repositoryName.
            repositoryHolder := (repository ? '') asValue
        ].
        self cvsIsSetup value:true
    ] ifFalse:[
        self useManager value:false.
        self localSourceFirst value:false.
        self cvsIsSetup value:false
    ].
    self checkClassesWhenCheckingIn 
        value:(currentUserPrefs at:#checkClassesWhenCheckingIn ifAbsent:true).
    self cvsRootHolder 
        value:CVSSourceCodeManager repositoryName ? '/cvs/stx'.
    self cvsBinDirectoryHolder value:CVSSourceCodeManager cvsBinDirectory.
    rootsPerModule notNil ifTrue:[
        listOfModules := rootsPerModule keys asList.
    ].
    self selectedPerModuleRootChanged.
    self modifiedChannel value:false
!

removePerModuleRoot

    |module|

    acceptChannel value:true.    
    module := self perModuleRootModule value.
    listOfModules remove:module ifAbsent:nil.
    rootsPerModule removeKey:module ifAbsent:nil.
    self perModuleRootModule value:nil.
    self perModuleRoot value:nil.
!

setupSourceCodeManager

   AbstractLauncherApplication::LauncherDialogs cvsConfigurationDialog.
   manager := (Smalltalk at:#SourceCodeManager).
   cvsIsSetup value:manager notNil.
   manager notNil ifTrue:[
        repositoryHolder value: manager repositoryName.
        sourceCacheDir value:(AbstractSourceCodeManager cacheDirectoryName).
   ].
! !

!AbstractSettingsApplication::SourceCodeManagementSettingsAppl methodsFor:'aspects'!

acceptChannel

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

checkClassesWhenCheckingIn

    checkClassesWhenCheckingIn isNil ifTrue:[
        checkClassesWhenCheckingIn := (currentUserPrefs at:#checkClassesWhenCheckingIn ifAbsent:true) asValue.
        checkClassesWhenCheckingIn onChangeSend:#evaluateModified to:self
    ].
    ^ checkClassesWhenCheckingIn.
!

cvsBinDirectoryHolder
    cvsBinDirectoryHolder isNil ifTrue:[
        cvsBinDirectoryHolder := ValueHolder new.
    ].
    ^ cvsBinDirectoryHolder.
!

cvsIsSetup
    cvsIsSetup isNil ifTrue:[
        cvsIsSetup := true asValue.
    ].
    ^ cvsIsSetup.
!

cvsRootHolder

    cvsRootHolder isNil ifTrue:[
        cvsRootHolder := ValueHolder new.
        cvsRootHolder onChangeSend:#evaluateModified to:self
    ].
    ^ cvsRootHolder.
!

cvsRootPrototypeList

    cvsRootPrototypeList isNil ifTrue:[
        OperatingSystem getDomainName = 'exept' ifFalse:[
            cvsRootPrototypeList := #(
                                'host:/cvs/stx' 
                                ':pserver:user@host:/cvs/stx'
                             ).
            cvsRootPrototypeList := cvsRootPrototypeList copyWith:(':pserver:' , OperatingSystem getLoginName , '@host:/cvs/stx')
        ] ifTrue:[
            cvsRootPrototypeList := #(
                                '/cvs/stx' 
                                'exept:/cvs/stx' 
                             ).
            cvsRootPrototypeList := cvsRootPrototypeList copyWith:(':pserver:' , OperatingSystem getLoginName , '@exept:/cvs/stx')
        ].

        OperatingSystem isUNIXlike ifTrue:[
            cvsRootPrototypeList := cvsRootPrototypeList , #(
                              '/cvs/stx' 
                             ).
        ] ifFalse:[
            OperatingSystem isMSDOSlike ifTrue:[
                cvsRootPrototypeList := cvsRootPrototypeList , #(
                                  ':local:c:\cvs\stx' 
                                 ).
            ] ifFalse:[
                "there might be more here in the future"
            ]
        ].
    ].
    ^ cvsRootPrototypeList.
!

listOfModules

    listOfModules isNil ifTrue:[
        listOfModules := rootsPerModule keys asList.
        listOfModules sort.
    ].
    ^ listOfModules.
!

localSourceFirst

    localSourceFirst isNil ifTrue:[
        localSourceFirst := ValueHolder new.
        localSourceFirst onChangeSend:#evaluateModified to:self
    ].
    ^ localSourceFirst.
!

perModuleRoot
    "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 ;-)"

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

perModuleRootModule
    "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 ;-)"

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

removeEnabled

    removeEnabled isNil ifTrue:[
        removeEnabled := false asValue.
    ].
    ^ removeEnabled.
!

selectedPerModuleRoot

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

sourceCacheDir
    ^ sourceCacheDir.
!

useManager
    ^ useManager.
! !

!AbstractSettingsApplication::SourceCodeManagementSettingsAppl methodsFor:'change & update'!

selectedPerModuleRootChanged

    |module cvsRoot|

    self acceptChannel value:true.    
    module := self selectedPerModuleRoot value.
    module isNil ifTrue:[ ^ self].
    self removeEnabled value:true.
    cvsRoot := rootsPerModule at:module ifAbsent:''.
    self perModuleRootModule value:module.
    self perModuleRoot value:cvsRoot.
!

sourceDirChanged
    | nm fn|

    manager isNil ifTrue:[^ self].

    nm := self sourceCacheDir value.
    nm isEmptyOrNil ifTrue:[^ self].

    (fn := nm asFilename) exists ifFalse:[
        (self confirm:('SourceCache directory ''' , nm , ''' does not exist.\Create ?' withCRs)) ifTrue:[
            fn makeDirectory; 
               makeReadableForAll;
               makeWritableForAll;
               makeExecutableForAll.
        ] ifFalse:[
            self sourceCacheDir value:(AbstractSourceCodeManager cacheDirectoryName).
            ^ self.
        ].
    ].
    (fn exists 
    and:[fn isDirectory
    and:[fn isReadable
    and:[fn isWritable]]]) ifTrue:[
        AbstractSourceCodeManager cacheDirectoryName:nm.
    ] ifFalse:[
        self warn:'Invalid sourceCache directory.'.
        self sourceCacheDir value:(AbstractSourceCodeManager cacheDirectoryName).
    ].
!

update:something with:aParameter from:changedObject
    changedObject == sourceCacheDir ifTrue:[
        self sourceDirChanged.
        self evaluateModified.
        ^ self
    ].

    changedObject == self selectedPerModuleRoot ifTrue:[
        self selectedPerModuleRootChanged.
        ^ self
    ].

    super update:something with:aParameter from:changedObject
! !

!AbstractSettingsApplication::SourceCodeManagementSettingsAppl methodsFor:'initialization & release'!

initialize
    (AbstractSourceCodeManager notNil) ifTrue:[AbstractSourceCodeManager autoload].

    useManager := false asValue.
    useManager onChangeSend:#evaluateModified to:self.

    sourceCacheDir := nil asValue.
    sourceCacheDir addDependent:self.

    repositoryHolder := '' asValue.
    rootsPerModule := Dictionary new.

    SourceCodeManager == CVSSourceCodeManager ifTrue:[
        rootsPerModule declareAllFrom:(SourceCodeManager repositoryNamesPerModule).
    ].

    super initialize.
!

postOpen
!

postOpenAsSubcanvasWith:aBuilder

    self postOpen.
    ^ super postOpenAsSubcanvasWith:aBuilder
!

postOpenWith:aBuilder

    self postOpen.
    ^ super postOpenWith:aBuilder
! !

!AbstractSettingsApplication::SourceCodeManagementSettingsAppl methodsFor:'queries'!

hasManager
    ^ AbstractSourceCodeManager notNil
                  and:[AbstractSourceCodeManager isLoaded]
!

hasUnsavedChanges
    (self useManager value ~= ((Smalltalk at:#SourceCodeManager) notNil)) 
        ifTrue:[^ true].

    ((self hasManager and:[self useManager value]) 
    and:[
            Class tryLocalSourceFirst ~= self localSourceFirst value or:[
            AbstractSourceCodeManager cacheDirectoryName ~= self sourceCacheDir value]
        ]) 
        ifTrue:[^ true].

    ((UserPreferences current at:#checkClassesWhenCheckingIn ifAbsent:true) ~= self checkClassesWhenCheckingIn value)
        ifTrue:[^ true].

    (CVSSourceCodeManager cvsBinDirectory ~= self cvsBinDirectoryHolder value) 
        ifTrue:[^ true].

    (CVSSourceCodeManager repositoryName ? '/files/CVS' ~= self cvsRootHolder value)
        ifTrue:[^ true].

    ((Dictionary new declareAllFrom:(CVSSourceCodeManager repositoryNamesPerModule)) ~= rootsPerModule)
        ifTrue:[^ true].

    (self sourceCacheDir value ~= AbstractSourceCodeManager cacheDirectoryName)
        ifTrue:[^ true].
        
    ^ false
! !

!AbstractSettingsApplication::StyleSettingsAppl class methodsFor:'defaults'!

standardStyles

    ^  #(
        'decWindows'
        'iris' 
        'motif' 
        'mswindows95' 
        'next' 
        'normal'
        'os2' 
        'st80' 
       )
! !

!AbstractSettingsApplication::StyleSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::StyleSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@DA@@@@@@@@@@@@@@@@@@@@@@@@@@DBAPD@@@@@@@@@@@@@@@@@@@@@@@DBAPTF@P@@@@@@@@@@@@@@@@@@@@DBAPTFA DA@@@@@@@@@@@@
@@@@@@LB@ HFA \G@PD@@@@@@@@@@@@@@@LB@ HB@  GA0(J@P@@@@@@@@@@@@LB@ HB@ HBB \IB ,A@@@@@@@@@@LB@ HB@ HB@ 4NB ,OC0DE@@@@@@LB
@ HB@ HB@ HB@ 8OC0TE@P@@@@@@@0HB@ HB@ HBCQDQC0TEAPHP@AHRD!!HRD!!HRD!!HRD!!HRD!!HAA@HC@@@RD HED1LTEQXVE1 BAPTR@ DC@@@@D!!HBAQLS
EATVE!!\X@ TED HC@@@@@AHRAPPYFQ([GA0]G TDAAHC@@@@@@@C@0HB@ HB@ HB@!!<MDQDC@@@@@@@@@0LB@ HB@ HB@ H_CQDQ@0@@@@@@@@LC@ HB@ HB
@ HBCP4QDPL@@@@@@@@C@0HB@ HB@ HB@ 4MDQDC@@@@@@@@@0LB@ HB@ HB@!!<MDQDQ@0@@@@@@@@LC@ HB@ HB@ H_CQDQDPL@@@@@@@@C@0HB@ HB@ HB
CP4QDQDC@@@@@@@@@0LC@0LC@0LC@0LC@0LC@0@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 32 96 88 248 248 248 80 80 80 128 128 128 192 192 192 64 144 136 48 120 112 56 136 128 56 128 120 40 104 96 40 104 104 32 96 96 232 232 232 32 88 88 32 88 80 64 104 104 224 224 224 0 88 128 24 152 192 16 136 184 16 128 168 8 120 160 8 112 152 8 104 144 16 120 152 16 112 144 8 104 136 8 96 128 8 88 120 0 80 112 240 240 240]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@C@@@G @@O0@@_8@@?<@A?>@C??@G??0O??0G??8???0??? ???@??>@??<@??<@??<@??<@??<@??<@??<@??<@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'ViewStyle Selection'
          #name: 'ViewStyle Selection'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 491 573)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#LabelSpec
              #label: 'Label'
              #name: 'Label1'
              #layout: #(#LayoutFrame 0 0.0 -44 1 0 1.0 0 1)
              #style: #(#FontDescription #helvetica #bold #roman 12)
              #translateLabel: true
              #labelChannel: #infoLabelHolder
              #resizeForLabel: true
              #adjust: #left
            )
           #(#LabelSpec
              #label: 'NoticeText'
              #name: 'Text'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 160 0)
              #translateLabel: true
              #labelChannel: #noticeLabelHolder
              #resizeForLabel: true
              #adjust: #left
            )
           #(#CheckBoxSpec
              #label: 'standard styles only'
              #name: 'CheckBox1'
              #layout: #(#LayoutFrame 0 0.0 160 0 0 1.0 182 0)
              #model: #showStandardStylesOnly
              #translateLabel: true
            )
           #(#SequenceViewSpec
              #name: 'StyleList'
              #layout: #(#LayoutFrame 0 0.0 182 0 0 1.0 -44 1)
              #model: #selectedStyle
              #hasHorizontalScrollBar: true
              #hasVerticalScrollBar: true
              #doubleClickSelector: #doubleClickAt:
              #useIndex: false
              #sequenceList: #styleList
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::StyleSettingsAppl methodsFor:'actions'!

basicSaveSettings

    | newStyle transcript|

    newStyle := self selectedStyle value.

    self withWaitCursorDo:[
        Transcript showCR:'change style to ' , newStyle , ' ...'.
        View defaultStyle:newStyle asSymbol.
    ].
    DebugView newDebugger.
    transcript := Transcript current.
    transcript notNil ifTrue:[
        | app|
        app := transcript topView application.
        (app respondsTo:#reopenLauncher) ifTrue:[
            app reopenLauncher.
        ].
    ].
!

doubleClickAt:aLine

    self saveSettings.
!

help

    self warn:'no help available here'.
"/    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/keyboardSetting.html'].
!

readSettings
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::StyleSettingsAppl methodsFor:'aspects'!

infoLabelHolder

    infoLabelHolder isNil ifTrue:[
        infoLabelHolder := '' asValue.
    ].
    ^ infoLabelHolder.
!

noticeLabelHolder

    noticeLabelHolder isNil ifTrue:[
        noticeLabelHolder := '' asValue.
    ].
    ^ noticeLabelHolder.
!

selectedStyle

    selectedStyle isNil ifTrue:[
        selectedStyle := ValueHolder new.
        selectedStyle addDependent:self.
    ].
    ^ selectedStyle.
!

showStandardStylesOnly

    showStandardStylesOnly isNil ifTrue:[
        showStandardStylesOnly := true asValue.
        showStandardStylesOnly addDependent:self.
    ].
    ^ showStandardStylesOnly.
!

styleList

    styleList isNil ifTrue:[
        styleList := List new.
        styleList addDependent:self.
    ].
    ^ styleList.
! !

!AbstractSettingsApplication::StyleSettingsAppl methodsFor:'change & update'!

changeInfoLabel

    |nm sheet comment|

    comment := ''.
    nm := self selectedStyle value.
    nm notNil ifTrue:[
        sheet := ViewStyle fromFile:(nm , '.style').
        comment := (sheet at:#comment ifAbsent:'') withoutSeparators.
    ].
    comment := comment withCRs asStringCollection.
    comment size == 1 ifTrue:[
        comment := comment first
    ].
    self infoLabelHolder value:comment
!

update:something with:aParameter from:changedObject
    changedObject == self showStandardStylesOnly ifTrue:[
        self updateList.
        ^ self.
    ].
    changedObject == self selectedStyle ifTrue:[
        self changeInfoLabel.
        self evaluateModified.
        ^ self.
    ].

    super update:something with:aParameter from:changedObject
!

updateList

    |listOfStyles lastSelection|

    lastSelection := self selectedStyle value.
    listOfStyles := styleDirectoryContents select:[:aFileName | aFileName asFilename hasSuffix:'style'].
    listOfStyles := listOfStyles collect:[:aFileName | aFileName asFilename withoutSuffix name].
    Filename isCaseSensitive ifFalse:[
        listOfStyles := listOfStyles collect:[:aStyleName | aStyleName asLowercase].
    ].
    listOfStyles remove:'generic' ifAbsent:nil; remove:'mswindows3' ifAbsent:nil.
    self showStandardStylesOnly value ifTrue:[
        listOfStyles := listOfStyles select:[:aStyleName | self class standardStyles includes:aStyleName].
    ].

    listOfStyles sort.
    self styleList contents:listOfStyles.
    self selectedStyle value:lastSelection.
! !

!AbstractSettingsApplication::StyleSettingsAppl 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
!

initialize

    |someRsrcFile resourceDir|

    super initialize.

    someRsrcFile := Smalltalk getSystemFileName:('resources' asFilename constructString:'normal.style').
    someRsrcFile isNil ifTrue:[
        someRsrcFile := Smalltalk getResourceFileName:'normal.style' forPackage:'stx:libview'.
        someRsrcFile isNil ifTrue:[
            someRsrcFile := Smalltalk getResourceFileName:'styles/normal.style' forPackage:'stx:libview'.
        ].
    ].
    someRsrcFile notNil ifTrue:[
        resourceDir := someRsrcFile asFilename directoryName
    ] ifFalse:[
        resourceDir := Smalltalk getSystemFileName:'resources'.
        resourceDir isNil ifTrue:[
            self warn:'no styles found (missing ''resources'' directory)'.
            ^ self
        ].
    ].

    [
        styleDirectoryContents := resourceDir asFilename directoryContents.
    ] on:FileStream openErrorSignal do:[:ex|
        self warn:'no styles found (unaccessable ''resources'' directory)'.
        ^ self
    ].

    self updateList.
    (self class standardStyles includes:View defaultStyle) ifFalse:[
        self showStandardStylesOnly value:false
    ].
    self selectedStyle value:(View defaultStyle).
    self noticeLabelHolder value:(resources at:'STYLE_MSG' default:'Select a Style') withCRs.    
! !

!AbstractSettingsApplication::StyleSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^  (self selectedStyle value ~= View defaultStyle)
! !

!AbstractSettingsApplication::SyntaxColorSettingsAppl class methodsFor:'defaults'!

emphasisList

    ^ #(
        #normal         
        #underline       
        #'red underline'  
        #underwave 
        #'red underwave' 
        #bold   
        #boldUnderline  
        #'bold+red underline'
        #boldUnderwave 
        #'bold+red underwave'
        #italic
        #italicUnderline
        #'italic+red underline'
        #italicUnderwave 
        #'italic+red underwave'
        #reverse
    )
!

exampleText

    ^  'methodSelector:methodArg
    "method comment:
     some stupid code to show the current settings"

    |methodVar|

    "/ another comment ...
    self at:methodArg.        "/ a message
    self fooBarBaz:methodVar. "/ a bad message
    methodVar := Array new:1.
    unknonVar := 1.           "/ a bad variable
    UnknonVar := 1.           "/ another bad variable
    "self bar:methodVar.  detect commented code easily"
    1 to:5 do:[:i | self at:i + 1].
    Transcript showCR:''some string'' , #someSymbol.
    ^ self.
'.
!

fontList

    ^ #(
        normal
        underline
        #'red underline'
        underwave
        #'red underwave'
        bold
        boldUnderline
        #'bold+red underline'
        boldUnderwave
        #'bold+red underwave'
        italic
        italicUnderline
        #'italic+red underline'
        italicUnderwave
        #'italic+red underwave'
        reverse
    )
! !

!AbstractSettingsApplication::SyntaxColorSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::SyntaxColorSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
A0\GA0\GA0\GA0\GA0\GA0\GA0\GA0\IBP$IBP$IBP$IBP$IBP$IBP$IBP\GBP$ABP$I@P$IBP$CBPLIBP$IBPLGA0$ABP$IBP$ABP$I@0$CBP$IBPLIA0\I
@P$IBP$I@P$IBP$IBP$IBP$CBP\GBPDIBP$IBPDIBP$IBP$IBP$CBP$GA0$ABP$IBP$ABP$IBP$IBP$I@0$IA0\I@P$IBP$I@P$IBP$IBP$I@0$IBP\GBPDI
BP$IBPDIBP$IBP$IBPLIBP$GA0$I@P$IBPDIBP$IBP$IBPLIBP$IA0\IBP$IBP$IBP$IBP$IBP$IBP$IBP\GBP$I@P$IBP$IBP$IBP$IBP$IBP$GA0$I@P$I
BP$IBP$IBP$IBP$IBP$IA0\IBPDIBP$ABP$I@P$IBP$IBP$IBP\GBPDA@P$ABPDI@P$ABP$ABP$IBP$GA0$I@P$I@P$ABPDI@P$IBP$IBP$IA0\IBPDIBPDI
@P$ABPDIBP$IBP$IBP\GBP$ABP$I@P$IBPDIBP$ABP$IBP$GA0$IBP$IBP$IBP$IBP$IBP$IBP$IA0\IA@$DBPPIA@$DBPPIBP$IBP$IBP\GBP$DBPPIA@$D
BPPIA@$IBP$IBP$GA0\GA0\GA0\GA0\GA0\GA0\GA0\GA0@a') ; colorMapFromArray:#[160 160 160 0 0 0 48 48 48 0 0 255 255 0 0 255 168 88 195 195 195 88 88 88 255 220 168 255 255 255]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'???<???<???<???<???<???<???<???<???<???<???<???<???<???<???<???<???<???<???<???<???<???<') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Syntax Color Settings'
          #name: 'Syntax Color Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 711 651)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fit
              #verticalLayout: #topSpace
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel1'
                    #horizontalLayout: #fitSpace
                    #verticalLayout: #topSpace
                    #horizontalSpace: 5
                    #verticalSpace: 8
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#CheckBoxSpec
                          #label: 'Syntax Coloring'
                          #name: 'CheckBox1'
                          #model: #syntaxColoring
                          #translateLabel: true
                          #extent: #(#Point 685 22)
                        )
                       #(#CheckBoxSpec
                          #label: 'Immediate Selector Check'
                          #name: 'ImmediateSelectorCheckBox'
                          #enableChannel: #syntaxColoring
                          #model: #fullSelectorCheck
                          #translateLabel: true
                          #extent: #(#Point 685 22)
                        )
                       #(#TextEditorSpec
                          #name: 'TextEditor2'
                          #enableChannel: #syntaxColoring
                          #model: #coloredText
                          #hasHorizontalScrollBar: true
                          #hasVerticalScrollBar: true
                          #isReadOnly: true
                          #extent: #(#Point 685 280)
                        )
                       #(#ViewSpec
                          #name: 'Box11'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#ComboListSpec
                                #name: 'ComboList3'
                                #layout: #(#LayoutFrame 0 0 -22 1 0 1 0 1)
                                #enableChannel: #syntaxColoring
                                #model: #syntaxElementSelection
                                #comboList: #syntaxElementList
                                #useIndex: false
                              )
                             )
                           
                          )
                          #extent: #(#Point 685 35)
                        )
                       #(#ViewSpec
                          #name: 'Box12'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#ComboListSpec
                                #name: 'ComboList5'
                                #layout: #(#LayoutFrame 0 0 -22 1 0 1 0 1)
                                #enableChannel: #syntaxColoring
                                #model: #syntaxEmphasisSelection
                                #comboList: #syntaxEmphasisList
                                #useIndex: false
                              )
                             #(#LabelSpec
                                #label: 'Emphasis:'
                                #name: 'Label1'
                                #layout: #(#LayoutFrame 0 0 0 0 205 0 22 0)
                                #translateLabel: true
                                #adjust: #left
                              )
                             )
                           
                          )
                          #extent: #(#Point 685 44)
                        )
                       #(#ViewSpec
                          #name: 'Box1'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#ColorMenuSpec
                                #name: 'ColorMenu2'
                                #layout: #(#LayoutFrame 0 0 -22 1 0 1 0 1)
                                #enableChannel: #syntaxColoring
                                #model: #syntaxColor
                                #labelsAreColored: true
                              )
                             #(#LabelSpec
                                #label: 'Text Color:'
                                #name: 'Label2'
                                #layout: #(#LayoutFrame 0 0 0 0 205 0 22 0)
                                #translateLabel: true
                                #adjust: #left
                              )
                             )
                           
                          )
                          #extent: #(#Point 685 44)
                        )
                       #(#ViewSpec
                          #name: 'Box10'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#ActionButtonSpec
                                #label: 'Reset To:'
                                #name: 'Button2'
                                #layout: #(#LayoutFrame 0 0 -22 1 150 0 0 1)
                                #translateLabel: true
                                #model: #resetToColorScheme
                                #enableChannel: #syntaxColoring
                              )
                             #(#ComboListSpec
                                #name: 'ComboList4'
                                #layout: #(#LayoutFrame 150 0 -22 1 0 1 0 1)
                                #enableChannel: #syntaxColoring
                                #model: #resetListSelection
                                #comboList: #resetList
                                #useIndex: false
                              )
                             )
                           
                          )
                          #extent: #(#Point 685 35)
                        )
                       )
                     
                    )
                    #extent: #(#Point 695 609)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::SyntaxColorSettingsAppl methodsFor:'actions'!

basicSaveSettings

    oldUserPreferences := currentUserPrefs copy.
    currentUserPrefs syntaxColoring:self syntaxColoring value.
    currentUserPrefs at:#fullSelectorCheck put:self fullSelectorCheck value.
!

formattingConfiguration
    "automatically generated by UIPainter ..."

    "*** the code below performs no action"
    "*** (except for some feedback on the Transcript)"
    "*** Please change as required and accept in the browser."

    "action to be added ..."

    Transcript showCR:self class name, ': action for formattingConfiguration ...'.
!

help

"/    self warn:'no help available here'.
    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/sourceSettings.html'].
!

readSettings
    |colorList resetListLoc|

    oldUserPreferences notNil ifTrue:[
        (UserPreferences
            reset;
            current) declareAllFrom:oldUserPreferences
    ].
    self syntaxColoring value:currentUserPrefs syntaxColoring.
    self fullSelectorCheck value:currentUserPrefs fullSelectorCheck.
    oldUserPreferences := currentUserPrefs copy.
    colorList := UserPreferences syntaxColorNames.
    resetListLoc := currentUserPrefs listOfPredefinedSyntaxColoringSchemes 
                collect:[:entry | entry second].
    self resetList value:resetListLoc.
    self resetListSelection value:resetListLoc first.
    self syntaxEmphasisList value:self class emphasisList.
    self syntaxElementList value:colorList.
    self syntaxElementSelection value:(colorList at:1).
    self modifiedChannel value:false
!

recolor

    |text|

    self syntaxColoring value ifTrue:[
        text := SyntaxHighlighter formatMethod:self class exampleText in:nil.
    ] ifFalse:[
        text := self class exampleText.
    ].
    self coloredText value:text
!

resetToColorScheme

    |resetSelector|

    resetSelector := resetListDictionary keyAtValue:(self resetListSelection value).
    currentUserPrefs perform:resetSelector. 
    self recolor.
    self evaluateModified.
! !

!AbstractSettingsApplication::SyntaxColorSettingsAppl methodsFor:'aspects'!

coloredText

    coloredText isNil ifTrue:[
        coloredText := ValueHolder new.
    ].
    ^ coloredText.
!

fullSelectorCheck

    fullSelectorCheck isNil ifTrue:[
        fullSelectorCheck := currentUserPrefs fullSelectorCheck asValue.
        fullSelectorCheck onChangeSend:#evaluateModified to:self
    ].
    ^ fullSelectorCheck.
!

resetList

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

resetListSelection

    resetListSelection isNil ifTrue:[
        resetListSelection := ValueHolder new.
    ].
    ^ resetListSelection.
!

syntaxColor

    syntaxColor isNil ifTrue:[
        syntaxColor := ValueHolder new.
        syntaxColor addDependent:self.
    ].
    ^ syntaxColor.
!

syntaxColoring

    syntaxColoring isNil ifTrue:[
        syntaxColoring := true asValue.
        syntaxColoring addDependent:self.
        syntaxColoring onChangeSend:#evaluateModified to:self.
    ].
    ^ syntaxColoring.
!

syntaxElementList
    "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 ;-)"

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

syntaxElementSelection

    syntaxElementSelection isNil ifTrue:[
        syntaxElementSelection := ValueHolder new.
        syntaxElementSelection addDependent:self.
"/       syntaxElementSelection onChangeSend:#syntaxElementSelectionChanged to:self.
    ].
    ^ syntaxElementSelection.
!

syntaxEmphasisList
    "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 ;-)"

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

syntaxEmphasisSelection

    syntaxEmphasisSelection isNil ifTrue:[
        syntaxEmphasisSelection := ValueHolder new.
        syntaxEmphasisSelection addDependent:self.
    ].
    ^ syntaxEmphasisSelection.
! !

!AbstractSettingsApplication::SyntaxColorSettingsAppl methodsFor:'change & update'!

getEmphasis:anEmphasisOrSymbol
    " return emphasis Symbol for emphasis or emphasis for emphasis symbol "

    ^ emphasisDictionary at:anEmphasisOrSymbol ifAbsent:[nil]
!

syntaxColorChanged

    currentUserPrefs at:(self syntaxColorSelector value) put:(self syntaxColor value).
    self recolor.
    self evaluateModified.
!

syntaxElementSelectionChanged

    | syntaxEmphasisValue |

    self syntaxColor value:(currentUserPrefs perform:(self syntaxColorSelector value)).
    syntaxEmphasisValue := (currentUserPrefs perform:(self syntaxEmphasisSelector value)).
    self syntaxEmphasisSelection value:(self getEmphasis:syntaxEmphasisValue).
    self recolor.
!

syntaxEmphasisSelectionChanged

    |em|

    em := self getEmphasis:self syntaxEmphasisSelection value.
    currentUserPrefs at:(self syntaxEmphasisSelector value) value put:em.
    self recolor.
    self evaluateModified.
!

update:something with:aParameter from:changedObject
    changedObject == self syntaxElementSelection ifTrue:[
        self syntaxElementSelectionChanged.
        ^ self.
    ].
    changedObject == self syntaxColor ifTrue:[
        self syntaxColorChanged.
        ^ self.
    ].
    changedObject == self syntaxEmphasisSelection ifTrue:[
        self syntaxEmphasisSelectionChanged.
        ^ self.
    ].
    changedObject == self syntaxColoring ifTrue:[
        self recolor.
        ^ self.
    ].

    super update:something with:aParameter from:changedObject
! !

!AbstractSettingsApplication::SyntaxColorSettingsAppl methodsFor:'initialization & release'!

initialize
    self initializeEmphasisDictionary.
    super initialize.

    resetListDictionary := Dictionary new.
    currentUserPrefs listOfPredefinedSyntaxColoringSchemes do:[:entry | 
        resetListDictionary at:(entry at:1) put:(entry at:2)
    ].
!

initializeEmphasisDictionary

    emphasisDictionary := Dictionary new.
    self class emphasisList do:[ : entry |
        entry == #'red underline' ifTrue:[
            emphasisDictionary at:entry put:(Array with:#underline with:(#underlineColor->Color red)).
            emphasisDictionary at:(Array with:#underline with:(#underlineColor->Color red)) put:entry.
        ] ifFalse:[
            entry == #'red underwave' ifTrue:[
                emphasisDictionary at:entry put:(Array with:#underwave with:(#underlineColor->Color red)).
                emphasisDictionary at:(Array with:#underwave with:(#underlineColor->Color red)) put:entry.
            ] ifFalse:[
                entry == #'bold+red underline' ifTrue:[
                    emphasisDictionary at:entry put:(Array with:#bold with:#underline with:(#underlineColor->Color red)).
                    emphasisDictionary at:(Array with:#bold with:#underline with:(#underlineColor->Color red)) put:entry.
                ] ifFalse:[
                    entry == #'bold+red underwave' ifTrue:[
                        emphasisDictionary at:entry put:(Array with:#bold with:#underwave with:(#underlineColor->Color red)).
                        emphasisDictionary at:(Array with:#bold with:#underwave with:(#underlineColor->Color red)) put:entry.
                    ] ifFalse:[
                        entry == #'italic+red underline' ifTrue:[
                            emphasisDictionary at:entry put:(Array with:#italic with:#underline with:(#underlineColor->Color red)).
                            emphasisDictionary at:(Array with:#italic with:#underline with:(#underlineColor->Color red)) put:entry.
                        ] ifFalse:[
                            entry == #'italic+red underwave' ifTrue:[
                                emphasisDictionary at:entry put:(Array with:#italic with:#underwave with:(#underlineColor->Color red)).
                                emphasisDictionary at:(Array with:#italic with:#underwave with:(#underlineColor->Color red)) put:entry.
                            ] ifFalse:[
                                emphasisDictionary at:entry put:entry
                            ]
                        ]
                    ]
                ]
            ]
        ]
    ].
!

release

    oldUserPreferences notNil ifTrue:[
        (UserPreferences reset; current) declareAllFrom:oldUserPreferences
    ].
    super release
! !

!AbstractSettingsApplication::SyntaxColorSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    |colorList colorPerformer emphasisPerformer|

    colorList := UserPreferences syntaxColorNames.
    colorList do:[:syntaxElement |
        colorPerformer := (self syntaxColorSelectorForElement:syntaxElement) value.
        emphasisPerformer := (self syntaxEmphasisSelectorForElement:syntaxElement) value.
        ((oldUserPreferences perform:colorPerformer) ~= (currentUserPrefs perform:colorPerformer)) ifTrue:[
            ^ true
        ].
        ((oldUserPreferences perform:emphasisPerformer) ~= (currentUserPrefs perform:emphasisPerformer)) ifTrue:[
            ^ true
        ].
        syntaxElement
    ].
    currentUserPrefs syntaxColoring ~= self syntaxColoring value ifTrue:[^ true].
    currentUserPrefs fullSelectorCheck ~= self fullSelectorCheck value ifTrue:[^ true].
    ^ false
!

syntaxColorSelector

    ^ self syntaxColorSelectorForElement:self syntaxElementSelection value
!

syntaxColorSelectorForElement:aSyntaxElement

    ^ [(aSyntaxElement replChar:$  withString: '') asLowercaseFirst asSymbol]
!

syntaxEmphasisSelector 

    ^ self syntaxEmphasisSelectorForElement:self syntaxElementSelection value 
!

syntaxEmphasisSelectorForElement:anEmElement 

    ^ [((((self syntaxColorSelectorForElement:anEmElement) value) readStream upToAll: 'Color'), 'Emphasis') asLowercaseFirst asSymbol]
! !

!AbstractSettingsApplication::SystemMessageSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::SystemMessageSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@A XFA @@@@@@@@@@@@@@@@@@@@@@A!!HRCPX@@@@@@@@@@@@@@@@@@@@@A!!H.KP4MA @@@@@@@@@@@@@@@@@@@@XRPB<#H0L@@@@@@@@@@@@@
@@@@@@@FD$@/H2LC@@@@@@@@@@@@@@@@@@@@A!!H6LRH"@P@@@@@@@@@@@@@@@@@@@@XFC#LKB0D@@@@@@@@@@@@@@@@@@@@@@@XZ@PD@@@@@@@@@@@@@@@@@
@@@@@@@FF DA@@@@@@@@@@@@@@@@@@@@@@@@A!!(A@P@@@@@@@@@@@@@@@@@@@@\GA3@ZDQDAAPT@@@@@@@@@@@@@@@\;QDP''EQ@PE@$IAP@@@@@@@@@@@@@G
N4QDI1TPDAPIBPT@@@@@@@@@@@@@A31CP3(UJ"( B (D@@@@@@@@@@@@@@\>Q4\8IR0,J1@PA@@@@@@@@@@@@@@GO$]GNBT,KB,PD@P@@@@@@@@@@@@@A35H
RC$&I2\(D1LA@@@@@@@@@@@@@@\?Q$X7G2D!!IATU@P@@@@@@@@@@A0\2P$UEMQ VE!!$WE00B@@@@@@@@@@\GL$IEQSTXE!!XYE1\L@ @@@@@@@@@GA0=CPTD4
GA4]G!!,[B@D@@@@@@@@@@@@GAPPD@ HB@ DA@PD@@@@@@@@a') ; colorMapFromArray:#[0 0 0 2 2 4 38 38 12 58 34 14 60 60 20 74 70 28 78 46 20 82 82 28 94 94 36 95 95 38 107 107 50 110 62 20 114 114 52 118 58 12 122 82 44 122 122 60 125 123 72 130 74 20 133 101 52 135 134 78 142 134 68 145 144 88 146 146 92 152 152 98 153 153 106 158 158 108 162 114 44 162 162 116 163 163 120 163 164 116 165 164 116 165 165 120 167 165 116 167 166 118 168 90 24 168 98 26 168 167 124 170 169 124 170 170 128 170 170 130 170 171 128 171 168 122 172 170 128 172 171 130 172 172 130 178 106 36 178 122 60 181 121 48 182 122 52 184 116 49 184 184 140 187 122 43 187 186 148 188 188 150 196 141 89 198 198 162 203 203 172 204 203 170 205 202 168 210 210 178 219 217 188 219 219 190 220 220 188 220 220 190 222 174 132 232 231 214 233 233 216 234 234 212 236 231 208 236 236 220 241 241 232 243 243 232 243 243 234]; mask:((ImageMask new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@G @@O @@_0@@_0@@_0@@_0@@_0@@G @@G @@G @@?<@A?>@A?>@A?>@A?>@A?>@A?>@A?>@G??@G??@G??@A?>@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Messages Settings'
          #name: 'Messages Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 577 391)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #horizontalLayout: #fitSpace
              #verticalLayout: #topSpace
              #horizontalSpace: 5
              #verticalSpace: 5
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel1'
                    #horizontalLayout: #fit
                    #verticalLayout: #topSpace
                    #horizontalSpace: 3
                    #verticalSpace: 20
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#FramedBoxSpec
                          #label: 'Info & Error Messages'
                          #name: 'FramedBox2'
                          #labelPosition: #topLeft
                          #translateLabel: true
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'VM Info Messages'
                                #name: 'VMInfoMessages'
                                #layout: #(#LayoutFrame 5 0 5 0 -5 1 27 0)
                                #model: #vmInfo
                                #translateLabel: true
                              )
                             #(#CheckBoxSpec
                                #label: 'VM Error Messages'
                                #name: 'VMErrorMessages'
                                #layout: #(#LayoutFrame 5 0 30 0 -5 1 52 0)
                                #model: #vmErrors
                                #translateLabel: true
                              )
                             #(#CheckBoxSpec
                                #label: 'Display Error Messages (Xlib, Xtlib, WinAPI ...)'
                                #name: 'DisplayErrorMessages'
                                #layout: #(#LayoutFrame 5 0 55 0 -5 1 77 0)
                                #model: #displayErrors
                                #translateLabel: true
                              )
                             #(#CheckBoxSpec
                                #label: 'Other Info Messages'
                                #name: 'OtherInfoMessages'
                                #layout: #(#LayoutFrame 5 0 80 0 -5 1 102 0)
                                #model: #classInfos
                                #translateLabel: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 551 133)
                        )
                       #(#FramedBoxSpec
                          #label: 'Change File'
                          #name: 'FramedBox1'
                          #labelPosition: #topLeft
                          #translateLabel: true
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#CheckBoxSpec
                                #label: 'Log compiles in Changefile'
                                #name: 'CheckBox1'
                                #layout: #(#LayoutFrame 5 0 5 0 -5 1 27 0)
                                #model: #updChanges
                                #translateLabel: true
                              )
                             #(#CheckBoxSpec
                                #label: 'Log doIts in Changefile'
                                #name: 'CheckBox2'
                                #layout: #(#LayoutFrame 5 0 30 0 -5 1 52 0)
                                #model: #logDoits
                                #translateLabel: true
                              )
                             #(#LabelSpec
                                #label: 'Changefile Name:'
                                #name: 'ChangefileNameLabel'
                                #layout: #(#LayoutFrame 5 0 55 0 200 0 77 0)
                                #translateLabel: true
                                #adjust: #right
                              )
                             #(#InputFieldSpec
                                #name: 'ChangeFileNameEntryField'
                                #layout: #(#LayoutFrame 200 0 55 0 -5 1 77 0)
                                #model: #changeFileName
                                #immediateAccept: true
                                #acceptOnReturn: true
                                #acceptOnTab: true
                                #acceptOnLostFocus: true
                                #acceptOnPointerLeave: true
                              )
                             )
                           
                          )
                          #extent: #(#Point 551 120)
                        )
                       )
                     
                    )
                    #extent: #(#Point 551 250)
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::SystemMessageSettingsAppl methodsFor:'actions'!

basicSaveSettings

    ObjectMemory infoPrinting:self vmInfo value.
    ObjectMemory debugPrinting:self vmErrors value.
    Object infoPrinting:self classInfos value.
    DeviceWorkstation errorPrinting:self displayErrors value.
    ObjectMemory nameForChanges:self changeFileName value.
    Smalltalk logDoits:self logDoits value.
    Class updateChanges:self updChanges value.
!

help

    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/messageSettings.html'].
!

readSettings
    self vmInfo value:ObjectMemory infoPrinting.
    self vmErrors value:ObjectMemory debugPrinting.
    self classInfos value:Object infoPrinting.
    self displayErrors value:DeviceWorkstation errorPrinting.
    self changeFileName value:ObjectMemory nameForChanges.
    self logDoits value:Smalltalk logDoits.
    self updChanges value:Class updatingChanges.
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::SystemMessageSettingsAppl methodsFor:'aspects'!

changeFileName

    changeFileName isNil ifTrue:[
        changeFileName := ObjectMemory nameForChanges asValue.
        changeFileName onChangeSend:#evaluateModified to:self
    ].
    ^ changeFileName.
!

classInfos

    classInfos isNil ifTrue:[
        classInfos := Object infoPrinting asValue.
        classInfos onChangeSend:#evaluateModified to:self
    ].
    ^ classInfos.
!

displayErrors

    displayErrors isNil ifTrue:[
        displayErrors := DeviceWorkstation errorPrinting asValue.
        displayErrors onChangeSend:#evaluateModified to:self
    ].
    ^ displayErrors.
!

logDoits

    logDoits isNil ifTrue:[
        logDoits := Smalltalk logDoits asValue.
        logDoits onChangeSend:#evaluateModified to:self
    ].
    ^ logDoits.
!

updChanges

    updChanges isNil ifTrue:[
        updChanges := Class updatingChanges asValue.
        updChanges onChangeSend:#evaluateModified to:self
    ].
    ^ updChanges.
!

vmErrors

    vmErrors isNil ifTrue:[
        vmErrors := ObjectMemory debugPrinting asValue.
        vmErrors onChangeSend:#evaluateModified to:self
    ].
    ^ vmErrors.
!

vmInfo

    vmInfo isNil ifTrue:[
        vmInfo := ObjectMemory infoPrinting asValue.
        vmInfo onChangeSend:#evaluateModified to:self
    ].
    ^ vmInfo.
! !

!AbstractSettingsApplication::SystemMessageSettingsAppl methodsFor:'initialization & release'!

initialize

    resources := self class classResources.
    super initialize
! !

!AbstractSettingsApplication::SystemMessageSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^(self vmInfo value ~= ObjectMemory infoPrinting  or:[
      self vmErrors value ~= ObjectMemory debugPrinting or:[
      self classInfos value ~= Object infoPrinting or:[
      Smalltalk logDoits ~= self logDoits value or:[
      Class updatingChanges ~= self updChanges value or:[
      ObjectMemory nameForChanges ~= self changeFileName value or:[
      self displayErrors value ~= DeviceWorkstation errorPrinting ]]]]]])
! !

!AbstractSettingsApplication::ToolsSettingsAppl class methodsFor:'image specs'!

defaultIcon
    "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 defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:#'AbstractSettingsApplication::ToolsSettingsAppl class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@@@@@@@@@@@@@@@@@@@@@@@@@@@B@ @@@@@@@@@@@@@@@@@@@@@@@@@@@ H@
@@@@@@@D@ XFA @@@@@@@@@@@@HB@@@@@@@@@@HC@ XFA @@@@@@@@@B@ @@@@@@@@@@@@\BCPXF@@@@@@@@@ H@@@@RB @@@@@@@ <MA @@@@@@@@HB@@@@
D <MB@@B@  MC0X@@@@@@@@B@ @@@@LCD@4OCP<MC08FA X@@@@@@ H@@@DR@0LCD@<MC08FA  FA @@@@HB@@@@D!!HR@0LC@0LCA <LBPXF@@@B@ @@@@@@
D!!HRD!!HC@0LCC04KBP@@@ H@@@@@@@@@@AHRD!!HR@0LCDP<@@@HB@@@@@@@@@@@@@@@@D!!HR@0LC@@@B@ @@@@@@@@@@@@X@@@@@D!!HR@0@@@ H@@@@@@@@@
@@@@@@@@@@@@D 4@@@HB@@@@@@@@@@@@@@@@@@@@@@@@@@@B@ @@@@@@@@@@@@@@@@@@@@@@@@@@@ H@@@@@@@@@@@@@@@@@@@@@@@@@@@HB@ HB@ HB@ HB
@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ @a') ; colorMapFromArray:#[0 0 0 48 48 48 96 100 96 120 120 120 128 128 128 248 172 168 168 172 168 184 184 184 192 192 192 192 196 192 200 196 200 200 204 200 208 208 208 224 220 224 232 232 232 232 236 232 240 236 240 240 240 240 248 252 248]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@?@@@?0@@_8@GO<@G3<@G?>@G??@G?? G?? C?? @?? @G? @B_ @@G @@A @@@@@@@@@@@@@@@@') ; yourself); yourself]
! !

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Tool Settings'
          #name: 'Tool Settings'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 511 513)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#VerticalPanelViewSpec
              #name: 'VerticalPanel2'
              #layout: #(#LayoutFrame 0 0 0 0 358 0 234 0)
              #horizontalLayout: #left
              #verticalLayout: #top
              #horizontalSpace: 3
              #verticalSpace: 3
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#CheckBoxSpec
                    #label: 'Use the New Changes Browser'
                    #name: 'ChangesBrowser'
                    #model: #useNewChangesBrowser
                    #translateLabel: true
                    #extent: #(#Point 489 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Use the New System Browser'
                    #name: 'NewSystemBrowser'
                    #model: #useNewSystemBrowser
                    #translateLabel: true
                    #extent: #(#Point 489 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Use the New VersionDiff Browser'
                    #name: 'VersionDiffBrowser'
                    #model: #useNewVersionDiffBrowser
                    #translateLabel: true
                    #extent: #(#Point 489 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Use the New File Browser'
                    #name: 'NewFileBrowser'
                    #model: #useNewFileBrowser
                    #translateLabel: true
                    #extent: #(#Point 489 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Use the New FileTree File Dialog'
                    #name: 'UseNewFileDialogCheckBox'
                    #model: #useNewFileDialog
                    #translateLabel: true
                    #extent: #(#Point 489 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Use the New Settings Dialog'
                    #name: 'UseNewSettinsApplicationCheckBox'
                    #model: #useNewSettingsApplication
                    #translateLabel: true
                    #extent: #(#Point 489 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Use the New Process Monitor'
                    #name: 'UseNewProcessMonitor'
                    #model: #useProcessMonitorV2
                    #translateLabel: true
                    #extent: #(#Point 489 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Use Hierarchical Inspector'
                    #name: 'HierarchicalInspector'
                    #model: #useNewInspector
                    #translateLabel: true
                    #extent: #(#Point 489 25)
                  )
                 #(#CheckBoxSpec
                    #label: 'Show Clock in Launcher'
                    #name: 'Clock'
                    #model: #showClockInLauncher
                    #translateLabel: true
                    #extent: #(#Point 489 25)
                  )
                 #(#ViewSpec
                    #name: 'Box1'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Transcripts Buffer Size:'
                          #name: 'Label1'
                          #layout: #(#LayoutFrame 5 0 5 0 144 0 27 0)
                          #translateLabel: true
                          #adjust: #right
                        )
                       #(#InputFieldSpec
                          #name: 'Transcripts Buffer Size'
                          #layout: #(#LayoutFrame 147 0 5 0 -5 1 27 0)
                          #model: #transcriptBufferSize
                          #type: #number
                          #immediateAccept: true
                          #acceptOnReturn: true
                          #acceptOnTab: true
                          #acceptOnLostFocus: true
                          #acceptOnPointerLeave: true
                        )
                       )
                     
                    )
                    #extent: #(#Point 489 27)
                  )
                 )
               
              )
              #useDefaultExtent: true
            )
           )
         
        )
      )
! !

!AbstractSettingsApplication::ToolsSettingsAppl methodsFor:'actions'!

basicSaveSettings

    | showClock launcher reopenLauncher|

    currentUserPrefs := UserPreferences current.
    currentUserPrefs useNewInspector:self useNewInspector value.
    currentUserPrefs useNewChangesBrowser:self useNewChangesBrowser value.
    currentUserPrefs useNewSystemBrowser:self useNewSystemBrowser value.
    currentUserPrefs useNewVersionDiffBrowser:self useNewVersionDiffBrowser value.
    currentUserPrefs useNewFileDialog:self useNewFileDialog value.
    currentUserPrefs useProcessMonitorV2:self useProcessMonitorV2 value.
    currentUserPrefs useNewSettingsApplication ~= self useNewSettingsApplication value ifTrue:[
        currentUserPrefs useNewSettingsApplication:self useNewSettingsApplication value.
        reopenLauncher := true.
    ].
    (Smalltalk at:#FileBrowserV2) isBehavior ifTrue:[
        currentUserPrefs useNewFileBrowser ~= self useNewFileBrowser value ifTrue:[
            currentUserPrefs useNewFileBrowser:self useNewFileBrowser value.
            (self useNewFileBrowser value and:[FileBrowserV2 isLoaded]) ifTrue:[
                FileBrowserV2 installInLauncher.
            ] ifFalse:[
                FileBrowserV2 removeFromLauncher.
            ].
            reopenLauncher := true.
        ]
    ].
    showClock := self showClockInLauncher value.
    currentUserPrefs showClockInLauncher ~= showClock ifTrue:[
        currentUserPrefs showClockInLauncher:showClock.
        launcher := Transcript application.
        (launcher isKindOf:ToolApplicationModel) ifTrue:[
            showClock ifTrue:[
                launcher startClock
            ] ifFalse:[
                launcher stopClock
            ]
        ]
    ].
    Inspector := currentUserPrefs inspectorClassSetting.
    Transcript current lineLimit:self transcriptBufferSize value.
    reopenLauncher ifTrue:[
        launcher := Transcript application.
        (launcher isKindOf:ToolApplicationModel) ifTrue:[
            launcher reopenLauncher.
        ]
    ].
!

help

    self withWaitCursorDo:[HTMLDocumentView openFullOnHelpFile:'Launcher/toolSettings.html'].
!

readSettings
    currentUserPrefs := UserPreferences current.
    self showClockInLauncher value:currentUserPrefs showClockInLauncher.
    self transcriptBufferSize value:Transcript current lineLimit.
    self useNewChangesBrowser value:currentUserPrefs useNewChangesBrowser.
    self useNewFileBrowser value:currentUserPrefs useNewFileBrowser.
    self useNewInspector value:currentUserPrefs useNewInspector.
    self useNewSystemBrowser value:currentUserPrefs useNewSystemBrowser.
    self useNewVersionDiffBrowser 
        value:currentUserPrefs useNewVersionDiffBrowser.
    self useProcessMonitorV2 value:currentUserPrefs useProcessMonitorV2.
    self useNewFileDialog value:currentUserPrefs useNewFileDialog.
    self useNewSettingsApplication 
        value:currentUserPrefs useNewSettingsApplication.
    self modifiedChannel value:false
! !

!AbstractSettingsApplication::ToolsSettingsAppl methodsFor:'aspects'!

showClockInLauncher

    showClockInLauncher isNil ifTrue:[
        showClockInLauncher := currentUserPrefs showClockInLauncher asValue.
        showClockInLauncher onChangeSend:#evaluateModified to:self
    ].
    ^ showClockInLauncher.
!

transcriptBufferSize

    transcriptBufferSize isNil ifTrue:[
        transcriptBufferSize := Transcript current lineLimit asValue.
        transcriptBufferSize onChangeSend:#evaluateModified to:self
    ].
    ^ transcriptBufferSize.
!

useNewChangesBrowser

    useNewChangesBrowser isNil ifTrue:[
        useNewChangesBrowser := currentUserPrefs useNewChangesBrowser asValue.
        useNewChangesBrowser onChangeSend:#evaluateModified to:self
    ].
    ^ useNewChangesBrowser.
!

useNewFileBrowser

    useNewFileBrowser isNil ifTrue:[
        useNewFileBrowser := currentUserPrefs useNewFileBrowser asValue.
        useNewFileBrowser onChangeSend:#evaluateModified to:self
    ].
    ^ useNewFileBrowser.
!

useNewFileDialog

    useNewFileDialog isNil ifTrue:[
        useNewFileDialog := true asValue.
        useNewFileDialog onChangeSend:#evaluateModified to:self
    ].
    ^ useNewFileDialog.
!

useNewInspector

    useNewInspector isNil ifTrue:[
        useNewInspector := currentUserPrefs useNewInspector asValue.
        useNewInspector onChangeSend:#evaluateModified to:self
    ].
    ^ useNewInspector.
!

useNewSettingsApplication

    useNewSettingsApplication isNil ifTrue:[
        useNewSettingsApplication := true asValue.
        useNewSettingsApplication onChangeSend:#evaluateModified to:self
    ].
    ^ useNewSettingsApplication.
!

useNewSystemBrowser

    useNewSystemBrowser isNil ifTrue:[
        useNewSystemBrowser := currentUserPrefs useNewSystemBrowser asValue.
        useNewSystemBrowser onChangeSend:#evaluateModified to:self
    ].
    ^ useNewSystemBrowser.
!

useNewVersionDiffBrowser

    useNewVersionDiffBrowser isNil ifTrue:[
        useNewVersionDiffBrowser := currentUserPrefs useNewVersionDiffBrowser asValue.
        useNewVersionDiffBrowser onChangeSend:#evaluateModified to:self
    ].
    ^ useNewVersionDiffBrowser.
!

useProcessMonitorV2

    useProcessMonitorV2 isNil ifTrue:[
        useProcessMonitorV2 := currentUserPrefs useProcessMonitorV2 asValue.
        useProcessMonitorV2 onChangeSend:#evaluateModified to:self
    ].
    ^ useProcessMonitorV2.
! !

!AbstractSettingsApplication::ToolsSettingsAppl methodsFor:'queries'!

hasUnsavedChanges

    ^ ((self useNewInspector value       ~= currentUserPrefs useNewInspector)       or:[
       (self useNewChangesBrowser value  ~= currentUserPrefs useNewChangesBrowser)  or:[
       (self useNewSystemBrowser value   ~= currentUserPrefs useNewSystemBrowser)   or:[
       (self showClockInLauncher value   ~= currentUserPrefs showClockInLauncher)   or:[
       (self useNewVersionDiffBrowser value ~= currentUserPrefs useNewVersionDiffBrowser) or:[
       (self useNewFileBrowser value     ~= currentUserPrefs useNewFileBrowser) or:[
       (self useNewFileDialog value     ~= currentUserPrefs useNewFileDialog) or:[
       (self useNewSettingsApplication value ~= currentUserPrefs useNewSettingsApplication) or:[
       (self useProcessMonitorV2 value ~= currentUserPrefs useProcessMonitorV2) or:[
       (self transcriptBufferSize value  ~= Transcript current lineLimit)]]]]]]]]])
! !

!AbstractSettingsApplication class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/AbstractSettingsApplication.st,v 1.59 2003-04-29 10:07:20 penk Exp $'
! !