lowgl-0.4.0.1: Basic gl wrapper and reference

Safe HaskellNone
LanguageHaskell2010

Graphics.GL.Low.Texture

Contents

Synopsis

Documentation

Textures are objects that contain image data that can be sampled by a shader. An obvious application of this is texture mapping, but there are many other uses for textures. The image data doesn't have to be an image at all, it can represent anything.

Each sampler uniform in your shader points to a texture unit (zero by default). This texture unit is where it will read texture data from. To assign a texture to a texture unit, use setActiveTextureUnit then bind a texture. This will not only bind it to the relevant texture binding target but also to the active texture unit. You can change which unit a sampler points to by setting it using the setUniform1i command.

You can avoid dealing with active texture units if theres only one sampler because the default unit is zero.

newTexture2D :: Storable a => Vector a -> (Int, Int) -> ImageFormat -> IO Texture Source

Create a new 2D texture from raw image data, its dimensions, and the assumed image format. The dimensions should be powers of 2.

newCubeMap :: Storable a => Cube (Vector a, (Int, Int)) -> ImageFormat -> IO Texture Source

Create a new cubemap texture from six raw data sources. Each side will have the same format.

newEmptyTexture2D :: Int -> Int -> ImageFormat -> IO Texture Source

Create an empty texture with the specified dimensions and format.

newEmptyCubeMap :: Int -> Int -> ImageFormat -> IO Texture Source

Create a cubemap texture where each of the six sides has the specified dimensions and format.

deleteTexture :: Texture -> IO () Source

Delete a texture.

bindTexture2D :: Texture -> IO () Source

Bind a 2D texture to the 2D texture binding target and the currently active texture unit.

bindTextureCubeMap :: Texture -> IO () Source

Bind a cubemap texture to the cubemap texture binding target and the currently active texture unit.

setActiveTextureUnit :: Int -> IO () Source

Set the active texture unit. The default is zero.

setTex2DFiltering :: Filtering -> IO () Source

Set the filtering for the 2D texture currently bound to the 2D texture binding target.

setCubeMapFiltering :: Filtering -> IO () Source

Set the filtering for the cubemap texture currently bound to the cubemap texture binding target.

setTex2DWrapping :: Wrapping -> IO () Source

Set the wrapping mode for the 2D texture currently bound to the 2D texture binding target.

setCubeMapWrapping :: Wrapping -> IO () Source

Set the wrapping mode for the cubemap texture currently bound to the cubemap texture binding target. Because no filtering occurs between cube faces you probably want ClampToEdge.

data Texture Source

Handle to a texture object. It may be a Tex2D or a cubemap.

data Filtering Source

Texture filtering modes.

Constructors

Nearest

No interpolation.

Linear

Linear interpolation.

data Wrapping Source

Texture wrapping modes.

Constructors

Repeat

Tile the texture past the boundary.

MirroredRepeat

Tile the texture but mirror every other tile.

ClampToEdge

Use the edge color for anything past the boundary.

Example

This example loads a PNG file with JuicyPixels and displays the image on a square. Since the window is not square and no aspect ratio transformation was applied, the picture is squished.

module Main where

import Control.Monad.Loops (whileM_)
import qualified Data.Vector.Storable as V
import Codec.Picture
import Data.Word

import qualified Graphics.UI.GLFW as GLFW
import Linear
import Graphics.GL.Low

main = do
  GLFW.init
  GLFW.windowHint (GLFW.WindowHint'ContextVersionMajor 3)
  GLFW.windowHint (GLFW.WindowHint'ContextVersionMinor 2)
  GLFW.windowHint (GLFW.WindowHint'OpenGLForwardCompat True)
  GLFW.windowHint (GLFW.WindowHint'OpenGLProfile GLFW.OpenGLProfile'Core)
  mwin <- GLFW.createWindow 640 480 "Texture" Nothing Nothing
  case mwin of
    Nothing  -> putStrLn "createWindow failed"
    Just win -> do
      GLFW.makeContextCurrent (Just win)
      GLFW.swapInterval 1
      (vao, prog, texture) <- setup
      whileM_ (not <$> GLFW.windowShouldClose win) $ do
        GLFW.pollEvents
        draw vao prog texture
        GLFW.swapBuffers win

setup = do
  -- establish a VAO
  vao <- newVAO
  bindVAO vao
  -- load the shader
  vsource <- readFile "texture.vert"
  fsource <- readFile "texture.frag"
  prog <- newProgram vsource fsource
  useProgram prog
  -- load the vertices
  let blob = V.fromList -- a quad has four vertices
        [ -0.5, -0.5, 0, 1
        , -0.5,  0.5, 0, 0
        ,  0.5, -0.5, 1, 1
        ,  0.5,  0.5, 1, 0 ] :: V.Vector Float
  vbo <- newBufferObject blob StaticDraw
  bindVBO vbo
  setVertexLayout [ Attrib "position" 2 GLFloat
                  , Attrib "texcoord" 2 GLFloat ]
  -- load the element array to draw a quad with two triangles
  indices <- newElementArray (V.fromList [0,1,2,3,2,1] :: V.Vector Word8) StaticDraw
  bindElementArray indices
  -- load the texture with JuicyPixels
  let fromRight (Right x) = x
  ImageRGBA8 (Image w h image) <- fromRight <$> readImage "logo.png"
  texture <- newTexture2D image (w,h) RGBA 
  setTex2DFiltering Linear
  return (vao, prog, texture)

draw vao prog texture = do
  clearColorBuffer (0.5, 0.5, 0.5)
  bindVAO vao
  useProgram prog
  bindTexture2D texture
  drawIndexedTriangles 6 UByteIndices

The vertex shader for this example looks like

#version 150
in vec2 position;
in vec2 texcoord;
out vec2 Texcoord;
void main()
{
    gl_Position = vec4(position, 0.0, 1.0);
    Texcoord = texcoord;
}

And the fragment shader looks like

#version 150
in vec2 Texcoord;
out vec4 outColor;
uniform sampler2D tex;
void main()
{
  outColor = texture(tex, Texcoord);
}