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

« back to all changes in this revision

Viewing changes to lib/percept/src/percept_image.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:
58
58
 
59
59
graf1(Width, Height, {Xmin, Ymin, Xmax, Ymax}, Data) ->
60
60
    
61
 
    %% Calculate areas
 
61
    %z Calculate areas
62
62
    HO = 20,
63
 
    GrafArea = #graph_area{x = HO, y = 4, width = Width - 2*HO, height = Height - 17},
 
63
    GrafArea   = #graph_area{x = HO, y = 4, width = Width - 2*HO, height = Height - 17},
64
64
    XticksArea = #graph_area{x = HO, y = Height - 13, width = Width - 2*HO, height = 13},
65
 
    YticksArea = #graph_area{x = 1, y = 4, width = HO, height = Height - 17},
 
65
    YticksArea = #graph_area{x = 1,  y = 4, width = HO, height = Height - 17},
66
66
    
67
67
    %% Initiate Image
68
68
 
69
69
    Image = egd:create(Width, Height),
70
 
   
71
70
 
72
71
    %% Set colors
73
72
    
91
90
%% Color, {ForegroundColor, ProcFillColor, PortFillColor}
92
91
%% DataBounds, {Xmin, Ymin, Xmax, Ymax}
93
92
 
94
 
draw_graf(Gif, [{SX,SY1,SY2}|Data], Colors, GraphArea, {Xmin, _Ymin, Xmax, Ymax}) ->
 
93
draw_graf(Im, [{SX,SY1,SY2}|Data], Colors, GraphArea, {Xmin, _Ymin, Xmax, Ymax}) ->
95
94
    
96
 
    #graph_area{x = X0, y = Y0, width = Width, height = Height} = GraphArea,
97
 
    {Black, ProcColor, PortColor} = Colors,
 
95
    #graph_area{width = Width, height = Height} = GraphArea,
98
96
 
99
97
    DX = (Width)/(Xmax - Xmin),
100
98
    DY = (Height)/(Ymax),
101
99
    
102
 
    lists:foldl( 
103
 
        fun ({X,Y1,Y2}, {PX, PY}) ->
104
 
            NX1 = trunc(X0 + PX*DX - Xmin*DX),
105
 
            NX2 = trunc(X0 + X*DX - Xmin*DX),
106
 
            if 
107
 
                abs(trunc(NX1) - trunc(NX2)) > 0 ->
108
 
                    NY1 = trunc(Y0 + Height - PY*DY),
109
 
                    NY2 = trunc(Y0 + Height - Y1*DY),
110
 
                    NY3 = trunc(Y0 + Height - (Y2 + Y1)*DY),
111
 
 
112
 
                    ZLY = trunc(Y0 + Height),
113
 
            
114
 
                    % Fill procs
115
 
                    egd:filledRectangle(
116
 
                        Gif,
117
 
                        {NX1,ZLY},
118
 
                        {NX2,NY2},
119
 
                        ProcColor),
120
 
            
121
 
                    % fill ports
122
 
                    egd:filledRectangle(
123
 
                        Gif,
124
 
                        {NX1,NY2},
125
 
                        {NX2,NY3},
126
 
                        PortColor),
127
 
                    % top line
128
 
                    egd:line(
129
 
                        Gif,
130
 
                        {NX1,NY3},
131
 
                        {NX2,NY3},
132
 
                        Black),
133
 
                    % left line
134
 
                    egd:line(
135
 
                        Gif,
136
 
                        {NX1,NY1},
137
 
                        {NX1,NY3},
138
 
                        Black),
139
 
                    {X, Y1 + Y2};
140
 
                true ->
141
 
                    {PX,PY}
142
 
            end
143
 
        end, {SX, SY2 + SY1}, Data).
 
100
    draw_graf0(Im, Data, Colors, Xmin, GraphArea, DX, DY, SX, SY1 + SY2).
 
101
 
 
102
draw_graf0(_, [], _, _, _, _, _, _, _) -> ok;
 
103
draw_graf0(Im, [{X,Y1,Y2}|Data], {B, PrC, PoC}, Xmin, GraphArea, DX, DY, PX, PY) ->
 
104
    #graph_area{x = X0, y = Y0, height = Height} = GraphArea,
 
105
    NX1 = trunc(X0 + PX*DX - Xmin*DX),
 
