Blob Blame History Raw
From 5dec5d2abe1ed4b699769c5eb44547a950ff8b1f Mon Sep 17 00:00:00 2001
From: Peter Lemenkov <lemenkov@gmail.com>
Date: Thu, 10 May 2012 23:52:56 +0400
Subject: [PATCH 1/6] No Erlang OpenCL support for now

Signed-off-by: Peter Lemenkov <lemenkov@gmail.com>
---
 src/wings_cc.erl     | 866 ---------------------------------------------------
 src/wings_cc_ref.erl | 449 --------------------------
 src/wings_cl.erl     | 108 +------
 src/wings_proxy.erl  |  78 +----
 4 files changed, 5 insertions(+), 1496 deletions(-)

diff --git a/src/wings_cc.erl b/src/wings_cc.erl
index 09ac158..54592ee 100644
--- a/src/wings_cc.erl
+++ b/src/wings_cc.erl
@@ -24,869 +24,3 @@
 %%%
 
 -module(wings_cc).
--export([init/3, update/2, gen_vab/1, gen_vab/2]).
-
-%% debug 
--import(lists, [reverse/1, foldl/3]).
-
--define(NEED_OPENGL, 1).
--include("wings.hrl").
--include_lib("cl/include/cl.hrl").
-
--compile(export_all).
-
--define(PL_UNITS, 4).
-
--record(v, {pos,                     % position
-	    vc}).                    % Valence
-
-%% The different working sets
-
--record(base, {v,    %% array of #v{}           nv
-	       f,    %% array of [v0,v1..,vn]   nf
-	       fi,   %% array of {Start,Size}   nf
-	       e,    %% array of v0,v1,f1,f2    ne
-	       as,   %% Vertex attrs
-	       level,%% Subdiv levels
-	       n,    %% Number of faces 
-	       mmap, %% Material map, {mat, start, vertex_count}
-	       vmap, %% array Wings Vertex Id -> CL vertex id
-	       fmap, %% gb_tree Wings face id -> CL face id
-	       type  %% Type of data plain,uv,color,color_uv
-	      }).
-
-%% OpenCL defines
--record(cls,      
-	{cl,
-	 %% CL temp buffers and respective sizes	  
-	 vab, vab_sz=0, fl, fl_sz=0, fi, fi_sz=0,
-	 sn, sn_sz %% Smooth normals ? can reuse fl?
-	}).
-
--record(cl_mem,   {v, v_no, f, fs_no, e, e_no, fi, fi0, as, max_vs}).
--record(cc_cache, {mem, old, wait}).
-
--define(EDGE_SZ, (4*4)).
--define(FACE_SZ, (4*4)).
--define(VERTEX_SZ, ((3*4)+4)).
--define(LOCK_SZ, 32).
-%%-define(DEFAULT, erlang).
--define(DEFAULT, opencl).
-
-%%%% API %%%%%%%%%
-
-%% Returns opaque data
-init(Plan, Level, We) when is_integer(Level) ->
-    build_data(Plan,Level,We,?DEFAULT);
-
-init(Plan, #base{level=Level}, We)  ->
-    build_data(Plan,Level,We,?DEFAULT).
-
-%% Update state with new vertex positions
-update(ChangedVs, Data) ->
-    case ?DEFAULT of 
-	erlang ->  wings_cc_ref:update(ChangedVs, Data);
-	_ ->       update_1(ChangedVs, Data)
-    end.
-
-%% Generates a subdivided #vab{}
-gen_vab(Base) ->
-    try
-	case subdiv(Base, ?DEFAULT) of
-	    skip -> create_vab(<<>>, []);
-	    Data ->
-		gen_vab_1(Data, Base)
-	end
-    catch
-	exit:{out_of_resources, Wanted, CardMax} ->
-	    io:format(?__(1,"OpenCL subd failed: wanted ~pMB only ~pMB available~n"), 
-		      [Wanted, CardMax]),
-	    DecBase = decrease_level(Base),
-	    gen_vab(DecBase)	   
-    end.
-%% Generates a subdivided #vab{} from Material Plan
-gen_vab(Plan, Base) ->
-    try 
-	case subdiv(Base, ?DEFAULT) of
-	    skip -> create_vab(<<>>, []);
-	    Data ->
-		gen_vab_1(Plan, Data, Base)
-	end
-    catch
-	exit:{out_of_resources, Wanted, CardMax} ->
-	    io:format(?__(1,"OpenCL subd failed: wanted ~pMB only ~pMB available~n"), 
-		      [Wanted, CardMax]),
-	    DecBase = decrease_level(Base),
-	    gen_vab(Plan, DecBase)
-    end.
-
-%% Subdivide mesh
-subdiv(Base = #base{level=N, n=Total, type=Type}, Impl) when Total > 0 ->
-    case Impl of
-	opencl ->
-	    {In,Out,CL} = cl_allocate(Base, cl_setup()),
-	    Wait = cl_write_input(Base, In, Out, CL),
-	    subdiv_1(N, In, Out, Type, CL, Wait);
-	erlang ->		
-	    wings_cc_ref:subdiv(Base)
-    end;
-subdiv(_, _) ->
-    skip.
-
-%% Generates a vab (and updates Data)
-%% Returns Vab
-gen_vab_1(Data0, Base) ->
-    case ?DEFAULT of
-	erlang -> create_vab(wings_cc_ref:gen_vab(Data0, Base), Base);
-	opencl -> create_vab(gen_vab_2(Data0, Base), Base)
-    end.
-
-gen_vab_1(Plan, Data, Base) ->
-    case ?DEFAULT of
-	erlang -> create_vab(wings_cc_ref:gen_vab(Plan, Data, Base), Base);
-	opencl -> create_vab(gen_vab_2(Plan, Data, Base), Base)
-    end.
-
-create_vab({Vs, SNs0, Attrs0, Edges, MatInfo}, #base{type=Type}) ->
-    Ns = case Vs of
-	     <<>> -> Vs;
-	     <<_:3/unit:32,NsP/bytes>> ->
-		 NsP
-	 end,
-    S = 3*4+3*4,
-    SNs = case SNs0 of
-	      <<>> -> {S, Ns};
-	      _ -> {4*4, SNs0}  %% Special case easier cl code
-	  end,
-    Colors = case Attrs0 of 
-		 <<>> -> none;
-		 _ when Type =:= color ->
-		     {3*4, Attrs0};
-		 _ when Type =:= color_uv ->
-		     {5*4, Attrs0};
-		 _ -> none		     
-	     end,
-    UVs = case Attrs0 of
-	      <<>> -> none;
-	      _ when Type =:= uv ->
-		  {2*4, Attrs0};
-	      <<_:3/unit:32,UVBin/bytes>> 
-		when Type =:= color_uv ->
-		  {5*4, UVBin};
-	      _ -> none
-	  end,
-    #vab{face_vs={S,Vs},face_fn={S,Ns}, face_es=Edges,
-	 face_sn=SNs, face_vc=Colors, face_uv=UVs,
-	 mat_map=MatInfo}.
-
-update_1(ChangedVs0, #base{vmap=VMap, v=VsBin0}=Base)
-  when is_list(ChangedVs0) ->
-    ChangedVs = [{array:get(Id,VMap),Pos} || {Id,Pos} <- ChangedVs0],
-    VsList = update_vs(lists:sort(ChangedVs), 0, VsBin0),
-    VsBin  = iolist_to_binary(VsList),
-    Base#base{v=VsBin};
-
-update_1(#we{vp=Vpos}, #base{vmap=VMap, v=VsBin0}=Base) ->
-    Change = fun(Vid, CLid, Acc) ->
-		     Pos = array:get(Vid, Vpos),
-		     Skip = CLid*16+12,
-		     <<_:Skip/binary, VI:4/binary, _/binary>> = VsBin0,
-		     [{CLid, Pos, VI}|Acc]
-	     end,
-    VsInfo = array:sparse_foldl(Change, [], VMap),
-    VsBin = << <<X:?F32,Y:?F32,Z:?F32,VI/binary>> 
-	       || {_,{X,Y,Z}, VI} <- lists:sort(VsInfo) >>,
-    true = size(VsBin) == size(VsBin0), %% Assert
-    Base#base{v=VsBin}.
-    
-update_vs([{Id, {X,Y,Z}}|Vs], Where, Bin) ->
-    Skip = Id*4*4-Where,
-    <<Head:Skip/binary, _:(4*3)/binary, Rest/binary>> = Bin,
-    New = <<X:?F32,Y:?F32,Z:?F32>>,
-    [Head, New | update_vs(Vs, Where+Skip+12, Rest)];
-update_vs([], _, Bin) -> [Bin].
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-
-build_data({Type, MatFs}, N, We0, Impl) ->
-    {FMap0, We} = gen_fmap(MatFs, We0),
-    FMap  = gb_trees:from_orddict(lists:sort(FMap0)),
-    Empty = array:new(),
-    StartAcc  = {Empty, Empty, {0, Empty}},
-    Get = fun(V,Eid,E,Acc) ->  
-		  get_face_info(V,Eid,E,Acc,FMap,We)
-	  end,
-    B0 = case Type of
-	     plain -> build_data_plain(FMap0, [], StartAcc, Get, We);
-	     _ ->  
-		 {Attrs, _Sz} = attrs(Type),
-		 build_data_attrs(FMap0, [], [], StartAcc, Get, Attrs, We)
-	 end,
-    B1 = calc_matmap(MatFs, B0#base{type=Type, level=N}),
-    pack_data(B1, Impl).
-
-build_data_plain([{F,_}|Fs], Ftab0, Acc0, Get, We) -> 
-    {Vs, Acc} = wings_face:fold(Get, {[], Acc0}, F, We), %% CCW
-    build_data_plain(Fs, [Vs|Ftab0], Acc, Get, We);
-build_data_plain([], Ftab0, {Vtab, Etab, {_,VMap}}, _, _) ->
-    Ftab = reverse(Ftab0),
-    #base{v=Vtab, e=Etab, f=Ftab, vmap=VMap}.
-
-build_data_attrs([{F,_}|Fs], Ftab0, Attrs, Acc0, Get, Type, We) -> 
-    Attr = wings_va:face_attr(Type, F, We),
-    {Vs, Acc} = wings_face:fold(Get, {[], Acc0}, F, We), %% CCW
-    build_data_attrs(Fs, [Vs|Ftab0], [Attr|Attrs], Acc, Get, Type, We);
-build_data_attrs([], Ftab, Attrs, {Vtab, Etab, {_,VMap}}, _, _, _) ->
-    #base{v=Vtab, e=Etab, f=reverse(Ftab), 
-	  vmap=VMap, as=reverse(Attrs)}.
-
-gen_fmap(Plan, We = #we{}) ->
-    Fmap0=[{_,Last}|_] = gen_fmap(Plan, 0, []),
-    %% Add hidden faces but not holes
-    {Hidden, Htab} = hidden_fs(We),
-    Fmap = reverse(gen_fmap2(Hidden, Last+1, Fmap0)),
-    {Fmap, We#we{he=Htab}}.
-
-gen_fmap([{_Mat, Fs}|MatFs], Curr, Fmap0) ->
-    Fmap = [{_,Last}|_] = gen_fmap2(Fs, Curr, Fmap0),
-    gen_fmap(MatFs, Last+1, Fmap);
-gen_fmap([], _, Fmap) ->
-    Fmap.
-
-gen_fmap2([Face|Fs], Id, Fmap) ->
-    gen_fmap2(Fs, Id+1, [{Face, Id}|Fmap]);
-gen_fmap2([],_,Fmap) -> Fmap.
-
-hidden_fs(#we{mirror=none, holes=[], fs=Ftab, he=Htab}) -> 
-    {hidden_fs2(gb_trees:iterator(Ftab),none,[]), Htab};
-hidden_fs(We = #we{mirror=Mirror, holes=Holes, fs=Ftab, he=Htab}) -> 
-    Exclude = case Mirror of
-		  none -> Holes;
-		  _ -> ordsets:add_element(Mirror, Holes)
-	      end,
-    He0 = wings_face:to_edges(Exclude, We),
-    He = gb_sets:union(gb_sets:from_list(He0), Htab),
-    {hidden_fs2(gb_trees:iterator(Ftab),Exclude,[]), He}.
-
-hidden_fs2(Iter0, none, Hidden) ->
-    case gb_trees:next(Iter0) of
-	{Face, _, Iter} when Face < 0 ->
-	    hidden_fs2(Iter, none, [Face|Hidden]);
-	_ ->
-	    Hidden
-    end;
-hidden_fs2(Iter0, Exclude, Hidden) ->
-    case gb_trees:next(Iter0) of
-	{Face, _, Iter} when Face < 0 ->
-	    case ordsets:is_element(Face, Exclude) of
-		true -> 
-		    hidden_fs2(Iter, Exclude, Hidden);
-		false ->
-		    hidden_fs2(Iter, Exclude, [Face|Hidden])
-	    end;
-	_ ->
-	    Hidden
-    end.
-
-calc_matmap(MatMap0, B=#base{f=Ftab0, level=N}) ->
-    Mul = trunc(math:pow(4,N-1)),  %% Subd level 
-    {Total, MatMap, FMap} = calc_matmap(MatMap0, 0, Ftab0, Mul, [], []),
-    B#base{n=Total, mmap=MatMap, fmap=FMap}.
-
-calc_matmap([{Mat,Fs}|Mfs], Start, Ftab0, Mul, FMap0, Acc) ->
-    {Next, Ftab, FMap} = calc_matmap_1(Fs, Ftab0, Mul, Start, FMap0),
-    calc_matmap(Mfs, Next, Ftab, Mul, FMap, 
-		[{Mat, ?GL_QUADS, Start*4, (Next-Start)*4}|Acc]);
-calc_matmap([], Total, _, _, FMap, Acc) ->
-    {Total, reverse(Acc), gb_trees:from_orddict(lists:sort(FMap))}.
-
-calc_matmap_1([Id|Fs], [Vs|Ftab], Mul, Count, FMap) ->
-    VSize = length(Vs),
-    Size = VSize*Mul,
-    FInfo = {Id, {Count, Size}},
-    calc_matmap_1(Fs, Ftab, Mul, Count + Size, [FInfo|FMap]);
-calc_matmap_1([], Ftab, _, Count, FMap) ->
-    {Count, Ftab, FMap}.
-
-decrease_level(#base{level=Level}) when Level =< 1 ->
-    throw(to_large);
-decrease_level(Base = #base{n=Total, level=Level, mmap=MatMap0, fmap=Fmap0}) ->
-    io:format(?__(1,"Could not acquire needed memory, " 
-		  "decreasing to subd level ~p~n"), [Level-1]),
-    MatMap = [{Mat, ?GL_QUADS, Start div 4, Stop div 4} || 
-		 {Mat, ?GL_QUADS, Start, Stop} <- MatMap0],
-    Fmap   = gb_trees:map(fun(_, {Count, Size}) -> 
-				  {Count div 4, Size div 4} 
-			  end,
-			  Fmap0),
-    Base#base{n=Total div 4, level=Level-1, mmap=MatMap, fmap=Fmap}.
-
-get_face_info(Orig, Eid, E, {Vs, {Vtab0, Etab0, VMap0}}, FMap, We) ->
-    {V, Vtab, VMap1} = setup_vertex(Orig, Vtab0, VMap0, We),
-    {Etab, VMap} = setup_edge(Eid, E, VMap1, FMap, Etab0, We#we.he),
-    {[V|Vs], {Vtab, Etab, VMap}}.
-
-setup_vertex(Orig, Vtab, VMap0, We = #we{vp=Vpos,he=He}) ->
-    {V,VMap} = update_vmap(Orig, VMap0),
-    case array:get(V, Vtab) of
-	undefined ->
-	    Count = fun(E,_,_,{C,H}) -> {C+1,add_hard(E,He,H)} end,
-	    N  = wings_vertex:fold(Count, {0, 0}, Orig, We),
-	    VP = #v{pos=array:get(Orig,Vpos), vc=N},
-	    {V,array:set(V,VP,Vtab),VMap};
-	_ ->
-	    {V,Vtab,VMap}
-    end.
-
-add_hard(_Edge, _Htab, H) when H > 3 -> 3;
-add_hard(Edge, Htab, H) ->
-    case gb_sets:is_member(Edge,Htab) of
-	true ->  H+1;
-	false -> H
-    end.
-
-setup_edge(Eid, #edge{vs=OV1,ve=OV2,lf=F1,rf=F2}, 
-	   VMap0, FMap, Etab, Htab) ->
-    case array:get(Eid, Etab) of
-	undefined ->
-	    {V1,VMap1} = update_vmap(OV1, VMap0),
-	    {V2,VMap}  = update_vmap(OV2, VMap1),
-	    {array:set(Eid, {V1,V2,
-			     get_face(F1, FMap),
-			     get_face(F2, FMap),
-			     gb_sets:is_member(Eid,Htab)
-			    }, 
-		       Etab), VMap};
-	_ ->
-	    {Etab, VMap0}
-    end.
-
-get_face(F, FMap) -> %% when F >= 0 ->
-    case gb_trees:lookup(F, FMap) of
-	none -> -1;
-	{value,Mapped} -> Mapped
-    end.
-
-update_vmap(Orig, VM={N,VMap}) ->
-    case array:get(Orig, VMap) of
-	undefined -> 
-	    {N, {N+1,array:set(Orig, N, VMap)}};
-	V ->
-	    {V, VM}
-    end.
-
-pack_data(B=#base{e=Etab0, f=Ftab0}, erlang) ->
-    Etab = array:from_list(array:sparse_to_list(Etab0)),
-    Ftab = array:from_list(Ftab0),
-    B#base{e=Etab, f=Ftab};
-pack_data(B0=#base{v=Vtab0, e=Etab0, f=Ftab0}, opencl) ->
-    GetFs = fun(Vs, {No, FI, Fs}) ->
-		    Len = length(Vs),
-		    {No+Len, <<FI/binary, No:?I32, Len:?I32>>,
-		     << Fs/binary, 
-			(<< <<V:?I32>> || V <- Vs >>)/binary >>}
-	    end,
-    {_, FI, Ftab} = foldl(GetFs, {0, <<>>, <<>>}, Ftab0),
-
-    GetEs = fun(_, {V0,V1,F1,F2,H}, Bin) ->
-		    %% Code neg vertex as hardedge
-		    V0H = if H -> -1-V0; true -> V0 end,
-		    <<Bin/binary, V0H:?I32, V1:?I32, F1:?I32, F2:?I32>>
-	    end,
-    Etab = array:sparse_foldl(GetEs, <<>>,  Etab0),
-
-    GetVs = fun(_, #v{pos={X1,Y1,Z1}, vc={Vc,Hc}}, Bin) ->
-		    VI = (Vc bsl 2) bor min(Hc,3),
-		    << Bin/binary,
-		       X1:?F32,Y1:?F32,Z1:?F32,VI:?F32 >>
-	    end,
-    Vtab = array:foldl(GetVs, <<>>, Vtab0),
-    B = pack_attrs(B0), 
-    B#base{v=Vtab, e=Etab, f=Ftab, fi=FI}.
-
-pack_attrs(B=#base{type=plain}) -> B;
-pack_attrs(B=#base{type=uv, as=AS0}) -> 
-    Pack = fun(FaceUVs, Acc) ->
-		   << Acc/binary, 
-		      (<< <<(uv_bin(UV))/binary>> 
-			  || UV <- FaceUVs >>)/binary >>
-	   end,
-    AS = foldl(Pack, <<>>, AS0),
-    B#base{as=AS};
-pack_attrs(B=#base{type=color, as=AS0}) -> 
-    Pack = fun(FaceUVs, Acc) ->
-		   << Acc/binary, 
-		      (<< <<(col_bin(UV))/binary>> 
-			  || UV <- FaceUVs >>)/binary >>
-	   end,
-    AS = foldl(Pack, <<>>, AS0),
-    B#base{as=AS};
-pack_attrs(B=#base{type=color_uv, as=AS0}) -> 
-    Pack = fun(FaceUVs, Acc) ->
-		   << Acc/binary, 
-		      (<< <<(col_uv_bin(ColUV))/binary>> 
-			  || ColUV <- FaceUVs >>)/binary >>
-	   end,
-    AS = foldl(Pack, <<>>, AS0),
-    B#base{as=AS}.
-
-    
-uv_bin({U,V}) -> <<U:?F32,V:?F32>>;
-uv_bin(_) -> <<0.0:?F32,0.0:?F32>>.
-     
-col_bin({R,G,B}) -> <<R:?F32,G:?F32,B:?F32>>;
-col_bin(_) -> <<1.0:?F32,1.0:?F32,1.0:?F32>>.
-
-col_uv_bin([{R,G,B}|{U,V}]) ->
-    <<R:?F32,G:?F32,B:?F32, U:?F32,V:?F32>>;
-col_uv_bin([none|{U,V}]) ->
-    <<1.0:?F32,1.0:?F32,1.0:?F32, U:?F32,V:?F32>>;
-col_uv_bin([{R,G,B}|none]) ->
-    <<R:?F32,G:?F32,B:?F32, 0.0:?F32,0.0:?F32>>;
-col_uv_bin([none|none]) ->
-    <<1.0:?F32,1.0:?F32,1.0:?F32, 0.0:?F32,0.0:?F32>>.
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%%%%%%% Opencl Implementation
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-
-subdiv_1(N,
-	 In = #cl_mem{v=VsIn, f=FsIn, fi=FiIn, e=EsIn, as=AsIn,
-		      v_no=NoVs, fs_no=NoFs, e_no=NoEs},
-	 Out= #cl_mem{v=VsOut, f=FsOut, e=EsOut, fi=FiOut, as=AsOut,
-		      v_no=NoVsOut,fs_no=NoFs1, e_no=NoEs1},
-	 Type, CLS=#cls{cl=CL}, Wait0)
-  when N > 0 ->
-    Args1 = [VsIn, FsIn, FiIn, VsOut, FsOut, NoFs, NoVs],
-    W0 = wings_cl:cast(gen_faces, Args1, NoFs, Wait0, CL),
-    [cl:release_event(Ev) || Ev <- Wait0],
-    Args2 = [FsIn, FiIn, VsOut, NoFs, NoVs, NoVsOut],
-    W1 = wings_cl:cast(add_center, Args2, ?PL_UNITS, [W0], CL),
-
-    Args3 = [VsIn, FsIn, EsIn, FiIn,VsOut, FsOut, EsOut, NoFs, NoVs, NoEs],
-    W2 = wings_cl:cast(gen_edges, Args3, NoEs, [W1], CL),
-    Args4 = [VsIn, VsOut, EsIn, NoEs, NoVsOut],
-    W3 = wings_cl:cast(add_edge_verts, Args4, ?PL_UNITS, [W2], CL),
-
-    Args5 = [VsIn,VsOut,NoVs,NoVsOut],
-    W4 = wings_cl:cast(move_verts, Args5, NoVsOut, [W3], CL),
-    Wait = case Type of 
-	       plain -> W4;
-	       color -> 
-		   Args6 = [AsIn, FiIn, AsOut, NoFs],
-		   wings_cl:cast(subd_vcolor, Args6, NoFs, [W4], CL);
-	       uv -> 
-		   Args6 = [AsIn, FiIn, AsOut, NoFs],
-		   wings_cl:cast(subd_uv, Args6, NoFs, [W4], CL);
-	       color_uv -> 
-		   Args6 = [AsIn, FiIn, AsOut, NoFs],
-		   wings_cl:cast(subd_col_uv, Args6, NoFs, [W4], CL);
-	       _ -> %%  unknown ignore
-		   W4
-	   end,
-    [cl:release_event(Ev) || Ev <- [W0,W1,W2,W3]],
-    subdiv_1(N-1, Out, 
-	     In#cl_mem{fi=FiOut, v_no=NoVsOut+NoFs1+NoEs1,
-		       fs_no=NoFs1*4, e_no=NoEs1*4},
-	     Type, CLS, [Wait]);
-subdiv_1(_C, ResultBuffs, OutBuffs, _, _, Wait) ->
-    #cc_cache{mem=ResultBuffs, old=OutBuffs, wait=Wait}.
-
-gen_vab_2(#cc_cache{mem=Mem,old=Old,wait=Wait}, B=#base{n=NoFs,level=N,type=Type}) ->
-    #cls{cl=CL, vab=Vab} = cl_setup(),
-    %% Create #vab{}
-    #cl_mem{v=Vs, f=Fs, e=Es, e_no=NoEs, as=As} = Mem,
-    WVab = wings_cl:cast(create_vab_all,[Vs,Fs,Vab,NoFs], NoFs, Wait,CL),
-    Attrs = gen_attrs(attrs(Type), As, NoFs, Wait, CL),
-    Edges = gen_edges([Es, Vs, As, N, NoEs], Wait, CL),
-    WData = wings_cl:read(Vab,NoFs*4*6*4,[WVab],CL),
-    {ok, VabBin} = cl:wait(WData),
-    Smooth = gen_smooth_normals(Vab, NoFs, Mem, Old, [WVab], CL),
-
-    [cl:release_event(Ev) || Ev <- [WVab,WData|Wait]],
-    cl_release(Mem, true),
-    cl_release(Old, false),
-    {VabBin, Smooth, Attrs, Edges, B#base.mmap}.
-
-gen_vab_2({_Type, MatFs}, 
-	  #cc_cache{mem=Mem, wait=Wait0, old=Old}, 
-	  #base{fmap=FMap, type=Type}) ->
-    #cls{cl=CL, vab=Vab, fl=FL} = cl_setup(),
-    %% Create #vab{}
-    #cl_mem{v=Vs, f=Fs, as=AsIn} = Mem,
-    CountF = fun(WFace, [Start|Bin0]) ->
-		     {Fstart,FSz} = gb_trees:get(WFace,FMap),
-		     Bin = <<
-			     Bin0/binary,
-			     Fstart:?I32,       %% Start in Fs
-			     FSz:?I32,          %% No of faces
-			     Start:?I32         %% Start in vab
-			   >>,
-		     [Start+FSz|Bin]
-	     end,
-    {NoOutFs,FsBin,MatI} = mat_index(MatFs, CountF, [0|<<>>], []),
-    NoInFs = byte_size(FsBin) div 12,
-    case NoInFs > 0 of 
-	true ->
-	    W1 = wings_cl:write(FL, FsBin, CL),
-	    Wait = [W1|Wait0],
-	    Args0 = [Vs,Fs,FL,Vab,NoInFs],
-	    WVab = wings_cl:cast(create_vab_sel,Args0,NoInFs,Wait,CL),
-	    #cl_mem{as=AsOut} = Old,
-	    VabSz = NoOutFs*4*6*4,
-	    WData = wings_cl:read(Vab,VabSz,[WVab],CL),	    
-	    {ok, VabBin} = cl:wait(WData),
-	    Args1 = [FL,AsIn,AsOut,NoInFs],
-	    Attrs = gen_sel_attr(Type, Args1, NoOutFs,Wait,CL),
-	    [cl:release_event(Ev) || Ev <- [WVab,W1|Wait]],
-	    cl_release(Mem, true),
-	    cl_release(Old, false),
-	    {VabBin, <<>>, Attrs, none, MatI};
-	false ->
-	    {<<>>, <<>>, <<>>, none, []}
-    end.
-
-mat_index([{Mat,Fs}|MFs], Fun, Acc0 = [Start|_], MI) ->
-    Acc = [Next|_] = foldl(Fun, Acc0, Fs),
-    NoVs = (Next-Start)*4,
-    MatInfo = {Mat,?GL_QUADS,Start*4,NoVs},
-    mat_index(MFs, Fun, Acc, [MatInfo|MI]);
-mat_index([], _, [Total|Bin], MatInfo) ->
-    {Total, Bin, MatInfo}.
-
-gen_attrs({plain,_}, _As, _Sz, _Wait, _CL) -> <<>>;
-gen_attrs({_,Sz}, As, NoFs, Wait, CL) -> 
-    AData = wings_cl:read(As,NoFs*4*Sz,Wait,CL),
-    {ok, A0} = cl:wait(AData),
-    A0.
-
-gen_edges(Args, Wait, CL) ->
-    Type = wings_pref:get_value(proxy_shaded_edge_style),
-    gen_edges(Type, Args, Wait, CL).
-gen_edges(all, _Args, _Wait, _CL) -> none;
-gen_edges(cage, _Args, _Wait, _CL) -> none;
-gen_edges(some, [Es,Vs,As,N,TotNoEs], Wait, CL) -> 
-    Ediv = trunc(math:pow(4,N)),
-    EMul = trunc(math:pow(2,N)),
-    NoEs = EMul * (TotNoEs div Ediv),
-    Args = [Es,Vs,As,N,NoEs],
-    EWait0 = wings_cl:cast(gen_some_edges, Args, NoEs, Wait, CL),
-    EWait1 = wings_cl:read(As, NoEs*2*3*4, [EWait0], CL),
-    {ok, EsBin} = cl:wait(EWait1),
-    {0, EsBin}.
-
-gen_smooth_normals(Vab, NoFs, 
-		   #cl_mem{f=Fs,e=Es,e_no=NoEs,v=VsNs,v_no=NoVs,as=Out1}, 
-		   #cl_mem{v=Vs,as=Out2}, Wait, CL) ->
-    VsOut = NoFs*4,
-    C1 = wings_cl:cast(clearf, [VsNs,4,NoVs], NoVs, Wait, CL),
-    C2 = wings_cl:cast(clearf, [Out1,4,VsOut], VsOut, Wait, CL),
-    C3 = wings_cl:cast(clearf, [Out2,4,VsOut], VsOut, Wait, CL),
-    Args0 = [Fs,Vab,VsNs,NoFs,NoVs],
-    Pass0 = wings_cl:cast(smooth_ns_pass0, Args0, ?PL_UNITS, [C1], CL),
-    Args1 = [Es,Fs,Vab,Out1,Out2,NoEs],
-    Pass1 = wings_cl:cast(smooth_ns_pass1, Args1, NoEs, [C3,C2,Pass0], CL),
-    Args2 = [Fs,Vs,VsNs,Vab,Out1,Out2,NoFs,NoVs],
-    Pass2 = wings_cl:cast(smooth_ns, Args2, NoFs, [Pass1], CL),
-
-    WData = wings_cl:read(Out1,VsOut*4*4,[Pass2],CL),
-    {ok, OutBin} = cl:wait(WData),
-    OutBin.
-
-gen_sel_attr(plain, _, _, _, _) ->
-    <<>>;
-gen_sel_attr(Type,[FL,AsIn,AsOut,NoInFs],NoOutFs,Wait,CL) ->
-    {T,Sz} = attrs(Type), 
-    Func = case T of 
-	       color    -> get_sel_vcolor;
-	       uv       -> get_sel_uv;
-	       [color|uv] -> get_sel_col_uv
-	   end,
-    Args = [FL,AsIn,AsOut,NoInFs],
-    AW = wings_cl:cast(Func,Args,NoInFs,Wait,CL),
-    AData = wings_cl:read(AsOut,NoOutFs*4*Sz,[AW],CL),
-    {ok, A0} = cl:wait(AData),
-    A0.
-
-attrs(uv) -> % wings_va type and byte size
-    {uv, 2*4};
-attrs(color) ->
-    {color, 3*4};
-attrs(color_uv) ->
-    {[color|uv], 3*4+2*4};
-attrs(plain) ->
-    {plain, 0}.
-
-cl_setup() ->
-    case get({?MODULE, cl}) of 
-	undefined -> 
-	    try 
-		cl_setup_1()
-	    catch _:Reason ->
-		    io:format("CL setup error: ~p~n",[Reason]),
-		    wings_pref:set_value(proxy_opencl_level, 0),
-		    wings_u:error_msg(?__(1, "Could not setup OpenCL, disabling proxy smooth."))
-	    end;
-	CL ->
-	    CL
-    end.
-
-cl_setup_1() ->
-    CL0 = wings_cl:compile("cc_subdiv.cl", wings_cl:setup()),
-    CL = #cls{cl=CL0},
-    put({?MODULE, cl}, CL),
-    CL.
-
-
-%% For now only one level at the time
-cl_allocate(Base=#base{fi=Fi, type=Type}, CL0=#cls{cl=CLI}) ->
-    Ctxt = wings_cl:get_context(CLI),
-    {NoFs,NoEs,NoVs, NoFs1, MaxFs,MaxEs,MaxVs} = verify_size(Base, CL0),
-
-    {_, ASz0} = attrs(Type),
-    ASz = max(ASz0, 4*4),  %% Also used for smooth normals 
-
-    Sizes = [Fi, MaxFs*?FACE_SZ, MaxEs*?EDGE_SZ, MaxVs*?VERTEX_SZ*?PL_UNITS,
-	     MaxFs*?FACE_SZ, MaxEs*?EDGE_SZ, MaxVs*?VERTEX_SZ*?PL_UNITS,
-	     MaxFs*ASz*4, MaxFs*ASz*4],
-	     
-    Buffs = create_buffers(Ctxt, Sizes, []),
-    [FiIn,FsIn,EsIn,VsIn,  FsOut,EsOut,VsOut,  AsIn,AsOut] = Buffs,
-    
-    CL = #cls{fi=FiOut} = check_temp_buffs(CL0, Ctxt, MaxFs, Buffs),
-    put({?MODULE, cl}, CL),
-
-    
-    {#cl_mem{v=VsIn, f=FsIn, e=EsIn, fi=FiIn, fi0=FiIn, as=AsIn,
-	     v_no=NoVs, fs_no=NoFs, e_no=NoEs, max_vs=MaxVs},
-     #cl_mem{v=VsOut, f=FsOut, e=EsOut, fi=FiOut, fi0=FiIn, as=AsOut,
-	     v_no=NoVs+NoFs+NoEs, fs_no=NoFs1, e_no=NoEs*4, max_vs=MaxVs},
-     CL}.
-
-create_buffers(Ctxt, [Size|Szs], Acc) when is_integer(Size) ->
-    case cl:create_buffer(Ctxt, [], Size) of	
-	{ok,Buffer} ->
-	    create_buffers(Ctxt, Szs, [Buffer|Acc]);
-	{error, out_of_resources} ->
-	    release_buffers(Acc, true)
-    end;
-create_buffers(Ctxt, [Binary|Szs], Acc) ->
-    case cl:create_buffer(Ctxt, [], byte_size(Binary), Binary) of	
-	{ok,Buffer} ->
-	    create_buffers(Ctxt, Szs, [Buffer|Acc]);
-	{error, out_of_resources} ->
-	    release_buffers(Acc, true)
-    end;
-create_buffers(_, [], Buffers) ->
-    lists:reverse(Buffers).
-
-release_buffers(Buffers, true) ->
-    case get({?MODULE, cl}) of
-	undefined ->
-	    ok;
-	#cls{cl=CL, vab=Vab, fl=FL, fi=FI} ->
-	    Vab /= undefined andalso cl:release_mem_object(Vab),
-	    FL /= undefined andalso cl:release_mem_object(FL),
-	    FI /= undefined andalso cl:release_mem_object(FI),
-	    put({?MODULE, cl}, #cls{cl=CL})
-    end,
-    release_buffers(Buffers, false);
-release_buffers(Buffers, false) ->
-    [cl:release_mem_object(Buff) || Buff <- Buffers],
-    exit({out_of_resources, unknown, unknown}).
-
-
-cl_write_input(#base{f=Fs,e=Es,v=Vs, as=As}, 
-	       #cl_mem{v=VsIn,f=FsIn,e=EsIn,as=AsIn,max_vs=MaxVs}, 
-	       #cl_mem{v=VsOut},
-	       #cls{cl=CL}) ->
-    NoVs = MaxVs * ?PL_UNITS,
-    Wait0 = wings_cl:cast(clearf, [VsIn, 4, NoVs], NoVs, [], CL),
-    Wait1 = wings_cl:cast(clearf, [VsOut, 4, NoVs], NoVs, [], CL), 
-    W3 = wings_cl:write(FsIn,  Fs, CL), 
-    W4 = wings_cl:write(EsIn,  Es, CL), 
-    {ok, _} = cl:wait(Wait0), {ok, _} = cl:wait(Wait1),
-    W1 = wings_cl:write(VsIn,  Vs, CL),
-    W2 = wings_cl:write(VsOut, Vs, CL),
-    Last = case As of
-	       undefined -> [];
-	       _ ->
-		   W5 = wings_cl:write(AsIn, As, CL), 
-		   [W5]
-	   end,
-    [W1,W2,W3,W4|Last].
-    
-cl_release(#cl_mem{v=Vs,f=Fs,e=Es,fi0=Fi0,as=As}, All) ->
-    Vs /= undefined andalso cl:release_mem_object(Vs),
-    Fs /= undefined andalso cl:release_mem_object(Fs),
-    Es /= undefined andalso cl:release_mem_object(Es),
-    As /= undefined andalso cl:release_mem_object(As),
-    All andalso cl:release_mem_object(Fi0).
-
-check_temp_buffs(CL=#cls{
-			 vab=Vab0, vab_sz=VabSz0, 
-			 fl=FL0, fl_sz=FLSz0, 
-			 fi=Fi0, fi_sz=FiSz0
-			 %%sn = SN0, sn_vz = SNSz0
-			}, Ctxt, MaxFs0, Buffs) ->
-    MaxFs = MaxFs0,
-    GenFi = fun() -> 
-		    << <<(C*4):?I32, 4:?I32>> || 
-			C <- lists:seq(0, MaxFs-1) >> 
-	    end,
-    {Vab,VabSz} = try 
-		      check_temp(Vab0,VabSz0,MaxFs*(3+3)*4*4,
-				 Ctxt,[write_only],none)
-		  catch error:{badmatch, _} ->
-			  cl:release_mem_object(FL0),
-			  cl:release_mem_object(Fi0),
-			  release_buffers(Buffs, false)
-		  end,
-    {FL,FLSz} = try check_temp(FL0,FLSz0,MaxFs*3*4,
-			       Ctxt,[read_only],none)
-		catch error:{badmatch, _} ->
-			cl:release_mem_object(Vab),
-			cl:release_mem_object(Fi0),
-			release_buffers(Buffs, false)
-		end,
-
-    {Fi,FiSz} = try check_temp(Fi0,FiSz0,MaxFs*2*4,
-			       Ctxt,[read_only],GenFi)
-		catch error:{badmatch, _} ->
-			cl:release_mem_object(Vab),
-			cl:release_mem_object(FL),
-			release_buffers(Buffs, false)
-		end,
-
-    CL#cls{vab=Vab, vab_sz=VabSz, 
-	   fl=FL,   fl_sz=FLSz, 
-	   fi=Fi,   fi_sz=FiSz
-	  }.
-
-check_temp(Buff, Current, Req, _, _, _) 
-  when Current >= Req ->
-    {Buff, Current};
-check_temp(undefined, _, Req, Ctxt, Opt, none) ->
-    {ok, Buff} = cl:create_buffer(Ctxt, Opt, Req),
-    {Buff, Req};
-check_temp(undefined, _, Req, Ctxt, Opt, Fun) ->
-    {ok,Buff} = cl:create_buffer(Ctxt, Opt, Req, Fun()),
-    {Buff, Req};
-check_temp(Buff0, _, Req, Ctxt, Opt, Data) ->
-    cl:release_mem_object(Buff0),
-    check_temp(undefined, 0, Req, Ctxt, Opt, Data).
-
-verify_size(#base{fi=Fi, e=Es, v=Vs, level=N}, #cls{cl=CL}) ->
-    NoFs = size(Fi) div 8,
-    NoEs = size(Es) div ?EDGE_SZ,
-    NoVs = size(Vs) div ?VERTEX_SZ,
-    
-    Skip = size(Fi) - 8,
-    <<_:Skip/binary, NoFs0:?I32, LastFc:?I32>> = Fi,
-    NoFs1 = NoFs0+LastFc,
-    Device = wings_cl:get_device(CL),
-    {ok, DevTotal} = cl:get_device_info(Device, max_mem_alloc_size),
-    {MaxFs, MaxEs, MaxVs} = verify_size_1(N-1, N, NoFs1, NoEs*4, NoVs+NoEs+NoFs, DevTotal),
-    {NoFs, NoEs, NoVs, NoFs1, MaxFs, MaxEs, MaxVs}.
-
-%% Does this function do anything good?
-verify_size_1(N, No, Fs, Es, Vs, CardMax) ->
-    VertexSz = (3+3)*4*4,
-    Temp  = Fs*VertexSz+Fs*3*4+Fs*2*4,
-    Total = Temp+2*(Fs*?FACE_SZ+Es*?EDGE_SZ+Vs*?VERTEX_SZ*?PL_UNITS+Fs*4*4),
-    case Total < CardMax of
-	true when N == 0 ->
-	    {Fs,Es,Vs};
-	true -> 
-	    verify_size_1(N-1, No, Fs*4, Es*4, Vs+Fs+Es, CardMax);
-	false ->
-	    exit({out_of_resources,Total div 1024, CardMax div 1024})
-    end.
-
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% DEBUG
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-
--ifdef(DO_DEBUG).
-%-ifdef(PL_UNITS).
-cl_vs(Str, N, Vs, Count, CL, Wait0) ->
-    Wait = if is_list(Wait0) -> Wait0; true -> [Wait0] end,
-    W1 = wings_cl:read(Vs,Count*?VERTEX_SZ,Wait,CL),
-    {ok, VsBin} = cl:wait(W1),
-
-    {ok, F} = file:open(Str ++ "_" ++ integer_to_list(N), [write]),
-    try 
-	W = fun(<<X:?F32,Y:?F32,Z:?F32,VI0:?F32>>,V) -> 
-		    VI = {trunc(VI0) div 4, trunc(VI0) rem 4},
-		    ok=io:format(F,"{~w, {~.4f,~.4f,~.4f}, ~w}~n", [V,X,Y,Z,VI]),
-		    V+1
-	    end,
-	lists:foldl(W, 0, [D || <<D:?VERTEX_SZ/binary>> <= VsBin])
-    catch E:R ->
-	    io:format("Failed ~p:~p ~p~n",[E,R,erlang:get_stacktrace()])
-    after 
-	file:close(F)
-    end.
-
-cl_es(Str, N, Es, Count, CL, Wait0) ->
-    Wait = if is_list(Wait0) -> Wait0; true -> [Wait0] end,
-    W1 = wings_cl:read(Es,Count*?EDGE_SZ,Wait,CL),
-    {ok, EsBin} = cl:wait(W1),
-
-    {ok, F} = file:open(Str ++ "_" ++ integer_to_list(N), [write]),
-    try 
-	W = fun(<<X:?I32,Y:?I32,Z:?I32,W:?I32>>,E) -> 
-		    ok=io:format(F,"{~w, {~.4w,~.4w,~.4w,~.4w}~n", [E,X,Y,Z,W]),
-		    E+1
-	    end,
-	lists:foldl(W, 0, [D || <<D:?EDGE_SZ/binary>> <= EsBin])
-    catch E:R ->
-	    io:format("Failed ~p:~p ~p~n",[E,R,erlang:get_stacktrace()])
-    after 
-	file:close(F)
-    end.
-
-cl_face(Str, N, Vs, Count, CL, Wait0) ->
-    Wait = if is_list(Wait0) -> Wait0; true -> [Wait0] end,
-    W1 = wings_cl:read(Vs,Count*?FACE_SZ,Wait,CL),
-    {ok, FsBin} = cl:wait(W1),
-
-    {ok, FD} = file:open(Str ++ "_" ++ integer_to_list(N), [write]),
-    try 
-	W = fun(<<X:?I32,Y:?I32,Z:?I32,VI0:?I32>>,V) -> 
-		    ok=io:format(FD,"{~w, {~w,~w,~w,~w}}.~n", 
-				 [V,X,Y,Z,VI0]),
-		    V+1
-	    end,
-	lists:foldl(W, 0, [D || <<D:?FACE_SZ/binary>> <= FsBin])
-    catch E:R ->
-	    io:format("Failed ~p:~p ~p~n",[E,R,erlang:get_stacktrace()])
-    after 
-	file:close(FD)	
-    end.
-
-
-cl_destroy(Mem) ->
-    %% During DEBUGGING REMOVE LATER BUGBUG
-    cl_release(Mem, true),
-    #cls{fl=Fl, fi=Fi,vab=Vab} = get({?MODULE, cl}),
-
-    cl:release_mem_object(Vab),
-    cl:release_mem_object(Fi),
-    cl:release_mem_object(Fl),
-
-    erase({?MODULE, cl}),
-    %% cl:release_queue(Q),
-    %% [cl:release_kernel(K) || #kernel{id=K} <- Ks],
-    %% cl:release_context(C),
-    ok.
-
-print_base(#base{v=Vs,f=Fs,fi=Fi,e=Es,n=N}) ->
-    io:format("Vs = ~w~n",[Vs]),
-    io:format("Fs = ~w~n",[Fs]),
-    io:format("Es = ~w~n",[Es]),
-    ok.
-
--endif.
-
diff --git a/src/wings_cc_ref.erl b/src/wings_cc_ref.erl
index 0b24b3a..20c7c01 100644
--- a/src/wings_cc_ref.erl
+++ b/src/wings_cc_ref.erl
@@ -13,452 +13,3 @@
 %%
 
 -module(wings_cc_ref).
-
--import(lists, [reverse/1, foldl/3]).
-
--define(NEED_OPENGL, 1).
--include("wings.hrl").
--include_lib("cl/include/cl.hrl").
-
--compile(export_all).
-
--record(v, {pos,                     % position
-	    vc}).                    % Valence
-
-%% The different working sets
-
--record(base, {v,    %% array of #v{}           nv
-	       f,    %% array of [v0,v1..,vn]   nf
-	       fi,   %% array of {Start,Size}   nf
-	       e,    %% array of v0,v1,f1,f2    ne
-	       as,   %% Vertex attrs
-	       level,%% Subdiv levels
-	       n,    %% Number of faces 
-	       mmap, %% Material map, {mat, start, vertex_count}
-	       vmap, %% array Wings Vertex Id -> CL vertex id
-	       fmap, %% gb_tree Wings face id -> CL face id
-	       type  %% Type of data plain,uv,color,color_uv
-	      }).
-
--define(EDGE_SZ, (4*4)).
--define(FACE_SZ, (4*4)).
--define(VERTEX_SZ, ((3*4)+4)).
--define(LOCK_SZ, 32).
-
-subdiv(#base{v=Vs,e=Es,f=Fs, as=As, level=N}) ->
-    subdiv_erl_1(Fs, Es, Vs, As, N).
-
-subdiv_erl_1(InFs, Es0, InVs, As, N) when N > 0 ->
-    SFs0 = array:sparse_foldl(fun(_F, Vs, R=[Prev|_]) ->
-				      [Prev+length(Vs)|R]
-			      end, [0], InFs),
-    SFs = array:from_list(reverse(SFs0)),
-    {OutVs1, OutFs1} = gen_face_points(InFs, InVs, InVs, SFs),
-    {OutVs2, OutFs, Es} = gen_edge_points(Es0, InVs, OutVs1, 
-					  SFs, InFs, OutFs1, undefined),
-    OutVs = move_vertex_points(InVs,OutVs2),
-    OutAs = subdiv_attrs(As),
-    %% erl_vs("evs_out3", N, OutVs),
-    subdiv_erl_1(OutFs, Es, OutVs, OutAs, N-1);
-subdiv_erl_1(Fs0, _Es0, Vtab, As, _N) ->
-    %% assert(Vtab, _Es0, Fs0),    
-    {Vtab, As, Fs0}.
-
-update(Changed, B=#base{v=Vs0,vmap=Map}) ->
-    Vs = case Changed of
-	     [_|_] ->
-		 Move = fun({Vid, Pos}, Vs) ->
-				try 
-				CLid = array:get(Vid, Map),
-				V = array:get(CLid, Vs),
-				array:set(CLid, V#v{pos=Pos}, Vs)
-				catch _:badarg ->
-					io:format("VMap ~w~n", 
-						  [array:to_orddict(Map)]),
-					io:format("Vid ~p ~n", [Vid]),
-					io:format("CLid ~p ~n", [catch array:get(Vid, Map)]),
-					exit(foo)
-				end
-			end,
-		 %% io:format("Changed ~p~n",[Changed]),
-		 foldl(Move, Vs0, Changed);
-	     #we{vp=Vpos} ->
-		 Move = fun(Vid, CLid, Vs) ->
-				Pos = array:get(Vid, Vpos),
-				V = array:get(CLid, Vs),
-				array:set(CLid, V#v{pos=Pos}, Vs)
-			end,
-		 array:sparse_foldl(Move, Vs0, Map)
-	 end,
-    B#base{v=Vs}.
-
-gen_vab({Vtab, As, Ftab}, #base{n=Total, type=Type, mmap=Mats}) -> 
-    Gen = fun(Id, Vs0, Bin) when Id < Total ->
-		  Vs = [(array:get(V,Vtab))#v.pos || V <- Vs0],
-		  {Nx,Ny,Nz} = e3d_vec:normal(Vs),
-		  Face = << <<X:?F32,Y:?F32,Z:?F32, 
-			      Nx:?F32,Ny:?F32,Nz:?F32 >> 
-			    || {X,Y,Z} <- Vs >>,
-		  <<Bin/binary, Face/binary >>;
-	     (_,_, Bin) ->
-		  throw(Bin)
-	  end,
-    Bin = try 
-	      array:foldl(Gen, <<>>, Ftab)
-	  catch throw:Bin1 ->
-		  Bin1
-	  end,    
-    AsBin = case As of
-		undefined -> <<>>;
-		_ ->
-		    try 		
-			lists:foldl(gen_attrib_fun(Type), <<>>, As)
-		    catch throw:Bin2 ->
-			    Bin2
-		    end
-	    end,
-    {Bin, <<>>, AsBin, Mats}.
-
-%% print( <<R:?F32, G:?F32, B:?F32, U:?F32, V:?F32, Rest/binary>>, Face) ->
-%%     io:format("~w: {~.4f,~.4f,~.4f}, {~.4f,~.4f}~n", [Face,R,G,B,U,V]),
-%%     print(Rest, Face+1);
-%% print(<<>>, _) -> ok.
-
-gen_attrib_fun(color) ->
-    fun(Colors, Bin) ->
-	    Face = << <<(col_bin(Col))/binary>> || Col <- Colors >>,
-	    <<Bin/binary, Face/binary >>
-    end;
-gen_attrib_fun(uv) ->
-    fun(Uvs, Bin) ->
-	    Face = << <<(uv_bin(Uv))/binary>> || Uv <- Uvs >>,
-	    <<Bin/binary, Face/binary >>
-    end;
-gen_attrib_fun(color_uv) ->
-    Gen = fun([Col|Uv], Bin) ->
-		  <<Bin/binary, (col_bin(Col))/binary,(uv_bin(Uv))/binary>>;
-	     (none, Bin) ->
-		  <<Bin/binary, (col_bin(none))/binary,(uv_bin(none))/binary>>
-	  end,
-    fun(Uvs, Bin) ->
-	    foldl(Gen,Bin, Uvs)
-    end;
-gen_attrib_fun(_) -> fun(_, _) -> throw(<<>>) end.
-
-uv_bin({U,V}) -> <<U:?F32, V:?F32>>;
-uv_bin(_) -> <<0.0:?F32, 0.0:?F32>>.
-     
-col_bin({R,G,B}) -> <<R:?F32, G:?F32, B:?F32>>;
-col_bin(_) -> <<1.0:?F32, 1.0:?F32, 1.0:?F32>>.
-
-gen_vab({_Type, MatFs}, Data, #base{fmap=FMap}) ->
-    gen_vab(MatFs, Data, FMap, 0, <<>>, []).
-
-gen_vab([{Mat,Fs}|T], D={Vtab, _, Ftab},FMap, Start, Bin0, MI) ->
-    %%io:format("Mat: ~p Fs: ~p ~p~n",[Mat, length(Fs), Fs]),
-    Build = fun(WFace, {C,Acc}) ->
-		    {FStart,Fsz} = gb_trees:get(WFace,FMap),
-		    Bin = gen_faces(FStart, FStart+Fsz, Ftab, Vtab, Acc),
-		    {C+Fsz*4, Bin}
-	    end,
-    {Stop, Bin} = lists:foldl(Build, {Start, Bin0}, Fs),
-    MatInfo = {Mat,?GL_QUADS,Start,Stop-Start},
-    gen_vab(T, D, FMap, Stop, Bin, [MatInfo|MI]);
-gen_vab([], _, _,_, Bin, Mi) ->
-    {Bin, <<>>, <<>>, Mi}.
-
-gen_faces(N, End, Ftab, Vtab, Acc0) when N < End -> 
-    Vs0 = array:get(N, Ftab),
-    Vs = [(array:get(V,Vtab))#v.pos || V <- Vs0],
-    {Nx,Ny,Nz} = e3d_vec:normal(Vs),
-    Face = (<< <<X:?F32,Y:?F32,Z:?F32, Nx:?F32,Ny:?F32,Nz:?F32 >> 
-	       || {X,Y,Z} <- Vs >>),
-    Acc = <<Acc0/binary, Face/binary >>,
-    gen_faces(N+1, End,  Ftab, Vtab, Acc);
-gen_faces(_,_,_,_,Acc) -> Acc.
-	    
-%%%  Step 2 build vertices/edges and faces
-
-gen_face_points(Fs0, InVs, OutVs0, SFs) ->
-    Face = fun(Face, Vs, {OutVs, Fs}) ->
-		   gen_face_point(Face, Vs, InVs, SFs, OutVs, Fs)
-	   end,
-    array:foldl(Face, {OutVs0, Fs0}, Fs0).
-
-gen_face_point(Face, FVs, InVs, SFs, OutVs0, Fs0) ->
-    VsPos = [(array:get(V, InVs))#v.pos || V <- FVs],
-    Center = e3d_vec:average(VsPos),
-    OutVs1 = add_center(FVs, Center, OutVs0, face), %% atomicly 
-    Vid = array:size(InVs) + Face,
-    NewFid = face_id(Face, SFs),
-    %% Face == 5 andalso 
-    %% 	io:format("F ~p c ~p~n",[{V0,V1,V2,V3}, Vid]),
-    New = #v{pos=Center, vc={length(FVs),0}},
-    OutVs = array:set(Vid, New, OutVs1),
-    {_, Fs} = foldl(fun(V, {Fid, Fs}) ->		  
-			    {Fid+1, array:set(Fid, [V, -5, Vid, -5], Fs)}
-		    end, {NewFid, Fs0}, FVs),
-    {OutVs, Fs}.
-
-gen_edge_points(Es, InVs, OutVs, FsNo, InFs, OutFs, EdsNo) ->
-    Edge = fun(Edge, Vs, Acc) ->
-		   gen_edge_point(Edge, Vs, Acc, InVs, FsNo, InFs, EdsNo)
-	   end,
-    array:foldl(Edge, {OutVs,OutFs,Es}, Es).
-
-gen_edge_point(Edge, {-1,-1,-1,-1,_Hard}, {OutVs0,Fs0,Es0}, 
-	       InVs,_FsNo,InFs,EdsNo) ->
-    SEdId = edge_id(Edge,EdsNo),
-    VStart = array:size(InVs),
-    FId = array:size(InFs) + VStart,
-    VId = FId + Edge,
-    Es1 = array:set(SEdId+0, {-1,-1,-1,-1,false}, Es0),
-    Es2 = array:set(SEdId+1, {-1,-1,-1,-1,false}, Es1),
-    Es3 = array:set(SEdId+2, {-1,-1,-1,-1,false}, Es2),
-    Es4 = array:set(SEdId+3, {-1,-1,-1,-1,false}, Es3),
-    OutVs = array:set(VId, #v{pos={0.0,0.0,0.0}, vc={4, 0}}, OutVs0),
-    {OutVs,Fs0,Es4};
-
-gen_edge_point(Edge, {V0,V1,F1,F2,Hard}, {OutVs0,Fs0,Es0}, 
-	       InVs,FsNo,InFs,EdsNo) ->
-    #v{pos=V0Pos} = array:get(V0, InVs),
-    #v{pos=V1Pos} = array:get(V1, InVs),
-
-    OutVs1 = add_center([V0], V1Pos, OutVs0, Hard),
-    OutVs2 = add_center([V1], V0Pos, OutVs1, Hard),
-    VStart = array:size(InVs),
-    %% Edge Split position
-    {EP,HC} = case Hard of 
-		  true ->  %% if Edge is hard Epoint = Mid,
-		      {e3d_vec:average(V0Pos, V1Pos),2};
-		  false -> %% Otherwise center of all
-		      {e3d_vec:average([(array:get(VStart+F1, OutVs2))#v.pos,
-					(array:get(VStart+F2, OutVs2))#v.pos,
-					V0Pos, V1Pos]),0}
-	      end,
-    FId = array:size(InFs) + VStart,
-    VId = FId + Edge,
-    OutVs = array:set(VId, #v{pos=EP, vc={4, HC}}, OutVs2),
-    SEdId = edge_id(Edge,EdsNo),
-
-    %% Complete faces 
-    case F1 >= 0 of
-	true ->
-	    SF1 = array:get(F1, FsNo),
-	    {F11,F12,CCW1} = 
-		find_new_faces(V0,V1,array:get(F1, InFs),SF1),
-	    Fs1 = update_face(F11, CCW1, VId, Fs0),
-	    Fs2 = update_face(F12, not CCW1, VId, Fs1),
-	    Es1 = array:set(SEdId+0, {VId,VStart+F1,F11,F12,false}, Es0);
-	false ->
-	    F11 = -1, 
-	    F12 = -1,
-	    Es1 = array:set(SEdId+0, {-1,-1,-1,-1,false}, Es0),
-	    Fs2 = Fs0
-    end,
-    case F2 >= 0 of
-	true ->
-	    SF2 = array:get(F2, FsNo),
-	    {F21,F22,CCW2} = 
-		find_new_faces(V0,V1,array:get(F2, InFs),SF2),
-	    Fs3 = update_face(F21, CCW2, VId, Fs2),
-	    Fs4 = update_face(F22, not CCW2, VId, Fs3),
-	    Es2 = array:set(SEdId+1, {VId,VStart+F2,F21,F22,false}, Es1);
-	false ->
-	    F21 = -1, 
-	    F22 = -1,
-	    Es2 = array:set(SEdId+1, {-1,-1,-1,-1,false}, Es1),
-	    Fs4 = Fs2
-    end,
-    %% Edge == 0 andalso 
-    	%% io:format("Up ~p ~p~n ~p => ~p ~p~n ~p => ~p~p~n",
-    	%% 	  [Edge, {V0,V1}, 
-    	%% 	   F1, {F11,F12}, get_face(F1, InFs),
-    	%% 	   F2, {F21,F22}, get_face(F2, InFs)]),
-    %% New Edges
-    Es3 = array:set(SEdId+2, {V0,VId,F11,F21,Hard}, Es2),
-    Es4 = array:set(SEdId+3, {VId,V1,F12,F22,Hard}, Es3),
-    {OutVs,Fs4,Es4}.
-
-move_vertex_points(In, Out) ->
-    Move = fun(V, InV=#v{pos=InPos,vc=Cs={VC,HC}}, VP) ->
-		   if HC < 2 ->
-			   {A,B} = vc_div(VC),
-			   #v{pos=PosOut} = array:get(V,Out),
-			   %% We started with Inpos remove it
-			   Ps  = e3d_vec:sub(PosOut, InPos),
-			   Pos = e3d_vec:add_prod(e3d_vec:mul(Ps, A), InPos, B),
-			   array:set(V, #v{pos=Pos, vc=Cs}, VP);
-		      HC =:= 2 ->
-			   #v{pos=Hard} = array:get(V,Out),
-			   Pos0 = e3d_vec:add_prod(Hard, InPos, 6.0),
-			   Pos  = e3d_vec:mul(Pos0, 1/8),
-			   array:set(V, #v{pos=Pos, vc=Cs}, VP);
-		      true ->
-			   array:set(V, InV, VP)
-		   end
-	   end,
-    array:sparse_foldl(Move, Out, In).
-
-vc_div(3) -> {1/9,  1/3};
-vc_div(4) -> {1/16, 2/4};
-vc_div(5) -> {1/25, 3/5};
-vc_div(N) -> {1/(N*N), (N-2.0)/N}.
-
-subdiv_attrs(undefined) -> undefined;
-subdiv_attrs(As0) -> 
-    {_,As} = lists:foldl(fun(Attrs = [First|_], {F,Out}) ->
-			     Last = lists:last(Attrs),			     
-			     Center = average(Attrs),
-			     {F+1,subdiv_attrs(Last, Attrs, Center, First, Out)}
-		     end, {0,[]}, As0),
-    reverse(As).
-
-subdiv_attrs(Last, [Curr|Attrs=[Next|_]], Center, First, Out) ->
-    FaceAttr = [Curr, average(Curr,Next),
-		Center, average(Curr,Last)],
-    subdiv_attrs(Curr, Attrs, Center, First, [FaceAttr|Out]);
-subdiv_attrs(Last, [Curr], Center, Next, Out) ->
-    FaceAttr = [Curr, average(Curr,Next),
-		Center, average(Curr,Last)],
-    [FaceAttr|Out].
-
-average(Attrs = [[_|_]|_]) ->
-    wings_va:average_attrs(Attrs);
-average(Attrs) ->
-    wings_color:average(Attrs).
-average(Attr1 = [_|_], Attr2) ->
-    wings_va:average_attrs(Attr1, Attr2);
-average(A1, A2) ->
-    wings_color:average(A1,A2).
-
-%% The order is important to get ccw winding
-%% find_new_faces(V0,V1,[V0,V1,_,_],Sid) -> {Sid+0,Sid+1,true};
-%% find_new_faces(V0,V1,[V1,V0,_,_],Sid) -> {Sid+1,Sid+0,false};
-%% find_new_faces(V0,V1,[_,V0,V1,_],Sid) -> {Sid+1,Sid+2,true};
-%% find_new_faces(V0,V1,[_,V1,V0,_],Sid) -> {Sid+2,Sid+1,false};
-%% find_new_faces(V0,V1,[_,_,V0,V1],Sid) -> {Sid+2,Sid+3,true};
-%% find_new_faces(V0,V1,[_,_,V1,V0],Sid) -> {Sid+3,Sid+2,false};
-%% find_new_faces(V0,V1,[V1,_,_,V0],Sid) -> {Sid+3,Sid+0,true};
-%% find_new_faces(V0,V1,[V0,_,_,V1],Sid) -> {Sid+0,Sid+3,false}.
-
-find_new_faces(V0,V1,[V0,VN|R],Sid) -> 
-    case VN of
-	V1 -> {Sid,Sid+1,true};
-	_ ->  {Sid,Sid+1+length(R),false}
-    end;
-find_new_faces(V0,V1,[V1,VN|R],Sid) -> 
-    case VN of
-	V0 -> {Sid+1,Sid,false};
-	_  -> {Sid+1+length(R),Sid,true}
-    end;
-find_new_faces(V0,V1,[_|R],Sid) ->
-    find_new_faces(V0,V1,R,Sid+1);
-find_new_faces(_,_, -1, _) ->
-    ok.
-    
-
-update_face(Face,true,VId, Fs) ->
-    try 
-	[A,-5,C,D] = array:get(Face,Fs),
-	array:set(Face, [A,VId,C,D], Fs)
-    catch Class:Reason ->
-	    io:format("Fs: ~p~n",[array:sparse_to_orddict(Fs)]),
-	    io:format("~p ~p ~p ~p~n",
-		      [Face,1,VId,array:get(Face, Fs)]),
-	    erlang:raise(Class, Reason, erlang:get_stacktrace())
-    end;
-update_face(Face,false,VId, Fs) ->
-    try
-	[A,B,C,-5] = array:get(Face,Fs),
-	array:set(Face, [A,B,C,VId], Fs)
-    catch Class:Reason ->
-	    io:format("XXX ~p ~n",[Fs]),
-	    io:format("Fs: ~p~n",[array:sparse_to_orddict(Fs)]),
-	    io:format("~p ~p ~p ~p~n",
-		      [Face,3,VId,array:get(Face, Fs)]),
-	    erlang:raise(Class, Reason, erlang:get_stacktrace())
-    end.
-
-add_center([V|Vs], Center, OutVs, Hard=true) ->
-    Vx = #v{pos=Pos} = array:get(V,OutVs),
-    Updated = array:set(V, Vx#v{pos = e3d_vec:add(Pos,Center)}, OutVs),
-    add_center(Vs, Center, Updated, Hard);
-add_center([V|Vs], Center, OutVs, Hard) ->
-    Vx = #v{pos=Pos, vc={_,He}} = array:get(V,OutVs),
-    if 
-	He < 2 -> 
-	    Updated = array:set(V, Vx#v{pos = e3d_vec:add(Pos,Center)}, OutVs),
-	    add_center(Vs, Center, Updated, Hard);
-	He =:= 2, Hard =:= face ->  %% Reset
-	    Updated = array:set(V, Vx#v{pos = {0.0,0.0,0.0}}, OutVs),
-	    add_center(Vs, Center, Updated, Hard);
-	true ->
-	    add_center(Vs, Center, OutVs, Hard)
-    end;
-add_center([],_,OutVs,_) ->
-    OutVs.
-
-face_id(Face, Fs) ->
-    array:get(Face, Fs).
-
-edge_id(Edge, undefined) -> Edge*4;
-edge_id(Edge, Es) -> array:get(Edge, Es).
-
-%%%%%%%%
-%%assert(_OutVs, _Es, _OutFs) -> ok;
-assert(OutVs, Es, OutFs) ->
-    io:format("Asserting .. ",[]),
-    Assert = 
-	fun(_, {-1,-1,-1,-1,_H}, _Fs0) -> ok;
-	   (Edge, E={V1,V2,F1,F2,_H}, _Fs0) ->
-		try 
-		    #v{} = array:get(V1, OutVs),
-		    #v{} = array:get(V2, OutVs),
-		    find_new_faces(V1,V2,get_face2(F1, OutFs),0),
-		    find_new_faces(V1,V2,get_face2(F2, OutFs),0)
-		catch _:Reason ->
-			io:format("assert failed ~p ~p~n", 
-				  [Reason, erlang:get_stacktrace()]),
-			io:format("Edge ~p ~p ~n", [Edge, E]),
-			io:format("  F ~p: ~p ~n", [F1,get_face2(F1, OutFs)]),
-			io:format("  F ~p: ~p ~n", [F2,get_face2(F2, OutFs)]),
-			exit(Reason)
-		end
-	end,
-    array:foldl(Assert, array:new([{default, []}]), Es),
-    %% ok = array:foldl(fun(_Face, [_,_,_,_], Ok) -> Ok;
-    %% 			(Face, Eds, _) -> {Face,Eds}
-    %% 		     end, ok, F2Es),
-    io:format("Asserted~n",[]).
-
-get_face2(F, Fs) when F >= 0 ->
-    array:get(F,Fs);
-get_face2(_,_) -> -1.
-
-erl_vs(Str, N, Vs) ->
-    {ok, F} = file:open(Str ++ "_" ++ integer_to_list(N), [write]),
-    try 
-	W = fun(V, #v{pos={X,Y,Z}, vc=VI},_) -> 
-		    io:format(F,"{~w, {~.4f,~.4f,~.4f}, ~w}~n", [V,X,Y,Z,VI])
-	    end,
-	ok = array:foldl(W, ok, Vs)
-    catch E:R ->
-	    io:format("Failed ~p:~p ~p~n",[E,R,erlang:get_stacktrace()])
-    after 
-	file:close(F)	
-    end.
-
-erl_face(Str, N, Fs) ->
-    {ok, FD} = file:open(Str ++ "_" ++ integer_to_list(N), [write]),
-    try 
-	W = fun(F, [V1,V2,V3,V4], _) -> 
-		    io:format(FD,"{~w, {~w,~w,~w,~w}}.~n", [F,V1,V2,V3,V4])
-	    end,
-	ok = array:foldl(W, ok, Fs)
-    catch E:R ->
-	    io:format("Failed ~p:~p ~p~n",[E,R,erlang:get_stacktrace()])
-    after 
-	file:close(FD)	
-    end.
-
diff --git a/src/wings_cl.erl b/src/wings_cl.erl
index 04babb1..cee4583 100644
--- a/src/wings_cl.erl
+++ b/src/wings_cl.erl
@@ -12,111 +12,9 @@
 %%
 
 -module(wings_cl).
--include_lib("cl/include/cl.hrl").
-
--export([is_available/0,
-	 setup/0, compile/2, get_context/1, get_device/1,
-	 cast/5, write/3, read/4,
-	 tcast/5
-	]).
-
--record(cli, {context, kernels, q, cl, device}).
--record(kernel, {name, id, wg}).
 
+-export([is_available/0]).
 
 is_available() ->
-    try 
-	true == erlang:system_info(smp_support) orelse throw({error, no_smp_support}),
-	ok == cl:start() orelse throw({error, no_opencl_loaded}),
-	{ok, Ps} = cl:get_platform_ids(),
-	[] /= Ps
-    catch _:Reason ->
-	    io:format("OpenCL not available ~p ~n",[Reason]),
-	    false
-    end.
-
-
-%% setup() -> cli().
-setup() ->
-    Prefered = wings_pref:get_value(cl_type, gpu),
-    Other = [gpu,cpu] -- [Prefered],
-    CL = case clu:setup(Prefered) of 
-	     {error, _} -> 
-		 case clu:setup(Other) of
-		     {error, R} -> 
-			 exit({no_opencl_device, R});
-		     Cpu -> Cpu
-		 end;
-	     Gpu ->
-		 Gpu
-	 end,
-    [Device|_] = CL#cl.devices,
-    {ok,Queue} = cl:create_queue(CL#cl.context,Device,[]),
-    #cli{context=CL#cl.context, q=Queue, device=Device, cl=CL}.
-
-%% compile(File,cli()) -> cli().
-compile(File, CLI = #cli{cl=CL, device=Device}) ->
-    Dir = filename:join(code:lib_dir(wings),"shaders"),
-    {ok, Bin} = file:read_file(filename:join([Dir, File])),
-    case clu:build_source(CL, Bin) of
-	{error, {Err={error,build_program_failure}, _}} ->
-	    %% io:format("~s", [Str]),
-	    exit(Err);
-	{ok, Program} -> 
-	    {ok, MaxWGS} = cl:get_device_info(Device, max_work_group_size),
-	    {ok, Kernels0} = cl:create_kernels_in_program(Program),
-	    Kernels = [kernel_info(K,Device, MaxWGS) || K <- Kernels0],
-	    cl:release_program(Program),
-	    CLI#cli{kernels=Kernels}
-    end.
-
-kernel_info(K,Device, MaxWGS) ->
-    {ok, WG} = cl:get_kernel_workgroup_info(K, Device, work_group_size),
-    {ok, Name} = cl:get_kernel_info(K, function_name),
-    #kernel{name=list_to_atom(Name), wg=min(WG,MaxWGS), id=K}.
-
-get_context(#cli{context=Context}) ->
-    Context.
-get_device(#cli{device=Device}) ->
-    Device.
-
-
-%% cast(Kernel, Args, NoInvocations, [Wait], cli()) -> Wait
-tcast(Name, Args, No, Wait, CL) ->
-    cast(Name, Args, No, Wait, true, CL).
-
-cast(Name, Args, No, Wait, CL) ->
-    cast(Name, Args, No, Wait, false, CL).
-cast(Name, Args, No, Wait, Time, #cli{q=Q, kernels=Ks}) ->
-    #kernel{id=K, wg=WG0} = lists:keyfind(Name, 2, Ks),
-    try clu:apply_kernel_args(K, Args) of
-	ok -> ok
-    catch error:Reason ->
-	    io:format("Bad args ~p: ~p~n",[Name, Args]),
-	    erlang:raise(error,Reason, erlang:get_stacktrace())
-    end,
-    {GWG,WG} = if  No > WG0  -> 
-		       {(1+(No div WG0))*WG0, WG0};
-		   true -> {No,No}
-	       end,
-    %% io:format("X ~p GWG ~p WG ~p~n", [Name, GWG, WG]),
-    {ok, Event} = cl:enqueue_nd_range_kernel(Q,K,[GWG],[WG],Wait),
-    Time andalso time_wait(Name, Event),
-    Event.
-
-time_wait(Name, Event) ->
-    Before = os:timestamp(),
-    {ok,completed} = cl:wait(Event),
-    io:format("CL ~p Time: ~p\n", [Name, timer:now_diff(os:timestamp(),Before)]).
-
-
-%% write(CLMem, Bin, cli()) -> Wait
-write(CLMem, Bin, #cli{q=Q}) ->
-    {ok, W1} = cl:enqueue_write_buffer(Q, CLMem, 0, byte_size(Bin), Bin, []),
-    W1.
-
-%% read(CLMem, Sz, [Wait], cli()) -> Wait
-read(CLMem, Sz, Wait, #cli{q=Q}) -> 
-    {ok, W} = cl:enqueue_read_buffer(Q,CLMem,0,Sz, Wait),
-    W.
-
+    io:format("OpenCL is not available in Fedora (yet).~n"),
+    false.
diff --git a/src/wings_proxy.erl b/src/wings_proxy.erl
index da3d682..9bf4322 100644
--- a/src/wings_proxy.erl
+++ b/src/wings_proxy.erl
@@ -164,14 +164,6 @@ update_edges_1(_, #sp{vab=#vab{face_vs=BinVs,face_fn=Ns,mat_map=MatMap}}, all) -
     wings_draw_setup:disableVertexPointer(BinVs),
     wings_draw_setup:disableNormalPointer(Ns),
     Dl;
-update_edges_1(#dlo{}, #sp{type={wings_cc,_}, vab=#vab{face_es={0,Bin}}}, some) ->
-    Dl = gl:genLists(1),
-    gl:newList(Dl, ?GL_COMPILE),
-    gl:enableClientState(?GL_VERTEX_ARRAY),
-    wings_draw:drawVertices(?GL_LINES, Bin),
-    gl:disableClientState(?GL_VERTEX_ARRAY),
-    gl:endList(),
-    Dl;
 update_edges_1(#dlo{src_we=#we{vp=OldVtab}}, #sp{we=#we{vp=Vtab,es=Etab}=We}, some) ->
     Dl = gl:genLists(1),
     gl:newList(Dl, ?GL_COMPILE),
@@ -306,7 +298,7 @@ draw_edges_1(#dlo{proxy_data=#sp{proxy_edges=ProxyEdges}}, _) ->
 proxy_smooth(We0, Pd0, St) ->
     Level = wings_pref:get_value(proxy_opencl_level),
     if is_integer(Level),Level > 0 -> 
-	    Impl = wings_cc;
+	    Impl = ?MODULE;
        true ->
 	    Impl = ?MODULE
     end,
@@ -316,16 +308,7 @@ proxy_smooth(We0, Pd0, St) ->
 	{_, _} = Info when Impl =:= ?MODULE ->
 	    create_proxy_subdiv(Info, We0, St);
 	{Op, _} ->
-	    case Pd0 of
-		#sp{type={wings_cc,Data}} when Op =:= update ->
-		    update_proxy_cc(We0, Data);
-		_ ->
-		    try 
-			create_proxy_cc(We0, Level, St)
-		    catch to_large -> %% Fallback if we can't allocate memory
-			    create_proxy_subdiv({smooth,We0}, We0, St)
-		    end
-	    end
+	    create_proxy_subdiv({smooth,We0}, We0, St)
     end.
 
 proxy_needs_update(We, #sp{we=SWe,src_we=We,vab=#vab{face_vs=Bin}})
@@ -357,56 +340,6 @@ create_proxy_subdiv(Info, We0, St) ->
     Plan = wings_draw_setup:prepare(gb_trees:to_list(We#we.fs), We, St),
     flat_faces(Plan, #sp{src_we=We0,we=We}).
 
-update_proxy_cc(We0, Data0) ->
-    Data = wings_cc:update(We0, Data0),
-    Vab  = wings_cc:gen_vab(Data),
-    #sp{src_we=We0,we=We0,vab=Vab,type={wings_cc,Data}}.
-
-create_proxy_cc(We = #we{fs=Ftab}, Level, St) ->
-    Plan = wings_draw_setup:prepare(gb_trees:keys(Ftab), We, St),
-    Data = wings_cc:init(Plan, Level, We),
-    Vab  = wings_cc:gen_vab(Data),
-    #sp{src_we=We,we=We,vab=Vab,type={wings_cc,Data}}.
-
-split_proxy(#dlo{proxy=true, src_we=We=#we{fs=Ftab},
-		 proxy_data=Pd=#sp{type={wings_cc,Data0}}},
-	    DynVs0, St) ->
-    Fs0 = gb_trees:keys(Ftab),
-    DynFs0 = wings_face:from_vs(DynVs0, We),
-
-    %% Expand once (to get the split drawing faces)
-    DynVs1 = wings_face:to_vertices(DynFs0, We),
-    DynFs = wings_face:from_vs(DynVs1, We),
-
-    Data = case proxy_needs_update(We, Pd) of
-	       {false, _} -> 
-		   Data0;
-	       {update, _} ->
-		   wings_cc:update(DynVs0, Data0);
-	       {_, _} ->
-		   Plan = wings_draw_setup:prepare(Fs0, We, St),
-		   wings_cc:init(Plan, Data0, We)
-	   end,
-    StaticFsSet = gb_sets:subtract(gb_sets:from_ordset(Fs0), 
-				   gb_sets:from_ordset(DynFs)),
-    StaticFs = gb_sets:to_list(StaticFsSet),
-    StaticPlan = wings_draw_setup:prepare(StaticFs, We, St),
-    StaticVab = wings_cc:gen_vab(StaticPlan, Data),
-    StaticDL = wings_draw:draw_flat_faces(StaticVab, St),
-    
-    %% To get the subdiv correct we need outer layer of faces during calc
-    SubdivVs = wings_face:to_vertices(DynFs, We),
-    SubdivFs = wings_face:from_vs(SubdivVs, We),
-    SubdivPlan = wings_draw_setup:prepare(SubdivFs, We, St),
-    SubdivData = wings_cc:init(SubdivPlan, Data0, We),
-    
-    DynPlan  = wings_draw_setup:prepare(DynFs, We, St),
-    DynVab   = wings_cc:gen_vab(DynPlan, SubdivData),
-    DynDL = wings_draw:draw_flat_faces(DynVab, St),
-    Split = #split{dyn=DynPlan, info=SubdivData},
-    #sp{we=We,src_we=We,type={wings_cc,Data},
-	faces=[StaticDL,DynDL],split=Split};
-
 split_proxy(#dlo{proxy=true,proxy_data=Pd0,src_we=SrcWe}, DynVs0, St) ->
     DynFs0 = wings_face:from_vs(DynVs0, SrcWe),
     #we{mirror=Mirror,holes=Holes} = SrcWe,
@@ -452,13 +385,6 @@ update_dynamic(ChangedVs, St,
     Pd1  = flat_faces(DynPlan, Pd0#sp{we=We, src_we=SrcWe}),
     Temp = wings_draw:draw_flat_faces(Pd1#sp.vab, St),
     D0#dlo{proxy_data=Pd1#sp{faces=[SDL,Temp]}};
-update_dynamic(ChangedVs, St, 
-	       D0=#dlo{proxy=true,proxy_data=#sp{type={wings_cc,_}}=Pd0}) ->
-    #sp{faces=[SDL|_],split=SP=#split{dyn=DynPlan, info=Data0}}=Pd0,
-    Data = wings_cc:update(ChangedVs, Data0),
-    Vab  = wings_cc:gen_vab(DynPlan, Data),
-    DL   = wings_draw:draw_flat_faces(Vab, St),
-    D0#dlo{proxy_data=Pd0#sp{faces=[SDL,DL], split=SP#split{info=Data}}};
 update_dynamic(_, _, D) ->
     D.
 
-- 
1.8.1.4