module Graphics.Rendering.OpenGL.GL.Clipping (
ClipPlaneName(..), clipPlane, maxClipPlanes
) where
import Data.StateVar
import Foreign.Marshal.Alloc
import Foreign.Marshal.Utils
import Foreign.Ptr
import Foreign.Storable
import Graphics.Rendering.OpenGL.GL.Capability
import Graphics.Rendering.OpenGL.GL.CoordTrans
import Graphics.Rendering.OpenGL.GL.QueryUtils
import Graphics.Rendering.OpenGL.GLU.ErrorsInternal
import Graphics.GL
newtype ClipPlaneName = ClipPlaneName GLsizei
deriving ( Eq, Ord, Show )
clipPlane :: ClipPlaneName -> StateVar (Maybe (Plane GLdouble))
clipPlane name =
makeStateVarMaybe
(return $ nameToCap name)
(alloca $ \buf -> do
clipPlaneAction name $ flip glGetClipPlane $ castPtr buf
peek buf)
(\plane -> with plane $ clipPlaneAction name . flip glClipPlane . castPtr)
nameToCap :: ClipPlaneName -> EnableCap
nameToCap (ClipPlaneName i) = CapClipPlane i
clipPlaneAction :: ClipPlaneName -> (GLenum -> IO ()) -> IO ()
clipPlaneAction (ClipPlaneName i) act =
maybe recordInvalidEnum act (clipPlaneIndexToEnum i)
maxClipPlanes :: GettableStateVar GLsizei
maxClipPlanes = makeGettableStateVar (getSizei1 id GetMaxClipPlanes)