Copyright | (c) Sven Panne 2002-2019 |
---|---|
License | BSD3 |
Maintainer | Sven Panne <svenpanne@gmail.com> |
Stability | stable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This module corresponds to section 2.11 (Coordinate Transformations) of the OpenGL 2.1 specs.
Synopsis
- depthRange :: StateVar (GLclampd, GLclampd)
- data Position = Position !GLint !GLint
- data Size = Size !GLsizei !GLsizei
- viewport :: StateVar (Position, Size)
- maxViewportDims :: GettableStateVar Size
- data MatrixMode
- matrixMode :: StateVar MatrixMode
- data MatrixOrder
- class Storable c => MatrixComponent c where
- class Matrix m where
- withNewMatrix :: MatrixComponent c => MatrixOrder -> (Ptr c -> IO ()) -> IO (m c)
- withMatrix :: MatrixComponent c => m c -> (MatrixOrder -> Ptr c -> IO a) -> IO a
- newMatrix :: MatrixComponent c => MatrixOrder -> [c] -> IO (m c)
- getMatrixComponents :: MatrixComponent c => MatrixOrder -> m c -> IO [c]
- matrix :: (Matrix m, MatrixComponent c) => Maybe MatrixMode -> StateVar (m c)
- multMatrix :: (Matrix m, MatrixComponent c) => m c -> IO ()
- data GLmatrix a
- loadIdentity :: IO ()
- ortho :: GLdouble -> GLdouble -> GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ()
- frustum :: GLdouble -> GLdouble -> GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ()
- depthClamp :: StateVar Capability
- activeTexture :: StateVar TextureUnit
- preservingMatrix :: IO a -> IO a
- unsafePreservingMatrix :: IO a -> IO a
- stackDepth :: Maybe MatrixMode -> GettableStateVar GLsizei
- maxStackDepth :: MatrixMode -> GettableStateVar GLsizei
- rescaleNormal :: StateVar Capability
- normalize :: StateVar Capability
- data Plane a = Plane !a !a !a !a
- data TextureCoordName
- data TextureGenMode
- textureGenMode :: TextureCoordName -> StateVar (Maybe TextureGenMode)
Controlling the Viewport
depthRange :: StateVar (GLclampd, GLclampd) Source #
After clipping and division by w, depth coordinates range from -1 to 1,
corresponding to the near and far clipping planes. depthRange
specifies a
linear mapping of the normalized depth coordinates in this range to window
depth coordinates. Regardless of the actual depth buffer implementation,
window coordinate depth values are treated as though they range from 0
through 1 (like color components). Thus, the values accepted by depthRange
are both clamped to this range before they are accepted.
The initial setting of (0, 1) maps the near plane to 0 and the far plane to 1. With this mapping, the depth buffer range is fully utilized.
It is not necessary that the near value be less than the far value. Reverse mappings such as (1, 0) are acceptable.
A 2-dimensional position, measured in pixels.
A 2-dimensional size, measured in pixels.
viewport :: StateVar (Position, Size) Source #
Controls the affine transformation from normalized device coordinates to window coordinates. The viewport state variable consists of the coordinates (x, y) of the lower left corner of the viewport rectangle, (in pixels, initial value (0,0)), and the size (width, height) of the viewport. When a GL context is first attached to a window, width and height are set to the dimensions of that window.
Let (xnd, ynd) be normalized device coordinates. Then the window coordinates (xw, yw) are computed as follows:
xw = (xnd + 1) (width / 2) + x
yw = (ynd + 1) (heigth / 2) + y
Viewport width and height are silently clamped to a range that depends on the
implementation, see maxViewportDims
.
maxViewportDims :: GettableStateVar Size Source #
The implementation-dependent maximum viewport width and height.
Matrices
data MatrixMode Source #
A matrix stack.
Modelview GLsizei | The modelview matrix stack of the specified vertex unit. |
Projection | The projection matrix stack. |
Texture | The texture matrix stack. |
Color | The color matrix stack. |
MatrixPalette | The matrix palette stack. |
Instances
Eq MatrixMode Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans (==) :: MatrixMode -> MatrixMode -> Bool # (/=) :: MatrixMode -> MatrixMode -> Bool # | |
Ord MatrixMode Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans compare :: MatrixMode -> MatrixMode -> Ordering # (<) :: MatrixMode -> MatrixMode -> Bool # (<=) :: MatrixMode -> MatrixMode -> Bool # (>) :: MatrixMode -> MatrixMode -> Bool # (>=) :: MatrixMode -> MatrixMode -> Bool # max :: MatrixMode -> MatrixMode -> MatrixMode # min :: MatrixMode -> MatrixMode -> MatrixMode # | |
Show MatrixMode Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans showsPrec :: Int -> MatrixMode -> ShowS # show :: MatrixMode -> String # showList :: [MatrixMode] -> ShowS # |
matrixMode :: StateVar MatrixMode Source #
Controls which matrix stack is the target for subsequent matrix operations.
The initial value is (Modelview
0).
data MatrixOrder Source #
Instances
Eq MatrixOrder Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans (==) :: MatrixOrder -> MatrixOrder -> Bool # (/=) :: MatrixOrder -> MatrixOrder -> Bool # | |
Ord MatrixOrder Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans compare :: MatrixOrder -> MatrixOrder -> Ordering # (<) :: MatrixOrder -> MatrixOrder -> Bool # (<=) :: MatrixOrder -> MatrixOrder -> Bool # (>) :: MatrixOrder -> MatrixOrder -> Bool # (>=) :: MatrixOrder -> MatrixOrder -> Bool # max :: MatrixOrder -> MatrixOrder -> MatrixOrder # min :: MatrixOrder -> MatrixOrder -> MatrixOrder # | |
Show MatrixOrder Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans showsPrec :: Int -> MatrixOrder -> ShowS # show :: MatrixOrder -> String # showList :: [MatrixOrder] -> ShowS # |
class Storable c => MatrixComponent c where Source #
getMatrix, loadMatrix, loadTransposeMatrix, multMatrix_, multTransposeMatrix, getUniformv, uniformMatrix4v, rotate, translate, scale
Instances
MatrixComponent GLfloat Source # | |
Defined in Graphics.Rendering.OpenGL.GL.MatrixComponent getMatrix :: GetPNameMatrix p => p -> Ptr GLfloat -> IO () loadMatrix :: Ptr GLfloat -> IO () loadTransposeMatrix :: Ptr GLfloat -> IO () multMatrix_ :: Ptr GLfloat -> IO () multTransposeMatrix :: Ptr GLfloat -> IO () getUniformv :: GLuint -> GLint -> Ptr GLfloat -> IO () uniformMatrix4v :: GLint -> GLsizei -> GLboolean -> Ptr GLfloat -> IO () rotate :: GLfloat -> Vector3 GLfloat -> IO () Source # | |
MatrixComponent GLdouble Source # | |
Defined in Graphics.Rendering.OpenGL.GL.MatrixComponent getMatrix :: GetPNameMatrix p => p -> Ptr GLdouble -> IO () loadMatrix :: Ptr GLdouble -> IO () loadTransposeMatrix :: Ptr GLdouble -> IO () multMatrix_ :: Ptr GLdouble -> IO () multTransposeMatrix :: Ptr GLdouble -> IO () getUniformv :: GLuint -> GLint -> Ptr GLdouble -> IO () uniformMatrix4v :: GLint -> GLsizei -> GLboolean -> Ptr GLdouble -> IO () rotate :: GLdouble -> Vector3 GLdouble -> IO () Source # |
Nothing
withNewMatrix :: MatrixComponent c => MatrixOrder -> (Ptr c -> IO ()) -> IO (m c) Source #
Create a new matrix of the given order (containing undefined elements) and call the action to fill it with 4x4 elements.
withMatrix :: MatrixComponent c => m c -> (MatrixOrder -> Ptr c -> IO a) -> IO a Source #
Call the action with the given matrix. Note: The action is not allowed to modify the matrix elements!
newMatrix :: MatrixComponent c => MatrixOrder -> [c] -> IO (m c) Source #
getMatrixComponents :: MatrixComponent c => MatrixOrder -> m c -> IO [c] Source #
Instances
Matrix GLmatrix Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans withNewMatrix :: MatrixComponent c => MatrixOrder -> (Ptr c -> IO ()) -> IO (GLmatrix c) Source # withMatrix :: MatrixComponent c => GLmatrix c -> (MatrixOrder -> Ptr c -> IO a) -> IO a Source # newMatrix :: MatrixComponent c => MatrixOrder -> [c] -> IO (GLmatrix c) Source # getMatrixComponents :: MatrixComponent c => MatrixOrder -> GLmatrix c -> IO [c] Source # |
matrix :: (Matrix m, MatrixComponent c) => Maybe MatrixMode -> StateVar (m c) Source #
multMatrix :: (Matrix m, MatrixComponent c) => m c -> IO () Source #
Instances
Matrix GLmatrix Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans withNewMatrix :: MatrixComponent c => MatrixOrder -> (Ptr c -> IO ()) -> IO (GLmatrix c) Source # withMatrix :: MatrixComponent c => GLmatrix c -> (MatrixOrder -> Ptr c -> IO a) -> IO a Source # newMatrix :: MatrixComponent c => MatrixOrder -> [c] -> IO (GLmatrix c) Source # getMatrixComponents :: MatrixComponent c => MatrixOrder -> GLmatrix c -> IO [c] Source # | |
Eq (GLmatrix a) Source # | |
Ord (GLmatrix a) Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans | |
Show (GLmatrix a) Source # | |
MatrixComponent a => Uniform (GLmatrix a) Source # | Note: |
Defined in Graphics.Rendering.OpenGL.GL.Shaders.Uniform |
loadIdentity :: IO () Source #
preservingMatrix :: IO a -> IO a Source #
Push the current matrix stack down by one, duplicating the current matrix,
excute the given action, and pop the current matrix stack, replacing the
current matrix with the one below it on the stack (i.e. restoring it to its
previous state). The returned value is that of the given action. Note that
a round-trip to the server is probably required. For a more efficient
version, see unsafePreservingMatrix
.
unsafePreservingMatrix :: IO a -> IO a Source #
A more efficient, but potentially dangerous version of preservingMatrix
:
The given action is not allowed to throw an exception or change the
current matrix mode permanently.
Normal Transformation
rescaleNormal :: StateVar Capability Source #
If rescaleNormal
contains Enabled
, normal vectors specified with
normal
are scaled by a scaling
factor derived from the modelview matrix. rescaleNormal
requires that the
originally specified normals were of unit length, and that the modelview
matrix contains only uniform scales for proper results. The initial value of
rescaleNormal
is Disabled
.
Generating Texture Coordinates
Plane !a !a !a !a |
Instances
Eq a => Eq (Plane a) Source # | |
Ord a => Ord (Plane a) Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans | |
Show a => Show (Plane a) Source # | |
Storable a => Storable (Plane a) Source # | |
data TextureCoordName Source #
Instances
Eq TextureCoordName Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans (==) :: TextureCoordName -> TextureCoordName -> Bool # (/=) :: TextureCoordName -> TextureCoordName -> Bool # | |
Ord TextureCoordName Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans compare :: TextureCoordName -> TextureCoordName -> Ordering # (<) :: TextureCoordName -> TextureCoordName -> Bool # (<=) :: TextureCoordName -> TextureCoordName -> Bool # (>) :: TextureCoordName -> TextureCoordName -> Bool # (>=) :: TextureCoordName -> TextureCoordName -> Bool # max :: TextureCoordName -> TextureCoordName -> TextureCoordName # min :: TextureCoordName -> TextureCoordName -> TextureCoordName # | |
Show TextureCoordName Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans showsPrec :: Int -> TextureCoordName -> ShowS # show :: TextureCoordName -> String # showList :: [TextureCoordName] -> ShowS # |
data TextureGenMode Source #
Instances
Eq TextureGenMode Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans (==) :: TextureGenMode -> TextureGenMode -> Bool # (/=) :: TextureGenMode -> TextureGenMode -> Bool # | |
Ord TextureGenMode Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans compare :: TextureGenMode -> TextureGenMode -> Ordering # (<) :: TextureGenMode -> TextureGenMode -> Bool # (<=) :: TextureGenMode -> TextureGenMode -> Bool # (>) :: TextureGenMode -> TextureGenMode -> Bool # (>=) :: TextureGenMode -> TextureGenMode -> Bool # max :: TextureGenMode -> TextureGenMode -> TextureGenMode # min :: TextureGenMode -> TextureGenMode -> TextureGenMode # | |
Show TextureGenMode Source # | |
Defined in Graphics.Rendering.OpenGL.GL.CoordTrans showsPrec :: Int -> TextureGenMode -> ShowS # show :: TextureGenMode -> String # showList :: [TextureGenMode] -> ShowS # |