[prev in list] [next in list] [prev in thread] [next in thread] 

List:       olpc-etoys
Subject:    Re: [etoys-dev] Etoys: MorphicExtras-kfr.77.mcz
From:       karl ramberg <karlramberg () gmail ! com>
Date:       2013-02-11 19:12:59
Message-ID: CAGzzWLh_rbEiddCUr6CUe_wsgzfp9p-oryU5X5gQMe=hd98KTA () mail ! gmail ! com
[Download RAW message or body]

[Attachment #2 (multipart/alternative)]


Hm, GraphMorph should not really be part of this...


On Mon, Feb 11, 2013 at 7:34 PM, <commits@source.squeak.org> wrote:

> Karl Ramberg uploaded a new version of MorphicExtras to project Etoys:
> http://source.squeak.org/etoys/MorphicExtras-kfr.77.mcz
>
> ==================== Summary ====================
>
> Name: MorphicExtras-kfr.77
> Author: kfr
> Time: 11 February 2013, 7:34:04 pm
> UUID: d5a59509-3afd-3c46-a1c3-4c4e804aeef9
> Ancestors: MorphicExtras-kfr.76
>
> Fixing issues with flexing FlapTab
>
> =============== Diff against MorphicExtras-kfr.75 ===============
>
> Item was changed:
>   ----- Method: FlapTab>>computeEdgeFraction (in category 'edge') -----
>   computeEdgeFraction
>         "Compute and remember the edge fraction"
>
>         | aBox aFraction |
>         self isCurrentlySolid ifTrue: [^ edgeFraction ifNil: [self
> edgeFraction: 0.5]].
>
> +       aBox := ((self pasteUpMorph ifNil: [self currentWorld]) bounds)
> insetBy: (self extent // 2).
> +       aFraction := self
> -       aBox _ ((self pasteUpMorph ifNil: [ActiveWorld]) bounds) insetBy:
> (self extent // 2).
> -       aFraction _ self
>                 ifVertical:
>                         [(self center y - aBox top) / (aBox height max: 1)]
>                 ifHorizontal:
>                         [(self center x - aBox left) / (aBox width max:
> 1)].
>         ^ self edgeFraction: aFraction!
>
> Item was changed:
>   ----- Method: FlapTab>>fitOnScreen (in category 'positioning') -----
>   fitOnScreen
>         "19 sept 2000 - allow flaps in any paste up"
>         | constrainer t l |
> +       constrainer := self pasteUpMorph ifNil: [self currentWorld].
> -       constrainer := self pasteUpMorph ifNil: [self].
>         self flapShowing "otherwise no point in doing this"
>                 ifTrue:[self spanWorld].
>         self orientation == #vertical ifTrue: [
> +               t := ((self top min: (constrainer bottom- self height))
> max: constrainer top).
> -               t _ ((self top min: (constrainer bottom- self height))
> max: constrainer top).
>                 t = self top ifFalse: [self top: t].
>         ] ifFalse: [
> +               l := ((self left min: (constrainer right - self width))
> max: constrainer left).
> -               l _ ((self left min: (constrainer right - self width))
> max: constrainer left).
>                 l = self left ifFalse: [self left: l].
>         ].
>         self flapShowing ifFalse: [self positionObject: self atEdgeOf:
> constrainer].
>   !
>
> Item was changed:
>   ----- Method: FlapTab>>hideFlap (in category 'show & hide') -----
>   hideFlap
>         | aWorld |
> +       aWorld := self world ifNil: [self currentWorld].
> +       self privateDeleteReferent.
> -       aWorld _ self world ifNil: [self currentWorld].
> -       referent privateDelete.
>         aWorld removeAccommodationForFlap: self.
> +       flapShowing := false.
> -       flapShowing _ false.
>         self isInWorld ifFalse: [aWorld addMorphFront: self].
>         self adjustPositionAfterHidingFlap.
>         aWorld haloMorphs do:
>                 [:m | m target isInWorld ifFalse: [m delete]]!
>
> Item was changed:
>   ----- Method: FlapTab>>maybeHideFlapOnMouseLeaveDragging (in category
> 'show & hide') -----
>   maybeHideFlapOnMouseLeaveDragging
>         | aWorld |
>         self hasHalo ifTrue: [^ self].
>         referent isInWorld ifFalse: [^ self].
>         (dragged or: [referent bounds containsPoint: self cursorPoint])
>                 ifTrue: [^ self].
>         aWorld _ self world.
> +       self privateDeleteReferent.  "could make me worldless if I'm
> inboard"
> -       referent privateDelete.  "could make me worldless if I'm inboard"
>         aWorld ifNotNil: [aWorld removeAccommodationForFlap: self].
> +       flapShowing := false.
> -       flapShowing _ false.
>         self isInWorld ifFalse: [aWorld addMorphFront: self].
>         self adjustPositionAfterHidingFlap!
>
> Item was changed:
>   ----- Method: FlapTab>>mouseMove: (in category 'event handling') -----
>   mouseMove: evt
>         "Handle a mouse-move event.   The event, a MorphicEvent, is passed
> in."
>
>         | aPosition newReferentThickness adjustedPosition thick |
>
> +       dragged ifFalse: [(thick := self referentThickness) > 0
> +                       ifTrue: [lastReferentThickness := thick]].
> +       ((self containsPoint: (aPosition := evt cursorPoint)) and:
> [dragged not])
> -       dragged ifFalse: [(thick _ self referentThickness) > 0
> -                       ifTrue: [lastReferentThickness _ thick]].
> -       ((self containsPoint: (aPosition _ evt cursorPoint)) and: [dragged
> not])
>                 ifFalse:
>                         [flapShowing ifFalse: [self showFlap].
> +                       adjustedPosition := aPosition - evt hand
> targetOffset.
> -                       adjustedPosition _ aPosition - evt hand
> targetOffset.
>                         (edgeToAdhereTo == #bottom)
>                                 ifTrue:
> +                                       [newReferentThickness := inboard
> -                                       [newReferentThickness _ inboard
>                                                 ifTrue:
>                                                         [self world height
> - adjustedPosition y]
>                                                 ifFalse:
>                                                         [self world height
> - adjustedPosition y - self height]].
>
>                         (edgeToAdhereTo == #left)
>                                         ifTrue:
> +                                               [newReferentThickness :=
> -                                               [newReferentThickness _
>                                                         inboard
>                                                                 ifTrue:
>
> [adjustedPosition x + self width]
>                                                                 ifFalse:
>
> [adjustedPosition x]].
>
>                         (edgeToAdhereTo == #right)
>                                         ifTrue:
> +                                               [newReferentThickness :=
> -                                               [newReferentThickness _
>                                                         inboard
>                                                                 ifTrue:
>
> [self world width - adjustedPosition x]
>                                                                 ifFalse:
>
> [self world width - adjustedPosition x - self width]].
>
>                         (edgeToAdhereTo == #top)
>                                         ifTrue:
> +                                               [newReferentThickness :=
> -                                               [newReferentThickness _
>                                                         inboard
>                                                                 ifTrue:
>
> [adjustedPosition y + self height]
>                                                                 ifFalse:
>
> [adjustedPosition y]].
>
>                         self isCurrentlySolid ifFalse:
>                                 [(#(left right) includes: edgeToAdhereTo)
>                                         ifFalse:
>                                                 [self left:
> adjustedPosition x]
>                                         ifTrue:
>                                                 [self top:
> adjustedPosition y]].
>
>                         ((edgeToAdhereTo == #left) and: [(self
>  valueOfProperty: #rigidThickness) notNil]) ifTrue:
>                                 [newReferentThickness := referent width].
>
>                         self applyThickness: newReferentThickness.
> +                       dragged := true.
> -                       dragged _ true.
>                         self fitOnScreen.
>                         self computeEdgeFraction]!
>
> Item was changed:
>   ----- Method: FlapTab>>mouseUp: (in category 'event handling') -----
>   mouseUp: evt
>         "The mouse came back up, presumably after having dragged the tab.
>  Caution: if not operating full-screen, this notification can easily be
> *missed*, which is why the edge-fraction-computation is also being done on
> mouseMove."
>
>         super mouseUp: evt.
>         (self referentThickness <= 0 or:
>                 [(referent isInWorld and: [(referent boundsInWorld
> intersects: referent owner boundsInWorld) not])]) ifTrue:
>                         [self hideFlap.
> +                       flapShowing := false].
> -                       flapShowing _ false].
>         self fitOnScreen.
>         dragged ifTrue:
>                 [self computeEdgeFraction.
> +               dragged := false].
> -               dragged _ false].
>         Flaps doAutomaticLayoutOfFlapsIfAppropriate!
>
> Item was removed:
> - ----- Method: FlapTab>>ownerChanged (in category 'change reporting')
> -----
> - ownerChanged
> -       self fitOnScreen.
> -       ^super ownerChanged.!
>
> Item was changed:
>   ----- Method: FlapTab>>positionObject: (in category 'positioning') -----
>   positionObject: anObject
>           "anObject could be myself or my referent"
>
> + "Could consider container := referent pasteUpMorph, to allow flaps on
> things other than the world, but for the moment, let's skip it!!"
> - "Could consider container _ referent pasteUpMorph, to allow flaps on
> things other than the world, but for the moment, let's skip it!!"
>
>         "19 sept 2000 - going for all paste ups"
> +
> -
>         ^self
>                 positionObject: anObject
> +               atEdgeOf: (self pasteUpMorph ifNil: [^ self currentWorld])!
> -               atEdgeOf: (self pasteUpMorph ifNil: [^ self])!
>
> Item was added:
> + ----- Method: FlapTab>>privateDeleteReferent (in category 'show & hide')
> -----
> + privateDeleteReferent
> +       referent isFlexed
> +               ifTrue: [referent owner privateDelete]
> +               ifFalse: [referent privateDelete]!
>
> Item was changed:
>   ----- Method: FlapTab>>spanWorld (in category 'positioning') -----
>   spanWorld
>         "Make the receiver's height or width commensurate with that of the
> container."
>
>         | container |
>
> +       container := self pasteUpMorph ifNil: [self currentWorld].
> -       container _ self pasteUpMorph ifNil: [self currentWorld].
>         (self orientation == #vertical) ifTrue: [
>                 referent vResizing == #rigid
>                         ifTrue:[referent spanContainerVertically:
> container height].
>                 referent hResizing == #rigid
>                         ifTrue:[referent width: (referent width min:
> container width - self width)].
>                 referent top: container top + self referentMargin y.
>         ] ifFalse: [
>                 referent hResizing == #rigid
>                         ifTrue:[referent width: container width].
>                 referent vResizing == #rigid
>                         ifTrue:[referent height: (referent height min:
> container height - self height)].
>                 referent left: container left + self referentMargin x.
> +       ]!
> -       ] !
>
> Item was changed:
>   RectangleMorph subclass: #GraphMorph
> +       instanceVariableNames: 'data dataColor cursor cursorColor
> cursorColorAtZeroCrossings startIndex minVal maxVal cachedForm hasChanged
> samplingRate'
> -       instanceVariableNames: 'data dataColor cursor cursorColor
> cursorColorAtZeroCrossings startIndex minVal maxVal cachedForm hasChanged'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'MorphicExtras-Widgets'!
>
>   !GraphMorph commentStamp: '<historical>' prior: 0!
>   I display a graph of numbers, normalized so the full range of values
> just fits my height. I support a movable cursor that can be dragged with
> the mouse.
>
>   Implementation notes: Some operations on me may be done at sound
> sampling rates (e.g. 11-44 thousand times/second). To allow such high
> bandwidth application, certain operations that change my appearance do not
> immediately report a damage rectangle. Instead, a flag is set indicating
> that my display needs to refreshed and a step method reports the damage
> rectangle if that flag is set. Also, I cache a bitmap of my graph to allow
> the cursor to be moved without redrawing the graph.
>   !
>
> Item was added:
> + ----- Method: GraphMorph>>elementCount (in category 'accessing') -----
> + elementCount
> +       ^data size!
>
> Item was added:
> + ----- Method: GraphMorph>>getSamplingRate (in category 'accessing') -----
> + getSamplingRate
> +       ^samplingRate asString asSymbol!
>
> Item was changed:
>   ----- Method: GraphMorph>>initialize (in category 'initialization') -----
>   initialize
>         "initialize the state of the receiver"
>         super initialize.
>         ""
>         self extent: 365 @ 80.
>
>         dataColor _ Color darkGray.
>         cursor _ 1.0.
> +       samplingRate := 11025.
>         "may be fractional"
>         cursorColor _ Color red.
>         cursorColorAtZeroCrossings _ Color red.
>         startIndex _ 1.
>         hasChanged _ false.
>         self
>                 data: ((0 to: 360 - 1)
>                                 collect: [:x | (100.0 * x degreesToRadians
> sin) asInteger])!
>
> Item was changed:
>   ----- Method: GraphMorph>>play (in category 'commands') -----
>   play
> +       self playOnce: data size!
> -       self playOnce!
>
> Item was changed:
>   ----- Method: GraphMorph>>playOnce (in category 'commands') -----
>   playOnce
>
>         | scale absV scaledData |
>         data isEmpty ifTrue: [^ self].  "nothing to play"
>         scale _ 1.
>         data do: [:v | (absV _ v abs) > scale ifTrue: [scale _ absV]].
>         scale _ 32767.0 / scale.
>         scaledData _ SoundBuffer newMonoSampleCount: data size.
> +       cursor to: data size do: [:i | scaledData at: i put: (scale *
> (data at: i)) truncated].
> +       SoundService default playSampledSound: scaledData rate:
> samplingRate.
> -       1 to: data size do: [:i | scaledData at: i put: (scale * (data at:
> i)) truncated].
> -       SoundService default playSampledSound: scaledData rate: 11025.
>   !
>
> Item was added:
> + ----- Method: GraphMorph>>playOnce: (in category 'commands') -----
> + playOnce: aSampleNumber
> +
> +       | scale absV scaledData |
> +       data isEmpty ifTrue: [^ self].  "nothing to play"
> +       scale _ 1.
> +       data do: [:v | (absV _ v abs) > scale ifTrue: [scale _ absV]].
> +       scale _ 32767.0 / scale.
> +       scaledData _ SoundBuffer newMonoSampleCount: data size.
> +       cursor to: aSampleNumber do: [:i | scaledData at: i put: (scale *
> (data at: i)) truncated].
> +       SoundService default playSampledSound: scaledData rate:
> samplingRate.
> + !
>
> Item was added:
> + ----- Method: GraphMorph>>playTo: (in category 'commands') -----
> + playTo: aSampleNumber
> +       self playOnce: aSampleNumber!
>
> Item was added:
> + ----- Method: GraphMorph>>samplingRate (in category 'accessing') -----
> + samplingRate
> +     ^samplingRate!
>
> Item was added:
> + ----- Method: GraphMorph>>samplingRate: (in category 'accessing') -----
> + samplingRate: aSamplingRate
> +       ((SamplingRate resolutions) includes:  aSamplingRate) ifFalse: [^
> self].
> +       samplingRate:= aSamplingRate!
>
> Item was added:
> + ----- Method: GraphMorph>>setSamplingRate: (in category 'accessing')
> -----
> + setSamplingRate: aSymbol
> +       samplingRate :=  aSymbol asString asNumber!
>
> Item was added:
> + ----- Method: Player>>getSamplingRate (in category
> '*MorphicExtras-Widgets') -----
> + getSamplingRate
> +       ^ self getValueFromCostume: #getSamplingRate!
>
> Item was added:
> + ----- Method: Player>>playTo: (in category '*MorphicExtras-Widgets')
> -----
> + playTo: aSampleNumber
> +       costume renderedMorph playTo: aSampleNumber!
>
> Item was added:
> + ----- Method: Player>>setSamplingRate: (in category
> '*MorphicExtras-Widgets') -----
> + setSamplingRate: aSymbol
> +       costume renderedMorph setSamplingRate: aSymbol!
>
> Item was added:
> + SymbolListType subclass: #SamplingRate
> +       instanceVariableNames: ''
> +       classVariableNames: ''
> +       poolDictionaries: ''
> +       category: 'MorphicExtras-Widgets'!
>
> Item was added:
> + ----- Method: SamplingRate>>initialize (in category 'as yet
> unclassified') -----
> + initialize
> +       "Vocabulary initialize"
> +       super initialize.
> +       self vocabularyName: #SamplingRate.
> +       symbols := #('11025' '22050' '44100')
> +
> + !
>
> Item was added:
> + ----- Method: SamplingRate>>representsAType (in category 'as yet
> unclassified') -----
> + representsAType
> +       ^true!
>
> _______________________________________________
> etoys-dev mailing list
> etoys-dev@squeakland.org
> http://lists.squeakland.org/mailman/listinfo/etoys-dev
>

[Attachment #5 (text/html)]

<div dir="ltr">Hm, GraphMorph should not really be part of this...</div><div \
class="gmail_extra"><br><br><div class="gmail_quote">On Mon, Feb 11, 2013 at 7:34 PM, \
<span dir="ltr">&lt;<a href="mailto:commits@source.squeak.org" \
target="_blank">commits@source.squeak.org</a>&gt;</span> wrote:<br> <blockquote \
class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc \
solid;padding-left:1ex">Karl Ramberg uploaded a new version of MorphicExtras to \
project Etoys:<br> <a href="http://source.squeak.org/etoys/MorphicExtras-kfr.77.mcz" \
target="_blank">http://source.squeak.org/etoys/MorphicExtras-kfr.77.mcz</a><br> <br>
==================== Summary ====================<br>
<br>
Name: MorphicExtras-kfr.77<br>
Author: kfr<br>
Time: 11 February 2013, 7:34:04 pm<br>
UUID: d5a59509-3afd-3c46-a1c3-4c4e804aeef9<br>
Ancestors: MorphicExtras-kfr.76<br>
<br>
Fixing issues with flexing FlapTab<br>
<br>
=============== Diff against MorphicExtras-kfr.75 ===============<br>
<br>
Item was changed:<br>
  ----- Method: FlapTab&gt;&gt;computeEdgeFraction (in category &#39;edge&#39;) \
-----<br>  computeEdgeFraction<br>
        &quot;Compute and remember the edge fraction&quot;<br>
<br>
        | aBox aFraction |<br>
        self isCurrentlySolid ifTrue: [^ edgeFraction ifNil: [self edgeFraction: \
0.5]].<br> <br>
+       aBox := ((self pasteUpMorph ifNil: [self currentWorld]) bounds) insetBy: \
(self extent // 2).<br> +       aFraction := self<br>
-       aBox _ ((self pasteUpMorph ifNil: [ActiveWorld]) bounds) insetBy: (self \
                extent // 2).<br>
-       aFraction _ self<br>
                ifVertical:<br>
                        [(self center y - aBox top) / (aBox height max: 1)]<br>
                ifHorizontal:<br>
                        [(self center x - aBox left) / (aBox width max: 1)].<br>
        ^ self edgeFraction: aFraction!<br>
<br>
Item was changed:<br>
  ----- Method: FlapTab&gt;&gt;fitOnScreen (in category &#39;positioning&#39;) \
-----<br>  fitOnScreen<br>
        &quot;19 sept 2000 - allow flaps in any paste up&quot;<br>
        | constrainer t l |<br>
+       constrainer := self pasteUpMorph ifNil: [self currentWorld].<br>
-       constrainer := self pasteUpMorph ifNil: [self].<br>
        self flapShowing &quot;otherwise no point in doing this&quot;<br>
                ifTrue:[self spanWorld].<br>
        self orientation == #vertical ifTrue: [<br>
+               t := ((self top min: (constrainer bottom- self height)) max: \
                constrainer top).<br>
-               t _ ((self top min: (constrainer bottom- self height)) max: \
constrainer top).<br>  t = self top ifFalse: [self top: t].<br>
        ] ifFalse: [<br>
+               l := ((self left min: (constrainer right - self width)) max: \
                constrainer left).<br>
-               l _ ((self left min: (constrainer right - self width)) max: \
constrainer left).<br>  l = self left ifFalse: [self left: l].<br>
        ].<br>
        self flapShowing ifFalse: [self positionObject: self atEdgeOf: \
                constrainer].<br>
  !<br>
<br>
Item was changed:<br>
  ----- Method: FlapTab&gt;&gt;hideFlap (in category &#39;show &amp; hide&#39;) \
-----<br>  hideFlap<br>
        | aWorld |<br>
+       aWorld := self world ifNil: [self currentWorld].<br>
+       self privateDeleteReferent.<br>
-       aWorld _ self world ifNil: [self currentWorld].<br>
-       referent privateDelete.<br>
        aWorld removeAccommodationForFlap: self.<br>
+       flapShowing := false.<br>
-       flapShowing _ false.<br>
        self isInWorld ifFalse: [aWorld addMorphFront: self].<br>
        self adjustPositionAfterHidingFlap.<br>
        aWorld haloMorphs do:<br>
                [:m | m target isInWorld ifFalse: [m delete]]!<br>
<br>
Item was changed:<br>
  ----- Method: FlapTab&gt;&gt;maybeHideFlapOnMouseLeaveDragging (in category \
&#39;show &amp; hide&#39;) -----<br>  maybeHideFlapOnMouseLeaveDragging<br>
        | aWorld |<br>
        self hasHalo ifTrue: [^ self].<br>
        referent isInWorld ifFalse: [^ self].<br>
        (dragged or: [referent bounds containsPoint: self cursorPoint])<br>
                ifTrue: [^ self].<br>
        aWorld _ self world.<br>
+       self privateDeleteReferent.  &quot;could make me worldless if I&#39;m \
                inboard&quot;<br>
-       referent privateDelete.  &quot;could make me worldless if I&#39;m \
inboard&quot;<br>  aWorld ifNotNil: [aWorld removeAccommodationForFlap: self].<br>
+       flapShowing := false.<br>
-       flapShowing _ false.<br>
        self isInWorld ifFalse: [aWorld addMorphFront: self].<br>
        self adjustPositionAfterHidingFlap!<br>
<br>
Item was changed:<br>
  ----- Method: FlapTab&gt;&gt;mouseMove: (in category &#39;event handling&#39;) \
-----<br>  mouseMove: evt<br>
        &quot;Handle a mouse-move event.   The event, a MorphicEvent, is passed \
in.&quot;<br> <br>
        | aPosition newReferentThickness adjustedPosition thick |<br>
<br>
+       dragged ifFalse: [(thick := self referentThickness) &gt; 0<br>
+                       ifTrue: [lastReferentThickness := thick]].<br>
+       ((self containsPoint: (aPosition := evt cursorPoint)) and: [dragged not])<br>
-       dragged ifFalse: [(thick _ self referentThickness) &gt; 0<br>
-                       ifTrue: [lastReferentThickness _ thick]].<br>
-       ((self containsPoint: (aPosition _ evt cursorPoint)) and: [dragged not])<br>
                ifFalse:<br>
                        [flapShowing ifFalse: [self showFlap].<br>
+                       adjustedPosition := aPosition - evt hand targetOffset.<br>
-                       adjustedPosition _ aPosition - evt hand targetOffset.<br>
                        (edgeToAdhereTo == #bottom)<br>
                                ifTrue:<br>
+                                       [newReferentThickness := inboard<br>
-                                       [newReferentThickness _ inboard<br>
                                                ifTrue:<br>
                                                        [self world height - \
adjustedPosition y]<br>  ifFalse:<br>
                                                        [self world height - \
adjustedPosition y - self height]].<br> <br>
                        (edgeToAdhereTo == #left)<br>
                                        ifTrue:<br>
+                                               [newReferentThickness :=<br>
-                                               [newReferentThickness _<br>
                                                        inboard<br>
                                                                ifTrue:<br>
                                                                        \
                [adjustedPosition x + self width]<br>
                                                                ifFalse:<br>
                                                                        \
[adjustedPosition x]].<br> <br>
                        (edgeToAdhereTo == #right)<br>
                                        ifTrue:<br>
+                                               [newReferentThickness :=<br>
-                                               [newReferentThickness _<br>
                                                        inboard<br>
                                                                ifTrue:<br>
                                                                        [self world \
                width - adjustedPosition x]<br>
                                                                ifFalse:<br>
                                                                        [self world \
width - adjustedPosition x - self width]].<br> <br>
                        (edgeToAdhereTo == #top)<br>
                                        ifTrue:<br>
+                                               [newReferentThickness :=<br>
-                                               [newReferentThickness _<br>
                                                        inboard<br>
                                                                ifTrue:<br>
                                                                        \
                [adjustedPosition y + self height]<br>
                                                                ifFalse:<br>
                                                                        \
[adjustedPosition y]].<br> <br>
                        self isCurrentlySolid ifFalse:<br>
                                [(#(left right) includes: edgeToAdhereTo)<br>
                                        ifFalse:<br>
                                                [self left: adjustedPosition x]<br>
                                        ifTrue:<br>
                                                [self top: adjustedPosition y]].<br>
<br>
                        ((edgeToAdhereTo == #left) and: [(self  valueOfProperty: \
                #rigidThickness) notNil]) ifTrue:<br>
                                [newReferentThickness := referent width].<br>
<br>
                        self applyThickness: newReferentThickness.<br>
+                       dragged := true.<br>
-                       dragged _ true.<br>
                        self fitOnScreen.<br>
                        self computeEdgeFraction]!<br>
<br>
Item was changed:<br>
  ----- Method: FlapTab&gt;&gt;mouseUp: (in category &#39;event handling&#39;) \
-----<br>  mouseUp: evt<br>
        &quot;The mouse came back up, presumably after having dragged the tab.  \
Caution: if not operating full-screen, this notification can easily be *missed*, \
which is why the edge-fraction-computation is also being done on mouseMove.&quot;<br>

<br>
        super mouseUp: evt.<br>
        (self referentThickness &lt;= 0 or:<br>
                [(referent isInWorld and: [(referent boundsInWorld intersects: \
referent owner boundsInWorld) not])]) ifTrue:<br>  [self hideFlap.<br>
+                       flapShowing := false].<br>
-                       flapShowing _ false].<br>
        self fitOnScreen.<br>
        dragged ifTrue:<br>
                [self computeEdgeFraction.<br>
+               dragged := false].<br>
-               dragged _ false].<br>
        Flaps doAutomaticLayoutOfFlapsIfAppropriate!<br>
<br>
Item was removed:<br>
- ----- Method: FlapTab&gt;&gt;ownerChanged (in category &#39;change reporting&#39;) \
                -----<br>
- ownerChanged<br>
-       self fitOnScreen.<br>
-       ^super ownerChanged.!<br>
<br>
Item was changed:<br>
  ----- Method: FlapTab&gt;&gt;positionObject: (in category &#39;positioning&#39;) \
-----<br>  positionObject: anObject<br>
          &quot;anObject could be myself or my referent&quot;<br>
<br>
+ &quot;Could consider container := referent pasteUpMorph, to allow flaps on things \
                other than the world, but for the moment, let&#39;s skip \
                it!!&quot;<br>
- &quot;Could consider container _ referent pasteUpMorph, to allow flaps on things \
other than the world, but for the moment, let&#39;s skip it!!&quot;<br> <br>
        &quot;19 sept 2000 - going for all paste ups&quot;<br>
+<br>
-<br>
        ^self<br>
                positionObject: anObject<br>
+               atEdgeOf: (self pasteUpMorph ifNil: [^ self currentWorld])!<br>
-               atEdgeOf: (self pasteUpMorph ifNil: [^ self])!<br>
<br>
Item was added:<br>
+ ----- Method: FlapTab&gt;&gt;privateDeleteReferent (in category &#39;show &amp; \
hide&#39;) -----<br> + privateDeleteReferent<br>
+       referent isFlexed<br>
+               ifTrue: [referent owner privateDelete]<br>
+               ifFalse: [referent privateDelete]!<br>
<br>
Item was changed:<br>
  ----- Method: FlapTab&gt;&gt;spanWorld (in category &#39;positioning&#39;) \
-----<br>  spanWorld<br>
        &quot;Make the receiver&#39;s height or width commensurate with that of the \
container.&quot;<br> <br>
        | container |<br>
<br>
+       container := self pasteUpMorph ifNil: [self currentWorld].<br>
-       container _ self pasteUpMorph ifNil: [self currentWorld].<br>
        (self orientation == #vertical) ifTrue: [<br>
                referent vResizing == #rigid<br>
                        ifTrue:[referent spanContainerVertically: container \
height].<br>  referent hResizing == #rigid<br>
                        ifTrue:[referent width: (referent width min: container width \
- self width)].<br>  referent top: container top + self referentMargin y.<br>
        ] ifFalse: [<br>
                referent hResizing == #rigid<br>
                        ifTrue:[referent width: container width].<br>
                referent vResizing == #rigid<br>
                        ifTrue:[referent height: (referent height min: container \
height - self height)].<br>  referent left: container left + self referentMargin \
x.<br> +       ]!<br>
-       ] !<br>
<br>
Item was changed:<br>
  RectangleMorph subclass: #GraphMorph<br>
+       instanceVariableNames: &#39;data dataColor cursor cursorColor \
cursorColorAtZeroCrossings startIndex minVal maxVal cachedForm hasChanged \
                samplingRate&#39;<br>
-       instanceVariableNames: &#39;data dataColor cursor cursorColor \
cursorColorAtZeroCrossings startIndex minVal maxVal cachedForm hasChanged&#39;<br>  \
classVariableNames: &#39;&#39;<br>  poolDictionaries: &#39;&#39;<br>
        category: &#39;MorphicExtras-Widgets&#39;!<br>
<br>
  !GraphMorph commentStamp: &#39;&lt;historical&gt;&#39; prior: 0!<br>
  I display a graph of numbers, normalized so the full range of values just fits my \
height. I support a movable cursor that can be dragged with the mouse.<br> <br>
  Implementation notes: Some operations on me may be done at sound sampling rates \
(e.g. 11-44 thousand times/second). To allow such high bandwidth application, certain \
operations that change my appearance do not immediately report a damage rectangle. \
Instead, a flag is set indicating that my display needs to refreshed and a step \
method reports the damage rectangle if that flag is set. Also, I cache a bitmap of my \
graph to allow the cursor to be moved without redrawing the graph.<br>

  !<br>
<br>
Item was added:<br>
+ ----- Method: GraphMorph&gt;&gt;elementCount (in category &#39;accessing&#39;) \
-----<br> + elementCount<br>
+       ^data size!<br>
<br>
Item was added:<br>
+ ----- Method: GraphMorph&gt;&gt;getSamplingRate (in category &#39;accessing&#39;) \
-----<br> + getSamplingRate<br>
+       ^samplingRate asString asSymbol!<br>
<br>
Item was changed:<br>
  ----- Method: GraphMorph&gt;&gt;initialize (in category &#39;initialization&#39;) \
-----<br>  initialize<br>
        &quot;initialize the state of the receiver&quot;<br>
        super initialize.<br>
        &quot;&quot;<br>
        self extent: 365 @ 80.<br>
<br>
        dataColor _ Color darkGray.<br>
        cursor _ 1.0.<br>
+       samplingRate := 11025.<br>
        &quot;may be fractional&quot;<br>
        cursorColor _ Color red.<br>
        cursorColorAtZeroCrossings _ Color red.<br>
        startIndex _ 1.<br>
        hasChanged _ false.<br>
        self<br>
                data: ((0 to: 360 - 1)<br>
                                collect: [:x | (100.0 * x degreesToRadians sin) \
asInteger])!<br> <br>
Item was changed:<br>
  ----- Method: GraphMorph&gt;&gt;play (in category &#39;commands&#39;) -----<br>
  play<br>
+       self playOnce: data size!<br>
-       self playOnce!<br>
<br>
Item was changed:<br>
  ----- Method: GraphMorph&gt;&gt;playOnce (in category &#39;commands&#39;) -----<br>
  playOnce<br>
<br>
        | scale absV scaledData |<br>
        data isEmpty ifTrue: [^ self].  &quot;nothing to play&quot;<br>
        scale _ 1.<br>
        data do: [:v | (absV _ v abs) &gt; scale ifTrue: [scale _ absV]].<br>
        scale _ 32767.0 / scale.<br>
        scaledData _ SoundBuffer newMonoSampleCount: data size.<br>
+       cursor to: data size do: [:i | scaledData at: i put: (scale * (data at: i)) \
truncated].<br> +       SoundService default playSampledSound: scaledData rate: \
                samplingRate.<br>
-       1 to: data size do: [:i | scaledData at: i put: (scale * (data at: i)) \
                truncated].<br>
-       SoundService default playSampledSound: scaledData rate: 11025.<br>
  !<br>
<br>
Item was added:<br>
+ ----- Method: GraphMorph&gt;&gt;playOnce: (in category &#39;commands&#39;) \
-----<br> + playOnce: aSampleNumber<br>
+<br>
+       | scale absV scaledData |<br>
+       data isEmpty ifTrue: [^ self].  &quot;nothing to play&quot;<br>
+       scale _ 1.<br>
+       data do: [:v | (absV _ v abs) &gt; scale ifTrue: [scale _ absV]].<br>
+       scale _ 32767.0 / scale.<br>
+       scaledData _ SoundBuffer newMonoSampleCount: data size.<br>
+       cursor to: aSampleNumber do: [:i | scaledData at: i put: (scale * (data at: \
i)) truncated].<br> +       SoundService default playSampledSound: scaledData rate: \
samplingRate.<br> + !<br>
<br>
Item was added:<br>
+ ----- Method: GraphMorph&gt;&gt;playTo: (in category &#39;commands&#39;) -----<br>
+ playTo: aSampleNumber<br>
+       self playOnce: aSampleNumber!<br>
<br>
Item was added:<br>
+ ----- Method: GraphMorph&gt;&gt;samplingRate (in category &#39;accessing&#39;) \
-----<br> + samplingRate<br>
+     ^samplingRate!<br>
<br>
Item was added:<br>
+ ----- Method: GraphMorph&gt;&gt;samplingRate: (in category &#39;accessing&#39;) \
-----<br> + samplingRate: aSamplingRate<br>
+       ((SamplingRate resolutions) includes:  aSamplingRate) ifFalse: [^ self].<br>
+       samplingRate:= aSamplingRate!<br>
<br>
Item was added:<br>
+ ----- Method: GraphMorph&gt;&gt;setSamplingRate: (in category &#39;accessing&#39;) \
-----<br> + setSamplingRate: aSymbol<br>
+       samplingRate :=  aSymbol asString asNumber!<br>
<br>
Item was added:<br>
+ ----- Method: Player&gt;&gt;getSamplingRate (in category \
&#39;*MorphicExtras-Widgets&#39;) -----<br> + getSamplingRate<br>
+       ^ self getValueFromCostume: #getSamplingRate!<br>
<br>
Item was added:<br>
+ ----- Method: Player&gt;&gt;playTo: (in category &#39;*MorphicExtras-Widgets&#39;) \
-----<br> + playTo: aSampleNumber<br>
+       costume renderedMorph playTo: aSampleNumber!<br>
<br>
Item was added:<br>
+ ----- Method: Player&gt;&gt;setSamplingRate: (in category \
&#39;*MorphicExtras-Widgets&#39;) -----<br> + setSamplingRate: aSymbol<br>
+       costume renderedMorph setSamplingRate: aSymbol!<br>
<br>
Item was added:<br>
+ SymbolListType subclass: #SamplingRate<br>
+       instanceVariableNames: &#39;&#39;<br>
+       classVariableNames: &#39;&#39;<br>
+       poolDictionaries: &#39;&#39;<br>
+       category: &#39;MorphicExtras-Widgets&#39;!<br>
<br>
Item was added:<br>
+ ----- Method: SamplingRate&gt;&gt;initialize (in category &#39;as yet \
unclassified&#39;) -----<br> + initialize<br>
+       &quot;Vocabulary initialize&quot;<br>
+       super initialize.<br>
+       self vocabularyName: #SamplingRate.<br>
+       symbols := #(&#39;11025&#39; &#39;22050&#39; &#39;44100&#39;)<br>
+<br>
+ !<br>
<br>
Item was added:<br>
+ ----- Method: SamplingRate&gt;&gt;representsAType (in category &#39;as yet \
unclassified&#39;) -----<br> + representsAType<br>
+       ^true!<br>
<br>
_______________________________________________<br>
etoys-dev mailing list<br>
<a href="mailto:etoys-dev@squeakland.org">etoys-dev@squeakland.org</a><br>
<a href="http://lists.squeakland.org/mailman/listinfo/etoys-dev" \
target="_blank">http://lists.squeakland.org/mailman/listinfo/etoys-dev</a><br> \
</blockquote></div><br></div>



_______________________________________________
etoys-dev mailing list
etoys-dev@squeakland.org
http://lists.squeakland.org/mailman/listinfo/etoys-dev


[prev in list] [next in list] [prev in thread] [next in thread] 

Configure | About | News | Add a list | Sponsored by KoreLogic