~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/percept/src/egd_render.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
24
24
 
25
25
-export([binary/1, binary/2]).
26
26
-compile(inline).
 
27
-compile(export_all).
27
28
 
28
29
-include("egd.hrl").
29
 
 
30
 
%% Definitions
31
 
%-type(line_span_data() :: {
32
 
%       Z       :: integer(), 
33
 
%       X0      :: integer(), 
34
 
%       X1      :: integer(), 
35
 
%       Color   :: rgba_float()}).
36
 
 
37
 
binary(Image) -> 
38
 
    binary(Image, opaque).
 
30
-define('DummyC',0).
 
31
 
 
32
binary(Image) -> binary(Image, opaque).
39
33
 
40
34
binary(Image, Type) ->
41
35
    parallel_binary(Image,Type).
74
68
scanlines({Y,Y}, _, _,_, Scanlines) -> Scanlines;
75
69
scanlines({Yi,Y}, Os, {_,_,Width,_}=LSB, Type, Scanlines) ->
76
70
    OLSs = parse_objects_on_line(Y-1, Width, Os),
77
 
    URLSs = resulting_line_spans(lists:reverse([LSB|OLSs]),Type, []),
 
71
    URLSs = resulting_line_spans([LSB|OLSs],Type),
78
72
 
79
73
    % FIXME: Can we keep the list sorted instead of sorting it?
80
74
    % sort descending
81
 
    RLSs = lists:sort(fun ({_,A,_,_}, {_,B,_,_}) -> if A < B -> false; true -> true end end, URLSs),
 
75
    RLSs = lists:reverse(URLSs),
82
76
 
83
77
    Scanline = resulting_scanline(RLSs,Width),
84
78
 
92
86
    Scanline = lists:duplicate(trunc(Xr - Xl + 1), <<R:8,G:8,B:8>>),
93
87
    resulting_scanline(RLSs, Width, [Scanline|Scanlines]).
94
88
 
95
 
%print_line_spans([]) -> io:format("~n"), ok;
96
 
%print_line_spans([{_,Xl,Xr,_}|LSs]) ->
97
 
%    io:format("[~p,~p]", [Xl,Xr]),
98
 
%    print_line_spans(LSs).
99
 
 
100
 
%check_binary(Bin, {_,_,W, _}) ->
101
 
%   Size = erlang:size(erlang:list_to_binary(Bin)),
102
 
%   ScanlineWidth = trunc(Size/3),
103
 
%   if 
104
 
%       ScanlineWidth =/= W + 1 ->
105
 
%           io:format("check_binary: Image width ~p vs. Scanline width ~p~n", [W+1,ScanlineWidth]),
106
 
%           throw(bad_binary);
107
 
%       true -> ok
108
 
%   end.
109
 
 
110
 
%check_line_spans([]) -> ok;
111
 
%check_line_spans([_]) -> ok; 
112
 
%check_line_spans([LSa, LSb | LSs]) ->
113
 
%    {_,Xal,_Xar,_} = LSa,
114
 
%    {_,_Xbl,Xbr,_} = LSb,
115
 
%    Overlap = do_lines_overlap(LSa,LSb),
116
 
%    LLSa = ls_length(LSa),
117
 
%    LLSb = ls_length(LSb),
118
 
%
119
 
%    if
120
 
%       LLSa < 0 ->
121
 
%           io:format("check_line_spans:~p ~n", [Overlap]),
122
 
%           debug_print_ls_states([{ls_left, LSa},{ls_right, LSb}]),
123
 
%           throw({bad_length, ls_left});
124
 
%       LLSb < 0 ->
125
 
%           io:format("check_line_spans:~p ~n", [Overlap]),
126
 
%           debug_print_ls_states([{ls_left, LSa},{ls_right, LSb}]),
127
 
%           throw({bad_length, ls_right});
128
 
%       Overlap =/= false ->
129
 
%           io:format("check_line_spans:~p ~n", [Overlap]),
130
 
%           debug_print_ls_states([{ls_left, LSa},{ls_right, LSb}]),
131
 
%           throw(overlap_error);
132
 
%       Xal - Xbr =/= 1 ->      
133
 
%           io:format("check_line_spans:~p~n", [Overlap]),
134
 
%           debug_print_ls_states([{ls_left, LSa},{ls_right, LSb}]),
135
 
