-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Painless 2D vector graphics, animations and simulations. -- -- Gloss hides the pain of drawing simple vector graphics behind a nice -- data type and a few display functions. Gloss uses OpenGL under the -- hood, but you won't need to worry about any of that. Get something -- cool on the screen in under 10 minutes. @package gloss @version 1.13.2.2 -- | Functions to load bitmap data from various places. module Graphics.Gloss.Data.Bitmap -- | Represents a rectangular section in a bitmap data Rectangle Rectangle :: (Int, Int) -> (Int, Int) -> Rectangle -- | x- and y-pos in the bitmap in pixels [rectPos] :: Rectangle -> (Int, Int) -- | width/height of the area in pixelsi [rectSize] :: Rectangle -> (Int, Int) -- | Abstract 32-bit RGBA bitmap data. data BitmapData -- | width, height in pixels bitmapSize :: BitmapData -> (Int, Int) -- | Description of how the bitmap is layed out in memory. -- -- data BitmapFormat BitmapFormat :: RowOrder -> PixelFormat -> BitmapFormat [rowOrder] :: BitmapFormat -> RowOrder [pixelFormat] :: BitmapFormat -> PixelFormat -- | Order of rows in an image are either: -- -- data RowOrder TopToBottom :: RowOrder BottomToTop :: RowOrder -- | Pixel formats describe the order of the color channels in memory. data PixelFormat PxRGBA :: PixelFormat PxABGR :: PixelFormat -- | 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. bitmapOfForeignPtr :: Int -> Int -> BitmapFormat -> ForeignPtr Word8 -> Bool -> Picture bitmapDataOfForeignPtr :: Int -> Int -> BitmapFormat -> ForeignPtr Word8 -> Bool -> BitmapData -- | 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. bitmapOfByteString :: Int -> Int -> BitmapFormat -> ByteString -> Bool -> Picture bitmapDataOfByteString :: Int -> Int -> BitmapFormat -> ByteString -> Bool -> BitmapData -- | O(size). Copy a BMP file into a bitmap. bitmapOfBMP :: BMP -> Picture -- | O(size). Copy a BMP file into a bitmap. bitmapDataOfBMP :: BMP -> BitmapData -- | Load an uncompressed 24 or 32bit RGBA BMP file as a bitmap. loadBMP :: FilePath -> IO Picture -- | Predefined and custom colors. module Graphics.Gloss.Data.Color -- | 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. data Color -- | Make a custom color. All components are clamped to the range [0..1]. makeColor :: Float -> Float -> Float -> Float -> Color -- | Make a custom color. All components are clamped to the range [0..255]. makeColorI :: Int -> Int -> Int -> Int -> Color -- | Take the RGBA components of a color. rgbaOfColor :: Color -> (Float, Float, Float, Float) -- | Mix two colors with the given ratios. mixColors :: Float -> Float -> Color -> Color -> Color -- | Add RGB components of a color component-wise, then normalise them to -- the highest resulting one. The alpha components are averaged. addColors :: Color -> Color -> Color -- | Make a dimmer version of a color, scaling towards black. dim :: Color -> Color -- | Make a brighter version of a color, scaling towards white. bright :: Color -> Color -- | Lighten a color, adding white. light :: Color -> Color -- | Darken a color, adding black. dark :: Color -> Color -- | Set the red value of a Color. withRed :: Float -> Color -> Color -- | Set the green value of a Color. withGreen :: Float -> Color -> Color -- | Set the blue value of a Color. withBlue :: Float -> Color -> Color -- | Set the alpha value of a Color. withAlpha :: Float -> Color -> Color -- | A greyness of a given order. -- -- Range is 0 = black, to 1 = white. greyN :: Float -> Color black :: Color white :: Color red :: Color green :: Color blue :: Color yellow :: Color cyan :: Color magenta :: Color rose :: Color violet :: Color azure :: Color aquamarine :: Color chartreuse :: Color orange :: Color module Graphics.Gloss.Data.Display -- | Describes how Gloss should display its output. data Display -- | Display in a window with the given name, size and position. InWindow :: String -> (Int, Int) -> (Int, Int) -> Display -- | Display full screen. FullScreen :: Display instance GHC.Show.Show Graphics.Gloss.Data.Display.Display instance GHC.Read.Read Graphics.Gloss.Data.Display.Display instance GHC.Classes.Eq Graphics.Gloss.Data.Display.Display -- |

Point and vector arithmetic

