wxcore-0.92.2.0: wxHaskell core

Copyright(c) Daan Leijen 2003
LicensewxWindows
Maintainerwxhaskell-devel@lists.sourceforge.net
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Graphics.UI.WXCore.Draw

Contents

Description

Drawing.

Synopsis

DC

drawLines :: DC a -> [Point] -> IO () Source

Draw connected lines.

drawPolygon :: DC a -> [Point] -> IO () Source

Draw a polygon. The polygon is filled with the odd-even rule.

getTextExtent :: DC a -> String -> IO Size Source

Gets the dimensions of the string using the currently selected font.

getFullTextExtent :: DC a -> String -> IO (Size, Int, Int) Source

Gets the dimensions of the string using the currently selected font. Takes text string to measure, and returns the size, descent and external leading. Descent is the dimension from the baseline of the font to the bottom of the descender , and external leading is any extra vertical space added to the font by the font designer (is usually zero).

dcClearRect :: DC a -> Rect -> IO () Source

Clear a specific rectangle with the current background brush. This is preferred to dcClear for scrolled windows as dcClear sometimes only clears the original view area, instead of the currently visible scrolled area. Unfortunately, the background brush is not set correctly on wxMAC 2.4, and this will always clear to a white color on mac systems.

Creation

withPaintDC :: Window a -> (PaintDC () -> IO b) -> IO b Source

Use a PaintDC.

withClientDC :: Window a -> (ClientDC () -> IO b) -> IO b Source

Use a ClientDC.

dcDraw :: DC a -> IO b -> IO b Source

Safely perform a drawing operation on a DC.

withSVGFileDC :: FilePath -> (SVGFileDC () -> IO b) -> IO b Source

Use a SVGFileDC.

Draw state

data DrawState Source

The drawing state (pen,brush,font,text color,text background color) of a device context.

dcEncapsulate :: DC a -> IO b -> IO b Source

Run a computation after which the original drawing state of the DC is restored.

dcGetDrawState :: DC a -> IO DrawState Source

Get the drawing state. (Should be deleted with drawStateDelete).

dcSetDrawState :: DC a -> DrawState -> IO () Source

Set the drawing state.

drawStateDelete :: DrawState -> IO () Source

Release the resources associated with a drawing state.

Double buffering

dcBuffer :: WindowDC a -> Rect -> (DC () -> IO ()) -> IO () Source

Use double buffering to draw to a DC -- reduces flicker. Note that the windowOnPaint handler can already take care of buffering automatically. The rectangle argument is normally the view rectangle (windowGetViewRect). Uses a MemoryDC to draw into memory first and than blit the result to the device context. The memory area allocated is the minimal size necessary to accomodate the rectangle, but is re-allocated on each invokation.

dcBufferWithRef :: WindowDC a -> Maybe (Var (Bitmap ())) -> Rect -> (DC () -> IO ()) -> IO () Source

Optimized double buffering. Takes a possible reference to a bitmap. If it is Nothing, a new bitmap is allocated everytime. Otherwise, the reference is used to re-use an allocated bitmap if possible. The Rect argument specifies the the current logical view rectangle. The last argument is called to draw on the memory DC.

dcBufferWithRefEx :: WindowDC a -> (DC () -> IO ()) -> Maybe (Var (Bitmap ())) -> Rect -> (DC () -> IO ()) -> IO () Source

Optimized double buffering. Takes a clear routine as its first argument. Normally this is something like 'dc -> dcClearRect dc viewArea' but on certain platforms, like MacOS X, special handling is necessary.

dcBufferWithRefExGcdc :: WindowDC a -> (DC () -> IO ()) -> Maybe (Var (Bitmap ())) -> Rect -> (GCDC () -> IO b) -> IO () Source

Optimized double buffering with a GCDC. Takes a clear routine as its first argument. Normally this is something like 'dc -> dcClearRect dc viewArea' but on certain platforms, like MacOS X, special handling is necessary.

Scrolled windows

windowGetViewStart :: Window a -> IO Point Source

Get logical view start, adjusted for scrolling.

windowGetViewRect :: Window a -> IO Rect Source

Get logical view rectangle, adjusted for scrolling.

windowCalcUnscrolledPosition :: Window a -> Point -> IO Point Source

Get logical coordinates adjusted for scrolling.

Font

data FontStyle Source

Font descriptor. The font is normally specified thru the FontFamily, giving some degree of portability. The _fontFace can be used to specify the exact (platform dependent) font.

Note that the original wxWidgets FontStyle is renamed to FontShape.

Constructors

FontStyle 

Fields

_fontSize :: !Int
 
_fontFamily :: !FontFamily
 
_fontShape :: !FontShape
 
_fontWeight :: !FontWeight
 
_fontUnderline :: !Bool
 
_fontFace :: !String

normally ""

_fontEncoding :: !Int

normally wxFONTENCODING_DEFAULT

