1%%
2%%  wpc_collada.erl --
3%%
4%%     Collada export.
5%%
6%%  Copyright (c) 2017 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%%     $Id$
12%%
13-module(wpc_gltf).
14-export([init/0,menu/2,command/2]).
15
16-define(DEF_IMAGE_TYPE, ".png").
17
18-include_lib("src/wings.hrl").
19-include_lib("e3d/e3d.hrl").
20-include_lib("e3d/e3d_image.hrl").
21-include_lib("wx/include/gl.hrl").
22
23-define(F32L, 32/float-little).
24
25init() ->
26    %% Collada specifies an "up_axis" parameter, so your
27    %% model should usually be the "right way up"
28    wpa:pref_set_default(?MODULE, swap_y_z, false),
29    true.
30
31menu({file,export}, Menu) ->
32    menu_entry(Menu, true);
33menu({file, export_selected}, Menu) ->
34    menu_entry(Menu, true);
35menu({file,import}, Menu) ->
36    menu_entry(Menu, false);
37menu(_, Menu) -> Menu.
38
39menu_entry(Menu, true) ->
40    Menu ++ [{"glTF (.gltf|.glb)...", glb,[option]}];
41menu_entry(Menu, false) ->
42    Menu ++ [{"glTF (.gltf|.glb)", glb}].
43
44command({file, {import, glb}}, St) ->
45    Props = [{extensions, [{".gltf", "gl Transmission Format"},
46                           {".glb",  "gltf binary"}]}],
47    wpa:import(Props, fun do_import/1, St);
48command({file,{export,{glb,Ask}}}, St) ->
49    Exporter = fun(Ps, Fun) -> wpa:export(Ps, Fun, St) end,
50    do_export(Ask, export, Exporter, St);
51command({file,{export_selected,{glb,Ask}}}, St) ->
52    Exporter = fun(Ps, Fun) -> wpa:export_selected(Ps, Fun, St) end,
53    do_export(Ask, export_selected, Exporter, St);
54command(_, _) -> next.
55
56do_export(Ask, Op, _Exporter, _St) when is_atom(Ask) ->
57    wpa:dialog(Ask, ?__(1,"gl Transmission Format Export Options"),
58               dialog(export),
59	       fun(Res) ->
60		       {file,{Op,{glb,Res}}}
61	       end);
62do_export(Attr, _Op, Exporter, _St) when is_list(Attr) ->
63    set_pref(Attr),
64    SubDivs = proplists:get_value(subdivisions, Attr, 0),
65    Uvs = proplists:get_bool(include_uvs, Attr),
66    %% Units = proplists:get_value(units, Attr),
67    Ps = [{include_uvs,Uvs},%% {units,Units},
68          {tesselation, triangulate},
69          {include_hard_edges, true},
70	  {subdivisions,SubDivs}|props()],
71    Exporter(Ps, export_fun(Attr)),
72    keep.
73
74dialog(Type) ->
75    [{hframe,
76      [
77       {label, ?__(200,"File type") },
78       {menu, [
79               {"gl Transmission Format (*.gltf)", gltf},
80               {"glTF binary (*.glb)", glb}
81              ], glb, [{key, file_type}]}
82      ]},
83     %% wpa:dialog_template(?MODULE, units), panel,
84     wpa:dialog_template(?MODULE, Type, [include_colors, include_normals])].
85
86props() ->
87    [{extensions,
88      [{".glb",  "gltf binary"},
89       {".gltf", "gl Transmission Format"}]}].
90
91set_pref(KeyVals) ->
92    wpa:pref_set(?MODULE, KeyVals).
93
94export_fun(Attr) ->
95    fun(Filename, Contents) ->
96	    export_1(Filename, Contents, Attr)
97    end.
98
99export_1(Filename, Contents0, Attr) ->
100    Dir = filename:dirname(Filename),
101    FileType = proplists:get_value(file_type, Attr, glb),
102    ImageDir = case FileType of
103                   glb -> wings_u:basedir(user_cache);
104                   gltf -> Dir
105               end,
106    ok = filelib:ensure_dir(filename:join(ImageDir, "dummy")),
107    Imagetype = proplists:get_value(default_filetype, Attr, ?DEF_IMAGE_TYPE),
108    Contents1 = e3d_file:transform(Contents0, wpa:export_matrix(Attr)),
109    Contents2 = wpa:save_images(Contents1, ImageDir, Imagetype),
110    #e3d_file{objs=Objs, mat=Mat, creator=Creator} = Contents2,
111    GLTF0 = #{asset => #{generator => unicode:characters_to_binary(Creator),
112                         version=> <<"2.0">>},
113              accessors   => [],
114              bufferViews => [],
115              buffers => [],
116              images => [],
117              materials => [],
118              meshes => [],
119              nodes => [],
120              scene => 0,
121              scenes => [],
122              textures => []
123             },
124    {Ns,GLTF1} = lists:foldl(fun exp_object/2, {[], GLTF0}, Objs),
125    GLTF2 = exp_make_materials(Mat, FileType, GLTF1),
126    GLTF3 = GLTF2#{
127              accessors := lists:reverse(maps:get(accessors, GLTF2)),
128              meshes    := lists:reverse(maps:get(meshes, GLTF2)),
129              nodes     := lists:reverse(maps:get(nodes, GLTF2)),
130              scenes    := [#{nodes=>lists:reverse(Ns)}],
131              materials := lists:reverse(maps:get(materials, GLTF2)),
132              images    := lists:reverse(maps:get(images, GLTF2)),
133              textures  := lists:reverse(maps:get(textures, GLTF2))
134             },
135    GLTF4 = case maps:get(images, GLTF3) of
136                [] -> maps:remove(textures, maps:remove(images,GLTF3));
137                _  -> GLTF3
138            end,
139
140    {VtxData, GLTF5} = exp_setup_buffers(GLTF4),
141
142    case FileType of
143        glb -> %% Pack
144            EncGLTF = jsone:encode(GLTF5, [{float_format, [compact]}]),
145            GLTFSz  = byte_size(EncGLTF),
146            GLTFAlignSz = (4-GLTFSz rem 4) rem 4,
147            GLTFAlign = list_to_binary(lists:duplicate(GLTFAlignSz, $\s)),
148            VtxDataSz = byte_size(VtxData),
149            VtxAlignSz = (4-VtxDataSz rem 4) rem 4,
150            VASzB = VtxAlignSz*8,
151            TotSz = 12 + 8 + GLTFSz + GLTFAlignSz + 8 + VtxDataSz + VtxAlignSz,
152            Bin = <<"glTF", 2:32/little, TotSz:32/little,
153                    (GLTFSz+GLTFAlignSz):32/little, "JSON", EncGLTF/binary, GLTFAlign/binary,
154                    (VtxDataSz+VtxAlignSz):32/little, "BIN", 0:8, VtxData/binary, 0:VASzB
155                  >>,
156            %% io:format("TotSz: ~p ~p ~p ~p ~p ~p~n", [28, GLTFSz, GLTFAlignSz, VtxDataSz, VtxAlignSz, TotSz]),
157            %% io:format("      ~p~n",[byte_size(Bin)]),
158            ok = file:write_file(filename:join(Dir, Filename), Bin);
159        gltf ->
160            FileBin = filename:rootname(filename:basename(Filename)) ++ ".bin",
161            [Buff] = maps:get(buffers, GLTF5),
162            GLTF = GLTF5#{buffers:=[Buff#{uri=>unicode:characters_to_binary(FileBin)}]},
163            EncGLTF = jsone:encode(GLTF, [{indent, 2}, {space, 1},
164                                          {float_format, [compact]}]),
165            ok = file:write_file(Filename, unicode:characters_to_binary(EncGLTF)),
166            ok = file:write_file(filename:join(Dir, FileBin), VtxData)
167    end.
168
169exp_object(#e3d_object{name=Name, obj=WMesh}, {Ns,GLTF0}) ->
170    NameBin = unicode:characters_to_binary(Name),
171    {Mesh,GLTF1} = exp_mesh(WMesh, NameBin, GLTF0),
172    {MeshId, GLTF2} = exp_add(Mesh, meshes, GLTF1),
173    Node = #{name => NameBin, mesh => MeshId},
174    {Id, GLTF} = exp_add(Node, nodes, GLTF2),
175    {[Id|Ns], GLTF}.
176
177exp_mesh(WMesh0, Name, GLTF0) ->
178    WMesh1 = e3d_mesh:vertex_normals(WMesh0),
179    #e3d_mesh{vs=Vs,ns=Ns,tx=Tx,vc=Vc} = WMesh1,
180    WMesh = WMesh1#e3d_mesh{vs=array:from_list(Vs),
181                            ns=array:from_list(Ns),
182                            tx=array:from_list(Tx, {0.0,0.0}),
183                            vc=array:from_list(Vc)},
184    FacesByMaterial = segment_by_material(WMesh),
185    {Prims,GLTF} = exp_mesh_1(FacesByMaterial, WMesh, GLTF0, [], #{}),
186    {#{name=>Name, primitives=>Prims},GLTF}.
187
188exp_mesh_1([{[Mat|_], Fs}|MatFs], WMesh, GLTF0, Ps, S0) ->
189    {MId, GLTF} = material_id(Mat, GLTF0),
190    {Inds, S} = case {array:size(WMesh#e3d_mesh.tx),
191		      array:size(WMesh#e3d_mesh.vc)} of
192		    {0,0} -> exp_faces(Fs, WMesh, fun exp_face_n/3, [], S0);
193		    {_,0} -> exp_faces(Fs, WMesh, fun exp_face_tx/3, [], S0);
194		    {0,_} -> exp_faces(Fs, WMesh, fun exp_face_vc/3, [], S0);
195		    {_,_} -> exp_faces(Fs, WMesh, fun exp_face_tx_vc/3, [], S0)
196                end,
197    P = #{material=> MId, indices=>length(Fs)*3},
198    exp_mesh_1(MatFs, WMesh, GLTF, [{P, Inds}|Ps], S);
199exp_mesh_1([], #e3d_mesh{tx=Tx, vc=Vc, vs=Vs}, GLTF0, Ps0, S) ->
200    {Ps, GLTF1} = exp_add_index(lists:reverse(Ps0), GLTF0),
201    MinMax = e3d_bv:box(array:to_list(Vs)),
202    {Attr, GLTF} = exp_add_mesh_data(MinMax, array:size(Tx) =:= 0, array:size(Vc) =:= 0, S, GLTF1),
203    {[P#{attributes=>Attr} || P <- Ps], GLTF}.
204
205exp_add_index(Ps0, GLTF0) ->
206    AppendBin = fun({P, Inds}, Bin) -> {{P, byte_size(Bin)}, <<Bin/binary, Inds/binary>>} end,
207    {Ps1, Bin} = lists:mapfoldl(AppendBin, <<>>, Ps0),
208    {BVId, GLTF1} = exp_add(Bin, bufferViews, GLTF0),
209    lists:mapfoldr(fun({#{indices:=Len}=P, Offset}, GLTF_t) ->
210                           Access = exp_make_acc(BVId, Len, ?GL_UNSIGNED_INT,
211                                                <<"SCALAR">>, Offset),
212                           {AId, GLTF} = exp_add(Access, accessors, GLTF_t),
213                           {P#{indices:=AId}, GLTF}
214                   end, GLTF1, Ps1).
215
216exp_add_mesh_data({Min, Max}, NoTx, NoVc, S, GLTF0) ->
217    VsData = lists:sort(maps:values(S)),
218    N = maps:size(S),
219    Bin = << <<Bin/binary>> || {_, Bin} <- VsData>>,
220    Stride = case {NoTx,NoVc} of
221		 {true,true} -> 6*4;
222		 {false,true} -> 6*4+2*4;
223		 {true,false} -> 6*4+4*4;
224		 {false,false} -> 6*4+2*4+4*4
225             end,
226
227    {BVId, GLTF1} = exp_add(#{buffer=>Bin, byteStride=> Stride}, bufferViews, GLTF0),
228    VsAcc = exp_make_acc(BVId, N, ?GL_FLOAT, <<"VEC3">>, 0),
229    {VsA, GLTF2} = exp_add(VsAcc#{min=>tuple_to_list(Min), max=>tuple_to_list(Max)},
230                           accessors, GLTF1),
231    {NsA, GLTF3} = exp_add(exp_make_acc(BVId, N, ?GL_FLOAT, <<"VEC3">>, 3*4),
232                           accessors, GLTF2),
233    case {NoTx,NoVc} of
234	{true,true} ->
235            {#{'POSITION'=>VsA, 'NORMAL'=> NsA}, GLTF3};
236	{false,true} ->
237            {TxA, GLTF4} = exp_add(exp_make_acc(BVId, N, ?GL_FLOAT, <<"VEC2">>, 6*4),
238                                   accessors, GLTF3),
239            {#{'POSITION'=>VsA, 'NORMAL'=> NsA, 'TEXCOORD_0' => TxA}, GLTF4};
240	{true,false} ->
241	    {VcA, GLTF4} = exp_add(exp_make_acc(BVId, N, ?GL_FLOAT, <<"VEC4">>, 6*4),
242				   accessors, GLTF3),
243	    {#{'POSITION'=>VsA, 'NORMAL'=> NsA, 'COLOR_0' => VcA}, GLTF4};
244	{false,false} ->
245	    {TxA, GLTF4} = exp_add(exp_make_acc(BVId, N, ?GL_FLOAT, <<"VEC2">>, 6*4),
246				   accessors, GLTF3),
247	    {VcA, GLTF5} = exp_add(exp_make_acc(BVId, N, ?GL_FLOAT, <<"VEC4">>, 6*4+2*4),
248				   accessors, GLTF4),
249	    {#{'POSITION'=>VsA, 'NORMAL'=> NsA, 'TEXCOORD_0' => TxA, 'COLOR_0' => VcA}, GLTF5}
250    end.
251
252exp_faces([Face|Fs], WMesh, Fun, Inds, S0) ->
253    {Is, S} = Fun(Face, WMesh, S0),
254    exp_faces(Fs, WMesh, Fun, Is ++ Inds, S);
255exp_faces([], _, _Fun, Inds, S) ->
256    Bin = << <<I:32/little>> || I <- lists:reverse(Inds)>>,
257    {Bin, S}.
258
259exp_face_n(#e3d_face{vs=[V1,V2,V3], ns=[N1,N2,N3]}, #e3d_mesh{vs=Vs,ns=Ns}, S0) ->
260    {F1,S1} = exp_data(V1,N1,Vs,Ns,S0),
261    {F2,S2} = exp_data(V2,N2,Vs,Ns,S1),
262    {F3,S3} = exp_data(V3,N3,Vs,Ns,S2),
263    {[F3,F2,F1], S3}.
264
265exp_face_tx(#e3d_face{vs=[V1,V2,V3], ns=[N1,N2,N3], tx=FTx},
266            #e3d_mesh{vs=Vs,ns=Ns,tx=Tx}, S0) ->
267    [T1,T2,T3] = fix_tx(FTx),
268    {F1,S1} = exp_data(V1,N1,T1,Vs,Ns,Tx,none,S0),
269    {F2,S2} = exp_data(V2,N2,T2,Vs,Ns,Tx,none,S1),
270    {F3,S3} = exp_data(V3,N3,T3,Vs,Ns,Tx,none,S2),
271    {[F3,F2,F1], S3}.
272
273exp_face_vc(#e3d_face{vs=[V1,V2,V3], ns=[N1,N2,N3], vc=FVc},
274	    #e3d_mesh{vs=Vs,ns=Ns,vc=Vc}, S0) ->
275    [VC1,VC2,VC3] = fix_tx(FVc),
276    {F1,S1} = exp_data(V1,N1,VC1,Vs,Ns,none,Vc,S0),
277    {F2,S2} = exp_data(V2,N2,VC2,Vs,Ns,none,Vc,S1),
278    {F3,S3} = exp_data(V3,N3,VC3,Vs,Ns,none,Vc,S2),
279    {[F3,F2,F1], S3}.
280
281exp_face_tx_vc(#e3d_face{vs=[V1,V2,V3], ns=[N1,N2,N3], tx=FTx, vc=FVc},
282	    #e3d_mesh{vs=Vs,ns=Ns,tx=Tx,vc=Vc}, S0) ->
283    [T1,T2,T3] = fix_tx(FTx),
284    [VC1,VC2,VC3] = fix_tx(FVc),
285    {F1,S1} = exp_data(V1,N1,{T1,VC1},Vs,Ns,Tx,Vc,S0),
286    {F2,S2} = exp_data(V2,N2,{T2,VC2},Vs,Ns,Tx,Vc,S1),
287    {F3,S3} = exp_data(V3,N3,{T3,VC3},Vs,Ns,Tx,Vc,S2),
288    {[F3,F2,F1], S3}.
289
290
291exp_data(V,N,Vs,Ns,S0) ->
292    Key = {V,N},
293    case maps:get(Key, S0, undefined) of
294        {Id, _} -> {Id, S0};
295        undefined ->
296            Id = maps:size(S0),
297            {X,Y,Z} = array:get(V, Vs),
298            {NX,NY,NZ} = array:get(N, Ns),
299            Bin = << X:?F32L, Y:?F32L, Z:?F32L,
300                    NX:?F32L,NY:?F32L,NZ:?F32L>>,
301            {Id, S0#{Key=>{Id, Bin}}}
302    end.
303
304exp_data(V,N,Uv,Vs,Ns,Tx,none,S0) ->
305    Key = {V,N,Uv},
306    case maps:get(Key, S0, undefined) of
307        {Id, _} -> {Id, S0};
308        undefined ->
309            Id = maps:size(S0),
310            {X,Y,Z} = array:get(V, Vs),
311            {NX,NY,NZ} = array:get(N, Ns),
312            {XU,XV} = array:get(Uv, Tx),
313            Bin = << X:?F32L, Y:?F32L, Z:?F32L,
314                     NX:?F32L,NY:?F32L,NZ:?F32L,
315                     XU:?F32L,(1.0-XV):?F32L>>,
316            {Id, S0#{Key=>{Id, Bin}}}
317    end;
318exp_data(V,N,Cl,Vs,Ns,none,Vc,S0) ->
319    Key = {V,N,Cl},
320    case maps:get(Key, S0, undefined) of
321	{Id, _} -> {Id, S0};
322	undefined ->
323	    Id = maps:size(S0),
324	    {X,Y,Z} = array:get(V, Vs),
325	    {NX,NY,NZ} = array:get(N, Ns),
326	    {R,G,B,A} =
327	    	case array:get(Cl, Vc) of
328		    {R0,G0,B0} -> {R0,G0,B0,1.0};
329		    RGBA -> RGBA
330		end,
331	    Bin = << X:?F32L, Y:?F32L, Z:?F32L,
332		     NX:?F32L,NY:?F32L,NZ:?F32L,
333		     R:?F32L,G:?F32L,B:?F32L,A:?F32L>>,
334	    {Id, S0#{Key=>{Id, Bin}}}
335    end;
336exp_data(V,N,{Uv,Cl},Vs,Ns,Tx,Vc,S0) ->
337    Key = {V,N,Uv},
338    case maps:get(Key, S0, undefined) of
339	{Id, _} -> {Id, S0};
340	undefined ->
341	    Id = maps:size(S0),
342	    {X,Y,Z} = array:get(V, Vs),
343	    {NX,NY,NZ} = array:get(N, Ns),
344	    {XU,XV} = array:get(Uv, Tx),
345	    {R,G,B,A} =
346	    case array:get(Cl, Vc) of
347		{R0,G0,B0} -> {R0,G0,B0,1.0};
348		RGBA -> RGBA
349	    end,
350	    Bin = << X:?F32L, Y:?F32L, Z:?F32L,
351		     NX:?F32L,NY:?F32L,NZ:?F32L,
352		     XU:?F32L,(1.0-XV):?F32L,
353		     R:?F32L,G:?F32L,B:?F32L,A:?F32L>>,
354	    {Id, S0#{Key=>{Id, Bin}}}
355    end.
356
357
358exp_setup_buffers(#{bufferViews:=BVs0} = GLTF0) ->
359    {Bin, BVs} = exp_setup_buffer(lists:reverse(BVs0), <<>>, []),
360    {0, GLTF} = exp_add(#{byteLength=>byte_size(Bin)}, buffers, GLTF0),
361    {Bin, GLTF#{bufferViews:=BVs}}.
362
363exp_setup_buffer([#{buffer:=B, byteStride:=Stride}|Bs], Bin, BVs)  ->
364    BV = #{buffer => 0, byteLength=> byte_size(B),
365           byteOffset => byte_size(Bin), byteStride => Stride},
366    exp_setup_buffer(Bs, <<Bin/binary, B/binary>>, [BV|BVs]);
367exp_setup_buffer([B|Bs], Bin, BVs) when is_binary(B) ->
368    BV = #{buffer => 0, byteLength=> byte_size(B), byteOffset => byte_size(Bin)},
369    exp_setup_buffer(Bs, <<Bin/binary, B/binary>>, [BV|BVs]);
370exp_setup_buffer([], Bin, BVs) ->
371    {Bin, lists:reverse(BVs)}.
372
373exp_make_materials(WMat, Type, #{materials:=UsedMats} = GLTF) ->
374    exp_make_materials(UsedMats, WMat, Type, GLTF#{materials:=[]}).
375
376exp_make_materials([Used|UMs], WMats, Type, GLTF0) ->
377    WMat = proplists:get_value(Used,WMats),
378    GL   = proplists:get_value(opengl, WMat),
379    {DR,DG,DB,DA} = proplists:get_value(diffuse, GL),
380    Metallic = proplists:get_value(metallic, GL, 0.1),
381    Roughness = proplists:get_value(roughness, GL, 0.8),
382    {ER,EG,EB,_} = proplists:get_value(emission, GL),
383    Maps = proplists:get_value(maps, WMat, []),
384    %% [io:format("Map: ~p ~p~n", [T, I#e3d_image{image= <<>>}]) || {T,I} <- Maps],
385
386    Base0 = #{baseColorFactor=> [DR,DG,DB,DA],
387              metallicFactor => Metallic,
388              roughnessFactor=> Roughness},
389    DiffMap = proplists:get_value(diffuse, Maps),
390
391    {Base1,GLTF1} = exp_add_image(DiffMap, Base0, baseColorTexture, Type, GLTF0),
392    {Base, GLTF2} = exp_add_image(merge_met_roughness(Maps),
393                                  Base1, metallicRoughnessTexture, Type, GLTF1),
394
395    Mat0 = #{pbrMetallicRoughness => Base,
396             emissiveFactor => [ER,EG,EB],
397             name => atom_to_binary(Used, utf8),
398             doubleSided => true
399           },
400    {Mat1, GLTF3} = exp_add_image(proplists:get_value(normal, Maps),
401                                 Mat0, normalTexture, Type, GLTF2),
402    {Mat2, GLTF4} = exp_add_image(proplists:get_value(emission, Maps),
403                                  Mat1, emissiveTexture, Type, GLTF3),
404    {Mat3, GLTF5} = exp_add_image(proplists:get_value(occlusion, Maps),
405                                  Mat2, occlusionTexture, Type, GLTF4),
406
407    Mat = case DiffMap of
408              #e3d_image{bytes_pp = 4} ->
409                  Mat3#{alphaMode=><<"BLEND">>, doubleSided:=false};
410              _ when DA < 1.0 ->
411                  Mat3#{alphaMode=><<"BLEND">>, doubleSided:=false};
412              _ -> Mat3
413          end,
414
415    {_, GLTF} = exp_add(Mat, materials, GLTF5),
416    exp_make_materials(UMs, WMats, Type, GLTF);
417exp_make_materials([], _, _, GLTF) ->
418    GLTF.
419
420merge_met_roughness(Maps) ->
421    {FN, E3d} =
422        case {proplists:get_value(metallic, Maps),
423              proplists:get_value(roughness, Maps)} of
424            {undefined, undefined}=Undef -> Undef;
425            {#e3d_image{filename=File}=Map, undefined} ->
426                {File, e3d_image:expand_channel(b, e3d_image:convert(Map, g8, 1))};
427            {undefined, #e3d_image{filename=File}=Map} ->
428                {File, e3d_image:expand_channel(g, e3d_image:convert(Map, g8, 1))};
429            {#e3d_image{width=W, height=H}=Met, #e3d_image{width=W, height=H}=Rough} ->
430                RGBA0 = e3d_image:expand_channel(b, e3d_image:convert(Met, g8, 1)),
431                RGBA1 = e3d_image:replace_channel(g, e3d_image:convert(Rough, g8, 1), RGBA0),
432                {Met#e3d_image.filename, RGBA1};
433            %% Different sizes, should rescale on off them here
434            {#e3d_image{filename=File}=Map, _} ->
435                {File, e3d_image:expand_channel(b, e3d_image:convert(Map, g8, 1))}
436        end,
437    case E3d of
438        undefined -> undefined;
439        _ ->
440            Dir = filename:dirname(FN),
441            Ext = filename:extension(FN),
442            FileName = filename:basename(FN, Ext),
443            SaveFile = filename:join(Dir, FileName ++ "_met_rough" ++ Ext),
444            RGB = e3d_image:convert(E3d, r8g8b8),
445            wings_image:image_write([{image, RGB}, {filename, SaveFile}]),
446            RGB#e3d_image{filename=SaveFile}
447    end.
448
449exp_add_image(undefined, Data, _, _, GLTF) ->
450    {Data, GLTF};
451exp_add_image(#e3d_image{filename=File}, Data, Key, gltf, GLTF0) ->
452    BinName = unicode:characters_to_binary(filename:basename(File)),
453    {ImId, GLTF1} = exp_add(#{uri => BinName}, images, GLTF0),
454    {TxId, GLTF2} = exp_add(#{source => ImId}, textures, GLTF1),
455    {Data#{Key=>#{index=>TxId}}, GLTF2};
456exp_add_image(#e3d_image{filename=File}, Data, Key, glb, GLTF0) ->
457    {ok, ImageBin} = file:read_file(File),
458    MType = case filename:extension(File) of
459                ".png" -> <<"image/png">>;
460                ".jpg" -> <<"image/jpeg">>
461            end,
462    {BvId, GLTF1} = exp_add(ImageBin, bufferViews, GLTF0),
463    {ImId, GLTF2} = exp_add(#{bufferView => BvId, mimeType=>MType}, images, GLTF1),
464    {TxId, GLTF3} = exp_add(#{source => ImId}, textures, GLTF2),
465    {Data#{Key=>#{index=>TxId}}, GLTF3}.
466
467
468segment_by_material(#e3d_mesh{fs=Fs}) ->
469    FacesByMaterial0 = gb_trees:empty(),
470    Sep = fun(#e3d_face{mat=Mats}=Face, Tree0) ->
471                  Tree1 = case gb_trees:lookup(Mats, Tree0) of
472                              {value,FaceList0} ->
473                                  FaceList = [Face|FaceList0],
474                                  gb_trees:update(Mats, FaceList, Tree0);
475                              none ->
476                                  gb_trees:insert(Mats, [Face], Tree0)
477                          end,
478                  Tree1
479	  end,
480    Segs = lists:foldl(Sep, FacesByMaterial0, Fs),
481    gb_trees:to_list(Segs).
482
483material_id(Mat, #{materials:= Mats} = GLTF) ->
484    case material_id(Mat, Mats, 0) of
485        {new, Id} ->
486            {Id, GLTF#{materials:=Mats ++ [Mat]}};
487        Id ->
488            {Id, GLTF}
489    end.
490
491material_id(Mat, [Mat|_], Id) ->
492    Id;
493material_id(Mat, [_|Mats], Id) ->
494    material_id(Mat, Mats, Id+1);
495material_id(_, [], Id) ->
496    {new, Id}.
497
498fix_tx([_,_,_]=Tx) -> Tx;
499fix_tx(_) -> [999999,999999,999999].
500
501exp_make_acc(BvId, N, CT, Type,Offset) when is_integer(BvId) ->
502    #{bufferView=>BvId,
503      byteOffset=>Offset,
504      componentType=>CT,
505      count=> N,
506      type=> Type}.
507
508exp_add(New, What, GLTF) ->
509    Orig = maps:get(What, GLTF),
510    {length(Orig), GLTF#{What:=[New|Orig]}}.
511
512%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
513
514-record(is, {file="",
515             dir ="",
516             objs=[],
517             matrix=[e3d_mat:identity()],
518             buffers  %% Binary data
519            }).
520
521do_import(File) ->
522    {ok, Bin} = file:read_file(File),
523    FileSz = byte_size(Bin),
524    case Bin of
525        <<"glTF", _Ver:32/little, FileSz:32/little,Chunks/binary>> ->
526            do_import(fetch_chunks(Chunks), File);
527        <<"glTF", _/binary>> ->
528            {error, "Data format error"};
529        _ ->
530            do_import([Bin], File)
531    end.
532
533do_import([JSON|Rest], File) ->
534    Dir = filename:dirname(File),
535    GLTF = jsone:decode(JSON, [{object_format, map}, {keys, atom}]),
536    case maps:get(extensionsRequired, GLTF, []) of
537        [] ->
538            SceneId = maps:get(scene, GLTF, 0),
539            #{nodes:=Nodes} = get_index(SceneId, scenes, GLTF),
540            #{buffers:=BufferIds} = GLTF,
541            GetBuffer = fun(Buff) -> imp_get_data(Buff, Dir, Rest) end,
542            GetImage = fun(Buff, Type) -> imp_get_image(Buff, Type, File, Rest, GLTF) end,
543            Buffers = [GetBuffer(BId) || BId <- BufferIds],
544            {Mats, GLTF_1} = make_mats(GLTF#{read_image=>GetImage}, File),
545            Objs = imp_objects(Nodes, GLTF_1, #is{buffers=Buffers, dir=Dir, file=filename:basename(File)}),
546            {ok, #e3d_file{dir=Dir, objs=Objs, mat=Mats}};
547        [_|_] ->
548            {error, "Unsupported extension required"}
549    end.
550
551fetch_chunks(<<Len:32/little, "JSON", Rest/binary>>) ->
552    PadSz = (4-Len rem 4) rem 4,
553    <<Chunk:Len/binary, _:PadSz/binary, Chunks/binary>> = Rest,
554    [Chunk | fetch_chunks(Chunks)];
555fetch_chunks(<<Len:32/little, "BIN", 0:8, Rest/binary>>) ->
556    PadSz = (4-Len rem 4) rem 4,
557    <<Chunk:Len/binary, _:PadSz/binary, Chunks/binary>> = Rest,
558    [Chunk | fetch_chunks(Chunks)];
559fetch_chunks(<<Len:32/little, Type:32/little, Rest/binary>>) ->
560    PadSz = (4-Len rem 4) rem 4,
561    <<_Chunk:Len/binary, _:PadSz/binary, Chunks/binary>> = Rest,
562    io:format("Skipped: ~p ~wbytes~n", [Type, Len]),
563    fetch_chunks(Chunks);
564fetch_chunks(_) ->
565    [].
566
567imp_objects([NodeId|Ns], GLTF, #is{matrix=MS, objs=Os}=IS) ->
568    Node = get_index(NodeId, nodes, GLTF),
569    Matrix = get_matrix(Node, hd(MS)),
570    case Node of
571        #{mesh:=MeshId} ->
572            Mesh = get_index(MeshId, meshes, GLTF),
573            Name0 = maps:get(name, Node, filename:rootname(IS#is.file)),
574            Name = unicode:characters_to_list(maps:get(name, Mesh, Name0)),
575            E3dMeshes = imp_mesh(Mesh, GLTF, IS),
576            Objs = [#e3d_object{name=Name, obj=E3dMesh#e3d_mesh{matrix=Matrix}} ||
577                       E3dMesh <- E3dMeshes],
578            imp_objects(Ns, GLTF, IS#is{objs=Objs++Os});
579        #{children:=Chs} ->
580            Objs = imp_objects(Chs, GLTF, IS#is{matrix=[Matrix|MS]}),
581            imp_objects(Ns, GLTF, IS#is{objs=Objs});
582        #{} -> %% Cameras and animation
583            imp_objects(Ns, GLTF, IS)
584    end;
585imp_objects([], _, #is{objs=Objs}) ->
586    lists:reverse(Objs).
587
588imp_mesh(#{primitives:=Ps}, GLTF, #is{buffers=Bs}) ->
589    E3dMeshes = lists:foldl(fun(P,M) -> imp_faces(P, GLTF, Bs, M) end, [], Ps),
590    [E3dMesh || {E3dMesh, _} <- E3dMeshes].
591
592imp_faces(#{attributes:=As, indices:=_}=P, GLTF, Bs, MS0) ->
593    Is = imp_mesh_data(indices, maps:get(indices, P, []), GLTF, Bs),
594    Mat = case maps:get(material, P, undefined) of
595              undefined -> default;
596              MI ->
597                  #{name:=Name} = get_index(MI, materials, GLTF),
598                  binary_to_atom(Name, utf8)
599          end,
600    Mode = maps:get(mode, P, ?GL_TRIANGLES),
601    VSA = maps:get('POSITION', As, none),
602    NA  = maps:get('NORMAL', As, none),
603    TXA = maps:get('TEXCOORD_0', As, none),
604    VCA = maps:get('COLOR_0', As, none),
605    Fs = fetch_is(Mode, Is, NA=/=none, TXA=/=none, VCA=/=none, [Mat]),
606    case same_buffers({VSA,NA,TXA,VCA}, MS0) of
607        {true, [{#e3d_mesh{fs=Fs0}=M,Buffs}|MS]} ->
608            [{M#e3d_mesh{fs=Fs++Fs0},Buffs}|MS];
609        {false, Buffs} ->
610            Vs = imp_mesh_data(pos, VSA, GLTF, Bs),
611            Ns = imp_mesh_data(normal, NA, GLTF, Bs),
612            Tx = imp_mesh_data(tx, TXA, GLTF, Bs),
613            Vc = imp_mesh_data(vc, VCA, GLTF, Bs),
614            Fs = fetch_is(Mode, Is, NA=/=none, TXA=/=none, VCA=/=none, [Mat]),
615            [{#e3d_mesh{type=triangle, vs=Vs, ns=Ns, tx=Tx, vc=Vc, fs=Fs},Buffs}|MS0]
616    end.
617
618same_buffers(Buffs, [{_,Buffs}|_]=MS) ->
619    {true, MS};
620same_buffers(Buffs, _) ->
621    {false, Buffs}.
622
623imp_mesh_data(_, none, _GLTF, _Buffers) ->
624    [];
625imp_mesh_data(What, AId, GLTF, Buffers) ->
626    %% Fetch accessor
627    #{bufferView:=BVId, componentType:=CType, type:=Type, count:=N} = A =
628        get_index(AId, accessors, GLTF),
629    Offset0 = maps:get(byteOffset, A, 0),
630
631    %% Fetch buffer block
632    #{buffer:=BId, byteLength:=_BuffL} = BV = get_index(BVId, bufferViews, GLTF),
633    Offset1 = maps:get(byteOffset, BV, 0),
634    Buffer = lists:nth(BId+1, Buffers),
635    Offset = Offset0+Offset1,
636
637    CSz = size(CType, Type),
638    Stride = maps:get(byteStride, BV, CSz),
639    BlockSz = CSz+(N-1)*Stride,
640
641    %% io:format("What: ~p ~p BL:~p BSz:~p~n", [What, BVId, _BuffL, BlockSz]),
642    %% io:format("OS ~p+~p=~p  ~p+~p < ~p~n",
643    %%           [Offset0,Offset1,Offset, Offset,BlockSz,byte_size(Buffer)]),
644    %% <<_:Offset1/binary,BuffBlock:BuffL/binary,_/binary>> = Buffer,
645    %% <<_:Offset0/binary,Buff:BlockSz/binary, _/binary>> = BuffBlock,
646    <<_:Offset/binary, Buff:BlockSz/binary, _/binary>> = Buffer,
647    ModType = case {What, Type} of
648                  {tx, <<"VEC2">>}        -> <<"VEC2_FLIP_Y">>;
649                  {tx, <<"VEC2_FLIP_Y">>} -> <<"VEC2">>;
650                  _ -> Type
651              end,
652    Data = imp_buff(Buff, CType, ModType, Stride-CSz),
653    N = length(Data),
654    Data.
655
656%%%%%%%%%
657
658imp_buff(Bin, ?GL_FLOAT, <<"SCALAR">>, Skip) ->
659    lists:reverse(imp_buff_1f(Bin, Skip, []));
660imp_buff(Bin, ?GL_FLOAT, <<"VEC2">>, Skip) ->
661    lists:reverse(imp_buff_2f(Bin, Skip, []));
662imp_buff(Bin, ?GL_FLOAT, <<"VEC2_FLIP_Y">>, Skip) ->
663    lists:reverse(imp_buff_2f_i(Bin, Skip, []));
664imp_buff(Bin, ?GL_FLOAT, <<"VEC3">>, Skip) ->
665    lists:reverse(imp_buff_3f(Bin, Skip, []));
666imp_buff(Bin, ?GL_FLOAT, <<"VEC4">>, Skip) ->
667    lists:reverse(imp_buff_4f(Bin, Skip, []));
668imp_buff(Bin, ?GL_BYTE, <<"SCALAR">>, Skip) ->
669    lists:reverse(imp_buff_1b(Bin, Skip, []));
670imp_buff(Bin, ?GL_UNSIGNED_BYTE, <<"SCALAR">>, Skip) ->
671    lists:reverse(imp_buff_1ub(Bin, Skip, []));
672imp_buff(Bin, ?GL_SHORT, <<"SCALAR">>, Skip) ->
673    lists:reverse(imp_buff_1s(Bin, Skip, []));
674imp_buff(Bin, ?GL_UNSIGNED_SHORT, <<"SCALAR">>, Skip) ->
675    lists:reverse(imp_buff_1us(Bin, Skip, []));
676imp_buff(Bin, ?GL_UNSIGNED_INT, <<"SCALAR">>, Skip) ->
677    lists:reverse(imp_buff_1ui(Bin, Skip, [])).
678
679imp_buff_1f(Bin, Skip, Acc) ->
680    case Bin of
681        <<A:32/float-little,_:Skip/binary, Rest/binary>> ->
682            imp_buff_1f(Rest, Skip, [A|Acc]);
683        <<A:32/float-little, _/binary>> when Skip > 0 ->
684            [A|Acc];
685        <<>> -> Acc
686    end.
687
688imp_buff_2f(Bin, Skip, Acc) ->
689    case Bin of
690        <<A:32/float-little,B:32/float-little,_:Skip/binary, Rest/binary>> ->
691            imp_buff_2f(Rest, Skip, [{A,B}|Acc]);
692        <<A:32/float-little,B:32/float-little, _/binary>> when Skip > 0 ->
693            [{A,B}|Acc];
694        <<>> -> Acc
695    end.
696
697imp_buff_2f_i(Bin, Skip, Acc) ->
698    case Bin of
699        <<A:32/float-little,B:32/float-little,_:Skip/binary, Rest/binary>> ->
700            imp_buff_2f_i(Rest, Skip, [{A,1.0-B}|Acc]);
701        <<A:32/float-little,B:32/float-little, _/binary>> when Skip > 0 ->
702            [{A,1.0-B}|Acc];
703        <<>> -> Acc
704    end.
705
706imp_buff_3f(Bin, Skip, Acc) ->
707    case Bin of
708        <<A:32/float-little,B:32/float-little,C:32/float-little,
709          _:Skip/binary, Rest/binary>> ->
710            imp_buff_3f(Rest, Skip, [{A,B,C}|Acc]);
711        <<A:32/float-little,B:32/float-little,C:32/float-little,
712          _/binary>> when Skip > 0 ->
713            [{A,B,C}|Acc];
714        <<>> -> Acc
715    end.
716
717imp_buff_4f(Bin, Skip, Acc) ->
718    case Bin of
719        <<A:32/float-little,B:32/float-little,C:32/float-little,D:32/float-little,
720          _:Skip/binary, Rest/binary>> ->
721            imp_buff_4f(Rest, Skip, [{A,B,C,D}|Acc]);
722        <<A:32/float-little,B:32/float-little,C:32/float-little,D:32/float-little,
723          _/binary>> when Skip > 0 ->
724            [{A,B,C,D}|Acc];
725        <<>> -> Acc
726    end.
727
728imp_buff_1b(Bin, Skip, Acc) ->
729    case Bin of
730        <<A:8,_:Skip/binary, Rest/binary>> ->
731            imp_buff_1b(Rest, Skip, [A|Acc]);
732        <<A:8, _/binary>> when Skip > 0 ->
733            [A|Acc];
734        <<>> -> Acc
735    end.
736
737imp_buff_1ub(Bin, Skip, Acc) ->
738    case Bin of
739        <<A:8/little-unsigned,_:Skip/binary, Rest/binary>> ->
740            imp_buff_1ub(Rest, Skip, [A|Acc]);
741        <<A:8/little-unsigned, _/binary>> when Skip > 0 ->
742            [A|Acc];
743        <<>> -> Acc
744    end.
745
746imp_buff_1s(Bin, Skip, Acc) ->
747    case Bin of
748        <<A:16/little,_:Skip/binary, Rest/binary>> ->
749            imp_buff_1s(Rest, Skip, [A|Acc]);
750        <<A:16/little, _/binary>> when Skip > 0 ->
751            [A|Acc];
752        <<>> -> Acc
753    end.
754
755imp_buff_1us(Bin, Skip, Acc) ->
756    case Bin of
757        <<A:16/little-unsigned,_:Skip/binary, Rest/binary>> ->
758            imp_buff_1us(Rest, Skip, [A|Acc]);
759        <<A:16/little-unsigned, _/binary>> when Skip > 0 ->
760            [A|Acc];
761        <<>> -> Acc
762    end.
763
764imp_buff_1ui(Bin, Skip, Acc) ->
765    case Bin of
766        <<A:32/little-unsigned,_:Skip/binary, Rest/binary>> ->
767            imp_buff_1ui(Rest, Skip, [A|Acc]);
768        <<A:32/little-unsigned, _/binary>> when Skip > 0 ->
769            [A|Acc];
770        <<>> -> Acc
771    end.
772
773size(?GL_FLOAT, <<"SCALAR">>) -> 4;
774size(?GL_FLOAT, <<"VEC2">>) -> 8;
775size(?GL_FLOAT, <<"VEC2_FLIP_Y">>) -> 8;
776size(?GL_FLOAT, <<"VEC3">>) -> 12;
777size(?GL_FLOAT, <<"VEC4">>) -> 16;
778size(?GL_BYTE, <<"SCALAR">>) -> 1;
779size(?GL_UNSIGNED_BYTE, <<"SCALAR">>) -> 1;
780size(?GL_SHORT, <<"SCALAR">>) -> 2;
781size(?GL_UNSIGNED_SHORT, <<"SCALAR">>) -> 2;
782size(?GL_UNSIGNED_INT, <<"SCALAR">>) -> 4.
783
784fetch_is(Mode, Is, UseN, UseTx, UseVc, Mat) ->
785    Inds = case Mode of
786               ?GL_TRIANGLES -> fetch_tris(Is);
787               ?GL_TRIANGLE_STRIP -> exit({nyi, strip});
788               ?GL_TRIANGLE_FAN -> exit({nyi, fan})
789           end,
790    [#e3d_face{vs=Ind, ns=attr(UseN, Ind), tx=attr(UseTx, Ind), vc=attr(UseVc,Ind), mat=Mat}
791     || Ind <- Inds].
792
793fetch_tris([A,B,C|Is]) ->
794    [[A,B,C]|fetch_tris(Is)];
795fetch_tris([]) ->
796    [].
797
798attr(true, Ind) -> Ind;
799attr(false, _Ind) -> [].
800
801%% type(?GL_FLOAT) -> float;
802%% type(?GL_BYTE) -> byte;
803%% type(?GL_UNSIGNED_BYTE) -> ubyte;
804%% type(?GL_SHORT) -> short;
805%% type(?GL_UNSIGNED_SHORT) -> ushort;
806%% type(?GL_UNSIGNED_INT) -> uint.
807
808%%%%%%%%%
809
810get_matrix(#{matrix:=List}, M0) ->
811    Mat = list_to_tuple([float(I) || I <- List]),
812    16 = tuple_size(Mat),
813    e3d_mat:mul(M0, Mat);
814get_matrix(Node, M0) ->
815    T = make_matrix(translation, Node),
816    R = make_matrix(rotation, Node),
817    S = make_matrix(scale, Node),
818    %% io:format("M=:~p~nT:~p~nR:~p~nS:~p~n",[M0,T,R,S]),
819    e3d_mat:mul(M0, e3d_mat:mul(S, e3d_mat:mul(R, T))).
820
821make_matrix(Key, Node) ->
822    case maps:get(Key, Node, undefined) of
823        undefined -> e3d_mat:identity();
824        Vals0 ->
825            [X,Y,Z|T] = [float(Val) || Val <- Vals0],
826            case Key of
827                translation -> e3d_mat:translate(X,Y,Z);
828                scale       -> e3d_mat:scale(X,Y,Z);
829                rotation when T =:= [0.0] -> e3d_mat:identity();
830                rotation    -> e3d_q:to_rotation_matrix({{X,Y,Z},hd(T)})
831            end
832    end.
833
834%%%%%%%%
835
836imp_get_data(#{uri:=<<"data:application/octet-stream;base64,", Base64/binary>>}, _, _) ->
837    base64:decode(Base64);
838imp_get_data(#{uri:=Uri}, Dir, _) when byte_size(Uri) < 512 ->
839    {ok, Buff} = file:read_file(filename:join(Dir, Uri)),
840    Buff;
841imp_get_data(#{byteLength:=BSz}, _, [Buffer]) ->
842    <<Bin:BSz/binary, _Pad/binary>> = Buffer,
843    Bin.
844
845imp_get_image(#{uri:=<<"data:image/", Rest/binary>>}, ImageType, File0, _, _) ->
846    {Ext, Bin} = case Rest of
847                     <<"jpeg;base64,", Base64/binary>> -> {"jpeg", base64:decode(Base64)};
848                     <<"png;base64,", Base64/binary>> -> {"png", base64:decode(Base64)}
849                 end,
850    DirFile = imp_save_filename(File0, ImageType, Ext),
851    imp_save_image(DirFile, Bin);
852imp_get_image(#{bufferView:=BVId, mimeType:=MType}=Image, ImageType, File0, [Buffer], GLTF) ->
853    Ext = case MType of
854              <<"image/png">> -> "png";
855              <<"image/jpeg">> -> "jpeg"
856          end,
857    {Dir, File1} = imp_save_filename(File0, ImageType, Ext),
858    File = maps:get(name, Image, File1),
859    #{byteLength:=BSz} = BV = get_index(BVId, bufferViews, GLTF),
860    Offset = maps:get(byteOffset, BV, 0),
861    <<_:Offset/binary,Bin:BSz/binary,_/binary>> = Buffer,
862    imp_save_image({Dir, unicode:characters_to_list(File)}, Bin).
863
864imp_save_image({Dir, File}, Bin) ->
865    %% Write temporary file, so we can load with wxImage:new(...)
866    case file:write_file(filename:join(Dir, File), Bin) of
867        ok -> File;
868        {error, _} ->
869            TmpDir = wings_u:basedir(user_cache),
870            TempFile = filename:join(TmpDir, File),
871            _ = file:write_file(TempFile, Bin),
872            TempFile
873    end.
874
875imp_save_filename(File0, ImageType, Ext) ->
876    Dir = filename:dirname(File0),
877    OrigName = filename:rootname(filename:basename(File0)),
878    File = lists:flatten(io_lib:format("~ts_~ts.~s",[OrigName, ImageType, Ext])),
879    {Dir, File}.
880
881make_mats(#{materials:=Ms0}=GLTF, File) ->
882    Dir = filename:dirname(File),
883    DefName = filename:rootname(filename:basename(File)),
884    Ms = mat_add_names(Ms0, 0, DefName),
885    GLMs = [make_mat(Mat, GLTF, Dir) || Mat <- Ms],
886    {GLMs, GLTF#{materials:=Ms}};
887make_mats(GLTF, _) ->
888    {[], GLTF}.
889
890make_mat(#{name:=Name}=Mat, GLTF, Dir) ->
891    case maps:get(pbrMetallicRoughness, Mat, none) of
892        none ->
893            Diffuse = [1.0,1.0,1.0,1.0],
894            DiffuseTx = {diffuse, none},
895            MetalTx = {metallic, none},
896            RoughTx = {roughness, none},
897            MetalF = 1.0,
898            RoughF = 0.9;
899        Pbr ->
900            Diffuse = [float(V) || V <- maps:get(baseColorFactor, Pbr, [1.0,1.0,1.0,1.0])],
901            DiffuseTx = {diffuse, get_texture(baseColorTexture, Pbr, GLTF)},
902            {Mtx,Rtx} = split_tx(get_texture(metallicRoughnessTexture, Pbr, GLTF), Dir),
903            MetalTx = {metallic, Mtx},
904            RoughTx = {roughness, Rtx},
905            MetalF = float(maps:get(metallicFactor, Pbr, 1.0)),
906            RoughF = float(maps:get(roughnessFactor, Pbr, 0.9))
907    end,
908
909    NormalTx = {normal, get_texture(normalTexture, Mat, GLTF)},
910    Emission = [float(V) || V <- maps:get(emmissiveFactor, Mat, [0.0,0.0,0.0])],
911    EmissionTx = {emission, get_texture(emissiveTexture, Mat, GLTF)},
912    OccTx = {occlusion, get_texture(occlusionTexture, Mat, GLTF)},
913    Txs = [NormalTx, DiffuseTx, MetalTx, RoughTx, EmissionTx, OccTx],
914    Maps = case [Map || {_, F} = Map <- Txs, F =/= none] of
915               [] -> [];
916               Maps0 -> [{maps, Maps0}]
917           end,
918    DiffuseC = list_to_tuple(Diffuse),
919    DefList = [{diffuse, DiffuseC},
920               {roughness, RoughF},
921               {metallic, MetalF},
922               {emission, list_to_tuple(Emission)}],
923    {binary_to_atom(Name, utf8), [{opengl, DefList}|Maps]}.
924
925get_texture(Name, Mat, #{read_image:=Get} = GLTF) ->
926    case maps:get(Name, Mat, none) of
927        none -> none;
928        #{index:=I} ->
929            #{source:=SrcId} = get_index(I, textures, GLTF),
930            case get_index(SrcId, images, GLTF) of
931                #{bufferView:=_} = Ref ->
932                    Get(Ref, Name);
933                #{uri:=<<"data:image/", _/binary>>} = Ref ->
934                    Get(Ref, Name);
935                #{uri:=File} when byte_size(File) < 512 ->
936                    unicode:characters_to_list(File)
937            end
938    end.
939
940%% Need to split combined image file to two files
941split_tx(none, _) -> {none, none};
942split_tx(OrigFileName, Dir0) ->
943    Dir = case filename:dirname(OrigFileName) of
944              "." -> Dir0;
945              Dir1 -> Dir1
946          end,
947    Ext = filename:extension(OrigFileName),
948    File = filename:basename(OrigFileName, Ext),
949    E3d = wings_image:image_read([{filename, OrigFileName}, {opt_dir, Dir0}]),
950    try
951        Metallic = e3d_image:channel(b,E3d),
952        MetFile = filename:join(Dir, File++"_met" ++ Ext),
953        wings_image:image_write([{filename, MetFile}, {image, Metallic}]),
954        Roughness = e3d_image:channel(g,E3d),
955        RoughFile = filename:join(Dir, File++"_rough" ++ Ext),
956        wings_image:image_write([{filename, RoughFile}, {image, Roughness}]),
957        {MetFile, RoughFile}
958    catch _:Reason:ST ->
959            ?dbg("Internal error: ~p ~p~n", [Reason, ST]),
960            {none, none}
961    end.
962
963mat_add_names([#{name:=_}=M|Ms], N, DefName) ->
964    [M|mat_add_names(Ms, N, DefName)];
965mat_add_names([M|Ms], N, DefName) ->
966    Name = unicode:characters_to_binary(io_lib:format("~ts_~w", [DefName,N])),
967    [M#{name=>Name}|mat_add_names(Ms, N+1, DefName)];
968mat_add_names([], _, _) ->
969    [].
970
971%%%%%%%%%
972
973get_index(I, Where, Map) ->
974    #{Where:=List} = Map,
975    lists:nth(1+I, List).
976