GraphicsContext.st
author Claus Gittinger <cg@exept.de>
Thu, 25 Apr 1996 18:26:07 +0200
changeset 611 e0442439a3c6
parent 585 426d2018cdc8
child 619 a46cb2ef56bf
permissions -rw-r--r--
documentation

"
 COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

Object subclass:#GraphicsContext
	instanceVariableNames:'paint bgPaint function font lineStyle lineWidth joinStyle
		capStyle mask maskOrigin transformation'
	classVariableNames:'White Black DefaultFont'
	poolDictionaries:''
	category:'Graphics-Support'
!

!GraphicsContext class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    this is an abstract superclass for all kinds of graphic drawables -
    both windows and printed pages (i.e. printers) are inheriting from
    this class (even drawables not at all associated with any device would do so).

    Drawing is done in paint/bgPaint colors, which can be true colors (i.e.
    directly supported by the underlying hardware) or simulated colors
    (i.e. dithered colors or images).
    The paint/bgPaint instance variables are set to the logical colors,
    device specific drawable may like to keep actual colors in addition.

    The transformation instance variable is typically nil, for a 1-to-1
    coordinate mapping (i.e. x/y coordinates are pixels in the drawable).
    If nonNil, the transformation must be an  instance of WindowingTransformation
    and offers both a scale-factor and a translation.
    Also, drawing in metric- or inch-units can be done using transformations.
    (see instance creation methods of WindowingTransformation, and examples
     in 'doc/coding').

    All drawing is defined upon a few basic drawing methods, which must be 
    implemented by subclasses (some subclasses also redefine the others for
    more performance)

    [Instance variables:]

        paint           <Color>         the paint used for drawing
        bgPaint         <Color>         the background used for drawing texts and bitmaps
        function        <Symbol>        the drawing function (i.e. #copy, #or, #xor ...)
                                        - not all Drawables support every function
                                        (i.e. paper only allows #copy)
        font            <Font>          the current font to be used for drawing
        lineStyle       <Symbol>        the lineStyle (i.e. #solid, #dashed, #doubleDashed)
        lineWidth       <SmallInteger>  the lineWidth (device dependent, usually pixels)
        joinStyle       <Symbol>        the style in which lines (in polygons)
                                        are joined (i.e. #miter, #bevel, #round)
        capStyle        <Symbol>        the style in which the last point of a line is drawn
                                        (i.e. #notLast, #butt, #round, #projecting)
        mask            <Form>          a mask used for drawing
                                        - not all Drawables support it
        maskOrigin      <Point>         the origin of the mask relative to
                                        the drawables origin

    [Class variables:[

        White           <Color>         cached white color - its needed so often
        Black           <Color>         cached black color - its needed so often

        DefaultFont     <Font>          default font to use

    [author:]
        Claus Gittinger
"
!

examples
"
    drawing uses a paint color (which may be a dithered one) which is
    used like a `pen'. 
    A few drawing operations (opaqueForm and opaqueString drawing)
    use two colors, the paint and a backgroundPaint. For example,
    normal string drawing (#displayString:...) only draws the fonts
    on-pixels in the current paint, leaving off-pixels unchanged.
    In contrast, #drawOpaqueString:.. also changes these to the bgPaint color.
    The bgPaint can be changed with #backgroundPaint: or #paint:on: (which modifies both).

    lets try it in a view:

        |v|

        v := View new.
        v openAndWait.

        v paint:(Color red).
        v displayString:'hello' x:10 y:50

    the same using opaque drawing:
        |v|

        v := View new.
        v openAndWait.

        v paint:(Color red) on:(Color yellow).
        v displayOpaqueString:'hello' x:10 y:50



    Lines are drawn using the paint color (if solid) or both paint and bgPaint
    (dashed lines). The look of the line is controlled by joinStyle, capStyle,
    lineWidth and lineStyle.
    `lineStyle' can be one of #solid, #dashed, #doubleDashed
    where: #solid        - is for solid lines, drawn with the current paint color 

           #dashed       - for dashed lines, where only the on-dashes are drawn
                           with the current paint color

           #doubleDashed - dashed lines, draws on-dashes with paint color,
                           off-dashes with bgPaint

    for example:

        |v|

        v := View new.
        v openAndWait.

        v paint:(Color red) on:(Color blue).
        v displayLineFrom:(10@10) to:(90@90).

        v lineStyle:#dashed.
        v displayLineFrom:(90@10) to:(10@90).
        
        v lineStyle:#doubleDashed.
        v displayRectangle:((5@5) corner:(95@95)).

    changing the line-width:

        |v|

        v := View new.
        v openAndWait.

        v paint:(Color red).
        v displayLineFrom:(20@20) to:(80@80).

        v lineWidth:5.
        v displayLineFrom:(80@20) to:(20@80).

        v lineWidth:8.
        v displayRectangle:((5@5) corner:(95@95)).

    with wide lines, the corners (of polygons or rectangles) can be
    one of the joinStyles: #miter, #bevel, #round. The default is #miter.

        |v|

        v := View new extent:200@200.
        v openAndWait.

        v lineWidth:15.
        v paint:(Color red).

        v displayRectangle:((65@65) corner:(135@135)).

        v joinStyle:#bevel.
        v displayRectangle:((45@45) corner:(155@155)).

        v joinStyle:#round.
        v displayRectangle:((25@25) corner:(175@175)).


    the endPoints look is controlled with capStyle;
    possible values are: #notLast, #butt, #round, #projecting.
    The default is #butt. 
    #notLast is mostly useful when exoring (inverting): it will not draw the
    endPoint, to allow another line to join the previous line without inverting
    this point twice. (See the X manual for more info).

        |v|

        v := View new extent:200@200.
        v openAndWait.

        v lineWidth:15.
        v paint:(Color red).

        v displayLineFrom:(25@25) to:(175@25).

        v capStyle:#round.
        v displayLineFrom:(25@55) to:(175@55).

        v capStyle:#projecting.
        v displayLineFrom:(25@85) to:(175@85).


    You can use a bitmap as a point color:
    (this may be slow on some graphics devices, though)

        |v|

        v := View new extent:200@200.
        v openAndWait.

        v lineWidth:15.
        v paint:(Image fromFile:'granite_small.tiff').

        v displayLineFrom:(25@25) to:(175@25).

        v capStyle:#round.
        v displayLineFrom:(25@55) to:(175@55).

        v capStyle:#projecting.
        v displayLineFrom:(25@85) to:(175@85).

    all views support a translation and scale, so you can draw in another
    coordinate system:

        |v|

        v := View new extent:200@200.
        v openAndWait.

        v displayForm:(Image fromFile:'SBrowser.xbm') x:10 y:10.

        v scale:(2@2); translation:50.
        v displayForm:(Image fromFile:'SBrowser.xbm') x:10 y:10.

        v scale:(0.5@0.5); translation:0.
        v displayForm:(Image fromFile:'SBrowser.xbm') x:10 y:10.

    if scaling is on, it is often useful to be able to draw individual
    things unscaled - this still translates the position, but
    uses the unscaled font (for example, to draw strings in a graphic):

        |v|

        v := View new extent:200@200.
        v openAndWait.

        v displayForm:(Image fromFile:'SBrowser.xbm') x:10 y:10.
        v displayString:'hello' x:50 y:40.

        v scale:(2@4).
        v displayForm:(Image fromFile:'SBrowser.xbm') x:10 y:10.
        v displayUnscaledString:'hello' x:50 y:40.

    Filled objects are drawin using the #fillXXX methods; for example,
    displayRectangleXXX draws the outline, while fillRectangleXXX draws a
    filled one:
        |v|

        v := View new extent:200@200.
        v openAndWait.

        v displayArcIn:(20@20 corner:50@50) from:0 angle:180.
        v paint:Color yellow.
        v fillArcIn:(120@120 corner:150@150) from:0 angle:180.

        v paint:Color red.
        v displayCircle:150@50 radius:30.
        v paint:Color blue.
        v fillCircle:50@150 radius:30.
"
! !

!GraphicsContext class methodsFor:'initialization'!

initialize
    "setup some defaults - these are usually redefined
     during startup."

    White isNil ifTrue:[
	Color isNil ifTrue:[^ self].
	Display isNil ifTrue:[^ self].

	Color initialize.

	White := Color white on:Display.
	Black := Color black on:Display.

	Font initialize.
	DefaultFont := Font family:'courier' face:'medium' style:'roman' size:12
    ]
! !

!GraphicsContext class methodsFor:'instance creation'!

new
    "return a new instance of myself. Redefined to initialize
     the new thingy"

    ^ self basicNew initialize
! !

!GraphicsContext class methodsFor:'accessing defaults'!

defaultFont
    "get the default font used for drawing"

    DefaultFont isNil ifTrue:[
	DefaultFont := Font family:'courier' face:'medium' style:'roman' size:12
    ].
    ^ DefaultFont
!

defaultFont:aFont
    "set the default font used for drawing"

    DefaultFont := aFont
! !

!GraphicsContext class methodsFor:'constants'!

capButt
    "return a constant to specify butt cap"

    ^ #butt
!

capNotLast
    "return a constant to specify not-last cap"

    ^ #notLast
!

capProjecting
    "return a constant to specify projecting cap"

    ^ #projecting
!

capRound
    "return a constant to specify round cap"

    ^ #round
!

joinBevel
    "return a constant to specify bevel join"

    ^ #bevel
!

joinMiter
    "return a constant to specify miter join"

    ^ #miter
!

joinRound
    "return a constant to specify round join"

    ^ #round
! !

!GraphicsContext methodsFor:'ST-80 compatibility'!

findFont:aFontDescription
    "given a fontDescription, return a device font for it
     on my device."

    ^ aFontDescription on:self device

    "Modified: 22.4.1996 / 19:45:41 / cg"
!

widthOfString:aString
    "given a string, return its width in pixels if
     drawn on the receivers device."

    ^ (font on:self device) widthOf:aString

    "Modified: 22.4.1996 / 19:46:10 / cg"
!

widthOfString:aString from:start to:stop
    "given a string, return the width in pixels if
     a substring is drawn on the receivers device."

    ^ (font on:self device) widthOf:aString from:start to:stop

    "Modified: 22.4.1996 / 19:46:25 / cg"
! !

!GraphicsContext methodsFor:'ST-80 displaying'!

displayArc:origin radius:radius from:startAngle angle:angle
    "draw an arc around a point"

    self displayArcX:(origin x - radius)
		   y:(origin y - radius)
		   w:(radius * 2) 
		   h:(radius * 2)
		from:startAngle angle:angle
!

displayArcBoundedBy:boundingBox startAngle:startAngle sweepAngle:sweepAngle at:origin
   "draw an arc/circle/ellipse - ST-80 compatibility"                                

   ^ self displayArcX:(boundingBox left + origin x)
		    y:(boundingBox top + origin y)
		width:(boundingBox width)
	       height:(boundingBox height)
		 from:startAngle
		angle:sweepAngle
!

displayLineFrom:startPoint to:endPoint translateBy:anOffset
    "draw a line - ST-80 compatibility"

    self displayLineFrom:(startPoint + anOffset)
		      to:(endPoint + anOffset)
!

displayPolyline:aPolygon
    "draw a polygon - ST-80 compatibility"

    ^ self displayPolygon:aPolygon 
!

displayRectangularBorder:aRectangle at:aPoint
    "draw a rectangle - ST-80 compatibility"

    self displayRectangle:(aRectangle translateBy:aPoint)
!

displayWedgeBoundedBy:boundingBox startAngle:startAngle sweepAngle:sweepAngle at:origin
   "fill an arc/circle/ellipse - ST-80 compatibility"

   ^ self fillArcX:(boundingBox left + origin x)
		 y:(boundingBox top + origin y)
	     width:(boundingBox width)
	    height:(boundingBox height)
	      from:startAngle
	     angle:sweepAngle
! !

!GraphicsContext methodsFor:'accessing'!

backgroundPaint
    "return the background paint color.
     (used for opaqueForms and opaqueStrings)"

    ^ bgPaint
!

backgroundPaint:aColor
    "set the background painting color (which is used for
     opaqueForms and opaqueStrings). aColor can be a dithered one."

    ^ self subclassResponsibility
!

capStyle
    "return the current cap-style for line-drawing"

    ^ capStyle
!

capStyle:aStyleSymbol
    "set the cap-style for line-drawing;
     possible styles are: #notLast, #butt, #round, #projecting"

    ^ self subclassResponsibility
!

clipRect
    "return the drawing clip-rectangle"

    ^ self subclassResponsibility
!

clipRect:aRectangle
    "set the drawing clip-rectangle"

    ^ self subclassResponsibility
!

clippingBounds
    "return the drawing clip-rectangle - name alias ST-80 compatibility"

    ^ self clipRect

    "Modified: 13.4.1996 / 20:13:04 / cg"
!

clippingRectangleOrNil
    "return the drawing clip-rectangle, or nil if there is none"

    ^ self subclassResponsibility

    "Created: 10.4.1996 / 14:31:19 / cg"
    "Modified: 13.4.1996 / 20:12:43 / cg"
!

font
    "return the current drawing font"

    ^ font
!

font:aFont
    "set the drawing font"

    ^ self subclassResponsibility
!

function
    "return the current drawing function"

    ^ function
!

function:aFunctionSymbol
    "set the drawing function"

    ^ self subclassResponsibility
!

graphicsContext
    "for ST-80 compatibility"

    ^ self
!

joinStyle
    "return the current join-style for polygon-drawing"

    ^ joinStyle
!

joinStyle:aStyleSymbol
    "set the join-style of lines in polygon-drawing;
     possible styles are: #miter, #bevel, #round"

    ^ self subclassResponsibility
!

lineStyle
    "return the current line-drawing-style"

    ^ lineStyle
!

lineStyle:aStyleSymbol
    "set the line-drawing-style;
     possible styles are: #solid, #dashed, #doubleDashed"

    lineStyle := aStyleSymbol
!

lineWidth
    "return the current drawing linewidth"

    ^ lineWidth
!

lineWidth:aNumber
    "set the line drawing width in pixels"

    lineWidth := aNumber
!

mask
    "return the current drawing mask"

    ^ mask
!

mask:aForm
    "set the drawing mask"

    ^ self subclassResponsibility
!

maskOrigin
    "return the origin within the mask (used to draw with patterns).
     Should be redefined in classes which support it.
     This is an alias for ST-80's #phase"

    ^ maskOrigin
!

maskOrigin:aPoint
    "set the origin within the mask (used to draw with patterns).
     Should be redefined in classes which support it.
     This is an alias for ST-80's #phase:"

    ^ self maskOriginX:aPoint x y:aPoint y
!

maskOriginX:x y:y 
    "set the origin within the mask (used to draw with patterns).
     Should be redefined in classes which support it.
     This is an alias for ST-80's #phase:"

    ^ self
!

paint
    "return the current paint drawing color"

    ^ paint
!

paint:aColor
    "set the drawing painting color, aColor can be a dithered one"

    paint := aColor
!

paint:fgColor on:bgColor
    "set the paint and backgroundPaint, used for text and bitmaps.
     Both colors may be dithered colors"

    self paint:fgColor.
    bgPaint := bgColor

    "Modified: 13.4.1996 / 20:20:24 / cg"
!

phase
    "return the origin within the mask (used to draw with patterns).
     This is an alias for ST/X's #maskOrigin"

    ^ self maskOrigin
!

phase:aPoint
    "set the origin within the mask (used to draw with patterns).
     This is an alias for ST/X's #maskOrigin:"

    ^ self maskOrigin:aPoint
!

setMaskOrigin:aPoint
    "set the origin within the mask (used to draw with patterns).
     OBSOLETE: use #maskOrigin: or #phase:"

    ^ self maskOrigin:aPoint
!

setMaskOriginX:x y:y
    "set the origin within the mask (used to draw with patterns).
     OBSOLETE: use #maskOriginX:y: or #phase:"

    ^ self maskOriginX:x y:y 
!

viewOrigin
    "return the drawables visible origin (for scrolling)"

    ^ 0@0
!

withPattern:aForm do:aBlock
    "draw with a pattern.
     Should be redefined in classes which support it"

    'GC: pattern drawing not implemented' infoPrintNL.

    aBlock value

    "Modified: 7.3.1996 / 19:17:05 / cg"
! !

!GraphicsContext methodsFor:'accessing-transformation'!

scale
    "return the scale factor (as point) of the transformation"

    transformation isNil ifTrue:[^ 1].
    ^ transformation scale
!

scale:aPoint
    "set the scale factor of the transformation"

    transformation isNil ifTrue:[
	aPoint = 1 ifTrue:[^ self].
	transformation := WindowingTransformation scale:aPoint translation:0
    ].

    transformation scale:aPoint.
!

transformation 
    "return the transformation"

    ^ transformation
!

transformation:aTransformation 
    "set the transformation"

    transformation := aTransformation
! !

!GraphicsContext methodsFor:'basic displaying'!

displayArcX:x y:y w:width h:height from:startAngle angle:angle
    "draw an arc in a box
     - this could be recoded to draw using displayLine"

    ^ self subclassResponsibility
!

displayForm:aForm x:x y:y
    "draw a form at x/y; if the form has depth 1, 1's in the form are
     drawn in current fg, 0's are ignored.
     If the form has depth ~~ 1, the result is undefined"

    |fg bg f noColor|

    fg := paint.
    bg := bgPaint.
    f := function.

    f ~~ #copy ifTrue:[
	self error:'function not supported'.
	^ self
    ].

    noColor := Color noColor.
    "
     stamp out fg-pixels
    "
    self paint:noColor on:Color allColor function:#and.
    self displayOpaqueForm:aForm x:x y:y.
    "
     or-in fg-pixels
    "
    self paint:fg on:Color noColor function:#or.
    self displayOpaqueForm:aForm x:x y:y.
    self paint:fg on:fg function:f.
!

displayOpaqueForm:aForm x:x y:y
    "draw a form at x/y; if the form has depth 1, 1's in the form are
     drawn in current fg, 0's in current bg color.
     If the form has depth ~~ 1, it is copied as is onto the receiver"

    ^ self subclassResponsibility
!

displayOpaqueString:aString from:index1 to:index2 x:x y:y
    "draw part of a string with both fg and bg at x/y in current font"

    ^ self subclassResponsibility
!

displayPolygon:aPolygon
    "draw a polygon
     - this could be recoded to draw using displayLine"

    ^ self subclassResponsibility
!

displayRectangleX:x y:y width:w height:h
    "draw a rectangle
     - this could be recoded to draw using displayLine"

    ^ self subclassResponsibility
!

displayString:aString from:index1 to:index2 x:x y:y
    "draw part of a string with fg at x/y in current font"

    ^ self subclassResponsibility
! !

!GraphicsContext methodsFor:'basic filling'!

fillArcX:x y:y w:w h:h from:start angle:angle
    "fill an arc with current paint color"

    ^ self subclassResponsibility
!

fillPolygon:points
    "fill a polygon with current paint color"

    ^ self subclassResponsibility
!

fillRectangleX:x y:y width:w height:h
    "fill a rectangle with current paint color"

    ^ self subclassResponsibility
! !

!GraphicsContext methodsFor:'bit blitting'!

copyFrom:aGC toX:dstX y:dstY
    "copy from a drawable - maybe self"

    self copyFrom:aGC x:0 y:0 toX:dstX y:dstY width:aGC width height:aGC height
!

copyFrom:aGC x:srcX y:srcY toX:dstX y:dstY width:w height:h
    "copy from a drawable - maybe self"

    ^ self subclassResponsibility
!

copyFrom:aGC x:dstX y:dstY width:w height:h
    "copy from a drawable - maybe self"

    self copyFrom:aGC x:0 y:0 toX:dstX y:dstY width:w height:h
! !

!GraphicsContext methodsFor:'drawing'!

displayArcIn:aRectangle from:startAngle angle:angle
    "draw an arc in a box"

    self displayArcX:(aRectangle left)
		   y:(aRectangle top)
		   w:(aRectangle width)
		   h:(aRectangle height)
		from:startAngle
	       angle:angle
!

displayArcOrigin:origin corner:corner from:startAngle angle:angle
    "draw an arc in a box"

    |left top right bot|

    left := origin x.
    top := origin y.
    right := corner x.
    bot := corner y.
    self displayArcX:left y:top
		   w:(right - left + 1) h:(bot - top + 1)
		from:startAngle angle:angle
!

displayCircle:aPoint radius:r
    "draw a circle around a center point"

    self displayCircleX:(aPoint x) y:(aPoint y) radius:r
!

displayCircleIn:aRectangle
    "draw a circle in a box"

    self
	displayArcX:(aRectangle left)
		  y:(aRectangle top)
		  w:(aRectangle width)
		  h:(aRectangle height)
	       from:0 angle:360
!

displayCircleX:x y:y radius:r
    "draw a circle around a center point"

    |d|
    d := 2 * r.
    self displayArcX:(x - r) y:(y - r)
		   w:d h:d
		from:0 angle:360
!

displayForm:aForm at:aPoint
    "draw a form"

    self displayForm:aForm x:(aPoint x) y:(aPoint y)
!

displayLineFrom:point1 to:point2
    "draw a line"

    self displayLineFromX:(point1 x) y:(point1 y)
		      toX:(point2 x) y:(point2 y)
!

displayOpaqueString:aString at:aPoint
    "draw a string with both fg and bg"

    self displayOpaqueString:aString x:(aPoint x) y:(aPoint y)
!

displayOpaqueString:aString from:start to:stop at:aPoint
    "draw part of a string - drawing both fg and bg"

    ^ self displayOpaqueString:aString from:start to:stop x:aPoint x y:aPoint y
!

displayOpaqueString:aString x:x y:y
    "draw a string with both fg and bg"

    self displayOpaqueString:aString from:1 to:(aString size) x:x y:y
!

displayPoint:aPoint
    "draw a pixel"

    self displayPointX:(aPoint x) y:(aPoint y)
!

displayPointX:x y:y
    "draw a point at x/y"

    self displayLineFromX:x y:y toX:x y:y
!

displayRectangle:aRectangle
    "draw a rectangle"

    self displayRectangleX:(aRectangle left)
			 y:(aRectangle top)
		     width:(aRectangle width)
		    height:(aRectangle height)
!

displayRectangleOrigin:origin corner:corner
    "draw a rectangle"

    |top left|

    left := origin x.
    top := origin y.
    self displayRectangleX:left y:top 
                     width:(corner x - left)
                    height:(corner y - top)

    "Modified: 13.4.1996 / 20:58:31 / cg"
!

displayString:aString at:aPoint
    "draw a string - drawing fg only"

    self displayString:aString x:aPoint x y:aPoint y
!

displayString:aString from:start to:stop at:aPoint
    "draw part of a string - drawing fg only"

    ^ self displayString:aString from:start to:stop x:aPoint x y:aPoint y
!

displayString:aString x:x y:y
    "draw a string - drawing fg only"

    self displayString:aString from:1 to:(aString size) x:x y:y
! !

!GraphicsContext methodsFor:'drawing in device coordinates'!

displayDeviceLineFromX:x1 y:y1 toX:x2 y:y2
    "draw a line in device coordinates"

    |sav|

    sav := transformation.
    transformation := nil.
    self displayLineFromX:x1 y:y1 toX:x2 y:y2.
    transformation := sav
!

fillDeviceRectangleX:x y:y width:w height:h
    "fill a rectangle with current paint color (device coordinates)"

    |sav|

    sav := transformation.
    transformation := nil.
    self fillRectangleX:x y:y width:w height:h.
    transformation := sav
!

fillDeviceRectangleX:x y:y width:w height:h with:aPattern
    "fill the rectangular area in the receiver with aPattern,
     which may be a Form or Color. Use device coordinates."

    self withPattern:aPattern do:[
	self fillDeviceRectangleX:x y:y width:w height:h
    ]
! !

!GraphicsContext methodsFor:'filling'!

fillArc:origin radius:r from:startAngle angle:angle
    "draw a filled arc around a point"

    |d|
    d := 2 * r.
    self fillArcX:(origin x - r) y:(origin y - r)
		w:d h:d
	     from:startAngle angle:angle
!

fillArcIn:aRectangle from:startAngle angle:angle
    "draw a filled arc in a box"

    self fillArcX:(aRectangle left)
                   y:(aRectangle top)
                   w:(aRectangle width)
                   h:(aRectangle height)
                from:startAngle
               angle:angle

    "Created: 13.4.1996 / 20:56:03 / cg"
!

fillArcOrigin:origin corner:corner from:startAngle angle:angle
    "draw a filled arc in a box"

    |left top right bot|

    left := origin x.
    top := origin y.
    right := corner x.
    bot := corner y.
    self 
        fillArcX:left 
        y:top
        w:(right - left + 1) 
        h:(bot - top + 1)
        from:startAngle 
        angle:angle

    "Created: 13.4.1996 / 20:56:56 / cg"
!

fillCircle:aPoint radius:aNumber
    "draw a filled circle around aPoint"

    self fillCircleX:(aPoint x) y:(aPoint y) radius:aNumber
!

fillCircleIn:aRectangle
    "draw a filled circle in a box"

    self
        fillArcX:(aRectangle left)
               y:(aRectangle top)
               w:(aRectangle width)
               h:(aRectangle height)
            from:0 
           angle:360

    "Created: 13.4.1996 / 20:57:41 / cg"
!

fillCircleX:x y:y radius:r
    "draw a filled circle around x@y"

    |d|

    d := 2 * r.
    self fillArcX:(x - r) y:(y - r) 
		w:d h:d 
	     from:0 angle:360
!

fillRectangle:aRectangle
    "fill a rectangle with current paint color"

    self fillRectangleX:(aRectangle left)
		      y:(aRectangle top)
		  width:(aRectangle width)
		 height:(aRectangle height)
!

fillRectangleOrigin:origin corner:corner
    "draw a filled rectangle"

    |top left|

    left := origin x.
    top := origin y.
    self fillRectangleX:left y:top 
                  width:(corner x - left)
                 height:(corner y - top)

    "Created: 13.4.1996 / 20:58:16 / cg"
! !

!GraphicsContext methodsFor:'initialization'!

initialize
    "set up some useful default values"

    paint := Black.
    bgPaint := White.
    function := #copy.
    lineWidth := 1.
    lineStyle := #solid.
    joinStyle := #miter.
    capStyle := #butt.
    font := DefaultFont.
! !

!GraphicsContext methodsFor:'misc'!

flush
    "send all buffered drawing to the device."

    self device flush

    "Modified: 22.4.1996 / 19:47:19 / cg"
! !

!GraphicsContext class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/GraphicsContext.st,v 1.27 1996-04-25 16:26:07 cg Exp $'
! !
GraphicsContext initialize!