~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

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

  • Committer: Elliot Murphy
  • Date: 2010-06-08 03:55:44 UTC
  • mfrom: (3.5.6 squeeze)
  • Revision ID: elliot@elliotmurphy.com-20100608035544-dd8zh2swk7jr5rz2
* Merge with Debian unstable; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
* Added missing symlinks to /usr/include for a few new header files.
* Fixed generation of ${erlang-base:Depends} and ${erlang-x11:Depends}
  substitution variables.
* Added a fix for a re:compile/2 crash on a long regular expression.
* Changed urgency to medium as the change fixes a security bug.
* Manpages in section 1 are needed even if only arch-dependent packages are
  built. So, re-enabled them.
* Fixed HiPE architecture recognition for powerpc Debian architecture.
* Moved xsltproc and fop to build-depends-indep and do not build
  documentation if only architecture-specific packages are built.
* Refreshed all patches.
* Made Emacs look in man5 and man7 for Erlang manpages and added code
  skeleton files to erlang-mode package.
* New upstream release.
* Moved manpages from incorrect sections 4 and 6 to correct 5 and 7
  (closes: #498492).
* Made manpages regexp in Emacs mode match only 3erl pages in section 3.
* Removed docb_gen script which is no longer needed to build manpages.
* Added erlang-doc package which contains documentation in HTML and PDF
  formats. This package replaces erlang-doc-html package and it's easier
  to synchronize it with the main Erlang packages as it's built from
  a single source package (closes: #558451).
* Removed RPATH from ssl and crypto application binaries as required by
  Debian policy.
* Added libwxgtk2.4-dev and libwxgtk2.6-dev to build conflicts.
* Added a few dpendencies for erlang-dialyzer, erlang-et, erlang-observer
  and erlang-examples packages which now call functions from more modules
  than in 1:13.b.3.
* Added a workaround which disables vfork() for hppa architecture
  (closes: #562218).
* Strictened check for JDK 1.5 adding a call to String(int[], int, int)
  because GCJ 4.4 doesn't implement it and OpenJDK isn't available for all
  architectures.
* Fixed erlang-manpages package section.
* Made erlang-depends add only substvars which are requested in
  debian/control file. This minimizes number of warnings from dh_gencontrol.
  Also, improved descriptions of the functions in erlang-depends escript.
* Added erlang-erl-docgen package to erlang-nox dependencies.
* Made dummy packages erlang-nox and erlang-x11 architecture all.
* Cleaned up working with custom substitution variables in debian/rules.
* Reorganized debian/rules to ensure that manpages arent built twice, and
  aren't built at all if only architecture-dependent packages are requested.
* Fixed project links in README.Debian.
* Added a new package erlang-jinterface which provides tools for
  communication of Java programs with Erlang processes. This adds build
  depandency on default-jdk and as a result enables Java module for IDL
  compiler.
* Bumped standards version to 3.8.4.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2008-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
 
19
19
%% 
29
29
-include("egd.hrl").
30
30
-define('DummyC',0).
31
31
 
32
 
binary(Image) -> binary(Image, opaque).
 
32
binary(Image) ->
 
33
    binary(Image, opaque).
33
34
 
34
35
binary(Image, Type) ->
35
36
    parallel_binary(precompile(Image),Type).
36
37
 
37
38
parallel_binary(Image = #image{ height = Height },Type) ->
38
 
    case lists:min([erlang:system_info(schedulers), Height]) of
 
39
    case erlang:min(erlang:system_info(schedulers), Height) of
39
40
        1 ->
40
41
            % if the height or the number of schedulers is 1
41
42
            % do the scanlines in this process.
42
43
            W  = Image#image.width,
43
44
            Bg = Image#image.background,
44
45
            Os = Image#image.objects,
45
 
            erlang:list_to_binary(lists:map(fun
46
 
                (Y) -> scanline(Y, Os, {0,0,W - 1, Bg}, Type)
47
 
            end, lists:seq(1, Height)));
 
46
            erlang:list_to_binary([scanline(Y, Os, {0,0,W - 1, Bg}, Type)
 
47
                                   || Y <- lists:seq(1, Height)]);
48
48
        Np ->
49
49
            Pids    = start_workers(Np, Type),
50
50
            Handler = handle_workers(Height, Pids),
54
54
            Res
55
55
    end.
56
56
 
57
 
start_workers(Np, Type) -> start_workers(Np, Type, []).
 
57
start_workers(Np, Type) ->
 
58
    start_workers(Np, Type, []).
 
59
 
58
60
start_workers( 0,    _, Pids) -> Pids;
59
61
start_workers(Np, Type, Pids) when Np > 0 -> 
60
62
    start_workers(Np - 1, Type, [spawn_link(fun() -> worker(Type) end)|Pids]).
90
92
    Handler ! {Pid, scan_complete},
91
93
    init_workers(Image, Handler, Pids).
92
94
 
93
 
handle_workers(H, Pids) -> spawn_link(fun() -> handle_workers(H, H, length(Pids)) end).
 
95
handle_workers(H, Pids) ->
 
96
    spawn_link(fun() -> handle_workers(H, H, length(Pids)) end).
 
97
 
94
98
handle_workers(_, 0, _) -> ok;
95
99
handle_workers(H, Hi, Np) when H > 0 ->
96
100
    N = trunc(Hi/(2*Np)),
110
114
    Pid ! {self(), done},
111
115
    finish_workers(Pids).
112
116
 
113
 
receive_binaries(H) -> receive_binaries(H, []).
 
117
receive_binaries(H) ->
 
118
    receive_binaries(H, []).
 
119
 
114
120
receive_binaries(0, Bins) -> erlang:list_to_binary(Bins);
115
121
receive_binaries(H, Bins) when H > 0 ->
116
122
    receive
118
124
            receive_binaries(H - 1, [Bin|Bins])
119
125
    end.
120
126
 
121
 
 
122
127
scanline(Y, Os, {_,_,Width,_}=LSB, Type) ->
123
 
    OLSs  = parse_objects_on_line(Y-1, Width, Os),
124
 
    URLSs = resulting_line_spans([LSB|OLSs],Type),
125
 
 
126
 
    % FIXME: Can we keep the list sorted instead of sorting it?
127
 
    % sort descending
128
 
    RLSs = lists:reverse(URLSs),
129
 
 
130
 
    resulting_scanline(RLSs,Width).
131
 
 
132
 
resulting_scanline(RLSs, Width) -> resulting_scanline(RLSs, Width, []).
133
 
resulting_scanline([], _, Scanlines) -> Scanlines;
134
 
resulting_scanline([{_,Xl, Xr, C} | RLSs], Width, Scanlines) ->
135
 
    {R,G,B,_} = rgb_float2byte(C),
136
 
    Scanline = lists:duplicate(trunc(Xr - Xl + 1), <<R:8,G:8,B:8>>),
137
 
    resulting_scanline(RLSs, Width, [Scanline|Scanlines]).
 
128
    OLSs = parse_objects_on_line(Y-1, Width, Os),
 
129
    RLSs = resulting_line_spans([LSB|OLSs],Type),
 
130
    [ lists:duplicate(Xr - Xl + 1, <<(trunc(R*255)):8,(trunc(G*255)):8,(trunc(B*255)):8>>) || {_,Xl, Xr, {R,G,B,_}} <- RLSs ].
138
131
 
139
132
resulting_line_spans(LSs,Type) ->
140
133
    %% Build a list of "transitions" from left to right.
141
134
    Trans = line_spans_to_trans(LSs),
142
135
    %% Convert list of "transitions" to linespans.
143
 
        trans_to_line_spans(Trans,Type).
 
136
    trans_to_line_spans(Trans,Type).
144
137
 
145
138
line_spans_to_trans(LSs) ->
146
139
    line_spans_to_trans(LSs,[],0).
191
184
 
192
185
color([],_) -> {0.0,0.0,0.0,0.0};
193
186
color([{_,C}|_],opaque) -> C;    
194
 
color(Layers,alpha) -> color1({0,0,0,0},Layers).
 
187
color(Layers,alpha) -> color1({0.0,0.0,0.0,0.0},Layers).
195
188
 
196
189
color1(Color,[]) -> Color;
197
 
color1(Color,[{_,C}|Layers]) -> color1(blend(Color,C),Layers).
198
 
 
199
 
blend(C1,C2) -> alpha_blend(C1,C2).
 
190
color1(Color,[{_,C}|Layers]) -> color1(alpha_blend(Color,C),Layers).
200
191
 
201
192
modify_layers(Layers,[]) -> Layers;
202
 
modify_layers(Layers,[{{_,Z,Op},C}|Trans]) ->
203
 
    modify_layers(case Op of
204
 
                      start ->
205
 
                          add_layer(Layers,Z,C);
206
 
                      stop ->
207
 
                          remove_layer(Layers,Z,C)
208
 
                  end,
209
 
                  Trans).
 
193
modify_layers(Layers,[{{_,Z,start},C}|Trans]) ->
 
194
    modify_layers(add_layer(Layers, Z, C), Trans);
 
195
modify_layers(Layers,[{{_,Z,stop },C}|Trans]) ->
 
196
    modify_layers(remove_layer(Layers, Z, C), Trans).
210
197
 
211
198
add_layer([{Z1,_}=H|Layers],Z,C) when Z1 > Z ->
212
199
    [H|add_layer(Layers,Z,C)];
216
203
remove_layer(Layers,Z,C) ->
217
204
    Layers -- [{Z,C}].
218
205
 
219
 
alpha_blend({R1,G1,B1,A1}, {R2,G2,B2,A2}) ->
 
206
alpha_blend({R1,G1,B1,A1}, {R2,G2,B2,A2}) when is_float(A1), is_float(A2)->
220
207
  Beta = A2*(1.0 - A1),
221
208
  A = A1 + Beta,
222
209
  R = R1*A1 + R2*Beta,
232
219
        false ->
233
220
            parse_objects_on_line(Y, Z + 1, Width, Os, Out);
234
221
        true ->
235
 
            OLs = object_line_data(Y, Z, O),
 
222
            OLs  = object_line_data(Y, Z, O),
236
223
            TOLs = trim_object_line_data(OLs, Width),
237
224
            parse_objects_on_line(Y, Z + 1, Width, Os, [TOLs|Out])
238
225
    end.
240
227
trim_object_line_data(OLs, Width) ->
241
228
    trim_object_line_data(OLs, Width, []).
242
229
trim_object_line_data([], _, Out) -> Out;
 
230
 
 
231
trim_object_line_data([{_, Xl, _, _}|OLs], Width, Out) when Xl > Width ->
 
232
    trim_object_line_data(OLs, Width, Out);
 
233
trim_object_line_data([{_, _, Xr, _}|OLs], Width, Out) when Xr < 0 ->
 
234
    trim_object_line_data(OLs, Width, Out);
243
235
trim_object_line_data([{Z, Xl, Xr, C}|OLs], Width, Out) ->
244
 
    if 
245
 
        Xl > Width ->
246
 
            trim_object_line_data(OLs, Width, Out);
247
 
        Xr < 0 ->
248
 
            trim_object_line_data(OLs, Width, Out);
249
 
        true ->
250
 
           trim_object_line_data(OLs, Width, [{Z, lists:max([0,Xl]), lists:min([Xr,Width]), C}|Out])
251
 
    end.
 
236
    trim_object_line_data(OLs, Width, [{Z, erlang:max(0,Xl), erlang:min(Xr,Width), C}|Out]).
252
237
 
253
238
% object_line_data
254
239
% In:
264
249
%       Calculate the length (start and finish index) of an objects horizontal
265
250
%       line given the height index.
266
251
 
267
 
object_line_data(Y, Z, Object) -> object_line_data(Y, Z, Object, Object#image_object.type).
 
252
object_line_data(Y, Z, Object) -> 
 
253
    object_line_data(Y, Z, Object, Object#image_object.type).
268
254
object_line_data(Y, Z, #image_object{ span = {X0, Y0, X1, Y1}, color = C}, rectangle) ->
269
255
    if
270
256
        Y0 =:= Y ; Y1 =:= Y ->
277
263
object_line_data(_Y, Z, #image_object{ span = {X0, _, X1, _}, color = C}, filled_rectangle) ->
278
264
    [{Z, X0, X1, C}];
279
265
 
280
 
object_line_data(Y, Z, #image_object{ span = {X0,Y0,X1,Y1}, color = C}, filled_ellipse) ->
 
266
object_line_data(Y, Z, #image_object{ internals={Xr,Yr,Yr2}, span = {X0,Y0,X1,Y1}, color = C}, filled_ellipse) ->
281
267
    if 
282
 
        X1 - X0 == 0 -> % if the width is exactly one pixel
283
 
            [{Z, X1, X0, C}];
284
 
        X1 - X0 < 0 -> throw(bad_ellipse_width);
285
 
        Y1 - Y0 == 0 -> % Height exactly one pixel, get width
 
268
        X1 - X0 == 0; Y1 - Y0 == 0 ->
286
269
            [{Z, X0, X1, C}];
287
270
        true ->
288
 
            Xr = (X1 - X0)/2,
289
 
            Yr = (Y1 - Y0)/2,
290
 
            Yo = trunc(Y - Y0 - Yr),
 
271
            Yo  = trunc(Y - Y0 - Yr),
291
272
            Yo2 = Yo*Yo,
292
 
            Yr2 = Yr*Yr,
293
 
            Xo = math:sqrt((1 - Yo2/Yr2))*Xr,
 
273
            Xo  = math:sqrt((1 - Yo2/Yr2))*Xr,
294
274
            [{Z, round(X0 - Xo + Xr), round(X0 + Xo + Xr), C}]
295
275
    end;
296
276
 
297
277
object_line_data(Y, Z, #image_object{ intervals = Is, color = C}, filled_triangle) ->
298
 
    case lists:keysearch(Y, 1, Is) of
299
 
        {value, {Y, Xl, Xr}} -> [{Z, Xl, Xr, C}];
 
278
    case lists:keyfind(Y, 1, Is) of
 
279
        {Y, Xl, Xr} -> [{Z, Xl, Xr, C}];
300
280
        false -> []
301
281
    end;    
302
282
 
303
283
object_line_data(Y, Z, #image_object{ intervals = Is, color = C}, line) ->
304
284
    case dict:find(Y, Is) of
305
 
        %{ok, {Xl, Xr}} -> [{Z, Xl, Xr, C}];
306
285
        {ok, Ls} -> [{Z, Xl, Xr, C}||{Xl,Xr} <- Ls];
307
286
        _ -> []
308
287
    end;
309
288
 
310
 
object_line_data(Y, Z, O, polygon) ->
311
 
    Is = lists:filter(
312
 
        fun({Yp,_,_}) ->
313
 
            if Yp == Y -> true; true -> false end
314
 
        end, O#image_object.intervals),
315
 
    [   {Z, Xl, Xr, O#image_object.color} || {_, Xl, Xr} <- Is];
316
 
 
317
 
object_line_data(Y, Z, #image_object{ color = C, intervals = Is }, text_horizontal) ->
318
 
    % FIXME: optimize!
319
 
    lists:foldl(
320
 
        fun ({Yg,Xl,Xr}, Out) ->
321
 
            if 
322
 
                Yg == Y ->
323
 
                    [{Z, Xl, Xr, C}|Out];
324
 
                true ->
325
 
                    Out
326
 
            end
327
 
        end, [], Is);
 
289
object_line_data(Y, Z, #image_object{ color = C, intervals = Is}, polygon) ->
 
290
    [{Z, Xl, Xr, C} || {Yp, Xl, Xr} <- Is, Yp =:= Y];
 
291
 
 
292
object_line_data(Y, Z, #image_object{ color = C, intervals = Is}, text_horizontal) ->
 
293
    [{Z, Xl, Xr, C} || {Yg, Xl, Xr} <- Is, Yg =:= Y];
 
294
 
328
295
object_line_data(_, Z, #image_object{ span = {X0,_,X1,_}, color = C}, _) ->
329
 
    % faked
330
296
    [{Z, X0, X1, C}].
331
297
 
332
 
is_object_on_line(Y, Object) ->
333
 
    is_object_bounds_on_line(Y, Object#image_object.span). 
 
298
is_object_on_line(Y, #image_object{ span = Span }) ->
 
299
    is_object_bounds_on_line(Y, Span). 
334
300
    
335
 
is_object_bounds_on_line(Y, {_,Y0,_,Y1}) ->
336
 
    if 
337
 
        Y < Y0 -> false;
338
 
        Y > Y1 -> false;
339
 
        true -> true
340
 
    end.
341
 
 
342
 
rgb_float2byte({R,G,B,A}) ->
343
 
    {trunc(R*255), trunc(G*255), trunc(B*255), trunc(A*255)}.
 
301
is_object_bounds_on_line(Y, {_,Y0,_,Y1}) when Y < Y0 ; Y > Y1 -> false;
 
302
is_object_bounds_on_line(_, _) -> true.
344
303
 
345
304
%%% primitives to line_spans
346
305
 
360
319
    
361
320
precompile_objects([O = #image_object{ type = polygon, points = Pts } | Os], Out) ->
362
321
    precompile_objects(Os, [O#image_object{ intervals = polygon_ls(Pts) } | Out]);
 
322
 
 
323
precompile_objects([O = #image_object{ type = filled_ellipse, span = {X0,Y0,X1,Y1} } | Os], Out) ->
 
324
    Xr  = (X1 - X0)/2,
 
325
    Yr  = (Y1 - Y0)/2,
 
326
    Yr2 = Yr*Yr,
 
327
    precompile_objects(Os, [ O#image_object{ internals={Xr,Yr,Yr2} } | Out]);
363
328
    
364
329
precompile_objects([O = #image_object{ type = arc, points = [P0,P1], internals = D }| Os], Out) ->
365
330
    Es = egd_primitives:arc_to_edges(P0, P1, D),
579
544
        true -> 1;
580
545
        false -> -1
581
546
    end, 
582
 
    case Steep of
583
 
        false ->
584
 
            line_ls_step_not_steep({X0, X1},Y0, DX, DY, Ystep, Error, X0, []);
585
 
        true -> 
586
 
            line_ls_step_steep({X0, X1},Y0, DX, DY, Ystep, Error, X0, [])
587
 
    end.
588
 
         
 
547
    line_ls_step(X0, X1,Y0, DX, DY, Ystep, Error, X0, Steep, []).
589
548
 
590
549
%% line_ls_step_(not)_steep
591
550
%% In:
594
553
%% Purpose:
595
554
%%      Produce an line_interval for each Yi (Y index)  
596
555
 
597
 
% Iterating the X-axis
598
 
 
599
 
line_ls_step_not_steep({X,X1},Y,Dx,Dy,Ys,E, X0, LSs) when X < X1 ->
600
 
    case E >= 0 of
601
 
        true ->
602
 
            line_ls_step_not_steep({X+1,X1},Y+Ys,Dx,Dy,Ys, E - Dx + Dy, X+1,[{Y,X0,X}|LSs]);
603
 
        false ->
604
 
            line_ls_step_not_steep({X+1,X1},Y,Dx,Dy,Ys, E + Dy, X0, LSs)
605
 
    end;
606
 
line_ls_step_not_steep({X,_},Y,_Dx,_Dy,_Ystep,_E,X0,LSs) ->
607
 
    [{Y,X0,X}|LSs].
608
 
 
609
 
% Iterating the Y-axis
610
 
line_ls_step_steep({X,X1},Y,Dx,Dy,Ystep,E, X0, LSs) when X =< X1 ->
611
 
    case E >= 0 of
612
 
        true ->
613
 
            line_ls_step_steep({X + 1,X1},Y+Ystep,Dx,Dy,Ystep,E - Dx + Dy,X,[{X,Y,Y}|LSs]);
614
 
        false ->
615
 
            line_ls_step_steep({X + 1,X1},Y,Dx,Dy,Ystep,E + Dy,X0, [{X,Y,Y}|LSs])
616
 
    end;
617
 
line_ls_step_steep({_X,_},_Y,_Dx,_Dy,_Ystep,_E,_X0,LSs) -> 
 
556
line_ls_step(X, X1, Y, Dx, Dy, Ys, E, X0, false = Steep, LSs) when X < X1, E >= 0 ->
 
557
    line_ls_step(X+1,X1,Y+Ys,Dx,Dy,Ys, E - Dx + Dy, X+1, Steep, [{Y,X0,X}|LSs]);
 
558
line_ls_step(X, X1, Y, Dx, Dy, Ys, E, X0, false = Steep, LSs) when X < X1 ->
 
559
    line_ls_step(X+1,X1,Y,Dx,Dy,Ys, E + Dy, X0, Steep, LSs);
 
560
line_ls_step(X, _X1, Y, _Dx, _Dy, _Ys, _E, X0, false, LSs) ->
 
561
    [{Y,X0,X}|LSs];
 
562
line_ls_step(X, X1, Y, Dx, Dy, Ys, E, _X0, true = Steep, LSs) when X =< X1, E >= 0 ->
 
563
    line_ls_step(X+1,X1,Y+Ys,Dx,Dy,Ys, E - Dx + Dy, X, Steep, [{X,Y,Y}|LSs]);
 
564
line_ls_step(X, X1, Y, Dx, Dy, Ys, E, X0, true = Steep, LSs) when X =< X1 ->
 
565
    line_ls_step(X+1,X1,Y,Dx,Dy,Ys,E + Dy, X0, Steep, [{X,Y,Y}|LSs]);
 
566
line_ls_step(_X,_,_Y,_Dx,_Dy,_Ys,_E,_X0,_,LSs) -> 
618
567
    LSs.
619
568
 
620
569
% Text
707
656
 
708
657
eps_footer() -> 
709
658
    "%%EOF\n".
 
659