What do you suppose about this ?

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
4 messages Options
Reply | Threaded
Open this post in threaded view
|

What do you suppose about this ?

Hans Schueren
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! !

_______________________________________________
Beginners mailing list
[hidden email]
http://lists.squeakfoundation.org/mailman/listinfo/beginners
Reply | Threaded
Open this post in threaded view
|

Re: What do you suppose about this ?

Raymond Asselin-4
Hi Hans,
Don't know what is your question or problem, but if GraphicsDemo is a subclass of ViewManager, I suppose there is a reason.
So in your intialize method may be it would be good to add "super initialize" .



> Le 2014-12-10 à 14:47, Hans Schueren <[hidden email]> a écrit :
>
> 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.! !
>
>

_______________________________________________
Beginners mailing list
[hidden email]
http://lists.squeakfoundation.org/mailman/listinfo/beginners
Reply | Threaded
Open this post in threaded view
|

Re: What do you suppose about this ?

Michael Rice
In reply to this post by Hans Schueren
Hello Hans,

Even dwarves started small. I've attached a small counter program, condensed from the counter example given here:


The best way to use MVC in Morphic is to have both an MVC project and a Morphic project. Do your Smalltalk programming in the Browser available in Morphic and do your testing in the MVC project.

For the attached example:
* Open a Morphic Project.
* From the Tools menu select File List (at the bottom) to locate Demo-Counter.st on your system. Select it. Click filein button.
* From the Morphic Project menu, open an MVC project.
* Left-click to open menu. Select open, then select browser.
* Drag top-leftmost category window of browser to last entry,  Demo-Counter.st, and select it.
* In the next left adjacent pane click class at bottom of the pane. Then click CounterView.
* In the top rightmost pane of browser, click open.
* Select text inside quotes in "CounterView open." (4th line)
* Click right button on above text, select doit from menu. This should open the Counter window
with an initial value of 0.
* Right mouse Yellow) button in CounterView opens menu, revealing menu two choices, increment and decrement.

Note 1: This code won't work in Morphic without some changes.

Note 2: The original MVC mouse buttons were RED (leftmost), Yellow (middle) and Blue (rightmost). In Morphic, and thus also MVC, the Yellow and Blue buttons have been swapped.

Hope you find this helpful.

Michael  

  

On Wed, Dec 10, 2014 at 2:47 PM, Hans Schueren <[hidden email]> wrote:
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! !

_______________________________________________
Beginners mailing list
[hidden email]
http://lists.squeakfoundation.org/mailman/listinfo/beginners


_______________________________________________
Beginners mailing list
[hidden email]
http://lists.squeakfoundation.org/mailman/listinfo/beginners

Demo-Counter.st (5K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: What do you suppose about this ?

Benoit St-Jean
In reply to this post by Raymond Asselin-4
Just saw your post Raymond!  Welcome back to the wonderful Smalltalk world!!!
 
-----------------
Benoit St-Jean
Yahoo! Messenger: bstjean
Twitter: @BenLeChialeux
Pinterest: benoitstjean
IRC: lamneth
Blogue: endormitoire.wordpress.com
"A standpoint is an intellectual horizon of radius zero".  (A. Einstein)


From: Raymond Asselin <[hidden email]>
To: A friendly place to get answers to even the most basic questions about Squeak. <[hidden email]>
Sent: Wednesday, December 10, 2014 4:07 PM
Subject: Re: [Newbies] What do you suppose about this ?

Hi Hans,
Don't know what is your question or problem, but if GraphicsDemo is a subclass of ViewManager, I suppose there is a reason.
So in your intialize method may be it would be good to add "super initialize" .



> Le 2014-12-10 à 14:47, Hans Schueren <[hidden email]> a écrit :
>
> 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.! !
>
>

_______________________________________________
Beginners mailing list
[hidden email]
http://lists.squeakfoundation.org/mailman/listinfo/beginners


_______________________________________________
Beginners mailing list
[hidden email]
http://lists.squeakfoundation.org/mailman/listinfo/beginners