cbaggers / varjo

Lisp to GLSL Language Translator
BSD 2-Clause "Simplified" License
223 stars 23 forks source link

Input and output for geometry shaders is problematic in varjo #86

Closed djeis97 closed 7 years ago

djeis97 commented 7 years ago

Since geometry shaders both take vertices and output vertices, distinguishing the input gl_position from the output gl_position requires one of them have an interface prefix, and the spec says the prefix is gl_in for the inputs. Also, since geometry shaders operate on whole primitives instead of single vertices, gl_in has to be an array. As far as I can tell, glsl-spec doesn't know anything about the gl_in interface for geometry shaders, so I cannot access this from varjo at all.

Output is also awkward, since the system geometry shaders use to output vertices is to set the output variables and then call EmitVertex(); and then set the output variables to the values for the next vertex and call EmitVertex(); again etc. This does not really work with varjo's system of using the function return values to set the output variables of the shader. This is possible right now if you only need to set the standard vertex variables- (setq gl-position ___) (emit-vertex) should work just fine (it compiles to the right glsl at least- I cannot actually test it).

Custom input/output variables are even worse: For input, they have to become arrays when they pass from the vertex (or tessellation, if that becomes a thing) shader to the geometry shader, so the type checking code will have to know to handle that. Because of this, I can't even test passing values from vertex to geometry- the type checker will not let me compile.

I'm not even sure how output would work, since there's no good way to declare output variables apart from returning extra values, and that does not work at all for varjo. Perhaps some alternative syntax will be required, or maybe a wrapper around emit-vertex?

EDIT: corrected a few blatant spelling/grammar errors...

cbaggers commented 7 years ago

First off thankyou so much for writing this out so clearly, everything you say is correct. I need to chew on this before coming up with the api changes, though it certainly involves some of the points above.

If you have glsl for a full pipeline including geometry would you mind posting it here, it would be a big help to look at some 'real' code while processing this.

I've been meaning to add proper interface-block support for a while so I think it's time I got that in too.

varjo has support for void now, so I expect we will use that and use #'emit-vertex. The other option would be to have a pretend 'primitive' type that you 'push' vertices too, and return. Sound a bit like dancing around a problem though.

Revisiting return in general will be nice. IIRC I still have logic in varjo for handling out and return from arbitrary places in the function, however it is stopped from working by the somewhat lazy implementation of make-regular-function. A revisit would let me look at what parts of CL's return mechanism we can support.

Thanks once again for reach out on this, I'm looking forward to getting into this

djeis97 commented 7 years ago

Most of my work with geometry shaders is me just messing around, so I don't really have anything of my own to show you. However, I've found this tutorial to be a great resource:

https://learnopengl.com/#!Advanced-OpenGL/Geometry-Shader

Here is the accompanying source for the example that uses a geometry shader to transform a point into a simple house shape: https://github.com/JoeyDeVries/LearnOpenGL/tree/master/src/4.advanced_opengl/9.geometry_shader

The c++ source needs glew, glfw, and a convenience class for compiling a group of shaders into a pipeline: https://github.com/JoeyDeVries/LearnOpenGL/blob/master/includes/learnopengl/shader.h

djeis97 commented 7 years ago

Well, I just experimented with using def-glsl-stage and passing a custom value from the vertex to geometry shader, and I discovered that varjo does already convert the outputs from the vertex shader to arrays when a geometry shader is involved. However, there is a bug in the v-array code: copy-type for arrays does not copy the element type, leaving it at the default of t which causes a few other parts of varjo to get very confused.

