view release on metacpan or search on metacpan
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT.hs view on Meta::CPAN
-- * Sophisticated input devices.
--
-- * An /idle/ routine and timers.
--
-- * A simple, cascading pop-up menu facility.
--
-- * Utility routines to generate various solid and wire frame objects.
--
-- * Support for bitmap and stroke fonts.
--
-- * Miscellaneous window management functions, including managing overlays.
--
-- This documentation serves as both a specification and a programming guide.
-- If you are interested in a brief introduction to programming with GLUT,
-- have a look at the relevant parts of <http://www.opengl.org/> and the vast
-- amount of books on OpenGL, most of them use GLUT.
--
-- The remainder of this section describes GLUT\'s design philosophy and
-- usage model. The following sections specify the GLUT routines, grouped by
-- functionality. The final sections discuss usage advice and the logical
-- programmer visible state maintained by GLUT.
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT.hs view on Meta::CPAN
-- to the native window system. And when an OpenGL program is written using the
-- native window system interface, despite the portability of the program\'s
-- OpenGL rendering code, the program itself will be window system dependent.
--
-- Testing and documenting OpenGL\'s functionality lead to the development of
-- the @tk@ and @aux@ toolkits. The @aux@ toolkit is used in the examples found
-- in the /OpenGL Programming Guide/. Unfortunately, @aux@ has numerous
-- limitations and its utility is largely limited to toy programs. The @tk@
-- library has more functionality than @aux@ but was developed in an /ad hoc/
-- fashion and still lacks much important functionality that IRIS GL programmers
-- expect, like pop-up menus and overlays.
--
-- GLUT is designed to fill the need for a window system independent programming
-- interface for OpenGL programs. The interface is designed to be simple yet
-- still meet the needs of useful OpenGL programs. Features from the IRIS GL,
-- @aux@, and @tk@ interfaces are included to make it easy for programmers used
-- to these interfaces to develop programs for GLUT.
-----------------------------------------------------------------------------
-- $DesignPhilosophy
-- GLUT simplifies the implementation of programs using OpenGL rendering. The
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT.hs view on Meta::CPAN
--
-- * /Initialization:/ Command line processing, window system initialization,
-- and initial window creation state are controlled by these routines.
--
-- * /Beginning Event Processing:/ This routine enters GLUT\'s event processing
-- loop. This routine never returns, and it continuously calls GLUT callbacks
-- as necessary.
--
-- * /Window Management:/ These routines create and control windows.
--
-- * /Overlay Management:/ These routines establish and manage overlays for
-- windows.
--
-- * /Menu Management:/ These routines create and control pop-up menus.
--
-- * /Callback Registration:/ These routines register callbacks to be called by
-- the GLUT event processing loop.
--
-- * /Color Index Colormap Management:/ These routines allow the manipulation
-- of color index colormaps for windows.
--
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT.hs view on Meta::CPAN
-- * /Dials and button box:/ A sophisticated input device consisting of a pad
-- of buttons and an array of rotating dials, often used by computer-aided
-- design programs.
--
-- * /Display mode:/ A set of OpenGL frame buffer capabilities that can be
-- attributed to a window.
--
-- * /Idle:/ A state when no window system events are received for processing
-- as callbacks and the idle callback, if one is registered, is called.
--
-- * /Layer in use:/ Either the normal plane or overlay. This per-window state
-- determines what frame buffer layer OpenGL commands affect.
--
-- * /Menu entry:/ A menu item that the user can select to trigger the menu
-- callback for the menu entry\'s value.
--
-- * /Menu item:/ Either a menu entry or a sub-menu trigger.
--
-- * /Modifiers:/ The Shift, Ctrl, and Alt keys that can be held down
-- simultaneously with a key or mouse button being pressed or released.
--
-- * /Multisampling:/ A technique for hardware antialiasing generally available
-- only on expensive 3D graphics hardware. Each pixel is composed of a number
-- of samples (each containing color and depth information). The samples are
-- averaged to determine the displayed pixel color value. Multisampling is
-- supported as an extension to OpenGL.
--
-- * /Normal plane:/ The default frame buffer layer where GLUT window state
-- resides; as opposed to the /overlay/.
--
-- * /Overlay:/ A frame buffer layer that can be displayed preferentially to
-- the /normal plane/ and supports transparency to display through to the
-- /normal plane/. Overlays are useful for rubber-banding effects, text
-- annotation, and other operations, to avoid damaging the normal plane frame
-- buffer state. Overlays require hardware support not present on all systems.
--
-- * /Pop:/ The act of forcing a window to the top of the stacking order for
-- sibling windows.
--
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Callbacks/Window.hs view on Meta::CPAN
-- License : BSD-style (see the file libraries/GLUT/LICENSE)
--
-- Maintainer : sven_panne@yahoo.com
-- Stability : provisional
-- Portability : portable
--
--------------------------------------------------------------------------------
module Graphics.UI.GLUT.Callbacks.Window (
-- * Redisplay callbacks
DisplayCallback, displayCallback, overlayDisplayCallback,
-- * Reshape callback
ReshapeCallback, reshapeCallback,
-- * Callback for visibility changes
Visibility(..), VisibilityCallback, visibilityCallback,
-- * Keyboard and mouse input callback
Key(..), SpecialKey(..), MouseButton(..), KeyState(..), Modifiers(..),
KeyboardMouseCallback, keyboardMouseCallback,
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Callbacks/Window.hs view on Meta::CPAN
--------------------------------------------------------------------------------
-- | A display callback
type DisplayCallback = IO ()
-- | Controls the display callback for the /current window./ When GLUT determines
-- that the normal plane for the window needs to be redisplayed, the display
-- callback for the window is called. Before the callback, the /current window/
-- is set to the window needing to be redisplayed and (if no overlay display
-- callback is registered) the /layer in use/ is set to the normal plane. The
-- entire normal plane region should be redisplayed in response to the callback
-- (this includes ancillary buffers if your program depends on their state).
--
-- GLUT determines when the display callback should be triggered based on the
-- window\'s redisplay state. The redisplay state for a window can be either set
-- explicitly by calling 'Graphics.UI.GLUT.Window.postRedisplay' or implicitly
-- as the result of window damage reported by the window system. Multiple posted
-- redisplays for a window are coalesced by GLUT to minimize the number of
-- display callbacks called.
--
-- When an overlay is established for a window, but there is no overlay display
-- callback registered, the display callback is used for redisplaying both the
-- overlay and normal plane (that is, it will be called if either the redisplay
-- state or overlay redisplay state is set). In this case, the /layer in use/ is
-- not implicitly changed on entry to the display callback.
--
-- See 'overlayDisplayCallback' to understand how distinct callbacks for the
-- overlay and normal plane of a window may be established.
--
-- When a window is created, no display callback exists for the window. It is
-- the responsibility of the programmer to install a display callback for the
-- window before the window is shown. A display callback must be registered for
-- any window that is shown. If a window becomes displayed without a display
-- callback being registered, a fatal error occurs. There is no way to
-- \"deregister\" a display callback (though another callback routine can always
-- be registered).
--
-- Upon return from the display callback, the normal damaged state of the window
-- (see 'Graphics.UI.GLUT.State.damaged') is cleared. If there is no overlay
-- display callback registered the overlay damaged state of the window (see
-- 'Graphics.UI.GLUT.State.damaged') is also cleared.
displayCallback :: SettableStateVar DisplayCallback
displayCallback = makeSettableStateVar $
setCallback DisplayCB glutDisplayFunc makeDisplayCallback . Just
foreign import ccall "wrapper" makeDisplayCallback ::
DisplayCallback -> IO (FunPtr DisplayCallback)
foreign import CALLCONV unsafe "glutDisplayFunc" glutDisplayFunc ::
FunPtr DisplayCallback -> IO ()
--------------------------------------------------------------------------------
-- | Controls the overlay display callback for the /current window./ The overlay
-- display callback is functionally the same as the window\'s display callback
-- except that the overlay display callback is used to redisplay the window\'s
-- overlay.
--
-- When GLUT determines that the overlay plane for the window needs to be
-- redisplayed, the overlay display callback for the window is called. Before
-- the callback, the /current window/ is set to the window needing to be
-- redisplayed and the /layer in use/ is set to the overlay. The entire overlay
-- region should be redisplayed in response to the callback (this includes
-- ancillary buffers if your program depends on their state).
--
-- GLUT determines when the overlay display callback should be triggered based
-- on the window\'s overlay redisplay state. The overlay redisplay state for a
-- window can be either set explicitly by calling
-- 'Graphics.UI.GLUT.Overlay.postOverlayRedisplay' or implicitly as the result
-- of window damage reported by the window system. Multiple posted overlay
-- redisplays for a window are coalesced by GLUT to minimize the number of
-- overlay display callbacks called.
--
-- Upon return from the overlay display callback, the overlay damaged state of
-- the window (see 'Graphics.UI.GLUT.State.damaged') is cleared.
--
-- Initially there is no overlay display callback registered when an overlay is
-- established. See 'displayCallback' to understand how the display callback
-- alone is used if an overlay display callback is not registered.
overlayDisplayCallback :: SettableStateVar (Maybe DisplayCallback)
overlayDisplayCallback = makeSettableStateVar $
setCallback OverlayDisplayCB glutOverlayDisplayFunc makeDisplayCallback
foreign import CALLCONV unsafe "glutOverlayDisplayFunc" glutOverlayDisplayFunc
:: FunPtr DisplayCallback -> IO ()
--------------------------------------------------------------------------------
-- | A reshape callback
type ReshapeCallback = Size -> IO ()
type ReshapeCallback' = CInt -> CInt -> IO ()
-- | Controls the reshape callback for the /current window./ The reshape callback
-- is triggered when a window is reshaped. A reshape callback is also triggered
-- immediately before a window\'s first display callback after a window is
-- created or whenever an overlay for the window is established. The parameter
-- of the callback specifies the new window size in pixels. Before the callback,
-- the /current window/ is set to the window that has been reshaped.
--
-- If a reshape callback is not registered for a window or 'reshapeCallback' is
-- set to 'Nothing' (to deregister a previously registered callback), the
-- default reshape callback is used. This default callback will simply call
--
-- @
-- 'viewport' ('Graphics.Rendering.OpenGL.GL.CoordTrans.Position' 0 0) ('Graphics.Rendering.OpenGL.GL.CoordTrans.Size' /width/ /height/)
-- @
--
-- on the normal plane (and on the overlay if one exists).
--
-- If an overlay is established for the window, a single reshape callback is
-- generated. It is the callback\'s responsibility to update both the normal
-- plane and overlay for the window (changing the layer in use as necessary).
--
-- When a top-level window is reshaped, subwindows are not reshaped. It is up to
-- the GLUT program to manage the size and positions of subwindows within a
-- top-level window. Still, reshape callbacks will be triggered for subwindows
-- when their size is changed using 'Graphics.UI.GLUT.Window.windowSize'.
reshapeCallback :: SettableStateVar (Maybe ReshapeCallback)
reshapeCallback = makeSettableStateVar $
setCallback ReshapeCB glutReshapeFunc (makeReshapeCallback . unmarshal)
where unmarshal cb w h = cb (Size (fromIntegral w) (fromIntegral h))
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Colormap.hs view on Meta::CPAN
glut_WINDOW_COLORMAP_SIZE, glut_TRANSPARENT_INDEX )
import Graphics.UI.GLUT.QueryUtils ( simpleGet, layerGet )
import Graphics.UI.GLUT.Window ( Window )
--------------------------------------------------------------------------------
-- | Controls the color index colormap entry of the /current window/\'s logical
-- colormap for the /layer in use/. The /layer in use/ of the /current window/
-- should be a color index window. The color index should be zero or greater and
-- less than the total number of colormap entries for the window (see
-- 'numColorMapEntries') and different from an overlay\'s transparent index (see
-- 'transparentIndex').
--
-- If the /layer in use/\'s colormap was copied by reference, setting a colormap
-- entry will force the duplication of the colormap.
colorMapEntry :: Index1 GLint -> StateVar (Color3 GLfloat)
colorMapEntry (Index1 cell) =
makeStateVar (getColorMapEntry (fromIntegral cell))
(setColorMapEntry (fromIntegral cell))
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Colormap.hs view on Meta::CPAN
b <- glutGetColor cell glut_BLUE
return $ Color3 r g b
foreign import CALLCONV unsafe "glutGetColor" glutGetColor ::
CInt -> CInt -> IO GLfloat
--------------------------------------------------------------------------------
-- | Copy (lazily if possible to promote sharing) the logical colormap from a
-- specified window to the /current window/\'s /layer in use/. The copy will be
-- from the normal plane to the normal plane; or from the overlay to the overlay
-- (never across different layers). Once a colormap has been copied, avoid
-- setting cells in the colormap via 'coloMapEntry' since that will force an
-- actual copy of the colormap if it was previously copied by reference.
-- 'copyColormap' should only be called when both the /current window/ and the
-- specified window are color index windows.
foreign import CALLCONV unsafe "glutCopyColormap" copyColormap ::
Window -> IO ()
--------------------------------------------------------------------------------
-- | Contains the number of entries in the colormap of the /current window/\'s
-- current layer (0 in RGBA mode).
numColorMapEntries :: GettableStateVar GLint
numColorMapEntries =
makeGettableStateVar $ simpleGet fromIntegral glut_WINDOW_COLORMAP_SIZE
--------------------------------------------------------------------------------
-- | Contains the transparent color index of the overlay of the /current window/
-- or -1 if no overlay is in use.
transparentIndex :: GettableStateVar (Index1 GLint)
transparentIndex =
makeGettableStateVar $
layerGet (Index1 . fromIntegral) glut_TRANSPARENT_INDEX
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Initialization.hs view on Meta::CPAN
WithAlphaComponent -> glut_ALPHA
WithDepthBuffer -> glut_DEPTH
WithStencilBuffer -> glut_STENCIL
Multisampling -> glut_MULTISAMPLE
Stereoscopic -> glut_STEREO
LuminanceMode -> glut_LUMINANCE
--------------------------------------------------------------------------------
-- | Controls the /initial display mode/ used when creating top-level windows,
-- subwindows, and overlays to determine the OpenGL display mode for the
-- to-be-created window or overlay.
--
-- Note that 'RGBAMode' selects the RGBA color model, but it does not request any
-- bits of alpha (sometimes called an /alpha buffer/ or /destination alpha/)
-- be allocated. To request alpha, specify 'WithAlphaComponent'. The same
-- applies to 'LuminanceMode'.
initialDisplayMode :: StateVar [DisplayMode]
initialDisplayMode = makeStateVar getInitialDisplayMode setInitialDisplayMode
getInitialDisplayMode :: IO [DisplayMode]
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Initialization.hs view on Meta::CPAN
-- has a different default, see the different constructors of
-- 'DisplayCapability'.
deriving ( Eq, Ord, Show )
displayCapabilityDescriptionToString :: DisplayCapabilityDescription -> String
displayCapabilityDescriptionToString (Where c r i) =
displayCapabilityToString c ++ relationToString r ++ show i
displayCapabilityDescriptionToString (With c) = displayCapabilityToString c
-- | Controls the /initial display mode/ used when creating top-level windows,
-- subwindows, and overlays to determine the OpenGL display mode for the
-- to-be-created window or overlay. It is described by a list of zero or more
-- capability descriptions, which are translated into a set of criteria used to
-- select the appropriate frame buffer configuration. The criteria are matched
-- in strict left to right order of precdence. That is, the first specified
-- criterion (leftmost) takes precedence over the later criteria for non-exact
-- criteria ('IsGreaterThan', 'IsLessThan', etc.). Exact criteria ('IsEqualTo',
-- 'IsNotEqualTo') must match exactly so precedence is not relevant.
--
-- Unspecified capability descriptions will result in unspecified criteria being
-- generated. These unspecified criteria help 'initialDisplayCapabilities'
-- behave sensibly with terse display mode descriptions.
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Menu.hs view on Meta::CPAN
type MenuCallback = IO ()
-- | Create a new pop-up menu for the /current window,/ attaching it to the
-- given mouse button. A previously attached menu (if any), is detached before
-- and won\'t receive callbacks anymore.
--
-- It is illegal to call 'attachMenu' while any (sub-)menu is in use, i.e.
-- popped up.
--
-- /X Implementation Notes:/ If available, GLUT for X will take advantage of
-- overlay planes for implementing pop-up menus. The use of overlay planes can
-- eliminate display callbacks when pop-up menus are deactivated. The
-- @SERVER_OVERLAY_VISUALS@ convention is used to determine if overlay visuals
-- are available.
attachMenu :: MouseButton -> Menu -> IO ()
attachMenu mouseButton menu@(Menu items) = do
win <- get currentWindow
let hook = MenuHook win mouseButton
detachMenu hook
unless (null items) $ do
(_, destructor) <- traverseMenu menu
addToMenuTable hook destructor
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Menu.hs view on Meta::CPAN
-- | Create a new pop-up menu and return a unique identifier for it, which can
-- be used when calling 'setMenu'. Implicitly, the /current menu/ is set to the
-- newly created menu.
--
-- When the menu callback is called because a menu entry is selected for the
-- menu, the /current menu/ will be implicitly set to the menu with the selected
-- entry before the callback is made.
--
-- /X Implementation Notes:/ If available, GLUT for X will take advantage of
-- overlay planes for implementing pop-up menus. The use of overlay planes can
-- eliminate display callbacks when pop-up menus are deactivated. The
-- @SERVER_OVERLAY_VISUALS@ convention is used to determine if overlay visuals
-- are available.
foreign import CALLCONV unsafe "glutCreateMenu" glutCreateMenu ::
FunPtr MenuCB -> IO MenuID
foreign import ccall "wrapper" makeMenuFunc :: MenuCB -> IO (FunPtr MenuCB)
-- | Destroy the specified menu. If it was the /current menu/, the /current
-- menu/ becomes invalid and 'getMenu' will return 'Nothing'.
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Overlay.hs view on Meta::CPAN
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.UI.GLUT.Overlay
-- Copyright : (c) Sven Panne 2003
-- License : BSD-style (see the file libraries/GLUT/LICENSE)
--
-- Maintainer : sven_panne@yahoo.com
-- Stability : provisional
-- Portability : portable
--
-- When overlay hardware is available, GLUT provides a set of routines for
-- establishing, using, and removing an overlay for GLUT windows. When an
-- overlay is established, a separate OpenGL context is also established. A
-- window\'s overlay OpenGL state is kept distinct from the normal planes\'
-- OpenGL state.
--
--------------------------------------------------------------------------------
module Graphics.UI.GLUT.Overlay (
-- * Overlay creation and destruction
hasOverlay, overlayPossible,
-- * Showing and hiding an overlay
overlayVisible,
-- * Changing the /layer in use/
Layer(..), layerInUse,
-- * Re-displaying
postOverlayRedisplay
) where
import Graphics.Rendering.OpenGL.GL.BasicTypes ( GLenum )
import Graphics.Rendering.OpenGL.GL.StateVar (
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Overlay.hs view on Meta::CPAN
SettableStateVar, makeSettableStateVar,
StateVar, makeStateVar )
import Graphics.UI.GLUT.Constants (
glut_OVERLAY_POSSIBLE, glut_HAS_OVERLAY, glut_NORMAL, glut_OVERLAY,
glut_LAYER_IN_USE )
import Graphics.UI.GLUT.QueryUtils ( layerGet )
import Graphics.UI.GLUT.Window ( Window )
--------------------------------------------------------------------------------
-- | Controls the overlay for the /current window/. The requested display mode
-- for the overlay is determined by the /initial display mode/.
-- 'overlayPossible' can be used to determine if an overlay is possible for the
-- /current window/ with the current /initial display mode/. Do not attempt to
-- establish an overlay when one is not possible; GLUT will terminate the
-- program.
--
-- When 'hasOverlay' is set to 'True' when an overlay already exists, the
-- existing overlay is first removed, and then a new overlay is established. The
-- state of the old overlay\'s OpenGL context is discarded. Implicitly, the
-- window\'s /layer in use/ changes to the overlay immediately after the overlay
-- is established.
--
-- The initial display state of an overlay is shown, however the overlay is only
-- actually shown if the overlay\'s window is shown.
--
-- Setting 'hasOverlay' to 'False' is safe even if no overlay is currently
-- established, nothing happens in this case. Implicitly, the window\'s /layer
-- in use/ changes to the normal plane immediately once the overlay is removed.
--
-- If the program intends to re-establish the overlay later, it is typically
-- faster and less resource intensive to use 'overlayVisible' to simply change
-- the display status of the overlay.
--
-- /X Implementation Notes:/ GLUT for X uses the @SERVER_OVERLAY_VISUALS@
-- convention to determine if overlay visuals are available. While the
-- convention allows for opaque overlays (no transparency) and overlays with the
-- transparency specified as a bitmask, GLUT overlay management only provides
-- access to transparent pixel overlays.
--
-- Until RGBA overlays are better understood, GLUT only supports color index
-- overlays.
hasOverlay :: StateVar Bool
hasOverlay = makeStateVar getHasOverlay setHasOverlay
setHasOverlay :: Bool -> IO ()
setHasOverlay False = glutRemoveOverlay
setHasOverlay True = glutEstablishOverlay
foreign import CALLCONV safe "glutRemoveOverlay" glutRemoveOverlay :: IO ()
foreign import CALLCONV safe "glutEstablishOverlay" glutEstablishOverlay :: IO ()
getHasOverlay :: IO Bool
getHasOverlay = layerGet (/= 0) glut_HAS_OVERLAY
--------------------------------------------------------------------------------
-- | Contains 'True' if an overlay could be established for the /current window/
-- given the current /initial display mode/. If it contains 'False',
-- 'establishOverlay' will fail with a fatal error if called.
overlayPossible :: GettableStateVar Bool
overlayPossible = makeGettableStateVar $ layerGet (/= 0) glut_OVERLAY_POSSIBLE
--------------------------------------------------------------------------------
-- | Controls the visibility of the overlay of the /current window/.
--
-- The effect of showing or hiding an overlay takes place immediately. Note that
-- 'showOverlay' will not actually display the overlay unless the window is also
-- shown (and even a shown window may be obscured by other windows, thereby
-- obscuring the overlay). It is typically faster and less resource intensive to
-- use the routines below to control the display status of an overlay as opposed
-- to removing and re-establishing the overlay.
overlayVisible :: SettableStateVar Bool
overlayVisible =
makeSettableStateVar $ \flag ->
if flag then glutShowOverlay else glutHideOverlay
foreign import CALLCONV safe "glutShowOverlay" glutShowOverlay :: IO ()
foreign import CALLCONV safe "glutHideOverlay" glutHideOverlay :: IO ()
--------------------------------------------------------------------------------
-- | The /layer in use/.
data Layer
= Normal -- ^ The normal plane.
| Overlay -- ^ The overlay.
deriving ( Eq, Ord )
marshalLayer :: Layer -> GLenum
marshalLayer l = case l of
Normal -> glut_NORMAL
Overlay -> glut_OVERLAY
unmarshalLayer :: GLenum -> Layer
unmarshalLayer l
| l == glut_NORMAL = Normal
| l == glut_OVERLAY = Overlay
| otherwise = error "unmarshalLayer"
--------------------------------------------------------------------------------
-- | Controls the per-window /layer in use/ for the /current window/, which can
-- either be the normal plane or the overlay. Selecting the overlay should only
-- be done if an overlay exists, however windows without an overlay may still
-- set the /layer in use/ to 'Normal'. OpenGL commands for the window are
-- directed to the current /layer in use/.
layerInUse :: StateVar Layer
layerInUse =
makeStateVar getLayerInUse setLayerInUse
setLayerInUse :: Layer -> IO ()
setLayerInUse = glutUseLayer . marshalLayer
foreign import CALLCONV safe "glutUseLayer" glutUseLayer :: GLenum -> IO ()
getLayerInUse :: IO Layer
getLayerInUse = layerGet (unmarshalLayer . fromIntegral) glut_LAYER_IN_USE
--------------------------------------------------------------------------------
-- | Mark the overlay of the given window (or the /current window/, if none is
-- supplied) as needing to be redisplayed. The next iteration through
-- 'Graphics.UI.GLUT.Begin.mainLoop', the window\'s overlay display callback
-- (or simply the display callback if no overlay display callback is registered)
-- will be called to redisplay the window\'s overlay plane. Multiple calls to
-- 'postOverlayRedisplay' before the next display callback opportunity (or
-- overlay display callback opportunity if one is registered) generate only a
-- single redisplay. 'postOverlayRedisplay' may be called within a window\'s
-- display or overlay display callback to re-mark that window for redisplay.
--
-- Logically, overlay damage notification for a window is treated as a
-- 'postOverlayRedisplay' on the damaged window. Unlike damage reported by the
-- window system, 'postOverlayRedisplay' will not set to true the overlay\'s
-- damaged status (see 'Graphics.UI.GLUT.State.damaged').
--
-- Also, see 'Graphics.UI.GLUT.Window.postRedisplay'.
postOverlayRedisplay :: Maybe Window -> IO ()
postOverlayRedisplay =
maybe glutPostOverlayRedisplay glutPostWindowOverlayRedisplay
foreign import CALLCONV safe "glutPostOverlayRedisplay"
glutPostOverlayRedisplay :: IO ()
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Window.hs view on Meta::CPAN
-- children of children.
numSubWindows :: GettableStateVar Int
numSubWindows =
makeGettableStateVar $
simpleGet fromIntegral glut_WINDOW_NUM_CHILDREN
--------------------------------------------------------------------------------
-- | Destroy the specified window and the window\'s associated OpenGL context,
-- logical colormap (if the window is color index), and overlay and related
-- state (if an overlay has been established). Any subwindows of the destroyed
-- window are also destroyed by 'destroyWindow'. If the specified window was the
-- /current window/, the /current window/ becomes invalid ('getWindow' will
-- return 'Nothing').
foreign import CALLCONV unsafe "glutDestroyWindow" destroyWindow ::
Window -> IO ()
--------------------------------------------------------------------------------
-- | Controls the /current window/. It does /not/ affect the /layer in use/ for
hugs98-Nov2003/fptools/libraries/GLUT/Graphics/UI/GLUT/Window.hs view on Meta::CPAN
isRealWindow = (/= makeWindow 0)
--------------------------------------------------------------------------------
-- | Mark the normal plane of given window (or the /current window/, if none
-- is supplied) as needing to be redisplayed. The next iteration through
-- 'Graphics.UI.GLUT.Begin.mainLoop', the window\'s display callback will be
-- called to redisplay the window\'s normal plane. Multiple calls to
-- 'postRedisplay' before the next display callback opportunity generates only a
-- single redisplay callback. 'postRedisplay' may be called within a window\'s
-- display or overlay display callback to re-mark that window for redisplay.
--
-- Logically, normal plane damage notification for a window is treated as a
-- 'postRedisplay' on the damaged window. Unlike damage reported by the window
-- system, 'postRedisplay' will /not/ set to true the normal plane\'s damaged
-- status (see 'Graphics.UI.GLUT.State.damaged').
--
-- Also, see 'Graphics.UI.GLUT.Overlay.postOverlayRedisplay'.
postRedisplay :: Maybe Window -> IO ()
postRedisplay = maybe glutPostRedisplay glutPostWindowRedisplay