1%%
2%%  wings_pick_nif.erl --
3%%
4%%     This module handles picking.
5%%
6%%  Copyright (c) 2009-2019 Bjorn Gustavsson & Dan Gudmundsson
7%%
8%%  See the file "license.terms" for information on usage and redistribution
9%%  of this file, and for a DISCLAIMER OF ALL WARRANTIES.
10%%
11%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
12%%
13%% This module and driver implements picking of faces, edges, and vertices
14%% without using the selection support in OpenGL. The selection support in
15%% OpenGL is not use by many applications, so it may not work reliably in
16%% all implementations of OpenGL.
17%%
18%% Conceptually, we use the same algorithm as OpenGL. We set up a special
19%% view volume that only includes a few pixels on each side of the mouse
20%% cursor (or what is inside the marquee) using a special pick matrix.
21%% We then go through all objects in the scene to which faces/edges/vertices
22%% fall inside the view volume.
23%%
24%% We use a different pick matrix and view volume than OpenGL, namely
25%% 0 <= X <= 1, 0 <= Y <= 1, 0 <= Z <= 1 instead of -1 <= X <= 1,
26%% -1 <= Y <= 1, -1 <= Z <= 1 as suggested by Jim Blinn in
27%% A Trip Down the Graphics Pipeline.
28%%
29%% Main references:
30%%
31%% Jim Blinn: A Trip Down the Graphics Pipeline. Chapter 13: Line Clipping.
32%%
33%% Paul Heckbert: Generic Convex Polygon Scan Conversion and Clipping in
34%%                Graphics Gems.
35%%
36-module(wings_pick_nif).
37-export([pick_matrix/5,matrix/2,cull/1,culling/0,front_face/1,
38	 faces/2,vertices/1,edges/1]).
39
40-on_load(init/0).
41
42-import(lists, [foldl/3,last/1,sort/1]).
43-define(FL, 32/native-float).
44
45%% Comment out the following line to use the pure Erlang
46%% reference implementation.
47-define(USE_DRIVER, 1).
48-define(nif_stub,nif_stub_error(?LINE)).
49nif_stub_error(Line) ->
50    erlang:nif_error({nif_not_loaded,module,?MODULE,line,Line}).
51
52init() ->
53    case get(wings_not_running) of
54	undefined ->
55            Name = "wings_pick_nif",
56	    Dir = case code:priv_dir(wings) of
57                      {error, _} -> filename:join(wings_util:lib_dir(wings),"priv");
58                      Priv -> Priv
59                  end,
60            Nif = filename:join(Dir, Name),
61            erlang:load_nif(Nif, 0);
62	_ ->
63	    false
64    end.
65
66%% pick_matrix(X, Y, Xs, Ys, ViewPort) -> PickMatrix
67%%  Set up a pick matrix like glu:pickMatrix/5,
68%%  but with a different viewing volume (the cube (0...1)^3
69%%  instead of (-1...1)^3).
70%%
71pick_matrix(X, Y, Xs, Ys, ViewPort) ->
72    M0 = e3d_transform:translate(e3d_transform:identity(), {0.5, 0.5, 0.5}),
73    M1 = e3d_transform:scale(M0, {0.5,0.5,0.5}),
74    Pick = e3d_transform:pick(X, Y, Xs, Ys, ViewPort),
75    e3d_transform:mul(M1, Pick).
76
77%% matrix(ModelViewMatrix, ProjectionMatrix)
78%%  Set the matrix to use for picking by combining the model
79%%  view and projection matrices.
80%%
81matrix(Model, Proj) when is_list(Model) ->
82    matrix(list_to_tuple(Model), Proj);
83matrix(Model, Proj) when is_list(Proj) ->
84    matrix(Model, list_to_tuple(Proj));
85matrix(Model, Proj) ->
86    Mat = e3d_mat:mul(Proj, Model),
87    put({?MODULE,matrix}, Mat),
88    ok.
89
90%% cull(true|false)
91%%  Enable or disable backface culling when picking.
92cull(false) ->
93    erase({?MODULE,cull}),
94    ok;
95cull(true) ->
96    put({?MODULE,cull}, true),
97    ok.
98
99culling() ->
100    get({?MODULE,cull}) =:= true.
101
102%% front_face(ccw|cw)
103%%  Define the vertex order for front facing triangles.
104front_face(ccw) ->
105    erase({?MODULE,front_face}),
106    ok;
107front_face(cw) ->
108    put({?MODULE,front_face}, cw),
109    ok.
110
111%% faces({Stride,VertexBuffer}, OneHit) -> {Index,Depth} | [Index]
112%%     Depth = 0..2^32-1 (0 means the near clipping plane)
113%%  Given a vertex buffer containing triangles, either return
114%%  {Index,Depth} (if OneHit is 'true'), or a list of indices for each
115%%  triangle that are wholly or partly inside the viewing volume
116%%  (if OneHit is 'false').
117%%
118-ifdef(USE_DRIVER).
119faces({_,<<>>}, _) ->
120    %% An empty binary is most probably not reference-counted,
121    %% so we must *not* send it down to the driver. (The length
122    %% of the I/O vector will be 2, not 3, and the driver will
123    %% ignore the request without sending any data back to us.)
124    [];
125faces({Stride, Bin}, OneHit) ->
126    faces_1(Stride, Bin, OneHit,
127            get({?MODULE,cull}) =:= true,
128            get({?MODULE,front_face}) /= cw,
129            get({?MODULE,matrix})
130           ).
131
132faces_1(_, _, _, _, _, _) ->
133    ?nif_stub.
134
135-else.
136faces({Stride,Bin}, OneHit) ->
137    Matrix = get({?MODULE,matrix}),
138    Cull0 = get({?MODULE,cull}) =:= true,
139    CwIsFront = get({?MODULE,front_face}) =:= cw,
140    Cull = case {Cull0,CwIsFront} of
141	       {false,_} -> none;
142	       {true,true} -> cull_ccw;
143	       {true,false} -> cull_cw
144	   end,
145    faces_1(Bin, Stride-12, Matrix, Cull, OneHit, 0, []).
146-endif.
147
148%% vertices([{Vertex,Position}]) -> [Vertex]
149%%  Return a list of all vertices that are inside the
150%%  viewing volume.
151%%
152vertices(VsPos) ->
153    Matrix = get({?MODULE,matrix}),
154    vertices_1(VsPos, Matrix, []).
155
156%% vertices([{Edge,Position}]) -> [Edges]
157%%  Return a list of all edges that are inside the
158%%  viewing volume.
159%%
160edges(EsPos) ->
161    Matrix = get({?MODULE,matrix}),
162    edges_1(EsPos, Matrix, []).
163
164%%%
165%%% Internal functions.
166%%%
167
168vertices_1([{V,{X0,Y0,Z0}}|T], Mat, Acc) ->
169    {X,Y,Z,W} = e3d_mat:mul(Mat, {X0,Y0,Z0,1.0}),
170    Inside = X >= 0 andalso W-X >= 0 andalso
171	Y >= 0 andalso W-Y >= 0 andalso
172	Z >= 0 andalso W-Z >= 0,
173    case Inside of
174	true ->
175	    vertices_1(T, Mat, [V|Acc]);
176	false ->
177	    vertices_1(T, Mat, Acc)
178    end;
179vertices_1([], _, Acc) -> Acc.
180
181edges_1([{E,{P0,P1}}|T], Mat, Acc) ->
182    case edge_visible(P0, P1, Mat) of
183	false -> edges_1(T, Mat, Acc);
184	true -> edges_1(T, Mat, [E|Acc])
185    end;
186edges_1([], _, Acc) ->
187    Acc.
188
189edge_visible({X0,Y0,Z0}, {X1,Y1,Z1}, Mat) ->
190    Pos0 = e3d_mat:mul(Mat, {X0,Y0,Z0,1.0}),
191    Pos1 = e3d_mat:mul(Mat, {X1,Y1,Z1,1.0}),
192    OutCode0 = outcode(Pos0),
193    OutCode1 = outcode(Pos1),
194    case OutCode0 band OutCode1 of
195	0 ->
196	    case OutCode0 bor OutCode1 of
197		0 ->
198		    %% Both endpoints are inside all planes. Trivial accept.
199		    true;
200		Clip ->
201		    non_trivial_edge_visible(OutCode0, Clip, Pos0, Pos1,
202					     32, 0.0, 1.0)
203	    end;
204	_ ->
205	    %% Both endpoints are outside the same plane. Trivial reject.
206	    false
207    end.
208
209non_trivial_edge_visible(_Code0, _Clip, _P0, _P1, 0, _A0, _B0) ->
210    %% The line has been clipped against all planes and
211    %% rejected. Non-trivial accept.
212    true;
213non_trivial_edge_visible(Code0, Clip, P0, P1, Plane, A0, B0) ->
214    case Clip band Plane of
215	0 ->
216	    %% Both endpoints are on the inside side of the plane.
217	    %% Continue with the next plane.
218	    non_trivial_edge_visible(Code0, Clip, P0, P1, Plane bsr 1, A0, B0);
219	_ ->
220	    %% One endpoint outside, one inside.
221	    Dot0 = pdot2(Plane, P0),
222	    Dot1 = pdot2(Plane, P1),
223	    NewAlpha = Dot0 / (Dot0 - Dot1),
224	    {A,B} = case Code0 band Plane of
225			0 ->
226			    {A0,min(B0, NewAlpha)};
227			_ ->
228			    {max(A0, NewAlpha),B0}
229		    end,
230	    if
231		B < A ->
232		    %% The line is completely outside of all planes.
233		    %% Non-trivial reject.
234		    false;
235		true ->
236		    non_trivial_edge_visible(Code0, Clip, P0, P1, Plane bsr 1, A, B)
237	    end
238    end.
239
240-define(SHIFT_OUT(Code, Dot), if Dot < 0.0 -> (Code bsl 1) bor 1;
241				 true -> Code bsl 1 end).
242outcode({X,_,_,_}=P) ->
243    outcode_1(P, ?SHIFT_OUT(0, X)).
244
245outcode_1({X,_,_,W}=P, Code) ->
246    outcode_2(P, ?SHIFT_OUT(Code, W-X)).
247
248outcode_2({_,Y,_,_}=P, Code) ->
249    outcode_3(P, ?SHIFT_OUT(Code, Y)).
250
251outcode_3({_,Y,_,W}=P, Code) ->
252    outcode_4(P, ?SHIFT_OUT(Code, W-Y)).
253
254outcode_4({_,_,Z,_}=P, Code) ->
255    outcode_5(P, ?SHIFT_OUT(Code, Z)).
256
257outcode_5({_,_,Z,W}, Code) ->
258    ?SHIFT_OUT(Code, W-Z).
259
260pdot2(32, {X,_,_,_}) -> X;
261pdot2(16, {X,_,_,W}) -> W-X;
262pdot2(8, {_,Y,_,_}) -> Y;
263pdot2(4, {_,Y,_,W}) -> W-Y;
264pdot2(2, {_,_,Z,_}) -> Z;
265pdot2(1, {_,_,Z,W}) -> W-Z.
266
267
268%%%
269%%% Reference implementation in pure Erlang of face picking.
270%%%
271
272-ifndef(USE_DRIVER).
273faces_1(Bin0, Unused, Mat, Cull, OneHit, I, Acc) ->
274    case Bin0 of
275	<<X1:?FL,Y1:?FL,Z1:?FL,_:Unused/binary,
276          X2:?FL,Y2:?FL,Z2:?FL,_:Unused/binary,
277          X3:?FL,Y3:?FL,Z3:?FL,_:Unused/binary,
278          Bin/binary>> ->
279	    Tri0 = [{X1,Y1,Z1,1.0},{X2,Y2,Z2,1.0},{X3,Y3,Z3,1.0}],
280	    Tri = [e3d_mat:mul(Mat, P) || P <- Tri0],
281	    case clip_tri(Tri, Cull) of
282		[] ->
283		    %% Outside.
284		    faces_1(Bin, Unused, Mat, Cull, OneHit, I+3, Acc);
285		[{_,_,Z,W}|_] ->
286		    %% Inside. Now clipped to the view frustum.
287		    Depth = round((Z/W)*16#FFFFFFFF),
288		    faces_1(Bin, Unused, Mat, Cull, OneHit, I+3, [{Depth,I}|Acc])
289	    end;
290	<<>> ->
291	    Hits = sort(Acc),
292	    case OneHit of
293		false ->
294		    sort([Hit || {_,Hit} <- Hits]);
295		true ->
296		    case Hits of
297			[] -> [];
298			[{Depth,Hit}|_] -> {Hit,Depth}
299		    end
300	    end
301    end.
302
303clip_tri(Tri, Cull) ->
304    case clip_tri_1(Tri) of
305	[] -> [];
306	Vs ->
307	    Inside = case Cull of
308			 none -> true;
309			 cull_cw -> is_ccw(Vs);
310			 cull_ccw -> not is_ccw(Vs)
311		     end,
312	    case Inside of
313		true -> Vs;
314		false -> []
315	    end
316    end.
317
318clip_tri_1(Tri) ->
319    OutCodes = [outcode(P) || P <- Tri],
320    And = foldl(fun(Code, Acc) -> Code band Acc end, 16#3F, OutCodes),
321    case And of
322	0 ->
323	    Or = foldl(fun(Code, Acc) -> Code bor Acc end, 0, OutCodes),
324	    case Or of
325		0 ->
326		    %% All vertices are inside all planes. Trivial accept.
327		    Tri;
328		_ ->
329		    %% Handle the non-trivial cases.
330		    non_trivial(Tri)
331	    end;
332	_ ->
333	    %% All vertices are outside at least one of the planes.
334	    %% Trivial reject.
335	    []
336    end.
337
338non_trivial(Ps) ->
339    non_trivial_1(Ps, 6).
340
341non_trivial_1(Ps, 0) ->
342    %% Checked against all planes and not rejected. Non-trivial accept.
343    Ps;
344non_trivial_1(Ps0, Plane) ->
345    case non_trivial_2(last(Ps0), Ps0, Plane) of
346	Ps when length(Ps) < 3 ->
347	    %% No longer a triangle or polygon. Non-trivial reject.
348	    [];
349	Ps ->
350	    non_trivial_1(Ps, Plane-1)
351    end.
352
353non_trivial_2(Prev, [P|T], Plane) ->
354    case {out(Plane, Prev),out(Plane, P)} of
355	{false,false} ->
356	    %% Both inside. Keep current vertex (P).
357	    [P|non_trivial_2(P, T, Plane)];
358	{false,true} ->
359	    %% Previous inside, current outside.
360	    %% Keep intersection of edge and clipping plane.
361	    [intersection(Prev, P, Plane)|non_trivial_2(P, T, Plane)];
362	{true,false} ->
363	    %% Previous outside, current inside.
364	    %% Keep intersection of edge and clipping plane,
365	    %% followed by current.
366	    [intersection(Prev, P, Plane),P|non_trivial_2(P, T, Plane)];
367	{true,true} ->
368	    %% Both outside. Remove the current vertex.
369	    non_trivial_2(P, T, Plane)
370    end;
371non_trivial_2(_, [], _) -> [].
372
373is_ccw([{X1,Y1,_,W1},{X2,Y2,_,W2},{X3,Y3,_,W3}|_]) ->
374    XWinC = X3/W3,
375    YWinC = Y3/W3,
376    DxAC = X1/W1 - XWinC,
377    DxBC = X2/W2 - XWinC,
378    DyAC = Y1/W1 - YWinC,
379    DyBC = Y2/W2 - YWinC,
380    Area = DxAC * DyBC - DxBC * DyAC,
381    Area >= 0.0.
382
383intersection(P0, P1, Plane) ->
384    Dot0 = pdot(Plane, P0),
385    Dot1 = pdot(Plane, P1),
386    A = Dot0 / (Dot0 - Dot1),
387    add(P0, mul(sub(P1, P0), A)).
388
389mul({V10,V11,V12,V13}, S) when is_float(S) ->
390    {V10*S,V11*S,V12*S,V13}.
391
392sub({V10,V11,V12,V13}, {V20,V21,V22,V23}) ->
393    {V10-V20,V11-V21,V12-V22,V13-V23}.
394
395add({V10,V11,V12,V13}, {V20,V21,V22,V23})
396  when is_float(V10), is_float(V11), is_float(V12) ->
397    {V10+V20,V11+V21,V12+V22,V13+V23}.
398
399out(Plane, P) -> pdot(Plane, P) < 0.0.
400
401pdot(1, {X,_,_,_}) -> X;
402pdot(2, {X,_,_,W}) -> W-X;
403pdot(3, {_,Y,_,_}) -> Y;
404pdot(4, {_,Y,_,W}) -> W-Y;
405pdot(5, {_,_,Z,_}) -> Z;
406pdot(6, {_,_,Z,W}) -> W-Z.
407-endif.
408