%           throw(contiuation_error);
136
 
%       true -> check_line_spans([LSb|LSs])
137
 
%    end.
138
 
 
139
 
% resulting_line_spans
140
 
% In:
141
 
%       LineIntervals = [line_span_data()]
142
 
% Out:
143
 
%       LineIntervals
144
 
% Purpose:
145
 
%       Reduce line spans. This function handles the overlapping color spans on a line.
146
 
%       Måste troligen ha en sorterad lista med object, där översta objecte ligger först i stacken.
147
 
%       FÖr varje object måste man titta under och se vilka den överlappar och antingen,
148
 
%       1) simple
149
 
%               Ta bort de som täcks eller dela upp underliggande span från det överlappande.
150
 
%       2) alpha
151
 
%               todo...
152
 
 
153
 
resulting_line_spans([], _, MLSs) -> MLSs;
154
 
resulting_line_spans([LS|LSs], Type, MLSs) ->
155
 
    resulting_line_spans(LSs, Type, merge_line_spans(LS, MLSs, Type)).
156
 
 
157
 
 
158
 
% merge_line_spans
159
 
% In: merge_line_spans/3
160
 
%       CLS :: line_span_data(), current line span
161
 
%       MLSs :: [line_span_data()] (non overlapping, continious, unsorted)
162
 
%       Type :: alpha | opaque (render engine, color blending or not)
163
 
% In: merge_line_spans/3
164
 
%        CLSs :: [line_span_data()], current line spans
165
 
%       LMLSs :: [line_span_data()], left merged line spans (iter)
166
 
%       RMLSs :: [line_span_data()], right merged line spans (iter)
167
 
%       Type :: alpha | opaque (render engine, color blending or not)
168
 
% Out:
169
 
%       [line_span_data()] (non overlapping, continious, unsorted)
170
 
% Purpose:
171
 
%       Entwines color intervals with non overlapping color intervals,
172
 
%       Remember: CLS may split and become several CLSs (at least two) -> handle it.
173
 
 
174
 
% OK, here we go!
175
 
merge_line_spans(CLS, MLSs, Type) ->
176
 
    merge_line_spans([CLS], [], MLSs, Type).    % init
177
 
merge_line_spans(CLS, [], [], _Type) -> 
178
 
    CLS; % If it is the first line span of MLSs
179
 
merge_line_spans(CLSs, MLSs, [], _Type) -> 
180
 
    lists:flatten([CLSs|MLSs]);   % Here we have iterated through all MLSs; add CLSs.
181
 
merge_line_spans([], LMLSs, RMLSs, _Type) -> 
182
 
    lists:flatten([LMLSs|RMLSs]); % FIXME: optimize? all CLSs is shadowed (in opaque)
183
 
merge_line_spans(CLSs, LMLSs, [ILS|RMLSs], Type) -> 
184
 
    merge_line_spans([], CLSs, LMLSs, ILS, RMLSs, Type).
185
 
 
186
 
merge_line_spans(LCLSs, [], LMLSs, ILS, RMLSs, Type) -> 
187
 
    merge_line_spans(LCLSs, [ILS|LMLSs], RMLSs, Type);
188
 
merge_line_spans(LCLSs, [{Zc,Xcl,Xcr,Cc}=CLS|RCLSs], LMLSs, {_Zi,Xil,Xir,_Ci}=ILS, RMLSs, opaque) ->
189
 
    % Compare the current line span with the iterating one and see if
190
 
    % something shines through the overlapping object.
191
 
    % Think: How does each RMLS affect the CLS object if they overlap?
192
 
 
193
 
    %  ILS ------------ (upper)
194
 
    %  CLS ------------ (lower)
195
 
    case do_lines_overlap(CLS,ILS) of
196
 
        % the current line span is ...
197
 
        left_partial -> % cut it
198
 
            CLS0 = {Zc, Xcl, Xil - 1, Cc},
199
 
            merge_line_spans([CLS0|LCLSs], RCLSs, LMLSs, ILS, RMLSs, opaque);
200
 
        right_partial -> % cut it
201
 
            CLS0 = {Zc, Xir + 1, Xcr, Cc},
202
 
            merge_line_spans([CLS0|LCLSs], RCLSs, LMLSs, ILS, RMLSs, opaque);
203
 
        outspaced -> % split and cut it
