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

« back to all changes in this revision

Viewing changes to lib/snmp/src/misc/snmp_verbosity.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id$
 
17
%%
 
18
-module(snmp_verbosity).
 
19
 
 
20
-include_lib("stdlib/include/erl_compile.hrl").
 
21
 
 
22
-export([print/4,print/5,printc/4,validate/1]).
 
23
 
 
24
-export([process_args/2]).
 
25
 
 
26
print(silence,_Severity,_Format,_Arguments) ->
 
27
    ok;
 
28
print(Verbosity,Severity,Format,Arguments) ->
 
29
    print1(printable(Verbosity,Severity),Format,Arguments).
 
30
 
 
31
 
 
32
print(silence,_Severity,_Module,_Format,_Arguments) ->
 
33
    ok;
 
34
print(Verbosity,Severity,Module,Format,Arguments) ->
 
35
    print1(printable(Verbosity,Severity),Module,Format,Arguments).
 
36
 
 
37
 
 
38
printc(silence,_Severity,_Format,_Arguments) ->
 
39
    ok;
 
40
printc(Verbosity,Severity,Format,Arguments) ->
 
41
    print2(printable(Verbosity,Severity),Format,Arguments).
 
42
 
 
43
 
 
44
print1(false,_Format,_Arguments) -> ok;
 
45
print1(Verbosity,Format,Arguments) ->
 
46
    V = image_of_verbosity(Verbosity),
 
47
    S = image_of_sname(get(sname)),
 
48
    A = process_args(Arguments, []),
 
49
    (catch io:format("*** [~s] SNMP ~s ~s *** ~n" 
 
50
                     "   " ++ Format ++ "~n",
 
51
                     [timestamp(), S, V | A])).
 
52
 
 
53
print1(false,_Module,_Format,_Arguments) -> ok;
 
54
print1(Verbosity,Module,Format,Arguments) ->
 
55
    V = image_of_verbosity(Verbosity),
 
56
    S = image_of_sname(get(sname)),
 
57
    A = process_args(Arguments, []),
 
58
    (catch io:format("*** [~s] SNMP ~s ~s ~s *** ~n" 
 
59
                     "   " ++ Format ++ "~n",
 
60
                     [timestamp(), S, Module, V | A])).
 
61
 
 
62
 
 
63
print2(false,_Format,_Arguments) -> ok;
 
64
print2(_Verbosity,Format,Arguments) ->
 
65
    A = process_args(Arguments, []),
 
66
    (catch io:format(Format ++ "~n",A)).
 
67
 
 
68
 
 
69
timestamp() ->
 
70
    format_timestamp(now()).
 
71
 
 
72
format_timestamp({_N1, _N2, N3} = Now) ->
 
73
    {Date, Time}   = calendar:now_to_datetime(Now),
 
74
    {YYYY,MM,DD}   = Date,
 
75
    {Hour,Min,Sec} = Time,
 
76
    FormatDate =
 
77
        io_lib:format("~.4w:~.2.0w:~.2.0w ~.2.0w:~.2.0w:~.2.0w 4~w",
 
78
                      [YYYY,MM,DD,Hour,Min,Sec,round(N3/1000)]),
 
79
    lists:flatten(FormatDate).
 
80
 
 
81
process_args([], Acc) ->
 
82
    lists:reverse(Acc);
 
83
process_args([{vapply, {M,F,A}}|T], Acc) when atom(M), atom(F), list(A) ->
 
84
    process_args(T, [(catch apply(M,F,A))|Acc]);
 
85
process_args([H|T], Acc) ->
 
86
    process_args(T, [H|Acc]).
 
87
 
 
88
 
 
89
%% printable(Verbosity,Severity)
 
90
printable(info,info)      -> info;
 
91
printable(log,info)       -> info;
 
92
printable(log,log)        -> log;
 
93
printable(debug,info)     -> info;
 
94
printable(debug,log)      -> log;
 
95
printable(debug,debug)    -> debug;
 
96
printable(trace,V)        -> V;
 
97
printable(_Verb,_Sev)     -> false.
 
98
 
 
99
 
 
100
image_of_verbosity(info)  -> "INFO";
 
101
image_of_verbosity(log)   -> "LOG";
 
102
image_of_verbosity(debug) -> "DEBUG";
 
103
image_of_verbosity(trace) -> "TRACE";
 
104
image_of_verbosity(_)     -> "".
 
105
 
 
106
%% ShortName
 
107
image_of_sname(ma)        -> "MASTER-AGENT";
 
108
image_of_sname(maw)       -> io_lib:format("MASTER-AGENT-worker(~p)",[self()]);
 
109
image_of_sname(mais)      -> io_lib:format("MASTER-AGENT-inform_sender(~p)",
 
110
                                           [self()]);
 
111
image_of_sname(mats)      -> io_lib:format("MASTER-AGENT-trap_sender(~p)",
 
112
                                           [self()]);
 
113
image_of_sname(maph)      -> io_lib:format("MASTER-AGENT-pdu_handler(~p)",
 
114
                                           [self()]);
 
115
image_of_sname(sa)        -> "SUB-AGENT";
 
116
image_of_sname(saw)       -> io_lib:format("SUB-AGENT-worker(~p)",[self()]);
 
117
image_of_sname(sais)      -> io_lib:format("SUB-AGENT-inform_sender(~p)",
 
118
                                           [self()]);
 
119
image_of_sname(sats)      -> io_lib:format("SUB-AGENT-trap_sender(~p)",
 
120
                                           [self()]);
 
121
image_of_sname(saph)      -> io_lib:format("SUB-AGENT-pdu_handler(~p)",
 
122
                                           [self()]);
 
123
image_of_sname(nif)       -> "A-NET-IF";
 
124
image_of_sname(ldb)       -> "A-LOCAL-DB";
 
125
image_of_sname(ns)        -> "A-NOTE-STORE";
 
126
image_of_sname(ss)        -> "A-SYMBOLIC-STORE";
 
127
image_of_sname(asup)      -> "A-SUPERVISOR";
 
128
image_of_sname(ms)        -> "A-MIB-SERVER";
 
129
image_of_sname(conf)      -> "A-CONF";
 
130
 
 
131
image_of_sname(abs)       -> "A-BKP";
 
132
image_of_sname(albs)      -> "A-LDB-BKP";
 
133
image_of_sname(ambs)      -> "A-MS-BKP";
 
134
image_of_sname(asbs)      -> "A-SS-BKP";
 
135
image_of_sname(mcbs)      -> "M-C-BKP";
 
136
 
 
137
image_of_sname(mse)       -> "M-SERVER";
 
138
image_of_sname(msew)      -> io_lib:format("M-SERVER-worker(~p)", [self()]);
 
139
image_of_sname(mns)       -> "M-NOTE-STORE";
 
140
image_of_sname(mnif)      -> "M-NET-IF";
 
141
image_of_sname(mconf)     -> "M-CONF";
 
142
 
 
143
image_of_sname(mgr)       -> "MGR";
 
144
image_of_sname(mgr_misc)  -> "MGR_MISC";
 
145
 
 
146
image_of_sname(undefined) -> "";
 
147
image_of_sname(V)         -> lists:flatten(io_lib:format("~p",[V])).
 
148
 
 
149
 
 
150
validate(info)  -> info;
 
151
validate(log)   -> log;
 
152
validate(debug) -> debug;
 
153
validate(trace) -> trace;
 
154
validate(_)     -> silence.
 
155