lambdacube3d / lambdacube-compiler

LambdaCube 3D is a Haskell-like purely functional language for GPU. Try it out:
http://lambdacube3d.com
Other
85 stars 9 forks source link

Passing more than three attributes to fragment shader #4

Closed NCrashed closed 8 years ago

NCrashed commented 8 years ago

Hi, it's I again. I hit limitation of current implementation of InterpolatedType family. Adding new clauses for InterpolatedType and JoinTupleType didn't help. Does adding support for tuples of higher dimensions require compiler fix?

I still getting errors like this:

compile error:
type of main should be Just (TyCon_ MaxDB 'Output []) instead of {a} -> {b : 'Tuple5 ('VecS 'Float 4) ('VecS 'Float 3) ('VecS 'Float 3) ('VecS 'Float 2) ('VecS 'Float 4) ~ 'JoinTupleType ('Vec 4 'Float) ('InterpolatedType a)} -> {c} -> {d} -> {e : 'Floating d} -> {f} -> {g : 'Floating f} -> {h} -> {i : a ~ 'Tuple4 ('Interpolated d) ('Interpolated f) ('Interpolated h) c} -> {j : 'Floating h} -> {k} -> {l : c ~ 'Interpolated k} -> {m : 'Floating k} -> {n : 'InterpolatedType ('Tuple4 ('Interpolated d) ('Interpolated f) ('Interpolated h) ('Interpolated k)) ~ 'Tuple4 'Position 'Normal 'UV 'ShadowCoord}->'Output

Scirpt (sorry for huge code):

type Position = Vec 3 Float 
type PositionHomo = Vec 4 Float 
type Normal = Vec 3 Float
type UV = Vec 2 Float
type Color = Vec 4 Float 
type ShadowCoord = Vec 4 Float 

homonize :: Vec 3 Float -> Vec 4 Float 
homonize v = V4 v%x v%y v%z 1 

unhomonize :: Vec 4 Float -> Vec 3 Float 
unhomonize v = V3 (v%x / v%w) (v%y / v%w) (v%z / v%w)

vec3 :: Float -> Vec 3 Float 
vec3 a = V3 a a a 

shadowMapSize :: Int 
shadowMapSize = 1024

-- | Transforms [-1 .. 1] range to [0 .. 1]
biasMatrix :: Mat 4 4 Float 
biasMatrix = M44F 
  (V4 0.5 0.0 0.0 0.0)
  (V4 0.0 0.5 0.0 0.0)
  (V4 0.0 0.0 0.5 0.0)
  (V4 0.5 0.5 0.5 1.0)

-- | Raster objects from view of directed light and save depth
type Position = Vec 3 Float 
type PositionHomo = Vec 4 Float 
type Normal = Vec 3 Float
type UV = Vec 2 Float
type Color = Vec 4 Float 
type ShadowCoord = Vec 4 Float 

homonize :: Vec 3 Float -> Vec 4 Float 
homonize v = V4 v%x v%y v%z 1 

unhomonize :: Vec 4 Float -> Vec 3 Float 
unhomonize v = V3 (v%x / v%w) (v%y / v%w) (v%z / v%w)

vec3 :: Float -> Vec 3 Float 
vec3 a = V3 a a a 

shadowMapSize :: Int 
shadowMapSize = 1024

-- | Transforms [-1 .. 1] range to [0 .. 1]
biasMatrix :: Mat 4 4 Float 
biasMatrix = M44F 
  (V4 0.5 0.0 0.0 0.0)
  (V4 0.0 0.5 0.0 0.0)
  (V4 0.0 0.0 0.5 0.0)
  (V4 0.5 0.5 0.5 1.0)

-- | Raster objects from view of directed light and save depth
makeShadowMap (depthMVP :: Mat 4 4 Float)
              (prims :: PrimitiveStream Triangle (Vec 3 Float, Vec 3 Float, Vec 2 Float))

    = imageFrame (emptyDepthImage 1, emptyColorImage (V4 1 1 1 1.0))
    `overlay`
      prims 
    & mapPrimitives (\(v, n, uv) -> let v' = depthMVP *. homonize v in (v', v'))
    & rasterizePrimitives (TriangleCtx CullBack PolygonFill NoOffset LastVertex) Smooth
    & mapFragments (\v -> v%zzzw)
    & accumulateWith (DepthOp Less True, ColorOp NoBlending (V4 True True True True))

-- | Final render of object using shadow map generated at previous pass
makeFrame (modelMat :: Mat 4 4 Float)
          (viewMat :: Mat 4 4 Float)
          (projMat :: Mat 4 4 Float)
          (texture :: Texture)
          (lightDirection :: Vec 3 Float)
          (shadowMap :: Texture)
          (depthMVP :: Mat 4 4 Float)
          (prims :: PrimitiveStream Triangle (Vec 3 Float, Vec 3 Float, Vec 2 Float))

    = imageFrame (emptyDepthImage 1, emptyColorImage (V4 0 0 0.4 1))
   `overlay`
      prims
    & mapPrimitives transform
    & rasterizePrimitives (TriangleCtx CullNone PolygonFill NoOffset LastVertex) (Smooth, Smooth, Smooth, Smooth)
    & mapFragments enlight
    & accumulateWith (DepthOp Less True, ColorOp NoBlending (V4 True True True True))
  where
    mv = modelMat .*. viewMat
    mvp = transpose $ mv .*. projMat -- loaded matricies are transposed
    viewmatInvT = inv mv -- double transpose eliminated

    transNormal :: Normal -> Normal
    transNormal = normalize . unhomonize . (viewmatInvT *.) . homonize

    transform :: (Position, Normal, UV) -> (PositionHomo, Position, Normal, UV, ShadowCoord)
    transform (p,n,uv) = (p', unhomonize pview, transNormal n, uv, shadowCoord)
      where p' = mvp *. homonize p
            pview = (transpose $ modelMat .*. viewMat) *. homonize p
            shadowCoord = (biasMatrix .*. depthMVP) *. homonize p

    enlight :: (Position, Normal, UV, ShadowCoord) -> Color
    enlight (vertPos, normal, uv, shc) = homonize colorLinear
      where 
        ambientColor = V3 0 0 0
        diffuseColor = texture2D (Sampler PointFilter MirroredRepeat texture) uv :: Vec 4 Float
        specColor = V3 1 1 1 
        shininess = 64.0

        lightDirView = unhomonize $ transpose viewMat *. homonize lightDirection
        lightDir = normalize $ lightDirView *! (-1)

        lambertian = max (lightDir `dot` normal) 0
        viewDir = normalize (vertPos *! (-1))
        halfDir = normalize $ lightDir + viewDir
        specAngle = max (halfDir `dot` normal) 0
        specular = if lambertian <= 0 then 0 else pow specAngle shininess

        colorLinear = ambientColor + (diffuseColor%xyz) *! lambertian + specColor *! specular

main :: Output
main = renderFrame $
  let shadowMap = Texture2D (V2 shadowMapSize shadowMapSize) . PrjImageColor $ makeShadowMap depthMVP objects
  in makeFrame (Uniform "modelMat") 
            (Uniform "viewMat")
            (Uniform "projMat")
            (Texture2DSlot "diffuseTexture")
            (Uniform "lightDir")
            shadowMap
            depthMVP
            objects
  where
    depthMVP = Uniform "depthMVP"
    objects = fetch_ "objects" (Attribute "position", Attribute "normal", Attribute "uv")
csabahruska commented 8 years ago

download the patch: tuple5.zip If you patch the 0.4 release it should work:

diff --git a/lc/Builtins.lc b/lc/Builtins.lc
index 271b636..d71c4d4 100644
--- a/lc/Builtins.lc
+++ b/lc/Builtins.lc
@@ -396,6 +396,8 @@ type family InterpolatedType a where
     InterpolatedType (Interpolated a) = a
     InterpolatedType (Interpolated a, Interpolated b) = (a, b)
     InterpolatedType (Interpolated a, Interpolated b, Interpolated c) = (a, b, c)
+    InterpolatedType (Interpolated a, Interpolated b, Interpolated c, Interpolated d) = (a, b, c, d)
+    InterpolatedType (Interpolated a, Interpolated b, Interpolated c, Interpolated d, Interpolated e) = (a, b, c, d, e)

 rasterizePrimitive
     :: ( b ~ InterpolatedType interpolation
diff --git a/src/LambdaCube/Compiler/Infer.hs b/src/LambdaCube/Compiler/Infer.hs
index 70fab42..8c52423 100644
--- a/src/LambdaCube/Compiler/Infer.hs
+++ b/src/LambdaCube/Compiler/Infer.hs
@@ -577,7 +577,12 @@ cstrT_ typ = cstr__ []
     cstr_ ns@[] (UL (FunN "'FragOps" [a])) (TyConN "'FragmentOperation" [x]) = cstr__ ns a x
     cstr_ ns@[] (UL (FunN "'FragOps" [a])) (TyConN "'Tuple2" [TyConN "'FragmentOperation" [x], TyConN "'FragmentOperation" [y]]) = cstr__ ns a $ TTuple2 x y

-    cstr_ ns@[] (TyConN "'Tuple2" [x, y]) (UL (FunN "'JoinTupleType" [x', y'])) = t2 (cstr__ ns x x') (cstr__ ns y y')
+    cstr_ ns@[] (TyConN "'Tuple2" [x, y]) (UL (FunN "'JoinTupleType" [a, b])) = t2 (cstr__ ns x a) (cstr__ ns y b)
+    cstr_ ns@[] (TyConN "'Tuple3" [x, y, z]) (UL (FunN "'JoinTupleType" [a, b])) = t2 (cstr__ ns x a) (cstr__ ns (TTuple2 y z) b)
+    cstr_ ns@[] (TyConN "'Tuple4" [x, y, z, w]) (UL (FunN "'JoinTupleType" [a, b])) = t2 (cstr__ ns x a)
+        (cstr__ ns (TTyCon "'Tuple3" (TType :~> TType :~> TType :~> TType) [y, z, w]) b)
+    cstr_ ns@[] (TyConN "'Tuple5" [x, y, z, w, p]) (UL (FunN "'JoinTupleType" [a, b])) = t2 (cstr__ ns x a)
+        (cstr__ ns (TTyCon "'Tuple4" (TType :~> TType :~> TType :~> TType :~> TType) [y, z, w, p]) b)
     cstr_ ns@[] (UL (FunN "'JoinTupleType" [x', y'])) (TyConN "'Tuple2" [x, y]) = t2 (cstr__ ns x' x) (cstr__ ns y' y)
     cstr_ ns@[] (UL (FunN "'JoinTupleType" [x', y'])) x@NoTup  = t2 (cstr__ ns x' x) (cstr__ ns y' $ TTyCon0 "'Tuple0")
NCrashed commented 8 years ago

Thank you! Couldn't find the right place in Infer.hs.

I build with stack and use latest commit from the repo, if the patch appears in master, I can just push commit hash. If not, I will fork and and the patch to the fork as workaround.

Again, thank you!

csabahruska commented 8 years ago

Use the patch for now. We will add this to master repo later.

NCrashed commented 8 years ago

For history: https://github.com/Teaspot-Studio/lambdacube-compiler/commit/2c53caeba24d9f37acb05f3a0b30361ffd25dffa

The patch is adapted for master and seems to work for me (original patch is for 0.4, but I wanted to stick with master).

Thank you, without the help I wouldn't be able to resolve the issue myself.

divipp commented 8 years ago

Thanks for the contribution! I implemented a solution which hopefully solves this forever. Tuples are now heterogeneous lists in master. There are several consequences:

NCrashed commented 8 years ago

Thank you!