module Graphics.Rendering.Ombra.Texture (
Texture,
mkTexture,
mkTextureFloat,
mkTextureRaw,
Filter(..),
setFilter,
colorTex
) where
import Data.Hashable
import Graphics.Rendering.Ombra.Backend (GLES)
import Graphics.Rendering.Ombra.Color
import Graphics.Rendering.Ombra.Internal.GL hiding (Texture)
import Graphics.Rendering.Ombra.Texture.Internal
import Graphics.Rendering.Ombra.Texture.Types
import Graphics.Rendering.Ombra.Vector
mkTexture :: GLES
=> Int
-> Int
-> Bool
-> [[Color]]
-> Texture
mkTexture w h g pss = TextureImage . TexturePixels g pss minfilter Linear
(fromIntegral w)
(fromIntegral h)
$ hash (w, h, length pss, g, take (w * h) (head pss))
where minfilter | g = (Linear, Just Nearest)
| (_:_:_) <- pss = (Linear, Just Nearest)
| otherwise = (Linear, Nothing)
mkTextureRaw :: GLES
=> Int
-> Int
-> Bool
-> [UInt8Array]
-> Int
-> Texture
mkTextureRaw w h g arr pxhash = TextureImage $ TextureRaw g arr minfilter Linear
(fromIntegral w)
(fromIntegral h)
$ hash (w, h, pxhash)
where minfilter | g = (Linear, Just Nearest)
| (_:_:_) <- arr = (Linear, Just Nearest)
| otherwise = (Linear, Nothing)
mkTextureFloat :: GLES
=> Int
-> Int
-> [Vec4]
-> Texture
mkTextureFloat w h vs = TextureImage . TextureFloat ps (Linear, Nothing) Linear
(fromIntegral w)
(fromIntegral h)
$ hash (w, h, take (w * h * 4) ps)
where ps = vs >>= \(Vec4 x y z w) -> [x, y, z, w]
setFilter :: (Filter, Maybe Filter)
-> Filter
-> Texture
-> Texture
setFilter min mag (TextureImage (TexturePixels g c _ _ w h s)) =
TextureImage (TexturePixels g c min mag w h s)
setFilter min mag (TextureImage (TextureRaw g c _ _ w h s)) =
TextureImage (TextureRaw g c min mag w h s)
setFilter min mag (TextureImage (TextureFloat c _ _ w h s)) =
TextureImage (TextureFloat c min mag w h s)
setFilter _ _ t = t
colorTex :: GLES => Color -> Texture
colorTex c = mkTexture 1 1 False [[c]]