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,
) 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.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
layer = Layer
infixl 1 `over`
over :: Layer -> Layer -> Layer
over = OverLayer
clear :: [Buffer] -> Layer -> Layer
clear = ClearLayer
colorTex :: GLES => Color -> Texture
colorTex c = mkTexture 1 1 [ c ]
subLayer :: Int -> Int -> Layer -> (Texture -> Layer) -> Layer
subLayer = colorSubLayer
colorSubLayer :: Int
-> Int
-> Layer
-> (Texture -> Layer)
-> Layer
colorSubLayer w h l = subRenderLayer . renderColor w h l
depthSubLayer :: Int
-> Int
-> Layer
-> (Texture -> Layer)
-> Layer
depthSubLayer w h l = subRenderLayer . renderDepth w h l
colorDepthSubLayer :: Int
-> Int
-> Layer
-> (Texture -> Texture -> Layer)
-> Layer
colorDepthSubLayer w h l = subRenderLayer . renderColorDepth w h l
colorStencilSubLayer :: Int
-> Int
-> Layer
-> (Texture -> Layer)
-> Layer
colorStencilSubLayer w h l = subRenderLayer . renderColorStencil w h l
colorSubLayer'
:: Int
-> Int
-> Layer
-> Int
-> Int
-> Int
-> Int
-> (Texture -> [Color] -> Layer)
-> Layer
colorSubLayer' w h l rx ry rw rh =
subRenderLayer . renderColorInspect w h l rx ry rw rh
depthSubLayer'
:: Int
-> Int
-> Layer
-> Int
-> Int
-> Int
-> Int
-> (Texture -> [Word8] -> Layer)
-> Layer
depthSubLayer' w h l rx ry rw rh =
subRenderLayer . renderDepthInspect w h l rx ry rw rh
colorDepthSubLayer'
:: Int
-> Int
-> Layer
-> Int
-> Int
-> Int
-> Int
-> (Texture -> Texture -> [Color] -> [Word8] -> Layer)
-> Layer
colorDepthSubLayer' w h l rx ry rw rh =
subRenderLayer . renderColorDepthInspect w h l rx ry rw rh
colorStencilSubLayer'
:: Int
-> Int
-> Layer
-> Int
-> Int
-> Int
-> Int
-> (Texture -> [Color] -> Layer)
-> Layer
colorStencilSubLayer' w h l rx ry rw rh =
subRenderLayer . renderColorStencilInspect w h l rx ry rw rh
buffersSubLayer :: Int
-> Int
-> Int
-> Layer
-> ([Texture] -> Layer)
-> Layer
buffersSubLayer w h n l = subRenderLayer . renderBuffers w h n l
buffersDepthSubLayer :: Int
-> Int
-> Int
-> Layer
-> ([Texture] -> Texture -> Layer)
-> Layer
buffersDepthSubLayer w h n l = subRenderLayer . renderBuffersDepth w h n l
buffersStencilSubLayer :: Int
-> Int
-> Int
-> Layer
-> ([Texture] -> Layer)
-> Layer
buffersStencilSubLayer w h n l = subRenderLayer . renderBuffersStencil w h n l
subRenderLayer :: RenderLayer Layer -> Layer
subRenderLayer = SubLayer
renderColor :: Int -> Int -> Layer -> (Texture -> a) -> RenderLayer a
renderColor w h l f = RenderLayer False [ColorLayer, DepthLayer] w h 0 0 0 0
False False l $ \[t, _] _ _ -> f t
renderDepth :: Int -> Int -> Layer -> (Texture -> a) -> RenderLayer a
renderDepth w h l f =
RenderLayer False [DepthLayer] w h 0 0 0 0 False False l $
\[t] _ _ -> f t
renderColorDepth :: Int
-> Int
-> Layer
-> (Texture -> Texture -> a)
-> RenderLayer a
renderColorDepth w h l f =
RenderLayer False [ColorLayer, DepthLayer] w h 0 0 0 0 False False l $
\[ct, dt] _ _ -> f ct dt
renderColorStencil :: Int
-> Int
-> Layer
-> (Texture -> a)
-> RenderLayer a
renderColorStencil w h l f =
RenderLayer False [ColorLayer, DepthStencilLayer] w h 0 0 0 0
False False l $
\[ct, _] _ _ -> f ct
renderColorInspect :: Int
-> Int
-> Layer
-> Int
-> Int
-> Int
-> Int
-> (Texture -> [Color] -> a)
-> RenderLayer a
renderColorInspect w h l rx ry rw rh f =
RenderLayer False [ColorLayer, DepthLayer] w h rx ry
rw rh True False l $
\[t, _] (Just c) _ -> f t c
renderDepthInspect :: Int
-> Int
-> Layer
-> Int
-> Int
-> Int
-> Int
-> (Texture -> [Word8] -> a)
-> RenderLayer a
renderDepthInspect w h l rx ry rw rh f =
RenderLayer False [DepthLayer] w h rx ry rw rh False True l $
\[t] _ (Just d) -> f t d
renderColorDepthInspect :: Int
-> Int
-> Layer
-> Int
-> Int
-> Int
-> Int
-> (Texture -> Texture -> [Color] -> [Word8] -> a)
-> RenderLayer a
renderColorDepthInspect w h l rx ry rw rh f =
RenderLayer False [ColorLayer, DepthLayer] w h rx ry rw rh True True l $
\[ct, dt] (Just c) (Just d) -> f ct dt c d
renderColorStencilInspect :: Int
-> Int
-> Layer
-> Int
-> Int
-> Int
-> Int
-> (Texture -> [Color] -> a)
-> RenderLayer a
renderColorStencilInspect w h l rx ry rw rh f =
RenderLayer False [ColorLayer, DepthStencilLayer] w h rx ry
rw rh True False l $
\[t, _] (Just c) _ -> f t c
renderBuffers :: Int -> Int -> Int -> Layer -> ([Texture] -> a) -> RenderLayer a
renderBuffers w h n l f =
RenderLayer True (DepthLayer : map BufferLayer [0 .. n 1]) w h
0 0 0 0 False False l $ \(_ : ts) _ _ -> f ts
renderBuffersDepth :: Int
-> Int
-> Int
-> Layer
-> ([Texture] -> Texture -> a)
-> RenderLayer a
renderBuffersDepth w h n l f =
RenderLayer True (DepthLayer : map BufferLayer [0 .. n 1]) w h
0 0 0 0 False False l $ \(dt : ts) _ _ -> f ts dt
renderBuffersStencil :: Int
-> Int
-> Int
-> Layer
-> ([Texture] -> a)
-> RenderLayer a
renderBuffersStencil w h n l f =
RenderLayer True (DepthStencilLayer : map BufferLayer [0 .. n 1]) w h
0 0 0 0 False False l $ \(_ : ts) _ _ -> f ts