~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
33
33
 
34
34
graph(SessionID, Env, Input) ->
35
35
    mod_esi:deliver(SessionID, header()),
36
 
    case graph(Env,Input) of
37
 
        Binaries when is_list(Binaries) ->
38
 
            lists:foreach(fun (B) ->
39
 
                mod_esi:deliver(SessionID, binary_to_list(B))
40
 
            end, Binaries);
41
 
        Binary ->
42
 
            mod_esi:deliver(SessionID, binary_to_list(Binary))
43
 
    end.
44
 
 
 
36
    mod_esi:deliver(SessionID, binary_to_list(graph(Env, Input))).
 
37
 
45
38
%% activity
46
39
%% @spec activity(SessionID, Env, Input) -> term() 
47
40
%% @doc An ESI callback implementation used by the httpd server.
48
41
 
49
42
activity(SessionID, Env, Input) ->
50
43
    mod_esi:deliver(SessionID, header()),
51
 
    case activity_bar(Env,Input) of
52
 
        Binaries when is_list(Binaries) ->
53
 
            lists:foreach(fun (B) ->
54
 
                mod_esi:deliver(SessionID, binary_to_list(B))
55
 
            end, Binaries);
56
 
        Binary ->
57
 
            mod_esi:deliver(SessionID, binary_to_list(Binary))
58
 
    end.
 
44
    mod_esi:deliver(SessionID, binary_to_list(activity_bar(Env, Input))).
59
45
 
60
46
proc_lifetime(SessionID, Env, Input) ->
61
47
    mod_esi:deliver(SessionID, header()),
62
 
    case proc_lifetime(Env,Input) of
63
 
        Binaries when is_list(Binaries) ->
64
 
            lists:foreach(fun (B) ->
65
 
                mod_esi:deliver(SessionID, binary_to_list(B))
66
 
            end, Binaries);
67
 
        Binary ->
68
 
            mod_esi:deliver(SessionID, binary_to_list(Binary))
69
 
    end.
 
48
    mod_esi:deliver(SessionID, binary_to_list(proc_lifetime(Env, Input))).
70
49
 
71
50
percentage(SessionID, Env, Input) ->
72
51
    mod_esi:deliver(SessionID, header()),
73
 
    case percentage(Env,Input) of
74
 
        Binaries when is_list(Binaries) ->
75
 
            lists:foreach(fun (B) ->
76
 
                mod_esi:deliver(SessionID, binary_to_list(B))
77
 
            end, Binaries);
78
 
        Binary ->
79
 
            mod_esi:deliver(SessionID, binary_to_list(Binary))
80
 
    end.
 
52
    mod_esi:deliver(SessionID, binary_to_list(percentage(Env,Input))).
81
53
 
82
54
scheduler_graph(SessionID, Env, Input) ->
83
55
    mod_esi:deliver(SessionID, header()),
84
 
    case scheduler_graph(Env,Input) of
85
 
        Binaries when is_list(Binaries) ->
86
 
            lists:foreach(fun (B) ->
87
 
                mod_esi:deliver(SessionID, binary_to_list(B))
88
 
            end, Binaries);
89
 
        Binary ->
90
 
            mod_esi:deliver(SessionID, binary_to_list(Binary))
91
 
    end.
 
56
    mod_esi:deliver(SessionID, binary_to_list(scheduler_graph(Env, Input))).
92
57
 
93
58
graph(_Env, Input) ->
94
59
    Query = httpd:parse_query(Input),
95
60
   
96
61
    RangeMin = percept_html:get_option_value("range_min", Query),
97
62
    RangeMax = percept_html:get_option_value("range_max", Query),
98
 
    Pids = percept_html:get_option_value("pids", Query),
99
 
    Width = percept_html:get_option_value("width", Query),
100
 
    Height = percept_html:get_option_value("height", Query),
 
63
    Pids     = percept_html:get_option_value("pids", Query),
 
64
    Width    = percept_html:get_option_value("width", Query),
 
65
    Height   = percept_html:get_option_value("height", Query),
101
66
    
102
67
    % Convert Pids to id option list
103
 
    IDs = [ {id, ID} || ID <- Pids],
 
68
    IDs      = [ {id, ID} || ID <- Pids],
104
69
   
105
70
    % seconds2ts
106
 
    StartTs = percept_db:select({system, start_ts}),
107
 
    TsMin = percept_analyzer:seconds2ts(RangeMin, StartTs),
108
 
    TsMax = percept_analyzer:seconds2ts(RangeMax, StartTs),
 
71
    StartTs  = percept_db:select({system, start_ts}),
 
72
    TsMin    = percept_analyzer:seconds2ts(RangeMin, StartTs),
 
73
    TsMax    = percept_analyzer:seconds2ts(RangeMax, StartTs),
109
74
    
110
 
    Options = [{ts_exact, true},{ts_min, TsMin},{ts_max, TsMax} | IDs],
 
75
    Options  = [{ts_exact, true},{ts_min, TsMin},{ts_max, TsMax} | IDs],
111
76
    
112
77
    Activities = percept_db:select({activity, Options}),
113
78
    
114
 
    Counts = percept_analyzer:activities2count(Activities, StartTs),
115
 
    
 
79
    Counts   = percept_analyzer:activities2count(Activities, StartTs),
 
80
 
116
81
    percept_image:graph(Width, Height,Counts).
117
82
 
118
83
scheduler_graph(_Env, Input) -> 
165
130
    percept_image:percentage(round(Width), round(Height), float(Percentage)).
166
131
 
167
132
header() ->
168
 
    "Content-Type: image/jpeg\r\n\r\n".
 
133
    "Content-Type: image/png\r\n\r\n".