1%%
2%%  e3d_image.erl --
3%%
4%%     Handle images (2D) and different file formats.
5%%
6%%  Copyright (c) 2001-2011 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
14-module(e3d_image).
15
16-include("e3d_image.hrl").
17
18%% Basic functionality
19
20-export([load/1, load/2,
21	 convert/2, convert/3, convert/4,
22	 save/2, save/3, save_bin/2, save_bin/3,
23         add_alpha/2,
24         channel/2, expand_channel/2, replace_channel/3, invert_channel/2,
25	 bytes_pp/1, pad_len/2, format_error/1,
26	 fix_outtype/3
27	]).
28
29%% Normal map handing
30-export([height2normal/2,
31	 height2normal/3,
32	 buildNormalMipmaps/1]).
33
34-compile({inline, [gray/3]}).
35-define(SINGLE_CHANNEL(T), (T =:= g8 orelse T =:= a8 orelse T =:= g32)).
36
37%% Func: load(FileName[, Options])
38%% Args: FileName = [Chars], Options = [Tagged Tuple]
39%% Rets: #e3d_image | {error, Reason}
40%% Desc: Loads an image file.
41%%       Default loads image with type/alignment/order set to what is
42%%       stored in the file.
43%%       Conversion between fileformats type/alignment/order can be done with
44%%       Options {type, Type} and/or {alignment, N} and/or {order, O} see e3d_image.hrl
45load(FileName) ->
46    load(FileName, []).
47load(FileName, Opts) when is_list(FileName), is_list(Opts) ->
48    Extension = file_extension(FileName),
49    Res = case ext_to_type(Extension) of
50	      tga -> e3d__tga:load(FileName, Opts);
51	      bmp -> e3d__bmp:load(FileName, Opts);
52	      tif -> e3d__tif:load(FileName, Opts);
53	      png -> e3d__png:load(FileName, Opts);
54              dds -> e3d__dds:load(FileName, Opts);
55	      _ -> return_error({not_supported,Extension})
56	  end,
57    fix_outtype(FileName, Res, Opts).
58
59%% Func: save(#e3d_image, Filename [, Opts])
60%% Rets: ok | {error, Reason}
61%% Desc: Saves image to file. Using extension to
62%%       know which fileformat to use.
63%%       Opts is a list of options.
64%%       Available options: compress
65%%        compress - compresses the file if it is possible/implemented (currently tif).
66save(Image, Filename) ->
67    save(Image, Filename, []).
68save(Image = #e3d_image{}, Filename, Opts) ->
69    Extension = file_extension(Filename),
70    case ext_to_type(Extension) of
71	tga -> e3d__tga:save(Image, Filename, Opts);
72	bmp -> e3d__bmp:save(Image, Filename, Opts);
73	tif -> e3d__tif:save(Image, Filename, Opts);
74	png -> e3d__png:save(Image, Filename, Opts);
75        dds -> e3d__dds:save(Image, Filename, Opts);
76	_ -> return_error({not_supported,Extension})
77    end.
78
79%% Func: save_bin(#e3d_image, Extension [, Opts])
80%% Rets: {ok,Binary} | {error, Reason}
81%% Desc: Saves image to binary. The Extension gives the
82%%       the file format to use.
83%%       Opts is a list of options.
84%%       Available options: compress
85%%        compress - compresses the file if it is possible/implemented (currently tif).
86save_bin(Image, Extension) ->
87    save_bin(Image, Extension, []).
88save_bin(#e3d_image{}=Image, Extension, Opts) ->
89    case ext_to_type(Extension) of
90	tga -> e3d__tga:save_bin(Image, Opts);
91	bmp -> e3d__bmp:save_bin(Image, Opts);
92	tif -> e3d__tif:save_bin(Image, Opts);
93	png -> e3d__png:save_bin(Image, Opts);
94	_ -> return_error({not_supported,Extension})
95    end.
96
97format_error({not_supported,Extension}) ->
98    io_lib:format("Files of type ~s are not supported", [Extension]);
99format_error(Other) ->
100    file:format_error(Other).
101
102%% Func: add_alpha(#e3d_image, Alpha : binary())
103%% Rets: #e3d_image | {error, Reason}
104%% Desc: Merges an alpha channel to rgb images
105add_alpha(I = #e3d_image{type=Type,bytes_pp=3,alignment=1,image=Data0}, Alpha) ->
106    Data = add_alpha(Data0, Alpha, <<>>),
107    I#e3d_image{bytes_pp=4, type=with_alpha(Type), image=Data}.
108%%    I#e3d_image{bytes_pp=1, type=g8, image=Alpha}.
109
110add_alpha(<<Col:24, Data/binary>>, <<A:8, Alpha/binary>>, Acc) ->
111    add_alpha(Data,Alpha, <<Acc/binary, Col:24, A:8>>);
112add_alpha(<<>>, <<>>, Acc) -> Acc.
113
114with_alpha(r8g8b8) -> r8g8b8a8;
115with_alpha(b8g8r8) -> b8g8r8a8.
116
117
118%% Func: channel(r|g|b|a, #e3d_image{})
119%% Rets: #e3d_image
120%% Desc: Make a gray image from a channel from Indata image
121
122-spec channel(r|g|b|a, #e3d_image{}) -> #e3d_image{}.
123channel(_Ch, #e3d_image{type=Single}=Img) when ?SINGLE_CHANNEL(Single) ->
124    Img;
125channel(r, #e3d_image{type=r8g8b8a8, bytes_pp=4, alignment=1, image=In}=Img) ->
126    Ch = << <<C:8>> || <<C:8,_:24>> <= In>>,
127    channel_img(Ch, "_r", Img);
128channel(r, #e3d_image{type=r8g8b8, bytes_pp=3, alignment=1, image=In}=Img) ->
129    Ch = << <<C:8>> || <<C:8,_:16>> <= In>>,
130    channel_img(Ch, "_r", Img);
131channel(g, #e3d_image{type=_, bytes_pp=4, alignment=1, image=In}=Img) ->
132    Ch = << <<C:8>> || <<_:8,C:8,_:16>> <= In>>,
133    channel_img(Ch, "_g", Img);
134channel(g, #e3d_image{type=_, bytes_pp=3, alignment=1, image=In}=Img) ->
135    Ch = << <<C:8>> || <<_:8,C:8,_:8>> <= In>>,
136    channel_img(Ch, "_g", Img);
137channel(b, #e3d_image{type=r8g8b8a8, bytes_pp=4, alignment=1, image=In}=Img) ->
138    Ch = << <<C:8>> || <<_:16,C:8,_:8>> <= In>>,
139    channel_img(Ch, "_b", Img);
140channel(b, #e3d_image{type=r8g8b8, bytes_pp=3, alignment=1, image=In}=Img) ->
141    Ch = << <<C:8>> || <<_:16,C:8>> <= In>>,
142    channel_img(Ch, "_b", Img);
143channel(a, #e3d_image{type=_, bytes_pp=4, alignment=1, image=In}=Img) ->
144    Ch = << <<C:8>> || <<_:24,C:8>> <= In>>,
145    channel_img(Ch, "_a", Img);
146%% b8g8r8a8..
147channel(b, #e3d_image{type=b8g8r8a8, bytes_pp=4, alignment=1, image=In}=Img) ->
148    Ch = << <<C:8>> || <<C:8,_:24>> <= In>>,
149    channel_img(Ch, "_b", Img);
150channel(b, #e3d_image{type=b8g8r8, bytes_pp=3, alignment=1, image=In}=Img) ->
151    Ch = << <<C:8>> || <<C:8,_:16>> <= In>>,
152    channel_img(Ch, "_b", Img);
153channel(r, #e3d_image{type=b8g8r8a8, bytes_pp=4, alignment=1, image=In}=Img) ->
154    Ch = << <<C:8>> || <<_:16,C:8,_:8>> <= In>>,
155    channel_img(Ch, "_r", Img);
156channel(r, #e3d_image{type=b8g8r8, bytes_pp=3, alignment=1, image=In}=Img) ->
157    Ch = << <<C:8>> || <<_:16,C:8>> <= In>>,
158    channel_img(Ch, "_r", Img).
159
160channel_img(Data, CN, #e3d_image{name=N, extra=X}=Img) ->
161    Name = filename:rootname(N) ++ CN,
162    Img#e3d_image{type=g8, bytes_pp=1,
163                  name=Name, filename=none,
164                  extra=lists:keydelete(mipmaps, 1, X),
165                  image=Data
166                 }.
167
168-spec expand_channel(Ch::r|g|b|a, #e3d_image{}) -> #e3d_image{}.
169%% Desc: Create a RGBA image from gray image Indata inserted to channel Ch
170%%       the other channels will be white
171expand_channel(r, #e3d_image{type=g8, image=In}=Img) ->
172    RGBA = << <<C:8, -1:24>> || <<C:8>> <= In>>,
173    Img#e3d_image{type=r8g8b8a8, bytes_pp=4, name=[], filename=none, extra=[], image=RGBA};
174expand_channel(g, #e3d_image{type=g8, image=In}=Img) ->
175    RGBA = << <<-1:8, C:8, -1:16>> || <<C:8>> <= In>>,
176    Img#e3d_image{type=r8g8b8a8, bytes_pp=4, name=[], filename=none, extra=[], image=RGBA};
177expand_channel(b, #e3d_image{type=g8, image=In}=Img) ->
178    RGBA = << <<-1:16, C:8, -1:8>> || <<C:8>> <= In>>,
179    Img#e3d_image{type=r8g8b8a8, bytes_pp=4, name=[], filename=none, extra=[], image=RGBA};
180expand_channel(a, #e3d_image{type=g8, image=In}=Img) ->
181    RGBA = << <<-1:24, C:8>> || <<C:8>> <= In>>,
182    Img#e3d_image{type=r8g8b8a8, bytes_pp=4, name=[], filename=none, extra=[], image=RGBA}.
183
184
185-spec replace_channel(Which::r|g|b|a, ChG8::#e3d_image{}, Orig::#e3d_image{})  -> #e3d_image{}.
186%% Desc replace 'Which' channel in 'Orig' with data from 'ChG8' image
187replace_channel(r, #e3d_image{type=g8,image=Ch}, #e3d_image{type=r8g8b8a8,image=Orig,extra=X}=Img) ->
188    Img#e3d_image{image=replace_r(Ch, Orig, <<>>), extra=lists:keydelete(mipmaps, 1, X)};
189replace_channel(g, #e3d_image{type=g8,image=Ch}, #e3d_image{type=r8g8b8a8,image=Orig,extra=X}=Img) ->
190    Img#e3d_image{image=replace_g(Ch, Orig, <<>>), extra=lists:keydelete(mipmaps, 1, X)};
191replace_channel(b, #e3d_image{type=g8,image=Ch}, #e3d_image{type=r8g8b8a8,image=Orig,extra=X}=Img) ->
192    Img#e3d_image{image=replace_b(Ch, Orig, <<>>), extra=lists:keydelete(mipmaps, 1, X)};
193replace_channel(a, #e3d_image{type=g8,image=Ch}, #e3d_image{type=r8g8b8a8,image=Orig,extra=X}=Img) ->
194    Img#e3d_image{image=replace_a(Ch, Orig, <<>>), extra=lists:keydelete(mipmaps, 1, X)}.
195
196replace_r(<<C:8, Ch/binary>>, <<_:8, GBA:24, Orig/binary>>, Acc) ->
197    replace_r(Ch, Orig, <<Acc/binary, C:8, GBA:24>>);
198replace_r(<<>>, <<>>, Acc) -> Acc.
199
200replace_g(<<C:8, Ch/binary>>, <<R:8, _:8, BA:16, Orig/binary>>, Acc) ->
201    replace_g(Ch, Orig, <<Acc/binary, R:8, C:8, BA:16>>);
202replace_g(<<>>, <<>>, Acc) -> Acc.
203
204replace_b(<<C:8, Ch/binary>>, <<RG:16, _:8, A:8, Orig/binary>>, Acc) ->
205    replace_b(Ch, Orig, <<Acc/binary, RG:16, C:8, A:8>>);
206replace_b(<<>>, <<>>, Acc) -> Acc.
207
208replace_a(<<C:8, Ch/binary>>, <<RGB:24, _:8, Orig/binary>>, Acc) ->
209    replace_a(Ch, Orig, <<Acc/binary, RGB:24, C:8>>);
210replace_a(<<>>, <<>>, Acc) -> Acc.
211
212
213-spec invert_channel(Ch::r|g|b|a, #e3d_image{}) -> #e3d_image{}.
214%% Desc: Create a copy of image with Ch channel inverted
215invert_channel(_, #e3d_image{type=G8orA8, image=Image}=Img)
216  when G8orA8 =:= g8; G8orA8 =:= a8 ->
217    Bin = << << (255-C):8 >> || <<C:8>> <= Image >>,
218    Img#e3d_image{image=Bin, filename=none};
219invert_channel(r, #e3d_image{type=r8g8b8, image=Image}=Img) ->
220    Bin = << << (255-C):8, P:16 >> || <<C:8, P:16>> <= Image >>,
221    Img#e3d_image{image=Bin, filename=none};
222invert_channel(g, #e3d_image{type=Type, image=Image}=Img)
223  when Type =:= r8g8b8; Type =:= b8g8r8 ->
224    Bin = << << Pre:8, (255-C):8, P:8 >> || <<Pre:8, C:8, P:8>> <= Image >>,
225    Img#e3d_image{image=Bin, filename=none};
226invert_channel(b, #e3d_image{type=r8g8b8, image=Image}=Img) ->
227    Bin = << << P:16, (255-C):8 >> || <<P:16, C:8>> <= Image >>,
228    Img#e3d_image{image=Bin, filename=none};
229invert_channel(r, #e3d_image{type=r8g8b8a8, image=Image}=Img) ->
230    Bin = << << (255-C):8, P:24 >> || <<C:8, P:24>> <= Image >>,
231    Img#e3d_image{image=Bin, filename=none};
232invert_channel(g, #e3d_image{type=Type, image=Image}=Img)
233  when Type =:= r8g8b8a8; Type =:= b8g8r8a8 ->
234    Bin = << << Pre:8, (255-C):8, P:16 >> || <<Pre:8, C:8, P:16>> <= Image >>,
235    Img#e3d_image{image=Bin, filename=none};
236invert_channel(b, #e3d_image{type=r8g8b8a8, image=Image}=Img) ->
237    Bin = << << Pre:16, (255-C):8, P:8 >> || <<Pre:16, C:8, P:8>> <= Image >>,
238    Img#e3d_image{image=Bin, filename=none};
239invert_channel(a, #e3d_image{type=WA, image=Image}=Img)
240  when WA =:= r8g8b8a8; WA =:= b8g8r8a8 ->
241    Bin = << << Pre:16, (255-C):8, P:8 >> || <<Pre:16, C:8, P:8>> <= Image >>,
242    Img#e3d_image{image=Bin, filename=none};
243invert_channel(b, #e3d_image{type=b8g8r8, image=Image}=Img) ->
244    Bin = << << (255-C):8, P:16 >> || <<C:8, P:16>> <= Image >>,
245    Img#e3d_image{image=Bin, filename=none};
246invert_channel(r, #e3d_image{type=b8g8r8, image=Image}=Img) ->
247    Bin = << << P:16, (255-C):8 >> || <<P:16, C:8>> <= Image >>,
248    Img#e3d_image{image=Bin, filename=none};
249invert_channel(b, #e3d_image{type=b8g8r8a8, image=Image}=Img) ->
250    Bin = << << (255-C):8, P:24 >> || <<C:8, P:24>> <= Image >>,
251    Img#e3d_image{image=Bin, filename=none};
252invert_channel(r, #e3d_image{type=b8g8r8a8, image=Image}=Img) ->
253    Bin = << << Pre:16, (255-C):8, P:8 >> || <<Pre:16, C:8, P:8>> <= Image >>,
254    Img#e3d_image{image=Bin, filename=none}.
255
256%% Func: convert(#e3d_image, NewType [,NewAlignment [,NewOrder ]])
257%% Rets: #e3d_image | {error, Reason}
258%% Desc: Converts an image to new type optionally NewAlignment and NewOrder
259convert(In, ToType) when is_atom(ToType) ->
260    convert(In, ToType, In#e3d_image.alignment, In#e3d_image.order).
261
262convert(In, ToType, NewAlignment) when is_atom(ToType) ->
263    convert(In, ToType, NewAlignment, In#e3d_image.order).
264
265convert(#e3d_image{type=Type, alignment=Al,order=O}=In, Type, Al, O) ->
266    In;
267convert(#e3d_image{width=W, bytes_pp=Bpp, alignment=Al,
268                   type=FromType, order=FromOrder, image=Bin, extra=Extra0}=In,
269        ToType, ToAlm, ToOrder) ->
270    try
271	Convert = col_conv(FromType, ToType),
272        ToBpp = if Convert =:= keep -> Bpp; true -> bytes_pp(ToType) end,
273	Reverse = order_conv(FromOrder, ToOrder),
274	New = map_rows(Bin, W, Bpp, Al, Convert, Reverse, ToBpp, ToAlm),
275        DoConvert = fun(EBin, Width) ->
276                            map_rows(EBin, Width, Bpp, Al, Convert, Reverse, ToBpp, ToAlm)
277                    end,
278        Extra = convert_extra(DoConvert, W, Extra0),
279	In#e3d_image{image=New,type=ToType,
280		     bytes_pp=ToBpp,
281		     alignment=ToAlm,order=ToOrder, extra=Extra}
282    catch Error ->
283	    Error
284    end.
285
286convert_extra(Convert, W, Extra0) ->
287    MMs0 = proplists:get_value(mipmaps, Extra0, undefined),
288    CMs0 = proplists:get_value(cubemaps, Extra0, undefined),
289    Extra1 = case MMs0 of
290                 undefined -> Extra0;
291                 _ ->
292                     E1 = proplists:delete(mipmaps, Extra0),
293                     MMs = convert_mipmaps(Convert, MMs0),
294                     [{mipmaps, MMs}|E1]
295             end,
296    case CMs0 of
297        undefined -> Extra1;
298        _ ->
299            E2 = proplists:delete(cubemaps, Extra1),
300            CMs = convert_cubemaps(Convert, W, CMs0),
301            [{cubemaps, CMs}|E2]
302    end.
303
304convert_mipmaps(Convert, MMs) ->
305    [{Convert(Img, W), W, H, Level} || {Img,W,H,Level} <- MMs].
306
307convert_cubemaps(Convert, W, CMs) ->
308    [CM#{tx:=Convert(Img, W), mipmaps:=convert_mipmaps(Convert, MMs)}
309     || CM = #{tx:=Img, mipmaps:=MMs} <- CMs].
310
311ext_to_type(".tga") -> tga;
312ext_to_type(".bmp") -> bmp;
313ext_to_type(".png") -> png;
314ext_to_type(".tif") -> tif;
315ext_to_type(".tiff") -> tif;
316ext_to_type(".dds") -> dds;
317ext_to_type(_) -> unknown.
318
319%% Func: pad_len(RowLength (in bytes), Alignment)
320%% Rets: integer()
321%% Desc: Get the number of bytes each row is padded with
322pad_len(RL, Align) ->
323    case RL rem Align of
324	0 -> 0;
325	Rem -> Align - Rem
326    end.
327
328%% Func: bytes_pp(Type)
329%% Rets: integer()
330%% Desc: Get the number of bytes per pixel for type Type
331bytes_pp(a8) -> 1;
332bytes_pp(g8) -> 1;
333bytes_pp(r8g8) -> 2;
334bytes_pp(r8g8b8) -> 3;
335bytes_pp(b8g8r8) -> 3;
336bytes_pp(r8g8b8a8) -> 4;
337bytes_pp(b8g8r8a8) -> 4;
338bytes_pp(#e3d_image{bytes_pp = Bpp}) ->
339    Bpp.
340
341
342%% Func: height2normal(Image, Scale, GenMipMap)
343%% Args: Image = #e3d_image, Scale = number, GenMipMap == Bool
344%% Rets: #e3d_image{}  | {error, Reason}
345%% Desc: Filter and build a normalmap from a heightmap.
346%%       assumes the heightmap is greyscale.
347height2normal(Image, Options, GenMipMap) ->
348    NM  = height2normal(Image, Options),
349    case GenMipMap of
350        true  -> NM#e3d_image{extra=[{mipmaps,buildNormalMipmaps(NM)}]};
351        false -> NM
352    end.
353
354%% Func: height2normal(Image, Params)
355%% Args: Image = #e3d_image, Params = #{scale::float(), inv_x::boolean(), inv_y::boolean()}
356%% Rets: #e3d_image | {error, Reason}
357%% Desc: Filter and build a normalmap from a heightmap.
358%%       the heightmap can be a greyscale or colored image.
359height2normal(Old, Opts) ->
360    InvX = maps:get(inv_x, Opts, false),
361    InvY = maps:get(inv_y, Opts, false),
362    Scale  = maps:get(scale, Opts, 4.0),
363    ScaleXY = {Scale*inv_multiply(InvX), Scale*inv_multiply(InvY)},
364    #e3d_image{width=W,height=H,image=I,name=Name} = e3d_image:convert(Old, g8, 1),
365    New = bumps(H, W, I, ScaleXY),
366    Old#e3d_image{bytes_pp=3,type=r8g8b8, image=New, alignment=1,
367		  filename=none, name=filename:rootname(Name)++"_normal"}.
368
369bumps(Rows, Cols, Bin, Scale) ->
370    Offset = (Rows-2)*Cols,
371    <<RowFirst:Cols/binary, Bin0/binary>> = Bin,
372    <<_:Offset/binary,RowLast/binary>> = Bin0,
373    bumps_0(Cols, <<RowLast/binary,Bin/binary,RowFirst/binary>>, Scale, <<>>).
374
375bumps_0(Cols, Bin0, _, Acc) when size(Bin0) =:= Cols*2 -> Acc;
376bumps_0(Cols, Bin0, Scale, Acc) ->
377    Offset = Cols -2,
378    <<RowUp:Cols/binary,Bin/binary>> = Bin0,
379    <<Row:Cols/binary,RowDown:Cols/binary,_/binary>> = Bin,
380    <<Ci,_:Offset/binary,Cf>> = Row,
381    Acc0 = bumpmapRow(<<Cf,Row/binary,Ci>>, RowUp, RowDown, Scale, <<>>),
382    bumps_0(Cols, Bin, Scale, <<Acc/binary,Acc0/binary>>).
383
384bumpmapRow(<<Cl,Row/binary>>, <<Ru,RowUp/binary>>, <<Rd,RowDown/binary>>, Scale, Acc) ->
385    <<_, Cr, _/binary>> = Row,
386    {R,G,B} = bumpmapRGB(Cl, Cr, Ru, Rd, Scale),
387    bumpmapRow(Row, RowUp, RowDown, Scale, <<Acc/binary, R:8, G:8, B:8>>);
388bumpmapRow(_, <<>>, <<>>, _, NormalRow) -> NormalRow.
389
390bumpmapRGB(Cl, Cr, Ru, Rd, {MulX,MulY}) ->
391    Z1 = (Cr-Cl)*-1.0*MulX,
392    Z2 = (Ru-Rd)*MulY,
393    {Nr,Ng,Nb} = e3d_vec:norm({Z1, Z2, 255.0}),
394    {R0,G0,B0} = {(Nr+1)*0.5,(Ng+1)*0.5,(Nb+1)*0.5},
395    {round(R0 *255), round(G0 *255), round(B0 *255)}.
396
397inv_multiply(true) -> -1.0;
398inv_multiply(_) -> 1.0.
399
400%  buildNormalMipmaps(Image) -> [{Bin,W,H,Level}]
401%  Generates all mipmap levels from an Normalmap
402%% Perfect for
403%% gl:texImage2D(?GL_TEXTURE_2D, Level, ?GL_RGB8, HW, HH, 0,
404%%		    ?GL_RGB, ?GL_UNSIGNED_BYTE, Down);
405
406buildNormalMipmaps(#e3d_image{width=W,height=H,image=Bin,
407			      alignment=1, type=r8g8b8}) ->
408    buildNormalMipmaps(1, W, H, Bin);
409buildNormalMipmaps(Image) ->
410    buildNormalMipmaps(convert(Image,r8g8b8,1)).
411buildNormalMipmaps(Level, W, H, Bin) ->
412    %% Half width and height but not beyond one.
413    HW = case W div 2 of Tw when Tw == 0 -> 1; Tw -> Tw end,
414    HH = case H div 2 of Th when Th == 0 -> 1; Th -> Th end,
415    Down = downSampleNormalMap(W,H,Bin),
416    if (HW>1) or (HH>1) ->
417	    [{Down,HW,HH,Level} | buildNormalMipmaps(Level+1, HW,HH,Down)];
418       true ->
419	    [{Down,HW,HH,Level}]
420    end.
421
422-define(N2RGB(XX), round(128.0+127.0*(XX))).
423downSampleNormalMap(W,H,Bin) ->
424    I = if H == 1 -> 0; true -> H-2 end,
425    J = if W == 1 -> 0; true -> W-2 end,
426    downSampleNormalMap(I,J,W,H,Bin,[]).
427
428downSampleNormalMap(I,_J,_W,_H,_Bin,Acc) when I < 0 ->
429    list_to_binary(Acc);
430downSampleNormalMap(I,J0,W,H,Bin,Acc) when J0 < 0 ->
431    J = if W == 1 -> 0; true -> W-2 end,
432    downSampleNormalMap(I-2,J,W,H,Bin,Acc);
433downSampleNormalMap(I,J,W,H,Bin,Acc) ->
434    OneOver127 = 1.0/127.0,
435    %% OneOver255 = 1.0/255.0,
436
437    %% The "%w2" and "%h2" modulo arithmetic makes sure that
438    %% Nx1 and 1xN normal map levels are handled correctly.
439
440    %% Fetch the four vectors (and magnitude) to be downsampled.
441
442    %% Don't have 32bits normal-maps for yet..
443
444    %% M0=OneOver255*M00, M1=OneOver255*M10,
445    %% M2=OneOver255*M20, M3=OneOver255*M30,
446
447    P0 = (I*W+J)*3,
448    P1 = ((I*W+((J+1) rem W))*3),
449    P2 = ((((I+1) rem H)*W+J)*3),
450    P3 = ((((I+1) rem H)*W+((J+1) rem W))*3),
451    <<_:P0/binary, X0,Y0,Z0, _/binary>> = Bin,
452    <<_:P1/binary, X1,Y1,Z1, _/binary>> = Bin,
453    <<_:P2/binary, X2,Y2,Z2, _/binary>> = Bin,
454    <<_:P3/binary, X3,Y3,Z3, _/binary>> = Bin,
455
456    M0=1.0,M1=1.0,M2=1.0,M3=1.0,
457
458    %% Sum 2x2 footprint of red component scaled
459    %% back to [-1,1] floating point range.
460    X = M0*(OneOver127*float(X0)-1.0)+M1*(OneOver127*float(X1)-1.0)+
461	M2*(OneOver127*float(X2)-1.0)+M3*(OneOver127*float(X3)-1.0),
462
463    %%  Sum 2x2 footprint of green component scaled back to [-1,1]
464    %%  floating point range.
465    Y = M0*(OneOver127*float(Y0)-1.0)+M1*(OneOver127*float(Y1)-1.0)+
466	M2*(OneOver127*float(Y2)-1.0)+M3*(OneOver127*float(Y3)-1.0),
467
468    %% Sum 2x2 footprint of blue component scaled back to [-1,1]
469    %% floating point range.
470    Z = M0*(OneOver127*float(Z0)-1.0)+M1*(OneOver127*float(Z1)-1.0)+
471	M2*(OneOver127*float(Z2)-1.0)+M3*(OneOver127*float(Z3)-1.0),
472
473    L = math:sqrt(X*X+Y*Y+Z*Z),
474    if L > 0.00005 ->
475%	    SL = L / 4,
476% 	    M = if SL > 1.0 -> 255;
477% 		   true -> 255*SL
478% 		end,
479	    %% Normalize the vector to unit length and convert to RGB
480	    InvL = 1.0/L,
481	    New = [?N2RGB(X*InvL),?N2RGB(Y*InvL),?N2RGB(Z*InvL)], %M],
482	    downSampleNormalMap(I,J-2,W,H,Bin, [New|Acc]);
483       true ->
484	    %% Ugh, a zero length vector.  Avoid division by zero and just
485	    %% use the unpeturbed normal (0,0,1).
486	    New = [128,128,255], %,0],
487	    downSampleNormalMap(I,J-2,W,H,Bin, [New|Acc])
488    end.
489
490%% Helpers
491file_extension(FileName) ->
492    lowercase(filename:extension(FileName)).
493
494lowercase([H|R]) when H >= $A, H =< $Z ->
495    [H + $a - $A | lowercase(R)];
496lowercase([H|R]) ->
497    [H | lowercase(R)];
498lowercase([]) ->
499    [].
500
501fix_outtype(File, Res = #e3d_image{}, Opts) ->
502    Type =
503	case lists:keysearch(type, 1, Opts) of
504	    {value, {type, T}} -> T;
505	    false -> Res#e3d_image.type
506	end,
507    Alignment =
508	case lists:keysearch(alignment, 1, Opts) of
509	    {value, {alignment, A}} -> A;
510	    false -> Res#e3d_image.alignment
511	end,
512    Order =
513	case lists:keysearch(order, 1, Opts) of
514	    {value, {order, O}} -> O;
515	    false -> Res#e3d_image.order
516	end,
517    convert(Res#e3d_image{filename=File}, Type, Alignment, Order);
518fix_outtype(_, Res, _) ->  %% Propagate Error Case
519    Res.
520
521map_rows(Bin, _, _, 1, keep, {false,false}, _, 1) ->
522    Bin;
523map_rows(Bin, _, _, 1, Convert, {false,false}, _, 1) ->
524    Convert(Bin); %% No need to handle rows specifically
525map_rows(Bin, W, BPP, FromAlm, Convert, {RRs, RCs}, ToBpp, ToAlm) ->
526    RowL = W*BPP,
527    FoldRow = row_conv(Convert, ToBpp, RCs, make_pad(W, ToBpp, ToAlm)),
528    map_bin(Bin, RowL, pad_len(RowL, FromAlm), FoldRow, RRs).
529
530col_conv(Type, Type) -> keep;
531col_conv(g8, Type) ->
532    case bytes_pp(Type) of
533	1 -> keep;
534	3 -> fun(Bin) -> << <<G:8,G:8,G:8>> || <<G:8>> <= Bin >> end;
535	4 -> fun(Bin) -> << <<G:8,G:8,G:8,255:8>> || <<G:8>>  <= Bin >> end
536    end;
537col_conv(a8, Type) ->
538    case bytes_pp(Type) of
539	1 -> keep;
540	3 -> fun(Bin) -> << <<G:8,G:8,G:8>> || <<G:8>> <= Bin >> end;
541	4 -> fun(Bin) -> << <<255:8,255:8,255:8,A:8>> || <<A:8>> <= Bin >> end
542    end;
543
544col_conv(r8g8b8, r8g8b8a8) -> fun(Bin) -> << <<RGB:24,255:8>> || <<RGB:24>> <= Bin >> end;
545col_conv(r8g8b8a8, r8g8b8) -> fun(Bin) -> << <<RGB:24>> || <<RGB:24,_:8>> <= Bin >> end;
546col_conv(b8g8r8, b8g8r8a8) -> fun(Bin) -> << <<RGB:24,255:8>> || <<RGB:24>> <= Bin >> end;
547col_conv(b8g8r8a8, b8g8r8) -> fun(Bin) -> << <<RGB:24>> || <<RGB:24,_:8>> <= Bin >> end;
548col_conv(r8g8b8, g8)       -> fun(Bin) -> << <<(gray(R,G,B)):8>> || <<R:8,G:8,B:8>> <= Bin >> end;
549col_conv(r8g8b8a8, g8)     -> fun(Bin) -> << <<(gray(R,G,B)):8>> || <<R:8,G:8,B:8,_:8>> <= Bin >> end;
550col_conv(b8g8r8, g8)       -> fun(Bin) -> << <<(gray(R,G,B)):8>> || <<B:8,G:8,R:8>> <= Bin >> end;
551col_conv(b8g8r8a8, g8)     -> fun(Bin) -> << <<(gray(R,G,B)):8>> || <<B:8,G:8,R:8,_:8>> <= Bin >> end;
552
553col_conv(In, Out) ->
554    InSz  = bytes_pp(In),
555    OutSz = bytes_pp(Out),
556    if InSz =:= OutSz, InSz =:= 3 ->
557	    fun(Bin) -> << <<R:8,G:8,B:8>> || <<B:8,G:8,R:8>> <= Bin >> end;
558       InSz =:= OutSz, InSz =:= 4 ->
559	    fun(Bin) -> << <<R:8,G:8,B:8,A:8>> || <<B:8,G:8,R:8,A:8>> <= Bin >> end;
560       InSz =:= 3, OutSz =:= 4 ->
561	    fun(Bin) -> << <<R:8,G:8,B:8,255:8>> || <<B:8,G:8,R:8>> <= Bin >> end;
562       InSz =:= 4, OutSz =:= 3 ->
563	    fun(Bin) -> << <<R:8,G:8,B:8>> || <<B:8,G:8,R:8, _:8>> <= Bin >> end;
564       InSz =:= 4, Out =:= a8  ->
565	    fun(Bin) -> << <<A:8>> || <<_:8,_:8,_:8, A:8>> <= Bin >> end;
566       InSz =:= 3, Out =:= a8 -> col_conv(In, g8);
567       true ->
568	    {error, {not_supported,conversion,In,Out}}
569    end.
570
571gray(G,G,G) -> G;
572gray(R,G,B) when B>G,B>R ->
573    (R+G+B) div 3; %% The formula below becomes very dark for "blueish" images
574gray(R,G,B) ->
575    round(0.2126*R + 0.7152*G + 0.0722*B).
576
577%% row_conv(ColorConvert, ReverseColumns, RowPad)
578row_conv(keep, Sz, Reverse, Pad) ->  %% Keep rows add padding
579    fun(Row) ->  reverse_and_pad(Row, Sz, Reverse, Pad) end;
580row_conv(Convert, Sz, Reverse, Pad) when is_function(Convert, 1) ->
581    fun(InRow) ->
582	    reverse_and_pad(Convert(InRow),Sz,Reverse,Pad)
583    end.
584
585reverse_and_pad(Bin, _, false, <<>>) -> Bin;
586reverse_and_pad(Bin, _, false, Pad)  -> <<Bin/binary, Pad/binary>>;
587reverse_and_pad(Bin, 1, true, Pad) -> reverse_and_pad(Bin, 1, false, Pad);
588reverse_and_pad(Bin0, Sz, true, Pad) ->
589    %% Unoptimized but should happen really rare..
590    Bin = bin_reverse(Bin0, Sz, 0, fun(C) -> C end, []),
591    <<Bin/binary, Pad/binary>>.
592
593map_bin(InBin, InSz, InSkip, Convert, Reverse) ->
594    case Reverse of
595	false ->
596	    << <<(Convert(Cut))/binary>> || <<Cut:InSz/binary, _:InSkip/binary>> <= InBin >>;
597	true ->
598	    bin_reverse(InBin, InSz, InSkip, Convert, [])
599    end.
600
601bin_reverse(<<>>, _InSz, _InSkip, _Convert, Acc) -> list_to_binary(Acc);
602bin_reverse(Bin, InSz, InSkip, Convert, Acc) ->
603    <<Col:InSz/binary, _:InSkip/binary, Rest/binary>> = Bin,
604    bin_reverse(Rest, InSz, InSkip, Convert, [Convert(Col)|Acc]).
605
606make_pad(W, ToBpp, ToAlm) ->
607    NewRowLength  = W * ToBpp,
608    NewPadLength = 8*pad_len(NewRowLength, ToAlm),
609    <<0:NewPadLength>>.
610
611order_conv(Order, Order) -> {false, false};   %% {SwapColumns, SwapRows}
612order_conv(lower_left, upper_right) -> {true,true};
613order_conv(upper_right, lower_left) -> {true,true};
614order_conv(lower_right, upper_left) -> {true,true};
615order_conv(upper_left, lower_right) -> {true,true};
616
617order_conv(lower_left, upper_left) ->  {true,false};
618order_conv(upper_right, lower_right) ->{true,false};
619order_conv(lower_right, upper_right) ->{true,false};
620order_conv(upper_left, lower_left) ->  {true,false};
621
622order_conv(lower_left,  lower_right) -> {false,true};
623order_conv(upper_right, upper_left) ->  {false,true};
624order_conv(lower_right, lower_left) ->  {false,true};
625order_conv(upper_left,  upper_right) -> {false,true}.
626
627return_error(Reason) ->
628    {error, {none, ?MODULE, Reason}}.
629