Bezier.st
author Claus Gittinger <cg@exept.de>
Wed, 12 Feb 1997 15:17:03 +0100
changeset 491 433097e01416
child 492 56d74636cb69
permissions -rw-r--r--
intitial checkin

Geometric subclass:#Bezier
	instanceVariableNames:'start end controlPoint1 controlPoint2'
	classVariableNames:'ScaledFlatness'
	poolDictionaries:''
	category:'Graphics-Geometry'
!

Bezier comment:'Bezier represents a type of parametric cubic curve.

Instance Variables:
        start                   <Point>         Starting point of curve.
        end                             <Point>         End point of curve.
        controlPoint1   <Point>         1st control point (associated with start).
        controlPoint2   <Point>         2nd control point (associated with end).

Class Variables:
        ScaledFlatness          <Integer>       Flatness parameter
'!

!Bezier class methodsFor:'documentation'!

documentation
"
    Beziers represent parametric cubic curvea.

    [instance variables:]
        start                   <Point>         startPoint of the curve.
        end                     <Point>         endPoint of the curve.
        controlPoint1           <Point>         control point.
        controlPoint2           <Point>         control point.

    [class variables:]
        ScaledFlatness          <Integer>       curves flatness parameter

    [author:]
        unknown (based upon the PD path package)
"
!

examples
"
  bezier:
                                                                        [exBegin]
    |v s|

    v := (View extent:110@110) openAndWait.

    s := Bezier
            start:10@10
            end:100@100
            controlPoint1:50@50
            controlPoint2:10@80.

    v paint:Color red.
    s displayStrokedOn:v.

    v paint:Color black.
    v displayPoint:10@10.
    v displayPoint:100@100.
    v displayPoint:50@50.
    v displayPoint:10@80.
                                                                        [exEnd]



    effect of different values for flatness parameter:
                                                                        [exBegin]
    |win bz start end p1 p2 osf size|

    win := StandardSystemView new.
    win minExtent: (size := 500 @ 300).

    start := 0@50.
    end := 500@50.
    p1 := 2@0.
    p2 := 475@200.
    osf := ScaledFlatness.
    ScaledFlatness := 16 * 4096.
    bz := Bezier start: start end: end controlPoint1: p1 controlPoint2: p2.

    0 to: size y - 150 by: size y // 15 do:[:yo |
        win add:(bz asPolyline asStroker) at: 0@yo.
        ScaledFlatness := ScaledFlatness // 2
    ].
    ScaledFlatness := osf.
    win open
                                                                        [exEnd]
"
! !

!Bezier class methodsFor:'instance creation'!

start:startPoint end:endPoint controlPoint1:controlPoint1 controlPoint2:controlPoint2
    "create & return a new bezier curve"

    ^ self basicNew 
        setStart:startPoint end:endPoint controlPoint1:controlPoint1 controlPoint2:controlPoint2

    "Created: 12.2.1997 / 11:33:19 / cg"
    "Modified: 12.2.1997 / 14:25:59 / cg"
! !

!Bezier class methodsFor:'class initialization'!

initialize
    "initialize class constants"

    ScaledFlatness := (0.5 * Scale) rounded.

    "
     Bezier initialize
    "

    "Modified: 12.2.1997 / 14:26:26 / cg"
! !

!Bezier methodsFor:'accessing'!

controlPoint1
    "return the first controlPoint"

    ^ controlPoint1

    "Modified: 12.2.1997 / 14:27:01 / cg"
!

controlPoint2
    "return the second controlPoint"

    ^ controlPoint2

    "Created: 12.2.1997 / 11:33:18 / cg"
    "Modified: 12.2.1997 / 14:27:12 / cg"
!

end
    "return the endPoint"

    ^ end

    "Created: 12.2.1997 / 11:33:18 / cg"
    "Modified: 12.2.1997 / 14:27:42 / cg"
!

start
    "return the startPoint"

    ^ start

    "Modified: 12.2.1997 / 14:27:32 / cg"
! !

!Bezier methodsFor:'comparing'!

= anObject 
    "return true, if the receiver and the arg represent the same bezier curve"

    self species == anObject species ifTrue:[
        start = anObject start ifTrue:[
            end = anObject end ifTrue:[
                controlPoint1 = anObject controlPoint1 ifTrue:[
                    controlPoint2 = anObject controlPoint2 ifTrue:[
                        ^ true
                    ]
                ]
            ]
        ]
    ].
    ^ false.

    "Modified: 12.2.1997 / 14:29:38 / cg"
!

hash
    "return an integer useful as hashKey;
     redefined, since = is redefined"

    ^ start hash + end hash + controlPoint1 hash + controlPoint2 hash

    "Modified: 12.2.1997 / 14:30:11 / cg"
! !

!Bezier methodsFor:'converting'!

asLine
    "return a line from the startPoint to the endPoint"

    ^ LineSegment from:start to:end

    "Created: 12.2.1997 / 11:33:19 / cg"
    "Modified: 12.2.1997 / 14:31:01 / cg"
!

asPolyline
    "return a polygon which approximates the curve"

    ^ Polygon vertices:(self computePoints)

    "Modified: 12.2.1997 / 14:31:28 / cg"
! !

!Bezier methodsFor:'displaying'!

displayFilledOn: aGraphicsContext
    "report an error: cannot be filled."

    self shouldNotImplement

    "Modified: 12.2.1997 / 14:31:49 / cg"
!

displayStrokedOn: aGraphicsContext
    "display the curve as an outline"

    aGraphicsContext displayPolygon:(self computePoints)

    "Modified: 12.2.1997 / 14:33:09 / cg"
! !

