
Hi again Hector, On 11/07/10 16:30, Hector Guilarte wrote:
Hello Claude,
Sorry for the delay - some things came up.
My problem is everywhere hahaha. I haven't been able to do anything with textures, but those steps do sound like the way to go. Maybe if you could explain them a little bit more I'll do it, or maybe with the examples you mentioned I'll get it myself.
Ok, here is a dump of relevant portions of my code. They all require (and other imports are noted above the snippets): import Graphics.UI.GLUT
When you say 'load' is the hardest: In all the tutorials or codes I've seen, I haven't been able to find any function which has that kind of signature, but I really have no idea on how to do such function myself :s. I really thought maybe OpenGL provided some functions to do it...
The main problem is the variety of different image formats - most are
compressed which means using corresponding libraries to decompress them
- and even for uncompressed images they usually have a header with
useful information such as width, height, channels.
-- For a file containing raw RGBA pixels (1 byte per channel)
-- hardcoded to 1024x1024x4 widthXheightXchannels):
-- this actually does load + upload in one function
import Control.Monad(when)
import System.Exit(exitFailure)
import System.IO(withBinaryFile, IOMode(ReadMode), openBinaryFile, hGetBuf)
import Foreign.Marshal.Alloc(allocaBytes)
loadTexture :: FilePath -> IO TextureObject
loadTexture f = do
withBinaryFile f ReadMode $ \h -> do
let bytes = 1024 * 1024 * 4
allocaBytes bytes $ \pixels -> do
bytes' <- hGetBuf h pixels bytes
when (bytes' /= bytes) exitFailure
[tex] <- genObjectNames 1
texture Texture2D $= Enabled
textureBinding Texture2D $= Just tex
build2DMipmaps Texture2D RGBA' 1024 1024
(PixelData RGBA UnsignedByte pixels)
textureFilter Texture2D $= ((Linear', Just Linear'), Linear')
textureWrapMode Texture2D S $= (Repeated, ClampToEdge)
textureWrapMode Texture2D T $= (Repeated, ClampToEdge)
textureBinding Texture2D $= Nothing
texture Texture2D $= Disabled
return tex
-- To convert SVG via PNG via PPM/PGM to a suitable raw format I use
-- a simple bash script (I called it "svg2rgba.sh")
-- warning: this assumes that the SVG has width = height = 1024 pixels
-- the magic numbers are 3 * width * height and 1 * width * height
-- given "foo.svg", convert it to "foo.rgba" by running:
-- ./svg2rgba.sh foo
#!/bin/bash
SVGFILE="${1}.svg"
PNGFILE="${1}.png"
PPMFILE="${1}.ppm"
PGMFILE="${1}.pgm"
RGBFILE="${1}.rgb"
AFILE="${1}.a"
RGBAFILE="${1}.rgba"
rsvg "${SVGFILE}" "${PNGFILE}"
pngtopnm "${PNGFILE}" > "${PPMFILE}"
pngtopnm -alpha "${PNGFILE}" > "${PGMFILE}"
tail -c 3145728 "${PPMFILE}" > "${RGBFILE}"
tail -c 1048576 "${PGMFILE}" > "${AFILE}"
./interleave31 "${RGBFILE}" "${AFILE}" > "${RGBAFILE}"
rm -f "${PNGFILE}" "${PPMFILE}" "${PGMFILE}" "${RGBFILE}" "${AFILE}"
-- to interleave the raw data I use this C code
-- again hardcoded to width = height = 1024
-- error checking and speed leaves much to be desired
-- save as "interleave31.c"
-- compile with: gcc -o interleave31 interleave31.c
#include
upload :: .... -- upload to the Graphics Card? I've used OpenGL in C++ and adding a texture is so easy, Probably I did all 3 steps you mention, but I never really worried about them, I just did it without paying attention on what was happening underneath.
import Foreign.Ptr(Ptr()) import Foreign.Marshal.Alloc(mallocBytes) data Image = Image{ iWidth, iHeight, iChannels :: Int, iBuffer :: Ptr () } image :: Int -> Int -> Int -> IO Image image w h c | w > 0 && h > 0 && c > 0 = do b <- mallocBytes $ w * h * c return Image{ iWidth = w, iHeight = h, iChannels = c, iBuffer = b } | otherwise = error $ "Image.image: " ++ show [w,h,c] upload :: Image -> IO TextureObject upload i | iChannels i == 4 = do [tex] <- genObjectNames 1 texture Texture2D $= Enabled textureBinding Texture2D $= Just tex build2DMipmaps Texture2D RGBA' (fromIntegral $ iWidth i) (fromIntegral $ iHeight i) (PixelData RGBA UnsignedByte (iBuffer i)) textureFilter Texture2D $= ((Linear', Just Linear'), Linear') textureWrapMode Texture2D S $= (Repeated, ClampToEdge) textureWrapMode Texture2D T $= (Repeated, ClampToEdge) textureBinding Texture2D $= Nothing texture Texture2D $= Disabled return tex | otherwise = error $ "Image.upload: " ++ show (iChannels i) -- Should be simple to adapt the above to handle channels /= 4
draw :: ... This does sounds like what I used to do in C++ and it's what I was hoping to find in Haskell...
data Quad = Quad{ quadX, quadY, quadR :: GLdouble, quadT :: TextureObject } -- cannot rebind texture within renderPrimitive -- might be more efficient to use 1 large texture -- with subportions of that 1 texture for each quad drawQuad :: Quad -> IO () drawQuad Quad{ quadX = x0, quadY = y0, quadR = s, quadT = tex } = do let t x y = texCoord $ TexCoord2 (x :: GLdouble) (y :: GLdouble) v x y = vertex $ Vertex2 x y textureBinding Texture2D $= Just tex renderPrimitive Quads $ do color $ Color3 1 1 (1::GLdouble) t 0 1 >> v (x0 - s) (y0 + s) t 0 0 >> v (x0 - s) (y0 - s) t 1 0 >> v (x0 + s) (y0 - s) t 1 1 >> v (x0 + s) (y0 + s) drawQuads :: [Quad] -> IO () drawQuads qs = do blend $= Enabled blendFunc $= (SrcAlpha, OneMinusSrcAlpha) texture Texture2D $= Enabled mapM_ drawQuad qs textureBinding Texture2D $= Nothing texture Texture2D $= Disabled blend $= Disabled
Thank you,
Hoping this helps,
Hector Guilarte
Claude
On Sun, Jul 11, 2010 at 10:06 AM, Claude Heiland-Allen
mailto:claudiusmaximus@goto10.org> wrote: Hi Hector,
On 11/07/10 03:02, Hector Guilarte wrote: > I've been looking for a way to map a texture into a Quad primitive with > HOpenGL with no luck. [snip]
I'm having trouble understanding where your problem is.
There are three steps to texturing using an image file:
load :: FilePath -> IO Image -- read file to raw pixel buffer upload :: Image -> IO TextureObject -- upload to graphics card draw :: TextureObject -> IO () -- use the texture on something
where data Image = Image{ width, height, channels :: Int, pixels :: Ptr () }
Which step is problematic?
'load' is the hardest IMO, and doesn't have anything to do with OpenGL. 'upload' I would implement with 'build2DMipmaps' 'draw' is easy: bind the texture, add a 'texCoord' before each 'vertex'
I could provide some example code for 'upload' and 'draw' if you think it would help.
Claude -- http://claudiusmaximus.goto10.org
_______________________________________________ HOpenGL mailing list HOpenGL@haskell.org mailto:HOpenGL@haskell.org http://www.haskell.org/mailman/listinfo/hopengl