| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Graphics.Gloss.Data.Picture
Synopsis
- data Picture- = Blank
- | Polygon Path
- | Line Path
- | Circle Float
- | ThickCircle Float Float
- | Arc Float Float Float
- | ThickArc Float Float Float Float
- | Text String
- | Bitmap BitmapData
- | BitmapSection Rectangle BitmapData
- | Color Color Picture
- | Translate Float Float Picture
- | Rotate Float Picture
- | Scale Float Float Picture
- | Pictures [Picture]
 
- type Point = (Float, Float)
- type Vector = Point
- type Path = [Point]
- blank :: Picture
- polygon :: Path -> Picture
- line :: Path -> Picture
- circle :: Float -> Picture
- thickCircle :: Float -> Float -> Picture
- arc :: Float -> Float -> Float -> Picture
- thickArc :: Float -> Float -> Float -> Float -> Picture
- text :: String -> Picture
- bitmap :: BitmapData -> Picture
- bitmapSection :: Rectangle -> BitmapData -> Picture
- color :: Color -> Picture -> Picture
- translate :: Float -> Float -> Picture -> Picture
- rotate :: Float -> Picture -> Picture
- scale :: Float -> Float -> Picture -> Picture
- pictures :: [Picture] -> Picture
- lineLoop :: Path -> Picture
- circleSolid :: Float -> Picture
- arcSolid :: Float -> Float -> Float -> Picture
- sectorWire :: Float -> Float -> Float -> Picture
- rectanglePath :: Float -> Float -> Path
- rectangleWire :: Float -> Float -> Picture
- rectangleSolid :: Float -> Float -> Picture
- rectangleUpperPath :: Float -> Float -> Path
- rectangleUpperWire :: Float -> Float -> Picture
- rectangleUpperSolid :: Float -> Float -> Picture
Documentation
A 2D picture
Constructors
| Blank | A blank picture, with nothing in it. | 
| Polygon Path | A convex polygon filled with a solid color. | 
| Line Path | A line along an arbitrary path. | 
| Circle Float | A circle with the given radius. | 
| ThickCircle Float Float | A circle with the given radius and thickness.
   If the thickness is 0 then this is equivalent to  | 
| Arc Float Float Float | A circular arc drawn counter-clockwise between two angles (in degrees) at the given radius. | 
| ThickArc Float Float Float Float | A circular arc drawn counter-clockwise between two angles
  (in degrees), with the given radius and thickness.
   If the thickness is 0 then this is equivalent to  | 
| Text String | Some text to draw with a vector font. | 
| Bitmap BitmapData | A bitmap image. | 
| BitmapSection Rectangle BitmapData | A subsection of a bitmap image where the first argument selects a sub section in the bitmap, and second argument determines the bitmap data. | 
| Color Color Picture | A picture drawn with this color. | 
| Translate Float Float Picture | A picture translated by the given x and y coordinates. | 
| Rotate Float Picture | A picture rotated clockwise by the given angle (in degrees). | 
| Scale Float Float Picture | A picture scaled by the given x and y factors. | 
| Pictures [Picture] | A picture consisting of several others. | 
Instances
| Eq Picture | |
| Data Picture | |
| Defined in Graphics.Gloss.Internals.Data.Picture Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Picture -> c Picture # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Picture # toConstr :: Picture -> Constr # dataTypeOf :: Picture -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Picture) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Picture) # gmapT :: (forall b. Data b => b -> b) -> Picture -> Picture # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Picture -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Picture -> r # gmapQ :: (forall d. Data d => d -> u) -> Picture -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Picture -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Picture -> m Picture # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Picture -> m Picture # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Picture -> m Picture # | |
| Show Picture | |
| Semigroup Picture | |
| Monoid Picture | |
Aliases for Picture constructors
thickCircle :: Float -> Float -> Picture Source #
A circle with the given thickness and radius.
   If the thickness is 0 then this is equivalent to Circle.
arc :: Float -> Float -> Float -> Picture Source #
A circular arc drawn counter-clockwise between two angles (in degrees) at the given radius.
thickArc :: Float -> Float -> Float -> Float -> Picture Source #
A circular arc drawn counter-clockwise between two angles (in degrees),
   with the given radius  and thickness.
   If the thickness is 0 then this is equivalent to Arc.
bitmap :: BitmapData -> Picture Source #
A bitmap image
bitmapSection :: Rectangle -> BitmapData -> Picture Source #
a subsection of a bitmap image first argument selects a sub section in the bitmap second argument determines the bitmap data
translate :: Float -> Float -> Picture -> Picture Source #
A picture translated by the given x and y coordinates.
rotate :: Float -> Picture -> Picture Source #
A picture rotated clockwise by the given angle (in degrees).
scale :: Float -> Float -> Picture -> Picture Source #
A picture scaled by the given x and y factors.
Compound shapes
circleSolid :: Float -> Picture Source #
A solid circle with the given radius.
arcSolid :: Float -> Float -> Float -> Picture Source #
A solid arc, drawn counter-clockwise between two angles at the given radius.
sectorWire :: Float -> Float -> Float -> Picture Source #
A wireframe sector of a circle. An arc is draw counter-clockwise from the first to the second angle at the given radius. Lines are drawn from the origin to the ends of the arc.
A path representing a rectangle centered about the origin
rectangleUpperPath :: Float -> Float -> Path Source #
A path representing a rectangle in the y > 0 half of the x-y plane.