{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
{-# LANGUAGE CPP, FlexibleContexts #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Graphics.UI.FLTK.LowLevel.Glut
(
GlutDraw(..),
GlutMouseCodes(..),
GlutUpDown(..),
GlutVisibility(..),
GlutMenuState(..),
GlutMenuItems(..),
GlutEnteredLeft(..),
GlutKeyboardCodes(..),
GlutConstants(..),
GlutWindowProperties(..),
GlutCursor(..),
GlutDisplayMode(..),
GlutWindow(..),
GlutMenu(..),
glutInitDisplayMode ,
glutInitWindowPosition,
glutInitWindowSize,
glutCursorFullCrossHair,
glutMainLoop,
glutCreateWindow,
glutCreateSubWindow,
glutDestroyWindow,
glutPostRedisplay,
glutPostWindowRedisplay,
glutSwapBuffers,
glutGetWindow,
glutSetWindow,
glutSetWindowTitle,
glutSetIconTitle,
glutPositionWindow,
glutReshapeWindow,
glutPopWindow,
glutPushWindow,
glutIconifyWindow,
glutShowWindow,
glutHideWindow,
glutFullScreen,
glutSetCursor,
glutWarpPointer,
glutEstablishOverlay,
glutRemoveOverlay,
glutUseLayer,
glutPostOverlayRedisplay,
glutShowOverlay,
glutHideOverlay,
glutCreateMenu,
glutDestroyMenu,
glutGetMenu,
glutSetMenu,
glutAddMenuEntry,
glutAddSubMenu,
glutChangeToMenuEntry,
glutChangeToSubMenu,
glutRemoveMenuItem,
glutAttachMenu,
glutDetachMenu,
glutDisplayFunc,
glutReshapeFunc,
glutKeyboardFunc,
glutMouseFunc,
glutMotionFunc,
glutPassiveMotionFunc,
glutEntryFunc,
glutVisibilityFunc,
glutIdleFunc,
glutTimerFunc,
glutMenuStateFunc,
glutMenuStatusFunc,
glutSpecialFunc,
glutOverlayDisplayFunc,
glutGetWindowRectangle,
glutGetWindowParent,
glutGetScreenSize,
glutGetMenuNumItems,
glutDisplayModePossible,
glutWindowBufferSize,
glutVersion,
glutOther,
glutGetModifiers,
glutHasKeyboard,
glutHasMouse,
glutNumMouseButtons,
glutOverlayPossible,
glutTransparencyIndex,
glutNormalDamaged,
glutOverlayDamaged,
glutWireSphere,
glutSolidSphere,
glutWireCone,
glutSolidCone,
glutWireCube,
glutSolidCube,
glutWireTorus,
glutSolidTorus,
glutWireDodecahedron,
glutSolidDodecahedron,
glutWireTeapot,
glutSolidTeapot,
glutWireOctahedron,
glutSolidOctahedron,
glutWireTetrahedron,
glutSolidTetrahedron,
glutWireIcosahedron,
glutSolidIcosahedron
)
where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import C2HS hiding (cFromEnum, cFromBool, cToBool,cToEnum)
import Graphics.UI.FLTK.LowLevel.FL
import Graphics.UI.FLTK.LowLevel.Fl_Types
import qualified Data.Text as T
import Graphics.UI.FLTK.LowLevel.Utils
import Graphics.UI.FLTK.LowLevel.Fl_Enumerations
data GlutDraw = GlutNormal
| GlutOverlay
deriving (Int -> GlutDraw -> ShowS
[GlutDraw] -> ShowS
GlutDraw -> String
(Int -> GlutDraw -> ShowS)
-> (GlutDraw -> String) -> ([GlutDraw] -> ShowS) -> Show GlutDraw
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GlutDraw] -> ShowS
$cshowList :: [GlutDraw] -> ShowS
show :: GlutDraw -> String
$cshow :: GlutDraw -> String
showsPrec :: Int -> GlutDraw -> ShowS
$cshowsPrec :: Int -> GlutDraw -> ShowS
Show)
instance Enum GlutDraw where
succ :: GlutDraw -> GlutDraw
succ GlutNormal = GlutDraw
GlutOverlay
succ GlutOverlay = String -> GlutDraw
forall a. HasCallStack => String -> a
error "GlutDraw.succ: GlutOverlay has no successor"
pred :: GlutDraw -> GlutDraw
pred GlutOverlay = GlutDraw
GlutNormal
pred GlutNormal = String -> GlutDraw
forall a. HasCallStack => String -> a
error "GlutDraw.pred: GlutNormal has no predecessor"
enumFromTo :: GlutDraw -> GlutDraw -> [GlutDraw]
enumFromTo from :: GlutDraw
from to :: GlutDraw
to = GlutDraw -> [GlutDraw]
go GlutDraw
from
where
end :: Int
end = GlutDraw -> Int
forall a. Enum a => a -> Int
fromEnum GlutDraw
to
go :: GlutDraw -> [GlutDraw]
go v :: GlutDraw
v = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (GlutDraw -> Int
forall a. Enum a => a -> Int
fromEnum GlutDraw
v) Int
end of
LT -> GlutDraw
v GlutDraw -> [GlutDraw] -> [GlutDraw]
forall a. a -> [a] -> [a]
: GlutDraw -> [GlutDraw]
go (GlutDraw -> GlutDraw
forall a. Enum a => a -> a
succ GlutDraw
v)
EQ -> [GlutDraw
v]
GT -> []
enumFrom :: GlutDraw -> [GlutDraw]
enumFrom from :: GlutDraw
from = GlutDraw -> GlutDraw -> [GlutDraw]
forall a. Enum a => a -> a -> [a]
enumFromTo GlutDraw
from GlutDraw
GlutOverlay
fromEnum :: GlutDraw -> Int
fromEnum GlutNormal = 0
fromEnum GlutOverlay = 1
toEnum :: Int -> GlutDraw
toEnum 0 = GlutDraw
GlutNormal
toEnum 1 = GlutDraw
GlutOverlay
toEnum unmatched :: Int
unmatched = String -> GlutDraw
forall a. HasCallStack => String -> a
error ("GlutDraw.toEnum: Cannot match " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
unmatched)
{-# LINE 281 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutMouseCodes = GlutLeftButton
| GlutMiddleButton
| GlutRightButton
deriving (Show)
instance Enum GlutMouseCodes where
succ :: GlutMouseCodes -> GlutMouseCodes
succ :: GlutUpDown -> GlutUpDown
succ GlutLeftButton = GlutMouseCodes
GlutMiddleButton
succ GlutMiddleButton = GlutMouseCodes
GlutRightButton
succ GlutRightButton = String -> GlutMouseCodes
forall a. HasCallStack => String -> a
error "GlutMouseCodes.succ: GlutRightButton has no successor"
pred GlutMiddleButton = GlutLeftButton
pred :: GlutMenuState -> GlutMenuState
pred GlutRightButton = GlutMiddleButton
pred GlutLeftButton = error "GlutMouseCodes.pred: GlutLeftButton has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutRightButton
fromEnum GlutLeftButton = 0
fromEnum GlutMiddleButton = 1
fromEnum GlutRightButton = 2
toEnum 0 = GlutLeftButton
toEnum 1 = GlutMiddleButton
toEnum 2 = GlutRightButton
toEnum unmatched = error ("GlutMouseCodes.toEnum: Cannot match " ++ show unmatched)
{-# LINE 282 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutUpDown = GlutDown
| GlutUp
deriving (Show)
instance Enum GlutUpDown where
succ GlutDown = GlutUp
succ GlutUp = error "GlutUpDown.succ: GlutUp has no successor"
pred GlutUp = GlutDown
pred GlutDown = error "GlutUpDown.pred: GlutDown has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutUp
fromEnum GlutDown = 0
fromEnum GlutUp = 1
toEnum 0 = GlutDown
toEnum :: Int -> GlutVisibility
toEnum 1 = GlutUp
toEnum unmatched = error ("GlutUpDown.toEnum: Cannot match " ++ show unmatched)
{-# LINE 283 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutVisibility = GlutNotVisible
| GlutVisible
deriving (Show)
instance Enum GlutVisibility where
succ GlutNotVisible = GlutVisible
succ GlutVisible = error "GlutVisibility.succ: GlutVisible has no successor"
pred GlutVisible = GlutNotVisible
pred GlutNotVisible = error "GlutVisibility.pred: GlutNotVisible has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutVisible
fromEnum GlutNotVisible = 0
fromEnum :: GlutMenuState -> Int
enumFrom :: GlutEnteredLeft -> [GlutEnteredLeft]
fromEnum GlutVisible = 1
toEnum 0 = GlutNotVisible
toEnum 1 = GlutVisible
toEnum unmatched = error ("GlutVisibility.toEnum: Cannot match " ++ show unmatched)
{-# LINE 284 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutMenuState = GlutMenuNotInUse
| GlutMenuInUse
deriving (Show)
instance Enum GlutMenuState where
succ GlutMenuNotInUse = GlutMenuInUse
succ GlutMenuInUse = error "GlutMenuState.succ: GlutMenuInUse has no successor"
pred GlutMenuInUse = GlutMenuNotInUse
pred GlutMenuNotInUse = error "GlutMenuState.pred: GlutMenuNotInUse has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutMenuInUse
fromEnum GlutMenuNotInUse = 0
fromEnum GlutMenuInUse = 1
toEnum 0 = GlutMenuNotInUse
toEnum 1 = GlutMenuInUse
toEnum unmatched = error ("GlutMenuState.toEnum: Cannot match " ++ show unmatched)
{-# LINE 285 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutMenuItems = GlutMenuNumItems
deriving (Show)
instance Enum GlutMenuItems where
succ GlutMenuNumItems = error "GlutMenuItems.succ: GlutMenuNumItems has no successor"
pred GlutMenuNumItems = error "GlutMenuItems.pred: GlutMenuNumItems has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutMenuNumItems
fromEnum GlutMenuNumItems = 8
toEnum 8 = GlutMenuNumItems
toEnum unmatched = error ("GlutMenuItems.toEnum: Cannot match " ++ show unmatched)
{-# LINE 286 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutEnteredLeft = GlutLeft
| GlutEntered
deriving (Show)
instance Enum GlutEnteredLeft where
succ GlutLeft = GlutEntered
succ GlutEntered = error "GlutEnteredLeft.succ: GlutEntered has no successor"
pred GlutEntered = GlutLeft
pred GlutLeft = error "GlutEnteredLeft.pred: GlutLeft has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutEntered
fromEnum GlutLeft = 0
fromEnum GlutEntered = 1
toEnum 0 = GlutLeft
toEnum 1 = GlutEntered
toEnum unmatched = error ("GlutEnteredLeft.toEnum: Cannot match " ++ show unmatched)
{-# LINE 287 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutKeyboardCodes = GlutKeyF1
| GlutKeyF2
| GlutKeyF3
| GlutKeyF4
| GlutKeyF5
| GlutKeyF6
| GlutKeyF7
| GlutKeyF8
| GlutKeyF9
| GlutKeyF10
| GlutKeyF11
| GlutKeyF12
| GlutKeyHome
| GlutKeyLeft
| GlutKeyUp
| GlutKeyRight
| GlutKeyDown
| GlutKeyPageUp
| GlutKeyPageDown
| GlutKeyEnd
| GlutKeyInsert
| GlutActiveShift
| GlutActiveCtrl
| GlutActiveAlt
deriving (Show)
instance Enum GlutKeyboardCodes where
succ GlutKeyF1 = GlutKeyF2
succ GlutKeyF2 = GlutKeyF3
pred :: GlutDisplayMode -> GlutDisplayMode
succ :: GlutCursor -> GlutCursor
pred :: GlutPeripheralProperties -> GlutPeripheralProperties
succ GlutKeyF3 = GlutKeyF4
succ GlutKeyF4 = GlutKeyF5
succ GlutKeyF5 = GlutKeyF6
succ GlutKeyF6 = GlutKeyF7
succ GlutKeyF7 = GlutKeyF8
succ GlutKeyF8 = GlutKeyF9
succ GlutKeyF9 = GlutKeyF10
succ GlutKeyF10 = GlutKeyF11
succ GlutKeyF11 = GlutKeyF12
succ GlutKeyF12 = GlutKeyHome
succ GlutKeyHome = GlutKeyLeft
succ GlutKeyLeft = GlutKeyUp
succ GlutKeyUp = GlutKeyRight
succ GlutKeyRight = GlutKeyDown
succ GlutKeyDown = GlutKeyPageUp
succ GlutKeyPageUp = GlutKeyPageDown
succ GlutKeyPageDown = GlutKeyEnd
succ GlutKeyEnd = GlutKeyInsert
succ GlutKeyInsert = GlutActiveShift
succ GlutActiveShift = GlutActiveCtrl
succ GlutActiveCtrl = GlutActiveAlt
succ GlutActiveAlt = error "GlutKeyboardCodes.succ: GlutActiveAlt has no successor"
pred GlutKeyF2 = GlutKeyF1
pred GlutKeyF3 = GlutKeyF2
pred GlutKeyF4 = GlutKeyF3
pred GlutKeyF5 = GlutKeyF4
pred GlutKeyF6 = GlutKeyF5
pred GlutKeyF7 = GlutKeyF6
pred GlutKeyF8 = GlutKeyF7
pred GlutKeyF9 = GlutKeyF8
pred GlutKeyF10 = GlutKeyF9
pred GlutKeyF11 = GlutKeyF10
pred :: GlutWindowProperties -> GlutWindowProperties
pred GlutKeyF12 = GlutKeyF11
pred GlutKeyHome = GlutKeyF12
pred GlutKeyLeft = GlutKeyHome
pred GlutKeyUp = GlutKeyLeft
pred GlutKeyRight = GlutKeyUp
pred GlutKeyDown = GlutKeyRight
pred GlutKeyPageUp = GlutKeyDown
pred GlutKeyPageDown = GlutKeyPageUp
pred GlutKeyEnd = GlutKeyPageDown
pred GlutKeyInsert = GlutKeyEnd
pred GlutActiveShift = GlutKeyInsert
pred GlutActiveCtrl = GlutActiveShift
pred GlutActiveAlt = GlutActiveCtrl
pred GlutKeyF1 = error "GlutKeyboardCodes.pred: GlutKeyF1 has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom :: GlutKeyboardCodes -> [GlutKeyboardCodes]
enumFrom from :: GlutKeyboardCodes
from = GlutKeyboardCodes -> GlutKeyboardCodes -> [GlutKeyboardCodes]
forall a. Enum a => a -> a -> [a]
enumFromTo GlutKeyboardCodes
from GlutKeyboardCodes
GlutActiveAlt
fromEnum GlutKeyF1 = 1
fromEnum GlutKeyF2 = 2
fromEnum GlutKeyF3 = 3
fromEnum GlutKeyF4 = 4
fromEnum GlutKeyF5 = 5
fromEnum GlutKeyF6 = 6
fromEnum GlutKeyF7 = 7
fromEnum GlutKeyF8 = 8
fromEnum GlutKeyF9 = 9
fromEnum GlutKeyF10 = 10
fromEnum GlutKeyF11 = 11
fromEnum GlutKeyF12 = 12
fromEnum GlutKeyHome = 65360
fromEnum GlutKeyLeft = 65361
fromEnum :: GlutWindowProperties -> Int
fromEnum GlutKeyUp = 65362
fromEnum GlutKeyRight = 65363
fromEnum GlutKeyDown = 65364
fromEnum GlutKeyPageUp = 65365
fromEnum GlutKeyPageDown = 65366
fromEnum GlutKeyEnd = 65367
fromEnum GlutKeyInsert = 65379
fromEnum GlutActiveShift = 65536
fromEnum GlutActiveCtrl = 262144
fromEnum GlutActiveAlt = 524288
toEnum 1 = GlutKeyF1
toEnum 2 = GlutKeyF2
toEnum 3 = GlutKeyF3
toEnum 4 = GlutKeyF4
toEnum 5 = GlutKeyF5
toEnum 6 = GlutKeyF6
toEnum 7 = GlutKeyF7
toEnum 8 = GlutKeyF8
toEnum 9 = GlutKeyF9
toEnum 10 = GlutKeyF10
toEnum 11 = GlutKeyF11
toEnum 12 = GlutKeyF12
toEnum 65360 = GlutKeyHome
toEnum 65361 = GlutKeyLeft
toEnum 65362 = GlutKeyUp
toEnum 65363 = GlutKeyRight
toEnum 65364 = GlutKeyDown
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
toEnum 65365 = GlutKeyPageUp
toEnum 65366 = GlutKeyPageDown
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
toEnum 65367 = GlutKeyEnd
toEnum 65379 = GlutKeyInsert
toEnum 65536 = GlutActiveShift
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
toEnum 262144 = GlutActiveCtrl
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
toEnum 524288 = GlutActiveAlt
toEnum unmatched = error ("GlutKeyboardCodes.toEnum: Cannot match " ++ show unmatched)
{-# LINE 288 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutConstants = GlutReturnZero
| GlutDisplayModePossible
| GlutVersion
| GlutOverlayPossible
| GlutTransparentIndex
| GlutNormalDamaged
| GlutOverlayDamaged
deriving (Show)
instance Enum GlutConstants where
succ GlutReturnZero = GlutDisplayModePossible
succ GlutDisplayModePossible = GlutVersion
succ GlutVersion = GlutOverlayPossible
succ GlutOverlayPossible = GlutTransparentIndex
succ GlutTransparentIndex = GlutNormalDamaged
succ GlutNormalDamaged = GlutOverlayDamaged
succ GlutOverlayDamaged = error "GlutConstants.succ: GlutOverlayDamaged has no successor"
pred GlutDisplayModePossible = GlutReturnZero
pred GlutVersion = GlutDisplayModePossible
pred GlutOverlayPossible = GlutVersion
pred GlutTransparentIndex = GlutOverlayPossible
pred GlutNormalDamaged = GlutTransparentIndex
pred GlutOverlayDamaged = GlutNormalDamaged
pred GlutReturnZero = error "GlutConstants.pred: GlutReturnZero has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutOverlayDamaged
fromEnum GlutReturnZero = 0
fromEnum GlutDisplayModePossible = 9
fromEnum GlutVersion = 16
fromEnum GlutOverlayPossible = 800
fromEnum GlutTransparentIndex = 803
fromEnum GlutNormalDamaged = 804
fromEnum GlutOverlayDamaged = 805
toEnum 0 = GlutReturnZero
toEnum 9 = GlutDisplayModePossible
toEnum 16 = GlutVersion
toEnum 800 = GlutOverlayPossible
toEnum 803 = GlutTransparentIndex
toEnum 804 = GlutNormalDamaged
toEnum 805 = GlutOverlayDamaged
toEnum unmatched = error ("GlutConstants.toEnum: Cannot match " ++ show unmatched)
{-# LINE 289 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutWindowProperties = GlutWindowX
| GlutWindowY
| GlutWindowWidth
| GlutWindowHeight
| GlutWindowParent
| GlutScreenWidth
| GlutScreenHeight
| GlutInitWindowX
| GlutInitWindowY
| GlutInitWindowWidth
| GlutInitWindowHeight
| GlutInitDisplayMode
| GlutWindowBufferSize
| GlutWindowDoublebuffer
| GlutWindowStereo
| GlutWindowColormapSize
| GlutWindowRedSize
| GlutWindowGreenSize
| GlutWindowBlueSize
| GlutWindowAlphaSize
| GlutWindowDepthSize
| GlutWindowStencilSize
| GlutWindowAccumRedSize
| GlutWindowAccumGreenSize
| GlutWindowAccumBlueSize
| GlutWindowAccumAlphaSize
| GlutWindowRgba
| GlutWindowNumSamples
deriving (Show)
instance Enum GlutWindowProperties where
succ GlutWindowX = GlutWindowY
succ GlutWindowY = GlutWindowWidth
succ GlutWindowWidth = GlutWindowHeight
succ GlutWindowHeight = GlutWindowParent
succ GlutWindowParent = GlutScreenWidth
succ GlutScreenWidth = GlutScreenHeight
succ GlutScreenHeight = GlutInitWindowX
succ GlutInitWindowX = GlutInitWindowY
succ GlutInitWindowY = GlutInitWindowWidth
succ GlutInitWindowWidth = GlutInitWindowHeight
succ GlutInitWindowHeight = GlutInitDisplayMode
succ GlutInitDisplayMode = GlutWindowBufferSize
succ GlutWindowBufferSize = GlutWindowDoublebuffer
succ GlutWindowDoublebuffer = GlutWindowStereo
succ GlutWindowStereo = GlutWindowColormapSize
succ GlutWindowColormapSize = GlutWindowRedSize
succ GlutWindowRedSize = GlutWindowGreenSize
succ GlutWindowGreenSize = GlutWindowBlueSize
succ GlutWindowBlueSize = GlutWindowAlphaSize
succ GlutWindowAlphaSize = GlutWindowDepthSize
succ GlutWindowDepthSize = GlutWindowStencilSize
succ GlutWindowStencilSize = GlutWindowAccumRedSize
succ GlutWindowAccumRedSize = GlutWindowAccumGreenSize
succ GlutWindowAccumGreenSize = GlutWindowAccumBlueSize
succ GlutWindowAccumBlueSize = GlutWindowAccumAlphaSize
succ GlutWindowAccumAlphaSize = GlutWindowRgba
succ GlutWindowRgba = GlutWindowNumSamples
succ GlutWindowNumSamples = error "GlutWindowProperties.succ: GlutWindowNumSamples has no successor"
pred GlutWindowY = GlutWindowX
pred GlutWindowWidth = GlutWindowY
pred GlutWindowHeight = GlutWindowWidth
pred GlutWindowParent = GlutWindowHeight
pred GlutScreenWidth = GlutWindowParent
pred GlutScreenHeight = GlutScreenWidth
pred GlutInitWindowX = GlutScreenHeight
pred GlutInitWindowY = GlutInitWindowX
pred GlutInitWindowWidth = GlutInitWindowY
pred GlutInitWindowHeight = GlutInitWindowWidth
pred GlutInitDisplayMode = GlutInitWindowHeight
pred GlutWindowBufferSize = GlutInitDisplayMode
pred GlutWindowDoublebuffer = GlutWindowBufferSize
pred GlutWindowStereo = GlutWindowDoublebuffer
pred GlutWindowColormapSize = GlutWindowStereo
pred GlutWindowRedSize = GlutWindowColormapSize
pred GlutWindowGreenSize = GlutWindowRedSize
pred GlutWindowBlueSize = GlutWindowGreenSize
pred GlutWindowAlphaSize = GlutWindowBlueSize
pred GlutWindowDepthSize = GlutWindowAlphaSize
pred GlutWindowStencilSize = GlutWindowDepthSize
pred GlutWindowAccumRedSize = GlutWindowStencilSize
pred GlutWindowAccumGreenSize = GlutWindowAccumRedSize
pred GlutWindowAccumBlueSize = GlutWindowAccumGreenSize
pred GlutWindowAccumAlphaSize = GlutWindowAccumBlueSize
pred GlutWindowRgba = GlutWindowAccumAlphaSize
pred GlutWindowNumSamples = GlutWindowRgba
pred GlutWindowX = error "GlutWindowProperties.pred: GlutWindowX has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutWindowNumSamples
fromEnum GlutWindowX = 1
fromEnum GlutWindowY = 2
fromEnum GlutWindowWidth = 3
fromEnum GlutWindowHeight = 4
fromEnum GlutWindowParent = 5
fromEnum GlutScreenWidth = 6
fromEnum GlutScreenHeight = 7
fromEnum GlutInitWindowX = 10
fromEnum GlutInitWindowY = 11
fromEnum GlutInitWindowWidth = 12
fromEnum GlutInitWindowHeight = 13
fromEnum GlutInitDisplayMode = 14
fromEnum GlutWindowBufferSize = 15
fromEnum GlutWindowDoublebuffer = 3122
fromEnum GlutWindowStereo = 3123
fromEnum GlutWindowColormapSize = 3409
fromEnum GlutWindowRedSize = 3410
fromEnum GlutWindowGreenSize = 3411
fromEnum GlutWindowBlueSize = 3412
fromEnum GlutWindowAlphaSize = 3413
fromEnum GlutWindowDepthSize = 3414
fromEnum GlutWindowStencilSize = 3415
fromEnum GlutWindowAccumRedSize = 3416
fromEnum GlutWindowAccumGreenSize = 3417
fromEnum GlutWindowAccumBlueSize = 3418
fromEnum GlutWindowAccumAlphaSize = 3419
fromEnum GlutWindowRgba = 6408
fromEnum GlutWindowNumSamples = 32937
toEnum 1 = GlutWindowX
toEnum 2 = GlutWindowY
toEnum 3 = GlutWindowWidth
toEnum 4 = GlutWindowHeight
toEnum 5 = GlutWindowParent
toEnum 6 = GlutScreenWidth
toEnum 7 = GlutScreenHeight
toEnum 10 = GlutInitWindowX
toEnum 11 = GlutInitWindowY
toEnum 12 = GlutInitWindowWidth
toEnum 13 = GlutInitWindowHeight
toEnum 14 = GlutInitDisplayMode
toEnum 15 = GlutWindowBufferSize
toEnum 3122 = GlutWindowDoublebuffer
toEnum 3123 = GlutWindowStereo
toEnum 3409 = GlutWindowColormapSize
toEnum 3410 = GlutWindowRedSize
toEnum 3411 = GlutWindowGreenSize
toEnum 3412 = GlutWindowBlueSize
toEnum 3413 = GlutWindowAlphaSize
toEnum 3414 = GlutWindowDepthSize
toEnum 3415 = GlutWindowStencilSize
toEnum 3416 = GlutWindowAccumRedSize
toEnum 3417 = GlutWindowAccumGreenSize
toEnum 3418 = GlutWindowAccumBlueSize
toEnum 3419 = GlutWindowAccumAlphaSize
toEnum 6408 = GlutWindowRgba
toEnum 32937 = GlutWindowNumSamples
toEnum unmatched = error ("GlutWindowProperties.toEnum: Cannot match " ++ show unmatched)
data GlutDisplayMode = GlutDisplayModeRgb
| GlutDisplayModeRgba
| GlutDisplayModeSingle
| GlutDisplayModeIndex
| GlutDisplayModeDouble
| GlutDisplayModeAccum
| GlutDisplayModeAlpha
| GlutDisplayModeDepth
| GlutDisplayModeStencil
| GlutDisplayModeMultisample
| GlutDisplayModeStereo
deriving (Show)
instance Enum GlutDisplayMode where
succ GlutDisplayModeRgb = GlutDisplayModeIndex
succ GlutDisplayModeRgba = GlutDisplayModeIndex
succ GlutDisplayModeSingle = GlutDisplayModeIndex
succ GlutDisplayModeIndex = GlutDisplayModeDouble
succ GlutDisplayModeDouble = GlutDisplayModeAccum
succ GlutDisplayModeAccum = GlutDisplayModeAlpha
succ GlutDisplayModeAlpha = GlutDisplayModeDepth
succ GlutDisplayModeDepth = GlutDisplayModeStencil
succ GlutDisplayModeStencil = GlutDisplayModeMultisample
succ GlutDisplayModeMultisample = GlutDisplayModeStereo
succ GlutDisplayModeStereo = error "GlutDisplayMode.succ: GlutDisplayModeStereo has no successor"
pred GlutDisplayModeIndex = GlutDisplayModeRgb
pred GlutDisplayModeDouble = GlutDisplayModeIndex
pred GlutDisplayModeAccum = GlutDisplayModeDouble
pred GlutDisplayModeAlpha = GlutDisplayModeAccum
pred GlutDisplayModeDepth = GlutDisplayModeAlpha
pred GlutDisplayModeStencil = GlutDisplayModeDepth
pred GlutDisplayModeMultisample = GlutDisplayModeStencil
pred GlutDisplayModeStereo = GlutDisplayModeMultisample
pred GlutDisplayModeRgb = error "GlutDisplayMode.pred: GlutDisplayModeRgb has no predecessor"
pred GlutDisplayModeRgba = error "GlutDisplayMode.pred: GlutDisplayModeRgba has no predecessor"
pred GlutDisplayModeSingle = error "GlutDisplayMode.pred: GlutDisplayModeSingle has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutDisplayModeStereo
fromEnum GlutDisplayModeRgb = 0
fromEnum GlutDisplayModeRgba = 0
fromEnum GlutDisplayModeSingle = 0
fromEnum GlutDisplayModeIndex = 1
fromEnum GlutDisplayModeDouble = 2
fromEnum GlutDisplayModeAccum = 4
fromEnum GlutDisplayModeAlpha = 8
fromEnum GlutDisplayModeDepth = 16
fromEnum GlutDisplayModeStencil = 32
fromEnum GlutDisplayModeMultisample = 128
fromEnum GlutDisplayModeStereo = 256
toEnum 0 = GlutDisplayModeRgb
toEnum 1 = GlutDisplayModeIndex
toEnum 2 = GlutDisplayModeDouble
toEnum 4 = GlutDisplayModeAccum
toEnum 8 = GlutDisplayModeAlpha
toEnum 16 = GlutDisplayModeDepth
toEnum 32 = GlutDisplayModeStencil
toEnum 128 = GlutDisplayModeMultisample
toEnum 256 = GlutDisplayModeStereo
toEnum unmatched = error ("GlutDisplayMode.toEnum: Cannot match " ++ show unmatched)
{-# LINE 291 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutCursor = GlutCursorInherit
| GlutCursorRightArrow
| GlutCursorBottomLeftCorner
| GlutCursorBottomRightCorner
| GlutCursorBottomSide
| GlutCursorCycle
| GlutCursorInfo
| GlutCursorLeftSide
| GlutCursorDestroy
| GlutCursorHelp
| GlutCursorRightSide
| GlutCursorSpray
| GlutCursorCrosshair
| GlutCursorLeftArrow
| GlutCursorTopLeftCorner
| GlutCursorTopRightCorner
| GlutCursorTopSide
| GlutCursorWait
| GlutCursorText
| GlutCursorUpDown
| GlutCursorLeftRight
| GlutCursorNone
deriving (Show)
instance Enum GlutCursor where
succ GlutCursorInherit = GlutCursorRightArrow
succ GlutCursorRightArrow = GlutCursorBottomLeftCorner
succ GlutCursorBottomLeftCorner = GlutCursorBottomRightCorner
succ GlutCursorBottomRightCorner = GlutCursorBottomSide
succ GlutCursorBottomSide = GlutCursorCycle
succ GlutCursorCycle = GlutCursorInfo
succ GlutCursorInfo = GlutCursorLeftSide
succ GlutCursorLeftSide = GlutCursorDestroy
succ GlutCursorDestroy = GlutCursorHelp
succ GlutCursorHelp = GlutCursorRightSide
succ GlutCursorRightSide = GlutCursorSpray
succ GlutCursorSpray = GlutCursorCrosshair
succ GlutCursorCrosshair = GlutCursorLeftArrow
succ GlutCursorLeftArrow = GlutCursorTopLeftCorner
succ GlutCursorTopLeftCorner = GlutCursorTopRightCorner
succ GlutCursorTopRightCorner = GlutCursorTopSide
succ GlutCursorTopSide = GlutCursorWait
succ GlutCursorWait = GlutCursorText
succ GlutCursorText = GlutCursorUpDown
succ GlutCursorUpDown = GlutCursorLeftRight
succ GlutCursorLeftRight = GlutCursorNone
succ GlutCursorNone = error "GlutCursor.succ: GlutCursorNone has no successor"
pred GlutCursorRightArrow = GlutCursorInherit
pred GlutCursorBottomLeftCorner = GlutCursorRightArrow
pred GlutCursorBottomRightCorner = GlutCursorBottomLeftCorner
pred GlutCursorBottomSide = GlutCursorBottomRightCorner
pred GlutCursorCycle = GlutCursorBottomSide
pred GlutCursorInfo = GlutCursorCycle
pred GlutCursorLeftSide = GlutCursorInfo
pred GlutCursorDestroy = GlutCursorLeftSide
pred GlutCursorHelp = GlutCursorDestroy
pred GlutCursorRightSide = GlutCursorHelp
pred GlutCursorSpray = GlutCursorRightSide
pred GlutCursorCrosshair = GlutCursorSpray
pred GlutCursorLeftArrow = GlutCursorCrosshair
pred GlutCursorTopLeftCorner = GlutCursorLeftArrow
pred GlutCursorTopRightCorner = GlutCursorTopLeftCorner
pred GlutCursorTopSide = GlutCursorTopRightCorner
pred GlutCursorWait = GlutCursorTopSide
pred GlutCursorText = GlutCursorWait
pred GlutCursorUpDown = GlutCursorText
pred GlutCursorLeftRight = GlutCursorUpDown
pred GlutCursorNone = GlutCursorLeftRight
pred GlutCursorInherit = error "GlutCursor.pred: GlutCursorInherit has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutCursorNone
fromEnum GlutCursorInherit = 0
fromEnum GlutCursorRightArrow = 2
fromEnum GlutCursorBottomLeftCorner = 7
fromEnum GlutCursorBottomRightCorner = 8
fromEnum GlutCursorBottomSide = 9
fromEnum GlutCursorCycle = 26
fromEnum GlutCursorInfo = 31
fromEnum GlutCursorLeftSide = 36
fromEnum GlutCursorDestroy = 45
fromEnum GlutCursorHelp = 47
fromEnum GlutCursorRightSide = 49
fromEnum GlutCursorSpray = 63
fromEnum GlutCursorCrosshair = 66
fromEnum GlutCursorLeftArrow = 67
fromEnum GlutCursorTopLeftCorner = 68
fromEnum GlutCursorTopRightCorner = 69
fromEnum GlutCursorTopSide = 70
fromEnum GlutCursorWait = 76
fromEnum GlutCursorText = 77
fromEnum GlutCursorUpDown = 78
fromEnum GlutCursorLeftRight = 79
fromEnum GlutCursorNone = 255
toEnum 0 = GlutCursorInherit
toEnum 2 = GlutCursorRightArrow
toEnum 7 = GlutCursorBottomLeftCorner
toEnum 8 = GlutCursorBottomRightCorner
toEnum 9 = GlutCursorBottomSide
toEnum 26 = GlutCursorCycle
toEnum 31 = GlutCursorInfo
toEnum 36 = GlutCursorLeftSide
toEnum 45 = GlutCursorDestroy
toEnum 47 = GlutCursorHelp
toEnum 49 = GlutCursorRightSide
toEnum 63 = GlutCursorSpray
toEnum 66 = GlutCursorCrosshair
toEnum 67 = GlutCursorLeftArrow
toEnum 68 = GlutCursorTopLeftCorner
toEnum 69 = GlutCursorTopRightCorner
toEnum 70 = GlutCursorTopSide
toEnum 76 = GlutCursorWait
toEnum 77 = GlutCursorText
toEnum 78 = GlutCursorUpDown
toEnum 79 = GlutCursorLeftRight
toEnum 255 = GlutCursorNone
toEnum unmatched = error ("GlutCursor.toEnum: Cannot match " ++ show unmatched)
{-# LINE 292 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
data GlutPeripheralProperties = GlutPeripheralHasKeyboard
| GlutPeripheralHasMouse
| GlutPeripheralHasSpaceball
| GlutPeripheralHasDialAndButtonBox
| GlutPeripheralHasTablet
| GlutPeripheralNumMouseButtons
| GlutPeripheralNumSpaceballButtons
| GlutPeripheralNumButtonBoxButtons
| GlutPeripheralNumDials
| GlutPeripheralNumTabletButtons
deriving (Show)
instance Enum GlutPeripheralProperties where
succ GlutPeripheralHasKeyboard = GlutPeripheralHasMouse
succ GlutPeripheralHasMouse = GlutPeripheralHasSpaceball
succ GlutPeripheralHasSpaceball = GlutPeripheralHasDialAndButtonBox
succ GlutPeripheralHasDialAndButtonBox = GlutPeripheralHasTablet
succ GlutPeripheralHasTablet = GlutPeripheralNumMouseButtons
succ GlutPeripheralNumMouseButtons = GlutPeripheralNumSpaceballButtons
succ GlutPeripheralNumSpaceballButtons = GlutPeripheralNumButtonBoxButtons
succ GlutPeripheralNumButtonBoxButtons = GlutPeripheralNumDials
succ GlutPeripheralNumDials = GlutPeripheralNumTabletButtons
succ GlutPeripheralNumTabletButtons = error "GlutPeripheralProperties.succ: GlutPeripheralNumTabletButtons has no successor"
pred GlutPeripheralHasMouse = GlutPeripheralHasKeyboard
pred GlutPeripheralHasSpaceball = GlutPeripheralHasMouse
pred GlutPeripheralHasDialAndButtonBox = GlutPeripheralHasSpaceball
pred GlutPeripheralHasTablet = GlutPeripheralHasDialAndButtonBox
pred GlutPeripheralNumMouseButtons = GlutPeripheralHasTablet
pred GlutPeripheralNumSpaceballButtons = GlutPeripheralNumMouseButtons
pred GlutPeripheralNumButtonBoxButtons = GlutPeripheralNumSpaceballButtons
pred GlutPeripheralNumDials = GlutPeripheralNumButtonBoxButtons
pred GlutPeripheralNumTabletButtons = GlutPeripheralNumDials
pred GlutPeripheralHasKeyboard = error "GlutPeripheralProperties.pred: GlutPeripheralHasKeyboard has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GlutPeripheralNumTabletButtons
fromEnum GlutPeripheralHasKeyboard = 600
fromEnum GlutPeripheralHasMouse = 601
fromEnum GlutPeripheralHasSpaceball = 602
fromEnum GlutPeripheralHasDialAndButtonBox = 603
fromEnum GlutPeripheralHasTablet = 604
fromEnum GlutPeripheralNumMouseButtons = 605
fromEnum GlutPeripheralNumSpaceballButtons = 606
fromEnum GlutPeripheralNumButtonBoxButtons = 607
fromEnum GlutPeripheralNumDials = 608
fromEnum GlutPeripheralNumTabletButtons = 609
toEnum 600 = GlutPeripheralHasKeyboard
toEnum 601 = GlutPeripheralHasMouse
toEnum 602 = GlutPeripheralHasSpaceball
toEnum 603 = GlutPeripheralHasDialAndButtonBox
toEnum 604 = GlutPeripheralHasTablet
toEnum 605 = GlutPeripheralNumMouseButtons
toEnum 606 = GlutPeripheralNumSpaceballButtons
toEnum 607 = GlutPeripheralNumButtonBoxButtons
toEnum 608 = GlutPeripheralNumDials
toEnum 609 = GlutPeripheralNumTabletButtons
toEnum unmatched = error ("GlutPeripheralProperties.toEnum: Cannot match " ++ show unmatched)
{-# LINE 293 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
type GlutCreateMenuPrim = CInt -> IO ()
type GlutSizePrim = CInt -> CInt -> IO ()
type GlutPositionPrim = CInt -> CInt -> IO ()
type GlutKeyboardPrim = CUChar -> CInt -> CInt -> IO ()
type GlutMousePrim = CInt -> CInt -> CInt -> CInt -> IO ()
type GlutEntryPrim = CInt -> IO ()
type GlutVisibilityPrim = CInt -> IO ()
type GlutTimerPrim = CInt -> IO ()
type GlutMenuStatePrim = CInt -> IO ()
type GlutMenuStatusPrim = CInt -> CInt -> CInt -> IO ()
type GlutSpecialPrim = CInt -> CInt -> CInt -> IO ()
data GlutWindow = GlutWindow { windowNumber :: CInt } deriving (Eq, Show)
data GlutMenu = GlutMenu { menuNumber :: CInt } deriving (Eq, Show)
glutCursorFullCrossHair :: GlutCursor
glutCursorFullCrossHair = GlutCursorCrosshair
data GLUTproc = GLUTproc ((C2HSImp.FunPtr (IO ()))) deriving Show
foreign import ccall "wrapper"
mkGlutCreateMenuPtr :: GlutCreateMenuPrim -> IO (FunPtr GlutCreateMenuPrim)
foreign import ccall "wrapper"
mkGlutSizeFPrim:: GlutSizePrim -> IO (FunPtr GlutSizePrim)
foreign import ccall "wrapper"
mkGlutPositionFPrim:: GlutPositionPrim -> IO (FunPtr GlutPositionPrim)
foreign import ccall "wrapper"
mkGlutKeyboardFPrim:: GlutKeyboardPrim -> IO (FunPtr GlutKeyboardPrim)
foreign import ccall "wrapper"
mkGlutMousePrim:: GlutMousePrim -> IO (FunPtr GlutMousePrim)
foreign import ccall "wrapper"
mkGlutEntryPrim:: GlutEntryPrim -> IO (FunPtr GlutEntryPrim)
foreign import ccall "wrapper"
mkGlutVisibilityPrim:: GlutVisibilityPrim -> IO (FunPtr GlutVisibilityPrim)
foreign import ccall "wrapper"
mkGlutTimerPtr :: GlutTimerPrim -> IO (FunPtr GlutTimerPrim)
foreign import ccall "wrapper"
mkGlutMenuStatePrim:: GlutMenuStatePrim -> IO (FunPtr GlutMenuStatePrim)
foreign import ccall "wrapper"
mkGlutMenuStatusPrim:: GlutMenuStatusPrim -> IO (FunPtr GlutMenuStatusPrim)
foreign import ccall "wrapper"
mkGlutSpecialPrim:: GlutMenuStatusPrim -> IO (FunPtr GlutMenuStatusPrim)
toGlutCreateMenuPrim :: (IO ()) -> IO (FunPtr GlutCreateMenuPrim)
toGlutCreateMenuPrim f = mkGlutCreateMenuPtr (\_ -> f)
toGlutSizePrim :: (Size -> IO ()) -> IO (FunPtr GlutSizePrim)
toGlutSizePrim sizeF = mkGlutSizeFPrim (\w' h' ->
let s = Size (Width (fromIntegral w')) (Height (fromIntegral h'))
in sizeF s
)
toGlutPositionPrim :: (Position -> IO ()) -> IO (FunPtr GlutPositionPrim)
toGlutPositionPrim positionF = mkGlutPositionFPrim (\x' y' ->
let p = Position (X (fromIntegral x')) (Y (fromIntegral y'))
in positionF p
)
toGlutKeyboardPrim :: (Char -> Position -> IO ()) -> IO (FunPtr GlutKeyboardPrim)
toGlutKeyboardPrim keyboardF = mkGlutKeyboardFPrim (\k' x' y' ->
let p = Position (X (fromIntegral x')) (Y (fromIntegral y'))
in
keyboardF (castCUCharToChar k') p
)
toGlutMousePrim :: (MouseButton -> GlutUpDown -> Position -> IO ()) -> IO (FunPtr GlutMousePrim)
toGlutMousePrim mouseF = mkGlutMousePrim (\mb' downup x' y' ->
let p = Position (X (fromIntegral x')) (Y (fromIntegral y'))
in mouseF (cToEnum mb') (cToEnum downup) p
)
toGlutEntryPrim :: (GlutEnteredLeft -> IO ()) -> IO (FunPtr GlutEntryPrim)
toGlutEntryPrim f = mkGlutEntryPrim (\entry' -> f (toEnum (fromIntegral entry')))
toGlutVisibilityPrim :: (GlutVisibility -> IO ()) -> IO (FunPtr GlutVisibilityPrim)
toGlutVisibilityPrim f = mkGlutVisibilityPrim (\entry' -> f (toEnum (fromIntegral entry')))
toGlutTimerPrim :: (IO ()) -> IO (FunPtr GlutTimerPrim)
toGlutTimerPrim f = mkGlutTimerPtr (\_ -> f)
toGlutMenuStatePrim :: (GlutMenuState -> IO ()) -> IO (FunPtr GlutMenuStatePrim)
toGlutMenuStatePrim f = mkGlutMenuStatePrim (\ms' -> f (toEnum (fromIntegral ms')))
toGlutMenuStatusPrim :: (GlutMenuState -> Position -> IO ()) -> IO (FunPtr GlutMenuStatusPrim)
toGlutMenuStatusPrim f = mkGlutMenuStatusPrim (\ms' x' y' ->
let p = Position (X (fromIntegral x')) (Y (fromIntegral y'))
in f (toEnum (fromIntegral ms')) p
)
toGlutSpecialPrim :: (GlutKeyboardCodes -> Position -> IO ()) -> IO (FunPtr GlutSpecialPrim)
toGlutSpecialPrim f = mkGlutSpecialPrim (\k' x' y' ->
let p = Position (X (fromIntegral x')) (Y (fromIntegral y'))
in f (toEnum (fromIntegral k')) p
)
glutInitDisplayMode :: (GlutDisplayMode) -> IO ()
glutInitDisplayMode a1 =
let {a1' = cFromEnum a1} in
glutInitDisplayMode'_ a1' >>
return ()
{-# LINE 397 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutInitWindowPosition' :: (CInt) -> (CInt) -> IO ()
glutInitWindowPosition' a1 a2 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
glutInitWindowPosition''_ a1' a2' >>
return ()
{-# LINE 398 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutInitWindowPosition :: Position -> IO ()
glutInitWindowPosition (Position (X x) (Y y)) = glutInitWindowPosition' (fromIntegral x) (fromIntegral y)
glutInitWindowSize' :: (CInt) -> (CInt) -> IO ()
glutInitWindowSize' a1 a2 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
glutInitWindowSize''_ a1' a2' >>
return ()
{-# LINE 401 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutInitWindowSize :: Size -> IO ()
glutInitWindowSize (Size (Width w) (Height h)) = glutInitWindowSize' (fromIntegral w) (fromIntegral h)
glutMainLoop :: IO ()
glutMainLoop =
glutMainLoop'_ >>
return ()
{-# LINE 404 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutCreateWindow' :: (CString) -> IO ((GlutWindow))
glutCreateWindow' a1 =
(flip ($)) a1 $ \a1' ->
glutCreateWindow''_ a1' >>= \res ->
let {res' = GlutWindow res} in
return (res')
{-# LINE 405 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutCreateWindow :: T.Text -> IO GlutWindow
glutCreateWindow t = copyTextToCString t >>= glutCreateWindow'
glutCreateSubWindow' :: (GlutWindow) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ((GlutWindow))
glutCreateSubWindow' a1 a2 a3 a4 a5 =
let {a1' = windowNumber a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
let {a5' = fromIntegral a5} in
glutCreateSubWindow''_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = GlutWindow res} in
return (res')
{-# LINE 408 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutCreateSubWindow :: GlutWindow -> Rectangle -> IO GlutWindow
glutCreateSubWindow glutWindow (Rectangle (Position (X x) (Y y)) (Size (Width w) (Height h))) =
glutCreateSubWindow' glutWindow x y w h
glutDestroyWindow :: (GlutWindow) -> IO ()
glutDestroyWindow a1 =
let {a1' = windowNumber a1} in
glutDestroyWindow'_ a1' >>
return ()
{-# LINE 412 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutPostRedisplay :: IO ()
glutPostRedisplay =
glutPostRedisplay'_ >>
return ()
{-# LINE 413 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutPostWindowRedisplay :: (GlutWindow) -> IO ()
glutPostWindowRedisplay a1 =
let {a1' = windowNumber a1} in
glutPostWindowRedisplay'_ a1' >>
return ()
{-# LINE 414 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSwapBuffers :: IO ()
glutSwapBuffers =
glutSwapBuffers'_ >>
return ()
{-# LINE 415 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutGetWindow :: IO ((GlutWindow))
glutGetWindow =
glutGetWindow'_ >>= \res ->
let {res' = GlutWindow res} in
return (res')
{-# LINE 416 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSetWindow :: (GlutWindow) -> IO ()
glutSetWindow a1 =
let {a1' = windowNumber a1} in
glutSetWindow'_ a1' >>
return ()
{-# LINE 417 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSetWindowTitle' :: (CString) -> IO ()
glutSetWindowTitle' a1 =
(flip ($)) a1 $ \a1' ->
glutSetWindowTitle''_ a1' >>
return ()
{-# LINE 418 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSetWindowTitle :: T.Text -> IO ()
glutSetWindowTitle t = copyTextToCString t >>= glutSetWindowTitle'
glutSetIconTitle' :: (CString) -> IO ()
glutSetIconTitle' a1 =
(flip ($)) a1 $ \a1' ->
glutSetIconTitle''_ a1' >>
return ()
{-# LINE 421 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSetIconTitle :: T.Text -> IO ()
glutSetIconTitle t = copyTextToCString t >>= glutSetIconTitle'
glutPositionWindow' :: (Int) -> (Int) -> IO ()
glutPositionWindow' a1 a2 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
glutPositionWindow''_ a1' a2' >>
return ()
{-# LINE 424 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutPositionWindow :: Position -> IO ()
glutPositionWindow (Position (X x) (Y y)) = glutPositionWindow' x y
glutReshapeWindow' :: (Int) -> (Int) -> IO ()
glutReshapeWindow' a1 a2 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
glutReshapeWindow''_ a1' a2' >>
return ()
{-# LINE 427 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutReshapeWindow :: Size -> IO ()
glutReshapeWindow (Size (Width w) (Height h)) = glutReshapeWindow' w h
glutPopWindow :: IO ()
glutPopWindow =
glutPopWindow'_ >>
return ()
{-# LINE 430 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutPushWindow :: IO ()
glutPushWindow =
glutPushWindow'_ >>
return ()
{-# LINE 431 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutIconifyWindow :: IO ()
glutIconifyWindow =
glutIconifyWindow'_ >>
return ()
{-# LINE 432 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutShowWindow :: IO ()
glutShowWindow =
glutShowWindow'_ >>
return ()
{-# LINE 433 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutHideWindow :: IO ()
glutHideWindow =
glutHideWindow'_ >>
return ()
{-# LINE 434 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutFullScreen :: IO ()
glutFullScreen =
glutFullScreen'_ >>
return ()
{-# LINE 435 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSetCursor :: (GlutCursor) -> IO ()
glutSetCursor a1 =
let {a1' = cFromEnum a1} in
glutSetCursor'_ a1' >>
return ()
{-# LINE 436 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWarpPointer' :: (Int) -> (Int) -> IO ()
glutWarpPointer' a1 a2 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
glutWarpPointer''_ a1' a2' >>
return ()
{-# LINE 437 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWarpPointer :: Position -> IO ()
glutWarpPointer (Position (X x) (Y y)) = glutWarpPointer' x y
glutEstablishOverlay :: IO ()
glutEstablishOverlay =
glutEstablishOverlay'_ >>
return ()
{-# LINE 440 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutRemoveOverlay :: IO ()
glutRemoveOverlay =
glutRemoveOverlay'_ >>
return ()
{-# LINE 441 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutUseLayer :: (Word32) -> IO ()
glutUseLayer a1 =
let {a1' = fromIntegral a1} in
glutUseLayer'_ a1' >>
return ()
{-# LINE 442 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutPostOverlayRedisplay :: IO ()
glutPostOverlayRedisplay =
glutPostOverlayRedisplay'_ >>
return ()
{-# LINE 443 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutShowOverlay :: IO ()
glutShowOverlay =
glutShowOverlay'_ >>
return ()
{-# LINE 444 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutHideOverlay :: IO ()
glutHideOverlay =
glutHideOverlay'_ >>
return ()
glutCreateMenu' :: (FunPtr GlutCreateMenuPrim) -> IO ()
glutCreateMenu' a1 =
let {a1' = id a1} in
glutCreateMenu''_ a1' >>
return ()
glutCreateMenu :: IO () -> IO ()
glutCreateMenu f = (toGlutCreateMenuPrim f) >>= glutCreateMenu'
glutDestroyMenu :: (GlutMenu) -> IO ()
glutDestroyMenu a1 =
let {a1' = menuNumber a1} in
glutDestroyMenu'_ a1' >>
return ()
{-# LINE 449 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutGetMenu :: IO ((GlutMenu))
glutGetMenu =
glutGetMenu'_ >>= \res ->
let {res' = GlutMenu res} in
return (res')
glutSetMenu :: (GlutMenu) -> IO ()
glutSetMenu a1 =
let {a1' = menuNumber a1} in
glutSetMenu'_ a1' >>
return ()
{-# LINE 451 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutAddMenuEntry' :: (CString) -> (Int) -> IO ()
glutAddMenuEntry' a1 a2 =
(flip ($)) a1 $ \a1' ->
let {a2' = fromIntegral a2} in
glutAddMenuEntry''_ a1' a2' >>
return ()
glutAddMenuEntry :: T.Text -> IO ()
glutAddMenuEntry l = copyTextToCString l >>= \l' -> glutAddMenuEntry' l' 0
glutAddSubMenu' :: (CString) -> (GlutMenu) -> IO ()
glutAddSubMenu' a1 a2 =
(flip ($)) a1 $ \a1' ->
let {a2' = menuNumber a2} in
glutAddSubMenu''_ a1' a2' >>
return ()
glutAddSubMenu :: T.Text -> GlutMenu -> IO ()
glutAddSubMenu t mn = copyTextToCString t >>= \t' -> glutAddSubMenu' t' mn
glutChangeToMenuEntry' :: (Int) -> (CString) -> (Int) -> IO ()
glutChangeToMenuEntry' a1 a2 a3 =
let {a1' = fromIntegral a1} in
(flip ($)) a2 $ \a2' ->
let {a3' = fromIntegral a3} in
glutChangeToMenuEntry''_ a1' a2' a3' >>
return ()
glutChangeToMenuEntry :: Int -> T.Text -> IO ()
glutChangeToMenuEntry index label = copyTextToCString label >>= \l -> glutChangeToMenuEntry' index l 0
glutChangeToSubMenu' :: (Int) -> (CString) -> (GlutMenu) -> IO ()
glutChangeToSubMenu' a1 a2 a3 =
let {a1' = fromIntegral a1} in
(flip ($)) a2 $ \a2' ->
let {a3' = menuNumber a3} in
glutChangeToSubMenu''_ a1' a2' a3' >>
return ()
{-# LINE 461 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutChangeToSubMenu :: Int -> T.Text -> GlutMenu -> IO ()
glutChangeToSubMenu i t m = copyTextToCString t >>= \t' -> glutChangeToSubMenu' i t' m
glutRemoveMenuItem :: (Int) -> IO ()
glutRemoveMenuItem a1 =
let {a1' = fromIntegral a1} in
glutRemoveMenuItem'_ a1' >>
return ()
{-# LINE 464 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutAttachMenu :: (GlutMenu) -> IO ()
glutAttachMenu a1 =
let {a1' = menuNumber a1} in
glutAttachMenu'_ a1' >>
return ()
{-# LINE 465 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutDetachMenu :: (GlutMenu) -> IO ()
glutDetachMenu a1 =
let {a1' = menuNumber a1} in
glutDetachMenu'_ a1' >>
return ()
{-# LINE 466 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutDisplayFunc' :: (FunPtr GlobalCallback) -> IO ()
glutDisplayFunc' a1 =
let {a1' = id a1} in
glutDisplayFunc''_ a1' >>
return ()
{-# LINE 467 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutDisplayFunc :: (IO ()) -> IO ()
glutDisplayFunc f = (mkGlobalCallbackPtr f) >>= glutDisplayFunc'
glutReshapeFunc' :: (FunPtr GlutSizePrim) -> IO ()
glutReshapeFunc' a1 =
let {a1' = id a1} in
glutReshapeFunc''_ a1' >>
return ()
{-# LINE 470 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutReshapeFunc :: (Size -> IO ()) -> IO ()
glutReshapeFunc f = toGlutSizePrim f >>= glutReshapeFunc'
glutKeyboardFunc' :: (FunPtr GlutKeyboardPrim) -> IO ()
glutKeyboardFunc' a1 =
let {a1' = id a1} in
glutKeyboardFunc''_ a1' >>
return ()
{-# LINE 473 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutKeyboardFunc :: (Char -> Position -> IO ()) -> IO ()
glutKeyboardFunc f = toGlutKeyboardPrim f >>= glutKeyboardFunc'
glutMouseFunc' :: (FunPtr GlutMousePrim) -> IO ()
glutMouseFunc' a1 =
let {a1' = id a1} in
glutMouseFunc''_ a1' >>
return ()
{-# LINE 476 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutMouseFunc :: (MouseButton -> GlutUpDown -> Position -> IO ()) -> IO ()
glutMouseFunc f = toGlutMousePrim f >>= glutMouseFunc'
glutMotionFunc' :: (FunPtr GlutPositionPrim) -> IO ()
glutMotionFunc' a1 =
let {a1' = id a1} in
glutMotionFunc''_ a1' >>
return ()
{-# LINE 479 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutMotionFunc :: (Position -> IO ()) -> IO ()
glutMotionFunc f = toGlutPositionPrim f >>= glutMotionFunc'
glutPassiveMotionFunc' :: (FunPtr GlutPositionPrim) -> IO ()
glutPassiveMotionFunc' a1 =
let {a1' = id a1} in
glutPassiveMotionFunc''_ a1' >>
return ()
{-# LINE 482 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutPassiveMotionFunc :: (Position -> IO ()) -> IO ()
glutPassiveMotionFunc f = toGlutPositionPrim f >>= glutPassiveMotionFunc'
glutEntryFunc' :: (FunPtr GlutEntryPrim) -> IO ()
glutEntryFunc' a1 =
let {a1' = id a1} in
glutEntryFunc''_ a1' >>
return ()
{-# LINE 485 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutEntryFunc :: (GlutEnteredLeft -> IO ()) -> IO ()
glutEntryFunc f = toGlutEntryPrim f >>= glutEntryFunc'
glutVisibilityFunc' :: (FunPtr GlutVisibilityPrim) -> IO ()
glutVisibilityFunc' a1 =
let {a1' = id a1} in
glutVisibilityFunc''_ a1' >>
return ()
{-# LINE 488 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutVisibilityFunc :: (GlutVisibility -> IO ()) -> IO ()
glutVisibilityFunc f = toGlutVisibilityPrim f >>= glutVisibilityFunc'
glutIdleFunc' :: (FunPtr GlobalCallback) -> IO ()
glutIdleFunc' a1 =
let {a1' = id a1} in
glutIdleFunc''_ a1' >>
return ()
{-# LINE 491 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutIdleFunc :: (IO ()) -> IO ()
glutIdleFunc f = (mkGlobalCallbackPtr f) >>= glutIdleFunc'
glutTimerFunc' :: (Int) -> (FunPtr GlutTimerPrim) -> (Int) -> IO ()
glutTimerFunc' a1 a2 a3 =
let {a1' = fromIntegral a1} in
let {a2' = id a2} in
let {a3' = fromIntegral a3} in
glutTimerFunc''_ a1' a2' a3' >>
return ()
{-# LINE 494 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutTimerFunc :: Int -> (IO ()) -> IO ()
glutTimerFunc timeout' f = (toGlutTimerPrim f) >>= \f' -> glutTimerFunc' timeout' f' 0
glutMenuStateFunc' :: (FunPtr GlutMenuStatePrim) -> IO ()
glutMenuStateFunc' a1 =
let {a1' = id a1} in
glutMenuStateFunc''_ a1' >>
return ()
{-# LINE 497 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutMenuStateFunc :: (GlutMenuState -> IO()) -> IO ()
glutMenuStateFunc f = toGlutMenuStatePrim f >>= glutMenuStateFunc'
glutMenuStatusFunc' :: (FunPtr GlutMenuStatusPrim) -> IO ()
glutMenuStatusFunc' a1 =
let {a1' = id a1} in
glutMenuStatusFunc''_ a1' >>
return ()
{-# LINE 500 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutMenuStatusFunc :: (GlutMenuState -> Position -> IO ()) -> IO ()
glutMenuStatusFunc f = toGlutMenuStatusPrim f >>= glutMenuStatusFunc'
glutSpecialFunc' :: (FunPtr GlutSpecialPrim) -> IO ()
glutSpecialFunc' a1 =
let {a1' = id a1} in
glutSpecialFunc''_ a1' >>
return ()
{-# LINE 503 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSpecialFunc :: (GlutKeyboardCodes -> Position -> IO ()) -> IO ()
glutSpecialFunc f = toGlutSpecialPrim f >>= glutSpecialFunc'
glutOverlayDisplayFunc' :: (FunPtr GlobalCallback) -> IO ()
glutOverlayDisplayFunc' a1 =
let {a1' = id a1} in
glutOverlayDisplayFunc''_ a1' >>
return ()
{-# LINE 506 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutOverlayDisplayFunc :: (IO ()) -> IO ()
glutOverlayDisplayFunc f = mkGlobalCallbackPtr f >>= glutOverlayDisplayFunc'
glutGet' :: (Word32) -> IO ((Int))
glutGet' a1 =
let {a1' = fromIntegral a1} in
glutGet''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 509 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutGetWindowRectangle :: IO Rectangle
glutGetWindowRectangle = do
x <- glutGet' (fromIntegral (fromEnum GlutWindowX))
y <- glutGet' (fromIntegral (fromEnum GlutWindowY))
w <- glutGet' (fromIntegral (fromEnum GlutWindowWidth))
h <- glutGet' (fromIntegral (fromEnum GlutWindowHeight))
return (toRectangle (x,y,w,h))
glutGetWindowParent :: IO (Maybe GlutWindow)
glutGetWindowParent :: IO (Maybe GlutWindow)
glutGetWindowParent = do
Int
n <- Word32 -> IO Int
glutGet' (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (GlutWindowProperties -> Int
forall a. Enum a => a -> Int
fromEnum GlutWindowProperties
GlutWindowParent))
Maybe GlutWindow -> IO (Maybe GlutWindow)
forall (m :: * -> *) a. Monad m => a -> m a
return (if (Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0) then Maybe GlutWindow
forall a. Maybe a
Nothing else (GlutWindow -> Maybe GlutWindow
forall a. a -> Maybe a
Just (CInt -> GlutWindow
GlutWindow (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n))))
glutGetScreenSize :: IO Size
glutGetScreenSize :: IO Size
glutGetScreenSize = do
Int
w <- Word32 -> IO Int
glutGet' (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (GlutWindowProperties -> Int
forall a. Enum a => a -> Int
fromEnum GlutWindowProperties
GlutScreenWidth))
Int
h <- Word32 -> IO Int
glutGet' (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (GlutWindowProperties -> Int
forall a. Enum a => a -> Int
fromEnum GlutWindowProperties
GlutScreenHeight))
Size -> IO Size
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int, Int) -> Size
toSize (Int
w,Int
h))
glutGetMenuNumItems :: IO Int
= Word32 -> IO Int
glutGet' (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (GlutMenuItems -> Int
forall a. Enum a => a -> Int
fromEnum GlutMenuItems
GlutMenuNumItems))
glutDisplayModePossible :: IO Bool
glutDisplayModePossible :: IO Bool
glutDisplayModePossible = Word32 -> IO Int
glutGet' (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (GlutConstants -> Int
forall a. Enum a => a -> Int
fromEnum GlutConstants
GlutDisplayModePossible)) IO Int -> (Int -> IO Bool) -> IO Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> (Int -> Bool) -> Int -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Bool
forall a. (Eq a, Num a, Ord a) => a -> Bool
cToBool
glutWindowBufferSize :: IO Int
glutWindowBufferSize :: IO Int
glutWindowBufferSize = Word32 -> IO Int
glutGet' (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (GlutWindowProperties -> Int
forall a. Enum a => a -> Int
fromEnum GlutWindowProperties
GlutWindowBufferSize))
glutVersion :: IO Int
glutVersion :: IO Int
glutVersion = Word32 -> IO Int
glutGet' (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (GlutConstants -> Int
forall a. Enum a => a -> Int
fromEnum GlutConstants
GlutVersion))
glutOther :: Word32 -> IO Int
glutOther :: Word32 -> IO Int
glutOther constant :: Word32
constant = Word32 -> IO Int
glutGet' (Word32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
constant)
glutLayerGet' :: (Word32) -> IO ((Int))
glutLayerGet' :: Word32 -> IO Int
glutLayerGet' a1 :: Word32
a1 =
let {a1' :: CUInt
a1' = Word32 -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
a1} in
CUInt -> IO CInt
glutLayerGet''_ CUInt
a1' IO CInt -> (CInt -> IO Int) -> IO Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \res :: CInt
res ->
let {res' :: Int
res' = fromIntegral res} in
Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
res')
{-# LINE 536 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutOverlayPossible :: IO Bool
glutOverlayPossible = glutLayerGet' (fromIntegral (fromEnum GlutOverlayPossible)) >>= return . cToBool
glutTransparencyIndex :: IO Int
glutTransparencyIndex = glutLayerGet' (fromIntegral (fromEnum GlutTransparentIndex))
glutNormalDamaged :: IO Bool
glutNormalDamaged = glutLayerGet' (fromIntegral (fromEnum GlutNormalDamaged)) >>= return . cToBool
glutOverlayDamaged :: IO Bool
glutOverlayDamaged :: IO Bool
glutOverlayDamaged = Word32 -> IO Int
glutLayerGet' (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (GlutConstants -> Int
forall a. Enum a => a -> Int
fromEnum GlutConstants
GlutOverlayDamaged)) IO Int -> (Int -> IO Bool) -> IO Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> (Int -> Bool) -> Int -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Bool
forall a. (Eq a, Num a, Ord a) => a -> Bool
cToBool
glutDeviceGet' :: (Word32) -> IO ((Int))
glutDeviceGet' :: Word32 -> IO Int
glutDeviceGet' a1 :: Word32
a1 =
let {a1' :: CUInt
a1' = Word32 -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
a1} in
CUInt -> IO CInt
glutDeviceGet''_ CUInt
a1' IO CInt -> (CInt -> IO Int) -> IO Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \res :: CInt
res ->
let {res' :: Int
res' = CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
res} in
Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
res')
{-# LINE 545 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutHasKeyboard :: IO Bool
glutHasKeyboard = glutDeviceGet' (fromIntegral (fromEnum GlutPeripheralHasKeyboard)) >>= return . cToBool
glutHasMouse :: IO Bool
glutHasMouse = glutDeviceGet' (fromIntegral (fromEnum GlutPeripheralHasMouse)) >>= return . cToBool
glutNumMouseButtons :: IO Int
glutNumMouseButtons = glutDeviceGet' (fromIntegral (fromEnum GlutPeripheralNumMouseButtons))
glutGetModifiers :: IO (([EventState]))
glutGetModifiers :: IO [EventState]
glutGetModifiers =
IO CInt
glutGetModifiers'_ IO CInt -> (CInt -> IO [EventState]) -> IO [EventState]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \res :: CInt
res ->
let {res' :: [EventState]
res' = CInt -> [EventState]
extractEventStates CInt
res} in
[EventState] -> IO [EventState]
forall (m :: * -> *) a. Monad m => a -> m a
return ([EventState]
res')
{-# LINE 552 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWireSphere :: (Double) -> (Int32) -> (Int32) -> IO ()
glutWireSphere :: Double -> Int32 -> Int32 -> IO ()
glutWireSphere a1 :: Double
a1 a2 :: Int32
a2 a3 :: Int32
a3 =
let {a1' :: CDouble
a1' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
a1} in
let {a2' :: CInt
a2' = Int32 -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
a2} in
let {a3' :: CInt
a3' = Int32 -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
a3} in
CDouble -> GlutSizePrim
glutWireSphere'_ CDouble
a1' CInt
a2' CInt
a3' IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# LINE 565 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSolidSphere :: (Double) -> (Int32) -> (Int32) -> IO ()
glutSolidSphere a1 a2 a3 =
let {a1' = realToFrac a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
glutSolidSphere'_ a1' a2' a3' >>
return ()
{-# LINE 566 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWireCone :: (Double) -> (Double) -> (Int32) -> (Int32) -> IO ()
glutWireCone a1 a2 a3 a4 =
let {a1' = realToFrac a1} in
let {a2' = realToFrac a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
glutWireCone'_ a1' a2' a3' a4' >>
return ()
{-# LINE 567 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSolidCone :: (Double) -> (Double) -> (Int32) -> (Int32) -> IO ()
glutSolidCone a1 a2 a3 a4 =
let {a1' = realToFrac a1} in
let {a2' = realToFrac a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
glutSolidCone'_ a1' a2' a3' a4' >>
return ()
{-# LINE 568 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWireCube :: (Double) -> IO ()
glutWireCube a1 =
let {a1' = realToFrac a1} in
glutWireCube'_ a1' >>
return ()
{-# LINE 569 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSolidCube :: (Double) -> IO ()
glutSolidCube a1 =
let {a1' = realToFrac a1} in
glutSolidCube'_ a1' >>
return ()
{-# LINE 570 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWireTorus :: (Double) -> (Double) -> (Int32) -> (Int32) -> IO ()
glutWireTorus a1 a2 a3 a4 =
let {a1' = realToFrac a1} in
let {a2' = realToFrac a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
glutWireTorus'_ a1' a2' a3' a4' >>
return ()
{-# LINE 571 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSolidTorus :: (Double) -> (Double) -> (Int32) -> (Int32) -> IO ()
glutSolidTorus a1 a2 a3 a4 =
let {a1' = realToFrac a1} in
let {a2' = realToFrac a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
glutSolidTorus'_ a1' a2' a3' a4' >>
return ()
{-# LINE 572 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWireDodecahedron :: IO ()
glutWireDodecahedron =
glutWireDodecahedron'_ >>
return ()
{-# LINE 573 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSolidDodecahedron :: IO ()
glutSolidDodecahedron =
glutSolidDodecahedron'_ >>
return ()
{-# LINE 574 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWireTeapot :: (Double) -> IO ()
glutWireTeapot a1 =
let {a1' = realToFrac a1} in
glutWireTeapot'_ a1' >>
return ()
{-# LINE 575 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSolidTeapot :: (Double) -> IO ()
glutSolidTeapot a1 =
let {a1' = realToFrac a1} in
glutSolidTeapot'_ a1' >>
return ()
{-# LINE 576 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWireOctahedron :: IO ()
glutWireOctahedron =
glutWireOctahedron'_ >>
return ()
{-# LINE 577 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSolidOctahedron :: IO ()
glutSolidOctahedron =
glutSolidOctahedron'_ >>
return ()
{-# LINE 578 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWireTetrahedron :: IO ()
glutWireTetrahedron =
glutWireTetrahedron'_ >>
return ()
{-# LINE 579 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSolidTetrahedron :: IO ()
glutSolidTetrahedron =
glutSolidTetrahedron'_ >>
return ()
{-# LINE 580 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutWireIcosahedron :: IO ()
glutWireIcosahedron =
glutWireIcosahedron'_ >>
return ()
{-# LINE 581 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
glutSolidIcosahedron :: IO ()
glutSolidIcosahedron =
glutSolidIcosahedron'_ >>
return ()
{-# LINE 582 "src/Graphics/UI/FLTK/LowLevel/Glut.chs" #-}
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutInitDisplayMode"
glutInitDisplayMode'_ :: (C2HSImp.CUInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutInitWindowPosition"
glutInitWindowPosition''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutInitWindowSize"
glutInitWindowSize''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutMainLoop"
glutMainLoop'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutCreateWindow"
glutCreateWindow''_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutCreateSubWindow"
glutCreateSubWindow''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutDestroyWindow"
glutDestroyWindow'_ :: (C2HSImp.CInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutPostRedisplay"
glutPostRedisplay'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutPostWindowRedisplay"
glutPostWindowRedisplay'_ :: (C2HSImp.CInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSwapBuffers"
glutSwapBuffers'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutGetWindow"
glutGetWindow'_ :: (IO C2HSImp.CInt)
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSetWindow"
glutSetWindow'_ :: (C2HSImp.CInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSetWindowTitle"
glutSetWindowTitle''_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSetIconTitle"
glutSetIconTitle''_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutPositionWindow"
glutPositionWindow''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutReshapeWindow"
glutReshapeWindow''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutPopWindow"
glutPopWindow'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutPushWindow"
glutPushWindow'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutIconifyWindow"
glutIconifyWindow'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutShowWindow"
glutShowWindow'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutHideWindow"
glutHideWindow'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutFullScreen"
glutFullScreen'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSetCursor"
glutSetCursor'_ :: (C2HSImp.CInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutWarpPointer"
glutWarpPointer''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutEstablishOverlay"
glutEstablishOverlay'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutRemoveOverlay"
glutRemoveOverlay'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutUseLayer"
glutUseLayer'_ :: (C2HSImp.CUInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutPostOverlayRedisplay"
glutPostOverlayRedisplay'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutShowOverlay"
glutShowOverlay'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutHideOverlay"
glutHideOverlay'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutCreateMenu"
:: ((C2HSImp.FunPtr (C2HSImp.CInt -> (IO ()))) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutDestroyMenu"
:: (C2HSImp.CInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutGetMenu"
:: (IO C2HSImp.CInt)
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSetMenu"
:: (C2HSImp.CInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutAddMenuEntry"
:: ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutAddSubMenu"
:: ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutChangeToMenuEntry"
:: (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutChangeToSubMenu"
:: (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutRemoveMenuItem"
:: (C2HSImp.CInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutAttachMenu"
:: (C2HSImp.CInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutDetachMenu"
:: (C2HSImp.CInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutDisplayFunc"
glutDisplayFunc''_ :: ((C2HSImp.FunPtr (IO ())) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutReshapeFunc"
glutReshapeFunc''_ :: ((C2HSImp.FunPtr (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutKeyboardFunc"
glutKeyboardFunc''_ :: ((C2HSImp.FunPtr (C2HSImp.CUChar -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutMouseFunc"
glutMouseFunc''_ :: ((C2HSImp.FunPtr (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutMotionFunc"
glutMotionFunc''_ :: ((C2HSImp.FunPtr (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutPassiveMotionFunc"
glutPassiveMotionFunc''_ :: ((C2HSImp.FunPtr (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutEntryFunc"
glutEntryFunc''_ :: ((C2HSImp.FunPtr (C2HSImp.CInt -> (IO ()))) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutVisibilityFunc"
glutVisibilityFunc''_ :: ((C2HSImp.FunPtr (C2HSImp.CInt -> (IO ()))) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutIdleFunc"
glutIdleFunc''_ :: ((C2HSImp.FunPtr (IO ())) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutTimerFunc"
glutTimerFunc''_ :: (C2HSImp.CUInt -> ((C2HSImp.FunPtr (C2HSImp.CInt -> (IO ()))) -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutMenuStateFunc"
:: ((C2HSImp.FunPtr (C2HSImp.CInt -> (IO ()))) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutMenuStatusFunc"
:: ((C2HSImp.FunPtr (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSpecialFunc"
glutSpecialFunc''_ :: ((C2HSImp.FunPtr (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutOverlayDisplayFunc"
glutOverlayDisplayFunc''_ :: ((C2HSImp.FunPtr (IO ())) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutGet"
glutGet''_ :: (C2HSImp.CUInt -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutLayerGet"
glutLayerGet''_ :: (C2HSImp.CUInt -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutDeviceGet"
glutDeviceGet''_ :: (C2HSImp.CUInt -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutGetModifiers"
glutGetModifiers'_ :: (IO C2HSImp.CInt)
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutWireSphere"
glutWireSphere'_ :: (C2HSImp.CDouble -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSolidSphere"
glutSolidSphere'_ :: (C2HSImp.CDouble -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutWireCone"
glutWireCone'_ :: (C2HSImp.CDouble -> (C2HSImp.CDouble -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSolidCone"
glutSolidCone'_ :: (C2HSImp.CDouble -> (C2HSImp.CDouble -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutWireCube"
glutWireCube'_ :: (C2HSImp.CDouble -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSolidCube"
glutSolidCube'_ :: (C2HSImp.CDouble -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutWireTorus"
glutWireTorus'_ :: (C2HSImp.CDouble -> (C2HSImp.CDouble -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSolidTorus"
glutSolidTorus'_ :: (C2HSImp.CDouble -> (C2HSImp.CDouble -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutWireDodecahedron"
glutWireDodecahedron'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSolidDodecahedron"
glutSolidDodecahedron'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutWireTeapot"
glutWireTeapot'_ :: (C2HSImp.CDouble -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSolidTeapot"
glutSolidTeapot'_ :: (C2HSImp.CDouble -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutWireOctahedron"
glutWireOctahedron'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSolidOctahedron"
glutSolidOctahedron'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutWireTetrahedron"
glutWireTetrahedron'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSolidTetrahedron"
glutSolidTetrahedron'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutWireIcosahedron"
glutWireIcosahedron'_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Glut.chs.h flc_glutSolidIcosahedron"
glutSolidIcosahedron'_ :: (IO ())