Adding (setf (slot-value new-inst 'element-type) (v-element-type type)) to #'(varjo::copy-type v-array) made everything work properly, and I'm about to push to http://github.com/djeis97/bezier some code which takes advantage of this to pass a color from the vertex to fragment shader through the geometry shader.

cbaggers commented 7 years ago

Step 1. Fix up array support: https://github.com/cbaggers/varjo/issues/90

cbaggers commented 7 years ago

I'm going afk for a few days whilst travelling. Will get cracking on the above when I return

cbaggers commented 7 years ago

@djeis97 great to hear that you got stuff working (and thanks for the PR). I spent a chunk of yesterday reading the spec and I think I know how I want to do interface blocks now.

cbaggers commented 7 years ago

Back in Norway and ready to get cracking on this. Arrays first

cbaggers commented 7 years ago

Made progress on arrays. Weekend & monday was spent on multi monitor support for CEPL along with an api for CEPL's hosts so upgrading will be less painful. Getting into interface blocks asap.

Writeup for the last week found here: http://techsnuffle.com/2017/03/28/tired-but-happy

ELS is next week so there'll be a little less progress that usual. It's all coming along slowly though.

cbaggers commented 7 years ago

I have been reading the glsl spec section on primtives again (and again) as I'm process how to implement this stuff. Notes below. They don’t draw any conclusions, just an attempt to get things in order for myself

cbaggers commented 7 years ago

Primitives and the Pipeline

Ok so the overall goal is to add lispy support geometry shaders. This requires handling the inputs & outputs which are arrayed versions of the previous stage.

They are arrayed to the 'length' of the primitive, so we need to have concept of the primitives used in the stages.

What is tricky is that geometry and tessellation-eval stages both have different allowed input & output primitives and it's not always clear how these map.

Also there is the concept of draw-mode which is specified in GL when calling draw-arrays or draw-elements. This again has overlapping but different choices.

I really like Varjo passing/checking data between stages and I also want this for primitives.

Let's just start running through what we have in different points in the pipeline.

-- Draw Modes --

We have a few options here:

These modes tell the gpu about what it will be drawing and, in the case of adjacency, something of the relationship between vertices.

We can see groupings in the above which may help later

-- Vertex Shader --

Very little of interest (from a primitive perspective) happens here. The next programmable stage after this will be either: tessellation, geometry or fragment.

The fragment stage isn't concerned with geometry so can be ignored for now.

-- Tessellation --

Although we aren't focusing on this yet we will need to eventually so let's consider it.

Takes a 'patch' in.. we will have to look into this

Unless transform feedback is support (which for now it is not) then the only output of tessellation-control shaders is via the 'out' variable.

primitives in: point-mode, triangles, quads?, isolines?

The primitives here are specifying how the tessellation engine will split up the incoming primitives:

the question marks next to quads & isolines are because quads are not valid draw modes in OpenGL core. This makes me wonder to what extent we need to support them..then again we shouldn't need special logic in the compiler for them so it's probably fine to leave them in. Core GL choice are CEPL's business, not Varjo's.

-- Geometry --

Valid input primitive kinds:

A much more restricted set. Adjacency here is weird as, if the primitive is from the tessellation stages does it still have adjacency? I wouldn't have thought so.

So here is something we can sanity check. Also we have 3 categories:

points, lines, triangles

This should be something we can infer in the simple cases. Looking at the list of draw modes these fall into the camps fairly well. Except quads, which seem to only be valid up to the tessellation stage, and patches which ¯_(ツ)_/¯

The allowed output primitives for this stage are:

This makes sense. I'm hoping that we will be able to infer the primitive based on some other function used in the shader body, but I'm not sure quite how yet (perhaps #'emit-primitive).

cbaggers commented 7 years ago

Next actionable thing to do it revisit %return and %out which are a bit hacky.

I'm thinking that %out should be removed and it's job divided. values can take on the task of assigning out-var related metadata to values and return's job will be to aggregate that etc.

We also need to allow (values) in the implicit return position. In this case we take the out details from the other return forms and validate they are structurally equivalent.

djeis97 commented 7 years ago

Patches are used as a draw primitive so that you can supply a variable number of verticies per primitive as input to the tesselation stage. For example, in the tesselation branch of djeis97/bezier I'm using 4 verticies per patch to draw a bezier curve. The first and last are the start and end points of the curve, while the two in the middle are the control points. Then all of those vertices are available at tesselation The number of verticies per patch is set at (%gl:patch-parameter-i :patch-vertices 4).

cbaggers commented 7 years ago

@djeis97 thanks for explaining, that was very helpful. I'll add a ticket for supporting patches to CEPL

cbaggers commented 7 years ago

Status updates: This was a few days ago http://techsnuffle.com/2017/04/07/lisping-elsewhere

Since then I have made good progress on the return/out logic:

I have now merged the feature-flesh-out-arrays into feature-cross-shader branch (where all this ^^ stuff is) so now I'll start looking into passing arrays between stages. This will lead neatly into handling the array'd inputs to the geometry shader. Hopefully after that there is only the primitive handling to do.

[edit] oh and arrays of arrays..I need to do that too

cbaggers commented 7 years ago

Huh..maybe passing arrays is further along that I expected.

TESTS> (mapcar #'glsl-code
               (compile-vert-frag () :450 nil
                 (()
                  (let ((i (vector 1 2 3)))
                    (values (v! 0 0 0 0)
                            i)))
                 (((foo? (:int 3)))
                  (v! (aref foo? 0) 0 0 0))))
("#version 450

out _FROM_VERTEX_
{
    int[3] _VERTEX_OUT_1;
};

void main() {
    int[3] return1;
    int[3] I = int[3](1, 2, 3);
    vec4 g_G1197 = vec4(float(0),float(0),float(0),float(0));
    return1 = I;
    gl_Position = g_G1197;
    int[3] g_G1199 = return1;
    _VERTEX_OUT_1 = g_G1199;
    return;
}

"
 "#version 450

in _FROM_VERTEX_
{
    int[3] _VERTEX_OUT_1;
};

layout(location = 0) out vec4 _FRAGMENT_OUT_0;

void main() {
    vec4 g_G1200 = vec4(float(_VERTEX_OUT_1[0]),float(0),float(0),float(0));
    _FRAGMENT_OUT_0 = g_G1200;
    return;
}
")

I'm not sure this compiles yet though :p time to go play I guess

cbaggers commented 7 years ago

Bwuhaha, finally some progress:

This lisp code:

(defun-g normals-vert ((vert g-pnt) &uniform (model->clip :mat4))
  (values (* model->clip (v! (pos vert) 1))
          (s~ (* model->clip (v! (norm vert) 0)) :xyz)))

(defun-g normals-geom ((normals (:vec3 3)))
  (declare (varjo:output-primitive :kind :line-strip :max-vertices 6))
  (labels ((gen-line ((index :int))
             (let ((magnitude 0.2))
               (setf gl-position (gl-position (aref gl-in index)))
               (emit-vertex)
               (setf gl-position
                     (+ (gl-position (aref gl-in index))
                        (* (v! (aref normals index) 0f0)
                           magnitude)))
               (emit-vertex)
               (end-primitive)
               (values))))
    (gen-line 0)
    (gen-line 1)
    (gen-line 2)
    (values)))

(defun-g normals-frag ()
  (v! 1 1 0 1))

(def-g-> draw-normals ()
  :vertex (normals-vert g-pnt)
  :geometry (normals-geom (:vec3 3))
  :fragment (normals-frag))

makes this glsl:

("#version 450

in vec3 fk_vert_position;
in vec3 fk_vert_normal;
in vec2 fk_vert_texture;

out _FROM_VERTEX_
{
    out vec3 _VERTEX_OUT_1;
};

uniform mat4 MODEL_62CLIP;

void main() {
    vec3 return1;
    vec4 g_G1550 = (MODEL_62CLIP * vec4(fk_vert_position,float(1)));
    return1 = (MODEL_62CLIP * vec4(fk_vert_normal,float(0))).xyz;
    gl_Position = g_G1550;
    vec3 g_G1552 = return1;
    _VERTEX_OUT_1 = g_G1552;
    return;
}
#version 450

layout (triangles) in;

in _FROM_VERTEX_
{
    in vec3 _VERTEX_OUT_1;
} inputs[3];

layout (line_strip, max_vertices = 6) out;

void GEN_LINE(int INDEX);

void GEN_LINE(int INDEX) {
    float MAGNITUDE = 0.2f;
    gl_Position = gl_in[INDEX].gl_Position;
    EmitVertex();
    gl_Position = (gl_in[INDEX].gl_Position + (vec4(inputs[INDEX]._VERTEX_OUT_1,0.0f) * MAGNITUDE));
    EmitVertex();
    EndPrimitive();
}

void main() {
    GEN_LINE(0);
    GEN_LINE(1);
    GEN_LINE(2);
}
#version 450

layout(location = 0) out vec4 _FRAGMENT_OUT_0;

void main() {
    vec4 g_G1553 = vec4(float(1),float(1),float(0),float(1));
    _FRAGMENT_OUT_0 = g_G1553;
    return;
}

Which let me draw these: norms

cbaggers commented 7 years ago

Next I have to fix up the glsl-stage support as handling interface blocks made this way trickier than before. I also need to finish the primitive propagation code. It's all looking good though.

djeis97 commented 7 years ago

That looks awesome! I'll try updating my bezier geometry shader soon.

cbaggers commented 7 years ago

ah feck, one thing I forgot in the happiness of getting something working is I havent added support for add the user defined per-vertex outputs. I'll clean up glsl stages first though

cbaggers commented 7 years ago

glsl stages in CEPL are coming back to life. The old fragment example works fine again. Geometry (and eventually tesselation) stages have the extra problem of having the extra array level, in the lisp signatures we write this as just an array of the type vec4 becomes (vec4 3) for example. However version of glsl before 4.3 dont support arrays of arrays so we actually array the interface block instead. So:

(defun-g normals-geom (("normals" (:vec3 3))) 
  ..)

becomes

in _FROM_VERTEX_
{
    in vec3 _VERTEX_OUT_1;
} inputs[3];

This means instead of writing normals[1] in your glsl like you would expect, you need to write inputs[1].normals. I will use a simple regex to fix this discrepancy soon.

@djeis97 Do you use tessellation stages in CEPL/Varjo yet? I'm expecting they are broken on my branch, I'll need to give them some love sometime too.

djeis97 commented 7 years ago

I'd been playing with them a little, got a basic bezier curve tessellation shader working using inline glsl. If I find time soon I'll see if these changes have broken anything there.

cbaggers commented 7 years ago

Here is this week's writeup of this: http://techsnuffle.com/2017/04/18/geometry-shader-shenanigans

cbaggers commented 7 years ago

Good progress already today. I have added emit-data which is the function that solves the 'adding per-vertex data' issue.

It behaves like return in that it can handle multiple values, is checked to be consistent by the compiler (in and across stages) and creates the out block for you. It is used like other per-vertex data, you call it and then call emit-vertex.

(varjo.tests::compile-geom ((normals (:vec3 3))) :450 t
  (declare (output-primitive :kind :line-strip :max-vertices 6))
  (labels ((gen-line ((index :int))
             (let ((magnitude 0.4))
               (setf gl-position (gl-position (aref gl-in index)))
               (emit-data (values (v! 1 2 3 4)  ;; <<<<<<<<<<<
                                  (v! 5 5)))
               (emit-vertex)
               (setf gl-position
                     (+ (gl-position (aref gl-in index))
                        (* (v! (aref normals index) 0f0)
                           magnitude)))
               (emit-data (values (v! 1 2 3 4)  ;; <<<<<<<<<<<
                                  (v! 5 5)))
               (emit-vertex)
               (end-primitive)
               (values))))
    (gen-line 0)
    (gen-line 1)
    (gen-line 2)
    (values)))
#version 450

layout (triangles) in;

in _IN_BLOCK_
{
    in vec3 NORMALS;
} inputs[3];

layout (line_strip, max_vertices = 6) out;

out _FROM_GEOMETRY_  // <<<<<<<<<<<<
{
    out vec4 _GEOMETRY_OUT_0;
    out vec2 _GEOMETRY_OUT_1;
};

void GEN_LINE(int INDEX);

void GEN_LINE(int INDEX) {
    float MAGNITUDE = 0.4f;
    gl_Position = gl_in[INDEX].gl_Position;
    vec2 return1;
    vec4 g_G1110 = vec4(float(1),float(2),float(3),float(4));
    return1 = vec2(float(5),float(5));
    vec4 g_G1112 = g_G1110;
    _GEOMETRY_OUT_0 = g_G1112; // <<<<<<<<<<<<
    vec2 g_G1113 = return1;
    _GEOMETRY_OUT_1 = g_G1113; // <<<<<<<<<<<<
    EmitVertex();
    gl_Position = (gl_in[INDEX].gl_Position + (vec4(inputs[INDEX].NORMALS,0.0f) * MAGNITUDE));
    vec2 return1;
    vec4 g_G1114 = vec4(float(1),float(2),float(3),float(4));
    return1 = vec2(float(5),float(5));
    vec4 g_G1116 = g_G1114;
    _GEOMETRY_OUT_0 = g_G1116; // <<<<<<<<<<<<
    vec2 g_G1117 = return1;
    _GEOMETRY_OUT_1 = g_G1117; // <<<<<<<<<<<<
    EmitVertex();
    EndPrimitive();
}

void main() {
    GEN_LINE(0);
    GEN_LINE(1);
    GEN_LINE(2);
}

I'm pretty happy with this. It's a bit messy but that is just due to how the GLSL for multiple returns is generated right now. When I go back and make that a little smarter this code will get cleaner

In CEPL the GLSL stages will simply use the same syntax as usual as there you explicitly declare the out params anyway

cbaggers commented 7 years ago

hehe with this we can now define an emit macro like this:

(v-defmacro emit ((&key position point-size)
                  &rest data)
  (assert position)
  `(progn
     (setf gl-position ,position)
     ,@(when point-size `((setf gl-point-size ,point-size)))
     (emit-data (values ,@data))
     (emit-vertex)))

and rewrite the above lisp code to:

(glsl-code
        (varjo.tests::compile-geom ((normals (:vec3 3))) :450 t
          (declare (output-primitive :kind :line-strip :max-vertices 6))
          (labels ((gen-line ((index :int))
                     (let ((magnitude 0.4))
                       (emit (:position (gl-position (aref gl-in index)))
                             (v! 1 2 3 4)
                             (v! 5 5))
                       (emit (:position (+ (gl-position (aref gl-in index))
                                           (* (v! (aref normals index) 0f0)
                                              magnitude)))
                             (v! 1 2 3 4)
                             (v! 5 5))
                       (end-primitive)
                       (values))))
            (gen-line 0)
            (gen-line 1)
            (gen-line 2)
            (values))))

This isnt the final version of this macro, I just love how it took 2 seconds to make this nicer once it was lisp. Yay macros!

cbaggers commented 7 years ago

@djeis97 I've cloned your bezier project and have found some bugs in the def-glsl-stage code (as expected) nothing fundamental though, hopefully will have it fixed tonight.

cbaggers commented 7 years ago

OK I've got some progress and some limitations. Good news is that geometry glsl stages can work, see the attached code.

Now for the limitations:

I'd love to tackle that last one when I have a glsl parser but for now we are kind of stuck with it.

That's all for tonight, the work is on the feature-cross-shader branch of Varjo & the feature-varjo-return-sets branch of CEPL. It's not stable enough to merge yet but it's getting there.

Ciao

(def-glsl-stage geom-glsl (("control" (:vec4 2)) ("color" (:vec4 2))
                           &uniform
                           ("transform" :mat4)
                           ("detail" :int)
                           &context :330 :geometry :lines)
  "
layout(line_strip, max_vertices=20) out;

vec3 evaluateBezierPosition( vec3 v[4], float t )
{
    vec3 p;
    float OneMinusT = 1.0 - t;
    float b0 = OneMinusT*OneMinusT*OneMinusT;
    float b1 = 3.0*t*OneMinusT*OneMinusT;
    float b2 = 3.0*t*t*OneMinusT;
    float b3 = t*t*t;
    return b0*v[0] + b1*v[1] + b2*v[2] + b3*v[3];
}

/**
*    Main
*/
void main()
{
  color_out = inputs[0].color;
  vec3 pos[4];
  pos[0] = gl_in[0].gl_Position.xyz;
  pos[1] = inputs[0].control.xyz;
  pos[2] = inputs[1].control.xyz;
  pos[3] = gl_in[1].gl_Position.xyz;
  float OneOverDetail = 1.0 / float(detail-1.0);
  for( int i=0; i<detail; i++ )
  {
    float t = i * OneOverDetail;
    vec3 p = evaluateBezierPosition( pos, t );
    gl_Position = transform * vec4( p.xyz, 1.0 );
    EmitVertex();
  }

    EndPrimitive();
}" (("color_out" :vec4)))
cbaggers commented 7 years ago

I've merged an enormous amount of stuff to master this evening. If you are working from git repos you will want to pull varjo, cepl, cepl.sdl2, skitter & cepl.skitter. This includes all the geometry stuff. Tessellation is not finished (and may be broken in CEPL) but I've been reading the glsl spec & wiki and it looks like getting the tessellation support with be easy (most of the hard stuff was done getting geometry working)

I'm away this weekend but may push a little bit here and there if I have time

cbaggers commented 7 years ago

Should be fixed in master now. I need to document this, but to see an example of a full pipeline see build test 20