module Graphics.LambdaCube.RenderSystem.GL.GLUtils where import qualified Data.Set as Set import Data.Bits import Unsafe.Coerce import Graphics.Rendering.OpenGL (($=)) import qualified Graphics.Rendering.OpenGL as GL import Graphics.LambdaCube.Types import Graphics.LambdaCube.Math import Graphics.LambdaCube.Common import Graphics.LambdaCube.PixelFormat import Graphics.LambdaCube.Texture import Graphics.LambdaCube.BlendMode import Graphics.LambdaCube.HardwareBuffer import Graphics.LambdaCube.HardwareVertexBuffer import Graphics.LambdaCube.RenderSystemCapabilities import Graphics.LambdaCube.TextureUnitState toGLMatrix :: Matrix4 -> IO (GL.GLmatrix GL.GLfloat) toGLMatrix m = GL.newMatrix GL.ColumnMajor $ unsafeCoerce $ toListsMatrix4 m getGLUsage :: Usage -> GL.BufferUsage getGLUsage usage = case usage of { HBU_STATIC -> GL.StaticDraw ; HBU_STATIC_WRITE_ONLY -> GL.StaticDraw ; HBU_DYNAMIC -> GL.DynamicDraw ; HBU_DYNAMIC_WRITE_ONLY -> GL.DynamicDraw ; HBU_DYNAMIC_WRITE_ONLY_DISCARDABLE -> GL.StreamDraw ; _ -> GL.DynamicDraw } getGLType :: VertexElementType -> GL.DataType getGLType t = case t of { VET_FLOAT1 -> GL.Float ; VET_FLOAT2 -> GL.Float ; VET_FLOAT3 -> GL.Float ; VET_FLOAT4 -> GL.Float ; VET_SHORT1 -> GL.Short ; VET_SHORT2 -> GL.Short ; VET_SHORT3 -> GL.Short ; VET_SHORT4 -> GL.Short ; VET_COLOUR_ABGR -> GL.UnsignedByte ; VET_COLOUR_ARGB -> GL.UnsignedByte ; VET_UBYTE4 -> GL.UnsignedByte } getGLTextureTarget :: TextureType -> GL.TextureTarget getGLTextureTarget textureType = case textureType of { TEX_TYPE_1D -> GL.Texture1D ; TEX_TYPE_2D -> GL.Texture2D ; TEX_TYPE_3D -> GL.Texture3D ; TEX_TYPE_CUBE_MAP -> GL.TextureCubeMap } optionalPO2 :: RenderSystemCapabilities -> Int -> Int optionalPO2 rcaps value = case Set.member RSC_NON_POWER_OF_2_TEXTURES (rscCapabilities rcaps) of { True -> value ; False -> 2 ^ ( 1 + log2 (value-1) ) } where log2 n = case n of 0 -> -1 _ -> 1 + log2 (shiftR n 1) getMaxMipmaps :: Int -> Int -> Int -> PixelFormat -> Int getMaxMipmaps width height depth format = maximum [f width, f height, f depth] where f x = floor $ logBase 2 $ fromIntegral x {- size_t GLPixelUtil::getMaxMipmaps(size_t width, size_t height, size_t depth, PixelFormat format) { size_t count = 0; do { if(width>1) width = width/2; if(height>1) height = height/2; if(depth>1) depth = depth/2; count ++; } while(!(width == 1 && height == 1 && depth == 1)); return count; } -} -- TODO getNativeFormat :: TextureType -> PixelFormat -> Bool -> PixelFormat getNativeFormat ttype format isTarget = PF_R8G8B8 {- PixelFormat GLTextureManager::getNativeFormat(TextureType ttype, PixelFormat format, int usage) { // Adjust requested parameters to capabilities const RenderSystemCapabilities *caps = Root::getSingleton().getRenderSystem()->getCapabilities(); // Check compressed texture support // if a compressed format not supported, revert to PF_A8R8G8B8 if(PixelUtil::isCompressed(format) && !caps->hasCapability( RSC_TEXTURE_COMPRESSION_DXT )) { return PF_A8R8G8B8; } // if floating point textures not supported, revert to PF_A8R8G8B8 if(PixelUtil::isFloatingPoint(format) && !caps->hasCapability( RSC_TEXTURE_FLOAT )) { return PF_A8R8G8B8; } // Check if this is a valid rendertarget format if( usage & TU_RENDERTARGET ) { /// Get closest supported alternative /// If mFormat is supported it's returned return GLRTTManager::getSingleton().getSupportedAlternative(format); } // Supported return format; } PixelFormat GLRTTManager::getSupportedAlternative(PixelFormat format) { if(checkFormat(format)) return format; /// Find first alternative PixelComponentType pct = PixelUtil::getComponentType(format); switch(pct) { case PCT_BYTE: format = PF_A8R8G8B8; break; case PCT_SHORT: format = PF_SHORT_RGBA; break; case PCT_FLOAT16: format = PF_FLOAT16_RGBA; break; case PCT_FLOAT32: format = PF_FLOAT32_RGBA; break; case PCT_COUNT: break; } if(checkFormat(format)) return format; /// If none at all, return to default return PF_A8R8G8B8; } -} getGLInternalFormat :: PixelFormat -> Bool -> GL.PixelInternalFormat getGLInternalFormat mFormat hwGamma = case mFormat of { PF_L8 -> GL.Luminance8 ; PF_L16 -> GL.Luminance16 ; PF_A8 -> GL.Alpha8 ; PF_A4L4 -> GL.Luminance4Alpha4 ; PF_BYTE_LA -> GL.Luminance8Alpha8 ; PF_R3G3B2 -> GL.R3G3B2 ; PF_A1R5G5B5 -> GL.RGB5A1 ; PF_R5G6B5 -> GL.RGB5 ; PF_B5G6R5 -> GL.RGB5 ; PF_A4R4G4B4 -> GL.RGBA4 ; PF_R8G8B8 -> if hwGamma then GL.SRGB8 else GL.RGB8 ; PF_B8G8R8 -> if hwGamma then GL.SRGB8 else GL.RGB8 ; PF_X8B8G8R8 -> if hwGamma then GL.SRGB8 else GL.RGB8 ; PF_X8R8G8B8 -> if hwGamma then GL.SRGB8 else GL.RGB8 ; PF_A8R8G8B8 -> if hwGamma then GL.SRGB8Alpha8 else GL.RGBA8 ; PF_B8G8R8A8 -> if hwGamma then GL.SRGB8Alpha8 else GL.RGBA8 ; PF_A2R10G10B10 -> GL.RGB10A2 ; PF_A2B10G10R10 -> GL.RGB10A2 --FIXME ; PF_FLOAT16_R -> GL_LUMINANCE16F_ARB --FIXME ; PF_FLOAT16_RGB -> GL_RGB16F_ARB --FIXME ; PF_FLOAT16_GR -> GL_LUMINANCE_ALPHA16F_ARB --FIXME ; PF_FLOAT16_RGBA -> GL_RGBA16F_ARB --FIXME ; PF_FLOAT32_R -> GL_LUMINANCE32F_ARB --FIXME ; PF_FLOAT32_GR -> GL_LUMINANCE_ALPHA32F_ARB --FIXME ; PF_FLOAT32_RGB -> GL_RGB32F_ARB --FIXME ; PF_FLOAT32_RGBA -> GL_RGBA32F_ARB ; PF_SHORT_RGBA -> GL.RGBA16 ; PF_SHORT_RGB -> GL.RGB16 ; PF_SHORT_GR -> GL.Luminance16Alpha16 -- case PF_DXT1: -- if (hwGamma) -- return GL_COMPRESSED_SRGB_ALPHA_S3TC_DXT1_EXT; -- else -- return GL_COMPRESSED_RGBA_S3TC_DXT1_EXT; -- case PF_DXT3: -- if (hwGamma) -- return GL_COMPRESSED_SRGB_ALPHA_S3TC_DXT3_EXT; -- else -- return GL_COMPRESSED_RGBA_S3TC_DXT3_EXT; -- case PF_DXT5: -- if (hwGamma) -- return GL_COMPRESSED_SRGB_ALPHA_S3TC_DXT5_EXT; -- else -- return GL_COMPRESSED_RGBA_S3TC_DXT5_EXT; ; _ -> error "Unsupported pixel format" } {- GLenum GLPixelUtil::getGLInternalFormat(PixelFormat mFormat, bool hwGamma) { switch(mFormat) { default: return GL_NONE; } } GLenum GLPixelUtil::getClosestGLInternalFormat(PixelFormat mFormat, bool hwGamma) { GLenum format = getGLInternalFormat(mFormat, hwGamma); if(format==GL_NONE) { if (hwGamma) return GL_SRGB8; else return GL_RGBA8; } else return format; } -} getClosestGLInternalFormat :: PixelFormat -> Bool -> GL.PixelInternalFormat getClosestGLInternalFormat mFormat hwGamma = case mFormat of { PF_L8 -> GL.Luminance8 ; PF_L16 -> GL.Luminance16 ; PF_A8 -> GL.Alpha8 ; PF_A4L4 -> GL.Luminance4Alpha4 ; PF_BYTE_LA -> GL.Luminance8Alpha8 ; PF_R3G3B2 -> GL.R3G3B2 ; PF_A1R5G5B5 -> GL.RGB5A1 ; PF_R5G6B5 -> GL.RGB5 ; PF_B5G6R5 -> GL.RGB5 ; PF_A4R4G4B4 -> GL.RGBA4 ; PF_R8G8B8 -> if hwGamma then GL.SRGB8 else GL.RGB8 ; PF_B8G8R8 -> if hwGamma then GL.SRGB8 else GL.RGB8 ; PF_X8B8G8R8 -> if hwGamma then GL.SRGB8 else GL.RGB8 ; PF_X8R8G8B8 -> if hwGamma then GL.SRGB8 else GL.RGB8 ; PF_A8R8G8B8 -> if hwGamma then GL.SRGB8Alpha8 else GL.RGBA8 ; PF_B8G8R8A8 -> if hwGamma then GL.SRGB8Alpha8 else GL.RGBA8 ; PF_A2R10G10B10 -> GL.RGB10A2 ; PF_A2B10G10R10 -> GL.RGB10A2 --FIXME ; PF_FLOAT16_R -> GL_LUMINANCE16F_ARB --FIXME ; PF_FLOAT16_RGB -> GL_RGB16F_ARB --FIXME ; PF_FLOAT16_GR -> GL_LUMINANCE_ALPHA16F_ARB --FIXME ; PF_FLOAT16_RGBA -> GL_RGBA16F_ARB --FIXME ; PF_FLOAT32_R -> GL_LUMINANCE32F_ARB --FIXME ; PF_FLOAT32_GR -> GL_LUMINANCE_ALPHA32F_ARB --FIXME ; PF_FLOAT32_RGB -> GL_RGB32F_ARB --FIXME ; PF_FLOAT32_RGBA -> GL_RGBA32F_ARB ; PF_SHORT_RGBA -> GL.RGBA16 ; PF_SHORT_RGB -> GL.RGB16 ; PF_SHORT_GR -> GL.Luminance16Alpha16 -- FIXME -- case PF_DXT1: -- if (hwGamma) -- return GL_COMPRESSED_SRGB_ALPHA_S3TC_DXT1_EXT; -- else -- return GL_COMPRESSED_RGBA_S3TC_DXT1_EXT; -- case PF_DXT3: -- if (hwGamma) -- return GL_COMPRESSED_SRGB_ALPHA_S3TC_DXT3_EXT; -- else -- return GL_COMPRESSED_RGBA_S3TC_DXT3_EXT; -- case PF_DXT5: -- if (hwGamma) -- return GL_COMPRESSED_SRGB_ALPHA_S3TC_DXT5_EXT; -- else -- return GL_COMPRESSED_RGBA_S3TC_DXT5_EXT; ; _ -> if hwGamma then GL.SRGB8 else GL.RGBA8 } getBlendMode :: SceneBlendFactor -> GL.BlendingFactor getBlendMode blend = case blend of { SBF_ONE -> GL.One ; SBF_ZERO -> GL.Zero ; SBF_DEST_COLOUR -> GL.DstColor ; SBF_SOURCE_COLOUR -> GL.SrcColor ; SBF_ONE_MINUS_DEST_COLOUR -> GL.OneMinusDstColor ; SBF_ONE_MINUS_SOURCE_COLOUR -> GL.OneMinusSrcColor ; SBF_DEST_ALPHA -> GL.DstAlpha ; SBF_SOURCE_ALPHA -> GL.SrcAlpha ; SBF_ONE_MINUS_DEST_ALPHA -> GL.OneMinusDstAlpha ; SBF_ONE_MINUS_SOURCE_ALPHA -> GL.OneMinusSrcAlpha } getBlendEquation op = case op of { SBO_ADD -> GL.FuncAdd ; SBO_SUBTRACT -> GL.FuncSubtract ; SBO_REVERSE_SUBTRACT -> GL.FuncReverseSubtract ; SBO_MIN -> GL.Min ; SBO_MAX -> GL.Max } getTextureAddressingMode tam = case tam of { TAM_WRAP -> (GL.Repeated, GL.Repeat) ; TAM_MIRROR -> (GL.Mirrored, GL.Repeat) ; TAM_CLAMP -> (GL.Repeated, GL.ClampToEdge) ; TAM_BORDER -> (GL.Repeated, GL.ClampToBorder) } getLayerBlendSource src = case src of { LBS_CURRENT -> GL.Previous ; LBS_TEXTURE -> GL.CurrentUnit ; LBS_MANUAL -> GL.Constant ; LBS_DIFFUSE -> GL.PrimaryColor ; LBS_SPECULAR -> GL.PrimaryColor } getTextureCombineFunction hasDot3 op = case op of { LBX_SOURCE1 -> GL.Replace' ; LBX_SOURCE2 -> GL.Replace' ; LBX_MODULATE -> GL.Modulate' ; LBX_MODULATE_X2 -> GL.Modulate' ; LBX_MODULATE_X4 -> GL.Modulate' ; LBX_ADD -> GL.AddUnsigned' ; LBX_ADD_SIGNED -> GL.AddSigned ; LBX_ADD_SMOOTH -> GL.Interpolate ; LBX_SUBTRACT -> GL.Subtract ; LBX_BLEND_DIFFUSE_COLOUR -> GL.Interpolate ; LBX_BLEND_DIFFUSE_ALPHA -> GL.Interpolate ; LBX_BLEND_TEXTURE_ALPHA -> GL.Interpolate ; LBX_BLEND_CURRENT_ALPHA -> GL.Interpolate ; LBX_BLEND_MANUAL -> GL.Interpolate ; LBX_DOTPRODUCT -> if hasDot3 then GL.Dot3RGB else GL.Modulate' } convertCompareFunction f = case f of { CMPF_ALWAYS_FAIL -> GL.Never ; CMPF_ALWAYS_PASS -> GL.Always ; CMPF_LESS -> GL.Less ; CMPF_LESS_EQUAL -> GL.Lequal ; CMPF_EQUAL -> GL.Equal ; CMPF_NOT_EQUAL -> GL.Notequal ; CMPF_GREATER_EQUAL -> GL.Gequal ; CMPF_GREATER -> GL.Greater }