!Bezier methodsFor:'private'!

addPointsFromStartX:p1X y:p1Y control1X:p2X y:p2Y control2X:p3X y:p3Y endX:p4X y:p4Y to:aCollection
    "actual workHorse for point computation"

    |x0 y0 x1 y1 x2 y2 t d dist dx3 dy3
      midX01 midY01 midX12 midY12 x1p y1p xm ym|

    x0 := p1X.  y0 := p1Y.
    x1 := p2X.  y1 := p2Y.
    x2 := p3X.  y2 := p3Y.

    [
        p4X = x0 ifTrue:[
            "p4X = x0, i.e. dx = 0"
            (x1 - x0) abs <= ScaledFlatness and: [(x2 - x0) abs <= ScaledFlatness]
        ] ifFalse:[
            dx3 := p4X - x0.
            dy3 := p4Y - y0.

            (dx3 >= 0 ifTrue: [dx3] ifFalse: [0 - dx3]) >=
             (dy3 >= 0 ifTrue: [dy3] ifFalse: [0 - dy3])
            ifTrue:[
                t := dy3 asFloat / dx3.
                d := ((1.0 + (t * t)) sqrt * ScaledFlatness) rounded.
                dist := (t * (x1 - x0)) rounded - (y1 - y0).

                (dist >= 0 ifTrue: [dist <= d] ifFalse: [dist + d >= 0]) 
                and:[dist := (t * (x2 - x0)) rounded - (y2 - y0).
                     dist >= 0 ifTrue: [dist <= d] ifFalse: [dist + d >= 0]]
            ] ifFalse:[
                t := dx3 asFloat / dy3.
                d := ((1.0 + (t * t)) sqrt * ScaledFlatness) rounded.
                dist := (t * (y1 - y0)) rounded - (x1 - x0).
                (dist >= 0 ifTrue: [dist <= d] ifFalse: [dist + d >= 0]) 
                and:[dist := (t * (y2 - y0)) rounded - (x2 - x0).
                     dist >= 0 ifTrue: [dist <= d] ifFalse: [dist + d >= 0]]
            ]
        ]
    ] whileFalse:[
        midX01 := (x0 + x1) // 2.  
        midY01 := (y0 + y1) // 2.
        midX12 := (x1 + x2) // 2.  
        midY12 := (y1 + y2) // 2.

        x2 := (x2 + p4X) // 2.  
        y2 := (y2 + p4Y) // 2.
        x1p := (midX01 + midX12) // 2.  
        y1p := (midY01 + midY12) // 2.
        x1 := (midX12 + x2) // 2.  
        y1 := (midY12 + y2) // 2.
        xm := (x1p + x1) // 2.  
        ym := (y1p + y1) // 2.

        self
            addPointsFromStartX:x0 y:y0
                      control1X:midX01 y:midY01
                      control2X:x1p y:y1p
                           endX:xm y:ym
                             to:aCollection.
        x0 := xm.  
        y0 := ym.
    ].
    aCollection add: (p4X asFloat * InverseScale) @ (p4Y asFloat  * InverseScale)

    "Created: 12.2.1997 / 15:05:52 / cg"
    "Modified: 12.2.1997 / 15:10:34 / cg"
!

computeBounds
    "return the reactngle which encloses the curve."

    ^ self class boundingRectangleForPoints:(self computePoints).

    "Modified: 12.2.1997 / 14:33:45 / cg"
!

computePoints
    "compute the points along the bezier - return a collection of points"

    |pointCollection|

    pointCollection := OrderedCollection new.
    pointCollection add:start.

    self 
        addPointsFromStartX: (start x * Scale) rounded
                          y: (start y * Scale) rounded
                  control1X: (controlPoint1 x * Scale) rounded
                          y: (controlPoint1 y * Scale) rounded
                  control2X: (controlPoint2 x * Scale) rounded
                          y: (controlPoint2 y * Scale) rounded
                       endX: (end x * Scale) rounded
                          y: (end y * Scale) rounded
                         to: pointCollection.
    ^ pointCollection

    "Modified: 12.2.1997 / 15:04:07 / cg"
!

setStart:startPoint end:endPoint controlPoint1:cp1 controlPoint2:cp2
    start := startPoint.
    end := endPoint.
    controlPoint1 := cp1.
    controlPoint2 := cp2

    "Modified: 12.2.1997 / 14:48:19 / cg"
! !

!Bezier methodsFor:'testing'!

outlineIntersects:aRectangle
    "return true, if the curve intersects a rectangle"

    ^ self class vertices:(self computePoints) intersectsRectangle:aRectangle

    "Created: 12.2.1997 / 11:33:18 / cg"
    "Modified: 12.2.1997 / 14:50:35 / cg"
! !

!Bezier methodsFor:'transforming'!

scaledBy:scaleFactor 
    "return a copy of the receiver, which is scaled by some amount"

    ^ self species
        start:(start * scaleFactor)
        end:(end * scaleFactor)
        controlPoint1:(controlPoint1 * scaleFactor)
        controlPoint2:(controlPoint2 * scaleFactor)

    "Created: 12.2.1997 / 11:33:18 / cg"
    "Modified: 12.2.1997 / 14:51:34 / cg"
!

translatedBy:translation 
    "return a copy of the receiver, which is translated by some amount"

    ^ self species
            start:(start + translation)
            end:(end + translation)
            controlPoint1:(controlPoint1 + translation)
            controlPoint2:(controlPoint2 + translation)

    "Modified: 12.2.1997 / 14:52:12 / cg"
! !

!Bezier class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Bezier.st,v 1.1 1997-02-12 14:17:03 cg Exp $'
! !
Bezier initialize!