module Graphics.Rendering.Ombra.Texture (
MonadTexture,
Texture,
mkTexture,
mkTextureFloat,
mkTextureRaw,
colorTex,
TextureParameters,
Filter(..),
WrappingFunction(..),
parameters,
potParameters,
potLinear
) 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.Draw
import Graphics.Rendering.Ombra.Texture.Types
import Graphics.Rendering.Ombra.Vector
parameters :: Filter
-> Filter
-> TextureParameters
parameters min mag = potParameters (min, Nothing) mag
False
ClampToEdge ClampToEdge
potParameters :: (Filter, Maybe Filter)
-> Filter
-> Bool
-> WrappingFunction
-> WrappingFunction
-> TextureParameters
potParameters = TextureParameters
potLinear :: Bool
-> TextureParameters
potLinear g = potParameters (Linear, Just Nearest) Linear g Repeat Repeat
mkTexture :: GLES
=> Int
-> Int
-> TextureParameters
-> [[Color]]
-> Texture
mkTexture w h params pss =
TextureImage $ TexturePixels pss
params
(fromIntegral w)
(fromIntegral h)
(hash ( w, h, params
, length pss
, take (w * h) (head pss)
)
)
mkTextureRaw :: GLES
=> Int
-> Int
-> TextureParameters
-> [UInt8Array]
-> Int
-> Texture
mkTextureRaw w h params arr pxhash =
TextureImage $ TextureRaw arr
params
(fromIntegral w)
(fromIntegral h)
(hash (w, h, params, pxhash))
mkTextureFloat :: GLES
=> Int
-> Int
-> TextureParameters
-> [Vec4]
-> Texture
mkTextureFloat w h params vs =
TextureImage $ TextureFloat ps
params
(fromIntegral w)
(fromIntegral h)
(hash (w, h, params, take (w * h * 4) ps))
where ps = vs >>= \(Vec4 x y z w) -> [x, y, z, w]
colorTex :: GLES => Color -> Texture
colorTex c = mkTexture 1 1 (potLinear False) [[c]]