204
 
            CLS0l = {Zc, Xcl, Xil - 1, Cc},
205
 
            CLS0r = {Zc, Xir + 1, Xcr, Cc},
206
 
            % Are we not supposed to put CLS0r in RCLSs to view it with other
207
 
            % MLSs? Seems to work now though...
208
 
            merge_line_spans([CLS0l, CLS0r | LCLSs], RCLSs, LMLSs, ILS, RMLSs, opaque);
209
 
        shadowed -> % drop it
210
 
            merge_line_spans(LCLSs, RCLSs, LMLSs, ILS, RMLSs, opaque);
211
 
        false -> 
212
 
            merge_line_spans([CLS|LCLSs], RCLSs, LMLSs, ILS, RMLSs, opaque) % do the same for the next CLS
213
 
    end;
214
 
merge_line_spans(LCLSs, [{Zc,Xcl,Xcr,Cc}=CLS|RCLSs], LMLSs, {Zi,Xil,Xir,Ci}=ILS, RMLSs, alpha) ->
215
 
    %  ILS ------------ (upper)
216
 
    %  CLS ------------ (lower)
217
 
    case do_lines_overlap(CLS,ILS) of
218
 
        % the current line span is ...
219
 
        left_partial -> % cut it
220
 
            if 
221
 
                Xir > Xcr ->
222
 
                CLS0 = {Zc, Xcl, Xil - 1, Cc},              % Cut current line span
223
 
                ALS  = {Zi, Xil, Xcr, alpha_blend(Ci,Cc)},  % alphalized part of iterating line span
224
 
                ILS0 = {Zi, Xcr + 1, Xir, Ci},              % Cut part of iterating line span
225
 
%               ok = check_line_spans([ILS0, ALS, CLS0]), 
226
 
                merge_line_spans([CLS0|LCLSs], RCLSs, LMLSs, ALS, [ILS0|RMLSs], alpha);
227
 
            true ->
228
 
                CLS0 = {Zc, Xcl, Xil - 1, Cc},              % Cut current line span
229
 
                ALS  = {Zi, Xil, Xcr, alpha_blend(Ci,Cc)},  % alphalized part of iterating line span
230
 
%               ok = check_line_spans([ALS, CLS0]), 
231
 
                merge_line_spans([CLS0|LCLSs], RCLSs, LMLSs, ALS, RMLSs, alpha)
232
 
            end;
233
 
        right_partial -> % cut it
234
 
            if 
235
 
            Xil < Xcl ->
236
 
                ILS0 = {Zi, Xil, Xcl - 1, Ci},              % Cut part of iterating line span
237
 
                ALS  = {Zi, Xcl, Xir, alpha_blend(Ci,Cc)},  % alphalized part of iterating line span
238
 
                CLS0 = {Zc, Xir + 1, Xcr, Cc},              % Cut current line span
239
 
%               ok = check_line_spans([CLS0, ALS, ILS0]), 
240
 
                merge_line_spans([CLS0|LCLSs], RCLSs, LMLSs, ILS0, [ALS|RMLSs],alpha);
241
 
            true ->
242
 
                ALS  = {Zi, Xcl, Xir, alpha_blend(Ci,Cc)},  % alphalized part of iterating line span
243
 
                CLS0 = {Zc, Xir + 1, Xcr, Cc},              % Cut current line span
244
 
%               ok = check_line_spans([CLS0, ALS]), 
245
 
                merge_line_spans([CLS0|LCLSs], RCLSs, LMLSs, ALS, RMLSs, alpha)
246
 
            end;
247
 
        outspaced -> % split and cut it
248
 
            CLS0l = {Zc, Xcl, Xil - 1, Cc},
249
 
            ALS   = {Zi, Xil, Xir, alpha_blend(Ci,Cc)},
250
 
            CLS0r = {Zc, Xir + 1, Xcr, Cc},
251
 
%           ok = check_line_spans([CLS0r, ALS, CLS0l]), 
252
 
            merge_line_spans([CLS0l,CLS0r | LCLSs], RCLSs, LMLSs, ALS, RMLSs, alpha);
253
 
        shadowed -> % dont drop it, alpha it
254
 
            if 
255
 
            Xil == Xcl , Xir == Xcr ->
256
 
                ALS = {Zi, Xil, Xir, alpha_blend(Ci,Cc)},
