Source codeContentsIndex
Graphics.UI.ObjectIO.StdPicture
Portabilityportable
Stabilityprovisional
Maintainerka2_mail@yahoo.com
Contents
Pen attributes
Font operations
Type classes
Data declarations
Region functions
Drawing functions
predefined fonts
A visible module
Description
StdPicture contains the drawing operations and access to Pictures.
Synopsis
newtype Draw a = Draw (Picture -> IO (a, Picture))
type Look = SelectState -> UpdateState -> Draw ()
doScreenDraw :: Draw x -> IO x
accClipPicture :: Region -> Draw x -> Draw x
accXorPicture :: Draw a -> Draw a
setPenAttributes :: [PenAttribute] -> Draw ()
getPenAttributes :: Draw [PenAttribute]
setPenPos :: Point2 -> Draw ()
getPenPos :: Draw Point2
setPenSize :: Int -> Draw ()
getPenSize :: Draw Int
setDefaultPenSize :: Draw ()
setPenColour :: Colour -> Draw ()
getPenColour :: Draw Colour
setDefaultPenColour :: Draw ()
setPenBack :: Colour -> Draw ()
getPenBack :: Draw Colour
setDefaultPenBack :: Draw ()
setPenFont :: Font -> Draw ()
getPenFont :: Draw Font
setDefaultPenFont :: Draw ()
getFontNames :: Draw [FontName]
getFontSizes :: Int -> Int -> FontName -> Draw [FontSize]
getFontCharWidth :: Font -> Char -> Draw Int
getFontCharWidths :: Font -> [Char] -> Draw [Int]
getFontStringWidth :: Font -> String -> Draw Int
getFontStringWidths :: Font -> [String] -> Draw [Int]
getFontMetrics :: Font -> Draw FontMetrics
getPenFontCharWidth :: Char -> Draw Int
getPenFontCharWidths :: [Char] -> Draw [Int]
getPenFontStringWidth :: String -> Draw Int
getPenFontStringWidths :: [String] -> Draw [Int]
getPenFontMetrics :: Draw FontMetrics
class MovePen f where
movePenPos :: f -> Draw ()
class Drawables figure where
draw :: figure -> Draw ()
drawAt :: Point2 -> figure -> Draw ()
undraw :: figure -> Draw ()
undrawAt :: Point2 -> figure -> Draw ()
class Fillables figure where
fill :: figure -> Draw ()
fillAt :: Point2 -> figure -> Draw ()
unfill :: figure -> Draw ()
unfillAt :: Point2 -> figure -> Draw ()
class Hilites figure where
hilite :: figure -> Draw ()
hiliteAt :: Point2 -> figure -> Draw ()
data Region = Region {
region_shape :: [RegionShape]
region_bound :: Rect
}
data RegionShape
= RegionRect Rect
| RegionPolygon Point2 [Vector2]
class ToRegion area where
toRegion :: area -> Region
data PolygonAt = PolygonAt {
polygon_pos :: Point2
polygon :: Polygon
}
isEmptyRegion :: Region -> Bool
getRegionBound :: Region -> Rectangle
sumRegion :: Region -> Region -> Region
drawPoint :: Draw ()
drawPointAt :: Point2 -> Draw ()
drawLineTo :: Point2 -> Draw ()
drawLine :: Point2 -> Point2 -> Draw ()
undrawLineTo :: Point2 -> Draw ()
undrawLine :: Point2 -> Point2 -> Draw ()
stdUnfillNewFrameLook :: SelectState -> UpdateState -> Draw ()
stdUnfillUpdAreaLook :: SelectState -> UpdateState -> Draw ()
module Graphics.UI.ObjectIO.StdPictureDef
Documentation
newtype Draw a
While drawing we need the current state called Picture state. The functions that are used for drawing need a Picture state as an argument and return the new updated state. The Draw monad is defined so that it would be easier for the user to write the functions. The Draw monad is in fact an IO monad, but it also takes care of the management of the Picture state. The definition of Draw is abstract.
Constructors
Draw (Picture -> IO (a, Picture))
show/hide Instances
type Look = SelectState -> UpdateState -> Draw ()
doScreenDraw :: Draw x -> IO x
accClipPicture :: Region -> Draw x -> Draw x
accXorPicture :: Draw a -> Draw a
Pen attributes
setPenAttributes :: [PenAttribute] -> Draw ()
getPenAttributes :: Draw [PenAttribute]
setPenPos :: Point2 -> Draw ()
getPenPos :: Draw Point2
The getPenPos function corresponds to the PenPos attribute. The function returns the current pen position.
setPenSize :: Int -> Draw ()
getPenSize :: Draw Int
setDefaultPenSize :: Draw ()
setPenColour :: Colour -> Draw ()
getPenColour :: Draw Colour
setDefaultPenColour :: Draw ()
setPenBack :: Colour -> Draw ()
getPenBack :: Draw Colour
setDefaultPenBack :: Draw ()
setPenFont :: Font -> Draw ()
getPenFont :: Draw Font
setDefaultPenFont :: Draw ()
Font operations
getFontNames :: Draw [FontName]
getFontSizes :: Int -> Int -> FontName -> Draw [FontSize]
getFontCharWidth :: Font -> Char -> Draw Int
getFontCharWidths :: Font -> [Char] -> Draw [Int]
getFontStringWidth :: Font -> String -> Draw Int
getFontStringWidths :: Font -> [String] -> Draw [Int]
getFontMetrics :: Font -> Draw FontMetrics
getPenFontCharWidth :: Char -> Draw Int
getPenFontCharWidths :: [Char] -> Draw [Int]
getPenFontStringWidth :: String -> Draw Int
getPenFontStringWidths :: [String] -> Draw [Int]
getPenFontMetrics :: Draw FontMetrics
Type classes
class MovePen f where
Methods
movePenPos :: f -> Draw ()
show/hide Instances
class Drawables figure where
Methods
draw :: figure -> Draw ()
drawAt :: Point2 -> figure -> Draw ()
undraw :: figure -> Draw ()
undrawAt :: Point2 -> figure -> Draw ()
show/hide Instances
class Fillables figure where
Methods
fill :: figure -> Draw ()
fillAt :: Point2 -> figure -> Draw ()
unfill :: figure -> Draw ()
unfillAt :: Point2 -> figure -> Draw ()
show/hide Instances
class Hilites figure where
Methods
hilite :: figure -> Draw ()
hiliteAt :: Point2 -> figure -> Draw ()
show/hide Instances
Data declarations
data Region
Constructors
Region
region_shape :: [RegionShape]
region_bound :: Rect
show/hide Instances
data RegionShape
Constructors
RegionRect Rect
RegionPolygon Point2 [Vector2]
class ToRegion area where
Methods
toRegion :: area -> Region
show/hide Instances
ToRegion PolygonAt
ToRegion Rectangle
ToRegion area => ToRegion [area]
(ToRegion area1, ToRegion area2) => ToRegion (Tup area1 area2)
data PolygonAt
Constructors
PolygonAt
polygon_pos :: Point2
polygon :: Polygon
show/hide Instances
Region functions
isEmptyRegion :: Region -> Bool
getRegionBound :: Region -> Rectangle
sumRegion :: Region -> Region -> Region
Drawing functions
drawPoint :: Draw ()
drawPointAt :: Point2 -> Draw ()
drawLineTo :: Point2 -> Draw ()
drawLine :: Point2 -> Point2 -> Draw ()
undrawLineTo :: Point2 -> Draw ()
undrawLine :: Point2 -> Point2 -> Draw ()
stdUnfillNewFrameLook :: SelectState -> UpdateState -> Draw ()
stdUnfillUpdAreaLook :: SelectState -> UpdateState -> Draw ()
predefined fonts
A visible module
module Graphics.UI.ObjectIO.StdPictureDef
Produced by Haddock version 0.8