[Newbies] What do you suppose about this ?

Hans Schueren werbung at hans-schueren.de
Wed Dec 10 19:47:51 UTC 2014


What do you suppose about this ?

from Hans - the Byte Surfer




ViewManager subclass: #GraphicsDemo
   instanceVariableNames:
     'pen graphs selectedGraph pane bitmap '
   classVariableNames:
     'Count '
   poolDictionaries:
     'ColorConstants '    !


!GraphicsDemo class methods !

initialize
         "Private - Set the color count to 0."
     Count := 0.! !



!GraphicsDemo methods !

animationMenu
         "Private - Answer the animation menu."
     ^(Menu
          labels: 'Big red\Little blue\Spider\Stop\Clear' withCrs
          lines: #()
          selectors: #(bigRed littleBlue spider deactivateAnimation 
clearAnimation))
              title: '&Animation';
              owner: self;
              yourself!

bigRed
         "Private - Create a red animated mandala."
     | mandala |
     mandala := AnimatedObject mandala: 11 diameter: 72 color: ClrRed.
     pane addObject: mandala.
     mandala display!

cleanUp
         "Private - Clean up GraphicsDemo before closing."

     self clearAnimation.
     bitmap notNil
         ifTrue: [bitmap release].!

clearAnimation
         "Private - Clear the animation."
     | objects |
     objects := pane contents.
     pane clear.
     objects do: [: each | each frames do: [: f | f release]]!

close: aPane
          "Private - Release the bitmaps of the animated objects."

     Smalltalk isRunTime
         ifTrue: [
             (MessageBox confirm: 'Are you sure you want to exit?')
                 ifTrue: [
                     self cleanUp.
                     self close.
                     ^Smalltalk exit]
                 ifFalse: [
                     ^self]]
         ifFalse: [
             self cleanUp.
             Transcript notNil ifTrue:[
                 Transcript enableDemo].
             ^super close].!

copyMetaFile
         "Copy a metafile to the clipboard."
     | storedPicture |
     storedPicture := pen segments at: (graphs at: #mandala).
     storedPicture isNil ifTrue: [^self].
     storedPicture pen width: pen width;
     height: pen height.
     Clipboard setMetaFile: storedPicture!

deactivateAnimation
         "Private - Stop the animation."
     pane stopAll!

display: aPane
          "Private - Display aPane contents."
     selectedGraph isNil
         ifTrue: [pen erase]
         ifFalse: [
             selectedGraph = #displayBitmap
                 ifTrue: [^self displayBitmap].
             graphs at: selectedGraph ifAbsent: [^self].
             pen erase.
             pen drawSegment: (graphs at: selectedGraph)]!

displayBitmap
         "Private - Paste the bitmap."
     bitmap notNil
         ifTrue:[
            pen copyBitmap: bitmap
               from: bitmap boundingBox
               to: (0 @ 0 extent: pen extent)]!

drag: aPane
         "Private - Track the mouse."
      | animatedObject |
     animatedObject := aPane childAt: aPane mouseLocation.
     animatedObject notNil
         ifTrue: [animatedObject drag: aPane mouseLocation].
     aPane when: #button1Move perform: nil!

dragon
         "Private - Draw a dragon pattern where anInteger
          is the recursion factor."
    self drawBlockNow: [
         pen
             home;
             north;
             dragon: 11]
         for: #dragon!

drawBlock: aBlock for: symbol
         "Private - Draw the selected graphics in a segment
             and make a backup."
     | intState wasActive |
     wasActive := pane stop.
     pen erase.
     selectedGraph := symbol.
     (graphs includesKey: symbol)
         ifFalse: [
             graphs at: symbol put: (pen retainPicture: aBlock)].
     self display: nil.
     pane makeBackup.
     wasActive ifTrue: [pane go]!

drawBlockNow: aBlock for: symbol
         "Private - Draw the selected graphics and make a
           backup of the receiver."
     | intState wasActive |
     wasActive := pane stop.
     pen erase.
     selectedGraph := symbol.
     (graphs includesKey: symbol)
         ifTrue: [self display: nil]
         ifFalse: [
             graphs at: symbol put: (pen drawRetainPicture: aBlock)].
     pane makeBackup.
     wasActive ifTrue: [pane go]!

drawMandalas
         "Private - Draw 8 mandalas."
     (Commander pen: 8 forDC: pen handle medium: pane)
           place: (self mainView rectangle extent) // 2;
           fanOut;
           up;
           go: 90;
           down;
           mandala: 12 diameter: 170 initDir: 270!

drawSpirals
         "Private - Draw 4 spirals."
     | commander |
     commander := (Commander pen: 4 forDC: pen handle medium: pane).
     commander
         place: (self mainView rectangle extent) // 2;
         fanOut;
         up;
         go: 90;
         down.
     1 to: 180 do: [: i |
         commander
             go: i;
             turn: 122]!

drawWalkLine
         "Private - Draw rotating lines."
     | incrX incrY numberOfLines boundX |
     numberOfLines := 60.
     incrX := pen width / numberOfLines.
     incrY := pen height / numberOfLines.
     boundX := (incrX * (numberOfLines)).
     1 to: numberOfLines + 1 do: [: i |
           pen
               foreColor: (GraphicsTool paletteIndex: (
                   (Count := Count + 1) \\ 7 + 1));
               place: (i - 1 * incrX) rounded @ 0;
               goto: (boundX - (i * incrX) @ (i * incrY)) rounded]!

drawWith: graphPane
         "Private - Assign the receiver's pen."
     pen := graphPane pen!

graphicsMenu: aPane
         "Private - Set the menu for the graph pane."
     aPane setMenu: (
              (Menu
                    labels: '&Walk Line\&Mandala\M&ulti 
Mandala\&Dragon\Multi &Spiral\&Paste' withCrs
                    lines: #()
                    selectors: #(walkLine mandala multiMandala dragon 
multiSpiral paste))
                  title: '&Graphics';
                  owner: self;
                  yourself)!