257
 
                merge_line_spans(LCLSs, RCLSs, LMLSs, ALS, RMLSs, alpha);
258
 
            Xil == Xcl ->
259
 
                ALS  = {Zi, Xil, Xcr, alpha_blend(Ci,Cc)},
260
 
                ILSr = {Zi, Xcr + 1, Xir, Ci},
261
 
%               ok = check_line_spans([ILSr, ALS]), 
262
 
                merge_line_spans(LCLSs, RCLSs, LMLSs, ALS, [ILSr|RMLSs], alpha);
263
 
            Xir == Xcr ->
264
 
                ILSl = {Zi, Xil, Xcl - 1, Ci},
265
 
                ALS   = {Zi, Xcl, Xcr, alpha_blend(Ci,Cc)},
266
 
%               ok = check_line_spans([ALS,ILSl]), 
267
 
                merge_line_spans(LCLSs, RCLSs, LMLSs, ILSl, [ALS|RMLSs], alpha);
268
 
            true ->
269
 
                ILS0l = {Zi, Xil, Xcl - 1, Ci},
270
 
                ALS   = {Zc, Xcl, Xcr, alpha_blend(Ci,Cc)},
271
 
                ILS0r = {Zi, Xcr + 1, Xir, Ci},
272
 
%               ok = check_line_spans([ILS0r, ALS, ILS0l]), 
273
 
                merge_line_spans(LCLSs, RCLSs, LMLSs, ILS0l, [ILS0r,ALS|RMLSs], alpha)
274
 
            end;
275
 
        false -> 
276
 
            merge_line_spans([CLS|LCLSs], RCLSs, LMLSs, ILS, RMLSs, alpha) % do the same for the next CLS
277
 
    end.
278
 
 
279
 
 
 
89
resulting_line_spans(LSs,Type) ->
 
90
    %% Build a list of "transitions" from left to right.
 
91
    Trans = line_spans_to_trans(LSs),
 
92
    %% Convert list of "transitions" to linespans.
 
93
        trans_to_line_spans(Trans,Type).
 
94
 
 
95
line_spans_to_trans(LSs) ->
 
96
    Trans = [],
 
97
    line_spans_to_trans(LSs,Trans,0).
 
98
 
 
99
line_spans_to_trans([],Db,_) ->
 
100
    lists:sort(Db);
 
101
line_spans_to_trans([{_,L,R,C}|LSs],Db,Z) ->
 
102
    line_spans_to_trans(LSs,[{{L,Z,start},C},{{R+1,Z,stop},C}|Db],Z+1).
 
103
 
 
104
trans_to_line_spans(Trans,Type) ->
 
105
    trans_to_line_spans(simplify_trans(Trans,Type,[],{0,0,0,0},[])).
 
106
 
 
107
trans_to_line_spans(SimpleTrans) ->
 
108
    trans_to_line_spans1(SimpleTrans,[]).
 
109
 
 
110
trans_to_line_spans1([],Spans) ->
 
111
    Spans;
 
112
trans_to_line_spans1([_],Spans) ->
 
113
    Spans;
 
114
trans_to_line_spans1([{L1,_},{L2,C2}|SimpleTrans],Spans) ->
 
115
    %% We are going backwards now...
 
116
    trans_to_line_spans1([{L2,C2}|SimpleTrans],[{?DummyC,L2,L1-1,C2}|Spans]).
 
117
 
 
118
simplify_trans([],_,_,_,Acc) ->
 
119
    Acc;
 
120
simplify_trans([{{L,_,_},_}|_] = Trans,Type,Layers,OldC,Acc) ->
 
121
    {NextTrans,RestTrans} =
 
122
        lists:splitwith(fun({{L1,_,_},_}) when L1 == L ->
 
123
                                true;
 
124
                           (_) ->
 
125
                                false
 
126
                        end, Trans),
 
127
    {C,NewLayers} = color(NextTrans,Layers,Type,OldC),
 
128
    case OldC of
 
129
        C -> %% No change in color, so transition unnecessary.
 
130
            simplify_trans(RestTrans,Type,NewLayers,OldC,Acc);
 
131
        _ ->
 
132
            simplify_trans(RestTrans,Type,NewLayers,C,[{L,C}|Acc])
 
133
    end.
 
134
 
 
135
color(Trans,Layers,Type,OldC) ->
 
