-------------------------------------------------------------------------------- -- | -- Module : Graphics.Rendering.OGL.GL.Polygons -- Copyright : (c) Sven Panne 2002-2006 -- License : BSD-style (see the file libraries/OpenGL/LICENSE) -- -- Maintainer : sven.panne@aedion.de -- Stability : stable -- Portability : portable -- -- This module corresponds to section 3.5 (Polygons) of the OpenGL 2.1 specs. -- -------------------------------------------------------------------------------- module Graphics.Rendering.OGL.GL.Polygons ( polygonSmooth, cullFace, PolygonStipple(..), GLpolygonstipple, polygonStipple, PolygonMode(..), polygonMode, polygonOffset, polygonOffsetPoint, polygonOffsetLine, polygonOffsetFill ) where import Control.Monad ( liftM2 ) import Foreign.ForeignPtr ( ForeignPtr, mallocForeignPtrArray, withForeignPtr ) import Foreign.Marshal.Array ( allocaArray, withArray, peekArray, pokeArray ) import Foreign.Ptr ( Ptr ) import Graphics.Rendering.OGL.Monad import Graphics.Rendering.OGL.GL.Capability ( EnableCap(CapPolygonSmooth,CapCullFace,CapPolygonStipple, CapPolygonOffsetPoint,CapPolygonOffsetLine,CapPolygonOffsetFill), makeCapability, makeStateVarMaybe ) import Graphics.Rendering.OGL.GL.BasicTypes ( GLenum, GLubyte, GLfloat, Capability ) import Graphics.Rendering.OGL.GL.Face ( marshalFace, unmarshalFace ) import Graphics.Rendering.OGL.GL.Colors ( Face(..) ) import Graphics.Rendering.OGL.GL.PixelRectangles ( PixelStoreDirection(..), rowLength, skipRows, skipPixels ) import Graphics.Rendering.OGL.GL.PolygonMode ( PolygonMode(..), marshalPolygonMode, unmarshalPolygonMode ) import Graphics.Rendering.OGL.GL.QueryUtils ( GetPName(GetCullFaceMode,GetPolygonMode,GetPolygonOffsetFactor, GetPolygonOffsetUnits), getInteger2, getEnum1, getFloat1 ) import Graphics.Rendering.OGL.GL.SavingState ( ClientAttributeGroup(PixelStoreAttributes), preservingClientAttrib ) import Graphics.Rendering.OGL.GL.StateVar ( HasSetter(($=)), StateVar, makeStateVar ) -------------------------------------------------------------------------------- polygonSmooth :: StateVar Capability polygonSmooth = makeCapability CapPolygonSmooth -------------------------------------------------------------------------------- cullFace :: StateVar (Maybe Face) cullFace = makeStateVarMaybe (return CapCullFace) (getEnum1 unmarshalFace GetCullFaceMode) (glCullFace . marshalFace) foreign import CALLCONV unsafe "glCullFace" glCullFace :: GLenum -> IO () -------------------------------------------------------------------------------- numPolygonStippleBytes :: Int numPolygonStippleBytes = 128 -- 32x32 bits divided into GLubytes class PolygonStipple s where withNewPolygonStipple :: (Ptr GLubyte -> GL ()) -> GL s withPolygonStipple :: s -> (Ptr GLubyte -> GL a) -> GL a newPolygonStipple :: [GLubyte] -> GL s getPolygonStippleComponents :: s -> GL [GLubyte] withNewPolygonStipple act = liftIO . allocaArray numPolygonStippleBytes $ \p -> do runGL $ act p components <- peekArray numPolygonStippleBytes p runGL $ newPolygonStipple components withPolygonStipple s act = do components <- getPolygonStippleComponents s liftIO $ withArray components (runGL . act) newPolygonStipple components = withNewPolygonStipple $ liftIO . flip pokeArray (take numPolygonStippleBytes components) getPolygonStippleComponents s = withPolygonStipple s $ liftIO . peekArray numPolygonStippleBytes -------------------------------------------------------------------------------- data GLpolygonstipple = GLpolygonstipple (ForeignPtr GLubyte) deriving ( Eq, Ord, Show ) instance PolygonStipple GLpolygonstipple where withNewPolygonStipple f = liftIO $ do fp <- mallocForeignPtrArray numPolygonStippleBytes withForeignPtr fp (runGL . f) return $ GLpolygonstipple fp withPolygonStipple (GLpolygonstipple fp) f = liftIO $ withForeignPtr fp (runGL . f) -------------------------------------------------------------------------------- polygonStipple :: PolygonStipple s => StateVar (Maybe s) polygonStipple = makeStateVarMaybe (return CapPolygonStipple) (withoutGaps Pack . runGL $ withNewPolygonStipple glGetPolygonStipple) (\s -> withoutGaps Unpack . runGL $ withPolygonStipple s glPolygonStipple) -- Note: No need to set rowAlignment, our memory allocator always returns a -- region which is at least 8-byte aligned (the maximum) withoutGaps :: PixelStoreDirection -> IO a -> IO a withoutGaps direction action = runGL . preservingClientAttrib [ PixelStoreAttributes ] $ do rowLength direction $= 0 skipRows direction $= 0 skipPixels direction $= 0 (liftIO action) foreign import CALLCONV unsafe "glGetPolygonStipple" glGetPolygonStipple :: Ptr GLubyte -> GL () foreign import CALLCONV unsafe "glPolygonStipple" glPolygonStipple :: Ptr GLubyte -> GL () -------------------------------------------------------------------------------- polygonMode :: StateVar (PolygonMode, PolygonMode) polygonMode = makeStateVar getPolygonMode setPolygonMode getPolygonMode :: IO (PolygonMode, PolygonMode) getPolygonMode = getInteger2 (\front back -> (un front, un back)) GetPolygonMode where un = unmarshalPolygonMode . fromIntegral setPolygonMode :: (PolygonMode, PolygonMode) -> IO () setPolygonMode (front, back) = do glPolygonMode (marshalFace Front) (marshalPolygonMode front) glPolygonMode (marshalFace Back ) (marshalPolygonMode back ) foreign import CALLCONV unsafe "glPolygonMode" glPolygonMode :: GLenum -> GLenum -> IO () -------------------------------------------------------------------------------- polygonOffset :: StateVar (GLfloat, GLfloat) polygonOffset = makeStateVar (liftM2 (,) (getFloat1 id GetPolygonOffsetFactor) (getFloat1 id GetPolygonOffsetUnits)) (uncurry glPolygonOffset) foreign import CALLCONV unsafe "glPolygonOffset" glPolygonOffset :: GLfloat -> GLfloat -> IO () -------------------------------------------------------------------------------- polygonOffsetPoint :: StateVar Capability polygonOffsetPoint = makeCapability CapPolygonOffsetPoint polygonOffsetLine :: StateVar Capability polygonOffsetLine = makeCapability CapPolygonOffsetLine polygonOffsetFill :: StateVar Capability polygonOffsetFill = makeCapability CapPolygonOffsetFill