summaryrefslogtreecommitdiff
path: root/src/LambdaCube/GL/Data.hs
diff options
context:
space:
mode:
authorJoe Crayne <joe@jerkface.net>2019-04-30 12:00:46 -0400
committerJoe Crayne <joe@jerkface.net>2019-05-06 19:44:07 -0400
commitfcf51c414e06ff24e7f2ec350ef0cef20b6238d2 (patch)
tree2a22c83cd3bd333667a729b66e13488816c93acd /src/LambdaCube/GL/Data.hs
parent154b25e0ad8a8ecedb02876215d29c12e87e6c93 (diff)
TextureCube support.
Diffstat (limited to 'src/LambdaCube/GL/Data.hs')
-rw-r--r--src/LambdaCube/GL/Data.hs81
1 files changed, 79 insertions, 2 deletions
diff --git a/src/LambdaCube/GL/Data.hs b/src/LambdaCube/GL/Data.hs
index 56955d1..952e14a 100644
--- a/src/LambdaCube/GL/Data.hs
+++ b/src/LambdaCube/GL/Data.hs
@@ -1,3 +1,4 @@
1{-# LANGUAGE LambdaCase #-}
1module LambdaCube.GL.Data where 2module LambdaCube.GL.Data where
2 3
3import Control.Applicative 4import Control.Applicative
@@ -15,6 +16,7 @@ import qualified Data.Vector.Storable as SV
15--import Control.DeepSeq 16--import Control.DeepSeq
16 17
17import Graphics.GL.Core33 18import Graphics.GL.Core33
19import Graphics.GL.EXT.TextureFilterAnisotropic
18import Data.Word 20import Data.Word
19import Codec.Picture 21import Codec.Picture
20import Codec.Picture.Types 22import Codec.Picture.Types
@@ -59,7 +61,10 @@ arrayType buf arrIdx = arrType $! bufArrays buf V.! arrIdx
59 61
60-- Texture 62-- Texture
61disposeTexture :: TextureData -> IO () 63disposeTexture :: TextureData -> IO ()
62disposeTexture (TextureData to) = withArray [to] $ glDeleteTextures 1 64disposeTexture (Texture2DName to) = withArray [to] $ glDeleteTextures 1
65
66disposeTextureCube :: TextureCubeData -> IO ()
67disposeTextureCube (TextureCubeName to) = withArray [to] $ glDeleteTextures 1
63 68
64-- FIXME: Temporary implemenation 69-- FIXME: Temporary implemenation
65uploadTexture2DToGPU :: DynamicImage -> IO TextureData 70uploadTexture2DToGPU :: DynamicImage -> IO TextureData
@@ -104,4 +109,76 @@ uploadTexture2DToGPU' isFiltered isSRGB isMip isClamped bitmap' = do
104 _ -> error "unsupported texture format!" 109 _ -> error "unsupported texture format!"
105 glTexImage2D GL_TEXTURE_2D 0 internalFormat (fromIntegral w) (fromIntegral h) 0 dataFormat GL_UNSIGNED_BYTE $ castPtr ptr 110 glTexImage2D GL_TEXTURE_2D 0 internalFormat (fromIntegral w) (fromIntegral h) 0 dataFormat GL_UNSIGNED_BYTE $ castPtr ptr
106 when isMip $ glGenerateMipmap GL_TEXTURE_2D 111 when isMip $ glGenerateMipmap GL_TEXTURE_2D
107 return $ TextureData to 112 return $ Texture2DName to
113
114
115compatibleImage :: DynamicImage -> DynamicImage
116compatibleImage bitmap' = case bitmap' of
117 ImageRGB8 i@(Image w h _) -> bitmap'
118 ImageRGBA8 i@(Image w h _) -> bitmap'
119 ImageYCbCr8 i@(Image w h _) -> ImageRGB8 $ convertImage i
120 di -> ImageRGBA8 $ convertRGBA8 di
121
122imageFormat :: Bool {- ^ is SRGB -} -> Int {- number of channels -} -> (GLenum,GLint) {- ^ dataFormat,internalFormat -}
123imageFormat isSRGB 3 = (GL_RGB , fromIntegral $ if isSRGB then GL_SRGB8 else GL_RGB8)
124imageFormat isSRGB 4 = (GL_RGBA, fromIntegral $ if isSRGB then GL_SRGB8_ALPHA8 else GL_RGBA8)
125imageFormat isSRGB _ = error "unsupported texture format!"
126
127uploadCubeMapToGPU :: [DynamicImage] -> IO TextureCubeData
128uploadCubeMapToGPU = uploadCubeMapToGPU' True False True True
129
130
131uploadCubeMapToGPU' :: Bool -> Bool -> Bool -> Bool -> [DynamicImage] -> IO TextureCubeData
132uploadCubeMapToGPU' isFiltered isSRGB isMip isClamped (bitmap':bitmaps') = do
133 -- The six faces of the cube are represented by six subtextures that must be square and of the same size.
134
135 let (bitmap,side):bitmaps =
136 zip (map compatibleImage (bitmap':bitmaps'))
137 [GL_TEXTURE_CUBE_MAP_POSITIVE_X .. GL_TEXTURE_CUBE_MAP_NEGATIVE_Z]
138
139 glPixelStorei GL_UNPACK_ALIGNMENT 1
140 to <- alloca $! \pto -> glGenTextures 1 pto >> peek pto
141 glBindTexture GL_TEXTURE_CUBE_MAP to
142 let (width,height) = bitmapSize bitmap
143 bitmapSize (ImageRGB8 (Image w h _)) = (w,h)
144 bitmapSize (ImageRGBA8 (Image w h _)) = (w,h)
145 bitmapSize _ = error "unsupported image type :("
146 withBitmap (ImageRGB8 (Image w h v)) f = SV.unsafeWith v $ f (w,h) 3 0
147 withBitmap (ImageRGBA8 (Image w h v)) f = SV.unsafeWith v $ f (w,h) 4 0
148 withBitmap _ _ = error "unsupported image type :("
149 texFilter = if isFiltered then GL_LINEAR else GL_NEAREST
150 wrapMode = case isClamped of
151 True -> GL_CLAMP_TO_EDGE
152 False -> GL_REPEAT
153 (minFilter,maxLevel) = case isFiltered && isMip of
154 False -> (texFilter,0)
155 True -> (GL_LINEAR_MIPMAP_LINEAR, floor $ log (fromIntegral $ max width height) / log 2)
156
157 glTexParameteri GL_TEXTURE_CUBE_MAP GL_TEXTURE_MIN_FILTER $ fromIntegral minFilter
158 glTexParameteri GL_TEXTURE_CUBE_MAP GL_TEXTURE_MAG_FILTER $ fromIntegral texFilter
159 glGetEXTTextureFilterAnisotropic >>= \case
160 False -> return ()
161 True -> alloca $ \ptr -> do
162 poke ptr 0
163 glGetIntegerv GL_MAX_TEXTURE_MAX_ANISOTROPY_EXT ptr
164 max <- peek ptr
165 glTexParameteri GL_TEXTURE_CUBE_MAP GL_TEXTURE_MAX_ANISOTROPY_EXT max
166 glTexParameteri GL_TEXTURE_CUBE_MAP GL_TEXTURE_WRAP_S $ fromIntegral wrapMode
167 glTexParameteri GL_TEXTURE_CUBE_MAP GL_TEXTURE_WRAP_T $ fromIntegral wrapMode
168
169 glTexParameteri GL_TEXTURE_CUBE_MAP GL_TEXTURE_BASE_LEVEL 0
170 glTexParameteri GL_TEXTURE_CUBE_MAP GL_TEXTURE_MAX_LEVEL $ fromIntegral maxLevel
171 fmt <- withBitmap bitmap $ \(w,h) nchn 0 ptr -> do
172 let fmt@(dataFormat,internalFormat) = imageFormat isSRGB nchn
173 -- Graphics.GL.Core42.glTexStorage2D GL_TEXTURE_CUBE_MAP (maxLevel + 1) internalFormat (fromIntegral w) (fromIntegral h)
174 -- glTexImage2D :: MonadIO m => GLenum -> GLint -> GLint -> GLsizei -> GLsizei -> GLint -> GLenum -> GLenum -> Ptr a -> m ()
175 glTexImage2D side 0 internalFormat (fromIntegral w) (fromIntegral h) 0 dataFormat GL_UNSIGNED_BYTE $ castPtr ptr
176 return (fmt,(w,h))
177 forM_ bitmaps $ \(b,targ) -> withBitmap b $ \wh nchn 0 ptr -> do
178 let (dataFormat,internalFormat) = case imageFormat isSRGB nchn of { x | (x,wh)==fmt -> x; _ -> error "incompatible images" }
179 glTexImage2D targ 0 internalFormat (fromIntegral $ fst wh) (fromIntegral $ snd wh) 0 dataFormat GL_UNSIGNED_BYTE $ castPtr ptr
180
181 when isMip $ glGenerateMipmap GL_TEXTURE_CUBE_MAP
182 -- A GL_INVALID_OPERATION error will be generated if target is GL_TEXTURE_CUBE_MAP,
183 -- and not all cube-map faces are initialized and consistent.
184 return $ TextureCubeName to