Safe Haskell | None |
---|---|
Language | Haskell2010 |
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]
- data Color
- makeColor :: Float -> Float -> Float -> Float -> Color
- makeColorI :: Int -> Int -> Int -> Int -> Color
- makeRawColor :: Float -> Float -> Float -> Float -> Color
- makeRawColorI :: Int -> Int -> Int -> Int -> Color
- rgbaOfColor :: Color -> (Float, Float, Float, Float)
- clampColor :: Color -> Color
- data Rectangle = Rectangle {}
- data BitmapData
- bitmapSize :: BitmapData -> (Int, Int)
- data BitmapFormat = BitmapFormat {}
- data PixelFormat
- data RowOrder
- bitmapOfForeignPtr :: Int -> Int -> BitmapFormat -> ForeignPtr Word8 -> Bool -> Picture
- bitmapDataOfForeignPtr :: Int -> Int -> BitmapFormat -> ForeignPtr Word8 -> Bool -> BitmapData
- bitmapOfByteString :: Int -> Int -> BitmapFormat -> ByteString -> Bool -> Picture
- bitmapDataOfByteString :: Int -> Int -> BitmapFormat -> ByteString -> Bool -> BitmapData
- bitmapOfBMP :: BMP -> Picture
- bitmapDataOfBMP :: BMP -> BitmapData
- loadBMP :: FilePath -> IO Picture
- displayPicture :: (Int, Int) -> Color -> State -> Float -> Picture -> IO ()
- renderPicture :: State -> Float -> Picture -> IO ()
- withModelview :: (Int, Int) -> IO () -> IO ()
- withClearBuffer :: Color -> IO () -> IO ()
- initState :: IO State
- data State
Picture data type
A 2D picture
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 Source # | |
Data Picture Source # | |
Defined in Graphics.Gloss.Internals.Data.Picture 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 Source # | |
Semigroup Picture Source # | |
Monoid Picture Source # | |
Colors
An abstract color value.
We keep the type abstract so we can be sure that the components
are in the required range. To make a custom color use makeColor
.
Instances
Eq Color Source # | |
Data Color Source # | |
Defined in Graphics.Gloss.Internals.Data.Color gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Color -> c Color # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Color # dataTypeOf :: Color -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Color) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color) # gmapT :: (forall b. Data b => b -> b) -> Color -> Color # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r # gmapQ :: (forall d. Data d => d -> u) -> Color -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Color -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Color -> m Color # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Color -> m Color # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Color -> m Color # | |
Num Color Source # | |
Show Color Source # | |
:: Float | Red component. |
-> Float | Green component. |
-> Float | Blue component. |
-> Float | Alpha component. |
-> Color |
Make a custom color. All components are clamped to the range [0..1].
makeColorI :: Int -> Int -> Int -> Int -> Color Source #
Make a custom color. All components are clamped to the range [0..255].
makeRawColor :: Float -> Float -> Float -> Float -> Color Source #
Make a custom color.
Using this function over makeColor
avoids clamping the components,
which saves time. However, if the components are out of range then
this will result in integer overflow at rendering time, and the actual
picture you get will be implementation dependent.
You'll only need to use this function when using the gloss-raster
package that builds a new color for every pixel. If you're just working
with the Picture data type then it there is no need for raw colors.
makeRawColorI :: Int -> Int -> Int -> Int -> Color Source #
Make a custom color, taking pre-clamped components.
clampColor :: Color -> Color Source #
Clamp components of a raw color into the required range.
Bitmaps
Represents a rectangular section in a bitmap
Instances
Eq Rectangle Source # | |
Data Rectangle Source # | |
Defined in Graphics.Gloss.Internals.Rendering.Bitmap gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rectangle -> c Rectangle # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rectangle # toConstr :: Rectangle -> Constr # dataTypeOf :: Rectangle -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rectangle) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rectangle) # gmapT :: (forall b. Data b => b -> b) -> Rectangle -> Rectangle # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rectangle -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rectangle -> r # gmapQ :: (forall d. Data d => d -> u) -> Rectangle -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rectangle -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rectangle -> m Rectangle # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rectangle -> m Rectangle # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rectangle -> m Rectangle # | |
Ord Rectangle Source # | |
Defined in Graphics.Gloss.Internals.Rendering.Bitmap | |
Read Rectangle Source # | |
Show Rectangle Source # | |
data BitmapData Source #
Abstract 32-bit RGBA bitmap data.
Instances
Eq BitmapData Source # | |
Defined in Graphics.Gloss.Internals.Rendering.Bitmap (==) :: BitmapData -> BitmapData -> Bool # (/=) :: BitmapData -> BitmapData -> Bool # | |
Data BitmapData Source # | |
Defined in Graphics.Gloss.Internals.Rendering.Bitmap gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitmapData -> c BitmapData # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BitmapData # toConstr :: BitmapData -> Constr # dataTypeOf :: BitmapData -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BitmapData) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BitmapData) # gmapT :: (forall b. Data b => b -> b) -> BitmapData -> BitmapData # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitmapData -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitmapData -> r # gmapQ :: (forall d. Data d => d -> u) -> BitmapData -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BitmapData -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitmapData -> m BitmapData # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitmapData -> m BitmapData # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitmapData -> m BitmapData # | |
Show BitmapData Source # | |
Defined in Graphics.Gloss.Internals.Rendering.Bitmap showsPrec :: Int -> BitmapData -> ShowS # show :: BitmapData -> String # showList :: [BitmapData] -> ShowS # |
bitmapSize :: BitmapData -> (Int, Int) Source #
width, height in pixels
data BitmapFormat Source #
Description of how the bitmap is layed out in memory.
- Prior version of Gloss assumed `BitmapFormat BottomToTop PxAGBR`
Instances
data PixelFormat Source #
Pixel formats describe the order of the color channels in memory.
Instances
Order of rows in an image are either:
TopToBottom
- the top row, followed by the next-lower row and so on.BottomToTop
- the bottom row followed by the next-higher row and so on.
Instances
Bounded RowOrder Source # | |
Enum RowOrder Source # | |
Defined in Graphics.Gloss.Internals.Rendering.Bitmap | |
Eq RowOrder Source # | |
Data RowOrder Source # | |
Defined in Graphics.Gloss.Internals.Rendering.Bitmap gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowOrder -> c RowOrder # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowOrder # toConstr :: RowOrder -> Constr # dataTypeOf :: RowOrder -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RowOrder) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowOrder) # gmapT :: (forall b. Data b => b -> b) -> RowOrder -> RowOrder # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowOrder -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowOrder -> r # gmapQ :: (forall d. Data d => d -> u) -> RowOrder -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RowOrder -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RowOrder -> m RowOrder # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RowOrder -> m RowOrder # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RowOrder -> m RowOrder # | |
Ord RowOrder Source # | |
Defined in Graphics.Gloss.Internals.Rendering.Bitmap | |
Show RowOrder Source # | |
bitmapOfForeignPtr :: Int -> Int -> BitmapFormat -> ForeignPtr Word8 -> Bool -> Picture Source #
O(1). Use a ForeignPtr
of RGBA data as a bitmap with the given
width and height.
The boolean flag controls whether Gloss should cache the data
between frames for speed. If you are programatically generating
the image for each frame then use False
. If you have loaded it
from a file then use True
.
bitmapDataOfForeignPtr :: Int -> Int -> BitmapFormat -> ForeignPtr Word8 -> Bool -> BitmapData Source #
bitmapOfByteString :: Int -> Int -> BitmapFormat -> ByteString -> Bool -> Picture Source #
O(size). Copy a ByteString
of RGBA data into a bitmap with the given
width and height.
The boolean flag controls whether Gloss should cache the data
between frames for speed. If you are programatically generating
the image for each frame then use False
. If you have loaded it
from a file then use True
.
bitmapDataOfByteString :: Int -> Int -> BitmapFormat -> ByteString -> Bool -> BitmapData Source #
bitmapDataOfBMP :: BMP -> BitmapData Source #
O(size). Copy a BMP
file into a bitmap.
loadBMP :: FilePath -> IO Picture Source #
Load an uncompressed 24 or 32bit RGBA BMP file as a bitmap.
Rendering
:: (Int, Int) | Window width and height. |
-> Color | Color to clear the window with. |
-> State | Current rendering state. |
-> Float | View port scale, which controls the level of detail. Use 1.0 to start with. |
-> Picture | Picture to draw. |
-> IO () |
Set up the OpenGL context, clear the buffer, and render the given picture into it.
This is the same as renderPicture
composed with withModelview
and withClearBuffer
. If you want to manage your own OpenGL context then
you can just call renderPicture
.
Using this function assumes that you've already opened a window
and set that to the active context. If you don't want to do your own window
management then use the gloss
package instead.
:: State | Current rendering state. |
-> Float | View port scale, which controls the level of detail. Use 1.0 to start with. |
-> Picture | Picture to render. |
-> IO () |
Render a picture into the current OpenGL context.
Assumes that the OpenGL matrix mode is set to Modelview
Set up the OpenGL rendering context for orthographic projection and run an action to draw the model.
Clear the OpenGL buffer with the given background color and run an action to draw the model.