UIPainterView.st
changeset 55 19e021c8f1ef
parent 53 d03569a6ff03
child 57 5af567f52811
equal deleted inserted replaced
54:d0b5a33e6df0 55:19e021c8f1ef
     9  other person.  No title to or ownership of the software is
     9  other person.  No title to or ownership of the software is
    10  hereby transferred.
    10  hereby transferred.
    11 "
    11 "
    12 
    12 
    13 UIObjectView subclass:#UIPainterView
    13 UIObjectView subclass:#UIPainterView
    14 	instanceVariableNames:'fontPanel code viewProperties superclassName className methodName
    14 	instanceVariableNames:'fontPanel viewProperties superclassName className methodName
    15 		categoryName'
    15 		categoryName'
    16 	classVariableNames:'HandCursor'
    16 	classVariableNames:'HandCursor'
    17 	poolDictionaries:''
    17 	poolDictionaries:''
    18 	category:'Interface-UIPainter'
    18 	category:'Interface-UIPainter'
    19 !
    19 !
    84     className := aString
    84     className := aString
    85 
    85 
    86     "Modified: 5.9.1995 / 18:47:17 / claus"
    86     "Modified: 5.9.1995 / 18:47:17 / claus"
    87 !
    87 !
    88 
    88 
       
    89 className:aClassName superclassName:aSuperclassName selector:aSelector
       
    90     className := aClassName.
       
    91     superclassName := aSuperclassName.
       
    92     methodName := aSelector.
       
    93 
       
    94 !
       
    95 
    89 methodName
    96 methodName
    90     ^ methodName
    97     ^ methodName
    91 
    98 
    92     "Modified: 5.9.1995 / 18:41:34 / claus"
    99     "Modified: 5.9.1995 / 18:41:34 / claus"
    93 !
   100 !
   130     prop isNil ifTrue:[^ self unselect]
   137     prop isNil ifTrue:[^ self unselect]
   131               ifFalse:[^ self select:(prop view)]
   138               ifFalse:[^ self select:(prop view)]
   132 
   139 
   133 ! !
   140 ! !
   134 
   141 
   135 !UIPainterView methodsFor:'code manipulation'!
   142 !UIPainterView ignoredMethodsFor:'code manipulation'!
   136 
   143 
   137 changeClass
   144 changeClass
   138     |box classNameHolder superclassNameHolder|
   145     |box classNameHolder superclassNameHolder|
   139 
   146 
   140     classNameHolder := (className ? 'MyClass') asValue.
   147     classNameHolder := (className ? 'MyClass') asValue.
   238     undoHistory transaction:#create text:(props name) do:[
   245     undoHistory transaction:#create text:(props name) do:[
   239         self undoCreate:(props identifier).
   246         self undoCreate:(props identifier).
   240     ].
   247     ].
   241 ! !
   248 ! !
   242 
   249 
   243 !UIPainterView methodsFor:'generating output'!
   250 !UIPainterView ignoredMethodsFor:'generating output'!
   244 
   251 
   245 generateClassDefinition
   252 generateClassDefinition
   246     |defCode|
   253     |defCode|
   247 
   254 
   248     defCode := superclassName , ' subclass:#' , className , '\'.
   255     defCode := superclassName , ' subclass:#' , className , '\'.
   251     defCode := defCode , '  classVariableNames:''''\'.
   258     defCode := defCode , '  classVariableNames:''''\'.
   252     defCode := defCode , '  poolDictionaries:''''\'.
   259     defCode := defCode , '  poolDictionaries:''''\'.
   253     defCode := defCode , '  category:''' , categoryName , '''\'.
   260     defCode := defCode , '  category:''' , categoryName , '''\'.
   254     defCode := defCode , Character excla asString , '\\'.
   261     defCode := defCode , Character excla asString , '\\'.
   255 
   262 
   256     code := code , (defCode withCRs)
   263     ^ defCode withCRs
   257 
   264 
   258 
   265 
   259 
   266 
   260 !
   267 ! !
       
   268 
       
   269 !UIPainterView methodsFor:'generating output'!
   261 
   270 
   262 generateCode
   271 generateCode
       
   272     "generate code for the windowSpec method"
       
   273 
       
   274     |code|
       
   275 
   263     code := ''.
   276     code := ''.
   264     (Smalltalk classNamed:className) isNil ifTrue:[
   277 
   265         self generateClassDefinition.
   278 "/    (Smalltalk classNamed:className asSymbol) isNil ifTrue:[
   266     ].
   279 "/        code := code , self generateClassDefinition.
   267 "/    self generateInitMethod.
   280 "/    ].
   268     code := code , self generateWindowSpec.
   281 "/    code := code , self generateInitMethod.
   269     self generateOutlets.
   282 
   270 
   283     code := code , self generateWindowSpecMethodSource.
       
   284 
       
   285 "/    code := code , self generateAspectMethods.
   271 
   286 
   272     ^ code withCRs
   287     ^ code withCRs
   273 
   288 
   274     "Modified: 5.9.1995 / 20:57:53 / claus"
   289     "Modified: 5.9.1995 / 20:57:53 / claus"
   275 ! !
   290 ! !
   276 
   291 
   277 !UIPainterView ignoredMethodsFor:'generating output'!
   292 !UIPainterView ignoredMethodsFor:'generating output'!
   278 
   293 
   279 generateInitCodeForGroup:aGroup
   294 generateInitCodeForGroup:aGroup
   280     |c name p objects outlets moreCode sym typ val|
   295     |code c name p objects outlets moreCode sym typ val|
   281 
   296 
   282     " <name> := <GroupClass> in:<name-of-superview>"
   297     " <name> := <GroupClass> in:<name-of-superview>"
       
   298 
       
   299     code := ''.
   283 
   300 
   284     p := self propertyOfGroup:aGroup.
   301     p := self propertyOfGroup:aGroup.
   285     name := p at:#variableName.
   302     name := p at:#variableName.
   286     c := '  ' , name , ' := ' , (aGroup class name) , ' new.\'.
   303     c := '  ' , name , ' := ' , (aGroup class name) , ' new.\'.
   287 
   304 
   289 
   306 
   290     " <name> <symbol>:<value>"
   307     " <name> <symbol>:<value>"
   291 
   308 
   292     objects := p at:#controlledObjects ifAbsent:[nil].
   309     objects := p at:#controlledObjects ifAbsent:[nil].
   293     objects notNil ifTrue:[
   310     objects notNil ifTrue:[
   294 	objects do:[:controlledObject |
   311         objects do:[:controlledObject |
   295 	    c := c , name , ' add:' , (self variableNameOf:controlledObject) , '.\'
   312             c := c , name , ' add:' , (self variableNameOf:controlledObject) , '.\'
   296 	]
   313         ]
   297     ].
   314     ].
   298 
   315 
   299     code := code , c withCRs
   316     code := code , c withCRs
   300 
   317 
   301 
   318 
   303 
   320 
   304 
   321 
   305 !
   322 !
   306 
   323 
   307 generateInitCodeForOtherStuff
   324 generateInitCodeForOtherStuff
   308     |g c name p outlets moreCode sym typ val|
   325     |code g c name p outlets moreCode sym typ val|
       
   326 
       
   327     code := ''.
   309 
   328 
   310     "generate code for groups"
   329     "generate code for groups"
   311 
   330 
   312     viewProperties do:[:props |
   331     viewProperties do:[:props |
   313 	g := props at:#group ifAbsent:[nil].
   332         g := props at:#group ifAbsent:[nil].
   314 	g notNil ifTrue:[
   333         g notNil ifTrue:[
   315 	    self generateInitCodeForGroup:g
   334             code := code , (self generateInitCodeForGroup:g)
   316 	]
   335         ]
   317     ]
   336     ].
       
   337     ^ code
   318 
   338 
   319 
   339 
   320 !
   340 !
   321 
   341 
   322 generateInitCodeForView:aView
   342 generateInitCodeForView:aView
   323     |c name p outlets moreCode sym typ val|
   343     |code c name p outlets moreCode sym typ val|
   324 
   344 
   325     " <name> := <ViewClass> in:<name-of-superview>"
   345     " <name> := <ViewClass> in:<name-of-superview>"
       
   346 
       
   347     code := ''.
   326 
   348 
   327     p := self propertyOfView:aView.
   349     p := self propertyOfView:aView.
   328     name := p at:#variableName.
   350     name := p at:#variableName.
   329     c := '    ' , name , ' := ' ,
   351     c := '    ' , name , ' := ' ,
   330 	 (aView class name) , ' in:' , (self variableNameOf:(aView superView)) , '.\'.
   352          (aView class name) , ' in:' , (self variableNameOf:(aView superView)) , '.\'.
   331 
   353 
   332     " <name> origin:(...) extent:(...)"
   354     " <name> origin:(...) extent:(...)"
   333 
   355 
   334     c := c , '    ' , name , ' origin:(', aView origin printString , ')'
   356     c := c , '    ' , name , ' origin:(', aView origin printString , ')'
   335 		    , ' extent:(', aView extent printString , ').\'.
   357                     , ' extent:(', aView extent printString , ').\'.
   336 
   358 
   337     moreCode := p at:#initCode ifAbsent:nil.
   359     moreCode := p at:#initCode ifAbsent:nil.
   338     moreCode notNil ifTrue:[
   360     moreCode notNil ifTrue:[
   339 	c := c , moreCode , '\' withCRs
   361         c := c , moreCode , '\' withCRs
   340     ].
   362     ].
   341 
   363 
   342     code := code , c withCRs.
   364     code := code , c withCRs.
   343 
   365 
   344     " <name> <symbol>:<value>"
   366     " <name> <symbol>:<value>"
   345 
   367 
   346     outlets := p at:#outlets ifAbsent:[nil].
   368     outlets := p at:#outlets ifAbsent:[nil].
   347     outlets notNil ifTrue:[
   369     outlets notNil ifTrue:[
   348 	outlets do:[:selectorOutlet |
   370         outlets do:[:selectorOutlet |
   349 	    sym := selectorOutlet at:#selector.
   371             sym := selectorOutlet at:#selector.
   350 	    typ := selectorOutlet at:#type.
   372             typ := selectorOutlet at:#type.
   351 	    val := selectorOutlet at:#value.
   373             val := selectorOutlet at:#value.
   352 	    c :=  '    ' , name , ' ' , sym.
   374             c :=  '    ' , name , ' ' , sym.
   353 	    (typ == #number) ifTrue:[
   375             (typ == #number) ifTrue:[
   354 		c := c , val printString
   376                 c := c , val printString
   355 	    ].
   377             ].
   356 	    (typ == #string) ifTrue:[
   378             (typ == #string) ifTrue:[
   357 		c := c , '''' , val , ''''
   379                 c := c , '''' , val , ''''
   358 	    ].
   380             ].
   359 	    (typ == #text) ifTrue:[
   381             (typ == #text) ifTrue:[
   360 		c := c , '''' , val asString , ''''
   382                 c := c , '''' , val asString , ''''
   361 	    ].
   383             ].
   362 	    (typ == #strings) ifTrue:[
   384             (typ == #strings) ifTrue:[
   363 		c := c , '#( '.
   385                 c := c , '#( '.
   364 		val asText do:[:aString |
   386                 val asText do:[:aString |
   365 		    c := c , '''' , aString , ''' '
   387                     c := c , '''' , aString , ''' '
   366 		].
   388                 ].
   367 		c := c , ')'
   389                 c := c , ')'
   368 	    ].
   390             ].
   369 	    (typ == #block) ifTrue:[
   391             (typ == #block) ifTrue:[
   370 		c := c , val
   392                 c := c , val
   371 	    ].
   393             ].
   372 	    (typ == #color) ifTrue:[
   394             (typ == #color) ifTrue:[
   373 		c := c , '(Color name:''' , val , ''')'
   395                 c := c , '(Color name:''' , val , ''')'
   374 	    ].
   396             ].
   375 	    c := c , '.' , Character cr asString.
   397             c := c , '.' , Character cr asString.
   376 	    code := code , c
   398             code := code , c
   377 	]
   399         ]
   378     ].
   400     ].
   379 
   401 
   380     self subviewsOf:aView do:[:v |
   402     self subviewsOf:aView do:[:v |
   381 	self generateInitCodeForView:v
   403         code := code , (self generateInitCodeForView:v)
   382     ]
   404     ].
       
   405     ^ code.
   383 
   406 
   384     "Modified: 5.9.1995 / 20:06:07 / claus"
   407     "Modified: 5.9.1995 / 20:06:07 / claus"
   385 !
   408 !
   386 
   409 
   387 generateInitMethod
   410 generateInitMethod
   388     |defCode|
   411     |defCode code|
   389 
   412 
   390     defCode := Character excla asString ,
   413     defCode := Character excla asString ,
   391 	       className , ' methodsFor:''initialization''' ,
   414                className , ' methodsFor:''initialization''' ,
   392 	       Character excla asString , '\\'.
   415                Character excla asString , '\\'.
   393 
   416 
   394     defCode := defCode , 'initialize\'.
   417     defCode := defCode , 'initialize\'.
   395     defCode := defCode , '    super initialize.\'.
   418     defCode := defCode , '    super initialize.\'.
   396     defCode := defCode , '    self setupSubViews.\'.
   419     defCode := defCode , '    self setupSubViews.\'.
   397     defCode := defCode , '    self setupLocalStuff\'.
   420     defCode := defCode , '    self setupLocalStuff\'.
   398     defCode := defCode , Character excla asString , '\\'.
   421     defCode := defCode , Character excla asString , '\\'.
   399 
   422 
   400     defCode := defCode , 'setupSubViews\'.
   423     defCode := defCode , 'setupSubViews\'.
   401     code := code , defCode withCRs.
   424     code := defCode withCRs.
   402 
   425 
   403     self subviewsOf:self do:[:v |
   426     self subviewsOf:self do:[:v |
   404 	self generateInitCodeForView:v
   427         code := code , (self generateInitCodeForView:v)
   405     ].
   428     ].
   406 
   429 
   407     self generateInitCodeForOtherStuff.
   430     code := code , (self generateInitCodeForOtherStuff).
   408 
   431 
   409     code := code , '    ^ self\' withCRs.
   432     code := code , '    ^ self\' withCRs.
   410 
   433 
   411     defCode := Character excla asString , '\\'.
   434     defCode := Character excla asString , '\\'.
   412     defCode := defCode , 'setupLocalStuff\'.
   435     defCode := defCode , 'setupLocalStuff\'.
   413     defCode := defCode , '    ^ self\'.
   436     defCode := defCode , '    ^ self\'.
   414     defCode := defCode , Character excla asString , ' ' ,
   437     defCode := defCode , Character excla asString , ' ' ,
   415 			 Character excla asString , '\\'.
   438                          Character excla asString , '\\'.
   416 
   439 
   417     code := code , defCode withCRs
   440     code := code , defCode withCRs.
   418 
   441     ^ code.
   419 
   442 
   420 
   443 
   421 
   444 
   422 
   445 
   423 ! !
   446 !
   424 
       
   425 !UIPainterView methodsFor:'generating output'!
       
   426 
   447 
   427 generateOutlets
   448 generateOutlets
   428     ^ self
   449     ^ self
   429 !
   450 ! !
       
   451 
       
   452 !UIPainterView methodsFor:'generating output'!
   430 
   453 
   431 generateSpecFor:something
   454 generateSpecFor:something
   432     "generate a spec for a view or collection of views
   455     "generate a spec for a view or collection of views
   433     "
   456     "
   434     |spec views|
   457     |spec views|
   447         ]
   470         ]
   448     ].
   471     ].
   449     ^ spec
   472     ^ spec
   450 !
   473 !
   451 
   474 
   452 generateWindowSpec
   475 generateWindowSpecMethodSource
   453     |spec specArray str|
   476     |spec specArray str code|
   454 
   477 
   455     subViews remove:inputView.
   478     subViews remove:inputView.
   456     [
   479     [
   457         spec := FullSpec fromView:self callBack:[:newSpec :view | self stuffPropertiesFrom:view intoSpec:newSpec].
   480         spec := FullSpec fromView:self callBack:[:newSpec :view | self stuffPropertiesFrom:view intoSpec:newSpec].
   458     ] valueNowOrOnUnwindDo:[
   481     ] valueNowOrOnUnwindDo:[
   459         subViews addFirst:inputView.
   482         subViews addFirst:inputView.
   460     ].
   483     ].
   461 
       
   462     specArray := spec literalArrayEncoding.
   484     specArray := spec literalArrayEncoding.
       
   485 
   463     str := WriteStream on:String new.
   486     str := WriteStream on:String new.
   464     self prettyPrintSpecArray:specArray on:str indent:5.
   487     self prettyPrintSpecArray:specArray on:str indent:5.
   465 
   488 
   466     code := Character excla asString 
   489     code := Character excla asString 
   467             , className , ' class methodsFor:''interface specs'''
   490             , className , ' class methodsFor:''interface specs'''
   489             , '\\'.
   512             , '\\'.
   490 
   513 
   491     ^ code withCRs
   514     ^ code withCRs
   492 
   515 
   493     "Modified: 5.9.1995 / 21:01:35 / claus"
   516     "Modified: 5.9.1995 / 21:01:35 / claus"
   494 !
   517 ! !
       
   518 
       
   519 !UIPainterView ignoredMethodsFor:'generating output'!
   495 
   520 
   496 nameOfClass
   521 nameOfClass
   497     ^ 'NewView'
   522     ^ 'NewView'
   498 !
   523 ! !
       
   524 
       
   525 !UIPainterView methodsFor:'generating output'!
   499 
   526 
   500 outletValueOf:aSymbol for:aView
   527 outletValueOf:aSymbol for:aView
   501 "/    |c name p outlets moreCode sym typ val|
   528 "/    |c name p outlets moreCode sym typ val|
   502 "/
   529 "/
   503 "/    p := self propertyOfView:aView.
   530 "/    p := self propertyOfView:aView.
   617     ].
   644     ].
   618     (name := props name) notNil ifTrue:[
   645     (name := props name) notNil ifTrue:[
   619         newSpec name:name
   646         newSpec name:name
   620     ].
   647     ].
   621 
   648 
   622 !
   649 ! !
       
   650 
       
   651 !UIPainterView ignoredMethodsFor:'generating output'!
   623 
   652 
   624 subviewVariableNames
   653 subviewVariableNames
   625     |names|
   654     |names|
   626 
   655 
   627     names := ''.
   656     names := ''.
   628     viewProperties do:[:p| names := names , ' ' , (p name)].
   657     viewProperties do:[:p| names := names , ' ' , (p name)].
   629   ^ names
   658   ^ names
   630 !
   659 ! !
       
   660 
       
   661 !UIPainterView methodsFor:'generating output'!
   631 
   662 
   632 subviewsOf:aView do:aBlock
   663 subviewsOf:aView do:aBlock
   633     |subs v|
   664     |subs v|
   634 
   665 
   635     (subs := aView subViews) notNil ifTrue:[
   666     (subs := aView subViews) notNil ifTrue:[
   723 
   754 
   724     superclassName := 'ApplicationModel'.
   755     superclassName := 'ApplicationModel'.
   725     className      := 'NewApplication'.
   756     className      := 'NewApplication'.
   726     methodName     := 'windowSpec'.
   757     methodName     := 'windowSpec'.
   727     categoryName   := 'Applications'.
   758     categoryName   := 'Applications'.
   728 
       
   729     viewProperties := OrderedCollection new.
   759     viewProperties := OrderedCollection new.
   730     HandCursor     := Cursor leftHand.
   760     HandCursor     := Cursor leftHand.
   731 
   761 
   732     "Modified: 5.9.1995 / 19:58:06 / claus"
   762     "Modified: 5.9.1995 / 19:58:06 / claus"
   733 ! !
   763 ! !