module Graphics.Rendering.Ombra.Layer (
Buffer(..),
Layer,
layer,
over,
clear,
Compatible,
Program,
program,
subLayer,
colorSubLayer,
depthSubLayer,
colorDepthSubLayer,
colorStencilSubLayer,
colorSubLayer',
depthSubLayer',
colorDepthSubLayer',
colorStencilSubLayer',
buffersSubLayer,
buffersDepthSubLayer,
buffersStencilSubLayer,
Layer',
LayerStatus(..),
drawable,
castLayer,
TTexture,
withTTexture,
permanent,
depthToTexture,
colorDepthToTexture,
colorStencilToTexture,
colorToTexture',
depthToTexture',
colorDepthToTexture',
colorStencilToTexture',
buffersDepthToTexture,
buffersStencilToTexture
) where
import Data.Word (Word8)
import Graphics.Rendering.Ombra.Backend (GLES)
import Graphics.Rendering.Ombra.Color
import Graphics.Rendering.Ombra.Internal.TList
import Graphics.Rendering.Ombra.Layer.Internal
import Graphics.Rendering.Ombra.Layer.Types
import Graphics.Rendering.Ombra.Object
import Graphics.Rendering.Ombra.Shader.Program
import Graphics.Rendering.Ombra.Texture
layer :: (Subset progAttr grpAttr, Subset progUni grpUni)
=> Program progUni progAttr -> Object grpUni grpAttr -> Layer' s t ()
layer = Layer
infixl 1 `over`
over :: Layer -> Layer -> Layer
over = flip (>>)
subLayer :: Int -> Int -> Layer -> (Texture -> Layer) -> Layer
subLayer = colorSubLayer
colorSubLayer :: Int
-> Int
-> Layer
-> (Texture -> Layer)
-> Layer
colorSubLayer w h l = colorDepthSubLayer w h l . flip . const
depthSubLayer :: Int
-> Int
-> Layer
-> (Texture -> Layer)
-> Layer
depthSubLayer w h l f = drawable $
depthToTexture w h (castLayer l) >>= \(_, t) -> withTTexture t f
colorDepthSubLayer :: Int
-> Int
-> Layer
-> (Texture -> Texture -> Layer)
-> Layer
colorDepthSubLayer w h l f = drawable $
colorDepthToTexture w h (castLayer l) >>=
\(_, ct, dt) -> withTTextures [ct, dt] $
\[ct', dt'] -> f ct' dt'
colorStencilSubLayer :: Int
-> Int
-> Layer
-> (Texture -> Layer)
-> Layer
colorStencilSubLayer w h l f = drawable $
colorStencilToTexture w h (castLayer l) >>= \(_, t) -> withTTexture t f
colorSubLayer'
:: Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Layer
-> (Texture -> [Color] -> Layer)
-> Layer
colorSubLayer' w h rx ry rw rh l f = drawable $
colorToTexture' w h rx ry rw rh (castLayer l) >>=
\(_, t, c) -> withTTexture t $ flip f c
depthSubLayer'
:: Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Layer
-> (Texture -> [Word8] -> Layer)
-> Layer
depthSubLayer' w h rx ry rw rh l f = drawable $
depthToTexture' w h rx ry rw rh (castLayer l) >>=
\(_, t, d) -> withTTexture t $ flip f d
colorDepthSubLayer'
:: Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Layer
-> (Texture -> Texture -> [Color] -> [Word8] -> Layer)
-> Layer
colorDepthSubLayer' w h rx ry rw rh l f = drawable $
colorDepthToTexture' w h rx ry rw rh (castLayer l) >>=
\(_, ct, dt, c, d) -> withTTextures [ct, dt] $
\[ct', dt'] -> f ct' dt' c d
colorStencilSubLayer'
:: Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Layer
-> (Texture -> [Color] -> Layer)
-> Layer
colorStencilSubLayer' w h rx ry rw rh l f = drawable $
colorStencilToTexture' w h rx ry rw rh (castLayer l) >>=
\(_, t, c) -> withTTexture t $ flip f c
buffersSubLayer :: Int
-> Int
-> Int
-> Layer
-> ([Texture] -> Layer)
-> Layer
buffersSubLayer w h n l = buffersDepthSubLayer w h n l . flip . const
buffersDepthSubLayer :: Int
-> Int
-> Int
-> Layer
-> ([Texture] -> Texture -> Layer)
-> Layer
buffersDepthSubLayer w h n l f = drawable $
buffersDepthToTexture w h n (castLayer l) >>=
\(_, bts, dt) -> withTTextures (dt : bts) $
\(dt' : bts') -> f bts' dt'
buffersStencilSubLayer :: Int
-> Int
-> Int
-> Layer
-> ([Texture] -> Layer)
-> Layer
buffersStencilSubLayer w h n l f = drawable $
buffersStencilToTexture w h n (castLayer l) >>=
\(_, bts) -> withTTextures bts f