106
    NX2 = trunc(X0 + X*DX - Xmin*DX),
 
107
    {OX,OY} = if 
 
108
        abs(trunc(NX1) - trunc(NX2)) > 0 ->
 
109
            NY1 = trunc(Y0 + Height - PY*DY),
 
110
            NY2 = trunc(Y0 + Height - Y1*DY),
 
111
            NY3 = trunc(Y0 + Height - (Y2 + Y1)*DY),
 
112
 
 
113
            ZLY = trunc(Y0 + Height),
 
114
    
 
115
            % Fill procs
 
116
            egd:filledRectangle(
 
117
                Im,
 
118
                {NX1,ZLY},
 
119
                {NX2,NY2},
 
120
                PrC),
 
121
    
 
122
            % fill ports
 
123
            egd:filledRectangle(
 
124
                Im,
 
125
                {NX1,NY2},
 
126
                {NX2,NY3},
 
127
                PoC),
 
128
            % top line
 
129
            egd:line(
 
130
                Im,
 
131
                {NX1,NY3},
 
132
                {NX2,NY3},
 
133
                B),
 
134
            % left line
 
135
            egd:line(
 
136
                Im,
 
137
                {NX1,NY1},
 
138
                {NX1,NY3},
 
139
                B),
 
140
            {X, Y1 + Y2};
 
141
        true ->
 
142
            {PX,PY}
 
143
    end,
 
144
    draw_graf0(Im, Data, {B, PrC, PoC}, Xmin, GraphArea, DX, DY, OX, OY).
144
145
 
145
146
draw_xticks(Image, Color, XticksArea, {Xmin, Xmax}, Data) ->
146
147
    #graph_area{x = X0, y = Y0, width = Width} = XticksArea,
178
179
            end
179
180
        end, 0, Data).
180
181
 
181
 
draw_yticks(Gif, Color, YticksArea, {_, Ymax}) ->
182
 
    #graph_area{x = X0, y = Y0, width = Width, height = Height} = YticksArea,
183
 
    DY = (Height)/(Ymax),
184
 
    Ys = lists:seq(0, trunc(Ymax)),
 
182
draw_yticks(Im, Color, TickArea, {_,Ymax}) ->
 
183
    #graph_area{x = X0, y = Y0, width = Width, height = Height} = TickArea,
 
184
    Font = load_font(),
185
185
    X = trunc(X0 + Width),
186
 
    Font = load_font(),
187
 
    egd:filledRectangle(Gif, {X, trunc(0 + Y0)}, {X, trunc(Y0 + Height)}, Color),
188
 
    lists:foreach(
189
 
        fun (Y) ->
190
 
            Y1 = trunc(Y0 + Height -  Y*DY),
191
 
            egd:filledRectangle(Gif, {X - 3, Y1}, {X + 3, Y1}, Color), 
192
 
            Text = lists:flatten(io_lib:format("~p", [Y])),
193
 
            text(Gif, {0, Y1 - 4}, Font, Text, Color)
194
 
        end, Ys).
 
186
    Dy = (Height)/(Ymax),
 
187
    Yts = if 
 
188
        Height/(Ymax*12) < 1.0 -> round(1 + Ymax*15/Height);
 
189
        true -> 1
 
190
    end,
 
191
    egd:filledRectangle(Im, {X, trunc(0 + Y0)}, {X, trunc(Y0 + Height)}, Color),
 
192
    draw_yticks0(Im, Font, Color, 0, Yts, Ymax, {X, Height, Dy}).
 
193
 
 
194
draw_yticks0(Im, Font, Color, Yi, Yts, Ymax, Area) when Yi < Ymax -> 
 
195
    {X, Height, Dy} = Area, 
 
196
    Y = round(Height - (Yi*Dy) + 3),
 
197
 
 
198
    egd:filledRectangle(Im, {X - 3, Y}, {X + 3, Y}, Color), 
 
199
    Text = lists:flatten(io_lib:format("~p", [Yi])),
 
200
    text(Im, {0, Y - 4}, Font, Text, Color),
 
201
    draw_yticks0(Im, Font, Color, Yi + Yts, Yts, Ymax, Area);
 
202
draw_yticks0(_, _, _, _, _, _, _) -> ok.
195
203
 
196
204
%%% -------------------------------------
197
205
%%% ACTIVITIES