UIPainterView.st
changeset 175 0b0b4d99e3e7
parent 165 f7df2a53d042
child 178 fb8451053c96
--- a/UIPainterView.st	Mon Jun 23 12:53:14 1997 +0200
+++ b/UIPainterView.st	Tue Jun 24 16:14:11 1997 +0200
@@ -17,16 +17,16 @@
 	category:'Interface-UIPainter'
 !
 
-Object subclass:#ViewProperty
-	instanceVariableNames:'view spec identifier'
-	classVariableNames:'Identifier'
+MultiSelectionInList subclass:#ListHolder
+	instanceVariableNames:'painter propertyList masterElement disabledChanged'
+	classVariableNames:''
 	poolDictionaries:''
 	privateIn:UIPainterView
 !
 
-MultiSelectionInList subclass:#ListHolder
-	instanceVariableNames:'painter propertyList masterElement disabledChanged'
-	classVariableNames:''
+Object subclass:#ViewProperty
+	instanceVariableNames:'view spec identifier'
+	classVariableNames:'Identifier'
 	poolDictionaries:''
 	privateIn:UIPainterView
 !
@@ -578,10 +578,7 @@
         |modelSelector menuSelector protoSpec thisCode|
 
         protoSpec := aProp spec.
-        protoSpec isNil ifTrue:[
-            self halt.
-            protoSpec := aProp view specClass basicNew.
-        ].
+
         (modelSelector := aProp model) notNil ifTrue:[
             (cls implements:modelSelector asSymbol) ifFalse:[
                 skip := false.
@@ -602,7 +599,6 @@
 
         (menuSelector := aProp menu) notNil ifTrue:[
             (cls implements:menuSelector asSymbol) ifFalse:[
-                "/ kludge ..
                 thisCode := (self generateAspectMethodFor:menuSelector spec:protoSpec inClass:cls).
                 code := code , thisCode
             ]
@@ -610,14 +606,12 @@
 
         aProp spec aspectSelectors do:[:aSel|
             (cls implements:aSel asSymbol) ifFalse:[
-                "/ kludge ..
                 thisCode := (self generateAspectMethodFor:aSel spec:protoSpec inClass:cls).
                 code := code , thisCode
             ]
         ].
         aProp spec actionSelectors do:[:aSel|
             (cls implements:aSel asSymbol) ifFalse:[
-                "/ kludge ..
                 thisCode := (self generateActionMethodFor:aSel spec:protoSpec inClass:cls).
                 code := code , thisCode
             ]
@@ -625,151 +619,6 @@
 
     ].
     ^ code
-
-    "Modified: 17.6.1997 / 14:07:36 / cg"
-!
-
-generateClassDefinition
-    |defCode|
-
-    defCode := superclassName , ' subclass:#' , className , '\'.
-    defCode := defCode , '  instanceVariableNames:'''.
-    defCode := defCode , self subviewVariableNames , '''\'.
-    defCode := defCode , '  classVariableNames:''''\'.
-    defCode := defCode , '  poolDictionaries:''''\'.
-    defCode := defCode , '  category:''' , categoryName , '''\'.
-    defCode := defCode , Character excla asString , '\\'.
-
-    ^ defCode withCRs
-
-
-
-!
-
-generateCode
-    "generate code for the windowSpec method"
-
-    |code|
-
-    self resetModification.
-
-    code := ''.
-
-"/    (Smalltalk classNamed:className asSymbol) isNil ifTrue:[
-"/        code := code , self generateClassDefinition.
-"/    ].
-"/    code := code , self generateInitMethod.
-
-    code := code , self generateWindowSpecMethodSource.
-
-"/    code := code , self generateAspectMethods.
-
-    ^ code withCRs
-
-    "Modified: 5.9.1995 / 20:57:53 / claus"
-!
-
-generateInitCodeForView:aView
-    |code c name p outlets moreCode sym typ val|
-
-    " <name> := <ViewClass> in:<name-of-superview>"
-
-    code := ''.
-
-    p := self propertyOfView:aView.
-    name := p at:#variableName.
-    c := '    ' , name , ' := ' ,
-         (aView class name) , ' in:' , (self uniqueNameOf:(aView superView)) , '.\'.
-
-    " <name> origin:(...) extent:(...)"
-
-    c := c , '    ' , name , ' origin:(', aView origin printString , ')'
-                    , ' extent:(', aView extent printString , ').\'.
-
-    moreCode := p at:#initCode ifAbsent:nil.
-    moreCode notNil ifTrue:[
-        c := c , moreCode , '\' withCRs
-    ].
-
-    code := code , c withCRs.
-
-    " <name> <symbol>:<value>"
-
-    outlets := p at:#outlets ifAbsent:[nil].
-    outlets notNil ifTrue:[
-        outlets do:[:selectorOutlet |
-            sym := selectorOutlet at:#selector.
-            typ := selectorOutlet at:#type.
-            val := selectorOutlet at:#value.
-            c :=  '    ' , name , ' ' , sym.
-            (typ == #number) ifTrue:[
-                c := c , val printString
-            ].
-            (typ == #string) ifTrue:[
-                c := c , '''' , val , ''''
-            ].
-            (typ == #text) ifTrue:[
-                c := c , '''' , val asString , ''''
-            ].
-            (typ == #strings) ifTrue:[
-                c := c , '#( '.
-                val asText do:[:aString |
-                    c := c , '''' , aString , ''' '
-                ].
-                c := c , ')'
-            ].
-            (typ == #block) ifTrue:[
-                c := c , val
-            ].
-            (typ == #color) ifTrue:[
-                c := c , '(Color name:''' , val , ''')'
-            ].
-            c := c , '.' , Character cr asString.
-            code := code , c
-        ]
-    ].
-
-    self subviewsOf:aView do:[:v |
-        code := code , (self generateInitCodeForView:v)
-    ].
-    ^ code.
-
-    "Modified: 5.9.1995 / 20:06:07 / claus"
-!
-
-generateInitMethod
-    |defCode code|
-
-    defCode := Character excla asString ,
-               className , ' methodsFor:''initialization''' ,
-               Character excla asString , '\\'.
-
-    defCode := defCode , 'initialize\'.
-    defCode := defCode , '    super initialize.\'.
-    defCode := defCode , '    self setupSubViews.\'.
-    defCode := defCode , '    self setupLocalStuff\'.
-    defCode := defCode , Character excla asString , '\\'.
-
-    defCode := defCode , 'setupSubViews\'.
-    code := defCode withCRs.
-
-    self subviewsOf:self do:[:v |
-        code := code , (self generateInitCodeForView:v)
-    ].
-    code := code , '    ^ self\' withCRs.
-
-    defCode := Character excla asString , '\\'.
-    defCode := defCode , 'setupLocalStuff\'.
-    defCode := defCode , '    ^ self\'.
-    defCode := defCode , Character excla asString , ' ' ,
-                         Character excla asString , '\\'.
-
-    code := code , defCode withCRs.
-    ^ code.
-
-
-
-
 !
 
 generateWindowSpecMethodSource
@@ -819,27 +668,6 @@
     ^ code withCRs
 
     "Modified: 5.9.1995 / 21:01:35 / claus"
-!
-
-storeContentsOn:aStream
-    listHolder propertiesDo:[:p| p storeOn:aStream]
-!
-
-subviewsOf:aView do:aBlock
-    |subs v|
-
-    (subs := aView subViews) notNil ifTrue:[
-        subs do:[:v|
-            (v ~~ inputView and:[v notNil]) ifTrue:[
-                (listHolder detectProperty:[:p|p view == v]) notNil ifTrue:[ 
-                    (v superView == aView) ifTrue:[
-                        aBlock value:v
-                    ]
-                ]
-            ]
-        ]
-    ]
-
 ! !
 
 !UIPainterView methodsFor:'initialization'!
@@ -867,29 +695,6 @@
 
 !
 
-initializeCreatedObject:anObject
-    "set default properties for a created object
-    "
-    |props spec cls|
-
-    cls   := anObject class.
-    spec  := anObject specClass fromView:anObject.
-    props := ViewProperty new.
-    props view:anObject.
-    props spec:spec.
-    props name:(self uniqueNameFor:spec).
-    listHolder add:props.
-
-    ((spec respondsTo:#label:) and:[self supportsLabel:anObject]) ifTrue:[
-        anObject label:(props name).
-        spec label:(props name)
-    ].
-
-    undoHistory withinTransaction:#create text:(props name) do:[
-        undoHistory addUndoSelector:#undoCreate: withArgs:(props identifier)
-    ].
-!
-
 setupFromSpec:specOrSpecArray
     |spec builder|
 
@@ -1079,49 +884,6 @@
 
 ! !
 
-!UIPainterView methodsFor:'selection'!
-
-addTreeFrom:aView to:aCollection
-    "add aView and contained subcomponents to collection
-    "
-    (self propertyOfView:aView) notNil ifTrue:[
-        aCollection add:aView.
-
-        (aView subViews notNil) ifTrue:[
-            aView subViews do:[:subView|
-                self addTreeFrom:subView to:aCollection
-            ]
-        ].
-    ]
-
-!
-
-selectSubComponents
-    "select all subcomponents for current selection
-    "
-    |startAtView aCollection|
-
-    aCollection := OrderedCollection new.
-    startAtView := self singleSelection.
-
-    startAtView isNil ifTrue:[
-        self subViews notNil ifTrue:[
-            self subViews do:[:subView|
-                subView ~~ inputView ifTrue:[
-                    self addTreeFrom:subView to:aCollection
-                ]
-            ]
-        ]
-    ] ifFalse:[
-        self addTreeFrom:startAtView to:aCollection
-    ].
-
-    aCollection size > 1 ifTrue:[
-        self updateSelectionFrom:aCollection.
-        self selectionChanged
-    ]
-! !
-
 !UIPainterView methodsFor:'specification'!
 
 addSpec:aSpecification builder:aBuilder in:aFrame
@@ -1245,64 +1007,6 @@
     ]
 ! !
 
-!UIPainterView methodsFor:'testing'!
-
-isHorizontalResizable:aComponent
-    "returns true if instance is horizontal resizeable
-    "
-    (aComponent isKindOf:ScrollBar) ifTrue:[
-        ^ aComponent orientation == #horizontal
-    ].
-    (aComponent isKindOf:Scroller) ifTrue:[
-        ^ aComponent orientation == #horizontal
-    ].
-    (aComponent isKindOf:Slider) ifTrue:[
-        ^ aComponent orientation == #horizontal
-    ].
-    ^ true
-
-
-!
-
-isVerticalResizable:aComponent
-    "returns true if instance is vertical resizeable
-    "
-    (aComponent isKindOf:EditField) ifTrue:[
-        ^ false
-    ].
-    (aComponent isKindOf:ComboBoxView) ifTrue:[
-        ^ false
-    ].
-    (aComponent isKindOf:CheckBox) ifTrue:[
-        ^ false
-    ].
-    (aComponent isKindOf:ScrollBar) ifTrue:[
-        ^ aComponent orientation == #vertical
-    ].
-    (aComponent isKindOf:Scroller) ifTrue:[
-        ^ aComponent orientation == #vertical
-    ].
-    (aComponent isKindOf:Slider) ifTrue:[
-        ^ aComponent orientation == #vertical
-    ].
-    ^ true
-
-
-!
-
-supportsLabel:aComponent
-    "returns true if component supports label
-    "
-    (aComponent respondsTo:#label:) ifTrue:[
-        (    (aComponent isKindOf:ArrowButton) 
-          or:[aComponent isKindOf:CheckToggle]
-        ) ifFalse:[
-            ^ true
-        ]
-    ].
-    ^ false
-! !
-
 !UIPainterView methodsFor:'transaction'!
 
 transaction:aType objects:something do:aOneArgBlock
@@ -1459,105 +1163,6 @@
 
 ! !
 
-!UIPainterView::ViewProperty class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-! !
-
-!UIPainterView::ViewProperty class methodsFor:'instance creation'!
-
-new
-    Identifier notNil ifTrue:[Identifier := Identifier + 1]
-                     ifFalse:[Identifier := 1].
-
-  ^ self basicNew initialize
-! !
-
-!UIPainterView::ViewProperty methodsFor:'accessing'!
-
-identifier
-    "return the unique identifier assigned to property
-    "
-    ^ identifier
-!
-
-identifier:anIdentifier
-    "set the unique identifier assigned to property; called after an restore of
-     a deleted instance
-    "
-    identifier := anIdentifier
-!
-
-spec
-    "return the value of the instance variable 'spec' (automatically generated)"
-
-    ^ spec!
-
-spec:something
-    "set the value of the instance variable 'spec' (automatically generated)"
-
-    spec := something.!
-
-view
-    "return the value of the instance variable 'view' (automatically generated)"
-
-    ^ view!
-
-view:something
-    "set the value of the instance variable 'view' (automatically generated)"
-
-    view := something.! !
-
-!UIPainterView::ViewProperty methodsFor:'initialization'!
-
-initialize
-    super initialize.
-    identifier := Identifier
-! !
-
-!UIPainterView::ViewProperty methodsFor:'misc'!
-
-extractNumberStartingAt:anIndex
-    "return the number from the name starting at anIndex or 0.
-    "
-    |val|
-
-    val := 0.
-
-    self name from:anIndex do:[:c|
-        c isDigit ifTrue:[val := val * 10 + c digitValue]
-                 ifFalse:[^ 0]
-    ].
-    ^ val
-        
-! !
-
-!UIPainterView::ViewProperty methodsFor:'spec messages'!
-
-doesNotUnderstand:aMessage
-    spec notNil ifTrue:[
-        (spec respondsTo:(aMessage selector)) ifTrue:[^ aMessage sendTo:spec]
-    ].
-    ^ nil
-!
-
-layout
-    spec layout
-!
-
-layout:aLayout
-    spec layout:aLayout
-!
-
-name
-    ^ spec name
-!
-
-name:aName
-    spec name:aName
-! !
-
 !UIPainterView::ListHolder class methodsFor:'instance creation'!
 
 for:aPainter
@@ -1891,6 +1496,105 @@
     super selectionIndex:aSel
 ! !
 
+!UIPainterView::ViewProperty class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+! !
+
+!UIPainterView::ViewProperty class methodsFor:'instance creation'!
+
+new
+    Identifier notNil ifTrue:[Identifier := Identifier + 1]
+                     ifFalse:[Identifier := 1].
+
+  ^ self basicNew initialize
+! !
+
+!UIPainterView::ViewProperty methodsFor:'accessing'!
+
+identifier
+    "return the unique identifier assigned to property
+    "
+    ^ identifier
+!
+
+identifier:anIdentifier
+    "set the unique identifier assigned to property; called after an restore of
+     a deleted instance
+    "
+    identifier := anIdentifier
+!
+
+spec
+    "return the value of the instance variable 'spec' (automatically generated)"
+
+    ^ spec!
+
+spec:something
+    "set the value of the instance variable 'spec' (automatically generated)"
+
+    spec := something.!
+
+view
+    "return the value of the instance variable 'view' (automatically generated)"
+
+    ^ view!
+
+view:something
+    "set the value of the instance variable 'view' (automatically generated)"
+
+    view := something.! !
+
+!UIPainterView::ViewProperty methodsFor:'initialization'!
+
+initialize
+    super initialize.
+    identifier := Identifier
+! !
+
+!UIPainterView::ViewProperty methodsFor:'misc'!
+
+extractNumberStartingAt:anIndex
+    "return the number from the name starting at anIndex or 0.
+    "
+    |val|
+
+    val := 0.
+
+    self name from:anIndex do:[:c|
+        c isDigit ifTrue:[val := val * 10 + c digitValue]
+                 ifFalse:[^ 0]
+    ].
+    ^ val
+        
+! !
+
+!UIPainterView::ViewProperty methodsFor:'spec messages'!
+
+doesNotUnderstand:aMessage
+    spec notNil ifTrue:[
+        (spec respondsTo:(aMessage selector)) ifTrue:[^ aMessage sendTo:spec]
+    ].
+    ^ nil
+!
+
+layout
+    spec layout
+!
+
+layout:aLayout
+    spec layout:aLayout
+!
+
+name
+    ^ spec name
+!
+
+name:aName
+    spec name:aName
+! !
+
 !UIPainterView class methodsFor:'documentation'!
 
 version