UIPainterView.st
changeset 59 0a2b2ff030a0
parent 57 5af567f52811
child 60 7542ab7fbbfe
equal deleted inserted replaced
58:668eb9eae2ac 59:0a2b2ff030a0
     1 "
       
     2  COPYRIGHT (c) 1995 by Claus Gittinger
       
     3 	      All Rights Reserved
       
     4 
       
     5  This software is furnished under a license and may be used
       
     6  only in accordance with the terms of that license and with the
       
     7  inclusion of the above copyright notice.   This software may not
       
     8  be provided or otherwise made available to, or used by, any
       
     9  other person.  No title to or ownership of the software is
       
    10  hereby transferred.
       
    11 "
       
    12 
       
    13 UIObjectView subclass:#UIPainterView
       
    14 	instanceVariableNames:'fontPanel viewProperties superclassName className methodName
       
    15 		categoryName'
       
    16 	classVariableNames:'HandCursor'
       
    17 	poolDictionaries:''
       
    18 	category:'Interface-UIPainter'
       
    19 !
       
    20 
       
    21 Object subclass:#ViewProperty
     1 Object subclass:#ViewProperty
    22 	instanceVariableNames:'aspectSelector changeSelector nameIndex view elementClass
     2 	instanceVariableNames:'aspectSelector changeSelector nameIndex view elementClass
    23 		labelSelector identifier tabable'
     3 		labelSelector identifier tabable defaultable menuSelector
       
     4 		initiallyInvisible'
    24 	classVariableNames:'Identifier'
     5 	classVariableNames:'Identifier'
    25 	poolDictionaries:''
     6 	poolDictionaries:''
    26 	privateIn:UIPainterView
     7 	privateIn:UIPainterView
    27 !
     8 !
    28 
       
    29 UIPainterView::ViewProperty subclass:#GroupProperties
       
    30 	instanceVariableNames:'controlledObjects group'
       
    31 	classVariableNames:''
       
    32 	poolDictionaries:''
       
    33 	privateIn:UIPainterView
       
    34 !
       
    35 
       
    36 !UIPainterView class methodsFor:'documentation'!
       
    37 
       
    38 copyright
       
    39 "
       
    40  COPYRIGHT (c) 1995 by Claus Gittinger
       
    41 	      All Rights Reserved
       
    42 
       
    43  This software is furnished under a license and may be used
       
    44  only in accordance with the terms of that license and with the
       
    45  inclusion of the above copyright notice.   This software may not
       
    46  be provided or otherwise made available to, or used by, any
       
    47  other person.  No title to or ownership of the software is
       
    48  hereby transferred.
       
    49 "
       
    50 !
       
    51 
       
    52 documentation
       
    53 "
       
    54     not yet finished, not yet published, not yet released.
       
    55 "
       
    56 ! !
       
    57 
       
    58 !UIPainterView class methodsFor:'defaults'!
       
    59 
       
    60 defaultMenuMessage   
       
    61     "This message is the default yo be sent to the menuHolder to get a menu
       
    62     "
       
    63     ^ #menu
       
    64 
       
    65 
       
    66 ! !
       
    67 
       
    68 !UIPainterView methodsFor:'accessing'!
       
    69 
       
    70 application
       
    71     self halt.
       
    72     ^ nil
       
    73 
       
    74     "Modified: 6.9.1995 / 00:46:44 / claus"
       
    75 !
       
    76 
       
    77 className
       
    78     ^ className
       
    79 
       
    80     "Modified: 5.9.1995 / 18:41:30 / claus"
       
    81 !
       
    82 
       
    83 className:aString
       
    84     className := aString
       
    85 
       
    86     "Modified: 5.9.1995 / 18:47:17 / claus"
       
    87 !
       
    88 
       
    89 className:aClassName superclassName:aSuperclassName selector:aSelector
       
    90     className := aClassName.
       
    91     superclassName := aSuperclassName.
       
    92     methodName := aSelector.
       
    93 
       
    94 !
       
    95 
       
    96 methodName
       
    97     ^ methodName
       
    98 
       
    99     "Modified: 5.9.1995 / 18:41:34 / claus"
       
   100 !
       
   101 
       
   102 methodName:aString
       
   103     methodName := aString
       
   104 
       
   105     "Modified: 5.9.1995 / 18:47:27 / claus"
       
   106 !
       
   107 
       
   108 selectNames:aStringOrCollection
       
   109     |prop coll s|
       
   110 
       
   111     (aStringOrCollection isNil or:[aStringOrCollection isEmpty]) ifTrue:[
       
   112         ^ self unselect
       
   113     ].
       
   114 
       
   115     (s := aStringOrCollection) isString ifFalse:[
       
   116         s size == 1 ifTrue:[
       
   117             s := s first
       
   118         ] ifFalse:[
       
   119             coll := OrderedCollection new.
       
   120 
       
   121             s do:[:aName|
       
   122                 (prop := self propertyOfName:aName) notNil ifTrue:[
       
   123                     coll add:(prop view)
       
   124                 ]
       
   125             ].
       
   126             coll size == 1 ifTrue:[ ^ self select:(coll at:1) ].
       
   127             coll size == 0 ifTrue:[ ^ self unselect ].
       
   128 
       
   129           ^ self select:coll.
       
   130         ]
       
   131     ].
       
   132 
       
   133     prop := self propertyOfName:s.
       
   134     prop isNil ifTrue:[^ self unselect]
       
   135               ifFalse:[^ self select:(prop view)]
       
   136 
       
   137 ! !
       
   138 
       
   139 !UIPainterView ignoredMethodsFor:'code manipulation'!
       
   140 
       
   141 changeClass
       
   142     |box classNameHolder superclassNameHolder|
       
   143 
       
   144     classNameHolder := (className ? 'MyClass') asValue.
       
   145     superclassNameHolder := (superclassName ? 'ApplicationModel') asValue.
       
   146 
       
   147     box := DialogBox new.
       
   148     box addTextLabel:'class:'.
       
   149     box addInputFieldOn:classNameHolder.
       
   150     box addTextLabel:'super class:'.
       
   151     box addInputFieldOn:superclassNameHolder.
       
   152     box addAbortButton; addOkButton.
       
   153 
       
   154     box open.
       
   155 
       
   156     box accepted ifTrue:[
       
   157         className := classNameHolder value.
       
   158         superclassName := superclassNameHolder value.
       
   159     ].
       
   160 
       
   161 
       
   162 
       
   163 
       
   164 
       
   165 
       
   166 !
       
   167 
       
   168 changeVariables
       
   169     | box names propList p n newName|
       
   170 
       
   171     names := VariableArray new.
       
   172     propList := VariableArray new.
       
   173     viewProperties do:[:props |
       
   174         n := props name.
       
   175         n notNil ifTrue:[
       
   176             names add:n.
       
   177             propList add:props
       
   178         ]
       
   179     ].
       
   180     box := BuilderVariablesBox new.
       
   181     box list:names.
       
   182     box selectAction:[:selection |
       
   183         p := propList at:selection
       
   184     ].
       
   185     box okAction:[
       
   186         newName := box enterValue.
       
   187 Transcript showCR:('renamed ' , (p name) , 'to:' , newName).
       
   188         p name:newName
       
   189     ].
       
   190     box showAtPointer
       
   191 
       
   192 
       
   193 
       
   194 ! !
       
   195 
       
   196 !UIPainterView methodsFor:'creating subviews'!
       
   197 
       
   198 addProperties:properties for:aView
       
   199     "set properties to a view and add properties to viewProperties.
       
   200      In case that properties are nil properties are created
       
   201     "
       
   202     |name props|
       
   203 
       
   204     (props := properties) isNil ifTrue:[
       
   205         props := self propertiesForNewView:aView.
       
   206     ].
       
   207 
       
   208     viewProperties add:props.
       
   209     name := props name.
       
   210 
       
   211     (aView respondsTo:#label:) ifTrue:[
       
   212         aView label:name
       
   213     ].
       
   214     aView name:name.
       
   215   ^ props
       
   216 !
       
   217 
       
   218 propertiesForNewView:aView
       
   219     |cls props index|
       
   220 
       
   221     cls := aView class.
       
   222 
       
   223     props := ViewProperty new.
       
   224     props view:aView.
       
   225     props elementClass:cls.
       
   226     index := self variableIndexForClass:cls.
       
   227     props nameIndex:index.
       
   228     props name:(self variableNameForClass:cls index:index).
       
   229 
       
   230 "/    props initCode:nil.       --- add user-defined init code later
       
   231 
       
   232     ^ props
       
   233 !
       
   234 
       
   235 setupCreatedObject:anObject
       
   236     "set default properties for a created object
       
   237     "
       
   238     |props|
       
   239 
       
   240     props := self addProperties:nil for:anObject.
       
   241 
       
   242     undoHistory transaction:#create text:(props name) do:[
       
   243         self undoCreate:(props identifier).
       
   244     ].
       
   245 ! !
       
   246 
       
   247 !UIPainterView methodsFor:'drag & drop'!
       
   248 
       
   249 canDrop:anObjectOrCollection
       
   250     Transcript showCR:'canDrop'.
       
   251     ^ true
       
   252 
       
   253 
       
   254 !
       
   255 
       
   256 drop:anObjectOrCollection at:aPoint
       
   257     Transcript showCR:'drop:anObjectOrCollection at:aPoint'.
       
   258 
       
   259 
       
   260 ! !
       
   261 
       
   262 !UIPainterView methodsFor:'event handling'!
       
   263 
       
   264 keyPress:key x:x y:y
       
   265     <resource: #keyboard ( #Copy #Paste) >
       
   266 
       
   267     key == #Copy ifTrue:[
       
   268         ^ self copySelection
       
   269     ].
       
   270 
       
   271     key == #Paste ifTrue:[
       
   272         ^ self pasteBuffer
       
   273     ].
       
   274 
       
   275     super keyPress:key x:x y:y
       
   276 
       
   277 
       
   278 
       
   279 
       
   280 
       
   281 ! !
       
   282 
       
   283 !UIPainterView ignoredMethodsFor:'generating output'!
       
   284 
       
   285 generateClassDefinition
       
   286     |defCode|
       
   287 
       
   288     defCode := superclassName , ' subclass:#' , className , '\'.
       
   289     defCode := defCode , '  instanceVariableNames:'''.
       
   290     defCode := defCode , self subviewVariableNames , '''\'.
       
   291     defCode := defCode , '  classVariableNames:''''\'.
       
   292     defCode := defCode , '  poolDictionaries:''''\'.
       
   293     defCode := defCode , '  category:''' , categoryName , '''\'.
       
   294     defCode := defCode , Character excla asString , '\\'.
       
   295 
       
   296     ^ defCode withCRs
       
   297 
       
   298 
       
   299 
       
   300 ! !
       
   301 
       
   302 !UIPainterView methodsFor:'generating output'!
       
   303 
       
   304 generateCode
       
   305     "generate code for the windowSpec method"
       
   306 
       
   307     |code|
       
   308 
       
   309     code := ''.
       
   310 
       
   311 "/    (Smalltalk classNamed:className asSymbol) isNil ifTrue:[
       
   312 "/        code := code , self generateClassDefinition.
       
   313 "/    ].
       
   314 "/    code := code , self generateInitMethod.
       
   315 
       
   316     code := code , self generateWindowSpecMethodSource.
       
   317 
       
   318 "/    code := code , self generateAspectMethods.
       
   319 
       
   320     ^ code withCRs
       
   321 
       
   322     "Modified: 5.9.1995 / 20:57:53 / claus"
       
   323 ! !
       
   324 
       
   325 !UIPainterView ignoredMethodsFor:'generating output'!
       
   326 
       
   327 generateInitCodeForGroup:aGroup
       
   328     |code c name p objects outlets moreCode sym typ val|
       
   329 
       
   330     " <name> := <GroupClass> in:<name-of-superview>"
       
   331 
       
   332     code := ''.
       
   333 
       
   334     p := self propertyOfGroup:aGroup.
       
   335     name := p at:#variableName.
       
   336     c := '  ' , name , ' := ' , (aGroup class name) , ' new.\'.
       
   337 
       
   338     code := code , c withCRs.
       
   339 
       
   340     " <name> <symbol>:<value>"
       
   341 
       
   342     objects := p at:#controlledObjects ifAbsent:[nil].
       
   343     objects notNil ifTrue:[
       
   344         objects do:[:controlledObject |
       
   345             c := c , name , ' add:' , (self variableNameOf:controlledObject) , '.\'
       
   346         ]
       
   347     ].
       
   348 
       
   349     code := code , c withCRs
       
   350 
       
   351 
       
   352 
       
   353 
       
   354 
       
   355 !
       
   356 
       
   357 generateInitCodeForOtherStuff
       
   358     |code g c name p outlets moreCode sym typ val|
       
   359 
       
   360     code := ''.
       
   361 
       
   362     "generate code for groups"
       
   363 
       
   364     viewProperties do:[:props |
       
   365         g := props at:#group ifAbsent:[nil].
       
   366         g notNil ifTrue:[
       
   367             code := code , (self generateInitCodeForGroup:g)
       
   368         ]
       
   369     ].
       
   370     ^ code
       
   371 
       
   372 
       
   373 !
       
   374 
       
   375 generateInitCodeForView:aView
       
   376     |code c name p outlets moreCode sym typ val|
       
   377 
       
   378     " <name> := <ViewClass> in:<name-of-superview>"
       
   379 
       
   380     code := ''.
       
   381 
       
   382     p := self propertyOfView:aView.
       
   383     name := p at:#variableName.
       
   384     c := '    ' , name , ' := ' ,
       
   385          (aView class name) , ' in:' , (self variableNameOf:(aView superView)) , '.\'.
       
   386 
       
   387     " <name> origin:(...) extent:(...)"
       
   388 
       
   389     c := c , '    ' , name , ' origin:(', aView origin printString , ')'
       
   390                     , ' extent:(', aView extent printString , ').\'.
       
   391 
       
   392     moreCode := p at:#initCode ifAbsent:nil.
       
   393     moreCode notNil ifTrue:[
       
   394         c := c , moreCode , '\' withCRs
       
   395     ].
       
   396 
       
   397     code := code , c withCRs.
       
   398 
       
   399     " <name> <symbol>:<value>"
       
   400 
       
   401     outlets := p at:#outlets ifAbsent:[nil].
       
   402     outlets notNil ifTrue:[
       
   403         outlets do:[:selectorOutlet |
       
   404             sym := selectorOutlet at:#selector.
       
   405             typ := selectorOutlet at:#type.
       
   406             val := selectorOutlet at:#value.
       
   407             c :=  '    ' , name , ' ' , sym.
       
   408             (typ == #number) ifTrue:[
       
   409                 c := c , val printString
       
   410             ].
       
   411             (typ == #string) ifTrue:[
       
   412                 c := c , '''' , val , ''''
       
   413             ].
       
   414             (typ == #text) ifTrue:[
       
   415                 c := c , '''' , val asString , ''''
       
   416             ].
       
   417             (typ == #strings) ifTrue:[
       
   418                 c := c , '#( '.
       
   419                 val asText do:[:aString |
       
   420                     c := c , '''' , aString , ''' '
       
   421                 ].
       
   422                 c := c , ')'
       
   423             ].
       
   424             (typ == #block) ifTrue:[
       
   425                 c := c , val
       
   426             ].
       
   427             (typ == #color) ifTrue:[
       
   428                 c := c , '(Color name:''' , val , ''')'
       
   429             ].
       
   430             c := c , '.' , Character cr asString.
       
   431             code := code , c
       
   432         ]
       
   433     ].
       
   434 
       
   435     self subviewsOf:aView do:[:v |
       
   436         code := code , (self generateInitCodeForView:v)
       
   437     ].
       
   438     ^ code.
       
   439 
       
   440     "Modified: 5.9.1995 / 20:06:07 / claus"
       
   441 !
       
   442 
       
   443 generateInitMethod
       
   444     |defCode code|
       
   445 
       
   446     defCode := Character excla asString ,
       
   447                className , ' methodsFor:''initialization''' ,
       
   448                Character excla asString , '\\'.
       
   449 
       
   450     defCode := defCode , 'initialize\'.
       
   451     defCode := defCode , '    super initialize.\'.
       
   452     defCode := defCode , '    self setupSubViews.\'.
       
   453     defCode := defCode , '    self setupLocalStuff\'.
       
   454     defCode := defCode , Character excla asString , '\\'.
       
   455 
       
   456     defCode := defCode , 'setupSubViews\'.
       
   457     code := defCode withCRs.
       
   458 
       
   459     self subviewsOf:self do:[:v |
       
   460         code := code , (self generateInitCodeForView:v)
       
   461     ].
       
   462 
       
   463     code := code , (self generateInitCodeForOtherStuff).
       
   464 
       
   465     code := code , '    ^ self\' withCRs.
       
   466 
       
   467     defCode := Character excla asString , '\\'.
       
   468     defCode := defCode , 'setupLocalStuff\'.
       
   469     defCode := defCode , '    ^ self\'.
       
   470     defCode := defCode , Character excla asString , ' ' ,
       
   471                          Character excla asString , '\\'.
       
   472 
       
   473     code := code , defCode withCRs.
       
   474     ^ code.
       
   475 
       
   476 
       
   477 
       
   478 
       
   479 !
       
   480 
       
   481 generateOutlets
       
   482     ^ self
       
   483 ! !
       
   484 
       
   485 !UIPainterView methodsFor:'generating output'!
       
   486 
       
   487 generateSpecFor:something 
       
   488     "generate a spec for a view or collection of views
       
   489     "
       
   490     |spec views|
       
   491 
       
   492     something notNil ifTrue:[
       
   493         something isCollection ifTrue:[views := something]
       
   494                               ifFalse:[views := Array with:something].
       
   495 
       
   496         spec := views collect:[:aView||topSpec|
       
   497             aView specClass isNil ifTrue:[^ nil].
       
   498 
       
   499             topSpec := aView specClass 
       
   500                             fromView:aView 
       
   501                             callBack:[:newSpec :view | self stuffPropertiesFrom:view intoSpec:newSpec].
       
   502             topSpec
       
   503         ]
       
   504     ].
       
   505     ^ spec
       
   506 
       
   507 
       
   508 
       
   509 
       
   510 
       
   511 
       
   512 !
       
   513 
       
   514 generateWindowSpecMethodSource
       
   515     |spec specArray str code|
       
   516 
       
   517     subViews remove:inputView.
       
   518     [
       
   519         spec := FullSpec fromView:self callBack:[:newSpec :view | self stuffPropertiesFrom:view intoSpec:newSpec].
       
   520     ] valueNowOrOnUnwindDo:[
       
   521         subViews addFirst:inputView.
       
   522     ].
       
   523     specArray := spec literalArrayEncoding.
       
   524 
       
   525     str := WriteStream on:String new.
       
   526     self prettyPrintSpecArray:specArray on:str indent:5.
       
   527 
       
   528     code := Character excla asString 
       
   529             , className , ' class methodsFor:''interface specs'''
       
   530             , Character excla asString , '\\'
       
   531 
       
   532             , methodName , '\'
       
   533             , '    "this window spec was automatically generated by the ST/X UIPainter"\\'
       
   534             , '    "do not manually edit this - the painter/builder may not be able to\'
       
   535             , '     handle the specification if its corrupted."\\'
       
   536             , '    "\'
       
   537             , '     UIPainter new openOnClass:' , className , ' andSelector:#' , methodName , '\'
       
   538             , '     ' , className , ' new openInterface:#' , methodName , '\'
       
   539             , '    "\'.
       
   540 
       
   541     methodName = 'windowSpec' ifTrue:[
       
   542         code := code , '    "' , className , ' open"\'
       
   543     ].
       
   544     code := code 
       
   545             , '\'
       
   546             , '    <resource: #canvas>\\'
       
   547             , '    ^\' 
       
   548             , '     ', str contents
       
   549             , '\'
       
   550             , Character excla asString
       
   551             , ' '
       
   552             , Character excla asString
       
   553             , '\\'.
       
   554 
       
   555     ^ code withCRs
       
   556 
       
   557     "Modified: 5.9.1995 / 21:01:35 / claus"
       
   558 ! !
       
   559 
       
   560 !UIPainterView ignoredMethodsFor:'generating output'!
       
   561 
       
   562 nameOfClass
       
   563     ^ 'NewView'
       
   564 ! !
       
   565 
       
   566 !UIPainterView methodsFor:'generating output'!
       
   567 
       
   568 outletValueOf:aSymbol for:aView
       
   569 "/    |c name p outlets moreCode sym typ val|
       
   570 "/
       
   571 "/    p := self propertyOfView:aView.
       
   572 "/    outlets := p at:#outlets ifAbsent:[^ nil].
       
   573 "/    outlets notNil ifTrue:[
       
   574 "/        outlets do:[:selectorOutlet |
       
   575 "/            sym := selectorOutlet at:#selector.
       
   576 "/            (sym == aSymbol) ifTrue:[
       
   577 "/                typ := selectorOutlet at:#type.
       
   578 "/                val := selectorOutlet at:#value.
       
   579 "/                ^ val
       
   580 "/            ]
       
   581 "/        ]
       
   582 "/    ].
       
   583     ^ nil
       
   584 
       
   585 
       
   586 
       
   587 
       
   588 !
       
   589 
       
   590 prettyPrintSpecArray:spec on:aStream indent:i
       
   591     "just for your convenience: prettyPrint a specArray to aStream - it looks better that way"
       
   592 
       
   593     |what oneLine|
       
   594 
       
   595     spec isArray ifFalse:[
       
   596         spec isLiteral ifTrue:[
       
   597             aStream nextPutAll:spec storeString
       
   598         ] ifFalse:[
       
   599             self halt.
       
   600         ].
       
   601         ^ self
       
   602     ].
       
   603 
       
   604     spec isEmpty ifTrue:[
       
   605         aStream nextPutAll:'#()'.
       
   606         ^ self
       
   607     ].
       
   608 
       
   609     what := spec at:1.
       
   610     what isArray ifTrue:[
       
   611         aStream cr; spaces:i+2.
       
   612         aStream nextPutAll:'#('.
       
   613         "/ a spec-collection
       
   614         spec do:[:element |
       
   615             self prettyPrintSpecArray:element on:aStream indent:i+2.
       
   616         ].
       
   617         aStream cr.
       
   618         aStream spaces:i+1.
       
   619         aStream nextPutAll:')'.
       
   620         ^ self.
       
   621     ].
       
   622 
       
   623     oneLine := false.
       
   624     (#(#LayoutFrame #LayoutOrigin #AlignmentOrigin 
       
   625        #Rectangle #Point
       
   626        #Color #ColorValue
       
   627     ) 
       
   628     includesIdentical:what) ifTrue:[
       
   629         oneLine := true
       
   630     ].
       
   631 
       
   632     oneLine ifFalse:[
       
   633         aStream cr.
       
   634         aStream spaces:i+2.
       
   635     ].
       
   636     aStream nextPutAll:'#('.
       
   637 
       
   638 
       
   639     aStream nextPutAll:what storeString.
       
   640 
       
   641     oneLine ifFalse:[
       
   642         aStream cr.
       
   643         aStream spaces:i+4.
       
   644     ].
       
   645 
       
   646     2 to:spec size do:[:index |
       
   647         aStream space.
       
   648         self prettyPrintSpecArray:(spec at:index) on:aStream indent:i+4.
       
   649         oneLine ifFalse:[
       
   650             (index odd and:[index ~~ (spec size)]) ifTrue:[
       
   651                 aStream cr; spaces:i+4.
       
   652             ]
       
   653         ]
       
   654     ].
       
   655     oneLine ifFalse:[
       
   656         aStream cr.
       
   657         aStream spaces:i+1.
       
   658     ].
       
   659     aStream nextPutAll:')'.
       
   660 
       
   661     "Modified: 5.9.1995 / 17:44:20 / claus"
       
   662 !
       
   663 
       
   664 storeContentsOn:aStream
       
   665     viewProperties do:[:p| p storeOn:aStream]
       
   666 !
       
   667 
       
   668 stuffPropertiesFrom:view intoSpec:newSpec
       
   669     "stuff any additional information (held in the properties) into the spec
       
   670      which was just created from view"
       
   671 
       
   672     |props aspectSelector changeSelector labelSelector name tabable|
       
   673 
       
   674     props := self propertyOfView:view.
       
   675     props isNil ifTrue:[^ self].
       
   676 
       
   677     (aspectSelector := props aspectSelector) notNil ifTrue:[
       
   678         newSpec model:aspectSelector
       
   679     ].
       
   680     (changeSelector := props changeSelector) notNil ifTrue:[
       
   681         newSpec change:changeSelector
       
   682     ].
       
   683     (labelSelector := props labelSelector) notNil ifTrue:[
       
   684         newSpec label:labelSelector
       
   685     ].
       
   686     (tabable := props tabable) notNil ifTrue:[
       
   687         newSpec tabable:tabable
       
   688     ].
       
   689     (name := props name) notNil ifTrue:[
       
   690         newSpec name:name
       
   691     ].
       
   692 
       
   693 ! !
       
   694 
       
   695 !UIPainterView ignoredMethodsFor:'generating output'!
       
   696 
       
   697 subviewVariableNames
       
   698     |names|
       
   699 
       
   700     names := ''.
       
   701     viewProperties do:[:p| names := names , ' ' , (p name)].
       
   702   ^ names
       
   703 ! !
       
   704 
       
   705 !UIPainterView methodsFor:'generating output'!
       
   706 
       
   707 subviewsOf:aView do:aBlock
       
   708     |subs v|
       
   709 
       
   710     (subs := aView subViews) notNil ifTrue:[
       
   711         subs do:[:v|
       
   712             (v ~~ inputView and:[v notNil]) ifTrue:[
       
   713                 (viewProperties detect:[:p | p view == v] ifNone:nil) notNil ifTrue:[ 
       
   714                     (v superView == aView) ifTrue:[
       
   715                         aBlock value:v
       
   716                     ]
       
   717                 ]
       
   718             ]
       
   719         ]
       
   720     ]
       
   721 
       
   722 ! !
       
   723 
       
   724 !UIPainterView methodsFor:'group manipulations'!
       
   725 
       
   726 groupEnterFields
       
   727     |props name index group objects|
       
   728 
       
   729     selection isNil ifTrue:[^ self].
       
   730     self selectionDo:[:aView |
       
   731         (aView isKindOf:EditField) ifFalse:[
       
   732             self warn:'select EditFields only !!'.
       
   733             ^ self
       
   734         ]
       
   735     ].
       
   736     self selectionHiddenDo:[
       
   737         group := EnterFieldGroup new.
       
   738 
       
   739         props := GroupProperties new.
       
   740         props elementClass:EnterFieldGroup.
       
   741         props group:group.
       
   742         index := self variableIndexForClass:EnterFieldGroup.
       
   743         props nameIndex:index.
       
   744         name := self variableNameForClass:EnterFieldGroup index:index.
       
   745         props name:name.
       
   746         objects := OrderedCollection new.
       
   747         props controlledObjects:objects.
       
   748         viewProperties add:props.
       
   749 
       
   750         self selectionDo:[:aView |
       
   751             objects add:aView.
       
   752             group add:aView
       
   753         ].
       
   754     ]
       
   755 
       
   756 
       
   757 !
       
   758 
       
   759 groupRadioButtons
       
   760     |props name index group objects|
       
   761 
       
   762     selection isNil ifTrue:[^ self].
       
   763     self selectionDo:[:aView |
       
   764         (aView isKindOf:RadioButton) ifFalse:[
       
   765             self warn:'select RadioButtons only !!'.
       
   766             ^ self
       
   767         ]
       
   768     ].
       
   769     self selectionHiddenDo:[
       
   770         group := RadioButtonGroup new.
       
   771 
       
   772         props := GroupProperties new.
       
   773         props elementClass:RadioButtonGroup.
       
   774         props group:group.
       
   775         index := self variableIndexForClass:RadioButtonGroup.
       
   776         props nameIndex:index.
       
   777         name := self variableNameForClass:RadioButtonGroup index:index.
       
   778         props name:name.
       
   779         group groupID:name asSymbol.
       
   780         objects := OrderedCollection new.
       
   781         props controlledObjects:objects.
       
   782         viewProperties add:props.
       
   783 
       
   784         self selectionDo:[:aView |
       
   785             aView turnOff.
       
   786             objects add:aView.
       
   787             group add:aView
       
   788         ].
       
   789     ]
       
   790 
       
   791     "Modified: 5.9.1995 / 16:06:15 / claus"
       
   792 ! !
       
   793 
       
   794 !UIPainterView methodsFor:'initialization'!
       
   795 
       
   796 initialize
       
   797     super initialize.
       
   798 
       
   799     superclassName := 'ApplicationModel'.
       
   800     className      := 'NewApplication'.
       
   801     methodName     := 'windowSpec'.
       
   802     categoryName   := 'Applications'.
       
   803     viewProperties := OrderedCollection new.
       
   804     HandCursor     := Cursor leftHand.
       
   805 
       
   806     "Modified: 5.9.1995 / 19:58:06 / claus"
       
   807 ! !
       
   808 
       
   809 !UIPainterView methodsFor:'interface to Builder'!
       
   810 
       
   811 addOutletDefinitionFor:outletSymbol type:type value:outletValue for:aView
       
   812     |outletProps selectorProps viewProps|
       
   813 
       
   814     viewProps := self propertyOfView:aView.
       
   815 "/    outletProps := viewProps at:#outlets ifAbsent:[nil].
       
   816 "/    outletProps isNil ifTrue:[
       
   817 "/        outletProps := Dictionary new.
       
   818 "/        viewProps at:#outlets put:outletProps
       
   819 "/    ].
       
   820 "/    selectorProps := outletProps at:outletSymbol ifAbsent:[nil].
       
   821 "/    selectorProps isNil ifTrue:[
       
   822 "/        selectorProps := Dictionary new.
       
   823 "/        outletProps at:outletSymbol put:selectorProps
       
   824 "/    ].
       
   825 "/
       
   826 "/    selectorProps at:#selector put:outletSymbol.
       
   827 "/    selectorProps at:#type put:type.
       
   828 "/    selectorProps at:#value put:outletValue
       
   829 
       
   830 !
       
   831 
       
   832 addSpec:specOrSpecArray
       
   833     |spec builder|
       
   834 
       
   835     spec := UISpecification from:specOrSpecArray.
       
   836 
       
   837     builder := UIBuilder new.
       
   838     builder componentCreationHook:[:view :spec :aBuilder |
       
   839                 self createdComponent:view forSpec:spec builder:aBuilder
       
   840             ].
       
   841     builder applicationClass:(Smalltalk classNamed:className).
       
   842     spec setupView:self for:builder.
       
   843 
       
   844     self realizeAllSubViews.
       
   845     inputView raise.
       
   846 
       
   847 "/    viewProperties := OrderedCollection new.
       
   848 "/    self generatePropertiesFor:(self subViews select:[:v | v ~~ inputView]).
       
   849 
       
   850     self changed:#tree.
       
   851 
       
   852 
       
   853     "Modified: 5.9.1995 / 23:36:55 / claus"
       
   854 !
       
   855 
       
   856 applicationName
       
   857     ^ className
       
   858 !
       
   859 
       
   860 aspectAt:aSymbol
       
   861     self halt.
       
   862     ^ nil
       
   863 
       
   864     "Modified: 6.9.1995 / 00:45:35 / claus"
       
   865 !
       
   866 
       
   867 aspectSelectorForView:aView
       
   868     |props aspect|
       
   869 
       
   870     props := self propertyOfView:aView.
       
   871     props isNil ifTrue:[^ nil].
       
   872     ^ props aspectSelector
       
   873 
       
   874 !
       
   875 
       
   876 changeSelectorForView:aView
       
   877     |props aspect|
       
   878 
       
   879     props := self propertyOfView:aView.
       
   880     props isNil ifTrue:[^ nil].
       
   881 "/    ^ props changeSelector
       
   882     ^ nil
       
   883 !
       
   884 
       
   885 createdComponent:newView forSpec:aSpec builder:aBuilder
       
   886     "callBack from UISpec view building"
       
   887 
       
   888     |props|
       
   889 
       
   890     props := self propertiesForNewView:newView.
       
   891 
       
   892     aSpec name notNil ifTrue:[
       
   893         (self propertyOfName:(aSpec name)) isNil ifTrue:[
       
   894             props name:aSpec name
       
   895         ]
       
   896     ].
       
   897 
       
   898     props labelSelector:(aSpec labelSelector).
       
   899     props aspectSelector:(aSpec modelSelector).
       
   900     props tabable:(aSpec tabable).
       
   901 
       
   902     viewProperties add:props.
       
   903 !
       
   904 
       
   905 generatePropertiesFor:aCollectionOfViews
       
   906 
       
   907     "/ done as two loops, to get bread-first naming
       
   908 
       
   909     aCollectionOfViews do:[:aView|
       
   910         |props|
       
   911 
       
   912         props := self propertiesForNewView:aView.
       
   913         viewProperties add:props.
       
   914         aView name:(props name).
       
   915 
       
   916         aView geometryLayout isNil ifTrue:[
       
   917             aView geometryLayout:(aView bounds asLayout).
       
   918         ]
       
   919     ].
       
   920 
       
   921     aCollectionOfViews do:[:aView |
       
   922         |subs|
       
   923 
       
   924         subs := aView subViews.
       
   925         subs notNil ifTrue:[
       
   926             self generatePropertiesFor:subs
       
   927         ]
       
   928     ].
       
   929 
       
   930 !
       
   931 
       
   932 inspectAttributes
       
   933     |p|
       
   934 
       
   935     self singleSelectionDo:[:aView |
       
   936         p := self propertyOfView:aView.
       
   937         p inspect
       
   938     ]
       
   939 !
       
   940 
       
   941 inspectSpec
       
   942     |s|
       
   943 
       
   944     self singleSelectionDo:[:aView |
       
   945         s := self generateSpecFor:aView.
       
   946         s first inspect
       
   947     ]
       
   948 !
       
   949 
       
   950 setAspectSelector:aspectSymbol forView:aView
       
   951     |props|
       
   952 
       
   953     props := self propertyOfView:aView.
       
   954 
       
   955     props notNil ifTrue:[
       
   956         self transaction:#aspect selectionDo:[:aView|
       
   957             |oldAspect|
       
   958 
       
   959             oldAspect := props aspectSelector.
       
   960 
       
   961             undoHistory addUndoBlock:[
       
   962                 props aspectSelector:oldAspect.
       
   963                 aView superView sizeChanged:nil
       
   964             ]
       
   965         ].
       
   966         props aspectSelector:aspectSymbol
       
   967     ]
       
   968 !
       
   969 
       
   970 setChangeSelector:changeSymbol forView:aView
       
   971     |props|
       
   972 
       
   973     props := self propertyOfView:aView.
       
   974     props notNil ifTrue:[
       
   975         props changeSelector:changeSymbol
       
   976     ]
       
   977 !
       
   978 
       
   979 setupFromSpec:specOrSpecArray
       
   980     self removeAll.
       
   981     self addSpec:specOrSpecArray
       
   982 !
       
   983 
       
   984 showFontPanel
       
   985     |action|
       
   986 
       
   987     fontPanel isNil ifTrue:[
       
   988 	fontPanel := FontPanel new 
       
   989     ].
       
   990 
       
   991     selection notNil ifTrue:[
       
   992 	action := [:family :face :style :size |
       
   993 		       self changeFontFamily:family face:face
       
   994 				       style:style size:size
       
   995 		  ].
       
   996 	fontPanel action:action.
       
   997 	fontPanel showAtPointer
       
   998     ]
       
   999 ! !
       
  1000 
       
  1001 !UIPainterView methodsFor:'menu & submenus'!
       
  1002 
       
  1003 menu
       
  1004     testMode ifFalse:[
       
  1005         selection notNil ifTrue:[^ self menuSelection ]
       
  1006                         ifFalse:[^ self menuPainter   ]
       
  1007     ].
       
  1008     ^ nil
       
  1009 !
       
  1010 
       
  1011 menuPainter
       
  1012     "menu in case of non empty selection; for views
       
  1013     "
       
  1014     |menu gridMenu|
       
  1015 
       
  1016     menu := PopUpMenu labels:( 
       
  1017                 resources array:#(
       
  1018                                   'paste' 
       
  1019                                   '-' 
       
  1020                                   'undo'
       
  1021                                   'delete undo history'
       
  1022                                   '-'
       
  1023                                   'grid'
       
  1024                                  ) 
       
  1025                               )
       
  1026                    selectors:#( 
       
  1027                                 #pasteBuffer
       
  1028                                 nil 
       
  1029                                 #undo
       
  1030                                 #undoDeleteAll
       
  1031                                 nil
       
  1032                                 #grid
       
  1033                               )
       
  1034                    accelerators:#(
       
  1035                                   #Paste
       
  1036                                   nil
       
  1037                                   nil
       
  1038                                   nil
       
  1039                                   nil
       
  1040                                   nil
       
  1041                               )
       
  1042                      receiver:self.
       
  1043 
       
  1044     (self canPaste:(self getSelection)) ifFalse:[
       
  1045         menu disable:#pasteBuffer
       
  1046     ].
       
  1047 
       
  1048     undoHistory isEmpty ifTrue:[
       
  1049         menu disable:#undo
       
  1050     ] ifFalse:[
       
  1051         menu subMenuAt:#undo put:(undoHistory popupMenu)
       
  1052     ].
       
  1053 
       
  1054     gridMenu := PopUpMenu labels:(
       
  1055                             resources array:#(
       
  1056                                     '\c show' 
       
  1057                                     '\c align'
       
  1058                                   )
       
  1059                                 )
       
  1060                       selectors:#(
       
  1061                                     #gridShown:
       
  1062                                     #gridAlign:
       
  1063                                 ).
       
  1064 
       
  1065     gridMenu checkToggleAt:#gridShown: put:(self gridShown).
       
  1066     gridMenu checkToggleAt:#gridAlign: put:aligning.
       
  1067     menu subMenuAt:#grid put:gridMenu.
       
  1068 
       
  1069   ^ menu
       
  1070 
       
  1071 
       
  1072 !
       
  1073 
       
  1074 menuSelection
       
  1075     "menu in case of non empty selection; for views
       
  1076     "
       
  1077     |menu|
       
  1078 
       
  1079     menu := PopUpMenu labels:( resources array:#(
       
  1080                                   'copy' 
       
  1081                                   'cut' 
       
  1082                                   'paste' 
       
  1083                                   '-' 
       
  1084                                   'arrange'
       
  1085                                   'dimension'
       
  1086                                   'align'
       
  1087                                 )
       
  1088                               )
       
  1089                    selectors:#(   #copySelection
       
  1090                                   #deleteSelection
       
  1091                                   #pasteBuffer
       
  1092                                   nil
       
  1093                                   #arrange
       
  1094                                   #dimension
       
  1095                                   #align
       
  1096                               )
       
  1097                    accelerators:#(#Copy
       
  1098                                   #Cut
       
  1099                                   #Paste
       
  1100                                   nil
       
  1101                                   nil
       
  1102                                   nil
       
  1103                                   nil
       
  1104                               )
       
  1105                      receiver:self.
       
  1106 
       
  1107     (    (self canPaste:(self getSelection))
       
  1108      and:[self supportsSubComponents:selection]
       
  1109     ) ifFalse:[
       
  1110         menu disable:#pasteBuffer
       
  1111     ].
       
  1112 
       
  1113     menu subMenuAt:#arrange   put:(self subMenuArrange).
       
  1114     menu subMenuAt:#dimension put:(self subMenuDimension).
       
  1115     menu subMenuAt:#align     put:(self subMenuAlign).
       
  1116   ^ menu
       
  1117 !
       
  1118 
       
  1119 subMenuAlign
       
  1120     "returns submenu alignment
       
  1121     "
       
  1122     |menu|
       
  1123 
       
  1124     menu := PopUpMenu labels:(
       
  1125                 resources array:#(
       
  1126                                     'align left' 
       
  1127                                     'align right'
       
  1128                                     'align left & right'
       
  1129                                     'align top' 
       
  1130                                     'align bottom'
       
  1131                                     'align centered vertical'
       
  1132                                     'align centered horizontal'
       
  1133                                     '-'
       
  1134                                     'spread horizontal'
       
  1135                                     'spread vertical'
       
  1136                                     'center horizontal in frame'
       
  1137                                     'center vertical in frame'
       
  1138                                   )
       
  1139                          )
       
  1140 
       
  1141               selectors:#(  
       
  1142                             alignSelectionLeft
       
  1143                             alignSelectionRight
       
  1144                             alignSelectionLeftAndRight
       
  1145                             alignSelectionTop
       
  1146                             alignSelectionBottom
       
  1147                             alignSelectionCenterHor
       
  1148                             alignSelectionCenterVer
       
  1149                             nil
       
  1150                             spreadSelectionHor
       
  1151                             spreadSelectionVer
       
  1152                             centerSelectionHor
       
  1153                             centerSelectionVer
       
  1154                          )
       
  1155                receiver:self.
       
  1156     ^ menu    
       
  1157 
       
  1158 !
       
  1159 
       
  1160 subMenuArrange
       
  1161     "returns submenu arrange
       
  1162     "
       
  1163     |menu|
       
  1164 
       
  1165     menu := PopUpMenu labels:( 
       
  1166                 resources array:#(
       
  1167                                     'to front' 
       
  1168                                     'to back' 
       
  1169                                  )
       
  1170                               )
       
  1171                    selectors:#(
       
  1172                                     raiseSelection
       
  1173                                     lowerSelection
       
  1174                               )
       
  1175                      receiver:self.
       
  1176   ^ menu
       
  1177 !
       
  1178 
       
  1179 subMenuDimension
       
  1180     "returns submenu dimension
       
  1181     "
       
  1182     |menu|
       
  1183 
       
  1184     menu := PopUpMenu labels:( 
       
  1185                 resources array:#(
       
  1186                                     'default extent' 
       
  1187                                     'default width' 
       
  1188                                     'default height'
       
  1189                                     '-'
       
  1190                                     'copy extent'
       
  1191                                     '-'
       
  1192                                     'paste extent'
       
  1193                                     'paste width'
       
  1194                                     'paste height'
       
  1195                                  )
       
  1196                               )
       
  1197                    selectors:#(
       
  1198                                     setToDefaultExtent
       
  1199                                     setToDefaultWidth
       
  1200                                     setToDefaultHeight
       
  1201                                     nil
       
  1202                                     copyExtent
       
  1203                                     nil
       
  1204                                     pasteExtent
       
  1205                                     pasteWidth
       
  1206                                     pasteHeight
       
  1207                               )
       
  1208                      receiver:self.
       
  1209   ^ menu
       
  1210 !
       
  1211 
       
  1212 subMenuFont
       
  1213     "returns submenu dimension
       
  1214     "
       
  1215     |menu|
       
  1216 
       
  1217     menu := PopUpMenu labels:( 
       
  1218                 resources array:#(
       
  1219                                     'larger' 
       
  1220                                     'smaller'
       
  1221                                     '-'
       
  1222                                     'normal'
       
  1223                                     'bold'
       
  1224                                     'italic'
       
  1225                                     'bold italic'
       
  1226                                     '-'
       
  1227                                     'font panel'
       
  1228                                  )
       
  1229                               )
       
  1230                    selectors:#(
       
  1231                                     largerFont 
       
  1232                                     smallerFont
       
  1233                                     nil
       
  1234                                     normalFont
       
  1235                                     boldFont
       
  1236                                     italicFont
       
  1237                                     boldItalicFont
       
  1238                                     nil
       
  1239                                     showFontPanel
       
  1240                               )
       
  1241                      receiver:self.
       
  1242   ^ menu
       
  1243 ! !
       
  1244 
       
  1245 !UIPainterView methodsFor:'menu actions'!
       
  1246 
       
  1247 copySelection
       
  1248     "copy the selection into the cut&paste-buffer
       
  1249     "
       
  1250     |specs|
       
  1251 
       
  1252     specs := self generateSpecFor:selection.
       
  1253 
       
  1254     specs notNil ifTrue:[
       
  1255         self setSelection:specs
       
  1256     ].
       
  1257     self unselect.
       
  1258 !
       
  1259 
       
  1260 deleteSelection
       
  1261     "delete the selection
       
  1262     "
       
  1263     |specs text|
       
  1264 
       
  1265     self numberOfSelections ~~ 0 ifTrue:[
       
  1266         specs := self generateSpecFor:selection.
       
  1267         text  := self transactionTextFor:selection.
       
  1268 
       
  1269         undoHistory transaction:#cut text:text do:[
       
  1270             super deleteSelection
       
  1271         ].
       
  1272         self setSelection:specs
       
  1273     ]
       
  1274 !
       
  1275 
       
  1276 gridAlign:aBool
       
  1277     aBool ifTrue:[self alignOn]
       
  1278          ifFalse:[self alignOff]
       
  1279 !
       
  1280 
       
  1281 gridShown:aBool
       
  1282     aBool ifTrue:[self showGrid]
       
  1283          ifFalse:[self hideGrid]
       
  1284 
       
  1285 !
       
  1286 
       
  1287 lowerSelection
       
  1288 
       
  1289     self selectionDo:[:aView| aView lower ].
       
  1290 !
       
  1291 
       
  1292 pasteBuffer
       
  1293     "add the objects in the paste-buffer
       
  1294     "
       
  1295     |paste builder frame pasteOrigin pasteOffset|
       
  1296 
       
  1297     paste := self getSelection.
       
  1298 
       
  1299     (self canPaste:paste) ifFalse:[ ^ self].
       
  1300     (paste isCollection)  ifFalse:[ paste := Array with:paste].
       
  1301 
       
  1302     frame := self singleSelection.
       
  1303 
       
  1304     (self supportsSubComponents:frame) ifFalse:[
       
  1305         frame := self
       
  1306     ].
       
  1307     self unselect.
       
  1308 
       
  1309     builder     := UIBuilder new.
       
  1310     selection   := OrderedCollection new.
       
  1311     pasteOffset := 0@0.
       
  1312     pasteOrigin := self sensor mousePoint.
       
  1313     pasteOrigin := device translatePoint:pasteOrigin from:device rootView id to:frame id.
       
  1314 
       
  1315     paste do:[:aSpec|
       
  1316         |v org|
       
  1317 
       
  1318         builder componentCreationHook:[:view :spec :aBuilder |  
       
  1319             self createdComponent:view forSpec:spec builder:aBuilder.
       
  1320         ].
       
  1321         builder applicationClass:(Smalltalk classNamed:className).
       
  1322         v := aSpec buildViewWithLayoutFor:builder in:frame.
       
  1323 
       
  1324         (frame bounds containsPoint:pasteOrigin) ifFalse:[
       
  1325             self moveObject:v to:pasteOffset.
       
  1326         ] ifTrue:[
       
  1327             self moveObject:v to:pasteOrigin + pasteOffset.
       
  1328         ].
       
  1329 
       
  1330         v realize.
       
  1331         selection add:v.
       
  1332 
       
  1333         pasteOffset := pasteOffset + 4.
       
  1334     ].
       
  1335 
       
  1336     self transaction:#paste selectionDo:[:v|
       
  1337         self undoCreate:((self propertyOfView:v) identifier)
       
  1338     ].
       
  1339     selection size == 1 ifTrue:[
       
  1340         selection := selection at:1
       
  1341     ].
       
  1342     self showSelection.
       
  1343     self realizeAllSubViews.
       
  1344     inputView raise.
       
  1345     self changed:#tree
       
  1346 
       
  1347 !
       
  1348 
       
  1349 raiseSelection
       
  1350 
       
  1351     self selectionDo:[:aView|
       
  1352         aView raise.
       
  1353         inputView raise.
       
  1354     ].
       
  1355 
       
  1356 ! !
       
  1357 
       
  1358 !UIPainterView methodsFor:'misc'!
       
  1359 
       
  1360 changeFontFamily:family face:face style:style size:size
       
  1361     |f|
       
  1362 
       
  1363     f := Font family:family
       
  1364                 face:face
       
  1365                style:style
       
  1366                 size:size.
       
  1367 
       
  1368     f notNil ifTrue:[
       
  1369         self selectionHiddenDo:[
       
  1370             self selectionDo:[:aView |
       
  1371                 aView font:f.
       
  1372                 self elementChanged:aView.
       
  1373             ]
       
  1374         ]
       
  1375     ]
       
  1376 
       
  1377     "Modified: 5.9.1995 / 12:13:27 / claus"
       
  1378 !
       
  1379 
       
  1380 changeVariableNameOf:aView to:newName
       
  1381     |prop|
       
  1382 
       
  1383     prop := self propertyOf:aView.
       
  1384 
       
  1385     prop isNil ifTrue:[
       
  1386         ^ self error:'no such view'
       
  1387     ].
       
  1388 
       
  1389     ((aView respondsTo:#label:) and:[aView label = prop name]) ifTrue:[
       
  1390         self selectionHiddenDo:[
       
  1391             |layout|
       
  1392             layout := aView geometryLayout copy.
       
  1393             aView label:newName.
       
  1394             aView geometryLayout:layout.
       
  1395         ]
       
  1396     ].
       
  1397 
       
  1398     prop  name:newName.
       
  1399     aView name:newName.
       
  1400     self changed:#widgetName
       
  1401 
       
  1402 
       
  1403 
       
  1404 !
       
  1405 
       
  1406 variableIndexForClass:aClass
       
  1407     |max|
       
  1408 
       
  1409     max := 0.
       
  1410 
       
  1411     viewProperties do:[:p|
       
  1412         p elementClass == aClass ifTrue:[
       
  1413             max := max max:(p nameIndex)
       
  1414         ]
       
  1415     ].
       
  1416     ^ max + 1
       
  1417 
       
  1418 !
       
  1419 
       
  1420 variableNameForClass:aClass index:index
       
  1421     |n|
       
  1422 
       
  1423     n := (aClass name) , index printString.
       
  1424     n at:1 put:(n at:1) asLowercase.
       
  1425   ^ n
       
  1426 
       
  1427 !
       
  1428 
       
  1429 variableNameOf:aView
       
  1430     |prop|
       
  1431 
       
  1432     aView notNil ifTrue:[
       
  1433         prop := self propertyOf:aView
       
  1434     ].
       
  1435 
       
  1436     prop notNil ifTrue:[^ prop name]
       
  1437                ifFalse:[^ 'self']
       
  1438 
       
  1439 ! !
       
  1440 
       
  1441 !UIPainterView methodsFor:'removing components'!
       
  1442 
       
  1443 remove:something
       
  1444     "remove something, anObject or a collection of objects from the contents
       
  1445      do redraw"
       
  1446 
       
  1447     self forEach:something do:[:anObject |
       
  1448 	self removeObject:anObject
       
  1449     ]
       
  1450 
       
  1451 
       
  1452 !
       
  1453 
       
  1454 removeAll
       
  1455     "remove the argument, anObject"
       
  1456 
       
  1457     self unselect.
       
  1458 
       
  1459     subViews notNil ifTrue:[
       
  1460         subViews copy do:[:sub |
       
  1461             sub ~~ inputView ifTrue:[   
       
  1462                 self removeTreeFrom:sub
       
  1463             ]
       
  1464         ]
       
  1465     ].
       
  1466 
       
  1467     viewProperties := OrderedCollection new.
       
  1468     undoHistory reinitialize.
       
  1469     self changed:#tree
       
  1470 !
       
  1471 
       
  1472 removeObject:anObject
       
  1473     "remove the argument, anObject"
       
  1474 
       
  1475     self removeTreeFrom:anObject.
       
  1476     self changed:#tree
       
  1477 
       
  1478     "Modified: 5.9.1995 / 20:51:28 / claus"
       
  1479 !
       
  1480 
       
  1481 removeTreeFrom:anObject
       
  1482     "remove the argument, anObject and all of its children
       
  1483     "
       
  1484     |props|
       
  1485 
       
  1486     anObject notNil ifTrue:[
       
  1487         (anObject subViews notNil) ifTrue:[
       
  1488             anObject subViews copy do:[:sub |
       
  1489                 self removeTreeFrom:sub
       
  1490             ]
       
  1491         ].
       
  1492         props := self propertyOf:anObject.
       
  1493 
       
  1494         props notNil ifTrue:[
       
  1495             self undoRemove:props.
       
  1496             viewProperties remove:props
       
  1497         ].
       
  1498         anObject destroy
       
  1499     ]
       
  1500 ! !
       
  1501 
       
  1502 !UIPainterView methodsFor:'searching'!
       
  1503 
       
  1504 findObjectAt:aPoint
       
  1505     "find the origin/corner of the currentWidget
       
  1506     "
       
  1507     |view|
       
  1508 
       
  1509     view := super findObjectAt:aPoint.
       
  1510 
       
  1511     view notNil ifTrue:[
       
  1512         "can be a view within a view not visible
       
  1513         "
       
  1514         [ (self propertyOfView:view) isNil ] whileTrue:[
       
  1515             (view := view superView) == self ifTrue:[^ nil]
       
  1516         ]
       
  1517     ].
       
  1518     ^ view
       
  1519 ! !
       
  1520 
       
  1521 !UIPainterView methodsFor:'seraching property'!
       
  1522 
       
  1523 propertyOf:something
       
  1524 
       
  1525     ^ viewProperties detect:[:p| (p view == something or:[p group == something])]
       
  1526                      ifNone:nil
       
  1527 
       
  1528 
       
  1529 
       
  1530 
       
  1531 
       
  1532 !
       
  1533 
       
  1534 propertyOfGroup:aGroup
       
  1535 
       
  1536     ^ viewProperties detect:[:p| p group == aGroup] ifNone:nil
       
  1537 !
       
  1538 
       
  1539 propertyOfIdentifier:anIdentifier
       
  1540 
       
  1541     ^ viewProperties detect:[:p| p identifier == anIdentifier] ifNone:nil.
       
  1542 !
       
  1543 
       
  1544 propertyOfName:aString
       
  1545 
       
  1546     aString = 'self' ifFalse:[
       
  1547         ^ viewProperties detect:[:p| p name = aString] ifNone:nil
       
  1548     ].
       
  1549     ^ nil
       
  1550 !
       
  1551 
       
  1552 propertyOfView:aView
       
  1553 
       
  1554     aView == self ifFalse:[
       
  1555         ^ viewProperties detect:[:p| p view == aView] ifNone:nil
       
  1556     ].
       
  1557     ^ nil
       
  1558 ! !
       
  1559 
       
  1560 !UIPainterView methodsFor:'testing'!
       
  1561 
       
  1562 isHorizontalResizable:aComponent
       
  1563 
       
  1564     (aComponent isKindOf:ScrollBar) ifTrue:[
       
  1565         ^ aComponent orientation == #horizontal
       
  1566     ].
       
  1567     (aComponent isKindOf:Scroller) ifTrue:[
       
  1568         ^ aComponent orientation == #horizontal
       
  1569     ].
       
  1570     (aComponent isKindOf:Slider) ifTrue:[
       
  1571         ^ aComponent orientation == #horizontal
       
  1572     ].
       
  1573     ^ true
       
  1574 
       
  1575 
       
  1576 !
       
  1577 
       
  1578 isVerticalResizable:aComponent
       
  1579 
       
  1580     (aComponent isKindOf:EditField) ifTrue:[
       
  1581         ^ false
       
  1582     ].
       
  1583     (aComponent isKindOf:ComboBoxView) ifTrue:[
       
  1584         ^ false
       
  1585     ].
       
  1586     (aComponent isKindOf:CheckBox) ifTrue:[
       
  1587         ^ false
       
  1588     ].
       
  1589     (aComponent isKindOf:ScrollBar) ifTrue:[
       
  1590         ^ aComponent orientation == #vertical
       
  1591     ].
       
  1592     (aComponent isKindOf:Scroller) ifTrue:[
       
  1593         ^ aComponent orientation == #vertical
       
  1594     ].
       
  1595     (aComponent isKindOf:Slider) ifTrue:[
       
  1596         ^ aComponent orientation == #vertical
       
  1597     ].
       
  1598     ^ true
       
  1599 
       
  1600 
       
  1601 ! !
       
  1602 
       
  1603 !UIPainterView methodsFor:'transaction & undo'!
       
  1604 
       
  1605 transaction:aType objects:something do:aOneArgBlock
       
  1606     "opens a transaction and evaluates a block within the transaction; the
       
  1607      argument to the block is a view from derived from something
       
  1608     "
       
  1609     |text|
       
  1610 
       
  1611     something notNil ifTrue:[
       
  1612         text := self transactionTextFor:something.
       
  1613 
       
  1614         undoHistory transaction:aType text:text do:[
       
  1615             something isCollection ifTrue:[
       
  1616                 something do:[:aView| aOneArgBlock value:aView ]
       
  1617             ] ifFalse:[
       
  1618                 aOneArgBlock value:something
       
  1619             ]
       
  1620         ]
       
  1621     ]
       
  1622 !
       
  1623 
       
  1624 transactionTextFor:anElementOrCollection
       
  1625     "returns text used by transaction or nil
       
  1626     "
       
  1627     |props size|
       
  1628 
       
  1629     anElementOrCollection notNil ifTrue:[
       
  1630         anElementOrCollection isCollection ifTrue:[
       
  1631             size := anElementOrCollection.
       
  1632             size == 0 ifTrue:[^ nil].
       
  1633             size ~~ 1 ifTrue:[^ 'a collection'].
       
  1634 
       
  1635             props := self propertyOfView:(anElementOrCollection at:1).
       
  1636         ] ifFalse:[
       
  1637             props := self propertyOfView:anElementOrCollection
       
  1638         ].
       
  1639         props notNil ifTrue:[ ^ props name ]
       
  1640     ].
       
  1641     ^ nil
       
  1642 !
       
  1643 
       
  1644 undoCreate:aViewIdentifier
       
  1645 
       
  1646     undoHistory isTransactionOpen ifTrue:[
       
  1647         undoHistory addUndoBlock:[
       
  1648             |props|
       
  1649 
       
  1650             props := self propertyOfIdentifier:aViewIdentifier.
       
  1651 
       
  1652             props notNil ifTrue:[
       
  1653                 self removeObject:(props view)
       
  1654             ]
       
  1655         ]
       
  1656     ]
       
  1657 !
       
  1658 
       
  1659 undoRemove:propertyOfView
       
  1660     |clsName layout parent aView|
       
  1661 
       
  1662     (propertyOfView notNil and:[undoHistory isTransactionOpen]) ifFalse:[
       
  1663         ^ self
       
  1664     ].
       
  1665 
       
  1666     aView   := propertyOfView view.
       
  1667     clsName := aView class.
       
  1668     layout  := aView geometryLayout.
       
  1669     parent  := aView superView.
       
  1670 
       
  1671     parent ~~ self ifTrue:[
       
  1672         parent := (self propertyOf:parent) identifier.
       
  1673     ] ifFalse:[
       
  1674         parent := nil
       
  1675     ].
       
  1676     propertyOfView view:nil.    
       
  1677 
       
  1678     undoHistory addUndoBlock:[
       
  1679         |recreatedView props|
       
  1680 
       
  1681         parent notNil ifTrue:[
       
  1682             props := self propertyOfIdentifier:parent.
       
  1683 
       
  1684             props notNil ifTrue:[parent := props view]
       
  1685                         ifFalse:[parent := self]
       
  1686         ] ifFalse:[
       
  1687             parent := self
       
  1688         ].
       
  1689 
       
  1690         recreatedView := clsName in:parent.
       
  1691         recreatedView geometryLayout:layout.
       
  1692         propertyOfView view:recreatedView.    
       
  1693         self addProperties:propertyOfView for:recreatedView.
       
  1694         recreatedView realize.
       
  1695         inputView raise.
       
  1696     ].
       
  1697     aView := nil.
       
  1698 
       
  1699 ! !
       
  1700 
       
  1701 !UIPainterView methodsFor:'update from Specification'!
       
  1702 
       
  1703 updateFromSpec:aSpec
       
  1704     "update current selected view from specification
       
  1705     "
       
  1706     self singleSelection notNil ifTrue:[
       
  1707         self selectionHiddenDo:[
       
  1708             self transaction:#specification selectionDo:[:aView|
       
  1709                 |spec builder|
       
  1710 
       
  1711                 spec := (self generateSpecFor:aView) first.
       
  1712 
       
  1713                 undoHistory addUndoBlock:[
       
  1714                     builder := UIBuilder new.
       
  1715                     spec setAttributesIn:aView with:builder.
       
  1716                     aView superView sizeChanged:nil
       
  1717                 ].
       
  1718                 builder := UIBuilder new.
       
  1719                 aSpec setAttributesIn:aView with:builder.
       
  1720                 aView superView sizeChanged:nil.
       
  1721                 (self propertyOfView:aView) tabable:aSpec tabable.
       
  1722             ].
       
  1723             self changed:#tree
       
  1724         ]
       
  1725     ]
       
  1726 
       
  1727 ! !
       
  1728 
     9 
  1729 !UIPainterView::ViewProperty class methodsFor:'instance creation'!
    10 !UIPainterView::ViewProperty class methodsFor:'instance creation'!
  1730 
    11 
  1731 new
    12 new
  1732     Identifier notNil ifTrue:[Identifier := Identifier + 1]
    13     Identifier notNil ifTrue:[Identifier := Identifier + 1]
  1757 changeSelector:something
    38 changeSelector:something
  1758     "set the value of the instance variable 'changeSelector' (automatically generated)"
    39     "set the value of the instance variable 'changeSelector' (automatically generated)"
  1759 
    40 
  1760     changeSelector := something.!
    41     changeSelector := something.!
  1761 
    42 
       
    43 defaultable
       
    44     "return the value of the instance variable 'defaultable' (automatically generated)"
       
    45 
       
    46     ^ defaultable!
       
    47 
       
    48 defaultable:something
       
    49     "set the value of the instance variable 'defaultable' (automatically generated)"
       
    50 
       
    51     defaultable := something.!
       
    52 
  1762 elementClass
    53 elementClass
  1763     "return the value of the instance variable 'elementClass' (automatically generated)"
    54     "return the value of the instance variable 'elementClass' (automatically generated)"
  1764 
    55 
  1765     ^ elementClass!
    56     ^ elementClass!
  1766 
    57 
  1777     "return the unique identifier assigned to property
    68     "return the unique identifier assigned to property
  1778     "
    69     "
  1779     ^ identifier
    70     ^ identifier
  1780 !
    71 !
  1781 
    72 
       
    73 initiallyInvisible
       
    74     "return the value of the instance variable 'initiallyInvisible' (automatically generated)"
       
    75 
       
    76     ^ initiallyInvisible!
       
    77 
       
    78 initiallyInvisible:something
       
    79     "set the value of the instance variable 'initiallyInvisible' (automatically generated)"
       
    80 
       
    81     initiallyInvisible := something.!
       
    82 
  1782 labelSelector
    83 labelSelector
  1783     "return the value of the instance variable 'labelSelector' (automatically generated)"
    84     "return the value of the instance variable 'labelSelector' (automatically generated)"
  1784 
    85 
  1785     ^ labelSelector!
    86     ^ labelSelector!
  1786 
    87 
  1787 labelSelector:something
    88 labelSelector:something
  1788     "set the value of the instance variable 'labelSelector' (automatically generated)"
    89     "set the value of the instance variable 'labelSelector' (automatically generated)"
  1789 
    90 
  1790     labelSelector := something.!
    91     labelSelector := something.!
       
    92 
       
    93 menuSelector
       
    94     "return the value of the instance variable 'menuSelector' (automatically generated)"
       
    95 
       
    96     ^ menuSelector!
       
    97 
       
    98 menuSelector:something
       
    99     "set the value of the instance variable 'menuSelector' (automatically generated)"
       
   100 
       
   101     menuSelector := something.!
  1791 
   102 
  1792 name
   103 name
  1793     "return the value of the instance variable 'name' (automatically generated)"
   104     "return the value of the instance variable 'name' (automatically generated)"
  1794 
   105 
  1795     ^ view name
   106     ^ view name
  1836 initialize
   147 initialize
  1837     super initialize.
   148     super initialize.
  1838     identifier := Identifier
   149     identifier := Identifier
  1839 ! !
   150 ! !
  1840 
   151 
  1841 !UIPainterView::GroupProperties methodsFor:'accessing'!
       
  1842 
       
  1843 controlledObjects
       
  1844     "return the value of the instance variable 'controlledObjects' (automatically generated)"
       
  1845 
       
  1846     ^ controlledObjects!
       
  1847 
       
  1848 controlledObjects:something
       
  1849     "set the value of the instance variable 'controlledObjects' (automatically generated)"
       
  1850 
       
  1851     controlledObjects := something.!
       
  1852 
       
  1853 group
       
  1854     "return the value of the instance variable 'group' (automatically generated)"
       
  1855 
       
  1856     ^ group!
       
  1857 
       
  1858 group:something
       
  1859     "set the value of the instance variable 'group' (automatically generated)"
       
  1860 
       
  1861     group := something.! !
       
  1862 
       
  1863 !UIPainterView class methodsFor:'documentation'!
       
  1864 
       
  1865 version
       
  1866     ^ '$Header$'
       
  1867 ! !