module Graphics.Rendering.Ombra.Object (
Object((:~>)),
nothing,
geom,
modifyGeometry,
depthTest,
depthMask,
colorMask,
ShaderVars,
VOShaderVars,
blend,
noBlend,
Blend.transparency,
Blend.additive,
stencil,
noStencil,
CullFace(..),
cull,
noCull,
Global,
(-=),
withTexture,
withTexSize,
withFramebufferSize,
ActiveTexture,
mirror,
CPUMirror,
MemberGlobal((~~>)),
RemoveGlobal((*~>)),
) where
import Data.Typeable
import Data.Type.Equality
import Data.Word (Word8)
import Graphics.Rendering.Ombra.Backend (GLES)
import qualified Graphics.Rendering.Ombra.Blend as Blend
import qualified Graphics.Rendering.Ombra.Stencil as Stencil
import Graphics.Rendering.Ombra.Geometry
import Graphics.Rendering.Ombra.Color
import Graphics.Rendering.Ombra.Object.Types
import Graphics.Rendering.Ombra.Internal.GL (ActiveTexture)
import Graphics.Rendering.Ombra.Internal.TList
import Graphics.Rendering.Ombra.Shader.CPU hiding (mirror)
import Graphics.Rendering.Ombra.Shader.Program
import Graphics.Rendering.Ombra.Shader.ShaderVar
import Graphics.Rendering.Ombra.Shader.Stages
import Graphics.Rendering.Ombra.Texture
blend :: Blend.Mode -> Object gs is -> Object gs is
blend m = Prop . Blend $ Just m
noBlend :: Object gs is -> Object gs is
noBlend = Prop $ Blend Nothing
stencil :: Stencil.Mode -> Object gs is -> Object gs is
stencil m = Prop . Stencil $ Just m
noStencil :: Object gs is -> Object gs is
noStencil = Prop $ Stencil Nothing
depthTest :: Bool -> Object gs is -> Object gs is
depthTest d = Prop $ DepthTest d
depthMask :: Bool -> Object gs is -> Object gs is
depthMask m = Prop $ DepthMask m
colorMask :: (Bool, Bool, Bool, Bool) -> Object gs is -> Object gs is
colorMask m = Prop $ ColorMask m
cull :: CullFace -> Object gs is -> Object gs is
cull m = Prop . Cull $ Just m
noCull :: Object gs is -> Object gs is
noCull = Prop $ Cull Nothing
nothing :: Object '[] '[]
nothing = NoMesh
geom :: Geometry (i ': is) -> Object '[] (i ': is)
geom = Mesh
class MemberGlobal g gs where
(~~>) :: (Uniform 'S g)
=> (CPU 'S g -> Global g)
-> Object gs is
-> Object gs is
instance MemberGlobal g (g ': gs) where
f ~~> (g :~> o) = globalApply f g :~> o
f ~~> (Prop p o) = Prop p $ f ~~> o
f ~~> (Append o o') = Append (f ~~> o) (f ~~> o')
f ~~> NoMesh = NoMesh
instance ((g == g1) ~ False, MemberGlobal g gs) =>
MemberGlobal g (g1 ': gs) where
f ~~> (g :~> o) = g :~> (f ~~> o)
f ~~> (Prop p o) = Prop p $ f ~~> o
f ~~> (Append o o') = Append (f ~~> o) (f ~~> o')
f ~~> NoMesh = NoMesh
globalApply :: (Uniform 'S g)
=> (CPU 'S g -> Global g)
-> Global g
-> Global g
globalApply f (Single g c) = f c
globalApply f (WithTexture t g) = WithTexture t $ globalApply f . g
globalApply f (WithTextureSize t g) = WithTextureSize t $ globalApply f . g
globalApply f (WithFramebufferSize g) = WithFramebufferSize $ globalApply f . g
globalApply f g = g
infixr 2 ~~>
class RemoveGlobal g gs' where
(*~>) :: (a -> g) -> Object gs' is -> Object (Remove g gs') is
instance Remove g (g : gs') ~ gs' =>
RemoveGlobal g (g ': gs') where
_ *~> (_ :~> o) = o
r *~> (Prop p o) = Prop p $ r *~> o
r *~> (Append o o') = Append (r *~> o) (r *~> o')
r *~> NoMesh = NoMesh
instance ( Remove g (g' ': gs') ~ (g' ': Remove g gs')
, RemoveGlobal g gs'
) => RemoveGlobal g (g' ': gs') where
r *~> (g :~> o) = g :~> (r *~> o)
r *~> (Prop p o) = Prop p $ r *~> o
r *~> (Append o o') = Append (r *~> o) (r *~> o')
r *~> NoMesh = NoMesh
infixr 2 *~>
modifyGeometry :: (Geometry (i ': is) -> Geometry (i' : is'))
-> Object gs (i ': is) -> Object gs (i' : is')
modifyGeometry fg (g :~> o) = g :~> modifyGeometry fg o
modifyGeometry fg (Mesh g) = Mesh $ fg g
modifyGeometry fg (Prop p o) = Prop p $ modifyGeometry fg o
modifyGeometry fg (Append o o') = Append (modifyGeometry fg o)
(modifyGeometry fg o')
modifyGeometry fg NoMesh = NoMesh
(-=) :: (ShaderVar g, Uniform 'S g) => (a -> g) -> CPU 'S g -> Global g
(-=) = Single
infixr 4 -=
withTexture :: Texture -> (ActiveTexture -> Global g) -> Global g
withTexture = WithTexture
withTexSize :: Texture -> ((Int, Int) -> Global g) -> Global g
withTexSize = WithTextureSize
withFramebufferSize :: ((Int, Int) -> Global g) -> Global g
withFramebufferSize = WithFramebufferSize
mirror :: (ShaderVar g, Uniform 'M g) => Proxy g -> CPU 'M g -> Global g
mirror = Mirror