-- -- Vectors aren't numbers according to Haskell, because they don't -- support all numeric operations sensibly. We define component-wise -- addition, subtraction, and negation along with scalar multiplication -- in this module, which is intended to be imported qualified. module Graphics.Gloss.Data.Point.Arithmetic -- | A point on the x-y plane. type Point = (Float, Float) -- | Add two vectors, or add a vector to a point. (+) :: Point -> Point -> Point infixl 6 + -- | Subtract two vectors, or subtract a vector from a point. (-) :: Point -> Point -> Point infixl 6 - -- | Multiply a scalar by a vector. (*) :: Float -> Point -> Point infixl 7 * -- | Negate a vector. negate :: Point -> Point -- | Geometric functions concerning angles. If not otherwise specified, all -- angles are in radians. module Graphics.Gloss.Geometry.Angle -- | Convert degrees to radians degToRad :: Float -> Float -- | Convert radians to degrees radToDeg :: Float -> Float -- | Normalize an angle to be between 0 and 2*pi radians normalizeAngle :: Float -> Float module Graphics.Gloss.Data.Picture -- | A 2D picture data Picture -- | A blank picture, with nothing in it. Blank :: Picture -- | A convex polygon filled with a solid color. Polygon :: Path -> Picture -- | A line along an arbitrary path. Line :: Path -> Picture -- | A circle with the given radius. Circle :: Float -> Picture -- | A circle with the given radius and thickness. If the thickness is 0 -- then this is equivalent to Circle. ThickCircle :: Float -> Float -> Picture -- | A circular arc drawn counter-clockwise between two angles (in degrees) -- at the given radius. Arc :: Float -> Float -> Float -> Picture -- | 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. ThickArc :: Float -> Float -> Float -> Float -> Picture -- | Some text to draw with a vector font. Text :: String -> Picture -- | A bitmap image. Bitmap :: BitmapData -> Picture -- | A subsection of a bitmap image where the first argument selects a sub -- section in the bitmap, and second argument determines the bitmap data. BitmapSection :: Rectangle -> BitmapData -> Picture -- | A picture drawn with this color. Color :: Color -> Picture -> Picture -- | A picture translated by the given x and y coordinates. Translate :: Float -> Float -> Picture -> Picture -- | A picture rotated clockwise by the given angle (in degrees). Rotate :: Float -> Picture -> Picture -- | A picture scaled by the given x and y factors. Scale :: Float -> Float -> Picture -> Picture -- | A picture consisting of several others. Pictures :: [Picture] -> Picture -- | A point on the x-y plane. type Point = (Float, Float) -- | A vector can be treated as a point, and vis-versa. type Vector = Point -- | A path through the x-y plane. type Path = [Point] -- | A blank picture, with nothing in it. blank :: Picture -- | A convex polygon filled with a solid color. polygon :: Path -> Picture -- | A line along an arbitrary path. line :: Path -> Picture -- | A circle with the given radius. circle :: Float -> Picture -- | A circle with the given thickness and radius. If the thickness is 0 -- then this is equivalent to Circle. thickCircle :: Float -> Float -> Picture -- | A circular arc drawn counter-clockwise between two angles (in degrees) -- at the given radius. arc :: Float -> Float -> Float -> Picture -- | 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. thickArc :: Float -> Float -> Float -> Float -> Picture -- | Some text to draw with a vector font. text :: String -> Picture -- | A bitmap image bitmap :: BitmapData -> Picture -- | a subsection of a bitmap image first argument selects a sub section in -- the bitmap second argument determines the bitmap data bitmapSection :: Rectangle -> BitmapData -> Picture -- | A picture drawn with this color. color :: Color -> Picture -> Picture -- | A picture translated by the given x and y coordinates. translate :: Float -> Float -> Picture -> Picture -- | A picture rotated clockwise by the given angle (in degrees). rotate :: Float -> Picture -> Picture -- | A picture scaled by the given x and y factors. scale :: Float -> Float -> Picture -> Picture -- | A picture consisting of several others. pictures :: [Picture] -> Picture -- | A closed loop along a path. lineLoop :: Path -> Picture -- | A solid circle with the given radius. circleSolid :: Float -> Picture -- | A solid arc, drawn counter-clockwise between two angles (in degrees) -- at the given radius. arcSolid :: Float -> Float -> Float -> Picture -- | A wireframe sector of a circle. An arc is draw counter-clockwise from -- the first to the second angle (in degrees) at the given radius. Lines -- are drawn from the origin to the ends of the arc. sectorWire :: Float -> Float -> Float -> Picture -- | A path representing a rectangle centered about the origin rectanglePath :: Float -> Float -> Path -- | A wireframe rectangle centered about the origin. rectangleWire :: Float -> Float -> Picture -- | A solid rectangle centered about the origin. rectangleSolid :: Float -> Float -> Picture -- | A path representing a rectangle in the y > 0 half of the x-y plane. rectangleUpperPath :: Float -> Float -> Path -- | A wireframe rectangle in the y > 0 half of the x-y plane. rectangleUpperWire :: Float -> Float -> Picture -- | A solid rectangle in the y > 0 half of the x-y plane. rectangleUpperSolid :: Float -> Float -> Picture module Graphics.Gloss.Data.ViewPort -- | The ViewPort represents the global transformation applied to -- the displayed picture. When the user pans, zooms, or rotates the -- display then this changes the ViewPort. data ViewPort ViewPort :: !(Float, Float) -> !Float -> !Float -> ViewPort -- | Global translation. [viewPortTranslate] :: ViewPort -> !(Float, Float) -- | Global rotation (in degrees). [viewPortRotate] :: ViewPort -> !Float -- | Global scaling (of both x and y coordinates). [viewPortScale] :: ViewPort -> !Float -- | The initial state of the viewport. viewPortInit :: ViewPort -- | Translates, rotates, and scales an image according to the -- ViewPort. applyViewPortToPicture :: ViewPort -> Picture -> Picture -- | Takes a point using screen coordinates, and uses the ViewPort -- to convert it to Picture coordinates. This is the inverse of -- applyViewPortToPicture for points. invertViewPort :: ViewPort -> Point -> Point module Graphics.Gloss.Data.Controller -- | Functions to asynchronously control a Gloss display. data Controller Controller :: IO () -> ((ViewPort -> IO ViewPort) -> IO ()) -> Controller -- | Indicate that we want the picture to be redrawn. [controllerSetRedraw] :: Controller -> IO () -- | Modify the current viewport, also indicating that it should be -- redrawn. [controllerModifyViewPort] :: Controller -> (ViewPort -> IO ViewPort) -> IO () -- | Geometric functions concerning vectors. module Graphics.Gloss.Data.Vector -- | A vector can be treated as a point, and vis-versa. type Vector = Point -- | The magnitude of a vector. magV :: Vector -> Float -- | The angle of this vector, relative to the +ve x-axis. argV :: Vector -> Float -- | The dot product of two vectors. dotV :: Vector -> Vector -> Float -- | The determinant of two vectors. detV :: Vector -> Vector -> Float -- | Multiply a vector by a scalar. mulSV :: Float -> Vector -> Vector -- | Rotate a vector by an angle (in radians). +ve angle is -- counter-clockwise. rotateV :: Float -> Vector -> Vector -- | Compute the inner angle (in radians) between two vectors. angleVV :: Vector -> Vector -> Float -- | Normalise a vector, so it has a magnitude of 1. normalizeV :: Vector -> Vector -- | Produce a unit vector at a given angle relative to the +ve x-axis. The -- provided angle is in radians. unitVectorAtAngle :: Float -> Vector module Graphics.Gloss.Data.Point -- | A point on the x-y plane. type Point = (Float, Float) -- | A path through the x-y plane. type Path = [Point] -- | Test whether a point lies within a rectangular box that is oriented on -- the x-y plane. The points P1-P2 are opposing points of the box, but -- need not be in a particular order. -- --
--   P2 +-------+
--      |       |
--      | + P0  |
--      |       |
--      +-------+ P1
--   
pointInBox :: Point -> Point -> Point -> Bool -- | Geometric functions concerning lines and segments. -- -- A Line is taken to be infinite in length, while a -- Seg is finite length line segment represented by its two -- endpoints. module Graphics.Gloss.Geometry.Line -- | Check if line segment (P1-P2) clears a box (P3-P4) by being well -- outside it. segClearsBox :: Point -> Point -> Point -> Point -> Bool -- | Given an infinite line which intersects P1 and P1, -- return the point on that line that is closest to P3 closestPointOnLine :: Point -> Point -> Point -> Point -- | Given an infinite line which intersects P1 and P2, let P4 be the point -- on the line that is closest to P3. -- -- Return an indication of where on the line P4 is relative to P1 and P2. -- --
--   if P4 == P1 then 0
--   if P4 == P2 then 1
--   if P4 is halfway between P1 and P2 then 0.5
--   
-- --
--      |
--     P1
--      |
--   P4 +---- P3
--      |
--     P2
--      |
--   
closestPointOnLineParam :: Point -> Point -> Point -> Float -- | Given four points specifying two lines, get the point where the two -- lines cross, if any. Note that the lines extend off to infinity, so -- the intersection point might not line between either of the two pairs -- of points. -- --
--   \      /
--    P1  P4
--     \ /
--      +
--     / \
--    P3  P2
--   /     \
--   
intersectLineLine :: Point -> Point -> Point -> Point -> Maybe Point -- | Get the point where a segment P1-P2 crosses an infinite line -- P3-P4, if any. intersectSegLine :: Point -> Point -> Point -> Point -> Maybe Point -- | Get the point where a segment crosses a horizontal line, if any. -- --
--            + P1
--           /
--   -------+---------
--         /        y0
--     P2 +
--   
intersectSegHorzLine :: Point -> Point -> Float -> Maybe Point -- | Get the point where a segment crosses a vertical line, if any. -- --
--          |
--          |   + P1
--          | /
--          +
--        / |
--   P2 +   |
--          | x0
--   
intersectSegVertLine :: Point -> Point -> Float -> Maybe Point -- | Get the point where a segment P1-P2 crosses another segement -- P3-P4, if any. intersectSegSeg :: Point -> Point -> Point -> Point -> Maybe Point -- | Check if an arbitrary segment intersects a horizontal segment. -- --
--                   + P2
--                  /
--   (xa, y3)  +---+----+ (xb, y3)
--                /
--            P1 +
--   
intersectSegHorzSeg :: Point -> Point -> Float -> Float -> Float -> Maybe Point -- | Check if an arbitrary segment intersects a vertical segment. -- --
--   (x3, yb) +
--            |   + P1
--            | /
--            +
--          / |
--     P2 +   |
--            + (x3, ya)
--   
intersectSegVertSeg :: Point -> Point -> Float -> Float -> Float -> Maybe Point module Graphics.Gloss.Interface.Environment -- | Get the size of the screen, in pixels. -- -- This will be the size of the rendered gloss image when fullscreen mode -- is enabled. getScreenSize :: IO (Int, Int) module Graphics.Gloss.Data.ViewState -- | The commands suported by the view controller. data Command CRestore :: Command CTranslate :: Command CRotate :: Command CScale :: Command CBumpZoomOut :: Command CBumpZoomIn :: Command CBumpLeft :: Command CBumpRight :: Command CBumpUp :: Command CBumpDown :: Command CBumpClockwise :: Command CBumpCClockwise :: Command type CommandConfig = [(Command, [(Key, Maybe Modifiers)])] -- | The default commands. Left click pans, wheel zooms, right click -- rotates, "r" key resets. defaultCommandConfig :: CommandConfig -- | State for controlling the viewport. These are used by the viewport -- control component. data ViewState ViewState :: !Map Command [(Key, Maybe Modifiers)] -> !Float -> !Float -> !Float -> !Maybe (Float, Float) -> !Maybe (Float, Float) -> !Maybe (Float, Float) -> ViewPort -> ViewState -- | The command list for the viewport controller. These can be safely -- overwridden at any time by deleting or adding entries to the list. -- Entries at the front of the list take precedence. [viewStateCommands] :: ViewState -> !Map Command [(Key, Maybe Modifiers)] -- | How much to scale the world by for each step of the mouse wheel. [viewStateScaleStep] :: ViewState -> !Float -- | How many degrees to rotate the world by for each pixel of x motion. [viewStateRotateFactor] :: ViewState -> !Float -- | Ratio to scale the world by for each pixel of y motion. [viewStateScaleFactor] :: ViewState -> !Float -- | During viewport translation, where the mouse was clicked on the window -- to start the translate. [viewStateTranslateMark] :: ViewState -> !Maybe (Float, Float) -- | During viewport rotation, where the mouse was clicked on the window to -- starte the rotate. [viewStateRotateMark] :: ViewState -> !Maybe (Float, Float) -- | During viewport scale, where the mouse was clicked on the window to -- start the scale. [viewStateScaleMark] :: ViewState -> !Maybe (Float, Float) -- | The current viewport. [viewStateViewPort] :: ViewState -> ViewPort -- | The initial view state. viewStateInit :: ViewState -- | Initial view state, with user defined config. viewStateInitWithConfig :: CommandConfig -> ViewState -- | Apply an event to a ViewState. updateViewStateWithEvent :: Event -> ViewState -> ViewState -- | Like updateViewStateWithEvent, but returns Nothing if no -- update was needed. updateViewStateWithEventMaybe :: Event -> ViewState -> Maybe ViewState instance GHC.Classes.Ord Graphics.Gloss.Data.ViewState.Command instance GHC.Classes.Eq Graphics.Gloss.Data.ViewState.Command instance GHC.Show.Show Graphics.Gloss.Data.ViewState.Command -- | Simulate mode is for producing an animation of some model who's -- picture changes over finite time steps. The behavior of the model can -- also depent on the current ViewPort. module Graphics.Gloss.Interface.Pure.Simulate -- | Run a finite-time-step simulation in a window. You decide how the -- model is represented, how to convert the model to a picture, and how -- to advance the model for each unit of time. This function does the -- rest. -- -- Once the window is open you can use the same commands as with -- display. simulate :: Display -> Color -> Int -> model -> (model -> Picture) -> (ViewPort -> Float -> model -> model) -> IO () -- | The ViewPort represents the global transformation applied to -- the displayed picture. When the user pans, zooms, or rotates the -- display then this changes the ViewPort. data ViewPort ViewPort :: !(Float, Float) -> !Float -> !Float -> ViewPort -- | Global translation. [viewPortTranslate] :: ViewPort -> !(Float, Float) -- | Global rotation (in degrees). [viewPortRotate] :: ViewPort -> !Float -- | Global scaling (of both x and y coordinates). [viewPortScale] :: ViewPort -> !Float -- | Simulate mode is for producing an animation of some model who's -- picture changes over finite time steps. The behavior of the model can -- also depent on the current ViewPort. module Graphics.Gloss.Interface.IO.Simulate simulateIO :: forall model. Display -> Color -> Int -> model -> (model -> IO Picture) -> (ViewPort -> Float -> model -> IO model) -> IO () -- | The ViewPort represents the global transformation applied to -- the displayed picture. When the user pans, zooms, or rotates the -- display then this changes the ViewPort. data ViewPort ViewPort :: !(Float, Float) -> !Float -> !Float -> ViewPort -- | Global translation. [viewPortTranslate] :: ViewPort -> !(Float, Float) -- | Global rotation (in degrees). [viewPortRotate] :: ViewPort -> !Float -- | Global scaling (of both x and y coordinates). [viewPortScale] :: ViewPort -> !Float -- | Display mode is for drawing a static picture. module Graphics.Gloss.Interface.IO.Interact -- | Open a new window and interact with an infrequently updated picture. -- -- Similar to displayIO, except that you manage your own events. interactIO :: Display -> Color -> world -> (world -> IO Picture) -> (Event -> world -> IO world) -> (Controller -> IO ()) -> IO () -- | Functions to asynchronously control a Gloss display. data Controller Controller :: IO () -> ((ViewPort -> IO ViewPort) -> IO ()) -> Controller -- | Indicate that we want the picture to be redrawn. [controllerSetRedraw] :: Controller -> IO () -- | Modify the current viewport, also indicating that it should be -- redrawn. [controllerModifyViewPort] :: Controller -> (ViewPort -> IO ViewPort) -> IO () -- | Possible input events. data Event EventKey :: Key -> KeyState -> Modifiers -> (Float, Float) -> Event EventMotion :: (Float, Float) -> Event EventResize :: (Int, Int) -> Event data Key Char :: Char -> Key SpecialKey :: SpecialKey -> Key MouseButton :: MouseButton -> Key data SpecialKey KeyUnknown :: SpecialKey KeySpace :: SpecialKey KeyEsc :: SpecialKey KeyF1 :: SpecialKey KeyF2 :: SpecialKey KeyF3 :: SpecialKey KeyF4 :: SpecialKey KeyF5 :: SpecialKey KeyF6 :: SpecialKey KeyF7 :: SpecialKey KeyF8 :: SpecialKey KeyF9 :: SpecialKey KeyF10 :: SpecialKey KeyF11 :: SpecialKey KeyF12 :: SpecialKey KeyF13 :: SpecialKey KeyF14 :: SpecialKey KeyF15 :: SpecialKey KeyF16 :: SpecialKey KeyF17 :: SpecialKey KeyF18 :: SpecialKey KeyF19 :: SpecialKey KeyF20 :: SpecialKey KeyF21 :: SpecialKey KeyF22 :: SpecialKey KeyF23 :: SpecialKey KeyF24 :: SpecialKey KeyF25 :: SpecialKey KeyUp :: SpecialKey KeyDown :: SpecialKey KeyLeft :: SpecialKey KeyRight :: SpecialKey KeyTab :: SpecialKey KeyEnter :: SpecialKey KeyBackspace :: SpecialKey KeyInsert :: SpecialKey KeyNumLock :: SpecialKey KeyBegin :: SpecialKey KeyDelete :: SpecialKey KeyPageUp :: SpecialKey KeyPageDown :: SpecialKey KeyHome :: SpecialKey KeyEnd :: SpecialKey KeyShiftL :: SpecialKey KeyShiftR :: SpecialKey KeyCtrlL :: SpecialKey KeyCtrlR :: SpecialKey KeyAltL :: SpecialKey KeyAltR :: SpecialKey KeyPad0 :: SpecialKey KeyPad1 :: SpecialKey KeyPad2 :: SpecialKey KeyPad3 :: SpecialKey KeyPad4 :: SpecialKey KeyPad5 :: SpecialKey KeyPad6 :: SpecialKey KeyPad7 :: SpecialKey KeyPad8 :: SpecialKey KeyPad9 :: SpecialKey KeyPadDivide :: SpecialKey KeyPadMultiply :: SpecialKey KeyPadSubtract :: SpecialKey KeyPadAdd :: SpecialKey KeyPadDecimal :: SpecialKey KeyPadEqual :: SpecialKey KeyPadEnter :: SpecialKey data MouseButton LeftButton :: MouseButton MiddleButton :: MouseButton RightButton :: MouseButton WheelUp :: MouseButton WheelDown :: MouseButton AdditionalButton :: Int -> MouseButton data KeyState Down :: KeyState Up :: KeyState data Modifiers Modifiers :: KeyState -> KeyState -> KeyState -> Modifiers [shift] :: Modifiers -> KeyState [ctrl] :: Modifiers -> KeyState [alt] :: Modifiers -> KeyState -- | This game mode lets you manage your own input. Pressing ESC will still -- abort the program, but you don't get automatic pan and zoom controls -- like with displayInWindow. module Graphics.Gloss.Interface.Pure.Game -- | Play a game in a window. Like simulate, but you manage your -- own input events. play :: Display -> Color -> Int -> world -> (world -> Picture) -> (Event -> world -> world) -> (Float -> world -> world) -> IO () -- | Possible input events. data Event EventKey :: Key -> KeyState -> Modifiers -> (Float, Float) -> Event EventMotion :: (Float, Float) -> Event EventResize :: (Int, Int) -> Event data Key Char :: Char -> Key SpecialKey :: SpecialKey -> Key MouseButton :: MouseButton -> Key data SpecialKey KeyUnknown :: SpecialKey KeySpace :: SpecialKey KeyEsc :: SpecialKey KeyF1 :: SpecialKey KeyF2 :: SpecialKey KeyF3 :: SpecialKey KeyF4 :: SpecialKey KeyF5 :: SpecialKey KeyF6 :: SpecialKey KeyF7 :: SpecialKey KeyF8 :: SpecialKey KeyF9 :: SpecialKey KeyF10 :: SpecialKey KeyF11 :: SpecialKey KeyF12 :: SpecialKey KeyF13 :: SpecialKey KeyF14 :: SpecialKey KeyF15 :: SpecialKey KeyF16 :: SpecialKey KeyF17 :: SpecialKey KeyF18 :: SpecialKey KeyF19 :: SpecialKey KeyF20 :: SpecialKey KeyF21 :: SpecialKey KeyF22 :: SpecialKey KeyF23 :: SpecialKey KeyF24 :: SpecialKey KeyF25 :: SpecialKey KeyUp :: SpecialKey KeyDown :: SpecialKey KeyLeft :: SpecialKey KeyRight :: SpecialKey KeyTab :: SpecialKey KeyEnter :: SpecialKey KeyBackspace :: SpecialKey KeyInsert :: SpecialKey KeyNumLock :: SpecialKey KeyBegin :: SpecialKey KeyDelete :: SpecialKey KeyPageUp :: SpecialKey KeyPageDown :: SpecialKey KeyHome :: SpecialKey KeyEnd :: SpecialKey KeyShiftL :: SpecialKey KeyShiftR :: SpecialKey KeyCtrlL :: SpecialKey KeyCtrlR :: SpecialKey KeyAltL :: SpecialKey KeyAltR :: SpecialKey KeyPad0 :: SpecialKey KeyPad1 :: SpecialKey KeyPad2 :: SpecialKey KeyPad3 :: SpecialKey KeyPad4 :: SpecialKey KeyPad5 :: SpecialKey KeyPad6 :: SpecialKey KeyPad7 :: SpecialKey KeyPad8 :: SpecialKey KeyPad9 :: SpecialKey KeyPadDivide :: SpecialKey KeyPadMultiply :: SpecialKey KeyPadSubtract :: SpecialKey KeyPadAdd :: SpecialKey KeyPadDecimal :: SpecialKey KeyPadEqual :: SpecialKey KeyPadEnter :: SpecialKey data MouseButton LeftButton :: MouseButton MiddleButton :: MouseButton RightButton :: MouseButton WheelUp :: MouseButton WheelDown :: MouseButton AdditionalButton :: Int -> MouseButton data KeyState Down :: KeyState Up :: KeyState data Modifiers Modifiers :: KeyState -> KeyState -> KeyState -> Modifiers [shift] :: Modifiers -> KeyState [ctrl] :: Modifiers -> KeyState [alt] :: Modifiers -> KeyState -- | This game mode lets you manage your own input. Pressing ESC will not -- abort the program. You also don't get automatic pan and zoom controls -- like with display. module Graphics.Gloss.Interface.IO.Game -- | Play a game in a window, using IO actions to build the pictures. playIO :: forall world. Display -> Color -> Int -> world -> (world -> IO Picture) -> (Event -> world -> IO world) -> (Float -> world -> IO world) -> IO () -- | Possible input events. data Event EventKey :: Key -> KeyState -> Modifiers -> (Float, Float) -> Event EventMotion :: (Float, Float) -> Event EventResize :: (Int, Int) -> Event data Key Char :: Char -> Key SpecialKey :: SpecialKey -> Key MouseButton :: MouseButton -> Key data SpecialKey KeyUnknown :: SpecialKey KeySpace :: SpecialKey KeyEsc :: SpecialKey KeyF1 :: SpecialKey KeyF2 :: SpecialKey KeyF3 :: SpecialKey KeyF4 :: SpecialKey KeyF5 :: SpecialKey KeyF6 :: SpecialKey KeyF7 :: SpecialKey KeyF8 :: SpecialKey KeyF9 :: SpecialKey KeyF10 :: SpecialKey KeyF11 :: SpecialKey KeyF12 :: SpecialKey KeyF13 :: SpecialKey KeyF14 :: SpecialKey KeyF15 :: SpecialKey KeyF16 :: SpecialKey KeyF17 :: SpecialKey KeyF18 :: SpecialKey KeyF19 :: SpecialKey KeyF20 :: SpecialKey KeyF21 :: SpecialKey KeyF22 :: SpecialKey KeyF23 :: SpecialKey KeyF24 :: SpecialKey KeyF25 :: SpecialKey KeyUp :: SpecialKey KeyDown :: SpecialKey KeyLeft :: SpecialKey KeyRight :: SpecialKey KeyTab :: SpecialKey KeyEnter :: SpecialKey KeyBackspace :: SpecialKey KeyInsert :: SpecialKey KeyNumLock :: SpecialKey KeyBegin :: SpecialKey KeyDelete :: SpecialKey KeyPageUp :: SpecialKey KeyPageDown :: SpecialKey KeyHome :: SpecialKey KeyEnd :: SpecialKey KeyShiftL :: SpecialKey KeyShiftR :: SpecialKey KeyCtrlL :: SpecialKey KeyCtrlR :: SpecialKey KeyAltL :: SpecialKey KeyAltR :: SpecialKey KeyPad0 :: SpecialKey KeyPad1 :: SpecialKey KeyPad2 :: SpecialKey KeyPad3 :: SpecialKey KeyPad4 :: SpecialKey KeyPad5 :: SpecialKey KeyPad6 :: SpecialKey KeyPad7 :: SpecialKey KeyPad8 :: SpecialKey KeyPad9 :: SpecialKey KeyPadDivide :: SpecialKey KeyPadMultiply :: SpecialKey KeyPadSubtract :: SpecialKey KeyPadAdd :: SpecialKey KeyPadDecimal :: SpecialKey KeyPadEqual :: SpecialKey KeyPadEnter :: SpecialKey data MouseButton LeftButton :: MouseButton MiddleButton :: MouseButton RightButton :: MouseButton WheelUp :: MouseButton WheelDown :: MouseButton AdditionalButton :: Int -> MouseButton data KeyState Down :: KeyState Up :: KeyState data Modifiers Modifiers :: KeyState -> KeyState -> KeyState -> Modifiers [shift] :: Modifiers -> KeyState [ctrl] :: Modifiers -> KeyState [alt] :: Modifiers -> KeyState -- | Display mode is for drawing a static picture. module Graphics.Gloss.Interface.Pure.Display -- | Open a new window and display the given picture. display :: Display -> Color -> Picture -> IO () -- | Display mode is for drawing a static picture. module Graphics.Gloss.Interface.IO.Display -- | Open a new window and display an infrequently updated picture. -- -- Once the window is open you can use the same commands as with -- display. -- -- displayIO :: Display -> Color -> IO Picture -> (Controller -> IO ()) -> IO () -- | Functions to asynchronously control a Gloss display. data Controller Controller :: IO () -> ((ViewPort -> IO ViewPort) -> IO ()) -> Controller -- | Indicate that we want the picture to be redrawn. [controllerSetRedraw] :: Controller -> IO () -- | Modify the current viewport, also indicating that it should be -- redrawn. [controllerModifyViewPort] :: Controller -> (ViewPort -> IO ViewPort) -> IO () -- | Display mode is for drawing a static picture. module Graphics.Gloss.Interface.Pure.Animate -- | Open a new window and display the given animation. -- -- Once the window is open you can use the same commands as with -- display. animate :: Display -> Color -> (Float -> Picture) -> IO () -- | Gloss hides the pain of drawing simple vector graphics behind a nice -- data type and a few display functions. -- -- Getting something on the screen is as easy as: -- --
--   import Graphics.Gloss
--   main = display (InWindow "Nice Window" (200, 200) (10, 10)) white (Circle 80)
--   
--   
-- -- Once the window is open you can use the following: -- --
--   * Quit
--     - esc-key
--   
--   * Move Viewport
--     - arrow keys
--     - left-click drag
--   
--   * Zoom Viewport
--     - page up/down-keys
--     - control-left-click drag
--     - right-click drag
--     - mouse wheel
--   
--   * Rotate Viewport
--     - home/end-keys
--     - alt-left-click drag
--   
--   * Reset Viewport
--     r-key
--   
-- -- Animations can be constructed similarly using the animate. -- -- If you want to run a simulation based around finite time steps then -- try simulate. -- -- If you want to manage your own key/mouse events then use play. -- -- Gloss uses OpenGL under the hood, but you don't have to worry about -- any of that. -- -- Gloss programs should be compiled with -threaded, otherwise -- the GHC runtime will limit the frame-rate to around 20Hz. -- -- To build gloss using the GLFW window manager instead of GLUT use -- cabal install gloss --flags="GLFW -GLUT" -- --
--   Release Notes:
--   
--    For 1.13.1:
--     Thanks to Thaler Jonathan
--     * Repaired GLFW backend.
--     Thanks to Samuel Gfrörer
--     * Support for bitmap sections.
--     Thanks to Basile Henry
--     * Handle resize events in playField driver.
--   
--    For 1.12.1:
--     Thanks to Trevor McDonell
--     * Travis CI integration, general cleanups.
--   
--    For 1.11.1:
--     Thanks to Lars Wyssard
--     * Use default display resolution in full-screen mode.
--   
--    For 1.10.1:
--     * Gloss no longer consumes CPU time when displaying static pictures.
--     * Added displayIO wrapper for mostly static pictures, eg when
--       plotting graphs generated from infrequently updated files.
--     * Allow viewport to be scaled with control-left-click drag.
--     * Rotation of viewport changed to alt-left-click drag.
--     * Preserve current colour when rendering bitmpaps.
--     * Changed to proper sum-of-squares colour mixing, rather than naive
--       addition of components which was causing mixed colours to be too dark.
--    Thanks to Thomas DuBuisson
--     * Allow bitmaps to be specified in RGBA byte order as well as ABGR.
--    Thanks to Gabriel Gonzalez
--     * Package definitions for building with Stack.
--   
-- -- For more information, check out http://gloss.ouroborus.net. module Graphics.Gloss -- | Describes how Gloss should display its output. data Display -- | Display in a window with the given name, size and position. InWindow :: String -> (Int, Int) -> (Int, Int) -> Display -- | Display full screen. FullScreen :: Display -- | Open a new window and display the given picture. display :: Display -> Color -> Picture -> IO () -- | Open a new window and display the given animation. -- -- Once the window is open you can use the same commands as with -- display. animate :: Display -> Color -> (Float -> Picture) -> IO () -- | Run a finite-time-step simulation in a window. You decide how the -- model is represented, how to convert the model to a picture, and how -- to advance the model for each unit of time. This function does the -- rest. -- -- Once the window is open you can use the same commands as with -- display. simulate :: Display -> Color -> Int -> model -> (model -> Picture) -> (ViewPort -> Float -> model -> model) -> IO () -- | Play a game in a window. Like simulate, but you manage your -- own input events. play :: Display -> Color -> Int -> world -> (world -> Picture) -> (Event -> world -> world) -> (Float -> world -> world) -> IO () -- | Animate a picture in a window. module Graphics.Gloss.Interface.IO.Animate -- | Open a new window and display the given animation. -- -- Once the window is open you can use the same commands as with -- display. animateIO :: Display -> Color -> (Float -> IO Picture) -> (Controller -> IO ()) -> IO () -- | Like animateIO but don't allow the display to be panned around. animateFixedIO :: Display -> Color -> (Float -> IO Picture) -> (Controller -> IO ()) -> IO () -- | Functions to asynchronously control a Gloss display. data Controller Controller :: IO () -> ((ViewPort -> IO ViewPort) -> IO ()) -> Controller -- | Indicate that we want the picture to be redrawn. [controllerSetRedraw] :: Controller -> IO () -- | Modify the current viewport, also indicating that it should be -- redrawn. [controllerModifyViewPort] :: Controller -> (ViewPort -> IO ViewPort) -> IO ()