136
    case modify_layers(Layers,Trans) of
 
137
        Layers ->
 
138
            {OldC,Layers};
 
139
        NewLayers ->
 
140
            {color(NewLayers,Type),NewLayers}
 
141
    end.
 
142
 
 
143
color([],_) -> {0,0,0,0};
 
144
color([{_,C}|_],opaque) -> C;    
 
145
color(Layers,alpha) -> color1({0,0,0,0},Layers).
 
146
 
 
147
color1(Color,[]) -> Color;
 
148
color1(Color,[{_,C}|Layers]) -> color1(blend(Color,C),Layers).
 
149
 
 
150
blend(C1,C2) -> alpha_blend(C1,C2).
 
151
 
 
152
modify_layers(Layers,[]) -> Layers;
 
153
modify_layers(Layers,[{{_,Z,Op},C}|Trans]) ->
 
154
    modify_layers(case Op of
 
155
                      start ->
 
156
                          add_layer(Layers,Z,C);
 
157
                      stop ->
 
158
                          remove_layer(Layers,Z,C)
 
159
                  end,
 
160
                  Trans).
 
161
 
 
162
add_layer([{Z1,_}=H|Layers],Z,C) when Z1 > Z ->
 
163
    [H|add_layer(Layers,Z,C)];
 
164
add_layer(Layers,Z,C) ->
 
165
    [{Z,C}|Layers].
 
166
 
 
167
remove_layer(Layers,Z,C) ->
 
168
    Layers -- [{Z,C}].
 
169
    
280
170
 
281
171
alpha_blend({R1,G1,B1,A1}, {R2,G2,B2,A2}) ->
282
172
  Beta = A2*(1 - A1),
286
176
  B = B1*A1 + B2*Beta,
287
177
  {R,G,B,A}.
288
178
 
289
 
do_lines_overlap({_,Xll, Xlr, _}, {_,Xul, Xur,_}) ->
290
 
    if 
291
 
        % Xul -------------- Xur
292
 
        % Xll -------------- Xlr
293
 
        Xlr < Xul -> false;
294
 
        Xll > Xur -> false;
295
 
        true ->
296
 
           if 
297
 
                % ---------
298
 
                %      ---------
299
 
                Xul =< Xll , Xur < Xlr -> right_partial;
300
 
 
301
 
                %     ------------
302
 
                % ------
303
 
                Xll < Xul , Xlr =< Xur -> left_partial;
304
 
                
305
 
                %    --------    
306
 
                % ---------------
307
 
                Xul > Xll , Xur < Xlr -> outspaced;
308
 
                
309
 
                % -------------
310
 
                %     ----
311
 
                Xul =< Xll , Xur >= Xlr -> shadowed;
312
 
                true ->
313
 
                    %debug_print_ls_states([{upper_ls, LSu}, {lower_ls, LSl}]),
314
 
                    throw(non_complete_closure)
315
 
           end
316
 
    end.
317
 
    
318
 
%ls_length({_,Xl,Xr,_}) -> Xr - Xl.
319
 
 
320
 
%debug_print_ls_states([]) -> ok;
321
 
%debug_print_ls_states([{Name, {_,Xl,Xr,_}=LS}|LSs]) ->
322
 
%    io:format("- ~p Xl=~p, Xr=~p -> L=~p~n", [Name, Xl,Xr,ls_length(LS)]),
323
 
%    debug_print_ls_states(LSs);
324
 
%debug_print_ls_states([{Name, Msg}|LSs]) -> 
325
 
%    io:format("- ~p -> ~p~n", [Name, Msg]),
326
 
%    debug_print_ls_states(LSs).
327
 
 
328
 
% parse_objects_on_line
329
 
% In: 
330
 
%       Y :: index of height
331
 
%       Width :: width of image
332
 
%       Objects :: [image_object()]
333
 
% Out:
334
 
%       LineData :: [ObjectLineData]
335
 
%       ObjectLineData :: {Z, X,  Length, RGB}
336
 
% Purpose:
337
 
%       Calculate the resulting length and color for each object.
338
 
 
339
179
parse_objects_on_line(Y, Width, Objects) ->
340
180
    parse_objects_on_line(Y, 1, Width, Objects, []).
341
181
parse_objects_on_line(_Y, _Z, _, [], Out) -> lists:flatten(Out);