initWindowSize
         "Private - Answer default initial window extent."
     ^Display extent * 7 // 8!

littleBlue
         "Private - Create a blue animated mandala."
     | mandala |
     mandala := AnimatedObject mandala: 9 diameter: 48 color: ClrBlue.
     pane addObject: mandala.
     mandala display!

mandala
         "Private - Draw a mandala."
     pen home.
     self drawBlockNow: [
         pen  mandala: 20 diameter: pen height * 7 // 8]
         for: #mandala!

mouseDown: aPane
         "Private - Process a mouse down event."
     | aPoint animatedObject |
     aPoint := aPane mouseLocation.
     animatedObject := aPane childAt: aPoint.
     animatedObject notNil ifTrue: [
         ^aPane when: #button1Move perform: #drag:]!

multiMandala
         "Private - Draw 8 mandalas."
     self drawBlockNow: [self drawMandalas]
         for: #multiMandala!

multiSpiral
         "Private - Draw 4 spirals."
     self drawBlockNow: [self drawSpirals]
         for: #multiSpiral!

open
         "Open the graphics demo window."
     graphs := Dictionary new.
     self label: 'Graphics Demo';
         foreColor: ClrBlack;
         backColor: ClrWhite;
         when: #close perform: #close:;
         owner: self.
     self addSubpane: (pane := AnimationPane new
         owner: self;
         when: #getContents perform: #drawWith:;
         when: #display perform: #display:;
         when: #button1Down perform: #mouseDown:;
         when: #getMenu perform: #graphicsMenu:).
     self openWindow.
     self menuWindow addMenu: self animationMenu.!

paste
         "Private - Paste a bitmap from the clipboard to window."
     selectedGraph := #displayBitmap.
     bitmap notNil ifTrue: [bitmap release].
     (bitmap := Clipboard getBitmap) isNil ifTrue: [^self].
     self displayBitmap.
     pane makeBackup!

pasteMetaFile
         "Paste a metafile from the clipboard."
     | storedPicture |
     storedPicture := Clipboard getMetaFile.
     storedPicture isNil ifTrue: [^self].
     pen erase.
     storedPicture play: pen!

setScale
         "Private - Set the scale for displaying selected graph demo."
      | scale |
      scale := (pen  width * 2 / pen width) @ (pen height * 2 /
          pen height).
      (pen setScale: scale) = 1
          ifFalse: [^self error: 'setScale error'].
      self perform: selectedGraph!

spider
         "Private - Create a spider chaser."
     | spider |
     spider := AnimatedObject spider: 100.
     pane addObject: spider.
     spider endBlock: [: s | Menu message: 'Gotcha!! !!'].
     spider display.
     spider animate!

walkLine
         "Private - Draw rotating lines."
     self drawBlock: [self drawWalkLine]
         for: #walkLine! !



More information about the Beginners mailing list