-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathlogging.erl
executable file
·153 lines (130 loc) · 4.19 KB
/
logging.erl
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
-module(logging).
-compile(export_all).
% Read File to List Alternate
readfile(FileName) ->
{ok, Binary} = file:read_file(FileName),
string:tokens(erlang:binary_to_list(Binary), "\n").
% Get the list of Users with their Status.
get_users(List) ->
get_users(List, []).
get_users([First | Rest], Users) ->
User = list_to_atom(get_node_value(First, "USER:")),
Status = list_to_atom(get_node_value(First, "STATUS:")),
get_users(Rest, Users ++ [{User, Status}]);
get_users([], Users) ->
Users.
% Get the list of Buddies filtered by the status.
get_buddies(List, Status) ->
get_buddies(List, Status, []).
get_buddies([First | Rest], Status, Users) ->
{UserId, UserStatus} = First,
case Status == UserStatus of
true ->
get_buddies(Status, Rest, Users ++ [UserId]);
false ->
get_buddies(Status, Rest, Users)
end;
get_buddies([], _, Users) ->
Users.
% Get the Per User Activity
get_per_user_activity(List) ->
get_per_user_activity(List, []).
get_per_user_activity([First | Rest], UserActivities) ->
get_per_user_activity(Rest, assemble_per_user_activity(UserActivities, First));
get_per_user_activity([], UserActivities) ->
UserActivities.
% Assemble Per User Activity
assemble_per_user_activity(UserActivities, Line) ->
UserId = list_to_atom(get_node_value(Line, "FROM:")),
Type = list_to_atom(get_node_value(Line, "TYPE:")),
FoundUserId = find_key(UserActivities, UserId),
case FoundUserId == [] of
true ->
UserActivities ++ [[UserId, [{Type, 1}]]];
false ->
[_ | RestActivities] = FoundUserId,
[Activities | _] = RestActivities,
FoundType = find_key(Activities, Type),
case FoundType == [] of
true ->
replace_key(UserActivities, UserId, Activities ++ [{Type, 1}]);
false ->
replace_key(UserActivities, UserId, increment_key(Activities, Type, 1))
end
end.
% Get Statistics
get_statistics(List) ->
get_statistics(List, []).
get_statistics([First | Rest], Statistics) ->
get_statistics(Rest, increment_key(Statistics, get_timestamp(First), 1));
get_statistics([], Statistics) ->
Statistics.
% Increment Key
increment_key(List, Key, Count) ->
FindKey = find_key(List, Key),
case FindKey == [] of
true ->
List ++ [{Key, Count}];
false ->
{_, PrevCount} = FindKey,
replace_key(List, Key, (PrevCount + Count), [])
end.
% Replace Key
replace_key(List, KeyFilter, ValueFilter) ->
replace_key(List, KeyFilter, ValueFilter, []).
replace_key([First | Rest], KeyFilter, ValueFilter, NewList) ->
KeyPairCandidate = First,
case is_tuple(KeyPairCandidate) of
true ->
{KeyCurrent, ValueCurrent} = KeyPairCandidate,
case KeyFilter == KeyCurrent of
true ->
replace_key(Rest, KeyFilter, ValueFilter, NewList ++ [{KeyFilter, ValueFilter}]);
false ->
replace_key(Rest, KeyFilter, ValueFilter, NewList ++ [{KeyCurrent, ValueCurrent}])
end;
false ->
[KeyCurrent | _] = KeyPairCandidate,
case KeyFilter == KeyCurrent of
true ->
replace_key(Rest, KeyFilter, ValueFilter, NewList ++ [[KeyFilter, ValueFilter]]);
false ->
replace_key(Rest, KeyFilter, ValueFilter, NewList ++ [First])
end
end;
replace_key([], _, _, NewList) ->
NewList.
% Find Key in the List, return the Key if found.
find_key([First | Rest], KeyNeedle) ->
KeyPairCandidate = First,
case is_tuple(KeyPairCandidate) of
true ->
{KeyCurrent, _} = KeyPairCandidate;
false ->
[KeyCurrent | _] = KeyPairCandidate
end,
case KeyCurrent == KeyNeedle of
true -> KeyPairCandidate;
false -> find_key(Rest, KeyNeedle)
end;
% Just return a blank list if the key is not found.
find_key([], _) ->
[].
% Get the Node Value
get_node_value(Line, Node) ->
NodeStartToken = string:str(Line, Node),
NodeRemString = string:sub_string(Line, NodeStartToken),
ValueStartToken = string:str(NodeRemString, ":") + 1,
BlankToken = string:str(NodeRemString, " "),
ValueEndToken = if %string:str(NodeRemString, " ") - 1,
BlankToken > 0 ->
BlankToken - 1;
true ->
string:len(NodeRemString)
end,
string:sub_string(NodeRemString, ValueStartToken, ValueEndToken).
% Get the Session Time Value
get_timestamp(Line) ->
SquareBracketStart = string:str(Line, "[") + 1,
SquareBracketEnd = string:str(Line, "]") -1,
string:sub_string(Line, SquareBracketStart, SquareBracketEnd).