data FontFamily Source

Standard font families.

Constructors

FontDefault

A system default font.

FontDecorative

Decorative font.

FontRoman

Formal serif font.

FontScript

Hand writing font.

FontSwiss

Sans-serif font.

FontModern

Fixed pitch font.

FontTeletype

A teletype (i.e. monospaced) font

data FontShape Source

The font style.

fontDefault :: FontStyle Source

Default 10pt font.

fontSwiss :: FontStyle Source

Default 10pt sans-serif font.

fontSmall :: FontStyle Source

Default 8pt font.

fontItalic :: FontStyle Source

Default 10pt italic.

fontFixed :: FontStyle Source

Monospaced font, 10pt.

withFontStyle :: FontStyle -> (Font () -> IO a) -> IO a Source

Use a font that is automatically deleted at the end of the computation.

dcWithFontStyle :: DC a -> FontStyle -> IO b -> IO b Source

Set a font that is automatically deleted at the end of the computation.

dcSetFontStyle :: DC a -> FontStyle -> IO () Source

Set the font info of a DC.

dcGetFontStyle :: DC a -> IO FontStyle Source

Get the current font info.

fontCreateFromStyle :: FontStyle -> IO (Font (), IO ()) Source

Create a Font from FontStyle. Returns both the font and a deletion procedure.

fontGetFontStyle :: Font () -> IO FontStyle Source

Get the FontStyle from a Font object.

Brush

data BrushStyle Source

Brush style.

Constructors

BrushStyle 

data BrushKind Source

Brush kind.

Constructors

BrushTransparent

No filling

BrushSolid

Solid color

BrushHatch

Hatch pattern

BrushStipple

Bitmap pattern (on win95 only 8x8 bitmaps are supported)

Fields

_brushBitmap :: !(Bitmap ())
 

data HatchStyle Source

Hatch style.

Constructors

HatchBDiagonal

Backward diagonal

HatchCrossDiag

Crossed diagonal

HatchFDiagonal

Forward diagonal

HatchCross

Crossed orthogonal

HatchHorizontal

Horizontal

HatchVertical

Vertical

brushDefault :: BrushStyle Source

Default brush (transparent, black).

brushSolid :: Color -> BrushStyle Source

A solid brush of a specific color.

brushTransparent :: BrushStyle Source

A transparent brush.

dcSetBrushStyle :: DC a -> BrushStyle -> IO () Source

Set the brush style (and text background color) of a device context.

dcGetBrushStyle :: DC a -> IO BrushStyle Source

Get the current brush of a device context.

withBrushStyle :: BrushStyle -> (Brush () -> IO a) -> IO a Source

Use a brush that is automatically deleted at the end of the computation.

dcWithBrushStyle :: DC a -> BrushStyle -> IO b -> IO b Source

Use a brush that is automatically deleted at the end of the computation.

dcWithBrush :: DC b -> Brush a -> IO c -> IO c Source

brushCreateFromStyle :: BrushStyle -> IO (Brush (), IO ()) Source

Create a new brush from a BrushStyle. Returns both the brush and its deletion procedure.

Pen

data PenStyle Source

Pen style.

Constructors

PenStyle 

data PenKind Source

Pen kinds.

Constructors

PenTransparent

No edge.

PenSolid 
PenDash 

Fields

_penDash :: !DashStyle
 
PenHatch 

Fields

_penHatch :: !HatchStyle
 
PenStipple

_penColor is ignored

Fields

_penBitmap :: !(Bitmap ())
 

data CapStyle Source

Cap style

Constructors

CapRound

End points are rounded

CapProjecting 
CapButt 

data JoinStyle Source

Join style.

Constructors

JoinRound

Corners are rounded

JoinBevel

Corners are bevelled

JoinMiter

Corners are blocked

penDefault :: PenStyle Source

Default pen (PenStyle PenSolid black 1 CapRound JoinRound)

penColored :: Color -> Int -> PenStyle Source

A solid pen with a certain color and width.

penTransparent :: PenStyle Source

A transparent pen.

dcSetPenStyle :: DC a -> PenStyle -> IO () Source

Set the current pen style. The text color is also adapted.

dcGetPenStyle :: DC a -> IO PenStyle Source

Get the current pen style.

withPenStyle :: PenStyle -> (Pen () -> IO a) -> IO a Source

Use a pen that is automatically deleted at the end of the computation.

dcWithPenStyle :: DC a -> PenStyle -> IO b -> IO b Source

Set a pen that is automatically deleted at the end of the computation.

dcWithPen :: DC a -> Pen p -> IO b -> IO b Source

Set a pen that is used during a certain computation.

penCreateFromStyle :: PenStyle -> IO (Pen (), IO ()) Source

Create a new pen from a PenStyle. Returns both the pen and its deletion procedure.

penGetPenStyle :: Pen a -> IO PenStyle Source

Create a PenStyle from a Pen.