module FWGL.Shader.Default2D where
import FWGL.Shader
type Uniforms = '[View2, Image, Depth, Transform2]
type Attributes = '[Position2, UV]
newtype Image = Image Sampler2D
deriving (Typeable, ShaderType, UniformCPU CSampler2D)
newtype Depth = Depth Float
deriving (Typeable, ShaderType, UniformCPU CFloat)
newtype Transform2 = Transform2 Mat3
deriving (Typeable, ShaderType, UniformCPU CMat3)
newtype View2 = View2 Mat3
deriving (Typeable, ShaderType, UniformCPU CMat3)
newtype Position2 = Position2 Vec2
deriving (Typeable, ShaderType, AttributeCPU CVec2)
newtype UV = UV Vec2
deriving (Typeable, ShaderType, AttributeCPU CVec2)
vertexShader :: VertexShader '[Transform2, View2, Depth]
'[Position2, UV] '[UV]
vertexShader (Transform2 trans :- View2 view :- Depth z :- N)
(Position2 (Vec2 x y) :- uv@(UV _) :- N) =
let Vec3 x' y' _ = view * trans * Vec3 x y 1
in Vertex (Vec4 x' y' z 1) :- uv :- N
fragmentShader :: FragmentShader '[Image] '[UV]
fragmentShader (Image sampler :- N) (UV (Vec2 s t) :- N) =
Fragment (texture2D sampler (Vec2 s $ 1 t)) :- N